source: LMDZ6/branches/LMDZ-tracers/libf/phylmd/infotrac_phy.F90 @ 3871

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

Extension of the tracers management.

The tracers files can be:

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

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

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

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

coma-separated list of components.

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

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

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

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

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

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

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

File size: 15.5 KB
Line 
1MODULE infotrac_phy
2
3  USE       strings_mod, ONLY: msg, fmsg, test, strIdx, int2str
4
5  USE readTracFiles_mod, ONLY: getKey_init, getKey, indexUpdate
6
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 :: init_infotrac_phy                              !--- Initialization
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 :: pbl_flg, conv_flg, solsym
20
21  !=== FOR ISOTOPES: General
22  !--- General
23  PUBLIC :: iso, isotopes, nbIso                           !--- Derived type, full isotopes families database + nb of families
24  PUBLIC :: isoSelect , ixIso                              !--- Isotopes family selection tool + selected family index
25  !=== FOR ISOTOPES: Specific to H2O isotopes
26  PUBLIC :: iH2O, tnat, alpha_ideal                        !--- H2O isotopes index, natural abundance, fractionning coeff.
27  !=== FOR ISOTOPES: Depending on selected isotopes family
28  PUBLIC :: isotope, isoKeys                               !--- Selected isotopes database + associated keys (cf. getKey)
29  PUBLIC :: isoName, isoZone, isoPhas                      !--- Isotopes and tagging zones names, phases
30  PUBLIC :: niso, nzon, npha, nitr                         !---  " " numbers + isotopes & tagging tracers number
31  PUBLIC :: iZonIso, iTraPha                               !--- 2D index tables to get "iq" index
32  PUBLIC :: isoCheck                                       !--- Run isotopes checking routines
33
34  !=== FOR BOTH TRACERS AND ISOTOPES
35  PUBLIC :: getKey                                         !--- Get a key from "tracers" or "isotope"
36
37  !=== FOR STRATOSPHERIC AEROSOLS
38#ifdef CPP_StratAer
39  PUBLIC :: nbtr_bin, nbtr_sulgas, id_OCS_strat, id_H2SO4_strat, id_SO2_strat, id_BIN01_strat, id_TEST_strat
40#endif
41
42  INTERFACE isoSelect; MODULE PROCEDURE isoSelectByIndex, isoSelectByName; END INTERFACE isoSelect
43
44!=== CONVENTIONS FOR TRACERS NUMBERS:
45!  |--------------------+----------------------+-----------------+---------------+----------------------------|
46!  | water in different |    water tagging     |  water isotopes | other tracers | additional tracers moments |
47!  | phases: H2O-[gls]  |      isotopes        |                 |               |  for higher order schemes  |
48!  |--------------------+----------------------+-----------------+---------------+----------------------------|
49!  |                    |                      |                 |               |                            |
50!  |<--     nqo      -->|<-- nqo*niso* nzon -->|<-- nqo*niso  -->|<--  nbtr   -->|<--        (nmom)        -->|         
51!  |                    |                                        |                                            |
52!  |                    |<-- nqo*niso*(nzon+1)  =   nqo*nitr  -->|<--    nqtottr = nbtr + nmom             -->|
53!  |                                                                             = nqtot - nqo*(nitr+1)       |
54!  |                                                                                                          |
55!  |<--                        nqtrue  =  nbtr + nqo*(nitr+1)                 -->|                            |
56!  |                                                                                                          |
57!  |<--                        nqtot   =  nqtrue + nmom                                                    -->|
58!  |                                                                                                          |
59!  |----------------------------------------------------------------------------------------------------------|
60! NOTES FOR THIS TABLE:
61!  * The used "niso", "nzon" and "nitr" are the H2O components of "isotopes(ip)"  (isotopes(ip)%prnt == 'H2O'),
62!    since water is so far the sole tracers family removed from the main tracers table.
63!  * For water, "nqo" is equal to the more general field "isotopes(ip)%npha".
64!  * "niso", "nzon", "nitr", "npha" are defined for other isotopic tracers families, if any.
65!
66!=== TRACERS DESCRIPTOR: DERIVED TYPE EMBEDDING MOST OF THE USEFUL QUANTITIES (LENGTH: nqtot)
67!    Each entry is accessible using "%" sign.
68!  |------------+-------------------------------------------------+-------------+------------------------+
69!  |  entry     | Meaning                                         | Former name | Possible values        |
70!  |------------+-------------------------------------------------+-------------+------------------------+
71!  | name       | Name (short)                                    | tname       |                        |
72!  | nam1       | Name of the 1st generation ancestor             | /           |                        |
73!  | prnt       | Name of the parent                              | /           |                        |
74!  | lnam       | Long name (with adv. scheme suffix) for outputs | ttext       |                        |
75!  | type       | Type (so far: tracer or tag)                    | /           | tracer,tag             |
76!  | phas       | Phases list ("g"as / "l"iquid / "s"olid)        | /           | [g][l][s]              |
77!  | iadv       | Advection scheme number                         | iadv        | 1-20,30 exc. 3-9,15,19 |
78!  | igen       | Generation (>=1)                                | /           |                        |
79!  | itr        | Index in "tr_seri" (0: absent from physics)     | cf. niadv   | 1:nqtottr              |
80!  | iprnt      | Index of the parent tracer                      | iqpere      | 1:nqtot                |
81!  | idesc      | Indexes of the childs (all generations)         | iqfils      | 1:nqtot                |
82!  | ndesc      | Number of the descendants (all generations)     | nqdesc      | 1:nqtot                |
83!  | nchld      | Number of childs (first generation only)        | nqfils      | 1:nqtot                |
84!  | keys       | key/val pairs accessible with "getKey" routine  | /           |                        |
85!  | iso_num    | Isotope name  index in iso(igr)%name(:)         | iso_indnum  | 1:niso                 |
86!  | iso_zon    | Isotope zone  index in iso(igr)%zone(:)         | zone_num    | 1:nzon                 |
87!  | iso_pha    | Isotope phase index in iso(igr)%phas            | phase_num   | 1:npha                 |
88!  +------------+-------------------------------------------------+-------------+------------------------+
89!
90!=== ISOTOPES DESCRIPTOR: DERIVED TYPE EMBEDDING MOST OF THE USEFUL QUANTITIES (LENGTH: NUMBER OF ISOTOPES FAMILIES USED)
91!    Each entry is accessible using "%" sign.
92!  |------------+-------------------------------------------------+-------------+-----------------------+
93!  |  entry     | Meaning                                         | Former name | Possible values       |
94!  |------------+-------------------------------------------------+-------------+-----------------------+
95!  | prnt       | Parent tracer (isotopes family name)            |             |                       |
96!  | trac, nitr | Isotopes & tagging tracers + number of elements |             |                       |
97!  | zone, nzon | Geographic tagging zones   + number of elements |             |                       |
98!  | phas, npha | Phases list                + number of elements |             | [g][l][s], 1:3        |
99!  | niso       | Number of isotopes, excluding tagging tracers   |             |                       |
100!  | iTraPha    | Index in "xt" = f(iname(niso+1:nitr),iphas)     | iqiso       | 1:niso                |
101!  | iZonIso    | Index in "xt" = f(izone, iname(1:niso))         | index_trac  | 1:nzon                |
102!  |------------+-------------------------------------------------+-------------+-----------------------+
103
104  !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
105  INTEGER,            SAVE :: nqtot, &                     !--- Tracers nb in dynamics (incl. higher moments & water)
106                              nbtr,  &                     !--- Tracers nb in physics  (excl. higher moments & water)
107                              nqo,   &                     !--- Number of water phases
108                              nbIso                        !--- Number of available isotopes family
109  CHARACTER(LEN=256), SAVE :: type_trac                    !--- Keyword for tracers type
110
111  !=== DERIVED TYPES EMBEDDING MOST INFORMATIONS ABOUT TRACERS AND ISOTOPES FAMILIES
112  TYPE(tra), TARGET,  SAVE, ALLOCATABLE ::  tracers(:)     !=== TRACERS DESCRIPTORS VECTOR
113  TYPE(iso), TARGET,  SAVE, ALLOCATABLE :: isotopes(:)     !=== ISOTOPES PARAMETERS VECTOR
114!$OMP THREADPRIVATE(tracers, isotopes)
115
116  !=== ALIASES FOR CURRENTLY SELECTED ISOTOPES FAMILY OF VARIABLES EMBEDDED IN THE VECTOR "isotopes"
117  TYPE(iso),          SAVE, POINTER :: isotope             !--- CURRENTLY SELECTED ISOTOPES FAMILY DESCRIPTOR
118  INTEGER,            SAVE          :: ixIso, iH2O         !--- Index of the selected isotopes family and H2O family
119  LOGICAL,            SAVE, POINTER :: isoCheck            !--- Flag to trigger the checking routines
120  TYPE(kys),          SAVE, POINTER :: isoKeys(:)          !--- ONE SET OF KEYS FOR EACH ISOTOPE (LISTED IN isoName)
121  CHARACTER(LEN=256), SAVE, POINTER :: isoName(:),       & !--- ISOTOPES NAMES FOR THE CURRENTLY SELECTED FAMILY
122                                       isoZone(:),       & !--- TAGGING ZONES  FOR THE CURRENTLY SELECTED FAMILY
123                                       isoPhas             !--- USED PHASES    FOR THE CURRENTLY SELECTED FAMILY
124  INTEGER,            SAVE          :: niso, nzon, npha, & !--- NUMBER OF ISOTOPES, TAGGING ZONES AND PHASES
125                                       nitr                !--- NUMBER OF ISOTOPES + ISOTOPIC TAGGING TRACERS
126  INTEGER,            SAVE, POINTER :: iZonIso(:,:)        !--- INDEX IN "isoTrac" AS f(tagging zone, isotope)
127  INTEGER,            SAVE, POINTER :: iTraPha(:,:)        !=== INDEX IN "isoTrac" AS f(isotopic tracer, phase)
128!$OMP THREADPRIVATE(isotope, ixIso,iH2O, isoCheck, isoKeys, isoName,isoZone,isoPhas, niso,nzon,npha,nitr, iZonIso,iTraPha)
129
130  !=== VARIABLES EMBEDDED IN "tracers", BUT DUPLICATED, AS THEY ARE RATHER FREQUENTLY USED + VARIABLES FOR INCA
131  REAL,               SAVE, ALLOCATABLE ::     tnat(:),  & !--- Natural relative abundance of water isotope        (niso)
132                                        alpha_ideal(:)     !--- Ideal fractionning coefficient (for initial state) (niso)
133  INTEGER,            SAVE, ALLOCATABLE :: conv_flg(:),  & !--- Convection     activation ; needed for INCA        (nbtr)
134                                            pbl_flg(:)     !---  Boundary layer activation ; needed for INCA        (nbtr)
135  INTEGER,            SAVE, ALLOCATABLE ::    niadv(:),  &
136                                         itr_indice(:)     !--- Indexes of the tracers passed to phytrac        (nqtottr)
137  CHARACTER(LEN=256), SAVE, ALLOCATABLE ::   solsym(:)     !--- Names from INCA                                    (nbtr)
138!OMP THREADPRIVATE(tnat, alpha_ideal, conv_flg, pbl_flg, niadv, itr_indice, solsym)
139
140#ifdef CPP_StratAer
141  !=== SPECIFIC TO STRATOSPHERIC AEROSOLS (CK/OB)
142  INTEGER, SAVE :: nbtr_bin, nbtr_sulgas, id_OCS_strat, id_H2SO4_strat, id_SO2_strat, id_BIN01_strat, id_TEST_strat
143!OMP THREADPRIVATE(nbtr_bin, nbtr_sulgas, id_OCS_strat, id_H2SO4_strat, id_SO2_strat, id_BIN01_strat, id_TEST_strat)
144#endif
145
146CONTAINS
147
148SUBROUTINE init_infotrac_phy(tracers_, isotopes_, type_trac_, solsym_, nbtr_, niadv_, pbl_flg_, conv_flg_)
149  ! transfer information on tracers from dynamics to physics
150  USE print_control_mod, ONLY: prt_level, lunout
151  IMPLICIT NONE
152  TYPE(tra),        INTENT(IN) ::  tracers_(:)
153  TYPE(iso),        INTENT(IN) :: isotopes_(:)
154  CHARACTER(LEN=*), INTENT(IN) :: type_trac_, solsym_(:)
155  INTEGER,          INTENT(IN) :: nbtr_, niadv_(:), pbl_flg_(:), conv_flg_(:)
156
157  CHARACTER(LEN=256) :: modname="init_infotrac_phy"
158  LOGICAL :: lerr
159
160  tracers   = tracers_
161  isotopes  = isotopes_
162  type_trac = type_trac_
163  solsym    = solsym_
164  nqtot     = SIZE(tracers_)
165  nbtr      = nbtr_
166  niadv     = niadv_
167  nbIso     = SIZE(isotopes_)
168  pbl_flg  = pbl_flg_
169  conv_flg = conv_flg_
170
171  !=== Specific to water
172  CALL getKey_init(tracers, isotopes)
173  IF(.NOT.isoSelect('H2O')) THEN
174    iH2O = ixIso
175    lerr = getKey('tnat' ,tnat,        isoName)
176    lerr = getKey('alpha',alpha_ideal, isoName)
177    nqo  = isotope%npha
178  END IF
179  IF(prt_level > 1) WRITE(lunout,*) TRIM(modname)//": nqtot, nqo, nbtr = ",nqtot, nqo, nbtr
180  itr_indice = PACK(tracers(:)%itr, MASK = tracers(:)%itr/=0)
181print*,'66'
182
183  !? conv_flg, pbl_flg, solsym
184  !? isoInit
185
186#ifdef CPP_StratAer
187  IF (type_trac == 'coag') THEN
188    nbtr_bin=0
189    nbtr_sulgas=0
190    DO iq = 1, nqtrue
191      IF(tracers(iq)%name(1:3)=='BIN') nbtr_bin    = nbtr_bin   +1
192      IF(tracers(iq)%name(1:3)=='GAS') nbtr_sulgas = nbtr_sulgas+1
193      SELECT CASE(tracers(iq)%name)
194        CASE('BIN01');    id_BIN01_strat = iq - nqo; CALL msg('id_BIN01_strat=', id_BIN01_strat)
195        CASE('GASOCS');   id_OCS_strat   = iq - nqo; CALL msg('id_OCS_strat  =', id_OCS_strat)
196        CASE('GASSO2');   id_SO2_strat   = iq - nqo; CALL msg('id_SO2_strat  =', id_SO2_strat)
197        CASE('GASH2SO4'); id_H2SO4_strat = iq - nqo; CALL msg('id_H2SO4_strat=', id_H2SO4_strat)
198        CASE('GASTEST');  id_TEST_strat  = iq - nqo; CALL msg('id_TEST_strat=' , id_TEST_strat)
199      END SELECT
200    END DO
201    CALL msg('nbtr_bin      =',nbtr_bin)
202    CALL msg('nbtr_sulgas   =',nbtr_sulgas)
203  END IF
204#endif
205
206END SUBROUTINE init_infotrac_phy
207
208
209!==============================================================================================================================
210!=== THE ROUTINE isoSelect IS USED TO SWITCH FROM AN ISOTOPE FAMILY TO ANOTHER: ISOTOPES DEPENDENT PARAMETERS ARE UPDATED
211!     Singe generic "isoSelect" routine, using the predefined parent index (fast version) or its name (first time).
212!==============================================================================================================================
213LOGICAL FUNCTION isoSelectByName(iName) RESULT(lerr)
214  CHARACTER(LEN=*), INTENT(IN)  :: iName
215  INTEGER :: iIso
216  iIso = strIdx(isotopes(:)%prnt, iName)
217  IF(test(fmsg(iIso == 0,'no isotope family named "'//TRIM(iName)//'"'),lerr)) RETURN
218  IF(isoSelectByIndex(iIso)) RETURN
219END FUNCTION isoSelectByName
220!==============================================================================================================================
221LOGICAL FUNCTION isoSelectByIndex(iIso) RESULT(lerr)
222  INTEGER, INTENT(IN) :: iIso
223  lerr = .FALSE.
224  IF(iIso == ixIso) RETURN                                      !--- Nothing to do if the index is already OK
225  IF(test(fmsg(iIso<=0 .OR. iIso>=nbIso,'Inconsistent isotopes family index '//TRIM(int2str(iIso))),lerr)) RETURN
226  ixIso = iIso                                                  !--- Update currently selected family index
227  isotope => isotopes(ixIso)                                    !--- Select corresponding component
228  !--- VARIOUS ALIASES
229  isoKeys => isotope%keys; niso = isotope%niso
230  isoName => isotope%trac; nitr = isotope%nitr; isoCheck => isotope%check
231  isoZone => isotope%zone; nzon = isotope%nzon; iZonIso  => isotope%iZonIso
232  isoPhas => isotope%phas; npha = isotope%npha; iTraPha  => isotope%iTraPha
233END FUNCTION isoSelectByIndex
234!==============================================================================================================================
235
236END MODULE infotrac_phy
Note: See TracBrowser for help on using the repository browser.