source: LMDZ6/trunk/libf/dyn3d_common/infotrac.f90 @ 5481

Last change on this file since 5481 was 5481, checked in by dcugnet, 13 hours ago

Remove tracers attributes "isAdvected" and "isInPhysics" from infotrac (iadv is enough).
Remove tracers attribute "isAdvected" from infotrac_phy (isInPhysics is now equivalent
to former isInPhysics .AND. iadv > 0

  • 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: 26.5 KB
Line 
1!$Id: infotrac.f90 5481 2025-01-16 19:14:15Z dcugnet $
2!
3MODULE infotrac
4
5   USE       strings_mod, ONLY: msg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse, strCount, strIdx
6   USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, tracers,  addPhase,  addKey, iH2O,  &
7       isoSelect,  indexUpdate, isot_type, testTracersFiles, isotope,  delPhase,  getKey, tran0, &
8       isoKeys, isoName, isoZone, isoPhas, processIsotopes,  isoCheck, itZonIso,  nbIso,         &
9          niso,   ntiso,   nzone,   nphas,   maxTableWidth,  iqIsoPha, iqWIsoPha, ixIso, new2oldH2O, newHNO3, oldHNO3
10   IMPLICIT NONE
11
12   PRIVATE
13
14   !=== FOR TRACERS:
15   PUBLIC :: init_infotrac                                 !--- Initialization of the tracers
16   PUBLIC :: tracers, type_trac                            !--- Full tracers database, tracers type keyword
17   PUBLIC :: nqtot,   nbtr,   nqo,   nqCO2,   nqtottr      !--- Main dimensions
18   PUBLIC :: conv_flg, pbl_flg                             !--- Convection & boundary layer activation keys
19   PUBLIC :: new2oldH2O, newHNO3, oldHNO3                  !--- For backwards compatibility in dynetat0
20   PUBLIC :: addPhase, delPhase                            !--- Add/remove the phase from the name of a tracer
21
22   !=== FOR ISOTOPES: General
23   PUBLIC :: isot_type, 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 water
26   PUBLIC :: iH2O                                          !--- Value of "ixIso" for "H2O" isotopes class
27   PUBLIC :: min_qParent, min_qMass, min_ratio             !--- Min. values for various isotopic quantities
28   !=== FOR ISOTOPES: Depending on the selected isotopes family
29   PUBLIC :: isotope                                       !--- Selected isotopes database (argument of getKey)
30   PUBLIC :: isoKeys, isoName, isoZone, isoPhas            !--- Isotopes keys & names, tagging zones names, phases
31   PUBLIC ::    niso,   ntiso,   nzone,   nphas            !--- Number of   "   "
32   PUBLIC :: itZonIso                                      !--- Index "it" in "isoName(1:niso)" = f(tagging idx, isotope idx)
33   PUBLIC :: iqIsoPha                                      !--- Index "iq" in "qx"              = f(isotope idx,   phase idx)
34   PUBLIC :: isoCheck                                      !--- Run isotopes checking routines
35   !=== FOR BOTH TRACERS AND ISOTOPES
36   PUBLIC :: getKey                                        !--- Get a key from "tracers" or "isotope"
37
38!=== CONVENTIONS FOR TRACERS NUMBERS:
39!  |--------------------+-----------------------+-----------------+---------------+----------------------------|
40!  | water in different |    water tagging      |  water isotopes | other tracers | additional tracers moments |
41!  | phases: H2O_[glsrb]|      isotopes         |                 |               |  for higher order schemes  |
42!  |--------------------+-----------------------+-----------------+---------------+----------------------------|
43!  |                    |                       |                 |               |                            |
44!  |<--     nqo      -->|<-- nqo*niso* nzone -->|<-- nqo*niso  -->|<--  nbtr   -->|<--        (nmom)        -->|         
45!  |                    |                                         |                                            |
46!  |                    |<-- nqo*niso*(nzone+1)  =   nqo*ntiso -->|<--    nqtottr = nbtr + nmom             -->|
47!  |                                                                              = nqtot - nqo*(ntiso+1)      |
48!  |                                                                                                           |
49!  |<--                        nqtrue  =  nbtr + nqo*(ntiso+1)                 -->|                            |
50!  |                                                                                                           |
51!  |<--                        nqtot   =  nqtrue + nmom                                                     -->|
52!  |                                                                                                           |
53!  |-----------------------------------------------------------------------------------------------------------|
54!  NOTES FOR THIS TABLE:
55!  * Used "niso", "nzone" and "ntiso" are components of "isotopes(ip)" for water (isotopes(ip)%parent == 'H2O'),
56!    since water is so far the sole tracers family, except passive CO2, removed from the main tracers table.
57!  * For water, "nqo" is equal to the more general field "isotopes(ip)%nphas".
58!  * "niso", "nzone", "ntiso", "nphas" are defined for other isotopic tracers families, if any.
59!
60!=== DERIVED TYPE EMBEDDING MOST OF THE TRACERS-RELATED QUANTITIES (LENGTH: nqtot)
61!    Each entry is accessible using "%" sign.
62!  |-------------+------------------------------------------------------+-------------+------------------------+
63!  |  entry      | Meaning                                              | Former name | Possible values        |
64!  |-------------+------------------------------------------------------+-------------+------------------------+
65!  | name        | Name (short)                                         | tname       |                        |
66!  | keys        | key/val pairs accessible with "getKey" routine       | /           |                        |
67!  | gen0Name    | Name of the 1st generation ancestor                  | /           |                        |
68!  | parent      | Name of the parent                                   | /           |                        |
69!  | longName    | Long name (with adv. scheme suffix) for outputs      | ttext       |                        |
70!  | type        | Type (so far: tracer or tag)                         | /           | tracer,tag             |
71!  | phase       | Phases list ("g"as / "l"iquid / "s"olid              |             | [g|l|s|r|b]            |
72!  |             |              "r"(cloud) / "b"lowing)                 | /           |                        |
73!  | component   | Name(s) of the merged/cumulated section(s)           | /           | coma-separated names   |
74!  | iGeneration | Generation (>=1)                                     | /           |                        |
75!  | iqParent    | Index of the parent tracer                           | iqpere      | 1:nqtot                |
76!  | iqDescen    | Indexes of the childs       (all generations)        | iqfils      | 1:nqtot                |
77!  | nqDescen    | Number of the descendants   (all generations)        | nqdesc      | 1:nqtot                |
78!  | nqChildren  | Number of childs            (1st generation only)    | nqfils      | 1:nqtot                |
79!  | iadv        | Advection scheme number                              | iadv        | 1,2,10-20(exc.15,19),30|
80!  | iso_iGroup  | Isotopes group index in isotopes(:)                  | /           | 1:nbIso                |
81!  | iso_iName   | Isotope  name  index in isotopes(iso_iGroup)%trac(:) | iso_indnum  | 1:niso                 |
82!  | iso_iZone   | Isotope  zone  index in isotopes(iso_iGroup)%zone(:) | zone_num    | 1:nzone                |
83!  | iso_iPhas   | Isotope  phase index in isotopes(iso_iGroup)%phas(:) | phase_num   | 1:nphas                |
84!  +-------------+------------------------------------------------------+-------------+------------------------+
85!
86!=== DERIVED TYPE EMBEDDING MOST OF THE ISOTOPES-RELATED QUANTITIES (LENGTH: nbIso, NUMBER OF ISOTOPES FAMILIES)
87!    Each entry is accessible using "%" sign.
88!  |-----------------+--------------------------------------------------+--------------------+-----------------+
89!  |  entry | length | Meaning                                          |    Former name     | Possible values |
90!  |-----------------+--------------------------------------------------+--------------------+-----------------+
91!  | parent          | Parent tracer (isotopes family name)             |                    |                 |
92!  | keys   | niso   | Isotopes keys/values pairs list + number         |                    |                 |
93!  | trac   | ntiso  | Isotopes + tagging tracers list + number         | / | ntraciso       |                 |
94!  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
95!  | phase  | nphas  | Phases                     list + number         |                    | [g|l|s|r|b] 1:5 |
96!  | iqIsoPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
97!  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
98!  +-----------------+--------------------------------------------------+--------------------+-----------------+
99
100   REAL, PARAMETER :: min_qParent = 1.e-30, min_qMass = 1.e-18, min_ratio = 1.e-16 ! MVals et CRisi
101
102   !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
103   INTEGER, SAVE :: nqtot                                       !--- Tracers nb in dynamics (incl. higher moments + H2O)
104   INTEGER, SAVE :: nbtr                                        !--- Tracers nb in physics  (excl. higher moments + H2O)
105   INTEGER, SAVE :: nqo                                         !--- Number of water phases
106   INTEGER, SAVE :: nqtottr                                     !--- Number of tracers passed to phytrac (TO BE DELETED ?)
107   INTEGER, SAVE :: nqCO2                                       !--- Number of tracers of CO2  (ThL)
108   CHARACTER(LEN=maxlen), SAVE :: type_trac                     !--- Keyword for tracers type(s)
109
110   !=== VARIABLES FOR INCA
111   INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), pbl_flg(:)        !--- Convection / boundary layer activation (nbtr)
112
113CONTAINS
114
115SUBROUTINE init_infotrac
116   USE iniprint_mod_h
117   USE control_mod, ONLY: planet_type
118   USE lmdz_reprobus_wrappers, ONLY: Init_chem_rep_trac
119   USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA, CPPKEY_REPROBUS, CPPKEY_STRATAER
120   USE dimensions_mod, ONLY: iim, jjm, llm, ndm
121IMPLICIT NONE
122!==============================================================================================================================
123!
124!   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
125!   -------
126!
127!   Modifications:
128!   --------------
129!   05/94: F.Forget      Modif special traceur
130!   02/02: M-A Filiberti Lecture de traceur.def
131!   01/22: D. Cugnet     Nouveaux tracer.def et tracer_*.def + encapsulation (types trac_type et isot_type)
132!
133!   Objet:
134!   ------
135!   GCM LMD nouvelle grille
136!
137!==============================================================================================================================
138!   ... modification de l'integration de q ( 26/04/94 ) ....
139!------------------------------------------------------------------------------------------------------------------------------
140! Declarations:
141
142
143!------------------------------------------------------------------------------------------------------------------------------
144! Local variables
145   INTEGER, ALLOCATABLE :: hadv(:), vadv(:)                          !--- Horizontal/vertical transport scheme number
146   INTEGER, ALLOCATABLE :: had (:), hadv_inca(:), conv_flg_inca(:), &!--- Variables specific to INCA
147                           vad (:), vadv_inca(:),  pbl_flg_inca(:)
148   CHARACTER(LEN=8), ALLOCATABLE :: solsym_inca(:)                   !--- Tracers names for INCA
149   INTEGER :: nqINCA
150   CHARACTER(LEN=2)      ::   suff(9)                                !--- Suffixes for schemes of order 3 or 4 (Prather)
151   CHARACTER(LEN=3)      :: descrq(30)                               !--- Advection scheme description tags
152   CHARACTER(LEN=maxlen) :: msg1, texp, ttp, nam, val                !--- Strings for messages and expanded tracers type
153   INTEGER :: fType                                                  !--- Tracers description file type ; 0: none
154                                                                     !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def"
155   INTEGER :: nqtrue                                                 !--- Tracers nb from tracer.def (no higher order moments)
156   INTEGER :: iad                                                    !--- Advection scheme number
157   INTEGER :: iq, jq, nt, im, nm, ig                                 !--- Indexes and temporary variables
158   LOGICAL :: lerr
159   TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
160   TYPE(trac_type), POINTER             :: t1, t(:)
161   CHARACTER(LEN=maxlen),   ALLOCATABLE :: types_trac(:)             !--- Keywords for tracers type(s), parsed version
162   CHARACTER(LEN=*), PARAMETER :: modname="init_infotrac"
163!------------------------------------------------------------------------------------------------------------------------------
164! Initialization :
165!------------------------------------------------------------------------------------------------------------------------------
166   suff          = ['x ','y ','z ','xx','xy','xz','yy','yz','zz']
167   descrq( 1:30) =  '   '
168   descrq( 1: 2) = ['LMV','BAK']
169   descrq(10:20) = ['VL1','VLP','FH1','FH2','VLH','   ','PPM','PPS','PPP','   ','SLP']
170   descrq(30)    =  'PRA'
171
172   CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname)
173   IF(strCount(type_trac, '|', nt)) CALL abort_gcm(modname, 'Could''nt parse the "type_trac" string with delimiter "|"', 1)
174   IF(nt >= 3) CALL abort_gcm(modname, 'you need to modify type_trac, this version is not supported by lmdz', 1)
175   IF(strParse(type_trac, '|', types_trac, n=nt)) CALL abort_gcm(modname, "couldn't parse "//'"type_trac"', 1)
176   IF(nt == 2) type_trac = types_trac(2) ! TO BE DELETED SOON
177
178   CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname)
179
180!##############################################################################################################################
181   IF(.TRUE.) THEN                                                   !=== SKIPED IF ALREADY DONE IN dyn3d_common/infotrac  ####
182!##############################################################################################################################
183   !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
184   msg1 = 'For type_trac = "'//TRIM(type_trac)//'":'
185   SELECT CASE(type_trac)
186      CASE('inca'); CALL msg(TRIM(msg1)//' coupling with INCA chemistry model',        modname)
187      CASE('inco'); CALL msg(TRIM(msg1)//' coupling jointly with INCA and CO2 cycle',  modname)
188      CASE('repr'); CALL msg(TRIM(msg1)//' coupling with REPROBUS chemistry model',    modname)
189      CASE('co2i'); CALL msg(TRIM(msg1)//' you have chosen to run with CO2 cycle',     modname)
190      CASE('coag'); CALL msg(TRIM(msg1)//' tracers are treated for COAGULATION tests', modname)
191      CASE('lmdz'); CALL msg(TRIM(msg1)//' tracers are treated in LMDZ only',          modname)
192      CASE DEFAULT; CALL abort_gcm(modname,'type_trac='//TRIM(type_trac)//' not possible yet.',1)
193   END SELECT
194
195   !--- COHERENCE TEST BETWEEN "type_trac" AND PREPROCESSING KEYS
196   SELECT CASE(type_trac)
197      CASE('inca', 'inco')
198         IF(.NOT.CPPKEY_INCA)     CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1)
199      CASE('repr')
200         IF(.NOT.CPPKEY_REPROBUS) CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1)
201      CASE('coag')
202         IF(.NOT.CPPKEY_STRATAER) CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1)
203   END SELECT
204!##############################################################################################################################
205   END IF
206!##############################################################################################################################
207
208!==============================================================================================================================
209! 0) DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE AND READ IT
210!==============================================================================================================================
211   texp = type_trac                                                  !=== EXPANDED (WITH "|" SEPARATOR) "type_trac"
212   IF(texp == 'inco') texp = 'co2i|inca'
213   IF(texp /= 'lmdz') texp = 'lmdz|'//TRIM(texp)
214   IF(testTracersFiles(modname, texp, fType, .TRUE.)) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
215   ttp = type_trac; IF(fType /= 1) ttp = texp
216   !---------------------------------------------------------------------------------------------------------------------------
217   IF(fType == 0) CALL abort_gcm(modname, 'Missing "traceur.def", "tracer.def" or "tracer_<keyword>.def tracers file.',1)
218   !---------------------------------------------------------------------------------------------------------------------------
219   IF(fType == 1 .AND. ANY(['inca', 'inco'] == type_trac)) &         !=== FOUND OLD STYLE INCA "traceur.def"
220      CALL abort_gcm(modname, 'retro-compatibility with old-style INCA traceur.def files has been disabled.', 1)
221   !---------------------------------------------------------------------------------------------------------------------------
222
223!##############################################################################################################################
224   IF(readTracersFiles(ttp, lRepr=type_trac == 'repr')) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
225!##############################################################################################################################
226
227!==============================================================================================================================
228! 1) Get various numbers: "nqtrue" (first order only tracers), "nqo" (water phases), 'nbtr' (tracers passed to physics), etc.
229!==============================================================================================================================
230   nqtrue = SIZE(tracers)                                                                               !--- "true" tracers
231   nqo    =      COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%name)     == 'H2O')     !--- Water phases
232   nbtr = nqtrue-COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%gen0Name) == 'H2O')     !--- Passed to phytrac
233   nqCO2  =      COUNT( [type_trac == 'inco', type_trac == 'co2i'] )
234   IF(CPPKEY_INCA) &
235   nqINCA =      COUNT(tracers(:)%component == 'inca')
236   IF(CPPKEY_REPROBUS) CALL Init_chem_rep_trac(nbtr, nqo, tracers(:)%name)
237
238!==============================================================================================================================
239! 2) Calculate nqtot, number of tracers needed (greater if advection schemes 20 or 30 have been chosen).
240!==============================================================================================================================
241   IF(getKey('hadv', hadv, ky=tracers(:)%keys)) CALL abort_gcm(modname, 'missing key "hadv"', 1)
242   IF(getKey('vadv', vadv, ky=tracers(:)%keys)) CALL abort_gcm(modname, 'missing key "vadv"', 1)
243   DO iq = 1, nqtrue
244      IF( hadv(iq)<20 .OR. (ANY(hadv(iq)==[20,30]) .AND. hadv(iq)==vadv(iq)) ) CYCLE
245      WRITE(msg1,'("The choice hadv=",i0,", vadv=",i0,a)')hadv(iq),vadv(iq),' for "'//TRIM(tracers(iq)%name)//'" is not available'
246      CALL abort_gcm(modname, TRIM(msg1), 1)
247   END DO
248   nqtot =    COUNT( hadv< 20 .AND. vadv< 20 ) &                     !--- No additional tracer
249         +  4*COUNT( hadv==20 .AND. vadv==20 ) &                     !--- 3  additional tracers
250         + 10*COUNT( hadv==30 .AND. vadv==30 )                       !--- 9  additional tracers
251
252   !--- More tracers due to the choice of advection scheme => assign total number of tracers
253   IF( nqtot /= nqtrue ) THEN
254      CALL msg('The choice of advection scheme for one or more tracers makes it necessary to add tracers')
255      CALL msg('The number of true tracers is '//TRIM(int2str(nqtrue)))
256      CALL msg('The total number of tracers needed is '//TRIM(int2str(nqtot)))
257   END IF
258
259!==============================================================================================================================
260! 3) Determine the advection scheme choice for water and tracers "iadv" and the field "long name".
261!     iadv = 1    "LMDZ-specific humidity transport" (for H2O vapour)          LMV
262!     iadv = 2    backward                           (for H2O liquid)          BAK
263!     iadv = 14   Van-Leer + specific humidity, modified by Francis Codron     VLH
264!     iadv = 10   Van-Leer (chosen for vapour and liquid water)                VL1
265!     iadv = 11   Van-Leer for hadv and PPM version (Monotonic) for vadv       VLP
266!     iadv = 12   Frederic Hourdin I                                           FH1
267!     iadv = 13   Frederic Hourdin II                                          FH2
268!     iadv = 16   Monotonic         PPM (Collela & Woodward 1984)              PPM
269!     iadv = 17   Semi-monotonic    PPM (overshoots allowed)                   PPS
270!     iadv = 18   Definite positive PPM (overshoots and undershoots allowed)   PPP
271!     iadv = 20   Slopes                                                       SLP
272!     iadv = 30   Prather                                                      PRA
273!
274!        In array q(ij,l,iq) : iq = 1/2[/3]    for vapour/liquid[/ice] water
275!        And optionaly:        iq = 3[4],nqtot for other tracers
276!==============================================================================================================================
277   ALLOCATE(ttr(nqtot))
278   jq = nqtrue+1
279   DO iq = 1, nqtrue
280      t1 => tracers(iq)
281
282      !--- VERIFY THE CHOICE OF ADVECTION SCHEME
283      iad = -1
284      IF(hadv(iq)     ==    vadv(iq)    ) iad = hadv(iq)
285      IF(hadv(iq)==10 .AND. vadv(iq)==16) iad = 11
286      WRITE(msg1,'("Bad choice of advection scheme for ",a,": hadv = ",i0,", vadv = ",i0)')TRIM(t1%name), hadv(iq), vadv(iq)
287      IF(iad == -1) CALL abort_gcm(modname, msg1, 1)
288
289      !--- SET FIELDS longName and iadv
290      t1%longName   = t1%name; IF(iad > 0) t1%longName=TRIM(t1%name)//descrq(iad)
291      t1%iadv       = iad
292      ttr(iq)       = t1
293
294      !--- DEFINE THE HIGHER ORDER TRACERS, IF ANY
295      nm = 0
296      IF(iad == 20) nm = 3                                           !--- 2nd order scheme
297      IF(iad == 30) nm = 9                                           !--- 3rd order scheme
298      IF(nm == 0) CYCLE                                              !--- No higher moments
299      ttr(jq+1:jq+nm)             = t1
300      ttr(jq+1:jq+nm)%name        = [ (TRIM(t1%name)    //'-'//TRIM(suff(im)), im=1, nm) ]
301      ttr(jq+1:jq+nm)%gen0Name    = [ (TRIM(t1%name)    //'-'//TRIM(suff(im)), im=1, nm) ]
302      ttr(jq+1:jq+nm)%parent      = [ (TRIM(t1%parent)  //'-'//TRIM(suff(im)), im=1, nm) ]
303      ttr(jq+1:jq+nm)%longName    = [ (TRIM(t1%longName)//'-'//TRIM(suff(im)), im=1, nm) ]
304      ttr(jq+1:jq+nm)%iadv        = [ (-iad,    im=1, nm) ]
305      jq = jq + nm
306   END DO
307   DEALLOCATE(hadv, vadv)
308   CALL MOVE_ALLOC(FROM=ttr, TO=tracers)
309
310   !--- SET FIELDS iqParent, iqDescen, nqDescen, nqChildren
311   IF(indexUpdate(tracers)) CALL abort_gcm(modname, 'problem with tracers indices update', 1)
312
313   !=== TEST ADVECTION SCHEME
314   DO iq = 1, nqtot ; t1 => tracers(iq)
315      iad = t1%iadv
316      ig  = t1%iGeneration
317      nam = t1%name
318      val = 'iadv='//TRIM(int2str(iad))
319
320      !--- ONLY TESTED VALUES FOR TRACERS FOR NOW:               iadv = 14, 10 (and 0 for non-transported tracers)
321      IF(ALL([10,14,0] /= iad)) CALL abort_gcm(modname, TRIM(val)//' has not been tested yet ; 10 or 14 only are allowed !', 1)
322
323      !--- ONLY TESTED VALUES SO FAR FOR PARENTS HAVING CHILDREN: iadv = 14, 10 (PARENTS: TRACERS OF GENERATION 0)
324      IF(ALL([10,14] /= iad) .AND. ig == 0 .AND. ANY(tracers(:)%parent==nam)) &
325         CALL abort_gcm(modname, TRIM(val)//' is not implemented for parents ; 10 or 14 only are allowed !', 1)
326
327      !--- ONLY TESTED VALUES SO FAR FOR DESCENDANTS (TRACERS OF GENERATION > 0): iadv = 10 ; WATER VAPOUR: iadv = 14
328      lerr = iad /= 10 .AND. ig > 0;                     IF(lerr) tracers(iq)%iadv = 10
329      CALL msg('WARNING! '//TRIM(val)//  ' not implemented for children. Setting iadv=10 for "'//TRIM(nam)//'"', modname, lerr)
330      lerr = iad == 14 .AND. nam /= addPhase('H2O','g'); IF(lerr) tracers(iq)%iadv = 10
331      CALL msg('WARNING! '//TRIM(val)//' is valid for water vapour only. Setting iadv=10 for "'//TRIM(nam)//'"', modname, lerr)
332   END DO
333
334   !=== READ PHYSICAL PARAMETERS FOR ISOTOPES ; DONE HERE BECAUSE dynetat0 AND iniacademic NEED "tnat" AND "alpha_ideal"
335   niso = 0; nzone = 0; nphas = nqo; ntiso = 0; isoCheck = .FALSE.
336   IF(processIsotopes()) CALL abort_gcm(modname, 'problem when processing isotopes parameters', 1)
337
338   !--- Convection / boundary layer activation for all tracers
339   IF(.NOT.ALLOCATED(conv_flg)) ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1
340   IF(.NOT.ALLOCATED( pbl_flg)) ALLOCATE( pbl_flg(nbtr));  pbl_flg(1:nbtr) = 1
341
342   !--- Note: nqtottr can differ from nbtr when nmom/=0
343   nqtottr = nqtot - COUNT(delPhase(tracers%gen0Name) == 'H2O' .AND. tracers%component == 'lmdz')
344   IF(COUNT(tracers%iso_iName == 0) - COUNT(delPhase(tracers%name) == 'H2O' .AND. tracers%component == 'lmdz') /= nqtottr) &
345      CALL abort_gcm(modname, 'problem with the computation of nqtottr', 1)
346
347   !=== DISPLAY THE RESULTS
348   IF(.NOT..TRUE.) RETURN
349   CALL msg('nqo    = '//TRIM(int2str(nqo)),    modname)
350   CALL msg('nbtr   = '//TRIM(int2str(nbtr)),   modname)
351   CALL msg('nqtrue = '//TRIM(int2str(nqtrue)), modname)
352   CALL msg('nqtot  = '//TRIM(int2str(nqtot)),  modname)
353   CALL msg('niso   = '//TRIM(int2str(niso)),   modname)
354   CALL msg('ntiso  = '//TRIM(int2str(ntiso)),  modname)
355   CALL msg('nqCO2  = '//TRIM(int2str(nqCO2)),  modname, CPPKEY_INCA)
356   CALL msg('nqINCA = '//TRIM(int2str(nqINCA)), modname, CPPKEY_INCA)
357   t => tracers
358   CALL msg('Information stored in '//TRIM(modname)//': ', modname)
359   IF(dispTable('isssssssiiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp',      &
360                              'iAdv', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'],     &
361      cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component),                         &
362      cat([(iq, iq=1, nqtot)], t%iadv, t%iGeneration, t%iqParent, t%nqDescen, t%nqChildren, t%iso_iGroup,  &
363                  t%iso_iName, t%iso_iZone, t%iso_iPhase), nColMax=maxTableWidth, nHead=2, sub=modname))   &
364      CALL abort_gcm(modname, "problem with the tracers table content", 1)
365   CALL msg('No isotopes identified.', modname, nbIso == 0)
366   IF(nbIso == 0) RETURN
367   CALL msg('For isotopes family "H2O":', modname)
368   CALL msg('  isoKeys%name = '//strStack(isoKeys%name), modname)
369   CALL msg('  isoName = '//strStack(isoName),      modname)
370   CALL msg('  isoZone = '//strStack(isoZone),      modname)
371   CALL msg('  isoPhas = '//TRIM(isoPhas),          modname)
372
373END SUBROUTINE init_infotrac
374
375END MODULE infotrac
Note: See TracBrowser for help on using the repository browser.