• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1! RUN: %S/test_modfile.sh %s %t %f18
2module m
3  integer(8), parameter :: a = 1, b = 2_8
4  parameter(n=3,l=-3,e=1.0/3.0)
5  real :: x(a:2*(a+b*n)-1)
6  real, dimension(8) :: y
7  type t(c, d)
8    integer, kind :: c = 1
9    integer, len :: d = a + b
10  end type
11  type(t(a+3,:)), allocatable :: z
12  class(t(a+4,:)), allocatable :: z2
13  class(*), allocatable :: z4
14  real*2 :: f
15  complex*32 :: g
16  type t2(i, j, h)
17    integer, len :: h
18    integer, kind :: j
19    integer, len :: i
20  end type
21contains
22  subroutine foo(x)
23    real :: x(2:)
24  end
25  subroutine bar(x)
26    real :: x(..)
27  end
28  subroutine baz(x)
29    type(*) :: x
30  end
31end
32
33!Expect: m.mod
34!module m
35!  integer(8),parameter::a=1_8
36!  integer(8),parameter::b=2_8
37!  integer(4),parameter::n=3_4
38!  integer(4),parameter::l=-3_4
39!  real(4),parameter::e=3.333333432674407958984375e-1_4
40!  real(4)::x(1_8:13_8)
41!  real(4)::y(1_8:8_8)
42!  type::t(c,d)
43!    integer(4),kind::c=1_4
44!    integer(4),len::d=3_4
45!  end type
46!  type(t(c=4_4,d=:)),allocatable::z
47!  class(t(c=5_4,d=:)),allocatable::z2
48!  class(*),allocatable::z4
49!  real(2)::f
50!  complex(16)::g
51!  type::t2(i,j,h)
52!    integer(4),len::h
53!    integer(4),kind::j
54!    integer(4),len::i
55!  end type
56!contains
57!  subroutine foo(x)
58!    real(4)::x(2_8:)
59!  end
60!  subroutine bar(x)
61!    real(4)::x(..)
62!  end
63!  subroutine baz(x)
64!    type(*)::x
65!  end
66!end
67