lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr114304-2.f90
blob5ef5874f528a714576641da26abb468868beb63f
1 ! { dg-do run }
3 ! PR fortran/114304
5 ! Ensure that '\t' (tab) is supported as separator in list-directed input
6 ! While not really standard conform, this is widely used in user input and
7 ! widely supported.
10 use iso_c_binding
11 implicit none
12 character(len=*,kind=c_char), parameter :: tab = C_HORIZONTAL_TAB
14 ! Accept '<tab>' as variant to ' ' as separator
15 ! Check that <carriage_return><new line> and <new_line> are handled
17 character(len=*,kind=c_char), parameter :: nml_str &
18 = '&inparm'//C_CARRIAGE_RETURN // C_NEW_LINE // &
19 'first'//tab//'='//tab//' .true.'// C_NEW_LINE // &
20 ' , other'//tab//' ='//tab//'3'//tab//', 2'//tab//'/'
22 ! Check that <carriage_return> is handled,
24 ! Note: For new line, Unix uses \n, Windows \r\n but old Apple systems used '\r'
26 ! Gfortran does not seem to support all \r, but the following is supported
27 ! since ages, ! which seems to be a gfortran extension as ifort and flang don't like it.
29 character(len=*,kind=c_char), parameter :: nml_str2 &
30 = '&inparm'//C_CARRIAGE_RETURN // C_NEW_LINE // &
31 'first'//C_NEW_LINE//'='//tab//' .true.'// C_CARRIAGE_RETURN // &
32 ' , other'//tab//' ='//tab//'3'//tab//', 2'//tab//'/'
34 character(len=*,kind=c_char), parameter :: str &
35 = tab//'1'//tab//'2,'//tab//'3'//tab//',4'//tab//','//tab//'5'//tab//'/'
36 character(len=*,kind=c_char), parameter :: str2 &
37 = tab//'1'//tab//'2;'//tab//'3'//tab//';4'//tab//';'//tab//'5'//tab//'/'
38 logical :: first
39 integer :: other(4)
40 integer :: ints(6)
41 namelist /inparm/ first , other
43 other = 1
45 open(99, file="test.inp")
46 write(99, '(a)') nml_str
47 rewind(99)
48 read(99,nml=inparm)
49 close(99, status="delete")
51 if (.not.first .or. any (other /= [3,2,1,1])) stop 1
53 other = 9
55 open(99, file="test.inp")
56 write(99, '(a)') nml_str2
57 rewind(99)
58 read(99,nml=inparm)
59 close(99, status="delete")
61 if (.not.first .or. any (other /= [3,2,9,9])) stop 2
63 ints = 66
65 open(99, file="test.inp", decimal='point')
66 write(99, '(a)') str
67 rewind(99)
68 read(99,*) ints
69 close(99, status="delete")
71 if (any (ints /= [1,2,3,4,5,66])) stop 3
73 ints = 77
75 open(99, file="test.inp", decimal='comma')
76 write(99, '(a)') str2
77 rewind(99)
78 read(99,*) ints
79 close(99, status="delete")
81 if (any (ints /= [1,2,3,4,5,77])) stop 4
82 end