* tree-loop-distribution.c (struct partition): New field recording
[official-gcc.git] / gcc / testsuite / gfortran.dg / eof_4.f90
blob293c0fa39f6fca322eae2be78352264a640bd6c8
1 ! { dg-do run }
2 ! PR55818 Reading a REAL from a file which doesn't end in a new line fails
3 ! Test case from PR reporter.
4 implicit none
5 integer :: stat
6 !integer :: var ! << works
7 real :: var ! << fails
8 character(len=10) :: cvar ! << fails
9 complex :: cval
10 logical :: lvar
12 open(99, file="test.dat", access="stream", form="unformatted", status="new")
13 write(99) "1", new_line("")
14 write(99) "2", new_line("")
15 write(99) "3"
16 close(99)
18 ! Test character kind
19 open(99, file="test.dat")
20 read (99,*, iostat=stat) cvar
21 if (stat /= 0 .or. cvar /= "1") call abort()
22 read (99,*, iostat=stat) cvar
23 if (stat /= 0 .or. cvar /= "2") call abort()
24 read (99,*, iostat=stat) cvar ! << FAILS: stat /= 0
25 if (stat /= 0 .or. cvar /= "3") call abort() ! << aborts here
27 ! Test real kind
28 rewind(99)
29 read (99,*, iostat=stat) var
30 if (stat /= 0 .or. var /= 1.0) call abort()
31 read (99,*, iostat=stat) var
32 if (stat /= 0 .or. var /= 2.0) call abort()
33 read (99,*, iostat=stat) var ! << FAILS: stat /= 0
34 if (stat /= 0 .or. var /= 3.0) call abort()
35 close(99, status="delete")
37 ! Test real kind with exponents
38 open(99, file="test.dat", access="stream", form="unformatted", status="new")
39 write(99) "1.0e3", new_line("")
40 write(99) "2.0e-03", new_line("")
41 write(99) "3.0e2"
42 close(99)
44 open(99, file="test.dat")
45 read (99,*, iostat=stat) var
46 if (stat /= 0) call abort()
47 read (99,*, iostat=stat) var
48 if (stat /= 0) call abort()
49 read (99,*) var ! << FAILS: stat /= 0
50 if (stat /= 0) call abort()
51 close(99, status="delete")
53 ! Test logical kind
54 open(99, file="test.dat", access="stream", form="unformatted", status="new")
55 write(99) "Tru", new_line("")
56 write(99) "fal", new_line("")
57 write(99) "t"
58 close(99)
60 open(99, file="test.dat")
61 read (99,*, iostat=stat) lvar
62 if (stat /= 0 .or. (.not.lvar)) call abort()
63 read (99,*, iostat=stat) lvar
64 if (stat /= 0 .or. lvar) call abort()
65 read (99,*) lvar ! << FAILS: stat /= 0
66 if (stat /= 0 .or. (.not.lvar)) call abort()
67 close(99, status="delete")
69 ! Test combinations of Inf and Nan
70 open(99, file="test.dat", access="stream", form="unformatted", status="new")
71 write(99) "infinity", new_line("")
72 write(99) "nan", new_line("")
73 write(99) "infinity"
74 close(99)
76 open(99, file="test.dat")
77 read (99,*, iostat=stat) var
78 if (stat /= 0) call abort()
79 read (99,*, iostat=stat) var
80 if (stat /= 0) call abort()
81 read (99,*) var ! << FAILS: stat /= 0
82 if (stat /= 0) call abort ! << aborts here
83 close(99, status="delete")
85 open(99, file="test.dat", access="stream", form="unformatted", status="new")
86 write(99) "infinity", new_line("")
87 write(99) "inf", new_line("")
88 write(99) "nan"
89 close(99)
91 open(99, file="test.dat")
92 read (99,*, iostat=stat) var
93 if (stat /= 0) call abort()
94 read (99,*, iostat=stat) var
95 if (stat /= 0) call abort()
96 read (99,*) var ! << FAILS: stat /= 0
97 if (stat /= 0) call abort ! << aborts here
98 close(99, status="delete")
100 open(99, file="test.dat", access="stream", form="unformatted", status="new")
101 write(99) "infinity", new_line("")
102 write(99) "nan", new_line("")
103 write(99) "inf"
104 close(99)
106 open(99, file="test.dat")
107 read (99,*, iostat=stat) var
108 if (stat /= 0) call abort()
109 read (99,*, iostat=stat) var
110 if (stat /= 0) call abort()
111 read (99,*) var ! << FAILS: stat /= 0
112 if (stat /= 0) call abort ! << aborts here
113 close(99, status="delete")
115 ! Test complex kind
116 open(99, file="test.dat", access="stream", form="unformatted", status="new")
117 write(99) "(1,2)", new_line("")
118 write(99) "(2,3)", new_line("")
119 write(99) "(4,5)"
120 close(99)
122 open(99, file="test.dat")
123 read (99,*, iostat=stat) cval
124 if (stat /= 0 .or. cval /= cmplx(1,2)) call abort()
125 read (99,*, iostat=stat) cval
126 if (stat /= 0 .or. cval /= cmplx(2,3)) call abort()
127 read (99,*, iostat=stat) cval ! << FAILS: stat /= 0, value is okay
128 if (stat /= 0 .or. cval /= cmplx(4,5)) call abort()
129 close(99, status="delete")