-
Notifications
You must be signed in to change notification settings - Fork 0
/
FileIO.f90
111 lines (76 loc) · 2.68 KB
/
FileIO.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
MODULE FileIO
! #DES: Subprograms for assisting with generic I/O
IMPLICIT NONE
PRIVATE
PUBLIC :: OpenFile, CloseFile, fileLengths, fileLength
CONTAINS
SUBROUTINE OpenFile(unit,fileName,action,success)
! #DES: Attempt to open the file 'fileName' on unit 'unit' with action 'action'
! #DES: Variable 'action' can be read, write or readwrite
IMPLICIT NONE
INTEGER, INTENT(IN) :: unit
CHARACTER(*), INTENT(IN) :: fileName, action
LOGICAL, INTENT(OUT), OPTIONAL :: success
INTEGER :: ios
IF (trim(adjustl(action)) /= "read" .AND. &
& trim(adjustl(action)) /= "write" .AND. &
& trim(adjustl(action)) /= "readwrite") &
& STOP "ILLEGAL ACTION ARGUMENT PROVIDED TO OpenFile IN FileIO"
IF (LEN(fileName) == 0) STOP "ZERO-LENGTH FILENAME PASSED TO OpenFile IN FileIO"
IF (unit <= 0) STOP "-VE UNIT NUMBER PASSED TO OpenFile IN FileIO"
IF (PRESENT(success)) THEN
IF (action == "read") THEN
INQUIRE(FILE=trim(adjustl(fileName)),EXIST=success)
IF (success .EQV. .FALSE.) RETURN
ENDIF
ENDIF
OPEN(UNIT=unit,FILE=trim(adjustl(fileName)),IOSTAT=ios,ACTION=trim(adjustl(action)))
IF (ios /= 0) THEN
WRITE(*,*) "ERROR: COULD NOT OPEN ", trim(adjustl(fileName)), " FOR ", trim(adjustl(action)), " ON UNIT ", unit
IF (PRESENT(success)) success = .FALSE.
ENDIF
END SUBROUTINE OpenFile
!*
SUBROUTINE CloseFile(unit)
! #DES: Attempt to close the file on unit 'unit'
IMPLICIT NONE
INTEGER, INTENT(IN) :: unit
INTEGER ios
IF (unit <= 0) STOP "-VE UNIT NUMBER PASSED TO CloseFile IN FileIO"
CLOSE(UNIT=unit,IOSTAT=ios)
IF (ios /= 0) THEN
WRITE(*,*) "ERROR: COULD NOT CLOSE FILE ON UNIT ", unit
ENDIF
ENDSUBROUTINE CloseFile
!*
INTEGER FUNCTION fileLength(fileName)
IMPLICIT NONE
CHARACTER(*), INTENT(IN) :: fileName
LOGICAL :: openSuccess
INTEGER, PARAMETER :: eneUnit = 100
INTEGER :: ios
fileLength = 0
CALL OpenFile(eneUnit,fileName,"read",success=openSuccess)
IF (openSuccess .EQV. .TRUE.) THEN
ios = 0; fileLength = 0
DO WHILE (ios == 0)
READ(eneUnit,*,IOSTAT=ios)
IF (ios == 0) fileLength = fileLength + 1
ENDDO
CALL CloseFile(eneUnit)
ELSE
STOP "FileIO:fileLength: File could not be opened"
ENDIF
END FUNCTION fileLength
!*
FUNCTION fileLengths(fileNames)
IMPLICIT NONE
CHARACTER(*), INTENT(IN) :: fileNames(:)
INTEGER :: fileLengths(SIZE(fileNames))
INTEGER :: step
fileLengths(:) = 0
DO step = 1, SIZE(fileNames)
fileLengths(step) = fileLength(fileNames(step))
ENDDO
END FUNCTION fileLengths
END MODULE FileIO