OpenCores
URL https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk

Subversion Repositories openrisc_me

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [graphite/] [pr42050.f90] - Blame information for rev 302

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 302 jeremybenn
! { dg-options "-O2 -fgraphite-identity " }
2
 
3
MODULE qs_ks_methods
4
  INTEGER, PARAMETER :: sic_list_all=1
5
  TYPE dft_control_type
6
     INTEGER :: sic_list_id
7
  END TYPE
8
CONTAINS
9
  SUBROUTINE sic_explicit_orbitals( )
10
    TYPE(dft_control_type), POINTER          :: dft_control
11
    INTEGER, ALLOCATABLE, DIMENSION(:, :)    :: sic_orbital_list
12
    INTEGER, DIMENSION(:), &
13
      POINTER                                :: mo_derivs
14
    SELECT CASE(dft_control%sic_list_id)
15
    CASE(sic_list_all)
16
      DO i=1,k_alpha
17
         IF (SIZE(mo_derivs,1)==1) THEN
18
         ELSE
19
             sic_orbital_list(3,iorb)=2
20
         ENDIF
21
      ENDDO
22
    END SELECT
23
    CALL test()
24
  END SUBROUTINE sic_explicit_orbitals
25
END MODULE qs_ks_methods

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.