aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/char_result_11.f90
blob: c37b20eb75aeffb60a0236c761d2fb282fb46156 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
! { dg-do link }
! PR 23675: Character function of module-variable length
! PR 25716: Implicit kind conversions in in expressions written to *.mod-files.
module cutils

    implicit none
    private
   
    type t
        integer :: k = 25
        integer :: kk(3) = (/30, 40, 50 /)
    end type t

    integer :: m1 = 25, m2 = 25, m3 = 25, m4 = 25, m5 = 25
    integer :: n5 = 3, n7 = 3, n9 = 3
    integer(1) :: n1 = 3, n2 = 3, n3 = 3, n4 = 3, n6 = 3, n8 = 3
    character(10) :: s = "abcdefghij"
    integer :: x(4) = (/ 30, 40, 50, 60 /)
    type(t), save :: tt1(5), tt2(5)

    public :: IntToChar1, IntToChar2, IntToChar3, IntToChar4, IntToChar5, &
                IntToChar6, IntToChar7, IntToChar8

contains

    pure integer function get_k(tt)
        type(t), intent(in) :: tt

        get_k = tt%k
    end function get_k
 
    function IntToChar1(integerValue) result(a)
        integer, intent(in) :: integerValue
        character(len=m1)  :: a
 
        write(a, *) integerValue
    end function IntToChar1
 
    function IntToChar2(integerValue) result(a)
        integer, intent(in) :: integerValue
        character(len=m2+n1)  :: a
 
        write(a, *) integerValue
    end function IntToChar2
 
    function IntToChar3(integerValue) result(a)
        integer, intent(in) :: integerValue
        character(len=iachar(s(n2:n3)))  :: a
 
        write(a, *) integerValue
    end function IntToChar3
 
    function IntToChar4(integerValue) result(a)
        integer, intent(in) :: integerValue
        character(len=tt1(n4)%k)  :: a
 
        write(a, *) integerValue
    end function IntToChar4
 
    function IntToChar5(integerValue) result(a)
        integer, intent(in) :: integerValue
        character(len=maxval((/m3, n5/)))  :: a
 
        write(a, *) integerValue
    end function IntToChar5
 
    function IntToChar6(integerValue) result(a)
        integer, intent(in) :: integerValue
        character(len=x(n6))  :: a
 
        write(a, *) integerValue
    end function IntToChar6
 
    function IntToChar7(integerValue) result(a)
        integer, intent(in) :: integerValue
        character(len=tt2(min(m4, n7, 2))%kk(n8))  :: a
     
        write(a, *) integerValue
    end function IntToChar7
 
    function IntToChar8(integerValue) result(a)
        integer, intent(in) :: integerValue
        character(len=get_k(t(m5, (/31, n9, 53/))))  :: a
 
        write(a, *) integerValue
    end function IntToChar8

end module cutils


program test

    use cutils

    implicit none
    character(25) :: str
    
    str = IntToChar1(3)
    print *, str
    str = IntToChar2(3)
    print *, str
    str = IntToChar3(3)
    print *, str
    str = IntToChar4(3)
    print *, str
    str = IntToChar5(3)
    print *, str
    str = IntToChar6(3)
    print *, str
    str = IntToChar7(3)
    print *, str
    str = IntToChar8(3)
    print *, str

end program test