aarch64: Add vector floating point extend pattern [PR113880, PR113869]
[official-gcc.git] / gcc / testsuite / gfortran.dg / read_dir.f90
blob2778210f0791ef26dbb079a0b982485a7b245d58
1 ! { dg-do run }
2 ! { dg-additional-sources read_dir-aux.c }
4 ! PR67367
6 program bug
7 use iso_c_binding
8 implicit none
10 interface
11 integer(c_int) function expect_open_to_fail () bind(C)
12 import
13 end
14 subroutine my_verify_not_exists(s) bind(C)
15 ! Aborts if the passed pathname (still) exists
16 import
17 character(len=1,kind=c_char) :: s(*)
18 end subroutine
19 subroutine my_mkdir(s) bind(C)
20 ! Call POSIX's mkdir - and ignore fails due to
21 ! existing directories but fail otherwise
22 import
23 character(len=1,kind=c_char) :: s(*)
24 end subroutine
25 subroutine my_rmdir(s) bind(C)
26 ! Call POSIX's rmdir - and ignore fails
27 import
28 character(len=1,kind=c_char) :: s(*)
29 end subroutine
30 end interface
32 character(len=*), parameter :: sdir = "junko.dir"
33 character(len=*,kind=c_char), parameter :: c_sdir = sdir // c_null_char
35 character(len=1) :: c
36 integer ios
38 if (expect_open_to_fail () /= 0) then
39 ! Windows is documented to fail with EACCESS when trying to open a
40 ! directory. However, target macros such as __WIN32__ are not defined
41 ! in Fortran; hence, we use a detour via this C function.
42 ! Check for '.' which is a known-to-exist directory:
43 open(unit=10, file='.',iostat=ios,action='read',access='stream')
44 if (ios == 0) &
45 stop 3 ! Error: open to fail (EACCESS)
46 stop 0 ! OK
47 endif
49 call my_mkdir(c_sdir)
50 open(unit=10, file=sdir,iostat=ios,action='read',access='stream')
52 if (ios.ne.0) then
53 call my_rmdir(c_sdir)
54 STOP 1
55 end if
56 read(10, iostat=ios) c
57 if (ios.ne.21.and.ios.ne.0) then ! EISDIR has often the value 21
58 close(10, status='delete')
59 call my_verify_not_exists(c_sdir)
60 STOP 2
61 end if
62 close(10, status='delete')
63 call my_verify_not_exists(c_sdir)
64 end program bug