1 ! { dg-do run { target { *-*-mingw* } } }
2 ! { dg-options "-fdec" }
4 ! Run-time tests for various carriagecontrol parameters with DEC I/O.
5 ! Ensures the output is as defined.
8 subroutine write_lines(fd
)
10 integer, intent(in
) :: fd
11 write(fd
, '(A)') "+ first"
12 write(fd
, '(A)') "-second line"
13 write(fd
, '(A)') "0now you know"
14 write(fd
, '(A)') "1this is the fourth line"
15 write(fd
, '(A)') "$finally we have a new challenger for the final line"
16 write(fd
, '(A)') CHAR(0)//"this is the end"
17 write(fd
, '(A)') " this is a plain old line"
20 subroutine check_cc (cc
, fname
, expected
)
22 ! carraigecontrol type, file name to write to
23 character(*), intent(in
) :: cc
, fname
25 character(*), intent(in
) :: expected
27 ! read buffer, line number, unit, status
28 character(len
=:), allocatable
:: buf
32 ! write lines using carriagecontrol setting
33 open(unit
=fd
, file
=fname
, action
='write', carriagecontrol
=cc
)
37 open(unit
=fd
, file
=fname
, action
='readwrite', &
38 form
='unformatted', access
='stream')
40 inquire(file
=fname
, size
=siz
)
41 allocate(character(len
=siz
) :: buf
)
42 read(unit
=fd
, pos
=1) buf
43 if (buf
.ne
. expected
) then
44 print *, '=================> ',cc
,' <================='
45 print *, '***** actual *****'
47 print *, '***** expected *****'
54 close(unit
=fd
, status
='delete')
60 character(*), parameter :: fname
= 'dec_io_2.txt'
62 !! In NONE mode, there are no line breaks between records.
63 character(*), parameter :: output_ccnone
= &
67 "1this is the fourth line"//&
68 "$finally we have a new challenger for the final line"//&
69 CHAR(0)//"this is the end"//&
70 " this is a plain old line"
72 !! In LIST mode, each record is terminated with a newline.
73 character(*), parameter :: output_cclist
= &
74 "+ first"//CHAR(13)//CHAR(10)//&
75 "-second line"//CHAR(13)//CHAR(10)//&
76 "0now you know"//CHAR(13)//CHAR(10)//&
77 "1this is the fourth line"//CHAR(13)//CHAR(10)//&
78 "$finally we have a new challenger for the final line"//CHAR(13)//CHAR(10)//&
79 CHAR(0)//"this is the end"//CHAR(13)//CHAR(10)//&
80 " this is a plain old line"//CHAR(13)//CHAR(10)
82 !! In FORTRAN mode, the default record break is CR, and the first character
83 !! implies the start- and end-of-record formatting.
84 ! '+' Overprinting: <text> CR
85 ! '-' One line feed: NL <text> CR
86 ! '0' Two line feeds: NL NL <text> CR
87 ! '1' Next page: FF <text> CR
88 ! '$' Prompting: NL <text>
89 !'\0' Overprinting with no advance: <text>
90 ! Other: defaults to Overprinting <text> CR
91 character(*), parameter :: output_ccfort
= ""//&
93 CHAR(10)//"second line"//CHAR(13)//&
94 CHAR(10)//CHAR(10)//"now you know"//CHAR(13)//&
95 CHAR(12)//"this is the fourth line"//CHAR(13)//&
96 CHAR(10)//"finally we have a new challenger for the final line"//&
98 CHAR(10)//"this is a plain old line"//CHAR(13)
100 call check_cc('none', fname
, output_ccnone
)
101 call check_cc('list', fname
, output_cclist
)
102 call check_cc('fortran', fname
, output_ccfort
)