source: LMDZ6/trunk/libf/phylmd/infotrac_phy.F90 @ 4124

Last change on this file since 4124 was 4124, checked in by dcugnet, 2 years ago

Remove solsym, ok_isotopes (=niso>0), ok_isotrac (=nzone>0)

File size: 18.2 KB
Line 
1
2! $Id: $
3
4MODULE infotrac_phy
5
6   USE       strings_mod, ONLY: msg, maxlen, strStack, strHead, strIdx, int2str
7   USE readTracFiles_mod, ONLY: trac_type, isot_type, keys_type, delPhase, getKey, tnom_iso => newH2OIso
8
9   IMPLICIT NONE
10
11   PRIVATE
12
13   !=== FOR TRACERS:
14   PUBLIC :: init_infotrac_phy                             !--- Initialization of the tracers
15   PUBLIC :: tracers, type_trac                            !--- Full tracers database, tracers type keyword
16   PUBLIC :: nqtot,   nbtr,   nqo,   nqCO2,   nqtottr      !--- Main dimensions
17   PUBLIC :: conv_flg, pbl_flg                             !--- Convection & boundary layer activation keys
18
19   !=== FOR ISOTOPES: General
20   PUBLIC :: isotopes,  nbIso                              !--- Derived type, full isotopes families database + nb of families
21   PUBLIC :: isoSelect, ixIso                              !--- Isotopes family selection tool + selected family index
22   !=== FOR ISOTOPES: Specific to water
23   PUBLIC :: iH2O                                          !--- H2O isotopes index
24   !=== FOR ISOTOPES: Depending on the selected isotopes family
25   PUBLIC :: isotope, isoKeys                              !--- Selected isotopes database + associated keys (cf. getKey)
26   PUBLIC :: isoName, isoZone, isoPhas                     !--- Isotopes and tagging zones names, phases
27   PUBLIC :: niso,    nzone,   nphas,   ntiso              !---  " " numbers + isotopes & tagging tracers number
28   PUBLIC :: itZonIso                                      !--- iq = function(tagging zone idx, isotope idx)
29   PUBLIC :: iqTraPha                                      !--- idx of tagging tracer in iName = function(isotope idx, phase idx)
30   PUBLIC :: isoCheck                                      !--- Run isotopes checking routines
31   !=== FOR BOTH TRACERS AND ISOTOPES
32   PUBLIC :: getKey                                        !--- Get a key from "tracers" or "isotope"
33
34   PUBLIC :: ntraciso, ntraceurs_zone, indnum_fn_num, use_iso, index_trac, iqiso
35   PUBLIC :: niso_possibles, ok_iso_verif
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* nzone -->|<-- nqo*niso  -->|<--  nbtr   -->|<--        (nmom)        -->|         
46!  |                    |                                         |                                            |
47!  |                    |<-- nqo*niso*(nzone+1)  =   nqo*ntiso -->|<--    nqtottr = nbtr + nmom             -->|
48!  |                                                                              = nqtot - nqo*(ntiso+1)      |
49!  |                                                                                                           |
50!  |<--                        nqtrue  =  nbtr + nqo*(ntiso+1)                 -->|                            |
51!  |                                                                                                           |
52!  |<--                        nqtot   =  nqtrue + nmom                                                     -->|
53!  |                                                                                                           |
54!  |-----------------------------------------------------------------------------------------------------------|
55!  NOTES FOR THIS TABLE:
56!  * Used "niso", "nzone" and "ntiso" are components of "isotopes(ip)" for water (isotopes(ip)%parent == 'H2O'),
57!    since water is so far the sole tracers family, except passive CO2, removed from the main tracers table.
58!  * For water, "nqo" is equal to the more general field "isotopes(ip)%nphas".
59!  * "niso", "nzone", "ntiso", "nphas" are defined for other isotopic tracers families, if any.
60!
61!=== DERIVED TYPE EMBEDDING MOST OF THE TRACERS-RELATED 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!  | 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]              |
72!  | component   | 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!  | iGeneration | Generation (>=1)                                     | /           |                        |
75!  | isAdvected  | advected tracers flag (.TRUE. if iadv >= 0)          | /           | nqtrue  .TRUE. values  |
76!  | isInPhysics | tracers not extracted from the main table in physics | /           | nqtottr .TRUE. values  |
77!  | iqParent    | Index of the parent tracer                           | iqpere      | 1:nqtot                |
78!  | iqDescen    | Indexes of the childs       (all generations)        | iqfils      | 1:nqtot                |
79!  | nqDescen    | Number of the descendants   (all generations)        | nqdesc      | 1:nqtot                |
80!  | nqChilds    | Number of childs            (1st generation only)    | nqfils      | 1:nqtot                |
81!  | iso_iGroup  | Isotopes group index in isotopes(:)                  | /           | 1:nbIso                |
82!  | iso_iName   | Isotope  name  index in isotopes(iso_iGroup)%trac(:) | iso_indnum  | 1:niso                 |
83!  | iso_iZone   | Isotope  zone  index in isotopes(iso_iGroup)%zone(:) | zone_num    | 1:nzone                |
84!  | iso_iPhas   | Isotope  phase index in isotopes(iso_iGroup)%phas(:) | phase_num   | 1:nphas                |
85!  | keys        | key/val pairs accessible with "getKey" routine       | /           |                        |
86!  +-------------+------------------------------------------------------+-------------+------------------------+
87!
88!=== DERIVED TYPE EMBEDDING MOST OF THE ISOTOPES-RELATED QUANTITIES (LENGTH: nbIso, NUMBER OF ISOTOPES FAMILIES)
89!    Each entry is accessible using "%" sign.
90!  |-----------------+--------------------------------------------------+--------------------+-----------------+
91!  |  entry | length | Meaning                                          |    Former name     | Possible values |
92!  |-----------------+--------------------------------------------------+--------------------+-----------------+
93!  | parent          | Parent tracer (isotopes family name)             |                    |                 |
94!  | keys   | niso   | Isotopes keys/values pairs list + number         |                    |                 |
95!  | trac   | ntiso  | Isotopes + tagging tracers list + number         | / | ntraciso       |                 |
96!  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
97!  | phase  | nphas  | Phases                     list + number         |                    | [g][l][s], 1:3  |
98!  | iqTraPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
99!  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
100!  +-----------------+--------------------------------------------------+--------------------+-----------------+
101
102   !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
103   INTEGER,                 SAVE :: nqtot,  &                   !--- Tracers nb in dynamics (incl. higher moments + H2O)
104                                    nbtr,   &                   !--- Tracers nb in physics  (excl. higher moments + H2O)
105                                    nqo,    &                   !--- Number of water phases
106                                    nbIso,  &                   !--- Number of available isotopes family
107                                    nqtottr, &                  !--- Number of tracers passed to phytrac (TO BE DELETED ?)
108                                    nqCO2                       !--- Number of tracers of CO2  (ThL)
109   CHARACTER(LEN=maxlen),   SAVE :: type_trac                   !--- Keyword for tracers type
110!$OMP THREADPRIVATE(nqtot, nbtr, nqo, nbIso, nqtottr, nqCO2, type_trac)
111
112   !=== DERIVED TYPES EMBEDDING MOST INFORMATIONS ABOUT TRACERS AND ISOTOPES FAMILIES
113   TYPE(trac_type), TARGET, SAVE, ALLOCATABLE ::  tracers(:)    !=== TRACERS DESCRIPTORS VECTOR
114   TYPE(isot_type), TARGET, SAVE, ALLOCATABLE :: isotopes(:)    !=== ISOTOPES PARAMETERS VECTOR
115!$OMP THREADPRIVATE(tracers, isotopes)
116
117   !=== ALIASES FOR CURRENTLY SELECTED ISOTOPES FAMILY OF VARIABLES EMBEDDED IN THE VECTOR "isotopes"
118   TYPE(isot_type),         SAVE, POINTER :: isotope            !--- CURRENTLY SELECTED ISOTOPES FAMILY DESCRIPTOR
119   INTEGER,                 SAVE          :: ixIso, iH2O        !--- Index of the selected isotopes family and H2O family
120   LOGICAL,                 SAVE, POINTER :: isoCheck           !--- Flag to trigger the checking routines
121   TYPE(keys_type),         SAVE, POINTER :: isoKeys(:)         !--- ONE SET OF KEYS FOR EACH ISOTOPE (LISTED IN isoName)
122   CHARACTER(LEN=maxlen),   SAVE, POINTER :: isoName(:),   &    !--- ISOTOPES NAMES FOR THE CURRENTLY SELECTED FAMILY
123                                             isoZone(:),   &    !--- TAGGING ZONES  FOR THE CURRENTLY SELECTED FAMILY
124                                             isoPhas            !--- USED PHASES    FOR THE CURRENTLY SELECTED FAMILY
125   INTEGER,                 SAVE, POINTER ::  niso, nzone, &    !--- NUMBER OF ISOTOPES, TAGGING ZONES AND PHASES
126                                             nphas, ntiso, &    !--- NUMBER OF PHASES AND ISOTOPES + ISOTOPIC TAGGING TRACERS
127                                            itZonIso(:,:), &    !--- INDEX IN "isoTrac" AS f(tagging zone idx,  isotope idx)
128                                            iqTraPha(:,:)       !--- INDEX IN "qx"      AS f(isotopic tracer idx, phase idx)
129!$OMP THREADPRIVATE(isotope, ixIso,iH2O, isoCheck, isoKeys, isoName,isoZone,isoPhas, niso,nzone,nphas,ntiso, itZonIso,iqTraPha)
130
131   !=== VARIABLES FOR ISOTOPES INITIALIZATION AND FOR INCA
132   INTEGER,          SAVE,    ALLOCATABLE ::conv_flg(:),  &     !--- Convection     activation ; needed for INCA        (nbtr)
133                                             pbl_flg(:)         !--- Boundary layer activation ; needed for INCA        (nbtr)
134!$OMP THREADPRIVATE(conv_flg, pbl_flg)
135
136   !--- Aliases for older names + quantities to be removed             (will be replaced by:)
137   INTEGER, POINTER, SAVE :: ntraciso, ntraceurs_zone           !--- -> ntiso, nzone
138!$OMP THREADPRIVATE         (ntraciso, ntraceurs_zone)   
139   INTEGER, POINTER, SAVE :: index_trac(:,:), iqiso(:,:)        !--- -> itZonIso, iqTraPha
140!$OMP THREADPRIVATE         (index_trac,      iqiso)
141   INTEGER, SAVE :: niso_possibles                              !--- suppressed (use effective niso instead)
142!$OMP THREADPRIVATE(niso_possibles)
143   LOGICAL, SAVE :: ok_iso_verif                                !--- -> isoCheck
144!$OMP THREADPRIVATE(ok_iso_verif)
145   LOGICAL, SAVE, ALLOCATABLE :: use_iso(:)                     !--- suppressed
146!$OMP THREADPRIVATE             (use_iso)
147   INTEGER, SAVE, ALLOCATABLE :: indnum_fn_num(:)
148!$OMP THREADPRIVATE             (indnum_fn_num)
149
150#ifdef CPP_StratAer
151  !=== SPECIFIC TO STRATOSPHERIC AEROSOLS (CK/OB)
152  INTEGER, SAVE ::  nbtr_bin, nbtr_sulgas         !--- number of aerosols bins and sulfur gases for StratAer model
153!$OMP THREADPRIVATE(nbtr_bin, nbtr_sulgas)
154  INTEGER, SAVE ::  id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat
155!$OMP THREADPRIVATE(id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat)
156#endif
157
158CONTAINS
159
160SUBROUTINE init_infotrac_phy(type_trac_, tracers_, isotopes_, nqtottr_, nqCO2_, pbl_flg_, conv_flg_)
161
162   USE print_control_mod, ONLY: prt_level, lunout
163
164   IMPLICIT NONE
165   CHARACTER(LEN=*),INTENT(IN) :: type_trac_
166   TYPE(trac_type), INTENT(IN) ::  tracers_(:)
167   TYPE(isot_type), INTENT(IN) :: isotopes_(:)
168   INTEGER,         INTENT(IN) :: nqtottr_
169   INTEGER,         INTENT(IN) :: nqCO2_
170   INTEGER,         INTENT(IN) :: conv_flg_(:)
171   INTEGER,         INTENT(IN) ::  pbl_flg_(:)
172
173   INTEGER :: iq, ixt
174#ifdef CPP_StratAer
175   CHARACTER(LEN=maxlen), ALLOCATABLE :: tnames(:)
176#endif
177   CHARACTER(LEN=maxlen) :: modname="init_infotrac_phy"
178
179   type_trac = type_trac_
180   tracers   = tracers_
181   isotopes  = isotopes_
182   nqtottr   = nqtottr_
183   nqCO2     = nqCO2_
184   pbl_flg   =  pbl_flg_
185   conv_flg  = conv_flg_
186   nqtot     = SIZE(tracers_)
187   nqo       = COUNT(delPhase(tracers%name)=='H2O' .AND. tracers%iGeneration==0)
188   nbtr      = SIZE(conv_flg)
189   nbIso     = SIZE(isotopes_)
190
191   !=== Determine selected isotopes class related quantities:
192   !    ixIso, isotope, niso,isoKeys, ntiso,isoName, nzone,isoZone, nphas,isoPhas, itZonIso, iqTraPha, isoCheck
193   IF(.NOT.isoSelect('H2O')) iH2O = ixIso
194   IF(prt_level > 1) THEN
195      CALL msg('nqtot   = '//TRIM(int2str(nqtot)),   modname)
196      CALL msg('nbtr    = '//TRIM(int2str(nbtr )),   modname)
197      CALL msg('nqo     = '//TRIM(int2str(nqo  )),   modname)
198      CALL msg('niso    = '//TRIM(int2str(niso )),   modname)
199      CALL msg('ntiso   = '//TRIM(int2str(ntiso)),   modname)
200      CALL msg('nqtottr = '//TRIM(int2str(nqtottr)), modname)
201      CALL msg('nqCO2   = '//TRIM(int2str(nqCO2)),   modname)
202   END IF
203
204#ifdef CPP_StratAer
205   IF (type_trac == 'coag') THEN
206      nbtr_bin    = COUNT([(tracers(iq)%name(1:3)=='BIN', iq=1, nqtot)])
207      nbtr_sulgas = COUNT([(tracers(iq)%name(1:3)=='GAS', iq=1, nqtot)])
208      tnames = PACK(tracers(:)%name, MASK=tracers(:)%isInPhysics)
209      id_BIN01_strat = strIdx(tnames, 'BIN01'   )
210      id_OCS_strat   = strIdx(tnames, 'GASOSC'  )
211      id_SO2_strat   = strIdx(tnames, 'GASSO2'  )
212      id_H2SO4_strat = strIdx(tnames, 'GASH2SO4')
213      id_TEST_strat  = strIdx(tnames, 'GASTEST' )
214      CALL msg('nbtr_bin       ='//TRIM(int2str(nbtr_bin      )), modname)
215      CALL msg('nbtr_sulgas    ='//TRIM(int2str(nbtr_sulgas   )), modname)
216      CALL msg('id_BIN01_strat ='//TRIM(int2str(id_BIN01_strat)), modname)
217      CALL msg('id_OCS_strat   ='//TRIM(int2str(id_OCS_strat  )), modname)
218      CALL msg('id_SO2_strat   ='//TRIM(int2str(id_SO2_strat  )), modname)
219      CALL msg('id_H2SO4_strat ='//TRIM(int2str(id_H2SO4_strat)), modname)
220      CALL msg('id_TEST_strat  ='//TRIM(int2str(id_TEST_strat )), modname)
221   END IF
222#endif
223
224   !--- Isotopic quantities (to be removed soon)
225   ntraciso       => ntiso
226   ntraceurs_zone => nzone
227   iqiso          => iqTraPha
228   index_trac     => itZonIso
229   ok_iso_verif   = isoCheck
230   niso_possibles = SIZE(tnom_iso)
231   indnum_fn_num  = [(strIdx(isotope%keys(:)%name, tnom_iso(ixt)), ixt=1, niso_possibles)]
232   use_iso        = indnum_fn_num /= 0
233#ifdef ISOVERIF
234   CALL msg('iso_iName = '//strStack(int2str(PACK(tracers(:)%iso_iName, MASK=tracers(:)%iso_iGroup==iH2O))), modname)
235#endif
236
237END SUBROUTINE init_infotrac_phy
238
239
240!==============================================================================================================================
241!=== THE ROUTINE isoSelect IS USED TO SWITCH FROM AN ISOTOPE FAMILY TO ANOTHER: ISOTOPES DEPENDENT PARAMETERS ARE UPDATED
242!     Single generic "isoSelect" routine, using the predefined index of the parent (fast version) or its name (first call).
243!==============================================================================================================================
244LOGICAL FUNCTION isoSelectByName(iName, lVerbose) RESULT(lerr)
245   IMPLICIT NONE
246   CHARACTER(LEN=*),  INTENT(IN)  :: iName
247   LOGICAL, OPTIONAL, INTENT(IN) :: lVerbose
248   INTEGER :: iIso
249   LOGICAL :: lV
250   lV = .FALSE.; IF(PRESENT(lVerbose)) lV = lVerbose
251   iIso = strIdx(isotopes(:)%parent, iName)
252   lerr = iIso == 0
253   CALL msg('no isotope family named "'//TRIM(iName)//'"', ll=lerr .AND. lV)
254   IF(lerr) RETURN
255   lerr = isoSelectByIndex(iIso, lV)
256END FUNCTION isoSelectByName
257!==============================================================================================================================
258LOGICAL FUNCTION isoSelectByIndex(iIso, lVerbose) RESULT(lerr)
259   IMPLICIT NONE
260   INTEGER,           INTENT(IN) :: iIso
261   LOGICAL, OPTIONAL, INTENT(IN) :: lVerbose
262   LOGICAL :: lv
263   lv = .FALSE.; IF(PRESENT(lVerbose)) lv = lVerbose
264   lerr = .FALSE.
265   IF(iIso == ixIso) RETURN                                      !--- Nothing to do if the index is already OK
266   lerr = iIso<=0 .OR. iIso>nbIso
267   CALL msg('Inconsistent isotopes family index '//TRIM(int2str(iIso))//': should be > 0 and <= '//TRIM(int2str(nbIso))//'"',&
268            ll=lerr .AND. lV)
269   IF(lerr) RETURN
270   ixIso = iIso                                                  !--- Update currently selected family index
271   isotope  => isotopes(ixIso)                                   !--- Select corresponding component
272   isoKeys  => isotope%keys;     niso     => isotope%niso
273   isoName  => isotope%trac;     ntiso    => isotope%ntiso
274   isoZone  => isotope%zone;     nzone    => isotope%nzone
275   isoPhas  => isotope%phase;    nphas    => isotope%nphas
276   itZonIso => isotope%itZonIso; isoCheck => isotope%check
277   iqTraPha => isotope%iqTraPha
278END FUNCTION isoSelectByIndex
279!==============================================================================================================================
280
281
282END MODULE infotrac_phy
Note: See TracBrowser for help on using the repository browser.