source: LMDZ6/branches/LMDZ-tracers/libf/dyn3d_common/infotrac.F90 @ 3852

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

Extension of the tracers management.

The tracers files can be:

1) "traceur.def": old format, with:

  • the number of tracers on the first line
  • one line for each tracer: <tracer name> <hadv> <vadv> [<parent name>]

2) "tracer.def": new format with one section each model component.
3) "tracer_<name>.def": new format with a single section.

The formats 2 and 3 reading is driven by the "type_trac" key, which can be a

coma-separated list of components.

  • Format 2: read the sections from the "tracer.def" file.
  • format 3: read one section each "tracer_<section name>.def" file.
  • the first line of a section is "&<section name>
  • the other lines start with a tracer name followed by <key>=<val> pairs.
  • the "default" tracer name is reserved ; the other tracers of the section inherit its <key>=<val>, except for the keys that are redefined locally.

This format helps keeping the tracers files compact, thanks to the "default"
special tracer and the three levels of factorization:

  • on the tracers names: a tracer name can be a coma-separated list of tracers => all the tracers of the list have the same <key>=<val> properties
  • on the parents names: the value of the "parent" property can be a coma-separated list of tracers => only possible for geographic tagging tracers
  • on the phases: the property "phases" is [g](l][s] (gas/liquid/solid)

Read information is stored in the vector "tracers(:)", of derived type "tra".

"isotopes_params.def" is a similar file, with one section each isotopes family.
It contains a database of isotopes properties ; if there are second generation
tracers (isotopes), the corresponding sections are read.

Read information is stored in the vector "isotopes(:)", of derived type "iso".

The "getKey" function helps to get the values of the parameters stored in
"tracers" or "isotopes".

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:keywords set to Id
File size: 36.9 KB
Line 
1MODULE infotrac
2
3  USE       strings_mod, ONLY: msg, find, strIdx,  strFind,  strHead, dispTable, cat, get_in,  &
4                              fmsg, test, int2str, strParse, strTail, strReduce, strStack, modname, testFile
5  USE readTracFiles_mod, ONLY: readTracersFiles, getKey_init, nphases, delPhase, aliasTracer, &
6                        tran0, readIsotopesFile, getKey, known_phases, addPhase, indexUpdate
7  USE trac_types_mod,    ONLY: tra, iso, kys
8
9  IMPLICIT NONE
10
11  PRIVATE
12
13  !=== FOR TRACERS:
14  PUBLIC :: tra,   tracers,  type_trac                     !--- Derived type, full database, tracers type keyword
15  PUBLIC :: nqtot,   nbtr,   nqo                           !--- Main dimensions
16  PUBLIC :: infotrac_init, aliasTracer                     !--- Initialization, tracers alias creation
17  PUBLIC :: itr_indice                                     !--- Indexes of the tracers passed to phytrac
18  PUBLIC :: niadv                                          !--- Indexes of true tracers (<=nqtot, such that iadv(idx)>0)
19  PUBLIC :: solsym, conv_flg, pbl_flg
20
21  !=== FOR ISOTOPES: General
22  !--- General
23  PUBLIC :: iso, isotopes, nbIso                           !--- Derived type, full isotopes families database + nb of families
24  PUBLIC :: isoSelect , ixIso                              !--- Isotopes family selection tool + selected family index
25  !=== FOR ISOTOPES: Specific to H2O isotopes
26  PUBLIC :: iH2O, tnat, alpha_ideal                        !--- H2O isotopes index, natural abundance, fractionning coeff.
27  !=== FOR ISOTOPES: Depending on selected isotopes family
28  PUBLIC :: isotope, isoKeys                               !--- Selected isotopes database + associated keys (cf. getKey)
29  PUBLIC :: isoName, isoZone, isoPhas                      !--- Isotopes and tagging zones names, phases
30  PUBLIC :: niso, nzon, npha, nitr                         !---  " " numbers + isotopes & tagging tracers number
31  PUBLIC :: iZonIso, iTraPha                               !--- 2D index tables to get "iq" index
32  PUBLIC :: isoCheck                                       !--- Run isotopes checking routines
33
34  !=== FOR BOTH TRACERS AND ISOTOPES
35  PUBLIC :: getKey                                         !--- Get a key from "tracers" or "isotope"
36
37  !=== FOR STRATOSPHERIC AEROSOLS
38#ifdef CPP_StratAer
39  PUBLIC :: nbtr_bin, nbtr_sulgas, id_OCS_strat, id_H2SO4_strat, id_SO2_strat, id_BIN01_strat, id_TEST_strat
40#endif
41
42  INTERFACE isoSelect; MODULE PROCEDURE isoSelectByIndex, isoSelectByName; END INTERFACE isoSelect
43
44!=== CONVENTIONS FOR TRACERS NUMBERS:
45!  |--------------------+----------------------+-----------------+---------------+----------------------------|
46!  | water in different |    water tagging     |  water isotopes | other tracers | additional tracers moments |
47!  | phases: H2O-[gls]  |      isotopes        |                 |               |  for higher order schemes  |
48!  |--------------------+----------------------+-----------------+---------------+----------------------------|
49!  |                    |                      |                 |               |                            |
50!  |<--     nqo      -->|<-- nqo*niso* nzon -->|<-- nqo*niso  -->|<--  nbtr   -->|<--        (nmom)        -->|         
51!  |                    |                                        |                                            |
52!  |                    |<-- nqo*niso*(nzon+1)  =   nqo*nitr  -->|<--    nqtottr = nbtr + nmom             -->|
53!  |                                                                             = nqtot - nqo*(nitr+1)       |
54!  |                                                                                                          |
55!  |<--                        nqtrue  =  nbtr + nqo*(nitr+1)                 -->|                            |
56!  |                                                                                                          |
57!  |<--                        nqtot   =  nqtrue + nmom                                                    -->|
58!  |                                                                                                          |
59!  |----------------------------------------------------------------------------------------------------------|
60! NOTES FOR THIS TABLE:
61!  * The used "niso", "nzon" and "nitr" are the H2O components of "isotopes(ip)"  (isotopes(ip)%prnt == 'H2O'),
62!    since water is so far the sole tracers family removed from the main tracers table.
63!  * For water, "nqo" is equal to the more general field "isotopes(ip)%npha".
64!  * "niso", "nzon", "nitr", "npha" are defined for other isotopic tracers families, if any.
65!
66!=== TRACERS DESCRIPTOR: DERIVED TYPE EMBEDDING MOST OF THE USEFUL QUANTITIES (LENGTH: nqtot)
67!    Each entry is accessible using "%" sign.
68!  |------------+-------------------------------------------------+-------------+------------------------+
69!  |  entry     | Meaning                                         | Former name | Possible values        |
70!  |------------+-------------------------------------------------+-------------+------------------------+
71!  | name       | Name (short)                                    | tname       |                        |
72!  | nam1       | Name of the 1st generation ancestor             | /           |                        |
73!  | prnt       | Name of the parent                              | /           |                        |
74!  | lnam       | Long name (with adv. scheme suffix) for outputs | ttext       |                        |
75!  | type       | Type (so far: tracer or tag)                    | /           | tracer,tag             |
76!  | phas       | Phases list ("g"as / "l"iquid / "s"olid)        | /           | [g][l][s]              |
77!  | iadv       | Advection scheme number                         | iadv        | 1-20,30 exc. 3-9,15,19 |
78!  | igen       | Generation (>=1)                                | /           |                        |
79!  | itr        | Index in "tr_seri" (0: absent from physics)     | cf. niadv   | 1:nqtottr              |
80!  | iprnt      | Index of the parent tracer                      | iqpere      | 1:nqtot                |
81!  | idesc      | Indexes of the childs (all generations)         | iqfils      | 1:nqtot                |
82!  | ndesc      | Number of the descendants (all generations)     | nqdesc      | 1:nqtot                |
83!  | nchld      | Number of childs (first generation only)        | nqfils      | 1:nqtot                |
84!  | keys       | key/val pairs accessible with "getKey" routine  | /           |                        |
85!  | iso_num    | Isotope name  index in iso(igr)%name(:)         | iso_indnum  | 1:niso                 |
86!  | iso_zon    | Isotope zone  index in iso(igr)%zone(:)         | zone_num    | 1:nzon                 |
87!  | iso_pha    | Isotope phase index in iso(igr)%phas            | phase_num   | 1:npha                 |
88!  +------------+-------------------------------------------------+-------------+------------------------+
89!
90!=== ISOTOPES DESCRIPTOR: DERIVED TYPE EMBEDDING MOST OF THE USEFUL QUANTITIES (LENGTH: NUMBER OF ISOTOPES FAMILIES USED)
91!    Each entry is accessible using "%" sign.
92!  |------------+-------------------------------------------------+-------------+-----------------------+
93!  |  entry     | Meaning                                         | Former name | Possible values       |
94!  |------------+-------------------------------------------------+-------------+-----------------------+
95!  | prnt       | Parent tracer (isotopes family name)            |             |                       |
96!  | trac, nitr | Isotopes & tagging tracers + number of elements |             |                       |
97!  | zone, nzon | Geographic tagging zones   + number of elements |             |                       |
98!  | phas, npha | Phases list                + number of elements |             | [g][l][s], 1:3        |
99!  | niso       | Number of isotopes, excluding tagging tracers   |             |                       |
100!  | iTraPha    | Index in "xt" = f(iname(niso+1:nitr),iphas)     | iqiso       | 1:niso                |
101!  | iZonIso    | Index in "xt" = f(izone, iname(1:niso))         | index_trac  | 1:nzon                |
102!  |------------+-------------------------------------------------+-------------+-----------------------+
103
104
105
106  !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
107  INTEGER,            SAVE :: nqtot, &                     !--- Tracers nb in dynamics (incl. higher moments & water)
108                              nbtr,  &                     !--- Tracers nb in physics  (excl. higher moments & water)
109                              nqo,   &                     !--- Number of water phases
110                              nbIso                        !--- Number of available isotopes family
111  CHARACTER(LEN=256), SAVE :: type_trac                    !--- Keyword for tracers type
112!$OMP THREADPRIVATE(nqtot, nbtr, nqo, nbIso, type_trac)
113
114  !=== DERIVED TYPES EMBEDDING MOST INFORMATIONS ABOUT TRACERS AND ISOTOPES FAMILIES
115  TYPE(tra), TARGET,  SAVE, ALLOCATABLE ::  tracers(:)      !=== TRACERS DESCRIPTORS VECTOR
116  TYPE(iso), TARGET,  SAVE, ALLOCATABLE :: isotopes(:)      !=== ISOTOPES PARAMETERS VECTOR
117!$OMP THREADPRIVATE(tracers, isotopes)
118
119  !=== ALIASES FOR CURRENTLY SELECTED ISOTOPES FAMILY OF VARIABLES EMBEDDED IN THE VECTOR "isotopes"
120  TYPE(iso),          SAVE, POINTER :: isotope             !--- CURRENTLY SELECTED ISOTOPES FAMILY DESCRIPTOR
121  INTEGER,            SAVE          :: ixIso, iH2O         !--- Index of the selected isotopes family and H2O family
122  LOGICAL,            SAVE, POINTER :: isoCheck            !--- Flag to trigger the checking routines
123  TYPE(kys),          SAVE, POINTER :: isoKeys(:)          !--- ONE SET OF KEYS FOR EACH ISOTOPE (LISTED IN isoName)
124  CHARACTER(LEN=256), SAVE, POINTER :: isoName(:),       & !--- ISOTOPES NAMES FOR THE CURRENTLY SELECTED FAMILY
125                                       isoZone(:),       & !--- TAGGING ZONES  FOR THE CURRENTLY SELECTED FAMILY
126                                       isoPhas             !--- USED PHASES    FOR THE CURRENTLY SELECTED FAMILY
127  INTEGER,            SAVE          :: niso, nzon, npha, & !--- NUMBER OF ISOTOPES, TAGGING ZONES AND PHASES
128                                       nitr                !--- NUMBER OF ISOTOPES + ISOTOPIC TAGGING TRACERS
129  INTEGER,            SAVE, POINTER :: iZonIso(:,:)        !--- INDEX IN "isoTrac" AS f(tagging zone, isotope)
130  INTEGER,            SAVE, POINTER :: iTraPha(:,:)        !=== INDEX IN "isoTrac" AS f(isotopic tracer, phase)
131!$OMP THREADPRIVATE(isotope, ixIso,iH2O, isoCheck, isoKeys, isoName,isoZone,isoPhas, niso,nzon,npha,nitr, iZonIso,iTraPha)
132
133  !=== VARIABLES EMBEDDED IN "tracers", BUT DUPLICATED, AS THEY ARE RATHER FREQUENTLY USED + VARIABLES FOR INCA
134  REAL,               SAVE, ALLOCATABLE ::     tnat(:),  & !--- Natural relative abundance of water isotope        (niso)
135                                        alpha_ideal(:)     !--- Ideal fractionning coefficient (for initial state) (niso)
136  INTEGER,            SAVE, ALLOCATABLE :: conv_flg(:),  & !--- Convection     activation ; needed for INCA        (nbtr)
137                                            pbl_flg(:),  & !--- Boundary layer activation ; needed for INCA        (nbtr)
138                                         itr_indice(:),  & !--- Indexes of the tracers passed to phytrac        (nqtottr)
139                                              niadv(:)
140  CHARACTER(LEN=8),   SAVE, ALLOCATABLE ::   solsym(:)     !--- Names from INCA                                    (nbtr)
141!OMP THREADPRIVATE(tnat, alpha_ideal, conv_flg, pbl_flg, itr_indice, solsym)
142
143#ifdef CPP_StratAer
144  !=== SPECIFIC TO STRATOSPHERIC AEROSOLS (CK/OB)
145  INTEGER, SAVE :: nbtr_bin, nbtr_sulgas, id_OCS_strat, id_H2SO4_strat, id_SO2_strat, id_BIN01_strat, id_TEST_strat
146!OMP THREADPRIVATE(nbtr_bin, nbtr_sulgas, id_OCS_strat, id_H2SO4_strat, id_SO2_strat, id_BIN01_strat, id_TEST_strat)
147#endif
148
149CONTAINS
150
151SUBROUTINE infotrac_init
152  USE control_mod, ONLY: planet_type, config_inca
153#ifdef REPROBUS
154  USE chem_rep,    ONLY: Init_chem_rep_trac
155#endif
156!==============================================================================================================================
157!
158!   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
159!   -------
160!
161!   Modifications:
162!   --------------
163!   05/94: F.Forget      Modif special traceur
164!   02/02: M-A Filiberti Lecture de traceur.def
165!   06/20: D. Cugnet     Nouveaux tracer.def et tracer_*.def + encapsulation (types tr et iso)
166!
167!   Objet:
168!   ------
169!   GCM LMD nouvelle grille
170!
171!==============================================================================================================================
172!   ... modification de l'integration de q ( 26/04/94 ) ....
173!------------------------------------------------------------------------------------------------------------------------------
174! Declarations:
175!  INCLUDE "dimensions.h"
176
177!------------------------------------------------------------------------------------------------------------------------------
178! Local variables
179  INTEGER, ALLOCATABLE :: hadv(:), hadv_inca(:), &                   !--- Horizontal/vertical transport scheme number
180                          vadv(:), vadv_inca(:)                      !--- + specific INCA versions
181  CHARACTER(LEN=1)   :: ph                                           !--- Phase
182  CHARACTER(LEN=2)   ::   suff(9)                                    !--- Suffixes for schemes of order 3 or 4 (Prather)
183  CHARACTER(LEN=3)   :: descrq(30)                                   !--- Advection scheme description
184  CHARACTER(LEN=4)   :: oldH2O(3)                                    !--- Old water names
185  CHARACTER(LEN=256) :: newH2O, iname, isoPhase                      !--- New water and isotope names, phases list
186  CHARACTER(LEN=256) :: msg1, msg2                                   !--- Strings for messages
187  CHARACTER(LEN=256), ALLOCATABLE, DIMENSION(:) :: &                 !--- Temporary storage
188             isoName, isoZone, tra0, zon0, tag0, n, p, z, str
189  INTEGER :: fType                                                   !--- Tracers description file type ; 0: none
190                                                                     !--- 1: "traceur.def"  2: "tracer.def"  3: "tracer_*.def"
191  INTEGER :: nqtrue                                                  !--- Tracers nb from tracer.def (no higher order moments)
192  INTEGER :: iad                                                     !--- Advection scheme
193  INTEGER :: iH2O                                                    !--- Index in "isotopes(:)" of H2O family
194  INTEGER :: ic,ip,iq,jq, it,nt, im,nm, ix, iz, niso, nzone, ntiso   !--- Indexes and temporary variables
195  LOGICAL, ALLOCATABLE :: lisoGen2(:), &                             !--- Mask for second generation isotopes
196                          lisoName(:), &                             !--- Mask for water isotopes
197                          lisoZone(:), ll(:)                         !--- Mask for water isotopes tagging tracers
198  LOGICAL :: lerr
199  TYPE(tra), ALLOCATABLE, TARGET :: ttr(:)
200  TYPE(tra), POINTER             :: t1, t(:)
201  TYPE(iso), POINTER             :: s
202!------------------------------------------------------------------------------------------------------------------------------
203! Initialization :
204!------------------------------------------------------------------------------------------------------------------------------
205  modname = 'infotrac_init'
206  type_trac='lmdz'!'lmdz,inca'
207  suff          = ['x ','y ','z ','xx','xy','xz','yy','yz','zz']
208  descrq( 1: 2) = ['LMV','BAK']
209  descrq(10:20) = ['VL1','VLP','FH1','FH2','VLH','   ','PPM','PPS','PPP','   ','SLP']
210  descrq(30)    =  'PRA'
211  oldH2O        = ['H2Ov','H2Ol','H2Oi']
212
213  !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
214  CALL msg('type_trac='//TRIM(type_trac))
215  IF(strParse(type_trac, ',', str, n=nt)) CALL abort_gcm(modname,'can''t parse "type_trac = '//TRIM(type_trac)//'"',1)
216  DO it = 1, nt                                                      !--- nt>1 if "type_trac" is a coma-separated keywords list
217    msg1 = 'For type_trac = "'//TRIM(str(it))//'":'
218    SELECT CASE(str(it))
219      CASE('inca'); CALL msg(TRIM(msg1)//' coupling with INCA chemistry model, config_inca='//config_inca)
220      CASE('repr'); CALL msg(TRIM(msg1)//' coupling with REPROBUS chemistry model')
221      CASE('co2i'); CALL msg(TRIM(msg1)//' you have chosen to run with CO2 cycle')
222      CASE('coag'); CALL msg(TRIM(msg1)//' tracers are treated for COAGULATION tests')
223      CASE('lmdz'); CALL msg(TRIM(msg1)//' tracers are treated in LMDZ only')
224      CASE DEFAULT
225        CALL abort_gcm(modname,'type_trac='//TRIM(str(it))//' not possible yet.',1)
226    END SELECT
227  END DO
228
229  !--- COHERENCE TEST BETWEEN "type_trac", "config_inca" AND PREPROCESSING KEYS
230  DO it=1,nt
231    SELECT CASE(type_trac)
232      CASE('inca'); IF(ALL(['aero', 'aeNP', 'chem']/=config_inca)) &
233        CALL abort_gcm(modname, 'Mismatch between type_trac and config_inca. Please modify "run.def"',1)
234#ifndef INCA
235        CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code',1)
236#endif
237      CASE('repr')
238#ifndef REPROBUS
239        CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code',1)
240#endif
241      CASE('coag')
242#ifndef CPP_StratAer
243        CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code',1)
244#endif
245    END SELECT
246  END DO
247
248  !--- Disable "config_inca" option for a run without INCA if it differs from "none"
249  IF (ALL(str(:) /= 'inca') .AND. config_inca /= 'none') THEN
250    CALL msg('setting config_inca="none" as you do not couple with INCA model')
251    config_inca = 'none'
252  END IF
253
254!------------------------------------------------------------------------------------------------------------------------------
255! 1) Get the numbers of: true tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid)
256!    (here, "true" tracers means declared tracers, first order only)
257!    Deal with the advection scheme choice for water and tracers:
258!     iadv = 1    "LMDZ-specific humidity transport" (for H2O vapour)          LMV
259!     iadv = 2    backward                           (for H2O liquid)          BAK
260!     iadv = 14   Van-Leer + specific humidity, modified by Francis Codron     VLH
261!     iadv = 10   Van-Leer (chosen for vapour and liquid water)                VL1
262!     iadv = 11   Van-Leer for hadv and PPM version (Monotonic) for vadv       VLP
263!     iadv = 12   Frederic Hourdin I                                           FH1
264!     iadv = 13   Frederic Hourdin II                                          FH2
265!     iadv = 16   Monotonic         PPM (Collela & Woodward 1984)              PPM
266!     iadv = 17   Semi-monotonic    PPM (overshoots allowed)                   PPS
267!     iadv = 18   Definite positive PPM (overshoots and undershoots allowed)   PPP
268!     iadv = 20   Slopes                                                       SLP
269!     iadv = 30   Prather                                                      PRA
270!
271!        In array q(ij,l,iq) : iq = 1          for vapour water
272!                              iq = 2          for liquid water
273!                             [iq = 3          for ice    water]
274!        And optionaly:        iq = 3[4],nqtot for other tracers
275!------------------------------------------------------------------------------------------------------------------------------
276!    Get choice of advection scheme from file tracer.def or from INCA
277!------------------------------------------------------------------------------------------------------------------------------
278
279  IF(readTracersFiles(type_trac, fType, tracers)) CALL abort_gcm(modname,'problem with tracers file(s)',1)
280  CALL msg(fType == 0, 'WARNING: USING DEFAULT VALUES !')
281
282  !----------------------------------------------------------------------------------------------------------------------------
283  SELECT CASE(fType)
284  !----------------------------------------------------------------------------------------------------------------------------
285    CASE(0)                                                          !=== NO READABLE TRACERS CONFIG FILE => DEFAULT
286    !--------------------------------------------------------------------------------------------------------------------------
287      IF(planet_type=='earth') THEN                                  !--- Default for Earth
288        nqo = 2; nbtr = 2
289        tracers(:)%name = ['H2O-g','H2O-l','RN   ','PB   ']
290        tracers(:)%prnt = [tran0  ,tran0  ,tran0  ,tran0  ]
291        tracers(:)%igen = [1      ,1      ,1      ,1      ]
292        hadv            = [14     ,10     ,10     ,10     ]
293        vadv            = [14     ,10     ,10     ,10     ]
294      ELSE                                                           !--- Default for other planets
295        nqo = 0; nbtr = 1
296        tracers(:)%name = ['dummy']
297        tracers(:)%prnt = ['dummy']
298        tracers(:)%igen = [1      ]
299        hadv            = [10     ]
300        vadv            = [10     ]
301      END IF
302      nqtrue = nbtr + nqo
303    !--------------------------------------------------------------------------------------------------------------------------
304    CASE(1)
305    !--------------------------------------------------------------------------------------------------------------------------
306      IF(type_trac=='inca') THEN                                     !=== OLD STYLE "traceur.def" FOR INCA FOUND
307      !------------------------------------------------------------------------------------------------------------------------
308        nqo = SIZE(tracers(:), DIM=1)
309        WRITE(msg1,'(a,i0)')'Only 2 or 3 water phases allowed ; found nqo=',nqo
310        IF(nqo/=2 .AND. nqo/=3) CALL abort_gcm(modname,TRIM(msg1),1)
311#ifdef INCA
312        CALL Init_chem_inca_trac(nbtr)                                   !--- Get nbtr from INCA
313#endif
314        ALLOCATE(hadv_inca(nbtr), vadv_inca(nbtr), conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr))
315#ifdef INCA
316        !--- Activation of:                      Convection, Boundary layer
317        CALL init_transport(hadv_inca, vadv_inca, conv_flg,   pbl_flg,   solsym)
318#endif
319        nqtrue = nbtr + nqo                                              !--- Total number of tracers
320        ALLOCATE(ttr(nqtrue)); ttr(1:nqo) = tracers(1:nqo)
321        DO iq = nqo+1, nqtrue
322          ttr(iq)%name = solsym(iq)
323          ttr(iq)%prnt = tran0
324          ttr(iq)%igen = 1
325          hadv = hadv_inca(iq-nqo)
326          vadv = vadv_inca(iq-nqo)
327        END DO
328        CALL MOVE_ALLOC(FROM=ttr, TO=tracers)
329      !------------------------------------------------------------------------------------------------------------------------
330      ELSE                                                           !=== OLD STYLE "traceur.def" CONFIG FILE FOUND
331      !------------------------------------------------------------------------------------------------------------------------
332        nqo = 0
333        DO ip = 1, SIZE(oldH2O)
334          ix = strIdx(tracers(:)%name,oldH2O(ip))                    !--- Old name of water in a specific phase (ix/=0)
335          IF(ix == 0) CYCLE
336          newH2O = 'H2O-'//known_phases(ip:ip)                       !--- Corresponding new name
337          nqo = nqo+1; tracers(ix)%name = newH2O                     !--- One more water phase ; replace old name with one
338          tracers(strFind(tracers(:)%nam1,oldH2O(ip)))%nam1 = newH2O
339          tracers(strFind(tracers(:)%prnt,oldH2O(ip)))%prnt = newH2O
340        END DO
341        nqtrue = SIZE(tracers,DIM=1)
342        nbtr   = nqtrue - nqo
343      END IF
344    !--------------------------------------------------------------------------------------------------------------------------
345    CASE DEFAULT                                                     !=== FOUND NEW STYLE TRACERS CONFIG FILE(S)
346    !--------------------------------------------------------------------------------------------------------------------------
347      nqo    = 2; IF(ANY(tracers(:)%name == 'H2O-s')) nqo=3
348      nqtrue = SIZE(tracers, DIM=1)
349      nbtr   = nqtrue - nqo
350  !----------------------------------------------------------------------------------------------------------------------------
351  END SELECT
352  !----------------------------------------------------------------------------------------------------------------------------
353  CALL getKey_init(tracers)
354  IF(.NOT.ALLOCATED(hadv)) lerr = getKey('hadv', hadv)
355  IF(.NOT.ALLOCATED(vadv)) lerr = getKey('vadv', vadv)
356  IF(.NOT.ALLOCATED(solsym)) ALLOCATE(solsym(nbtr))
357  IF(.NOT.ALLOCATED(conv_flg)) conv_flg = [(1, it=1, nbtr)]
358  IF(.NOT.ALLOCATED( pbl_flg))  pbl_flg = [(1, it=1, nbtr)]
359
360#ifdef CPP_StratAer
361  IF (type_trac == 'coag') THEN
362    nbtr_bin=0
363    nbtr_sulgas=0
364    DO iq = 1, nqtrue
365      IF(tracers(iq)%name(1:3)=='BIN') nbtr_bin    = nbtr_bin   +1
366      IF(tracers(iq)%name(1:3)=='GAS') nbtr_sulgas = nbtr_sulgas+1
367      SELECT CASE(tracers(iq)%name)
368        CASE('BIN01');    id_BIN01_strat = iq - nqo; CALL msg('id_BIN01_strat=', id_BIN01_strat)
369        CASE('GASOCS');   id_OCS_strat   = iq - nqo; CALL msg('id_OCS_strat  =', id_OCS_strat)
370        CASE('GASSO2');   id_SO2_strat   = iq - nqo; CALL msg('id_SO2_strat  =', id_SO2_strat)
371        CASE('GASH2SO4'); id_H2SO4_strat = iq - nqo; CALL msg('id_H2SO4_strat=', id_H2SO4_strat)
372        CASE('GASTEST');  id_TEST_strat  = iq - nqo; CALL msg('id_TEST_strat=' , id_TEST_strat)
373      END SELECT
374    END DO
375    CALL msg('nbtr_bin      =',nbtr_bin)
376    CALL msg('nbtr_sulgas   =',nbtr_sulgas)
377  END IF
378#endif
379
380  !--- Transfert number of tracers to Reprobus
381#ifdef REPROBUS
382  IF(type_trac == 'repr') CALL Init_chem_rep_trac(nbtr,nqo,tracers(:)%name)
383#endif
384
385!------------------------------------------------------------------------------------------------------------------------------
386! 2) Verify if the advection scheme 20 or 30 have been chosen.
387!    Calculate total number of tracers needed: nqtot
388!    Allocate variables depending on total number of tracers
389!------------------------------------------------------------------------------------------------------------------------------
390  DO iq = 1, nqtrue
391    t1 => tracers(iq)
392    IF( hadv(iq)<20 .OR. (ANY(hadv(iq)==[20,30]) .AND. hadv(iq)==vadv(iq)) ) CYCLE
393    WRITE(msg1,'(2(a,i0))')' is not available: hadv=',hadv(iq),', vadv=',vadv(iq)
394    CALL msg('This choice of advection scheme for "'//TRIM(t1%name)//'"'//TRIM(msg1))
395    CALL abort_gcm(modname,'Bad choice of advection scheme',1)
396  END DO
397  nqtot =    COUNT( hadv< 20 .AND. vadv< 20 ) &                      !--- No additional tracer
398        +  4*COUNT( hadv==20 .AND. vadv==20 ) &                      !--- 3  additional tracers
399        + 10*COUNT( hadv==30 .AND. vadv==30 )                        !--- 9  additional tracers
400
401  ! More tracers due to the choice of advection scheme => assign total number of tracers
402  IF( nqtot /= nqtrue ) THEN
403    CALL msg('The choice of advection scheme for one or more tracers makes it necessary to add tracers')
404    CALL msg('The number of true tracers is '//TRIM(int2str(nqtrue)))
405    CALL msg('The total number of tracers needed is '//TRIM(int2str(nqtot)))
406  END IF
407  ALLOCATE(ttr(nqtot))
408
409!------------------------------------------------------------------------------------------------------------------------------
410! 3) Determine iadv, long and short name, generation number, phase and region
411!------------------------------------------------------------------------------------------------------------------------------
412  jq = 0; ttr(:)%iadv = -1
413  DO iq = 1, nqtrue
414    jq = jq + 1
415    t1 => tracers(iq)
416
417    !--- Verify choice of advection schema
418    iad = -1
419    IF(hadv(iq)     ==    vadv(iq)    ) iad = hadv(iq)
420    IF(hadv(iq)==10 .AND. vadv(iq)==16) iad = 11
421    CALL msg(iad == -1, 'This choice of advection scheme for "'//TRIM(t1%name)//'" '//'is not available: hadv = ' &
422                            //TRIM(int2str(hadv(iq)))//', vadv='//TRIM(int2str(vadv(iq))) )
423    IF(iad == -1) CALL abort_gcm(modname,'Bad choice of advection scheme - 2',1)
424    t1%lnam = t1%name; IF(iad /= 0) t1%lnam=TRIM(t1%name)//descrq(iad)
425
426    !--- Defining most fields of the tracer derived type
427    ttr(jq)%name = t1%name
428    ttr(jq)%nam1 = t1%nam1
429    ttr(jq)%prnt = t1%prnt
430    ttr(jq)%lnam = t1%lnam
431    ttr(jq)%type = t1%type
432    ttr(jq)%phas = t1%phas
433    ttr(jq)%iadv = iad
434    ttr(jq)%igen = t1%igen
435
436    IF(ALL([20,30] /= iad)) CYCLE                                    !--- 1st order scheme: finished
437    IF(iad == 20) nm = 3                                             !--- 2nd order scheme
438    IF(iad == 30) nm = 9                                             !--- 3rd order scheme
439    ttr(jq+1:jq+nm)%name = [ (TRIM(t1%name)//'-'//TRIM(suff(im)), im=1, nm) ]
440    ttr(jq+1:jq+nm)%nam1 = [ (TRIM(t1%nam1)//'-'//TRIM(suff(im)), im=1, nm) ]
441    ttr(jq+1:jq+nm)%lnam = [ (TRIM(t1%lnam)//'-'//TRIM(suff(im)), im=1, nm) ]
442    ttr(jq+1:jq+nm)%prnt = t1%prnt
443    ttr(jq+1:jq+nm)%type = t1%type
444    ttr(jq+1:jq+nm)%phas = t1%phas
445    ttr(jq+1:jq+nm)%iadv = -iad
446    ttr(jq+1:jq+nm)%igen = t1%igen
447    jq = jq + nm
448  END DO
449  DEALLOCATE(hadv, vadv)
450
451  !--- Determine parent and childs indexes
452  CALL indexUpdate(ttr)
453
454  !=== TEST ADVECTION SCHEME
455  DO iq=1,nqtot ; t1 => ttr(iq); iad = t1%iadv
456    WRITE(msg1,'(a,i0)')'This LMDZ version has not been tested for option iadv=',iad
457    WRITE(msg2,'(a,i2,a)')'iadv=',iad,' not implemented yet for'
458
459    !--- ONLY TESTED VALUES FOR TRACERS FOR NOW: iadv = 14, 10 (and 0)
460    IF(ALL( [10,14,0] /= iad) ) CALL abort_gcm(modname, TRIM(msg1)//' ; only iadv=10 and iadv=14 are tested !', 1)
461
462    !--- ONLY TESTED VALUES FOR CHILDS  FOR NOW: iadv = 10     (CHILDS:  TRACERS OF GENERATION GREATER THAN 1)
463    IF(fmsg(iad/=10.AND.t1%igen>1,'WARNING ! '//TRIM(msg2)//' childs.  Setting iadv=10 for "'//TRIM(t1%name)//'".')) t1%iadv=10
464
465    !--- ONLY TESTED VALUES FOR PARENTS FOR NOW: iadv = 14, 10 (PARENTS: TRACERS OF GENERATION 1)
466    IF(t1%igen==1 .AND. ALL([10,14]/=iad)) CALL abort_gcm(modname, TRIM(msg2)//' parents: schemes 10 or 14 only !', 1)
467
468    !--- iadv = 14 IS ONLY VALID FOR WATER VAPOUR
469    IF(fmsg(iad==14 .AND. t1%name(1:5)/='H2O-g', 'WARNING ! '//TRIM(msg1)//', found for "' &
470                 //TRIM(t1%name)//'" but only valid for water vapour ! Setting iadv=10 for "'//TRIM(t1%name)//'".')) t1%iadv=10
471  END DO
472
473  !=== DISPLAY THE RESULTING LIST
474  CALL msg('Information stored in infotrac :')
475  IF(dispTable('isssiii', ['iq       ','name     ','long name','parent   ','iadv     ','ipar     ','igen     '],       &
476       cat(ttr(:)%name, ttr(:)%lnam, ttr(:)%prnt), cat([(iq, iq=1, nqtot)], ttr(:)%iadv, ttr(:)%iprnt, ttr(:)%igen))) &
477       CALL abort_gcm(modname,"problem with the tracers table content",1)
478
479  CALL MOVE_ALLOC(FROM=ttr, TO=tracers)
480  t => tracers
481
482  !=== VARIABLES RELATED TO GENERATIONS
483  niadv = PACK( [(iq,iq=1,nqtot)], MASK=t(:)%iadv>=0)           !--- Indexes of "true" tracers
484
485  p = PACK(delPhase(t%prnt),MASK=t%type=='tracer'.AND.t%igen==2)!--- Parents of 2nd generation isotopes
486  CALL strReduce(p, nbIso)
487  ALLOCATE(isotopes(nbIso))
488
489  IF(nbIso==0) RETURN                                           !=== NO ISOTOPES: FINISHED
490
491  CALL msg('Isotopes families required: '//strStack(p))
492
493  !--- ISOTOPES RELATED VARIABLES ; NULL OR EMPTY IF NO ISOTOPES
494  isotopes(:)%prnt = p
495  DO ip = 1, SIZE(p)                                            !--- Loop on isotopes categories
496    s => isotopes(ip)
497    iname = s%prnt
498
499    !=== Geographic tagging tracers descending on tracer "iname": mask, names, number
500    lisoZone = t(:)%type=='tag'    .AND. delPhase(t(:)%nam1) == iname .AND. t(:)%igen == 3
501    s%zone = PACK(strTail(t(:)%name,'_'), MASK = lisoZone)      !--- Tagging zones names  for isotopes category "iname"
502    CALL strReduce(s%zone)
503    s%nzon = SIZE(s%zone)                                       !--- Tagging zones number for isotopes category "iname"
504
505    !=== Isotopes childs of tracer "iname": mask, names, number (same for each phase of "iname")
506    lisoName = t(:)%type=='tracer' .AND. delPhase(t(:)%prnt) == iname .AND. t(:)%phas == 'g'
507    ALLOCATE(s%keys(COUNT(lisoName)))
508    s%keys(:)%name = PACK(delPhase(t(:)%name), MASK = lisoName)    !--- Effectively found isotopes of "iname"
509    s%niso = SIZE(s%keys)                                       !--- Number of "effectively found isotopes of "iname"
510    s%trac = [s%keys%name, ((TRIM(s%keys(it)%name)//'_'//TRIM(s%zone(iz)), it=1, s%niso), iz=1, s%nzon)]
511    s%nitr = SIZE(s%trac)                                       !--- " + their geographic tracers               [ntraciso]
512
513    !=== Phases for tracer "iname"
514    s%phas = ''
515    DO ix = 1, nphases; IF(strIdx(t%name,addPhase(iname, known_phases(ix:ix))) /= 0) s%phas = TRIM(s%phas)//ph; END DO
516    s%npha = LEN_TRIM(s%phas)                                   !--- Equal to "nqo" for water
517
518    !=== Tables giving the index in a table of effectively found items for each dynamical tracer (1<=iq<=nqtot)
519    DO iq = 1, nqtot
520      t1 => tracers(iq)
521      IF(t1%nam1 /= iname) CYCLE                                 !--- Only deal with tracers descending on "iname"
522      t1%iso_igr = ip                                            !--- Index of isotopes family in list "isotopes(:)%prnt"
523      t1%iso_num = strIdx(s%trac, delPhase(strHead(t1%name,'_')))!--- Index of current isotope       in effective isotopes list
524      t1%iso_zon = strIdx(s%zone,          strTail(t1%name,'_') )!--- Index of current isotope zone  in effective zones    list
525      t1%iso_pha =  INDEX(s%phas,TRIM(t1%phas))                  !--- Index of current isotope phase in effective phases   list
526      IF(t1%igen /= 3) t1%iso_zon = 0                            !--- Skip possible generation 2 tagging tracers
527    END DO
528
529    !=== Table used to get iq (index in dyn array, size nqtot) from the isotope and phase indexes ; the full isotopes list
530    !    (including tagging tracers) is sorted this way:  iso1, iso2, ..., iso1_zone1, iso2_zone1, ..., iso1_zoneN, iso2_zoneN
531    s%iTraPha = RESHAPE( [( (strIdx(t(:)%name,  addPhase(s%trac(it),s%phas(ip:ip))),     it=1, s%nitr), ip=1, s%npha)], &
532                         [s%nitr, s%npha] )
533
534    !=== Table used to get ix (index in tagging tracers isotopes list, size nitr) from the zone and isotope indexes
535    s%iZonIso = RESHAPE( [( (strIdx(s%trac(:), TRIM(s%trac(it))//'_'//TRIM(s%zone(iz))), iz=1, s%nzon), it=1, s%niso)], &
536                         [s%nzon, s%niso] )
537  END DO
538
539  !=== Indexes, in dynamical tracers list, of the tracers transmitted to phytrac (nqtottr non-vanishing elements)
540  ll = delPhase(t%name)/='H2O' .AND. t%iso_num ==0              !--- Mask of tracers passed to the physics
541  t(:)%itr = UNPACK([(iq,iq=1,COUNT(ll))], ll, [(0, iq=1, nqtot)])
542  itr_indice = PACK(t(:)%itr, MASK = t(:)%itr/=0)               !--- Might be removed (t%itr should be enough)
543
544  !=== READ PHYSICAL PARAMETERS FROM "isotopes_params.def" FILE
545  !    DONE HERE, AND NOT ONLY IN "infotrac_phy", BECAUSE SOME PHYSICAL PARAMS ARE NEEDED FOR RESTARTS (tnat AND alpha_ideal)
546  IF(readIsotopesFile('isotopes_params.def',isotopes)) CALL abort_gcm(modname,'Problem when reading isotopes parameters',1)
547print*,'coincoin'
548
549  !=== Specific to water
550  CALL getKey_init(tracers, isotopes)
551  IF(isoSelect('H2O')) RETURN                                   !--- Select water isotopes ; finished if no water isotopes.
552  iH2O = ixIso                                                  !--- Keep track of water family index
553  lerr = getKey('tnat' ,tnat,        isoName)
554  lerr = getKey('alpha',alpha_ideal, isoName)
555  CALL msg('end')
556
557END SUBROUTINE infotrac_init
558
559
560!==============================================================================================================================
561!=== THE ROUTINE isoSelect IS USED TO SWITCH FROM AN ISOTOPE FAMILY TO ANOTHER: ISOTOPES DEPENDENT PARAMETERS ARE UPDATED
562!     Singe generic "isoSelect" routine, using the predefined parent index (fast version) or its name (first time).
563!==============================================================================================================================
564LOGICAL FUNCTION isoSelectByName(iName) RESULT(lerr)
565  CHARACTER(LEN=*), INTENT(IN)  :: iName
566  INTEGER :: iIso
567  iIso = strIdx(isotopes(:)%prnt, iName)
568  IF(test(fmsg(iIso == 0,'no isotope family named "'//TRIM(iName)//'"'),lerr)) RETURN
569  IF(isoSelectByIndex(iIso)) RETURN
570END FUNCTION isoSelectByName
571!==============================================================================================================================
572LOGICAL FUNCTION isoSelectByIndex(iIso) RESULT(lerr)
573  INTEGER, INTENT(IN) :: iIso
574  lerr = .FALSE.
575  IF(iIso == ixIso) RETURN                                      !--- Nothing to do if the index is already OK
576  IF(test(fmsg(iIso<=0 .OR. iIso>=nbIso,'Inconsistent isotopes family index '//TRIM(int2str(iIso))),lerr)) RETURN
577  ixIso = iIso                                                  !--- Update currently selected family index
578  isotope => isotopes(ixIso)                                    !--- Select corresponding component
579  !--- VARIOUS ALIASES
580  isoKeys => isotope%keys; niso = isotope%niso
581  isoName => isotope%trac; nitr = isotope%nitr; isoCheck => isotope%check
582  isoZone => isotope%zone; nzon = isotope%nzon; iZonIso  => isotope%iZonIso
583  isoPhas => isotope%phas; npha = isotope%npha; iTraPha  => isotope%iTraPha
584END FUNCTION isoSelectByIndex
585!==============================================================================================================================
586
587END MODULE infotrac
Note: See TracBrowser for help on using the repository browser.