source: readTracFiles_mod.f90 @ 3

Last change on this file since 3 was 3, checked in by dcugnet, 3 years ago

Missing detail in the previous commit

File size: 86.5 KB
Line 
1MODULE readTracFiles_mod
2
3  USE strings_mod, ONLY:   msg, testFile,  strFind, strStack, strReduce,  strHead, strCount,   find, maxlen, fmsg, &
4            removeComment, cat, checkList, strIdx,  strParse, strReplace, strTail, reduceExpr, test, get_in, dispTable
5  USE trac_types_mod, ONLY : trac_type, isot_type, keys_type
6
7  IMPLICIT NONE
8
9  PRIVATE
10
11  PUBLIC :: initIsotopes, maxlen, trac_type, isot_type
12  PUBLIC :: readTracersFiles, aliasTracer, tracersSubset, indexUpdate!--- TOOLS ASSOCIATED TO TRACERS  DESCRIPTORS
13  PUBLIC :: readIsotopesFile                                         !--- TOOLS ASSOCIATED TO ISOTOPES DESCRIPTORS
14  PUBLIC :: getKey_init, getKey, setDirectKeys                       !--- GET/SET KEYS FROM/TO tracers & isotopes
15
16  PUBLIC :: known_phases, old_phases, nphases, phases_names, &       !--- VARIABLES RELATED TO THE PHASES
17            phases_sep, delPhase, addPhase                           !--- + ROUTINES TO ADD/REMOVE PHASE TO/FROM A NAME
18
19  PUBLIC :: tran0, idxAncestor, ancestor                             !--- GENERATION 0 TRACER + TOOLS FOR GENERATIONS
20
21!------------------------------------------------------------------------------------------------------------------------------
22  TYPE :: dataBase_type                                              !=== TYPE FOR TRACERS SECTION
23    CHARACTER(LEN=maxlen)  :: name                                   !--- Section name
24    TYPE(trac_type), ALLOCATABLE :: trac(:)                          !--- Tracers descriptors
25  END TYPE dataBase_type
26!------------------------------------------------------------------------------------------------------------------------------
27  INTERFACE getKey
28    MODULE PROCEDURE getKeyByName_s1, getKeyByName_i1, getKeyByName_r1, getKeyByName_sm, getKeyByName_im, getKeyByName_rm
29  END INTERFACE getKey
30!------------------------------------------------------------------------------------------------------------------------------
31  INTERFACE tracersSubset; MODULE PROCEDURE trSubset_Indx, trSubset_Name, trSubset_gen0Name; END INTERFACE tracersSubset
32  INTERFACE idxAncestor;   MODULE PROCEDURE idxAncestor_1, idxAncestor_m; END INTERFACE idxAncestor
33  INTERFACE    ancestor;   MODULE PROCEDURE    ancestor_1,    ancestor_m; END INTERFACE    ancestor
34  INTERFACE    addPhase;   MODULE PROCEDURE    addPhase_1,    addPhase_m; END INTERFACE    addPhase
35!------------------------------------------------------------------------------------------------------------------------------
36
37  !=== MAIN DATABASE: files sections descriptors
38  TYPE(dataBase_type), SAVE, ALLOCATABLE, TARGET :: dBase(:)
39
40  !--- SOME PARAMETERS THAT ARE NOT LIKELY TO CHANGE OFTEN
41  CHARACTER(LEN=maxlen), SAVE      :: tran0        = 'air'           !--- Default transporting fluid
42  CHARACTER(LEN=maxlen), PARAMETER :: old_phases   = 'vli'           !--- Old phases for water (no separator)
43  CHARACTER(LEN=maxlen), PARAMETER :: known_phases = 'gls'           !--- Known phases initials
44  INTEGER,               PARAMETER :: nphases=LEN_TRIM(known_phases) !--- Number of phases
45  CHARACTER(LEN=maxlen), SAVE      :: phases_names(nphases) &        !--- Known phases names
46                                = ['gaseous', 'liquid ', 'solid  ']
47  CHARACTER(LEN=1),   SAVE      :: phases_sep  =  '_'                !--- Phase separator
48  LOGICAL,            SAVE      :: tracs_merge = .TRUE.              !--- Merge/stack tracers lists
49  LOGICAL,            SAVE      :: lSortByGen  = .TRUE.              !--- Sort by growing generation
50
51  !=== LOCAL COPIES OF THE TRACERS AND ISOTOPES DESCRIPTORS, USED BY getKey (INITIALIZED IN getKey_init)
52  TYPE(trac_type), ALLOCATABLE, TARGET, SAVE ::  tracers(:)
53  TYPE(isot_type), ALLOCATABLE, TARGET, SAVE :: isotopes(:)
54
55  CHARACTER(LEN=maxlen) :: modname
56
57CONTAINS
58
59!==============================================================================================================================
60!==============================================================================================================================
61!=== READ ONE OR SEVERAL TRACER FILES AND FILL A "tr" TRACERS DESCRIPTOR DERIVED TYPE.
62!=== THE RETURN VALUE fType DEPENDS ON WHAT IS FOUND:
63!===  0: NO ADEQUATE FILE FOUND ; DEFAULT VALUES MUST BE USED
64!===  1: AN "OLD STYLE" TRACERS FILE "traceur.def":
65!===    First line: <nb tracers>     Other lines: <hadv> <vadv> <tracer name> [<parent name>]
66!===  2: A  "NEW STYLE" TRACERS FILE  "tracer.def" WITH SEVERAL SECTIONS.
67!===  3: SEVERAL  "  "  TRACERS FILES "tracer_<component>.def" WITH A SINGLE SECTION IN EACH.
68!=== REMARKS:
69!===  * EACH SECTION BEGINS WITH A "&<section name> LINE
70!===  * DEFAULT VALUES FOR ALL THE SECTIONS OF THE FILE ARE DEFINED IN THE SPECIAL SECTION "&default"
71!===  * EACH SECTION LINE HAS THE STRUCTURE:  <name(s)>  <key1>=<value1> <key2>=<value2> ...
72!===  * SO FAR, THE DEFINED KEYS ARE: parent, phases, hadv, vadv, type
73!===  * <name> AND <parent> CAN BE LISTS OF COMA-SEPARATED TRACERS ; THE ROUTINE EXPAND THESE FACTORIZATIONS.
74!=== FUNCTION RETURN VALUE "lerr" IS FALSE IN CASE SOMETHING WENT WRONG.
75!=== ABOUT THE KEYS:
76!     * The "keys" component (of type keys_type) is in principle enough to store everything we could need.
77!     But some variables are stored as direct-access keys to make the code more readable and because they are used often.
78!     * Most of the direct-access keys are set in this module, but some are not (lnam, iadv and itr for example).
79!     * Some of the direct-access keys must be updated (using the routine "setDirectKeys") is a subset of "tracers(:)"
80!     is extracted: the indexes are no longer valid for a subset (examples: tracers(:)%iqParent or tracers(:)%ichld).
81!     * If you need to convert a %key/%val pair into a direct-access key, add the corresponding line in "setDirectKeys".
82!==============================================================================================================================
83LOGICAL FUNCTION readTracersFiles(type_trac, fType, tracs) RESULT(lerr)
84!------------------------------------------------------------------------------------------------------------------------------
85  CHARACTER(LEN=*),             INTENT(IN)  :: type_trac              !--- List of components used
86  INTEGER,                      INTENT(OUT) :: fType                  !--- Type of input file found
87  TYPE(trac_type), ALLOCATABLE, INTENT(OUT) :: tracs(:)
88  CHARACTER(LEN=maxlen),  ALLOCATABLE ::  s(:), sections(:), trac_files(:)
89  CHARACTER(LEN=maxlen) :: str, fname, mesg
90  INTEGER               :: is, nsec, ierr, it, ntrac, ns, ip
91  LOGICAL, ALLOCATABLE  :: ll(:), lGen3(:)
92!------------------------------------------------------------------------------------------------------------------------------
93  lerr = .FALSE.
94  modname = 'readTracersFiles'
95  IF(.NOT.ALLOCATED(dBase)) ALLOCATE(dBase(0))
96
97  !--- Required sections + corresponding files names (new style single section case)
98  IF(test(strParse(type_trac, ',', sections), lerr)) RETURN          !--- Parse "type_trac" list
99
100  nsec = SIZE(sections, DIM=1)
101  ALLOCATE(trac_files(nsec)); DO is=1, nsec; trac_files(is) = 'tracer_'//TRIM(sections(is))//'.def'; END DO
102
103  !--- LOOK AT AVAILABLE FILES
104  ll = .NOT.testFile(trac_files)
105  fType = 0
106  IF(.NOT.testFile('traceur.def') .AND. nsec==1) fType = 1           !--- OLD STYLE FILE
107  IF(.NOT.testFile('tracer.def'))                fType = 2           !--- NEW STYLE ; SINGLE  FILE, SEVERAL SECTIONS
108  IF(ALL(ll))                                    fType = 3           !--- NEW STYLE ; SEVERAL FILES, SINGLE SECTION USED
109  IF(ANY(ll) .AND. fType/=3) THEN                                    !--- MISSING FILES
110    IF(test(checkList(trac_files, .NOT.ll, 'Failed reading tracers description', 'files', 'missing'), lerr)) RETURN
111  END IF
112
113  !--- TELLS WHAT WAS IS ABOUT TO BE USED
114  IF (fmsg('No adequate tracers description file(s) found ; default values will be used',          modname, fType==0)) RETURN
115  CALL msg('Trying to read old-style tracers description file "traceur.def"',                      modname, fType==1)
116  CALL msg('Trying to read the new style multi-sections tracers description file "tracer.def"',    modname, fType==2)
117  CALL msg('Trying to read the new style single section tracers description files "tracer_*.def"', modname, fType==3)
118
119  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
120  IF(fType==1) THEN                                                  !=== OLD FORMAT "traceur.def"
121  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
122    !--- OPEN THE "traceur.def" FILE
123    OPEN(90, FILE="traceur.def", FORM='formatted', STATUS='old', IOSTAT=ierr)
124
125    !--- GET THE TRACERS NUMBER
126    READ(90,'(i3)',IOSTAT=ierr)ntrac                                 !--- Number of lines/tracers
127    IF(test(fmsg('Invalid format for "'//TRIM(fname)//'"', modname, ierr /= 0), lerr)) RETURN
128
129    !--- READ THE REMAINING LINES: <hadv> <vadv> <tracer> [<transporting fluid>]
130    ALLOCATE(tracs(ntrac))
131    DO it=1,ntrac                                                    !=== READ RAW DATA: loop on the line/tracer number
132      READ(90,'(a)',IOSTAT=ierr) str
133      IF(test(fmsg('Invalid format for "' //TRIM(fname)//'"', modname, ierr>0), lerr)) RETURN
134      IF(test(fmsg('Not enough lines in "'//TRIM(fname)//'"', modname, ierr<0), lerr)) RETURN
135      ll = strParse(str, ' ', s, n=ns)
136      tracs(it)%keys%key = ['hadv', 'vadv']
137      tracs(it)%keys%val = s(1:2)
138      CALL msg('This file is for air tracers only',           modname, ns == 3 .AND. it == 1)
139      CALL msg('This files specifies the transporting fluid', modname, ns == 4 .AND. it == 1)
140      tracs(it)%name = s(3); tracs(it)%phase = known_phases(1:1)     !--- Default: name, gazeous phase "g"
141      DO ip = 1, nphases                                             !--- Deal with old water names
142        IF(s(3) /= 'H2O'//old_phases(ip:ip)) CYCLE
143        tracs(it)%phase = known_phases(ip:ip); tracs(it)%name = 'H2O'//phases_sep//TRIM(tracs(it)%phase)
144      END DO
145      tracs(it)%parent = tran0                                       !--- Default transporting fluid: Air
146      IF(ns == 4) tracs(it)%parent = s(4)                            !--- Transporting fluid name
147    END DO
148    CLOSE(90)
149
150    lGen3 = tracs%iGeneration==3
151    CALL setGeneration(tracs)                                        !--- Determine tracs(:)%iGeneration values
152    IF(test(checkTracers(tracs,      fname,fname),lerr)) RETURN      !--- Detect orphans and check phases
153    IF(test(checkUnique (tracs,lGen3,fname,fname),lerr)) RETURN      !--- Detect repeated tracers
154    CALL sortTracers  (tracs)                                        !--- Sort the tracers
155    CALL setDirectKeys(tracs)                                        !--- Set the directly accessible keys
156    tracs(:)%keys%name = tracs(:)%name                               !--- Copy tracers names in keys components
157    RETURN
158  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
159  END IF
160  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
161
162  !=== USING NEW FORMAT TRACERS DESCRIPTION FILES WITH POSSIBLY SEVERAL SECTIONS
163  CALL msg('The multiple required sections will be MERGED.',    modname, nsec > 1 .AND.      tracs_merge)
164  CALL msg('The multiple required sections will be CUMULATED.', modname, nsec > 1 .AND. .NOT.tracs_merge)
165
166  !=== FEED THE DATABASE WITH THE RAW CONTENT OF THE FILE
167  SELECT CASE(fType)
168    CASE(2); lerr = feedDBase(["tracer.def"],[type_trac])            !--- Single file, coma-separated sections list
169    CASE(3); lerr = feedDBase(trac_files,     sections  )            !--- Multiple files, one section name each file
170  END SELECT
171  IF(lerr) RETURN
172  IF(     tracs_merge) lerr = mergeTracers(dBase, tracs)             !--- MERGE    THE COMPONENTS OF THE DATABASE
173  IF(.NOT.tracs_merge) lerr = cumulTracers(dBase, tracs)             !--- CUMULATE THE COMPONENTS OF THE DATABASE
174  IF(lerr) RETURN
175  CALL setDirectKeys(tracs)                                          !--- Set the directly accessible keys
176
177END FUNCTION readTracersFiles
178!==============================================================================================================================
179
180!==============================================================================================================================
181LOGICAL FUNCTION feedDBase(fnames, snames) RESULT(lerr)
182! Purpose: Read the sections "snames(is)" (coma-separated list) from each "fnames(is)"
183!   file and create the corresponding tracers set descriptors in the database "dBase":
184! * dBase(id)%name                : section name
185! * dBase(id)%trac(:)%name        : tracers names
186! * dBase(id)%trac(it)%keys%key(:): names  of keys associated to tracer dBase(id)%trac(it)%name
187! * dBase(id)%trac(it)%keys%val(:): values of keys associated to tracer dBase(id)%trac(it)%name
188!------------------------------------------------------------------------------------------------------------------------------
189  CHARACTER(LEN=*), INTENT(IN)  :: fnames(:)                         !--- Files names
190  CHARACTER(LEN=*), INTENT(IN)  :: snames(:)                         !--- Coma-deparated list of sections (one list each file)
191  INTEGER,  ALLOCATABLE :: ndb(:)                                    !--- Nuber of sections for each file
192  INTEGER,  ALLOCATABLE :: ixf(:)                                    !--- File index for each section of the expanded list
193  LOGICAL,  ALLOCATABLE :: lTg(:)                                    !--- Tagging tracers mask
194  CHARACTER(LEN=maxlen) :: fnm, snm, modname
195  INTEGER               :: idb, i
196  LOGICAL :: ll
197!------------------------------------------------------------------------------------------------------------------------------
198  modname = 'feedDBase'
199  !=== READ THE REQUIRED SECTIONS
200  ll = strCount(snames, ',', ndb)                                    !--- Number of sections for each file
201  ALLOCATE(ixf(SUM(ndb)))
202  DO i=1, SIZE(fnames)
203    IF(test(readSections(fnames(i), snames(i), 'default'), lerr)) RETURN
204    ixf(1+SUM(ndb(1:i-1)):SUM(ndb(1:i))) = i                         !--- File index for each section of the expanded list
205  END DO
206  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
207  DO idb=1,SIZE(dBase)                                               !--- LOOP ON THE LOADED SECTIONS
208  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
209    fnm = fnames(ixf(idb)); snm = dBase(idb)%name
210    IF(test(expandSection(dBase(idb)%trac,   snm, fnm),lerr)) RETURN !--- EXPAND NAMES AND PARENTS LISTS
211    CALL setGeneration   (dBase(idb)%trac)                           !--- DETERMINE GENERATION NUMBER
212    IF(test(checkTracers (dBase(idb)%trac,   snm, fnm),lerr)) RETURN !--- CHECK ORPHANS AND PHASES
213    lTg = dBase(idb)%trac(:)%type == 'tag'                           !--- Flag for tagging tracers
214    IF(test(checkUnique  (dBase(idb)%trac,lTg,snm,fnm),lerr)) RETURN !--- CHECK TRACERS UNIQUENESS
215    CALL expandPhases    (dBase(idb)%trac)                           !--- EXPAND THE PHASES
216    CALL sortTracers     (dBase(idb)%trac)                           !--- SORT TRACERS
217  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
218  END DO
219  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
220
221  !=== DISPLAY BASIC INFORMATION
222  lerr = ANY([( dispTraSection('Expanded list for section "'//TRIM(dBase(idb)%name)//'"', dBase(idb)%name, modname), &
223                idb=1, SIZE(dBase) )])
224END FUNCTION feedDBase
225!------------------------------------------------------------------------------------------------------------------------------
226
227!------------------------------------------------------------------------------------------------------------------------------
228LOGICAL FUNCTION readSections(fnam,snam,defName) RESULT(lerr)
229!------------------------------------------------------------------------------------------------------------------------------
230  CHARACTER(LEN=*),           INTENT(IN) :: fnam                     !--- File name
231  CHARACTER(LEN=*),           INTENT(IN) :: snam                     !--- Coma-separated sections list
232  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: defName                  !--- Special section (default values) name
233!------------------------------------------------------------------------------------------------------------------------------
234  TYPE(dataBase_type),   ALLOCATABLE :: tdb(:)
235  CHARACTER(LEN=maxlen), ALLOCATABLE :: sec(:)
236  INTEGER,               ALLOCATABLE ::  ix(:)
237  INTEGER :: n0, idb, ndb, i, j
238  LOGICAL :: ll
239!------------------------------------------------------------------------------------------------------------------------------
240  n0 = SIZE(dBase) + 1                                               !--- Index for next entry in the database
241  CALL readSections_all()                                            !--- Read all the sections of file "fnam"
242  ndb= SIZE(dBase)                                                   !--- Current number of sections in the database
243  IF(PRESENT(defName)) THEN                                          !--- Add default values to all the tracers
244    DO idb=n0,ndb; CALL addDefault(dBase(idb)%trac, defName); END DO !--- and remove the virtual tracer "defName"
245  END IF
246  ll = strParse(snam, ',', keys = sec)                               !--- Requested sections names
247  ix = strIdx(dBase(:)%name, sec(:))                                 !--- Indexes of requested sections in database
248  IF(test(checkList(sec, ix == 0, 'In file "'//TRIM(fnam)//'"','section(s)', 'missing'), lerr)) RETURN
249  tdb = dBase(:); dBase = [tdb(1:n0-1),tdb(PACK(ix, MASK=ix/=0))]    !--- Keep requested sections only
250
251CONTAINS
252
253!------------------------------------------------------------------------------------------------------------------------------
254SUBROUTINE readSections_all()
255!------------------------------------------------------------------------------------------------------------------------------
256  CHARACTER(LEN=maxlen), ALLOCATABLE ::  s(:), v(:)
257  TYPE(trac_type),       ALLOCATABLE :: tt(:)
258  TYPE(trac_type)       :: tmp
259  CHARACTER(LEN=1024)   :: str
260  CHARACTER(LEN=maxlen) :: secn
261  INTEGER               :: ierr, n
262!------------------------------------------------------------------------------------------------------------------------------
263  IF(.NOT.ALLOCATED(dBase)) ALLOCATE(dBase(0))
264  OPEN(90, FILE=fnam, FORM='formatted', STATUS='old')
265  DO; READ(90,'(a)', IOSTAT=ierr)str
266    IF(ierr    /= 0 ) EXIT                                           !--- Finished: error or end of file
267    IF(str(1:1)=='#') CYCLE                                          !--- Skip comments lines
268    CALL removeComment(str)                                          !--- Skip comments at the end of a line
269    IF(str     == '') CYCLE                                          !--- Skip empty line (probably at the end of the file)
270    IF(str(1:1)=='&') THEN                                           !=== SECTION HEADER LINE
271      ndb  = SIZE(dBase)                                             !--- Number of sections so far
272      secn = str(2:LEN_TRIM(str))//' '                               !--- Current section name
273      IF(ANY(dBase(:)%name == secn)) CYCLE                           !--- Already known section
274      IF(secn(1:7) == 'version')     CYCLE                           !--- Skip the "version" special section
275      ndb = ndb + 1                                                  !--- Extend database
276      ALLOCATE(tdb(ndb))
277      tdb(1:ndb-1)  = dBase
278      tdb(ndb)%name = secn
279      ALLOCATE(tdb(ndb)%trac(0))
280      CALL MOVE_ALLOC(FROM=tdb, TO=dBase)
281    ELSE                                                             !=== TRACER LINE
282      ll = strParse(str,' ', keys = s, vals = v, n = n)              !--- Parse <key>=<val> pairs
283      tt = dBase(ndb)%trac(:)
284      tmp%name = s(1); tmp%component=secn; tmp%keys = keys_type(s(1), s(2:n), v(2:n))
285      dBase(ndb)%trac = [tt(:), tmp]
286      DEALLOCATE(tt)
287!      dBase(ndb)%trac = [dBase(ndb)%trac(:), tra(name=s(1), comp=secn, keys=keys_type(s(1), s(2:n), v(2:n)))]
288    END IF
289  END DO
290  CLOSE(90)
291
292END SUBROUTINE readSections_all
293!------------------------------------------------------------------------------------------------------------------------------
294
295END FUNCTION readSections
296!==============================================================================================================================
297
298
299!==============================================================================================================================
300SUBROUTINE addDefault(t, defName)
301!------------------------------------------------------------------------------------------------------------------------------
302! Purpose: Add the keys from virtual tracer named "defName" (if any) and remove this virtual tracer.
303!------------------------------------------------------------------------------------------------------------------------------
304  TYPE(trac_type), ALLOCATABLE, TARGET, INTENT(INOUT) :: t(:)
305  CHARACTER(LEN=*),                     INTENT(IN)    :: defName
306  INTEGER :: jd, it, k
307  TYPE(keys_type), POINTER :: ky
308  TYPE(trac_type), ALLOCATABLE :: tt(:)
309  jd = strIdx(t(:)%name, defName)
310  IF(jd == 0) RETURN
311  ky => t(jd)%keys
312  DO k = 1, SIZE(ky%key)                                             !--- Loop on the keys of the tracer named "defName"
313    CALL addKey_m(ky%key(k), ky%val(k), t(:)%keys)                   !--- Add key to all the tracers (no overwriting)
314  END DO
315  tt = [t(1:jd-1),t(jd+1:SIZE(t))]; CALL MOVE_ALLOC(FROM=tt, TO=t)   !--- Remove the virtual tracer named "defName"
316END SUBROUTINE addDefault
317!==============================================================================================================================
318
319!==============================================================================================================================
320SUBROUTINE subDefault(t, defName, lSubLocal)
321!------------------------------------------------------------------------------------------------------------------------------
322! Purpose: Substitute the keys from virtual tracer named "defName" (if any) and remove this virtual tracer.
323!          Substitute the keys locally (for the current tracer) if the flag "lSubLocal" is .TRUE.
324!------------------------------------------------------------------------------------------------------------------------------
325  TYPE(trac_type), ALLOCATABLE, TARGET, INTENT(INOUT) :: t(:)
326  CHARACTER(LEN=*),                     INTENT(IN)    :: defName
327  LOGICAL,                              INTENT(IN)    :: lSubLocal
328  INTEGER :: i0, it, ik
329  TYPE(keys_type), POINTER     :: k0, ky
330  TYPE(trac_type), ALLOCATABLE :: tt(:)
331  i0 = strIdx(t(:)%name, defName)
332  IF(i0 == 0) RETURN
333  k0 => t(i0)%keys
334  DO it = 1, SIZE(t); IF(it == i0) CYCLE                             !--- Loop on the tracers
335    ky => t(it)%keys
336
337    !--- Substitute in the values of <key>=<val> pairs the keys defined in the virtual tracer "defName"
338    DO ik = 1, SIZE(k0%key); CALL strReplace(ky%val, k0%key(ik), k0%val(ik), .TRUE.); END DO
339
340    IF(.NOT.lSubLocal) CYCLE
341    !--- Substitute in the values of <key>=<val> pairs the keys defined locally (in the current tracer)
342    DO ik = 1, SIZE(ky%key); CALL strReplace(ky%val, ky%key(ik), ky%val(ik), .TRUE.); END DO
343  END DO
344  tt = [t(1:i0-1),t(i0+1:SIZE(t))]; CALL MOVE_ALLOC(FROM=tt, TO=t)   !--- Remove the virtual tracer named "defName"
345
346END SUBROUTINE subDefault
347!==============================================================================================================================
348
349
350!==============================================================================================================================
351LOGICAL FUNCTION expandSection(tr, sname, fname) RESULT(lerr)
352!------------------------------------------------------------------------------------------------------------------------------
353! Purpose: Expand tracers and parents lists in the tracers descriptor "tra".
354! Note:  * The following keys are expanded, so are accessible explicitely using "%" operator: "parent" "type".
355!        * Default values are provided for these keys because they are necessary.
356!------------------------------------------------------------------------------------------------------------------------------
357  TYPE(trac_type), ALLOCATABLE, INTENT(INOUT) :: tr(:)                 !--- Tracer derived type vector
358  CHARACTER(LEN=*),             INTENT(IN)    :: sname
359  CHARACTER(LEN=*), OPTIONAL,   INTENT(IN)    :: fname
360  TYPE(trac_type),       ALLOCATABLE :: ttr(:)
361  CHARACTER(LEN=maxlen), ALLOCATABLE :: ta(:), pa(:)
362  CHARACTER(LEN=maxlen) :: msg1, modname
363  INTEGER :: it, nt, iq, nq, itr, ntr, ipr, npr, i
364  LOGICAL :: ll
365  modname = 'expandSection'
366  lerr = .FALSE.
367  nt = SIZE(tr)
368  nq = 0
369  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
370  DO it = 1, nt    !=== GET TRACERS NB AFTER EXPANSION + NEEDED KEYS (name, parent, type)
371  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
372    !--- Extract useful keys: parent name, type, component name
373    tr(it)%parent    = fgetKey(it, 'parent', tr(:)%keys,  tran0  )
374    tr(it)%type      = fgetKey(it, 'type'  , tr(:)%keys, 'tracer')
375    tr(it)%component = sname
376
377    !--- Determine the number of tracers and parents ; coherence checking
378    ll = strCount(tr(it)%name,   ',', ntr)
379    ll = strCount(tr(it)%parent, ',', npr)
380
381    !--- Tagging tracers only can have multiple parents
382    IF(test(npr/=1 .AND. TRIM(tr(it)%type)/='tag', lerr)) THEN
383      msg1 = 'Check section "'//TRIM(sname)//'"'
384      IF(PRESENT(fname)) msg1=TRIM(msg1)//' in file "'//TRIM(fname)//'"'
385      CALL msg(TRIM(msg1)//': "'//TRIM(tr(it)%name)//'" has several parents but is not a tag', modname); RETURN
386    END IF
387    nq = nq + ntr*npr                 
388  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
389  END DO
390  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
391  CALL delKey(['parent','type  '], tr)
392
393  ALLOCATE(ttr(nq))
394  iq = 1
395  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
396  DO it = 1, nt                                                      !=== EXPAND TRACERS AND PARENTS NAMES LISTS
397  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
398    ll = strParse(tr(it)%name, ',', ta, n=ntr)                       !--- Number of tracers
399    ll = strParse(tr(it)%parent, ',', pa, n=npr)                     !--- Number of parents
400    DO ipr=1,npr                                                     !--- Loop on parents list elts
401      DO itr=1,ntr                                                   !--- Loop on tracers list elts
402        i = iq+itr-1+(ipr-1)*ntr
403        ttr(i)%name = ta(itr); ttr(i)%parent = pa(ipr)
404        ttr(i)%keys = keys_type(ta(itr), tr(it)%keys%key, tr(it)%keys%val)
405      END DO
406    END DO
407    ttr(iq:iq+ntr*npr-1)%type = tr(it)%type                          !--- Duplicating type
408    iq = iq + ntr*npr
409  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
410  END DO
411  !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
412  DEALLOCATE(ta,pa)
413  CALL MOVE_ALLOC(FROM=ttr, TO=tr)
414
415END FUNCTION expandSection
416!==============================================================================================================================
417
418!==============================================================================================================================
419SUBROUTINE setGeneration(tr)
420!------------------------------------------------------------------------------------------------------------------------------
421! Purpose: Determine, for each tracer of "tr(:)":
422!   * the generation number
423!   * the first generation ancestor name
424!------------------------------------------------------------------------------------------------------------------------------
425! Arguments:
426  TYPE(trac_type), INTENT(INOUT) :: tr(:)                            !--- Tracer derived type vector
427!------------------------------------------------------------------------------------------------------------------------------
428! Local variables:
429  INTEGER :: iq, nq, ig
430  LOGICAL,               ALLOCATABLE :: lg(:)
431  CHARACTER(LEN=maxlen), ALLOCATABLE :: prn(:)
432!------------------------------------------------------------------------------------------------------------------------------
433  tr(:)%iGeneration = 0                                              !--- error if 0
434  nq = SIZE(tr, DIM=1)                                               !--- Number of tracers lines
435  lg = tr(:)%parent == tran0                                         !--- First generation tracers flag
436  WHERE(lg) tr(:)%iGeneration = 1                                    !--- First generation tracers
437
438  !=== Determine generation for each tracer
439  ig=0; prn = [tran0]
440  DO                                                                 !--- Update current generation flag
441    IF(ig/=0) prn = PACK( tr(:)%name, MASK=tr(:)%iGeneration == ig)
442    lg(:) = [(ANY(prn(:) == tr(iq)%parent), iq=1, nq)]               !--- Current generation tracers flag
443    IF( ALL( .NOT. lg ) ) EXIT                                       !--- Empty current generation
444    ig = ig+1; WHERE(lg) tr(:)%iGeneration = ig
445  END DO
446  tr(:)%gen0Name = ancestor(tr)                                      !--- First generation ancestor name
447
448END SUBROUTINE setGeneration
449!==============================================================================================================================
450
451!==============================================================================================================================
452LOGICAL FUNCTION checkTracers(tr, sname, fname) RESULT(lerr)
453!------------------------------------------------------------------------------------------------------------------------------
454! Purpose:
455!   * check for orphan tracers (without known parent)
456!   * check wether the phases are known or not ("g"aseous, "l"iquid or "s"olid so far)
457!------------------------------------------------------------------------------------------------------------------------------
458  TYPE(trac_type),            INTENT(IN) :: tr(:)                    !--- Tracer derived type vector
459  CHARACTER(LEN=*),           INTENT(IN) :: sname                    !--- Section name
460  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: fname                    !--- File name
461  CHARACTER(LEN=maxlen) :: mesg
462  CHARACTER(LEN=maxlen) :: bp(SIZE(tr, DIM=1)), pha                  !--- Bad phases list, phases of current tracer
463  CHARACTER(LEN=1) :: p
464  INTEGER :: ip, np, iq, nq
465!------------------------------------------------------------------------------------------------------------------------------
466  nq = SIZE(tr,DIM=1)                                                !--- Number of tracers lines
467  mesg = 'Check section "'//TRIM(sname)//'"'
468  IF(PRESENT(fname)) mesg=TRIM(mesg)//' in file "'//TRIM(fname)//'"'
469
470  !=== CHECK FOR ORPHAN TRACERS
471  IF(test(checkList(tr%name, tr%iGeneration==0, mesg, 'tracers', 'orphan'), lerr)) RETURN
472
473  !=== CHECK PHASES
474  DO iq=1,nq; IF(tr(iq)%iGeneration/=1) CYCLE                        !--- Generation 1 only is checked
475    pha = fgetKey(iq, 'phases', tr(:)%keys, 'g')                     !--- Phases
476    np = LEN_TRIM(pha); bp(iq)=' '
477    DO ip=1,np; p = pha(ip:ip); IF(INDEX(known_phases,p)==0) bp(iq) = TRIM(bp(iq))//p; END DO
478    IF(TRIM(bp(iq)) /= '') bp(iq) = TRIM(tr(iq)%name)//': '//TRIM(bp(iq))
479  END DO
480  lerr = checkList(bp, tr%iGeneration==1 .AND. bp/='', mesg, 'tracers phases', 'unknown')
481END FUNCTION checkTracers
482!==============================================================================================================================
483
484!==============================================================================================================================
485LOGICAL FUNCTION checkUnique(tr, lTag, sname, fname) RESULT(lerr)
486!------------------------------------------------------------------------------------------------------------------------------
487! Purpose: Make sure that tracers are not repeated.
488!------------------------------------------------------------------------------------------------------------------------------
489  TYPE(trac_type),            INTENT(IN) :: tr(:)                    !--- Tracer derived type vector
490  LOGICAL,                    INTENT(IN) :: lTag(:)                  !--- Tagging tracer flag
491  CHARACTER(LEN=*),           INTENT(IN) :: sname                    !--- Section name
492  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: fname                    !--- File name
493!------------------------------------------------------------------------------------------------------------------------------
494  INTEGER :: ip, np, iq, nq, k
495  LOGICAL, ALLOCATABLE  :: ll(:)
496  CHARACTER(LEN=maxlen) :: mesg, tnam, tdup(SIZE(tr,DIM=1))
497  CHARACTER(LEN=1)      :: p
498!------------------------------------------------------------------------------------------------------------------------------
499  mesg = 'Check section "'//TRIM(sname)//'"'
500  IF(PRESENT(fname)) mesg=TRIM(mesg)//' in file "'//TRIM(fname)//'"'
501  nq=SIZE(tr,DIM=1); lerr=.FALSE.                                    !--- Number of lines ; error flag
502  tdup(:) = ''
503  DO iq=1,nq; IF(lTag(iq)) CYCLE                                     !--- Tags can be repeated
504    tnam = tr(iq)%name
505    ll = tr(:)%name==tnam                                            !--- Mask for current tracer name
506    IF(COUNT(ll)==1 ) CYCLE                                          !--- Tracer is not repeated
507    IF(tr(iq)%iGeneration>1) THEN
508      tdup(iq) = tnam                                                !--- gen>1: MUST be unique
509    ELSE
510      DO ip=1,nphases; p=known_phases(ip:ip)                         !--- Loop on known phases
511        !--- Number of appearances of the current tracer with known phase "p"
512        np = COUNT( PACK( [(INDEX(fgetKey(k, 'phases', tr(:)%keys, 'g'),p), k=1, nq)] /=0 , MASK=ll ) )
513        IF(np <=1) CYCLE
514        tdup(iq) = TRIM(tdup(iq))//TRIM(phases_names(ip))
515        IF(ANY(tdup(1:iq-1) == tdup(iq))) tdup(iq)=''                !--- Avoid repeating same messages
516      END DO
517    END IF
518    IF(tdup(iq) /= '') tdup(iq)=TRIM(tnam)//' in '//TRIM(tdup(iq))//' phase(s)'
519  END DO
520  lerr = checkList(tdup, tdup/='', mesg, 'tracers', 'duplicated')
521END FUNCTION checkUnique
522!==============================================================================================================================
523
524!==============================================================================================================================
525SUBROUTINE expandPhases(tr)
526!------------------------------------------------------------------------------------------------------------------------------
527! Purpose: Expand the phases in the tracers descriptor "tr".
528!------------------------------------------------------------------------------------------------------------------------------
529  TYPE(trac_type), ALLOCATABLE, INTENT(INOUT) :: tr(:)               !--- Tracer derived type vector
530!------------------------------------------------------------------------------------------------------------------------------
531  TYPE(trac_type), ALLOCATABLE :: ttr(:)
532  INTEGER,   ALLOCATABLE ::  i0(:)
533  CHARACTER(LEN=maxlen)  :: nam, pha, trn
534  INTEGER :: ip, np, iq, jq, nq, it, nt, nc, i, n
535  LOGICAL :: lTg, lEx
536!------------------------------------------------------------------------------------------------------------------------------
537  nq = SIZE(tr, DIM=1)
538  nt = 0
539  DO iq = 1, nq                                                      !--- GET THE NUMBER OF TRACERS
540    IF(tr(iq)%iGeneration /= 1) CYCLE
541    nc = COUNT(tr(:)%gen0Name==tr(iq)%name .AND. tr%iGeneration/=1)  !--- Number of childs of tr(iq)
542    tr(iq)%phase = fgetKey(iq, 'phases', tr(:)%keys)                 !--- Phases list      of tr(iq)
543    np = LEN_TRIM(tr(iq)%phase)                                      !--- Number of phases of tr(iq)
544    nt = nt + (1+nc) * np                                            !--- Number of tracers after expansion
545  END DO
546  ALLOCATE(ttr(nt))
547  it = 1                                                             !--- Current "ttr(:)" index
548  DO iq = 1, nq                                                      !--- Loop on "tr(:)" indexes
549    lTg = tr(iq)%type=='tag'                                         !--- Current tracer is a tag
550    i0 = strFind(tr(:)%name, tr(iq)%gen0Name, n)                     !--- Indexes of first generation ancestor copies
551    np = SUM( [( LEN_TRIM(tr(i0(i))%phase),i=1,n )],1)               !--- Number of phases for current tracer tr(iq)
552    lEx = np>1                                                       !--- Need of a phase suffix
553    IF(lTg) lEx=lEx.AND.tr(iq)%iGeneration>1                         !--- No phase suffix for first generation tags
554    DO i=1,n                                                         !=== LOOP ON FIRST GENERATION ANCESTORS
555      jq=i0(i)                                                       !--- tr(jq): ith copy of 1st gen. ancestor of tr(iq)
556      IF(tr(iq)%iGeneration==1) jq=iq                                !--- Generation 1: current tracer phases only
557      pha = tr(jq)%phase                                             !--- Phases list for tr(jq)
558      DO ip=1,LEN_TRIM(pha)                                          !=== LOOP ON PHASES LISTS
559        trn=TRIM(tr(iq)%name); nam=trn                               !--- Tracer name (regular case)
560        IF(lTg) nam = TRIM(tr(iq)%parent)                            !--- Parent name (tagging case)
561        IF(lEx) nam = TRIM(nam)//phases_sep//pha(ip:ip)              !--- Phase extension needed
562        IF(lTg) nam = TRIM(nam)//'_'//TRIM(trn)                      !--- <parent>_<name> for tags
563        ttr(it) = tr(iq)                                             !--- Same <key>=<val> pairs
564        ttr(it)%name = nam                                           !--- Name with possibly phase suffix
565        ttr(it)%keys%name = nam                                      !--- Name inside the keys decriptor
566        ttr(it)%phase = pha(ip:ip)                                   !--- Single phase entry
567        IF(lEx.AND.tr(iq)%iGeneration>1) THEN
568          ttr(it)%parent   = TRIM(ttr(it)%parent)//phases_sep//pha(ip:ip)
569          ttr(it)%gen0Name = TRIM(ttr(it)%gen0Name)//phases_sep//pha(ip:ip)
570        END IF
571        it=it+1
572      END DO
573      IF(tr(iq)%iGeneration==1) EXIT                                 !--- Break phase loop for gen 1
574    END DO
575  END DO
576  CALL MOVE_ALLOC(FROM=ttr, TO=tr)
577  CALL delKey(['phases'],tr)                                         !--- Remove few keys entries
578
579END SUBROUTINE expandPhases
580!==============================================================================================================================
581
582!==============================================================================================================================
583SUBROUTINE sortTracers(tr)
584!------------------------------------------------------------------------------------------------------------------------------
585! Purpose: Sort tracers:
586!  * lGrowGen == T: in ascending generations numbers.
587!  * lGrowGen == F: tracer + its childs sorted by growing generation, one after the other.
588!------------------------------------------------------------------------------------------------------------------------------
589  TYPE(trac_type), ALLOCATABLE, INTENT(INOUT) :: tr(:)               !--- Tracer derived type vector
590  INTEGER :: ig, ng, iq, jq, n, ix(SIZE(tr)), k
591  INTEGER, ALLOCATABLE :: iy(:), iz(:)
592!------------------------------------------------------------------------------------------------------------------------------
593  iq = 1
594  IF(lSortByGen) THEN
595    ng = MAXVAL(tr(:)%iGeneration, MASK=.TRUE., DIM=1)               !--- Number of generations
596    DO ig = 0, ng                                                    !--- Loop on generations
597      iy = PACK([(k, k=1, SIZE(tr))], MASK=tr(:)%iGeneration==ig)    !--- Generation ig tracers indexes
598      n = SIZE(iy)
599      ix(iq:iq+n-1) = iy                                             !--- Stack growing generations idxs
600      iq = iq + n
601    END DO
602  ELSE
603    DO jq = 1, SIZE(tr,DIM=1)                                        !--- Loop on first generation tracers
604      IF(tr(jq)%iGeneration /= 1) CYCLE                              !--- Skip generations >= 1
605      ix(iq) = jq                                                    !--- First generation ancestor index first
606      iq = iq + 1
607      iy = strFind(tr(:)%gen0Name, tr(jq)%name)                      !--- Indexes of "tr(jq)" childs in "tr(:)"
608      ng = MAXVAL(tr(iy)%iGeneration, MASK=.TRUE., DIM=1)            !--- Generations number of the "tr(jq)" family
609      DO ig = 2, ng                                                  !--- Loop   on generations for the tr(jq) family
610        iz = find(tr(iy)%iGeneration, ig, n)                         !--- Indexes of the tracers "tr(iy(:))" of generation "ig"
611        ix(iq:iq+n-1) = iy(iz)                                       !--- Same indexes in "tr(:)"
612        iq = iq + n
613      END DO
614    END DO
615  END IF
616  tr = tr(ix)                                                        !--- Reorder the tracers
617END SUBROUTINE sortTracers
618!==============================================================================================================================
619
620!==============================================================================================================================
621LOGICAL FUNCTION mergeTracers(sections, tr) RESULT(lerr)
622  TYPE(dataBase_type),  TARGET, INTENT(IN)  :: sections(:)
623  TYPE(trac_type), ALLOCATABLE, INTENT(OUT) ::       tr(:)
624  TYPE(trac_type), POINTER ::   t1(:),   t2(:)
625  INTEGER,     ALLOCATABLE :: ixct(:), ixck(:)
626  INTEGER :: is, k1, k2, nk2, i1, i2, nt2
627  CHARACTER(LEN=maxlen) :: s1, v1, v2, tnam, knam, modname
628  modname = 'mergeTracers'
629  lerr = .FALSE.
630  t1 => sections(1)%trac(:)                                          !--- Alias: first tracers section
631  tr = t1
632  !----------------------------------------------------------------------------------------------------------------------------
633  DO is=2,SIZE(sections)                                             !=== SEVERAL SECTIONS: MERGE THEM
634  !----------------------------------------------------------------------------------------------------------------------------
635    t2  => sections(is)%trac(:)                                      !--- Alias: current tracers section
636    nt2  = SIZE(t2(:), DIM=1)                                        !--- Number of tracers in section
637    ixct = strIdx(t1(:)%name, t2(:)%name)                            !--- Indexes of common tracers
638    tr = [tr, PACK(t2, MASK= ixct==0)]                               !--- Append with new tracers
639    IF( ALL(ixct == 0) ) CYCLE                                       !--- No common tracers => done
640    CALL msg('Tracers defined in previous sections and duplicated in "'//TRIM(sections(is)%name)//'":', modname)
641    CALL msg(t1(PACK(ixct, MASK = ixct/=0))%name, modname, nmax=128) !--- Display duplicates (the 128 first at most)
642    !--------------------------------------------------------------------------------------------------------------------------
643    DO i2=1,nt2; tnam = t2(i2)%name                                  !=== LOOP ON COMMON TRACERS
644    !--------------------------------------------------------------------------------------------------------------------------
645      i1 = ixct(i2); IF(i1 == 0) CYCLE                               !--- Idx in t1(:) ; skip new tracers
646
647      !=== CHECK WETHER ESSENTIAL KEYS ARE IDENTICAL OR NOT
648      s1=' of "'//TRIM(tnam)//'" in "'//TRIM(sections(is)%name)//'" not matching previous value'
649     
650      IF(test(fmsg('Parent name'//TRIM(s1), modname, t1(i1)%parent      /= t2(i2)%parent),      lerr)) RETURN
651      IF(test(fmsg('Type'       //TRIM(s1), modname, t1(i1)%type        /= t2(i2)%type),        lerr)) RETURN
652      IF(test(fmsg('Generation' //TRIM(s1), modname, t1(i1)%iGeneration /= t2(i2)%iGeneration), lerr)) RETURN
653
654      !=== APPEND <key>=<val> PAIRS NOT PREVIOULSLY DEFINED
655      nk2  = SIZE(t2(i2)%keys%key(:))                                !--- Keys number in current section
656      ixck = strIdx(t1(i1)%keys%key(:), t2(i2)%keys%key(:))          !--- Common keys indexes
657
658      !=== APPEND NEW KEYS
659      tr(i1)%keys%key = [ tr(i1)%keys%key, PACK(tr(i2)%keys%key, MASK = ixck==0)]
660      tr(i1)%keys%val = [ tr(i1)%keys%val, PACK(tr(i2)%keys%val, MASK = ixck==0)]
661
662      !--- KEEP TRACK OF THE COMPONENTS NAMES
663      tr(i1)%component = TRIM(tr(i1)%component)//','//TRIM(tr(i2)%component)
664
665      !--- SELECT COMMON TRACERS WITH DIFFERING KEYS VALUES (PREVIOUS VALUE IS KEPT)
666      DO k2=1,nk2
667        k1 = ixck(k2); IF(k1 == 0) CYCLE
668        IF(t1(i1)%keys%val(k1) == t2(i2)%keys%val(k2)) ixck(k2)=0
669      END DO
670      IF(ALL(ixck==0)) CYCLE                                         !--- No identical keys with /=values
671
672      !--- DISPLAY INFORMATION: OLD VALUES ARE KEPT FOR THE KEYS FOUND IN PREVIOUS AND CURRENT SECTIONS
673      CALL msg('Key(s)'//TRIM(s1), modname)
674      DO k2 = 1, nk2                                                 !--- Loop on keys found in both t1(:) and t2(:)
675        knam = t2(i2)%keys%key(k2)                                   !--- Name of the current key
676        k1 = ixck(k2)                                                !--- Corresponding index in t1(:)
677        IF(k1 == 0) CYCLE                                            !--- New keys are skipped
678        v1 = t1(i1)%keys%val(k1); v2 = t2(i2)%keys%val(k2)           !--- Key values in t1(:) and t2(:)
679        CALL msg(' * '//TRIM(knam)//'='//TRIM(v2)//' ; previous value kept:'//TRIM(v1), modname)
680      END DO
681      !------------------------------------------------------------------------------------------------------------------------
682    END DO
683    !--------------------------------------------------------------------------------------------------------------------------
684  END DO
685  CALL sortTracers(tr)
686
687END FUNCTION mergeTracers
688!==============================================================================================================================
689
690!==============================================================================================================================
691LOGICAL FUNCTION cumulTracers(sections, tr) RESULT(lerr)
692  TYPE(dataBase_type),  TARGET, INTENT(IN)  :: sections(:)
693  TYPE(trac_type), ALLOCATABLE, INTENT(OUT) ::       tr(:)
694  TYPE(trac_type), POINTER     :: t1(:), t2(:)
695  INTEGER,   ALLOCATABLE :: nt(:)
696  CHARACTER(LEN=maxlen)  :: tnam, tnam_new
697  INTEGER :: iq, nq, is, ns, nsec
698  lerr = .FALSE.                                                     !--- Can't fail ; kept to match "mergeTracer" interface.
699  nsec =  SIZE(sections)
700  tr = [(      sections(is)%trac(:) , is=1, nsec )]                  !--- Concatenated tracers vector
701  nt = [( SIZE(sections(is)%trac(:)), is=1, nsec )]                  !--- Number of tracers in each section
702  !----------------------------------------------------------------------------------------------------------------------------
703  DO is=1, nsec                                                      !=== LOOP ON SECTIONS
704  !----------------------------------------------------------------------------------------------------------------------------
705    t1 => sections(is)%trac(:)
706    !--------------------------------------------------------------------------------------------------------------------------
707    DO iq=1, nt(is)                                                  !=== LOOP ON TRACERS
708    !--------------------------------------------------------------------------------------------------------------------------
709      tnam = t1(iq)%name                                             !--- Original name
710      IF(COUNT(t1%name == tnam) == 1) CYCLE                          !--- Current tracer is not duplicated: finished
711      tnam_new = TRIM(tnam)//phases_sep//TRIM(sections(is)%name)     !--- Same with section extension
712      nq = SUM(nt(1:is-1))                                           !--- Number of tracers in previous sections
713      ns = nt(is)                                                    !--- Number of tracers in the current section
714      tr(iq + nq)%name = tnam_new                                    !--- Modify tracer name
715      WHERE(tr(1+nq:ns+nq)%parent==tnam) tr(1+nq:ns+nq)%parent=tnam_new  !--- Modify parent name
716    !--------------------------------------------------------------------------------------------------------------------------
717    END DO
718  !----------------------------------------------------------------------------------------------------------------------------
719  END DO
720  !----------------------------------------------------------------------------------------------------------------------------
721  CALL sortTracers(tr)
722END FUNCTION cumulTracers
723!==============================================================================================================================
724
725!==============================================================================================================================
726SUBROUTINE setDirectKeys(tr)
727  TYPE(trac_type), INTENT(INOUT) :: tr(:)
728  CALL indexUpdate(tr)                                               !--- Update iqParent and iqDescen indexes vectors
729!  DO iq = 1, SIZE(tr)
730!    tr(iq)%keys%<key> = getKey_prv(it, "<key>", tr%keys,  tran0 )   !--- For additional keys
731!  END DO
732END SUBROUTINE setDirectKeys
733!==============================================================================================================================
734
735!==============================================================================================================================
736LOGICAL FUNCTION dispTraSection(message, sname, modname) RESULT(lerr)
737  CHARACTER(LEN=*), INTENT(IN) :: message, sname, modname
738  INTEGER :: idb, iq, nq
739  INTEGER, ALLOCATABLE :: hadv(:), vadv(:)
740  TYPE(trac_type), POINTER :: tm(:)
741  lerr = .FALSE.
742  idb = strIdx(dBase(:)%name, sname); IF(idb == 0) RETURN
743  tm => dBase(idb)%trac
744  nq = SIZE(tm)
745  IF(test(getKeyByName_im('hadv', hadv, tm(:)%name, tm(:)%keys),lerr)) RETURN
746  IF(test(getKeyByName_im('vadv', vadv, tm(:)%name, tm(:)%keys),lerr)) RETURN
747  CALL msg(TRIM(message)//':', modname)
748  IF(test(dispTable('iiissis', ['iq        ','hadv      ','vadv      ','short name','parent    ','igen      ','phase     '], &
749    cat(tm(:)%name,  tm(:)%parent, tm(:)%phase), cat([(iq, iq=1, nq)],  hadv,  vadv, tm(:)%iGeneration)), lerr)) RETURN
750END FUNCTION dispTraSection
751!==============================================================================================================================
752!==============================================================================================================================
753
754
755!==============================================================================================================================
756!== CREATE A SCALAR ALIAS OF THE COMPONENT OF THE TRACERS DESCRIPTOR "t" NAMED "tname" ========================================
757!==============================================================================================================================
758FUNCTION aliasTracer(tname, t) RESULT(out)
759  TYPE(trac_type),         POINTER    :: out
760  CHARACTER(LEN=*),        INTENT(IN) :: tname
761  TYPE(trac_type), TARGET, INTENT(IN) :: t(:)
762  INTEGER :: it
763  it = strIdx(t(:)%name, tname)
764  out => NULL(); IF(it /= 0) out => t(it)
765END FUNCTION aliasTracer
766!------------------------------------------------------------------------------------------------------------------------------
767
768
769!==============================================================================================================================
770!=== FROM A LIST OF INDEXES OR NAMES, CREATE A SUBSET OF THE TRACERS DESCRIPTORS LIST "trac" ==================================
771!==============================================================================================================================
772FUNCTION trSubset_Indx(trac,idx) RESULT(out)
773  TYPE(trac_type), ALLOCATABLE             ::  out(:)
774  TYPE(trac_type), ALLOCATABLE, INTENT(IN) :: trac(:)
775  INTEGER,                      INTENT(IN) ::  idx(:)
776  out = trac(idx)
777  CALL indexUpdate(out)
778END FUNCTION trSubset_Indx
779!------------------------------------------------------------------------------------------------------------------------------
780FUNCTION trSubset_Name(trac,nam) RESULT(out)
781  TYPE(trac_type), ALLOCATABLE             ::  out(:)
782  TYPE(trac_type), ALLOCATABLE, INTENT(IN) :: trac(:)
783  CHARACTER(LEN=*),             INTENT(IN) ::  nam(:)
784  out = trac(strIdx(trac(:)%name, nam))
785  CALL indexUpdate(out)
786END FUNCTION trSubset_Name
787!------------------------------------------------------------------------------------------------------------------------------
788
789
790!==============================================================================================================================
791!=== CREATE THE SUBSET OF THE TRACERS DESCRIPTORS LIST "trac" HAVING THE FIRST GENERATION ANCESTOR NAMED "nam" ================
792!==============================================================================================================================
793FUNCTION trSubset_gen0Name(trac,nam) RESULT(out)
794  TYPE(trac_type), ALLOCATABLE             ::  out(:)
795  TYPE(trac_type), ALLOCATABLE, INTENT(IN) :: trac(:)
796  CHARACTER(LEN=*),             INTENT(IN) ::  nam
797  out = trac(strFind(delPhase(trac(:)%gen0Name), nam))
798  CALL indexUpdate(out)
799END FUNCTION trSubset_gen0Name
800!------------------------------------------------------------------------------------------------------------------------------
801
802
803!==============================================================================================================================
804!=== UPDATE THE INDEXES iqParent, iqDescend AND iGeneration IN THE TRACERS DESCRIPTOR LIST "tr" (USEFULL FOR SUBSETS) =========
805!==============================================================================================================================
806SUBROUTINE indexUpdate(tr)
807  TYPE(trac_type), INTENT(INOUT) :: tr(:)
808  INTEGER :: iq, ig, ng, ngen
809  INTEGER, ALLOCATABLE :: ix(:)
810  tr(:)%iqParent = strIdx( tr(:)%name, tr(:)%parent )                !--- Parent index
811  ngen = MAXVAL(tr(:)%iGeneration, MASK=.TRUE.)
812  DO iq = 1, SIZE(tr)
813    ng = tr(iq)%iGeneration                                          !--- Generation of the current tracer
814    ix = idxAncestor(tr, igen = ng); ix = PACK(ix, ix/=0)            !--- Indexes of the tracers with ancestor tr(iq)
815    !--- Childs indexes in growing generation order
816    tr(iq)%iqDescen = [( PACK(ix, MASK = tr(ix)%iGeneration == ig), ig = ng+1, ngen)]
817    tr(iq)%nqDescen =     SUM(  [( COUNT(tr(ix)%iGeneration == ig), ig = ng+1, ngen)] )
818    tr(iq)%nqChilds =              COUNT(tr(ix)%iGeneration == ng+1)
819  END DO
820END SUBROUTINE indexUpdate
821!------------------------------------------------------------------------------------------------------------------------------
822 
823 
824!==============================================================================================================================
825!=== READ FILE "fnam" TO APPEND THE "dBase" TRACERS DATABASE WITH AS MUCH SECTIONS AS PARENTS NAMES IN "isot(:)%parent":   ====
826!===  * Each section dBase(i)%name contains the isotopes "dBase(i)%trac(:)" descending on "dBase(i)%name"="iso(i)%parent"  ====
827!===  * For each isotopes class, the <key>=<val> vector of each tracer is moved into the isotopes descriptor "isot"        ====
828!=== NOTES:                                                                                                                ====
829!===  * Most of the "isot" components have been defined in the calling routine (initIsotopes):                             ====
830!===      prnt,   nzon, zone(:),   niso, keys(:)%name,   nitr, trac(:),   npha, phas,  iTraPha(:,:),  iZonPhi(:,:)         ====
831!===  * Same syntax for isotopes file and "tracer.def": a tracers section contains one line for each of its isotopes       ====
832!===  * Each tracers section can contain a "params" virtual isotope line of isotopes parameters default values             ====
833!===  * In case keys are found both in the "params" section and the "*.def" file, the later value is retained              ====
834!===  * On each isotope line, defined keys can be used for other keys defintions (single level depth substitution)         ====
835!===  * The routine gives an error if a required isotope is not available in the database stored in "fnam"                 ====
836!==============================================================================================================================
837LOGICAL FUNCTION readIsotopesFile(fnam, isot) RESULT(lerr)
838  CHARACTER(LEN=*),        INTENT(IN)    :: fnam                     !--- Input file name
839  TYPE(isot_type), TARGET, INTENT(INOUT) :: isot(:)                  !--- Isotopes descriptors (field "prnt" must be defined !)
840  INTEGER :: ik, is, it, idb, nk0, i, iis
841  INTEGER :: nk, ns, nt, ndb, nb0, i0
842  CHARACTER(LEN=maxlen), POINTER     :: k(:), v(:), k0(:), v0(:)
843  CHARACTER(LEN=maxlen), ALLOCATABLE :: vals(:)
844  CHARACTER(LEN=maxlen)              :: val, modname
845  TYPE(keys_type),           POINTER ::   ky(:)
846  TYPE(trac_type),           POINTER ::   tt(:), t
847  TYPE(dataBase_type),   ALLOCATABLE ::  tdb(:)
848  LOGICAL,               ALLOCATABLE :: liso(:)
849  modname = 'readIsotopesFile'
850
851  !--- THE INPUT FILE MUST BE PRESENT
852  IF(test(fmsg('Missing isotopes parameters file "'//TRIM(fnam)//'"', modname, testFile(fnam)),lerr)) RETURN
853
854  !--- READ THE FILE SECTIONS, ONE EACH PARENT TRACER
855  nb0 = SIZE(dBase, DIM=1)+1                                         !--- Next database element index
856  IF(test(readSections(fnam,strStack(isot(:)%parent,',')),lerr)) RETURN !--- Read sections, one each parent tracer
857  ndb = SIZE(dBase, DIM=1)                                           !--- Current database size
858  DO idb = nb0, ndb
859   iis = idb-nb0+1
860
861    !--- GET FEW GLOBAL KEYS FROM "def" FILES AND ADD THEM TO THE 'params' SECTION
862    CALL addKeysFromDef(dBase(idb)%trac, 'params')
863
864    !--- SUBSTITUTE THE KEYS DEFINED IN THE 'params' VIRTUAL TRACER ; SUBSTITUTE LOCAL KEYS ; REMOVE 'params' VIRTUAL TRACER
865    CALL subDefault(dBase(idb)%trac, 'params', .TRUE.)
866
867    tt => dBase(idb)%trac
868
869    !--- REDUCE THE EXPRESSIONS TO OBTAIN SCALARS AND TRANSFER THEM TO THE "isot" ISOTOPES DESCRIPTORS VECTOR
870    DO it = 1, SIZE(dBase(idb)%trac)
871      t => dBase(idb)%trac(it)
872      is = strIdx(isot(iis)%keys(:)%name, t%name)                    !--- Index in "isot(iis)%keys(:)%name" of isotope "t%name"
873      IF(is == 0) CYCLE
874      liso = reduceExpr(t%keys%val, vals)                            !--- Reduce expressions (for substituted variables)
875      IF(test(ANY(liso), lerr)) RETURN                               !--- Some non-numerical elements were found
876      isot(iis)%keys(is)%key = PACK(t%keys%key, MASK=.NOT.liso)
877      isot(iis)%keys(is)%val = PACK(  vals,     MASK=.NOT.liso)
878    END DO
879
880    !--- CHECK FOR MISSING ISOTOPES (NO KEYS ALLOCATED)
881    liso = [( ALLOCATED(isot(iis)%keys(is)%key), is=1, SIZE(isot(iis)%keys) )]
882    IF(test(checkList(isot(iis)%keys(:)%name, .NOT.liso, &
883      'Check file "'//TRIM(fnam)//'" in section "'//TRIM(dBase(idb)%name)//'"', 'isotopes', 'missing'),lerr)) RETURN
884  END DO
885
886  !--- CLEAN THE DATABASE ENTRIES
887  IF(nb0 == 1) THEN
888    DEALLOCATE(dBase); ALLOCATE(dBase(0))
889  ELSE
890    ALLOCATE(tdb(nb0-1)); tdb(1:nb0-1)=dBase(1:nb0-1); CALL MOVE_ALLOC(FROM=tdb, TO=dBase)
891  END IF
892  lerr = dispIsotopes(isot, 'Isotopes parameters read from file', modname)
893
894END FUNCTION readIsotopesFile
895!==============================================================================================================================
896
897!==============================================================================================================================
898!=== IF ISOTOPES (2ND GENERATION TRACERS) ARE DETECTED:                                                                     ===
899!===    * COMPUTE MOST OF THE RELATED QUANTITIES ("isot" COMPONENTS).                                                       ===
900!===    * COMPUTE FEW ISOTOPES-DEDICATED "trac" COMPONENTS                                                                  ===
901!===    * CALL readIsotopesFile TO GET PHYSICAL QUANTITIES (<key>=<val> PAIRS)                                              ===
902!===      NOTE: THIS IS DONE HERE (IN A ROUTINE CALLED BY THE DYNAMIC), BECAUSE THE DYNAMIC NEEDS FEW PHYSICAL PARAMETERS.  ===
903!==============================================================================================================================
904SUBROUTINE initIsotopes(trac, isot)
905  TYPE(trac_type), ALLOCATABLE, TARGET, INTENT(INOUT) :: trac(:)
906  TYPE(isot_type), ALLOCATABLE, TARGET, INTENT(INOUT) :: isot(:)
907  CHARACTER(LEN=maxlen), ALLOCATABLE :: p(:), str(:)                 !--- Temporary storage
908  CHARACTER(LEN=maxlen) :: iname
909  CHARACTER(LEN=1)   :: ph                                           !--- Phase
910  INTEGER :: nbIso, ic, ip, iq, it, iz
911  LOGICAL, ALLOCATABLE :: ll(:)                                      !--- Mask
912  TYPE(trac_type), POINTER   ::  t(:), t1
913  TYPE(isot_type), POINTER   ::  s
914
915  t => trac
916
917  p = PACK(delPhase(t%parent), MASK = t%type=='tracer' .AND. t%iGeneration==2) !--- Parents of 2nd generation isotopes
918  CALL strReduce(p, nbIso)
919  ALLOCATE(isot(nbIso))
920
921  IF(nbIso==0) RETURN                                                !=== NO ISOTOPES: FINISHED
922
923  !--- ISOTOPES RELATED VARIABLES ; NULL OR EMPTY IF NO ISOTOPES
924  isot(:)%parent = p
925  DO ic = 1, SIZE(p)                                                 !--- Loop on isotopes classes
926    s => isot(ic)
927    iname = s%parent                                                 !--- Current isotopes class name (parent tracer name)
928
929    !=== Isotopes childs of tracer "iname": mask, names, number (same for each phase of "iname")
930    ll = t(:)%type=='tracer' .AND. delPhase(t(:)%parent) == iname .AND. t(:)%phase == 'g'
931    str = PACK(delPhase(t(:)%name), MASK = ll)                       !--- Effectively found isotopes of "iname"
932    s%niso = SIZE(str)                                               !--- Number of "effectively found isotopes of "iname"
933    ALLOCATE(s%keys(s%niso))
934    FORALL(it = 1:s%niso) s%keys(it)%name = str(it)
935
936    !=== Geographic tagging tracers descending on tracer "iname": mask, names, number
937    ll = t(:)%type=='tag'    .AND. delPhase(t(:)%gen0Name) == iname .AND. t(:)%iGeneration == 3
938    s%zone = PACK(strTail(t(:)%name,'_',lFirst=.TRUE.), MASK = ll)   !--- Tagging zones names  for isotopes category "iname"
939    CALL strReduce(s%zone)
940    s%nzon = SIZE(s%zone)                                            !--- Tagging zones number for isotopes category "iname"
941
942    !=== Geographic tracers of the isotopes childs of tracer "iname" (same for each phase of "iname")
943    !    NOTE: One might like to create a similar variable for 2nd generation tagging tracers (tagging the gen1 tracers)
944    str = PACK(delPhase(t(:)%name), MASK=ll)
945    CALL strReduce(str)
946    s%nitr = s%niso + SIZE(str)                                      !--- Number of isotopes + their geographic tracers [ntraciso]
947    ALLOCATE(s%trac(s%nitr))
948    FORALL(it = 1:s%niso) s%trac(it) = s%keys(it)%name
949    FORALL(it = s%niso+1:s%nitr) s%trac(it) = str(it-s%niso)
950
951    !=== Phases for tracer "iname"
952    s%phase = ''
953    DO ip = 1, nphases; ph = known_phases(ip:ip); IF(strIdx(t%name,addPhase(iname, ph)) /= 0) s%phase = TRIM(s%phase)//ph; END DO
954    s%npha = LEN_TRIM(s%phase)                                        !--- Equal to "nqo" for water
955
956    !=== Tables giving the index in a table of effectively found items for each dynamical tracer (1<=iq<=nqtot)
957    DO iq = 1, SIZE(t)
958      t1 => trac(iq)
959      IF(delPhase(t1%gen0Name) /= iname) CYCLE                       !--- Only deal with tracers descending on "iname"
960      t1%iso_iGroup = ic                                             !--- Isotopes family       idx in list "isotopes(:)%parent"
961      t1%iso_iName  = strIdx(s%trac, delPhase(strHead(t1%name,'_'))) !--- Current isotope       idx in effective isotopes list
962      t1%iso_iZone  = strIdx(s%zone,          strTail(t1%name,'_') ) !--- Current isotope zone  idx in effective zones    list
963      t1%iso_iPhase =  INDEX(s%phase,TRIM(t1%phase))                 !--- Current isotope phase idx in effective phases   list
964      IF(t1%iGeneration /= 3) t1%iso_iZone = 0                       !--- Skip possible generation 2 tagging tracers
965    END DO
966
967    !=== Table used to get iq (index in dyn array, size nqtot) from the isotope and phase indexes ; the full isotopes list
968    !    (including tagging tracers) is sorted this way:  iso1, iso2, ..., iso1_zone1, iso2_zone1, ..., iso1_zoneN, iso2_zoneN
969    s%iTraPha = RESHAPE( [( (strIdx(t(:)%name,  addPhase(s%trac(it),s%phase(ip:ip))),    it=1, s%nitr), ip=1, s%npha)], &
970                         [s%nitr, s%npha] )
971
972    !=== Table used to get ix (index in tagging tracers isotopes list, size nitr) from the zone and isotope indexes
973    s%iZonIso = RESHAPE( [( (strIdx(s%trac(:), TRIM(s%trac(it))//'_'//TRIM(s%zone(iz))), iz=1, s%nzon), it=1, s%niso)], &
974                         [s%nzon, s%niso] )
975  END DO
976
977  !=== READ PHYSICAL PARAMETERS FROM "isotopes_params.def" FILE
978  !    DONE HERE, AND NOT ONLY IN "infotrac_phy", BECAUSE SOME PHYSICAL PARAMS ARE NEEDED FOR RESTARTS (tnat AND alpha_ideal)
979  IF(readIsotopesFile('isotopes_params.def',isot)) CALL abort_gcm(modname,'Problem when reading isotopes parameters',1)
980
981END SUBROUTINE initIsotopes
982!==============================================================================================================================
983
984
985!==============================================================================================================================
986LOGICAL FUNCTION dispIsotopes(ides, message, modname) RESULT(lerr)
987  TYPE(isot_type),  INTENT(IN) :: ides(:)                            !--- Isotopes descriptor vector
988  CHARACTER(LEN=*), INTENT(IN) :: message                            !--- Message to display
989  CHARACTER(LEN=*), INTENT(IN) :: modname                            !--- Calling subroutine name
990  INTEGER :: ik, nk, ip, it, nt
991  CHARACTER(LEN=maxlen) :: prf
992  CHARACTER(LEN=maxlen), ALLOCATABLE :: ttl(:), val(:,:)
993  CALL msg(TRIM(message)//':', modname)
994  DO ip = 1, SIZE(ides)                                              !--- Loop on parents tracers
995    nk = SIZE(ides(ip)%keys(1)%key)                                  !--- Same keys for each isotope
996    nt = SIZE(ides(ip)%keys)                                         !--- Number of isotopes
997    prf = 'i'//REPEAT('s',nk+1)                                      !--- Profile for table printing
998    ALLOCATE(ttl(nk+2), val(nt,nk+1))
999    ttl(1:2) = ['iq  ','name']; ttl(3:nk+2) = ides(ip)%keys(1)%key(:)!--- Titles line with keys names
1000    val(:,1) = ides(ip)%keys(:)%name                                 !--- Values table 1st column: isotopes names 
1001    DO ik = 1, nk
1002      DO it = 1, nt
1003        val(it,ik+1) = ides(ip)%keys(it)%val(ik)                     !--- Other columns: keys values
1004      END DO
1005    END DO
1006    IF(test(fmsg('Problem with the table content', modname, dispTable(prf, ttl, val, cat([(it,it=1,nt)]), rFmt='(EN8.4)')), &
1007       lerr)) RETURN
1008    DEALLOCATE(ttl, val)
1009  END DO       
1010END FUNCTION dispIsotopes
1011!==============================================================================================================================
1012
1013
1014!==============================================================================================================================
1015SUBROUTINE addKey_1(key, val, ky, lOverWrite)
1016!------------------------------------------------------------------------------------------------------------------------------
1017! Purpose: Add the <key>=<val> pair in the "ky" keys descriptor.
1018!------------------------------------------------------------------------------------------------------------------------------
1019  CHARACTER(LEN=*),  INTENT(IN)    :: key, val
1020  TYPE(keys_type),   INTENT(INOUT) :: ky
1021  LOGICAL, OPTIONAL, INTENT(IN)    :: lOverWrite
1022  CHARACTER(LEN=maxlen), ALLOCATABLE :: k(:), v(:)
1023  INTEGER :: iky, nky
1024  LOGICAL :: lo
1025!------------------------------------------------------------------------------------------------------------------------------
1026  lo=.FALSE.; IF(PRESENT(lOverWrite)) lo=lOverWrite
1027  iky = strIdx(ky%key,key)
1028  IF(iky == 0) THEN
1029    nky = SIZE(ky%key)
1030    IF(nky == 0) THEN; ky%key = [key]; ky%val = [val]; ELSE; ky%key = [ky%key, key]; ky%val = [ky%val, val]; END IF
1031  ELSE IF(lo) THEN                                                   !--- Overwriting
1032    ky%key(iky) = key; ky%val(iky) = val
1033  END IF
1034END SUBROUTINE addKey_1
1035!==============================================================================================================================
1036SUBROUTINE addKey_m(key, val, ky, lOverWrite)
1037!------------------------------------------------------------------------------------------------------------------------------
1038! Purpose: Add the <key>=<val> pair in all the components of the "ky" keys descriptor.
1039!------------------------------------------------------------------------------------------------------------------------------
1040  CHARACTER(LEN=*),  INTENT(IN)    :: key, val
1041  TYPE(keys_type),   INTENT(INOUT) :: ky(:)
1042  LOGICAL, OPTIONAL, INTENT(IN)    :: lOverWrite
1043  INTEGER :: itr
1044  LOGICAL :: lo
1045!------------------------------------------------------------------------------------------------------------------------------
1046  lo=.FALSE.; IF(PRESENT(lOverWrite)) lo=lOverWrite
1047  DO itr = 1, SIZE(ky); CALL addKey_1(key, val, ky(itr), lo); END DO
1048END SUBROUTINE addKey_m
1049!==============================================================================================================================
1050SUBROUTINE addKeysFromDef(t, tr0)
1051!------------------------------------------------------------------------------------------------------------------------------
1052! Purpose: The values of the keys of the tracer named "tr0" are overwritten by the values found in the *.def files, if any.
1053!------------------------------------------------------------------------------------------------------------------------------
1054  TYPE(trac_type), ALLOCATABLE, INTENT(INOUT) :: t(:)
1055  CHARACTER(LEN=*),             INTENT(IN)    :: tr0
1056  CHARACTER(LEN=maxlen) :: val
1057  INTEGER               :: ik, jd
1058  jd = strIdx(t%name, tr0)
1059  IF(jd == 0) RETURN
1060  DO ik = 1, SIZE(t(jd)%keys%key)
1061    CALL get_in(t(jd)%keys%key(ik), val, 'zzzz')
1062    IF(val /= 'zzzz') CALL addKey_1(t(jd)%keys%key(ik), val, t(jd)%keys, .TRUE.)
1063  END DO
1064END SUBROUTINE addKeysFromDef
1065!==============================================================================================================================
1066SUBROUTINE delKey_1(itr, keyn, ky)
1067!------------------------------------------------------------------------------------------------------------------------------
1068! Purpose: Internal routine.
1069!   Remove <key>=<val> pairs in the "itr"th component of the "ky" keys descriptor.
1070!------------------------------------------------------------------------------------------------------------------------------
1071  INTEGER,          INTENT(IN)    :: itr
1072  CHARACTER(LEN=*), INTENT(IN)    :: keyn(:)
1073  TYPE(trac_type),  INTENT(INOUT) :: ky(:)
1074  CHARACTER(LEN=maxlen), ALLOCATABLE :: k(:), v(:)
1075  LOGICAL,               ALLOCATABLE :: ll(:)
1076  INTEGER :: iky
1077!------------------------------------------------------------------------------------------------------------------------------
1078  IF(itr<=0 .OR. itr>SIZE(ky, DIM=1)) RETURN                          !--- Index is out of range
1079  ll = [( ALL(keyn/=ky(itr)%keys%key(iky)), iky=1, SIZE(ky(itr)%keys%key) )]
1080  k = PACK(ky(itr)%keys%key, MASK=ll); CALL MOVE_ALLOC(FROM=k, TO=ky(itr)%keys%key)
1081  v = PACK(ky(itr)%keys%val, MASK=ll); CALL MOVE_ALLOC(FROM=v, TO=ky(itr)%keys%val)
1082END SUBROUTINE delKey_1
1083!==============================================================================================================================
1084SUBROUTINE delKey(keyn, ky)
1085!------------------------------------------------------------------------------------------------------------------------------
1086! Purpose: Internal routine.
1087!   Remove <key>=<val> pairs in all the components of the "t" tracers descriptor.
1088!------------------------------------------------------------------------------------------------------------------------------
1089  CHARACTER(LEN=*), INTENT(IN)    :: keyn(:)
1090  TYPE(trac_type),  INTENT(INOUT) :: ky(:)
1091  INTEGER :: iky
1092!------------------------------------------------------------------------------------------------------------------------------
1093  DO iky = 1, SIZE(ky); CALL delKey_1(iky, keyn, ky); END DO
1094END SUBROUTINE delKey
1095!==============================================================================================================================
1096
1097
1098!==============================================================================================================================
1099!=== PUBLIC ROUTINES: GET A KEY FROM A <key>=<val> LIST ; VECTORS, TRACER AND DATABASE VERSIONS ===============================
1100!=== BEWARE !!! IF THE "ky" ARGUMENT IS NOT PRESENT, THEN THE VARIABLES "tracers" AND "isotopes" ARE USED. ====================
1101!===     THEY ARE LOCAL TO THIS MODULE, SO MUST MUST BE INITIALIZED FIRST USING the "getKey_init" ROUTINE  ====================
1102!==============================================================================================================================
1103SUBROUTINE getKey_init(tracers_, isotopes_)
1104  TYPE(trac_type), OPTIONAL, INTENT(IN) ::  tracers_(:)
1105  TYPE(isot_type), OPTIONAL, INTENT(IN) :: isotopes_(:)
1106  IF(PRESENT( tracers_))  tracers =  tracers_
1107  IF(PRESENT(isotopes_)) isotopes = isotopes_
1108END SUBROUTINE getKey_init
1109!==============================================================================================================================
1110CHARACTER(LEN=maxlen) FUNCTION fgetKey(itr, keyn, ky, def_val) RESULT(out)
1111!------------------------------------------------------------------------------------------------------------------------------
1112! Purpose: Internal function ; get a key value in string format (this is the returned argument).
1113!------------------------------------------------------------------------------------------------------------------------------
1114  INTEGER,                    INTENT(IN) :: itr
1115  CHARACTER(LEN=*),           INTENT(IN) :: keyn
1116  TYPE(keys_type),            INTENT(IN) :: ky(:)
1117  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: def_val
1118!------------------------------------------------------------------------------------------------------------------------------
1119  INTEGER :: ik
1120  ik = 0; IF(itr>0 .AND. itr<=SIZE(ky)) ik = strIdx(ky(itr)%key(:), keyn)
1121  out = '';              IF(ik /= 0) out = ky(itr)%val(ik)           !--- Key was found
1122  IF(PRESENT(def_val) .AND. ik == 0) out = def_val                   !--- Default value from arguments
1123END FUNCTION fgetKey
1124!==============================================================================================================================
1125LOGICAL FUNCTION getKeyByName_s1(keyn, val, tname, ky) RESULT(lerr)
1126  !--- Purpose: Get the value of the key named "keyn" for the tracer named "tnam".
1127  !     * "ky" unspecified: try in "tracers" for "tnam" with phase and tagging suffixes, then in "isotopes" without.
1128  !     * "ky"   specified: try in "ky"      for "tnam" with phase and tagging suffixes, then without.
1129  !    The returned error code is always .FALSE.: an empty string is returned when the key hasn't been found.
1130  CHARACTER(LEN=*),          INTENT(IN)  :: keyn
1131  CHARACTER(LEN=maxlen),     INTENT(OUT) :: val
1132  CHARACTER(LEN=*),          INTENT(IN)  :: tname
1133  TYPE(keys_type), OPTIONAL, INTENT(IN)  :: ky(:)
1134  INTEGER :: is
1135  lerr = .FALSE.
1136  IF(PRESENT(ky)) THEN
1137    val = getKeyByName_prv(keyn, tname , ky);    IF(val /= '') RETURN          !--- "ky" and "tnam"
1138    val = getKeyByName_prv(keyn, delPhase(strHead(tname,'_')), ky)             !--- "ky" and "tnam" without phase
1139  ELSE
1140    IF(.NOT.ALLOCATED(tracers))  RETURN
1141    val = getKeyByName_prv(keyn, tname, tracers(:)%keys); IF(val /= '') RETURN !--- "tracers" and "tnam"
1142    IF(.NOT.ALLOCATED(isotopes)) RETURN
1143    IF(SIZE(isotopes) == 0)      RETURN
1144    DO is = 1, SIZE(isotopes); IF(strIdx(isotopes(is)%keys(:)%name, delPhase(strHead(tname,'_'))) /= 0) EXIT; END DO
1145    IF(is /= 0) val = getKeyByName_prv(keyn, tname, isotopes(is)%keys(:))      !--- "isotopes" and "tnam" without phase
1146  END IF
1147
1148CONTAINS
1149
1150FUNCTION getKeyByName_prv(keyn, tname, ky) RESULT(val)
1151  CHARACTER(LEN=maxlen)         :: val
1152  CHARACTER(LEN=*), INTENT(IN)  :: keyn
1153  CHARACTER(LEN=*), INTENT(IN)  :: tname
1154  TYPE(keys_type),  INTENT(IN)  :: ky(:)
1155  INTEGER :: itr, iky
1156  val = ''; iky = 0
1157  itr = strIdx(ky(:)%name, tname);                 IF(itr==0) RETURN           !--- Get the index of the wanted tracer
1158  IF(itr /= 0) iky = strIdx(ky(itr)%key(:), keyn); IF(iky==0) RETURN           !--- Wanted key    index
1159  val = ky(itr)%val(iky)
1160END FUNCTION getKeyByName_prv
1161
1162END FUNCTION getKeyByName_s1
1163!==============================================================================================================================
1164LOGICAL FUNCTION getKeyByName_sm(keyn, val, tnam, ky) RESULT(lerr)
1165  CHARACTER(LEN=*),                   INTENT(IN)  :: keyn
1166  CHARACTER(LEN=maxlen), ALLOCATABLE, INTENT(OUT) ::  val(:)
1167  CHARACTER(LEN=*), TARGET, OPTIONAL, INTENT(IN)  :: tnam(:)
1168  TYPE(keys_type),  TARGET, OPTIONAL, INTENT(IN)  ::   ky(:)
1169  CHARACTER(LEN=maxlen),    POINTER :: n(:)
1170  INTEGER :: iq
1171  n => tracers(:)%keys%name; IF(PRESENT(tnam)) n => tnam(:)
1172  ALLOCATE(val(SIZE(n)))
1173  IF(     PRESENT(ky)) lerr = ANY([(getKeyByName_s1(keyn, val(iq), n(iq), ky), iq=1, SIZE(n))])
1174  IF(.NOT.PRESENT(ky)) lerr = ANY([(getKeyByName_s1(keyn, val(iq), n(iq)),     iq=1, SIZE(n))])
1175END FUNCTION getKeyByName_sm
1176!==============================================================================================================================
1177LOGICAL FUNCTION getKeyByName_i1(keyn, val, tnam, ky) RESULT(lerr)
1178  CHARACTER(LEN=*),          INTENT(IN)  :: keyn
1179  INTEGER,                   INTENT(OUT) :: val
1180  CHARACTER(LEN=*),          INTENT(IN)  :: tnam
1181  TYPE(keys_type), OPTIONAL, INTENT(IN)  :: ky(:)
1182  CHARACTER(LEN=maxlen) :: sval
1183  INTEGER :: ierr
1184  IF(     PRESENT(ky)) lerr = getKeyByName_s1(keyn, sval, tnam, ky)
1185  IF(.NOT.PRESENT(ky)) lerr = getKeyByName_s1(keyn, sval, tnam)
1186  IF(test(fmsg('key "'//TRIM(keyn)//'" or tracer "'//TRIM(tnam)//'" is missing',        modname, lerr), lerr)) RETURN
1187  READ(sval, *, IOSTAT=ierr) val
1188  IF(test(fmsg('key "'//TRIM(keyn)//'" of tracer "'//TRIM(tnam)//'" is not an integer', modname, lerr), lerr)) RETURN
1189END FUNCTION getKeyByName_i1
1190!==============================================================================================================================
1191LOGICAL FUNCTION getKeyByName_im(keyn, val, tnam, ky) RESULT(lerr)
1192  CHARACTER(LEN=*),                   INTENT(IN)  :: keyn
1193  INTEGER,               ALLOCATABLE, INTENT(OUT) ::  val(:)
1194  CHARACTER(LEN=*), TARGET, OPTIONAL, INTENT(IN)  :: tnam(:)
1195  TYPE(keys_type),  TARGET, OPTIONAL, INTENT(IN)  ::   ky(:)
1196  CHARACTER(LEN=maxlen), POINTER :: n(:)
1197  INTEGER :: iq
1198  n => tracers(:)%name; IF(PRESENT(tnam)) n => tnam(:)
1199  ALLOCATE(val(SIZE(n)))
1200  IF(     PRESENT(ky)) lerr = ANY([(getKeyByName_i1(keyn, val(iq), n(iq), ky), iq=1, SIZE(n))])
1201  IF(.NOT.PRESENT(ky)) lerr = ANY([(getKeyByName_i1(keyn, val(iq), n(iq)),     iq=1, SIZE(n))])
1202END FUNCTION getKeyByName_im
1203!==============================================================================================================================
1204LOGICAL FUNCTION getKeyByName_r1(keyn, val, tnam, ky) RESULT(lerr)
1205  CHARACTER(LEN=*),          INTENT(IN)  :: keyn
1206  REAL,                      INTENT(OUT) :: val
1207  CHARACTER(LEN=*),          INTENT(IN)  :: tnam
1208  TYPE(keys_type), OPTIONAL, INTENT(IN)  :: ky(:)
1209  CHARACTER(LEN=maxlen) :: sval
1210  INTEGER :: ierr
1211  IF(     PRESENT(ky)) lerr = getKeyByName_s1(keyn, sval, tnam, ky)
1212  IF(.NOT.PRESENT(ky)) lerr = getKeyByName_s1(keyn, sval, tnam)
1213  IF(test(fmsg('key "'//TRIM(keyn)//'" or tracer "'//TRIM(tnam)//'" is missing',    modname, lerr), lerr)) RETURN
1214  READ(sval, *, IOSTAT=ierr) val
1215  IF(test(fmsg('key "'//TRIM(keyn)//'" of tracer "'//TRIM(tnam)//'" is not a real', modname, lerr), lerr)) RETURN
1216END FUNCTION getKeyByName_r1
1217!==============================================================================================================================
1218LOGICAL FUNCTION getKeyByName_rm(keyn, val, tnam, ky) RESULT(lerr)
1219  CHARACTER(LEN=*),                   INTENT(IN)  :: keyn
1220  REAL,                  ALLOCATABLE, INTENT(OUT) ::  val(:)
1221  CHARACTER(LEN=*), TARGET, OPTIONAL, INTENT(IN)  :: tnam(:)
1222  TYPE(keys_type),  TARGET, OPTIONAL, INTENT(IN)  ::   ky(:)
1223  CHARACTER(LEN=maxlen), POINTER :: n(:)
1224  INTEGER :: iq
1225  n => tracers(:)%name;  IF(PRESENT(tnam)) n => tnam(:)
1226  ALLOCATE(val(SIZE(n)))
1227  IF(     PRESENT(ky)) lerr = ANY([(getKeyByName_r1(keyn, val(iq), n(iq), ky), iq=1, SIZE(n))])
1228  IF(.NOT.PRESENT(ky)) lerr = ANY([(getKeyByName_r1(keyn, val(iq), n(iq)),     iq=1, SIZE(n))])
1229END FUNCTION getKeyByName_rm
1230!==============================================================================================================================
1231
1232
1233!==============================================================================================================================
1234!=== REMOVE, IF ANY, OR ADD THE PHASE SUFFIX OF THE TRACER NAMED "s" ==========================================================
1235!==============================================================================================================================
1236ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION delPhase(s) RESULT(out)
1237  CHARACTER(LEN=*), INTENT(IN) :: s
1238  INTEGER :: l, i, ix
1239  out = s
1240  IF(s == '') RETURN                                                           !--- Empty string: nothing to do
1241  !--- Index of found phase in "known_phases"
1242  ix = MAXLOC( [(i, i=1,nphases)], MASK=[( INDEX(s, phases_sep//known_phases(i:i))/=0, i=1, nphases)], DIM=1 )
1243  IF(ix == 0) RETURN                                                           !--- No phase pattern found
1244  i = INDEX(s, phases_sep//known_phases(ix:ix))                                !--- Index of <sep><pha> pattern in "str"
1245  l = LEN_TRIM(s)
1246  IF(i == l-1) THEN                                                            !--- <var><sep><pha>       => return <var>
1247    out = s(1:l-2)
1248  ELSE IF(s(i+2:i+2) == '_') THEN                                              !--- <var><sep><pha>_<tag> => return <var>_<tag>
1249    out = s(1:i-1)//s(i+2:l)
1250  END IF
1251END FUNCTION delPhase
1252!------------------------------------------------------------------------------------------------------------------------------
1253CHARACTER(LEN=maxlen) FUNCTION addPhase_1(s,pha) RESULT(out)
1254  CHARACTER(LEN=*), INTENT(IN) :: s
1255  CHARACTER(LEN=1), INTENT(IN) :: pha
1256  INTEGER :: l, i
1257  out = s
1258  IF(s == '') RETURN                                                           !--- Empty string: nothing to do
1259  i = INDEX(s, '_')                                                            !--- /=0 for <var>_<tag> tracers names
1260  l = LEN_TRIM(s)
1261  IF(i == 0) out =  TRIM(s)//phases_sep//pha                                   !--- <var>       => return <var><sep><pha>
1262  IF(i /= 0) out = s(1:i-1)//phases_sep//pha//'_'//s(i+1:l)                    !--- <var>_<tag> => return <var><sep><pha>_<tag>
1263END FUNCTION addPhase_1
1264!------------------------------------------------------------------------------------------------------------------------------
1265FUNCTION addPhase_m(s,pha) RESULT(out)
1266  CHARACTER(LEN=*),      INTENT(IN)  :: s(:)
1267  CHARACTER(LEN=1),      INTENT(IN)  :: pha
1268  CHARACTER(LEN=maxlen), ALLOCATABLE :: out(:) 
1269  INTEGER :: k
1270  out = [( addPhase_1(s(k), pha), k=1, SIZE(s) )]
1271END FUNCTION addPhase_m
1272!------------------------------------------------------------------------------------------------------------------------------
1273
1274
1275!==============================================================================================================================
1276!=== GET THE NAME(S) OF THE ANCESTOR(S) OF TRACER(S) "tname" AT GENERATION "igen"  IN THE TRACERS DESCRIPTORS LIST "tr" =======
1277!==============================================================================================================================
1278CHARACTER(LEN=maxlen) FUNCTION ancestor_1(t, tname, igen) RESULT(out)
1279  TYPE(trac_type),   INTENT(IN) :: t(:)
1280  CHARACTER(LEN=*),  INTENT(IN) :: tname
1281  INTEGER, OPTIONAL, INTENT(IN) :: igen
1282  INTEGER :: ig, ix
1283  ig = 1; IF(PRESENT(igen)) ig = igen
1284  ix = idxAncestor_1(t, tname, ig)
1285  out = ''; IF(ix /= 0) out = t(ix)%name
1286END FUNCTION ancestor_1
1287!------------------------------------------------------------------------------------------------------------------------------
1288FUNCTION ancestor_m(t, tname, igen) RESULT(out)
1289  CHARACTER(LEN=maxlen), ALLOCATABLE     ::   out(:)
1290  TYPE(trac_type),            INTENT(IN) ::     t(:)
1291  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: tname(:)
1292  INTEGER,          OPTIONAL, INTENT(IN) :: igen
1293  INTEGER, ALLOCATABLE :: ix(:)
1294  INTEGER :: ig
1295  ig = 1; IF(PRESENT(igen)) ig = igen
1296  IF(     PRESENT(tname)) ix = idxAncestor_m(t, tname,     ig)
1297  IF(.NOT.PRESENT(tname)) ix = idxAncestor_m(t, t(:)%name, ig)
1298  ALLOCATE(out(SIZE(ix))); out(:) = ''
1299  WHERE(ix /= 0) out = t(ix)%name
1300END FUNCTION ancestor_m
1301!==============================================================================================================================
1302
1303
1304!==============================================================================================================================
1305!=== GET THE INDEX(ES) OF THE ANCESTOR(S) OF TRACER(S) "tname" AT GENERATION "igen"  IN THE TRACERS DESCRIPTORS LIST "tr" =====
1306!==============================================================================================================================
1307INTEGER FUNCTION idxAncestor_1(t, tname, igen) RESULT(out)
1308! Return the name of the generation "igen" ancestor of "tname"
1309  TYPE(trac_type),   INTENT(IN) :: t(:)
1310  CHARACTER(LEN=*),  INTENT(IN) :: tname
1311  INTEGER, OPTIONAL, INTENT(IN) :: igen
1312  INTEGER :: ig
1313  ig = 1; IF(PRESENT(igen)) ig = igen
1314  out = strIdx(t(:)%name, tname)
1315  IF(out == 0)          RETURN
1316  IF(t(out)%iGeneration <= ig) RETURN
1317  DO WHILE(t(out)%iGeneration > ig); out = strIdx(t(:)%name, t(out)%parent); END DO
1318END FUNCTION idxAncestor_1
1319!------------------------------------------------------------------------------------------------------------------------------
1320FUNCTION idxAncestor_m(t, tname, igen) RESULT(out)
1321  INTEGER,          ALLOCATABLE          ::   out(:)
1322  TYPE(trac_type),            INTENT(IN) ::     t(:)
1323  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: tname(:)
1324  INTEGER,          OPTIONAL, INTENT(IN) :: igen
1325  INTEGER :: ig, ix
1326  ig = 1; IF(PRESENT(igen)) ig = igen
1327  IF(     PRESENT(tname)) out = [(idxAncestor_1(t, tname(ix),  ig), ix=1, SIZE(tname))]
1328  IF(.NOT.PRESENT(tname)) out = [(idxAncestor_1(t, t(ix)%name, ig), ix=1, SIZE(t))]
1329END FUNCTION idxAncestor_m
1330!==============================================================================================================================
1331
1332
1333END MODULE readTracFiles_mod
Note: See TracBrowser for help on using the repository browser.