source: XMLF90/src/sax/m_io.f90 @ 6

Last change on this file since 6 was 6, checked in by ymipsl, 15 years ago

Import des sources XMLF90

File size: 1.8 KB
Line 
1module m_io
2
3!
4! Basic  I/O tools
5!
6integer, public, save            :: io_eor, io_eof
7
8public  :: get_unit, setup_io
9private :: find_eor_eof
10
11CONTAINS
12
13! ----------------------------------------------------------------------
14subroutine setup_io()
15  call find_eor_eof(io_eor, io_eof)
16end subroutine setup_io
17
18! ----------------------------------------------------------------------
19subroutine get_unit(lun,iostat)
20
21! Get an available Fortran unit number
22
23integer, intent(out)  :: lun
24integer, intent(out)  :: iostat
25
26integer :: i
27logical :: unit_used
28
29do i = 10, 99
30   lun = i
31   inquire(unit=lun,opened=unit_used)
32   if (.not. unit_used) then
33      iostat = 0
34      return
35   endif
36enddo
37iostat = -1
38lun = -1
39end subroutine get_unit
40! ----------------------------------------------------------------------
41
42subroutine find_eor_eof(io_eor,io_eof)
43!
44! Determines the values of the iostat values for End of File and
45! End of Record (in non-advancing I/O)
46!
47integer, intent(out)           :: io_eor
48integer, intent(out)           :: io_eof
49
50integer           :: lun, iostat
51character(len=1)  :: c
52
53call get_unit(lun,iostat)
54
55if (iostat /= 0) stop "Out of unit numbers"
56
57open(unit=lun,status="scratch",form="formatted", &
58     action="readwrite",position="rewind",iostat=iostat)
59if (iostat /= 0)   stop "Cannot open test file"
60
61write(unit=lun,fmt=*)  "a"
62write(unit=lun,fmt=*)  "b"
63
64rewind(unit=lun)
65
66io_eor = 0
67do
68  read(unit=lun,fmt="(a1)",advance="NO",iostat=io_eor) c
69  if (io_eor /= 0) exit
70enddo
71
72io_eof = 0
73do
74  read(unit=lun,fmt=*,iostat=io_eof)
75  if (io_eof /= 0) exit
76enddo
77
78!!!!!!!!print *, "IO_EOR, IO_EOF: ", io_eor, io_eof
79
80close(unit=lun,status="delete")
81
82end subroutine find_eor_eof
83
84! ----------------------------------------------------------------------
85end module m_io
86
87
88
89
90
91
92
93
94
Note: See TracBrowser for help on using the repository browser.