source: trunk/LMDZ.TITAN/libf/muphytitan/asciiread.f90 @ 1897

Last change on this file since 1897 was 1897, checked in by jvatant, 7 years ago

Making Titan's hazy again - part II
+ Major updates of J.Burgalat YAMMS library and optical coupling, including :
++ Added the routines for haze optics inside YAMMS
++ Calling rad. transf. with interactive haze is plugged
in but should stay unactive as long as the microphysics is
in test phase : cf "uncoupl_optic_haze" flag : true for now !
++ Also some sanity checks for negative tendencies and
some others upkeep of YAMMS model
+ Also added a temporary CPP key USE_QTEST in physiq_mod
that enables to have microphysical tendencies separated
from dynamics for debugging and test phases
-- JVO and JB

File size: 14.0 KB
Line 
1! Copyright Jérémie Burgalat (2010-2015,2017)
2!
3! jeremie.burgalat@univ-reims.fr
4!
5! This software is a computer program whose purpose is to provide configuration
6! file and command line arguments parsing features to Fortran programs.
7!
8! This software is governed by the CeCILL-B license under French law and
9! abiding by the rules of distribution of free software.  You can  use,
10! modify and/ or redistribute the software under the terms of the CeCILL-B
11! license as circulated by CEA, CNRS and INRIA at the following URL
12! "http://www.cecill.info".
13!
14! As a counterpart to the access to the source code and  rights to copy,
15! modify and redistribute granted by the license, users are provided only
16! with a limited warranty  and the software's author,  the holder of the
17! economic rights,  and the successive licensors  have only  limited
18! liability.
19!
20! In this respect, the user's attention is drawn to the risks associated
21! with loading,  using,  modifying and/or developing or reproducing the
22! software by the user in light of its specific status of free software,
23! that may mean  that it is complicated to manipulate,  and  that  also
24! therefore means  that it is reserved for developers  and  experienced
25! professionals having in-depth computer knowledge. Users are therefore
26! encouraged to load and test the software's suitability as regards their
27! requirements in conditions enabling the security of their systems and/or
28! data to be ensured and,  more generally, to use and operate it in the
29! same conditions as regards security.
30!
31! The fact that you are presently reading this means that you have had
32! knowledge of the CeCILL-B license and that you accept its terms.
33
34!! file: asciiread.f90
35!! summary: ASCII data file reader source file
36!! author: burgalat
37!! date: 2013-2015,2017
38MODULE ASCIIREAD
39  !! ASCII data file reader module
40  !!
41  !! This module provides a single generic method that can be used to read 2D/3D
42  !! data array from ASCII file.
43  !!
44  !! ```
45  !! FUNCTION read_data(path,data) RESULT(err)
46  !! ```
47  !!
48  !! Where:
49  !!
50  !! - __path__ is a string with the path of the data file.
51  !! - __data__ is an output __allocatable__ 2D/3D array of real(kind=8) values.
52  !!
53  !! ## Expected Format of the data file
54  !!
55  !! The input file:
56  !!   - must use blank space(s) as value delimiter.
57  !!   - must have a regular number of columns, that is each data line must
58  !!     have the same number of columns.
59  !!   - can contains any number of empty lines and/or comment line (i.e. line
60  !!     where first non-blank character is "#"). All other lines are assumed
61  !!     to be data.
62  !! Moreover, in the case of 3D data, it must use a SINGLE empty line for "depth" block separator. 
63  !!
64  !! Error occured when:
65  !!
66  !! - path does not refer to a existing file (1)
67  !! - No free logical unit available (1)
68  !! - the file does not have regular data-columns number (5)
69  !! - at least a value cannot be cast in double precision (5)
70  !!
71  !! On error, __data__ array is not allocated.
72  !!
73  !! ## 3D data structure
74  !!
75  !! In the case of 3D data the method assumes that the input files consists in _D_ blocks
76  !! of _R_ lines with _C_ columns. Each block must be separated by a single empty line
77  !! and each columns must separated by one or more blank spaces (no tabulation ALLOWED).
78  !! 
79  !! On success, the shape of the 3D output array will be _data(R,C,D)_.
80  USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY: IOSTAT_END, IOSTAT_EOR
81  !USE STRING_OP, ONLY: tokenize,from_string, st_slen
82  USE STRING_OP
83  USE ERRORS
84  IMPLICIT NONE
85
86  PRIVATE
87  PUBLIC :: noerror,error, error_to_string,aborting
88  PUBLIC :: readline,read_data, OPERATOR(/=), OPERATOR(==)
89
90  !! Global interface to reading methods
91  INTERFACE read_data
92    MODULE PROCEDURE read_data_2d, read_data_3d
93  END INTERFACE
94
95  CONTAINS
96
97
98  FUNCTION read_data_3d(path,data3d,delimiter) RESULT(err)
99    !! Read an input ASCII data file and stores its content in a 3D array
100    !!
101    !! The function reads an ASCII file and saves its values in a real(kind=8) 3D-array.
102    !!
103    !! The input file:
104    !!
105    !! - must have a regular number of columns, that is each data line must have the same number
106    !!   of columns (according to the delimiter used). 
107    !! - must use a SINGLE empty line for "depth" block separator.
108    !! - can contains any number of comment lines (i.e. line where first non-blank character is "#").
109    !!   All other lines (except empty lines) are assumed to be data.
110    !!
111    !! Error occured when:
112    !!    - Path does not refer to a existing file (-11)
113    !!    - No free logical unit available (-1)
114    !!    - The file does not have regular data-columns number (-5)
115    !!    - At least a value cannot be cast in double precision (-10)
116    !!
117    !! The method assumes the input files consists in _D_ block of _R_ lines
118    !! with _C_ columns. Each block must be separated by a single empty line and
119    !! each columns must separated by one or more blank spaces (no tabulation ALLOWED).
120    !!
121    !! On success, the shape of the 3D output array will be _output(R,C,D)_.
122    !! On error, the 3D output array is __not allocated__.
123    CHARACTER(len=*), INTENT(in)                             :: path      !! Path of the input data file
124    REAL(kind=8), INTENT(out), DIMENSION(:,:,:), ALLOCATABLE :: data3d    !! 3D-array with the output values (double precision)
125    CHARACTER(len=*), INTENT(in), OPTIONAL                   :: delimiter !! Optional column delimiter(s)
126    TYPE(error) :: err                                                    !! Error status of the function
127    LOGICAL                                           :: ok
128    INTEGER                                           :: i,lc,tlc
129    INTEGER                                           :: ndr,ndc,ndd
130    INTEGER                                           :: ir,jc,kd,lu
131    REAL(kind=8), DIMENSION(:), ALLOCATABLE           :: tmp
132    CHARACTER(len=5)                                  :: slc
133    CHARACTER(len=15)                                 :: i2s
134    CHARACTER(len=:), ALLOCATABLE                     :: line,lm1,zdelim
135    CHARACTER(len=st_slen), DIMENSION(:), ALLOCATABLE :: wrds
136
137    zdelim = CHAR(9)//CHAR(32)
138    IF (PRESENT(delimiter)) zdelim = delimiter
139    ! Check file status
140    INQUIRE(FILE=TRIM(path),EXIST=ok)
141    IF (.NOT.ok) THEN
142      err = error(trim(path)//": no such file",-1) ; RETURN
143    ENDIF
144    lu = free_lun()
145    IF (lu == -1) THEN ; err = error("Cannot find available logical unit...",-1) ; RETURN ; ENDIF
146    ! Open file
147    OPEN(lu,FILE=TRIM(path),STATUS='OLD',ACTION='READ')
148
149    ! First pass :
150    ! ------------
151    !   - get size (rows, columns, depth)
152    !   - check size consistendcy
153    !   - check value type
154    lc = 0 ; tlc = 0
155    ndr = -1 ; ndc = -1 ; ndd = 1
156    DO WHILE(readline(lu,line))
157      lm1 = line
158      ! Read the line
159      lc = lc + 1 ; WRITE(slc,'(I5)') lc ; slc = ADJUSTL(slc)
160      ! skip comment line
161      IF (INDEX(TRIM(ADJUSTL(line)),"#") == 1) CYCLE
162      ! An empty line: new 2D block
163      IF (LEN_TRIM(line) == 0) THEN
164        ndd = ndd + 1
165        IF (ndr < 0) THEN
166          ndr = tlc
167        ELSEIF (tlc /= ndr) THEN
168          WRITE(i2s,'(I15)') ndd ; i2s = ADJUSTL(i2s)
169          err = error(trim(path)//":Invalid number of lines in block #"//i2s//"(line "//TRIM(slc)//")",-5)
170          RETURN
171        ENDIF
172        tlc = 0
173        CYCLE
174      ENDIF
175      tlc = tlc + 1
176      ! Splits line in words
177      IF (.NOT.tokenize(line,wrds,zdelim,.true.)) THEN
178        ! cannot tokenize
179        err = error(trim(path)//": Cannot parse line "//TRIM(slc),-5)
180        RETURN
181      ELSEIF (.NOT.from_string(wrds,tmp)) THEN
182        ! cannot cast values
183        err = error(trim(path)//": Cannot cast values at line "//TRIM(slc),-5)
184        RETURN
185      ELSEIF (ndc > 0 .AND. ndc /= SIZE(wrds)) THEN
186        ! current number of columns not equal to last one
187        err = error(trim(path)//": Invalid number of columns (line "//TRIM(slc)//")",-5)
188        RETURN
189      ENDIF
190      IF (ndc == -1) ndc = SIZE(wrds)
191      IF (ALLOCATED(wrds)) DEALLOCATE(wrds)
192      IF (ALLOCATED(tmp)) DEALLOCATE(tmp)
193    ENDDO
194
195    ! NOTE:
196    ! there is a possible bug if data file ends by an empty line:
197    ! we will have an extra empty bloc !
198    !   current patch: we save the last line of the file and check it:
199    !     - if we have empty line, we reduce ndd by one.
200    IF (LEN_TRIM(lm1) == 0) ndd = ndd-1
201
202    ! Rewind input data file
203    REWIND(lu)
204    ! Allocate memory
205    ALLOCATE(data3d(ndr,ndc,ndd))
206    ir = 0 ; kd = 1 ;
207    DO WHILE(readline(lu,line))
208      IF (INDEX(TRIM(ADJUSTL(line)),"#") == 1) CYCLE
209      ir = ir + 1
210      ! empty line update block subscripts
211      IF (LEN_TRIM(line) == 0) THEN
212        kd = kd + 1 ; ir = 0 ; CYCLE
213      ENDIF
214      ok = tokenize(line,wrds,zdelim,.true.)
215      DO jc = 1,ndc ; ok = from_string(wrds(jc),data3d(ir,jc,kd)) ; ENDDO
216      IF (ALLOCATED(wrds)) DEALLOCATE(wrds)
217    ENDDO
218    CLOSE(lu)
219  END FUNCTION read_data_3d
220
221  FUNCTION read_data_2d(path,data2d,delimiter) RESULT(err)
222    !! Read an input ASCII data file and stores its content in a 2D array
223    !!
224    !! The function reads an ASCII file and saves its values in a real(kind=8) 2D-array.
225    !!
226    !! The input file:
227    !!
228    !! - can contains any number of empty lines and/or comment line (i.e. line where first
229    !!   non-blank character is "#"). All other lines are assumed to be data.
230    !! - must have a regular number of columns, that is each data line must have the same
231    !!   number of columns.
232    !! - must use blank space(s) as value delimiter.
233    !!
234    !! Error occured when:
235    !!
236    !! - Path does not refer to a existing file (-1)
237    !! - No free logical unit available (-1)
238    !! - The file does not have regular data-columns number (-5)
239    !! - At least a value cannot be cast in double precision (-5)
240    !!
241    !! On error, the 2D output array is __not allocated__.
242    USE FSYSTEM
243    CHARACTER(len=*), INTENT(in)                           :: path      !! Path of the input data file
244    REAL(kind=8), INTENT(out), DIMENSION(:,:), ALLOCATABLE :: data2d    !! 2D-array with the output values (double precision)
245    CHARACTER(len=*), INTENT(in), OPTIONAL                 :: delimiter !! Optional column delimiter(s)
246    TYPE(error) :: err                                                  !! Error status of function.
247    LOGICAL                                           :: ok
248    INTEGER                                           :: i,e,vc,lc
249    INTEGER                                           :: nl,nc,lu
250    REAL(kind=8), DIMENSION(:), ALLOCATABLE           :: tmp
251    CHARACTER(len=5)                                  :: slc
252    CHARACTER(len=:), ALLOCATABLE                     :: line,zdelim
253    CHARACTER(len=st_slen), DIMENSION(:), ALLOCATABLE :: wrds
254    zdelim = CHAR(9)//CHAR(32)
255    IF (PRESENT(delimiter)) zdelim = delimiter
256    INQUIRE(FILE=TRIM(path),EXIST=ok)
257    IF (.NOT.ok) THEN
258      err = error(trim(path)//": no such file",-1) ; RETURN
259    ENDIF
260    lu = free_lun()
261    IF (lu == -1) THEN ; err = error("Cannot find available logical unit...",-1) ; RETURN ; ENDIF
262    OPEN(lu,FILE=TRIM(path),STATUS='OLD',ACTION='READ')
263    vc = 0 ; lc=0 ; ok = .true.
264    ! Read the file twice :)
265    lc=0 ; vc = 0 ; nc=-1
266    ! First pass : get number of row values and checks everything !
267    DO
268      ! Read the line
269      IF (.NOT.readline(lu,line)) EXIT
270      lc = lc + 1 ; WRITE(slc,'(I5)') lc ; slc = ADJUSTL(slc)
271      ! skip empty/comment line
272      IF (INDEX(TRIM(ADJUSTL(line)),"#") == 1.OR.LEN_TRIM(line) == 0) CYCLE
273      ! update row counter
274      vc = vc + 1
275      IF (.NOT.tokenize(line,wrds,zdelim,.true.)) THEN
276        ! cannot tokenize
277        err = error(trim(path)//": Cannot parse line "//TRIM(slc),-5)
278        RETURN
279      ELSEIF (.NOT.from_string(wrds,tmp)) THEN
280        ! cannot cast values
281        err = error(trim(path)//": Cannot cast values at line "//TRIM(slc),-5)
282        RETURN
283      ELSEIF (nc > 0 .AND. nc /= SIZE(tmp)) THEN
284        ! current number of columns not equal to last one
285        err = error(trim(path)//": Invalid number of columns (line "//TRIM(slc)//")",-5)
286        RETURN
287      ENDIF
288      IF (nc == -1) nc = SIZE(wrds)
289      IF (ALLOCATED(wrds)) DEALLOCATE(wrds)
290      IF (ALLOCATED(tmp)) DEALLOCATE(tmp)
291    ENDDO
292    ! Rewind input data file
293    REWIND(lu)
294    nl = vc
295    ! allocate memory
296    ALLOCATE(data2d(nl,nc))
297    ! Second pass : saves values :)
298    vc = 0
299    DO WHILE(vc <= nl)
300      ! Reads the line
301      IF (.NOT.readline(lu,line)) EXIT
302      ! Check if we have comment or null string
303      IF (INDEX(TRIM(ADJUSTL(line)),"#") == 1.OR.LEN_TRIM(line) == 0) CYCLE
304      vc = vc + 1
305      ok = tokenize(line,wrds,zdelim,.true.)
306      DO i = 1,nc
307        ok = from_string(wrds(i),data2d(vc,i))
308      ENDDO
309      IF (ALLOCATED(wrds)) DEALLOCATE(wrds)
310    ENDDO
311    CLOSE(lu)
312    RETURN
313  END FUNCTION read_data_2d
314
315  FUNCTION readline(lun,line) RESULT(not_eof)
316    !! Read a complete line
317    !!
318    !! Each time, it is called, the function reads a complete of the file opened in __lun__
319    !! logical unit and returns .false. if EOF has been reached, .true. otherwise.
320    !!
321    !! The function is intended to read a file line by line:
322    !!
323    !! ```
324    !! lu = 1
325    !! open(lu,file="path/to/the/file/to/read")
326    !! l=0   ! A line counter
327    !! DO WHILE(readline(lu,line))
328    !!   l = l + 1
329    !!   WRITE(*,'("L",I2.2,": ",(a))') il,line
330    !! ENDDO
331    !! CLOSE(1)
332    !! ```
333    INTEGER, INTENT(in)                        :: lun  !! Logical unit with the opened file to read.
334    CHARACTER(len=:), ALLOCATABLE, INTENT(out) :: line !! Processed line
335    LOGICAL  :: not_eof                                !! .true. if EOF has NOT been reached yet, .false. otherwise
336    CHARACTER(len=50) :: buf
337    INTEGER           :: e,sz
338    not_eof = .true. ; line = ''
339    DO
340      READ(lun,'(a)',ADVANCE="no",SIZE=sz,IOSTAT=e) buf
341      IF (e == IOSTAT_END) THEN
342        not_eof = .false.
343        IF (sz > 0) line=line//buf(1:sz)
344        EXIT
345      ELSE IF (e == IOSTAT_EOR) THEN
346        line = line//buf(1:sz)
347        EXIT
348      ELSE
349        line = line//buf
350      ENDIF
351    ENDDO
352  END FUNCTION readline
353
354END MODULE ASCIIREAD
Note: See TracBrowser for help on using the repository browser.