nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / use_18.f90
blob7975acd23e6e6d83371da753432f8073c65c9ac1
1 ! { dg-do compile }
3 ! PR fortran/51816
5 ! Contributed by Harald Anlauf
7 module foo
8 implicit none
9 type t
10 integer :: i
11 end type t
12 interface operator (*)
13 module procedure mult
14 end interface
15 contains
16 function mult (i, j)
17 type(t), intent(in) :: i, j
18 integer :: mult
19 mult = i%i * j%i
20 end function mult
21 end module foo
23 module bar
24 implicit none
25 type t2
26 integer :: i
27 end type t2
28 interface operator (>)
29 module procedure gt
30 end interface
31 contains
32 function gt (i, j)
33 type(t2), intent(in) :: i, j
34 logical :: gt
35 gt = i%i > j%i
36 end function gt
37 end module bar
39 use bar, only : t2, operator(>) , operator(>)
40 use foo, only : t
41 use foo, only : operator (*)
42 use foo, only : t
43 use foo, only : operator (*)
44 implicit none
45 type(t) :: i = t(1), j = t(2)
46 type(t2) :: k = t2(1), l = t2(2)
47 print *, i*j
48 print *, k > l
49 end