2017-02-20 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / deferred_type_param_8.f90
blob3c768c567a7485bcc4883d3b7a9152b4238936a7
1 ! { dg-do run }
3 ! PR fortran/53642
4 ! PR fortran/45170 (comments 24, 34, 37)
7 PROGRAM helloworld
8 implicit none
9 character(:),allocatable::string
10 character(11), parameter :: cmp = "hello world"
11 real::rnd
12 integer :: n, i
13 do i = 1, 10
14 call random_number(rnd)
15 n = ceiling(11*rnd)
16 call hello(n, string)
17 ! print '(A,1X,I0)', '>' // string // '<', len(string)
18 if (n /= len (string) .or. string /= cmp(1:n)) call abort ()
19 end do
21 call test_PR53642()
23 contains
25 subroutine hello (n,string)
26 character(:), allocatable, intent(out) :: string
27 integer,intent(in) :: n
28 character(11) :: helloworld="hello world"
30 string=helloworld(:n) ! Didn't work
31 ! string=(helloworld(:n)) ! Works.
32 ! allocate(string, source=helloworld(:n)) ! Fixed for allocate_with_source_2.f90
33 ! allocate(string, source=(helloworld(:n))) ! Works.
34 end subroutine hello
36 subroutine test_PR53642()
37 character(len=4) :: string="123 "
38 character(:), allocatable :: trimmed
40 trimmed = trim(string)
41 if (len_trim(string) /= len(trimmed)) call abort ()
42 if (len(trimmed) /= 3) call abort ()
43 if (trimmed /= "123") call abort ()
44 ! print *,len_trim(string),len(trimmed)
46 ! Clear
47 trimmed = "XXXXXX"
48 if (trimmed /= "XXXXXX" .or. len(trimmed) /= 6) call abort ()
50 trimmed = string(1:len_trim(string))
51 if (len_trim(trimmed) /= 3) call abort ()
52 if (trimmed /= "123") call abort ()
53 end subroutine test_PR53642
54 end PROGRAM helloworld