OSDN Git Service

2005-01-11 Paul Thomas <pault@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / char_result_11.f90
1 ! { dg-do compile }
2 ! PR 23675: Character function of module variable length
3 module cutils
4
5     implicit none
6     private
7    
8     type t
9         integer :: k = 25
10         integer :: kk(3) = (/30, 40, 50 /)
11     end type t
12
13     integer :: m1 = 25, m2 = 25, m3 = 25, m4 = 25, m5 = 25
14     integer :: n1 = 3, n2 = 3, n3 = 3, n4 = 3, n5 = 3, n6 = 3, n7 = 3, n8 = 3, n9 = 3
15     character(10) :: s = "abcdefghij"
16     integer :: x(4) = (/ 30, 40, 50, 60 /)
17     type(t) :: tt1(5), tt2(5)
18
19     public :: IntToChar1, IntToChar2, IntToChar3, IntToChar4, IntToChar5, &
20                 IntToChar6, IntToChar7, IntToChar8
21
22 contains
23
24     pure integer function get_k(tt)
25         type(t), intent(in) :: tt
26
27         get_k = tt%k
28     end function get_k
29  
30     function IntToChar1(integerValue) result(a)
31         integer, intent(in) :: integerValue
32         character(len=m1)  :: a
33  
34         write(a, *) integerValue
35     end function IntToChar1
36  
37     function IntToChar2(integerValue) result(a)
38         integer, intent(in) :: integerValue
39         character(len=m2+n1)  :: a
40  
41         write(a, *) integerValue
42     end function IntToChar2
43  
44     function IntToChar3(integerValue) result(a)
45         integer, intent(in) :: integerValue
46         character(len=iachar(s(n2:n3)))  :: a
47  
48         write(a, *) integerValue
49     end function IntToChar3
50  
51     function IntToChar4(integerValue) result(a)
52         integer, intent(in) :: integerValue
53         character(len=tt1(n4)%k)  :: a
54  
55         write(a, *) integerValue
56     end function IntToChar4
57  
58     function IntToChar5(integerValue) result(a)
59         integer, intent(in) :: integerValue
60         character(len=maxval((/m3, n5/)))  :: a
61  
62         write(a, *) integerValue
63     end function IntToChar5
64  
65     function IntToChar6(integerValue) result(a)
66         integer, intent(in) :: integerValue
67         character(len=x(n6))  :: a
68  
69         write(a, *) integerValue
70     end function IntToChar6
71  
72     function IntToChar7(integerValue) result(a)
73         integer, intent(in) :: integerValue
74         character(len=tt2(min(m4, n7, 2))%kk(n8))  :: a
75      
76         write(a, *) integerValue
77     end function IntToChar7
78  
79     function IntToChar8(integerValue) result(a)
80         integer, intent(in) :: integerValue
81         character(len=get_k(t(m5, (/31, n9, 53/))))  :: a
82  
83         write(a, *) integerValue
84     end function IntToChar8
85
86 end module cutils
87
88
89 program test
90
91     use cutils
92
93     implicit none
94     character(25) :: str
95     
96     str = IntToChar1(3)
97     print *, str
98     str = IntToChar2(3)
99     print *, str
100     str = IntToChar3(3)
101     print *, str
102     str = IntToChar4(3)
103     print *, str
104     str = IntToChar5(3)
105     print *, str
106     str = IntToChar6(3)
107     print *, str
108     str = IntToChar7(3)
109     print *, str
110     str = IntToChar8(3)
111     print *, str
112
113 end program test