source: LMDZ6/branches/Amaury_dev/libf/phylmd/infotrac_phy.F90 @ 5151

Last change on this file since 5151 was 5128, checked in by abarral, 2 months ago

Correct bug in vlspltqs_loc.f90 from r2270 where we call SSUM with incorrect arguments.
Merge the three different versions of abort_gcm into one
Fix seq, para 3D compilation broken from r5107 onwards
(lint) usual + Remove uneeded fixed-form continuations

File size: 30.3 KB
RevLine 
[4325]1!$Id: infotrac.F90 4301 2022-10-20 11:57:21Z dcugnet $
[5099]2
[2320]3MODULE infotrac_phy
4
[5117]5  USE       lmdz_strings, ONLY: msg, fmsg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse, strIdx
6  USE lmdz_readTracFiles, ONLY: trac_type, readTracersFiles, tracers, setGeneration, itZonIso, nzone, tran0, isoZone, &
[5098]7          delPhase, niso, getKey, isot_type, processIsotopes, isotope, maxTableWidth, iqIsoPha, nphas, ixIso, isoPhas, &
8          addPhase, iH2O, addKey, isoSelect, testTracersFiles, isoKeys, indexUpdate, iqWIsoPha, nbIso, ntiso, isoName, isoCheck
9  IMPLICIT NONE
[4046]10
[5098]11  PRIVATE
[2320]12
[5098]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  PUBLIC :: nbtr_bin, nbtr_sulgas                         !--- Number of aerosols bins and sulfur gases for StratAer model
19  PUBLIC :: id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat
[2320]20
[5098]21  !=== FOR WATER
22  PUBLIC :: ivap, iliq, isol
23  !=== FOR ISOTOPES: General
24  PUBLIC :: isot_type, nbIso                              !--- Derived type, full isotopes families database + nb of families
25  PUBLIC :: isoSelect, ixIso                              !--- Isotopes family selection tool + selected family index
26  !=== FOR ISOTOPES: Specific to water
27  PUBLIC :: iH2O                                          !--- H2O isotopes class index
28  !=== FOR ISOTOPES: Depending on the 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, nzone, nphas, ntiso              !---  " " numbers + isotopes & tagging tracers number
32  PUBLIC :: itZonIso                                      !--- idx "it" (in "isoName(1:niso)") = function(tagging idx, isotope idx)
33  PUBLIC :: iqIsoPha                                      !--- idx "iq" (in "qx") = function(isotope idx, phase idx) + aliases
34  PUBLIC :: iqWIsoPha                                      !--- Same as iqIsoPha but with normal water phases
[4984]35
[5098]36  PUBLIC :: isoCheck                                      !--- Run isotopes checking routines
37  !=== FOR BOTH TRACERS AND ISOTOPES
38  PUBLIC :: getKey                                        !--- Get a key from "tracers" or "isotope"
[2320]39
[5098]40  !=== CONVENTIONS FOR TRACERS NUMBERS:
41  !  |--------------------+-----------------------+-----------------+---------------+----------------------------|
42  !  | water in different |    water tagging      |  water isotopes | other tracers | additional tracers moments |
43  !  | phases: H2O_[gls]  |      isotopes         |                 |               |  for higher order schemes  |
44  !  |--------------------+-----------------------+-----------------+---------------+----------------------------|
45  !  |                    |                       |                 |               |                            |
46  !  |<--     nqo      -->|<-- nqo*niso* nzone -->|<-- nqo*niso  -->|<--  nbtr   -->|<--        (nmom)        -->|
47  !  |                    |                                         |                                            |
48  !  |                    |<-- nqo*niso*(nzone+1)  =   nqo*ntiso -->|<--    nqtottr = nbtr + nmom             -->|
49  !  |                                                                              = nqtot - nqo*(ntiso+1)      |
50  !  |                                                                                                           |
51  !  |<--                        nqtrue  =  nbtr + nqo*(ntiso+1)                 -->|                            |
52  !  |                                                                                                           |
53  !  |<--                        nqtot   =  nqtrue + nmom                                                     -->|
54  !  |                                                                                                           |
55  !  |-----------------------------------------------------------------------------------------------------------|
56  !  NOTES FOR THIS TABLE:
57  !  * Used "niso", "nzone" and "ntiso" are components of "isotopes(ip)" for water (isotopes(ip)%parent == 'H2O'),
58  !    since water is so far the sole tracers family, except passive CO2, removed from the main tracers table.
59  !  * For water, "nqo" is equal to the more general field "isotopes(ip)%nphas".
60  !  * "niso", "nzone", "ntiso", "nphas" are defined for other isotopic tracers families, if any.
[5099]61
[5098]62  !=== DERIVED TYPE EMBEDDING MOST OF THE TRACERS-RELATED QUANTITIES (LENGTH: nqtot)
63  !    Each entry is accessible using "%" sign.
64  !  |-------------+------------------------------------------------------+-------------+------------------------+
65  !  |  entry      | Meaning                                              | Former name | Possible values        |
66  !  |-------------+------------------------------------------------------+-------------+------------------------+
67  !  | name        | Name (short)                                         | tname       |                        |
68  !  | gen0Name    | Name of the 1st generation ancestor                  | /           |                        |
69  !  | parent      | Name of the parent                                   | /           |                        |
70  !  | longName    | Long name (with adv. scheme suffix) for outputs      | ttext       |                        |
71  !  | type        | Type (so far: tracer or tag)                         | /           | tracer,tag             |
72  !  | phase       | Phases list ("g"as / "l"iquid / "s"olid)             | /           | [g][l][s]              |
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  !  | keys        | key/val pairs accessible with "getKey" routine       | /           |                        |
80  !  | isAdvected  | advected tracers flag (.TRUE. if iadv >= 0)          | /           | nqtrue  .TRUE. values  |
81  !  | isInPhysics | tracers not extracted from the main table in physics | /           | nqtottr .TRUE. values  |
82  !  | iso_iGroup  | Isotopes group index in isotopes(:)                  | /           | 1:nbIso                |
83  !  | iso_iName   | Isotope  name  index in isotopes(iso_iGroup)%trac(:) | iso_indnum  | 1:niso                 |
84  !  | iso_iZone   | Isotope  zone  index in isotopes(iso_iGroup)%zone(:) | zone_num    | 1:nzone                |
85  !  | iso_iPhas   | Isotope  phase index in isotopes(iso_iGroup)%phas(:) | phase_num   | 1:nphas                |
86  !  +-------------+------------------------------------------------------+-------------+------------------------+
[5099]87
[5098]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  !  | iqIsoPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
99  !  | iqWIsoPha       | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
100  !  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
101  !  +-----------------+--------------------------------------------------+--------------------+-----------------+
[4120]102
[5098]103  !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
104  INTEGER, SAVE :: nqtot, &                     !--- Tracers nb in dynamics (incl. higher moments + H2O)
105          nbtr, &                     !--- Tracers nb in physics  (excl. higher moments + H2O)
106          nqo, &                     !--- Number of water phases
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(s)
110  !$OMP THREADPRIVATE(nqtot, nbtr, nqo, nqtottr, nqCO2, type_trac)
[4170]111
[5098]112  !=== INDICES OF WATER
113  INTEGER, SAVE :: ivap, iliq, isol ! Indices for vap, liq and ice
114  !$OMP THREADPRIVATE(ivap,iliq,isol)
[4984]115
[5098]116  !=== VARIABLES FOR INCA
117  INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), &   !--- Convection     activation ; needed for INCA        (nbtr)
118          pbl_flg(:)      !--- Boundary layer activation ; needed for INCA        (nbtr)
119  !$OMP THREADPRIVATE(conv_flg, pbl_flg)
[4120]120
[4056]121  !=== SPECIFIC TO STRATOSPHERIC AEROSOLS (CK/OB)
[5098]122  INTEGER, SAVE :: nbtr_bin, nbtr_sulgas         !--- number of aerosols bins and sulfur gases for StratAer model
123  !$OMP THREADPRIVATE(nbtr_bin, nbtr_sulgas)
124  INTEGER, SAVE :: id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat
125  !$OMP THREADPRIVATE(id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat)
[3677]126
[4120]127CONTAINS
[2320]128
[5098]129  SUBROUTINE init_infotrac_phy
[5112]130    USE lmdz_ioipsl_getin_p, ONLY: getin_p
[4325]131#ifdef REPROBUS
[4358]132   USE CHEM_REP, ONLY: Init_chem_rep_trac
[4325]133#endif
[5101]134    USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA, CPPKEY_STRATAER
[5111]135    USE lmdz_abort_physic, ONLY: abort_physic
[5118]136    USE lmdz_iniprint, ONLY: lunout, prt_level
[5128]137
138
[5098]139    IMPLICIT NONE
140    !==============================================================================================================================
[5099]141
[5098]142    !   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
143    !   -------
[5099]144
[5098]145    !   Modifications:
146    !   --------------
147    !   05/94: F.Forget      Modif special traceur
148    !   02/02: M-A Filiberti Lecture de traceur.def
149    !   01/22: D. Cugnet     Nouveaux tracer.def et tracer_*.def + encapsulation (types trac_type et isot_type)
[5099]150
[5098]151    !   Objet:
152    !   ------
153    !   GCM LMD nouvelle grille
[5099]154
[5098]155    !==============================================================================================================================
156    !   ... modification de l'integration de q ( 26/04/94 ) ....
157    !------------------------------------------------------------------------------------------------------------------------------
158    ! Declarations:
159    INCLUDE "dimensions.h"
[3924]160
[5098]161    !------------------------------------------------------------------------------------------------------------------------------
162    ! Local variables
163    INTEGER, ALLOCATABLE :: hadv(:), vadv(:)                          !--- Horizontal/vertical transport scheme number
164    INTEGER, ALLOCATABLE :: had (:), hadv_inca(:), conv_flg_inca(:), &!--- Variables specific to INCA
165            vad (:), vadv_inca(:), pbl_flg_inca(:)
166    CHARACTER(LEN = 8), ALLOCATABLE :: solsym_inca(:)                   !--- Tracers names for INCA
167    INTEGER :: nqINCA
168    CHARACTER(LEN = maxlen), ALLOCATABLE :: tnames(:)
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 = maxlen) :: msg1, texp, ttp                          !--- String for messages and expanded tracers type
172    INTEGER :: fType                                                  !--- Tracers description file type ; 0: none
173    !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def"
174    INTEGER :: nqtrue                                                 !--- Tracers nb from tracer.def (no higher order moments)
175    INTEGER :: iad                                                    !--- Advection scheme number
176    INTEGER :: iq, jq, nt, im, nm, k                                 !--- Indexes and temporary variables
177    LOGICAL :: lerr, lInit
178    TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
179    TYPE(trac_type), POINTER :: t1, t(:)
180    CHARACTER(LEN = maxlen), ALLOCATABLE :: types_trac(:)  !--- Keyword for tracers type(s), parsed version
[2690]181
[5098]182    CHARACTER(LEN = *), PARAMETER :: modname = "init_infotrac_phy"
183    !------------------------------------------------------------------------------------------------------------------------------
184    ! Initialization :
185    !------------------------------------------------------------------------------------------------------------------------------
186    suff = ['x ', 'y ', 'z ', 'xx', 'xy', 'xz', 'yy', 'yz', 'zz']
187    descrq(1:30) = '   '
188    descrq(1:2) = ['LMV', 'BAK']
189    descrq(10:20) = ['VL1', 'VLP', 'FH1', 'FH2', 'VLH', '   ', 'PPM', 'PPS', 'PPP', '   ', 'SLP']
190    descrq(30) = 'PRA'
[4638]191
[5098]192    CALL getin_p('type_trac', type_trac)
193
194    lerr = strParse(type_trac, '|', types_trac, n = nt)
195    IF (nt > 1) THEN
[5082]196      IF (nt > 2) CALL abort_physic(modname, 'you need to modify type_trac, this version is not supported by lmdz', 1)
[5098]197      IF (nt == 2) type_trac = types_trac(2)
198    ENDIF
[4638]199
[5098]200    CALL msg('type_trac = "' // TRIM(type_trac) // '"', modname)
201    lInit = .NOT.ALLOCATED(tracers)
[4325]202
[5098]203    !##############################################################################################################################
204    IF(lInit) THEN                                                    !=== SKIPED IF ALREADY DONE IN dyn3d_common/infotrac  ####
205      !##############################################################################################################################
206      !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
207      msg1 = 'For type_trac = "' // TRIM(type_trac) // '":'
208      SELECT CASE(type_trac)
209      CASE('inca'); CALL msg(TRIM(msg1) // ' coupling with INCA chemistry model', modname)
210      CASE('inco'); CALL msg(TRIM(msg1) // ' coupling jointly with INCA and CO2 cycle', modname)
211      CASE('repr'); CALL msg(TRIM(msg1) // ' coupling with REPROBUS chemistry model', modname)
212      CASE('co2i'); CALL msg(TRIM(msg1) // ' you have chosen to run with CO2 cycle', modname)
213      CASE('coag'); CALL msg(TRIM(msg1) // ' tracers are treated for COAGULATION tests', modname)
214      CASE('lmdz'); CALL msg(TRIM(msg1) // ' tracers are treated in LMDZ only', modname)
215      CASE DEFAULT; CALL abort_physic(modname, 'type_trac=' // TRIM(type_trac) // ' not possible yet.', 1)
216      END SELECT
[4325]217
[5098]218      !--- COHERENCE TEST BETWEEN "type_trac" AND PREPROCESSING KEYS
219      SELECT CASE(type_trac)
[4389]220      CASE('inca', 'inco')
[5103]221        IF (.NOT. CPPKEY_INCA) THEN
[5098]222          CALL abort_physic(modname, 'You must add cpp key INCA and compile with INCA code', 1)
223        END IF
[4389]224      CASE('repr')
[4325]225#ifndef REPROBUS
[5098]226        CALL abort_physic(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1)
[4325]227#endif
[4389]228      CASE('coag')
[5098]229        IF (.NOT. CPPKEY_STRATAER) THEN
230          CALL abort_physic(modname, 'You must add cpp key StratAer and compile with StratAer code', 1)
231        END IF
232      END SELECT
233      !##############################################################################################################################
234    END IF
235    !##############################################################################################################################
[2690]236
[5098]237    nqCO2 = COUNT([type_trac == 'inco', type_trac == 'co2i'])
[4325]238
[5098]239    !==============================================================================================================================
240    ! 1) Get the numbers of: true (first order only) tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid)
241    !==============================================================================================================================
242    texp = type_trac                                                  !=== EXPANDED VERSION OF "type_trac", WITH "|" SEPARATOR
243    IF(texp == 'inco') texp = 'co2i|inca'
244    IF(texp /= 'lmdz') texp = 'lmdz|' // TRIM(texp)
[4389]245
[5098]246    !=== DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE
247    IF(testTracersFiles(modname, texp, fType, lInit)) CALL abort_physic(modname, 'problem with tracers file(s)', 1)
[4500]248
[5098]249    ttp = type_trac; IF(fType /= 1) ttp = texp
[4389]250
[5098]251    !##############################################################################################################################
252    IF(lInit) THEN
253      IF(readTracersFiles(ttp, lRepr = type_trac=='repr')) CALL abort_physic(modname, 'problem with tracers file(s)', 1)
254    ELSE
[4389]255      CALL msg('No tracers description file(s) reading needed: already done in the dynamics', modname)
[5098]256    END IF
257    !##############################################################################################################################
[4325]258
[5098]259    !---------------------------------------------------------------------------------------------------------------------------
260    IF(fType == 0) CALL abort_physic(modname, 'Missing tracers file: "traceur.def", "tracer.def" or "tracer_<keyword>.def file.', 1)
261    !---------------------------------------------------------------------------------------------------------------------------
262    IF(fType == 1 .AND. ANY(['inca', 'inco']==type_trac) .AND. lInit) THEN  !=== FOUND OLD STYLE INCA "traceur.def"
263      !---------------------------------------------------------------------------------------------------------------------------
[5118]264      nqo = SIZE(tracers) - nqCO2
265      CALL Init_chem_inca_trac(nqINCA)                               !--- Get nqINCA from INCA
266      nbtr = nqINCA + nqCO2                                          !--- Number of tracers passed to phytrac
267      nqtrue = nbtr + nqo                                            !--- Total number of "true" tracers
268      IF(ALL([2, 3] /= nqo)) CALL abort_physic(modname, 'Only 2 or 3 water phases allowed ; found nqo=' // TRIM(int2str(nqo)), 1)
269      ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA))
270      ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA), pbl_flg_inca(nqINCA))
271      CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca)
272      ALLOCATE(ttr(nqtrue))
273      ttr(1:nqo + nqCO2) = tracers
274      ttr(1:nqo)%component = 'lmdz'
275      ttr(1 + nqo:nqCO2 + nqo)%component = 'co2i'
276      ttr(1 + nqo + nqCO2:nqtrue)%component = 'inca'
277      ttr(1 + nqo:nqtrue)%name = [('CO2     ', k = 1, nqCO2), solsym_inca]
278      ttr(1 + nqo + nqCO2:nqtrue)%parent = tran0
279      ttr(1 + nqo + nqCO2:nqtrue)%phase = 'g'
280      lerr = getKey('hadv', had, ky = tracers(:)%keys)
281      lerr = getKey('vadv', vad, ky = tracers(:)%keys)
282      hadv(1:nqo + nqCO2) = had(:); hadv(1 + nqo + nqCO2:nqtrue) = hadv_inca
283      vadv(1:nqo + nqCO2) = vad(:); vadv(1 + nqo + nqCO2:nqtrue) = vadv_inca
284      CALL MOVE_ALLOC(FROM = ttr, TO = tracers)
285      DO iq = 1, nqtrue
286        t1 => tracers(iq)
287        CALL addKey('name', t1%name, t1%keys)
288        CALL addKey('component', t1%component, t1%keys)
289        CALL addKey('parent', t1%parent, t1%keys)
290        CALL addKey('phase', t1%phase, t1%keys)
291      END DO
292      IF(setGeneration(tracers)) CALL abort_physic(modname, 'See below', 1) !- SET FIELDS %iGeneration, %gen0Name
293      DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca)
[5098]294      !---------------------------------------------------------------------------------------------------------------------------
295    ELSE                                                              !=== OTHER CASES (OLD OR NEW FORMAT, NO INCA MODULE)
296      !---------------------------------------------------------------------------------------------------------------------------
297      nqo = COUNT(delPhase(tracers(:)%name)     == 'H2O' &
298              .AND. tracers(:)%component == 'lmdz') !--- Number of water phases
[4325]299      nqtrue = SIZE(tracers)                                         !--- Total number of "true" tracers
[5098]300      nbtr = nqtrue - COUNT(delPhase(tracers(:)%gen0Name) == 'H2O' &
301              .AND. tracers(:)%component == 'lmdz') !--- Number of tracers passed to phytrac
[5118]302      nqINCA = COUNT(tracers(:)%component == 'inca')
[5098]303      lerr = getKey('hadv', hadv, ky = tracers(:)%keys)
304      lerr = getKey('vadv', vadv, ky = tracers(:)%keys)
305      !---------------------------------------------------------------------------------------------------------------------------
306    END IF
307    !---------------------------------------------------------------------------------------------------------------------------
[4325]308
[5098]309    !--- Transfert the number of tracers to Reprobus
[4325]310#ifdef REPROBUS
311   CALL Init_chem_rep_trac(nbtr, nqo, tracers(:)%name)
312#endif
313
[5098]314    !##############################################################################################################################
315    IF(lInit) THEN                                                    !=== SKIPED IF ALREADY DONE IN dyn3d_common/infotrac  ####
316      !##############################################################################################################################
[4325]317
[5098]318      !==============================================================================================================================
319      ! 2) Calculate nqtot, number of tracers needed (greater if advection schemes 20 or 30 have been chosen).
320      !==============================================================================================================================
321      DO iq = 1, nqtrue
322        IF(hadv(iq)<20 .OR. (ANY(hadv(iq)==[20, 30]) .AND. hadv(iq)==vadv(iq))) CYCLE
323        WRITE(msg1, '("The choice hadv=",i0,", vadv=",i0,a)')hadv(iq), vadv(iq), ' for "' // TRIM(tracers(iq)%name) // '" is not available'
324        CALL abort_physic(modname, TRIM(msg1), 1)
325      END DO
326      nqtot = COUNT(hadv< 20 .AND. vadv< 20) &                     !--- No additional tracer
327              + 4 * COUNT(hadv==20 .AND. vadv==20) &                     !--- 3  additional tracers
328              + 10 * COUNT(hadv==30 .AND. vadv==30)                       !--- 9  additional tracers
[4325]329
[5098]330      !--- More tracers due to the choice of advection scheme => assign total number of tracers
331      IF(nqtot /= nqtrue) THEN
332        CALL msg('The choice of advection scheme for one or more tracers makes it necessary to add tracers')
333        CALL msg('The number of true tracers is ' // TRIM(int2str(nqtrue)))
334        CALL msg('The total number of tracers needed is ' // TRIM(int2str(nqtot)))
335      END IF
[4325]336
[5098]337      !==============================================================================================================================
338      ! 3) Determine the advection scheme ; needed to compute the full tracers list, the long names, nqtot and %isAdvected
339      !==============================================================================================================================
340      ALLOCATE(ttr(nqtot))
341      jq = nqtrue + 1; tracers(:)%iadv = -1
342      DO iq = 1, nqtrue
343        t1 => tracers(iq)
[4325]344
[5098]345        !--- VERIFY THE CHOICE OF ADVECTION SCHEME
346        iad = -1
347        IF(hadv(iq)     ==    vadv(iq)) iad = hadv(iq)
348        IF(hadv(iq)==10 .AND. vadv(iq)==16) iad = 11
349        WRITE(msg1, '("Bad choice of advection scheme for ",a,": hadv = ",i0,", vadv = ",i0)')TRIM(t1%name), hadv(iq), vadv(iq)
350        IF(iad == -1) CALL abort_physic(modname, msg1, 1)
[4325]351
[5098]352        !--- SET FIELDS %longName, %isAdvected, %isInPhysics
353        t1%longName = t1%name; IF(iad > 0) t1%longName = TRIM(t1%name) // descrq(iad)
354        t1%isAdvected = iad >= 0
355        t1%isInPhysics = delPhase(t1%gen0Name) /= 'H2O' &
356                .OR. t1%component /= 'lmdz' !=== OTHER EXCEPTIONS TO BE ADDED: CO2i, SURSATURATED WATER CLOUD...
357        ttr(iq) = t1
[4325]358
[5098]359        !--- DEFINE THE HIGHER ORDER TRACERS, IF ANY
360        nm = 0
361        IF(iad == 20) nm = 3                                           !--- 2nd order scheme
362        IF(iad == 30) nm = 9                                           !--- 3rd order scheme
363        IF(nm == 0) CYCLE                                              !--- No higher moments
364        ttr(jq + 1:jq + nm) = t1
365        ttr(jq + 1:jq + nm)%name = [(TRIM(t1%name) // '-' // TRIM(suff(im)), im = 1, nm) ]
366        ttr(jq + 1:jq + nm)%parent = [(TRIM(t1%parent) // '-' // TRIM(suff(im)), im = 1, nm) ]
367        ttr(jq + 1:jq + nm)%longName = [(TRIM(t1%longName) // '-' // TRIM(suff(im)), im = 1, nm) ]
368        ttr(jq + 1:jq + nm)%isAdvected = [(.FALSE., im = 1, nm) ]
369        jq = jq + nm
370      END DO
371      DEALLOCATE(hadv, vadv)
372      CALL MOVE_ALLOC(FROM = ttr, TO = tracers)
[4325]373
[5098]374      !--- SET FIELDS %iqParent, %nqChildren, %iGeneration, %iqDescen, %nqDescen
375      IF(indexUpdate(tracers)) CALL abort_gcm(modname, 'problem when processing isotopes parameters', 1)
[4325]376
[5098]377      !##############################################################################################################################
378    END IF
379    !##############################################################################################################################
[4325]380
[5098]381    !##############################################################################################################################
382    IF(.NOT.lInit) THEN
383      !##############################################################################################################################
384      nqtot = SIZE(tracers)
385      !##############################################################################################################################
386    ELSE
387      !##############################################################################################################################
[4325]388
[5098]389      !=== READ PHYSICAL PARAMETERS FOR ISOTOPES
390      niso = 0; nzone = 0; nphas = nqo; ntiso = 0; isoCheck = .FALSE.
391      IF(processIsotopes()) CALL abort_physic(modname, 'Problem when processing isotopes parameters', 1)
[4325]392
[5098]393      !##############################################################################################################################
394    END IF
395    !##############################################################################################################################
396    !--- Convection / boundary layer activation for all tracers
397    IF (.NOT.ALLOCATED(conv_flg)) ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1
398    IF (.NOT.ALLOCATED(pbl_flg)) ALLOCATE(pbl_flg(nbtr));  pbl_flg(1:nbtr) = 1
[4325]399
[5098]400    !--- Note: nqtottr can differ from nbtr when nmom/=0
401    nqtottr = nqtot - COUNT(delPhase(tracers%gen0Name) == 'H2O' .AND. tracers%component == 'lmdz')
402    IF(COUNT(tracers%iso_iName == 0) - COUNT(delPhase(tracers%name) == 'H2O' .AND. tracers%component == 'lmdz') /= nqtottr) &
403            CALL abort_physic(modname, 'problem with the computation of nqtottr', 1)
[4325]404
[5098]405    !=== DISPLAY THE RESULTS
406    CALL msg('nqo    = ' // TRIM(int2str(nqo)), modname)
407    CALL msg('nbtr   = ' // TRIM(int2str(nbtr)), modname)
408    CALL msg('nqtrue = ' // TRIM(int2str(nqtrue)), modname)
409    CALL msg('nqtot  = ' // TRIM(int2str(nqtot)), modname)
410    CALL msg('niso   = ' // TRIM(int2str(niso)), modname)
411    CALL msg('ntiso  = ' // TRIM(int2str(ntiso)), modname)
412    IF (CPPKEY_INCA) THEN
413      CALL msg('nqCO2  = ' // TRIM(int2str(nqCO2)), modname)
414      CALL msg('nqINCA = ' // TRIM(int2str(nqINCA)), modname)
415    END IF
416    t => tracers
417    CALL msg('Information stored in infotrac_phy :', modname)
418    IF(dispTable('issssssssiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp', &
419            'isPh', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'], &
420            cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component, bool2str(t%isInPhysics)), &
421            cat([(iq, iq = 1, nqtot)], t%iGeneration, t%iqParent, t%nqDescen, t%nqChildren, t%iso_iGroup, &
422                    t%iso_iName, t%iso_iZone, t%iso_iPhase), nColMax = maxTableWidth, nHead = 2, sub = modname))   &
423            CALL abort_physic(modname, "problem with the tracers table content", 1)
424    IF(niso > 0) THEN
425      CALL msg('Where, for isotopes family "' // TRIM(isotope%parent) // '":', modname)
426      CALL msg('  isoKeys%name = ' // strStack(isoKeys%name), modname)
427      CALL msg('  isoName = ' // strStack(isoName), modname)
428      CALL msg('  isoZone = ' // strStack(isoZone), modname)
429      CALL msg('  isoPhas = ' // TRIM(isoPhas), modname)
430    ELSE
[4325]431      CALL msg('No isotopes identified.', modname)
[5098]432    END IF
[4325]433
434#ifdef ISOVERIF
435   CALL msg('iso_iName = '//strStack(int2str(PACK(tracers(:)%iso_iName, MASK=tracers(:)%iso_iGroup==iH2O))), modname)
436#endif
[5098]437    IF (CPPKEY_STRATAER) THEN
438      IF (type_trac == 'coag') THEN
439        nbtr_bin = COUNT([(tracers(iq)%name(1:3)=='BIN', iq = 1, nqtot)])
440        nbtr_sulgas = COUNT([(tracers(iq)%name(1:3)=='GAS', iq = 1, nqtot)])
441        tnames = PACK(tracers(:)%name, MASK = tracers(:)%isInPhysics)
442        id_BIN01_strat = strIdx(tnames, 'BIN01')
443        id_OCS_strat = strIdx(tnames, 'GASOCS')
444        id_SO2_strat = strIdx(tnames, 'GASSO2')
445        id_H2SO4_strat = strIdx(tnames, 'GASH2SO4')
446        id_TEST_strat = strIdx(tnames, 'GASTEST')
447        CALL msg('nbtr_bin       =' // TRIM(int2str(nbtr_bin)), modname)
448        CALL msg('nbtr_sulgas    =' // TRIM(int2str(nbtr_sulgas)), modname)
449        CALL msg('id_BIN01_strat =' // TRIM(int2str(id_BIN01_strat)), modname)
450        CALL msg('id_OCS_strat   =' // TRIM(int2str(id_OCS_strat)), modname)
451        CALL msg('id_SO2_strat   =' // TRIM(int2str(id_SO2_strat)), modname)
452        CALL msg('id_H2SO4_strat =' // TRIM(int2str(id_H2SO4_strat)), modname)
453        CALL msg('id_TEST_strat  =' // TRIM(int2str(id_TEST_strat)), modname)
454      END IF
455    END IF
456    CALL msg('end', modname)
[4056]457
[5098]458  END SUBROUTINE init_infotrac_phy
[2320]459
460END MODULE infotrac_phy
Note: See TracBrowser for help on using the repository browser.