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

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

In readTracFiles: the separator between the tracer name and its phase is no longer hardcoded and equal to "-",
but is a parameter ("phases_sep") which default value is "_".
Few more fixes.

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