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

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