[3090] | 1 | ! Copyright (c) (2013-2015,2017,2022) Jeremie Burgalat (jeremie.burgalat@univ-reims.fr). |
---|
[3083] | 2 | ! |
---|
| 3 | ! This file is part of SWIFT |
---|
| 4 | ! |
---|
| 5 | ! Permission is hereby granted, free of charge, to any person obtaining a copy of |
---|
| 6 | ! this software and associated documentation files (the "Software"), to deal in |
---|
| 7 | ! the Software without restriction, including without limitation the rights to |
---|
| 8 | ! use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of |
---|
| 9 | ! the Software, and to permit persons to whom the Software is furnished to do so, |
---|
| 10 | ! subject to the following conditions: |
---|
| 11 | ! |
---|
| 12 | ! The above copyright notice and this permission notice shall be included in all |
---|
| 13 | ! copies or substantial portions of the Software. |
---|
| 14 | ! |
---|
| 15 | ! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR |
---|
| 16 | ! IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS |
---|
| 17 | ! FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR |
---|
| 18 | ! COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER |
---|
| 19 | ! IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN |
---|
| 20 | ! CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. |
---|
[1793] | 21 | |
---|
[1897] | 22 | !! file: asciiread.f90 |
---|
[1793] | 23 | !! summary: ASCII data file reader source file |
---|
| 24 | !! author: burgalat |
---|
[3083] | 25 | !! date: 2013-2015,2017,2022 |
---|
[1793] | 26 | MODULE ASCIIREAD |
---|
| 27 | !! ASCII data file reader module |
---|
| 28 | !! |
---|
| 29 | !! This module provides a single generic method that can be used to read 2D/3D |
---|
| 30 | !! data array from ASCII file. |
---|
| 31 | !! |
---|
[3083] | 32 | !! ``` |
---|
[1793] | 33 | !! FUNCTION read_data(path,data) RESULT(err) |
---|
| 34 | !! ``` |
---|
| 35 | !! |
---|
| 36 | !! Where: |
---|
| 37 | !! |
---|
| 38 | !! - __path__ is a string with the path of the data file. |
---|
| 39 | !! - __data__ is an output __allocatable__ 2D/3D array of real(kind=8) values. |
---|
| 40 | !! |
---|
| 41 | !! ## Expected Format of the data file |
---|
| 42 | !! |
---|
| 43 | !! The input file: |
---|
| 44 | !! - must use blank space(s) as value delimiter. |
---|
| 45 | !! - must have a regular number of columns, that is each data line must |
---|
[3083] | 46 | !! have the same number of columns. |
---|
[1793] | 47 | !! - can contains any number of empty lines and/or comment line (i.e. line |
---|
| 48 | !! where first non-blank character is "#"). All other lines are assumed |
---|
| 49 | !! to be data. |
---|
[3083] | 50 | !! Moreover, in the case of 3D data, it must use a SINGLE empty line for "depth" block separator. |
---|
[1793] | 51 | !! |
---|
| 52 | !! Error occured when: |
---|
| 53 | !! |
---|
| 54 | !! - path does not refer to a existing file (1) |
---|
[1897] | 55 | !! - No free logical unit available (1) |
---|
[1793] | 56 | !! - the file does not have regular data-columns number (5) |
---|
| 57 | !! - at least a value cannot be cast in double precision (5) |
---|
| 58 | !! |
---|
| 59 | !! On error, __data__ array is not allocated. |
---|
| 60 | !! |
---|
| 61 | !! ## 3D data structure |
---|
| 62 | !! |
---|
| 63 | !! In the case of 3D data the method assumes that the input files consists in _D_ blocks |
---|
| 64 | !! of _R_ lines with _C_ columns. Each block must be separated by a single empty line |
---|
| 65 | !! and each columns must separated by one or more blank spaces (no tabulation ALLOWED). |
---|
[3083] | 66 | !! |
---|
[1793] | 67 | !! On success, the shape of the 3D output array will be _data(R,C,D)_. |
---|
| 68 | USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY: IOSTAT_END, IOSTAT_EOR |
---|
[1897] | 69 | !USE STRING_OP, ONLY: tokenize,from_string, st_slen |
---|
| 70 | USE STRING_OP |
---|
[1793] | 71 | USE ERRORS |
---|
| 72 | IMPLICIT NONE |
---|
| 73 | |
---|
| 74 | PRIVATE |
---|
| 75 | PUBLIC :: noerror,error, error_to_string,aborting |
---|
[1897] | 76 | PUBLIC :: readline,read_data, OPERATOR(/=), OPERATOR(==) |
---|
[1793] | 77 | |
---|
| 78 | !! Global interface to reading methods |
---|
| 79 | INTERFACE read_data |
---|
| 80 | MODULE PROCEDURE read_data_2d, read_data_3d |
---|
| 81 | END INTERFACE |
---|
| 82 | |
---|
[3083] | 83 | CONTAINS |
---|
[1793] | 84 | |
---|
| 85 | |
---|
| 86 | FUNCTION read_data_3d(path,data3d,delimiter) RESULT(err) |
---|
| 87 | !! Read an input ASCII data file and stores its content in a 3D array |
---|
| 88 | !! |
---|
| 89 | !! The function reads an ASCII file and saves its values in a real(kind=8) 3D-array. |
---|
[3083] | 90 | !! |
---|
[1793] | 91 | !! The input file: |
---|
| 92 | !! |
---|
| 93 | !! - must have a regular number of columns, that is each data line must have the same number |
---|
[3083] | 94 | !! of columns (according to the delimiter used). |
---|
[1793] | 95 | !! - must use a SINGLE empty line for "depth" block separator. |
---|
| 96 | !! - can contains any number of comment lines (i.e. line where first non-blank character is "#"). |
---|
| 97 | !! All other lines (except empty lines) are assumed to be data. |
---|
[3083] | 98 | !! |
---|
[1793] | 99 | !! Error occured when: |
---|
| 100 | !! - Path does not refer to a existing file (-11) |
---|
[1897] | 101 | !! - No free logical unit available (-1) |
---|
[1793] | 102 | !! - The file does not have regular data-columns number (-5) |
---|
| 103 | !! - At least a value cannot be cast in double precision (-10) |
---|
| 104 | !! |
---|
| 105 | !! The method assumes the input files consists in _D_ block of _R_ lines |
---|
| 106 | !! with _C_ columns. Each block must be separated by a single empty line and |
---|
| 107 | !! each columns must separated by one or more blank spaces (no tabulation ALLOWED). |
---|
[3083] | 108 | !! |
---|
[1793] | 109 | !! On success, the shape of the 3D output array will be _output(R,C,D)_. |
---|
| 110 | !! On error, the 3D output array is __not allocated__. |
---|
[3083] | 111 | CHARACTER(len=*), INTENT(in) :: path !! Path of the input data file |
---|
[1793] | 112 | REAL(kind=8), INTENT(out), DIMENSION(:,:,:), ALLOCATABLE :: data3d !! 3D-array with the output values (double precision) |
---|
| 113 | CHARACTER(len=*), INTENT(in), OPTIONAL :: delimiter !! Optional column delimiter(s) |
---|
| 114 | TYPE(error) :: err !! Error status of the function |
---|
| 115 | LOGICAL :: ok |
---|
| 116 | INTEGER :: i,lc,tlc |
---|
| 117 | INTEGER :: ndr,ndc,ndd |
---|
[1897] | 118 | INTEGER :: ir,jc,kd,lu |
---|
[1793] | 119 | REAL(kind=8), DIMENSION(:), ALLOCATABLE :: tmp |
---|
| 120 | CHARACTER(len=5) :: slc |
---|
| 121 | CHARACTER(len=15) :: i2s |
---|
| 122 | CHARACTER(len=:), ALLOCATABLE :: line,lm1,zdelim |
---|
| 123 | CHARACTER(len=st_slen), DIMENSION(:), ALLOCATABLE :: wrds |
---|
| 124 | |
---|
| 125 | zdelim = CHAR(9)//CHAR(32) |
---|
| 126 | IF (PRESENT(delimiter)) zdelim = delimiter |
---|
| 127 | ! Check file status |
---|
| 128 | INQUIRE(FILE=TRIM(path),EXIST=ok) |
---|
| 129 | IF (.NOT.ok) THEN |
---|
| 130 | err = error(trim(path)//": no such file",-1) ; RETURN |
---|
| 131 | ENDIF |
---|
[3083] | 132 | lu = free_lun() |
---|
[1897] | 133 | IF (lu == -1) THEN ; err = error("Cannot find available logical unit...",-1) ; RETURN ; ENDIF |
---|
[1793] | 134 | ! Open file |
---|
[1897] | 135 | OPEN(lu,FILE=TRIM(path),STATUS='OLD',ACTION='READ') |
---|
[1793] | 136 | |
---|
[3083] | 137 | ! First pass : |
---|
[1793] | 138 | ! ------------ |
---|
[3083] | 139 | ! - get size (rows, columns, depth) |
---|
[1793] | 140 | ! - check size consistendcy |
---|
| 141 | ! - check value type |
---|
[3083] | 142 | lc = 0 ; tlc = 0 |
---|
| 143 | ndr = -1 ; ndc = -1 ; ndd = 1 |
---|
| 144 | DO WHILE(readline(lu,line)) |
---|
[1793] | 145 | lm1 = line |
---|
| 146 | ! Read the line |
---|
| 147 | lc = lc + 1 ; WRITE(slc,'(I5)') lc ; slc = ADJUSTL(slc) |
---|
| 148 | ! skip comment line |
---|
| 149 | IF (INDEX(TRIM(ADJUSTL(line)),"#") == 1) CYCLE |
---|
[3083] | 150 | ! An empty line: new 2D block |
---|
[1793] | 151 | IF (LEN_TRIM(line) == 0) THEN |
---|
| 152 | ndd = ndd + 1 |
---|
| 153 | IF (ndr < 0) THEN |
---|
| 154 | ndr = tlc |
---|
| 155 | ELSEIF (tlc /= ndr) THEN |
---|
| 156 | WRITE(i2s,'(I15)') ndd ; i2s = ADJUSTL(i2s) |
---|
| 157 | err = error(trim(path)//":Invalid number of lines in block #"//i2s//"(line "//TRIM(slc)//")",-5) |
---|
| 158 | RETURN |
---|
| 159 | ENDIF |
---|
| 160 | tlc = 0 |
---|
| 161 | CYCLE |
---|
| 162 | ENDIF |
---|
| 163 | tlc = tlc + 1 |
---|
| 164 | ! Splits line in words |
---|
[3083] | 165 | IF (.NOT.tokenize(line,wrds,zdelim,.true.)) THEN |
---|
[1793] | 166 | ! cannot tokenize |
---|
| 167 | err = error(trim(path)//": Cannot parse line "//TRIM(slc),-5) |
---|
| 168 | RETURN |
---|
| 169 | ELSEIF (.NOT.from_string(wrds,tmp)) THEN |
---|
| 170 | ! cannot cast values |
---|
| 171 | err = error(trim(path)//": Cannot cast values at line "//TRIM(slc),-5) |
---|
| 172 | RETURN |
---|
[3083] | 173 | ELSEIF (ndc > 0 .AND. ndc /= SIZE(wrds)) THEN |
---|
[1793] | 174 | ! current number of columns not equal to last one |
---|
| 175 | err = error(trim(path)//": Invalid number of columns (line "//TRIM(slc)//")",-5) |
---|
| 176 | RETURN |
---|
| 177 | ENDIF |
---|
| 178 | IF (ndc == -1) ndc = SIZE(wrds) |
---|
[1897] | 179 | IF (ALLOCATED(wrds)) DEALLOCATE(wrds) |
---|
| 180 | IF (ALLOCATED(tmp)) DEALLOCATE(tmp) |
---|
[1793] | 181 | ENDDO |
---|
| 182 | |
---|
| 183 | ! NOTE: |
---|
| 184 | ! there is a possible bug if data file ends by an empty line: |
---|
| 185 | ! we will have an extra empty bloc ! |
---|
| 186 | ! current patch: we save the last line of the file and check it: |
---|
| 187 | ! - if we have empty line, we reduce ndd by one. |
---|
| 188 | IF (LEN_TRIM(lm1) == 0) ndd = ndd-1 |
---|
| 189 | |
---|
| 190 | ! Rewind input data file |
---|
[1897] | 191 | REWIND(lu) |
---|
[1793] | 192 | ! Allocate memory |
---|
| 193 | ALLOCATE(data3d(ndr,ndc,ndd)) |
---|
[3083] | 194 | ir = 0 ; kd = 1 ; |
---|
| 195 | DO WHILE(readline(lu,line)) |
---|
[1793] | 196 | IF (INDEX(TRIM(ADJUSTL(line)),"#") == 1) CYCLE |
---|
| 197 | ir = ir + 1 |
---|
[3083] | 198 | ! empty line update block subscripts |
---|
[1793] | 199 | IF (LEN_TRIM(line) == 0) THEN |
---|
| 200 | kd = kd + 1 ; ir = 0 ; CYCLE |
---|
| 201 | ENDIF |
---|
| 202 | ok = tokenize(line,wrds,zdelim,.true.) |
---|
| 203 | DO jc = 1,ndc ; ok = from_string(wrds(jc),data3d(ir,jc,kd)) ; ENDDO |
---|
[1897] | 204 | IF (ALLOCATED(wrds)) DEALLOCATE(wrds) |
---|
[1793] | 205 | ENDDO |
---|
[1897] | 206 | CLOSE(lu) |
---|
[1793] | 207 | END FUNCTION read_data_3d |
---|
| 208 | |
---|
| 209 | FUNCTION read_data_2d(path,data2d,delimiter) RESULT(err) |
---|
| 210 | !! Read an input ASCII data file and stores its content in a 2D array |
---|
| 211 | !! |
---|
| 212 | !! The function reads an ASCII file and saves its values in a real(kind=8) 2D-array. |
---|
[3083] | 213 | !! |
---|
[1793] | 214 | !! The input file: |
---|
| 215 | !! |
---|
[3083] | 216 | !! - can contains any number of empty lines and/or comment line (i.e. line where first |
---|
[1793] | 217 | !! non-blank character is "#"). All other lines are assumed to be data. |
---|
[3083] | 218 | !! - must have a regular number of columns, that is each data line must have the same |
---|
| 219 | !! number of columns. |
---|
[1793] | 220 | !! - must use blank space(s) as value delimiter. |
---|
[3083] | 221 | !! |
---|
[1793] | 222 | !! Error occured when: |
---|
| 223 | !! |
---|
| 224 | !! - Path does not refer to a existing file (-1) |
---|
[1897] | 225 | !! - No free logical unit available (-1) |
---|
[1793] | 226 | !! - The file does not have regular data-columns number (-5) |
---|
| 227 | !! - At least a value cannot be cast in double precision (-5) |
---|
| 228 | !! |
---|
| 229 | !! On error, the 2D output array is __not allocated__. |
---|
[1897] | 230 | USE FSYSTEM |
---|
[3083] | 231 | CHARACTER(len=*), INTENT(in) :: path !! Path of the input data file |
---|
[1793] | 232 | REAL(kind=8), INTENT(out), DIMENSION(:,:), ALLOCATABLE :: data2d !! 2D-array with the output values (double precision) |
---|
| 233 | CHARACTER(len=*), INTENT(in), OPTIONAL :: delimiter !! Optional column delimiter(s) |
---|
| 234 | TYPE(error) :: err !! Error status of function. |
---|
| 235 | LOGICAL :: ok |
---|
| 236 | INTEGER :: i,e,vc,lc |
---|
[1897] | 237 | INTEGER :: nl,nc,lu |
---|
[1793] | 238 | REAL(kind=8), DIMENSION(:), ALLOCATABLE :: tmp |
---|
| 239 | CHARACTER(len=5) :: slc |
---|
| 240 | CHARACTER(len=:), ALLOCATABLE :: line,zdelim |
---|
| 241 | CHARACTER(len=st_slen), DIMENSION(:), ALLOCATABLE :: wrds |
---|
| 242 | zdelim = CHAR(9)//CHAR(32) |
---|
| 243 | IF (PRESENT(delimiter)) zdelim = delimiter |
---|
| 244 | INQUIRE(FILE=TRIM(path),EXIST=ok) |
---|
| 245 | IF (.NOT.ok) THEN |
---|
| 246 | err = error(trim(path)//": no such file",-1) ; RETURN |
---|
| 247 | ENDIF |
---|
[3083] | 248 | lu = free_lun() |
---|
[1897] | 249 | IF (lu == -1) THEN ; err = error("Cannot find available logical unit...",-1) ; RETURN ; ENDIF |
---|
| 250 | OPEN(lu,FILE=TRIM(path),STATUS='OLD',ACTION='READ') |
---|
[1793] | 251 | vc = 0 ; lc=0 ; ok = .true. |
---|
| 252 | ! Read the file twice :) |
---|
| 253 | lc=0 ; vc = 0 ; nc=-1 |
---|
| 254 | ! First pass : get number of row values and checks everything ! |
---|
[3083] | 255 | DO |
---|
[1793] | 256 | ! Read the line |
---|
[1897] | 257 | IF (.NOT.readline(lu,line)) EXIT |
---|
[1793] | 258 | lc = lc + 1 ; WRITE(slc,'(I5)') lc ; slc = ADJUSTL(slc) |
---|
| 259 | ! skip empty/comment line |
---|
| 260 | IF (INDEX(TRIM(ADJUSTL(line)),"#") == 1.OR.LEN_TRIM(line) == 0) CYCLE |
---|
| 261 | ! update row counter |
---|
| 262 | vc = vc + 1 |
---|
[3083] | 263 | IF (.NOT.tokenize(line,wrds,zdelim,.true.)) THEN |
---|
[1793] | 264 | ! cannot tokenize |
---|
| 265 | err = error(trim(path)//": Cannot parse line "//TRIM(slc),-5) |
---|
| 266 | RETURN |
---|
| 267 | ELSEIF (.NOT.from_string(wrds,tmp)) THEN |
---|
| 268 | ! cannot cast values |
---|
| 269 | err = error(trim(path)//": Cannot cast values at line "//TRIM(slc),-5) |
---|
| 270 | RETURN |
---|
[3083] | 271 | ELSEIF (nc > 0 .AND. nc /= SIZE(tmp)) THEN |
---|
[1793] | 272 | ! current number of columns not equal to last one |
---|
| 273 | err = error(trim(path)//": Invalid number of columns (line "//TRIM(slc)//")",-5) |
---|
| 274 | RETURN |
---|
| 275 | ENDIF |
---|
| 276 | IF (nc == -1) nc = SIZE(wrds) |
---|
[1897] | 277 | IF (ALLOCATED(wrds)) DEALLOCATE(wrds) |
---|
| 278 | IF (ALLOCATED(tmp)) DEALLOCATE(tmp) |
---|
[1793] | 279 | ENDDO |
---|
| 280 | ! Rewind input data file |
---|
[1897] | 281 | REWIND(lu) |
---|
[1793] | 282 | nl = vc |
---|
| 283 | ! allocate memory |
---|
| 284 | ALLOCATE(data2d(nl,nc)) |
---|
| 285 | ! Second pass : saves values :) |
---|
[3083] | 286 | vc = 0 |
---|
[1793] | 287 | DO WHILE(vc <= nl) |
---|
| 288 | ! Reads the line |
---|
[1897] | 289 | IF (.NOT.readline(lu,line)) EXIT |
---|
[1793] | 290 | ! Check if we have comment or null string |
---|
| 291 | IF (INDEX(TRIM(ADJUSTL(line)),"#") == 1.OR.LEN_TRIM(line) == 0) CYCLE |
---|
| 292 | vc = vc + 1 |
---|
| 293 | ok = tokenize(line,wrds,zdelim,.true.) |
---|
| 294 | DO i = 1,nc |
---|
| 295 | ok = from_string(wrds(i),data2d(vc,i)) |
---|
| 296 | ENDDO |
---|
[1897] | 297 | IF (ALLOCATED(wrds)) DEALLOCATE(wrds) |
---|
[1793] | 298 | ENDDO |
---|
[1897] | 299 | CLOSE(lu) |
---|
[1793] | 300 | RETURN |
---|
| 301 | END FUNCTION read_data_2d |
---|
| 302 | |
---|
| 303 | FUNCTION readline(lun,line) RESULT(not_eof) |
---|
| 304 | !! Read a complete line |
---|
[3083] | 305 | !! |
---|
| 306 | !! Each time, it is called, the function reads a complete of the file opened in __lun__ |
---|
[1793] | 307 | !! logical unit and returns .false. if EOF has been reached, .true. otherwise. |
---|
| 308 | !! |
---|
| 309 | !! The function is intended to read a file line by line: |
---|
| 310 | !! |
---|
[1897] | 311 | !! ``` |
---|
[1793] | 312 | !! lu = 1 |
---|
| 313 | !! open(lu,file="path/to/the/file/to/read") |
---|
| 314 | !! l=0 ! A line counter |
---|
| 315 | !! DO WHILE(readline(lu,line)) |
---|
| 316 | !! l = l + 1 |
---|
| 317 | !! WRITE(*,'("L",I2.2,": ",(a))') il,line |
---|
| 318 | !! ENDDO |
---|
| 319 | !! CLOSE(1) |
---|
| 320 | !! ``` |
---|
[3083] | 321 | INTEGER, INTENT(in) :: lun !! Logical unit with the opened file to read. |
---|
| 322 | CHARACTER(len=:), ALLOCATABLE, INTENT(out) :: line !! Processed line |
---|
[1793] | 323 | LOGICAL :: not_eof !! .true. if EOF has NOT been reached yet, .false. otherwise |
---|
| 324 | CHARACTER(len=50) :: buf |
---|
| 325 | INTEGER :: e,sz |
---|
| 326 | not_eof = .true. ; line = '' |
---|
| 327 | DO |
---|
| 328 | READ(lun,'(a)',ADVANCE="no",SIZE=sz,IOSTAT=e) buf |
---|
| 329 | IF (e == IOSTAT_END) THEN |
---|
| 330 | not_eof = .false. |
---|
| 331 | IF (sz > 0) line=line//buf(1:sz) |
---|
| 332 | EXIT |
---|
| 333 | ELSE IF (e == IOSTAT_EOR) THEN |
---|
| 334 | line = line//buf(1:sz) |
---|
| 335 | EXIT |
---|
| 336 | ELSE |
---|
| 337 | line = line//buf |
---|
| 338 | ENDIF |
---|
| 339 | ENDDO |
---|
| 340 | END FUNCTION readline |
---|
| 341 | |
---|
[1897] | 342 | END MODULE ASCIIREAD |
---|