Ignore:
Timestamp:
Sep 23, 2024, 4:12:29 PM (3 months ago)
Author:
abarral
Message:

Merge r5196, r5199
Nb: skipping r5197 r5198 as they revert one-another

Location:
LMDZ6/branches/Amaury_dev
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev

  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/lmdz_infotrac.f90

    r5185 r5221  
    55          delPhase, niso, getKey, isot_type, processIsotopes, isotope, maxTableWidth, iqIsoPha, nphas, ixIso, isoPhas, &
    66          addPhase, iH2O, addKey, isoSelect, testTracersFiles, isoKeys, indexUpdate, iqWIsoPha, nbIso, ntiso, isoName, isoCheck
    7 
    8 
    9   IMPLICIT NONE
    10 
    11   PRIVATE
     7  USE lmdz_readTracFiles, ONLY: new2oldH2O, newHNO3, oldHNO3
     8
     9  IMPLICIT NONE; PRIVATE
    1210
    1311  !=== FOR TRACERS:
     
    1614  PUBLIC :: nqtot, nbtr, nqo, nqCO2, nqtottr      !--- Main dimensions
    1715  PUBLIC :: conv_flg, pbl_flg                             !--- Convection & boundary layer activation keys
     16  PUBLIC :: new2oldH2O, newHNO3, oldHNO3                  !--- For backwards compatibility in dynetat0
     17  PUBLIC :: addPhase, delPhase                            !--- Add/remove the phase from the name of a tracer
     18
    1819
    1920  !=== FOR ISOTOPES: General
     
    2122  PUBLIC :: isoSelect, ixIso                              !--- Isotopes family selection tool + selected family index
    2223  !=== FOR ISOTOPES: Specific to water
    23   PUBLIC :: iH2O                                          !--- H2O isotopes class index
     24  PUBLIC :: iH2O                                          !--- Value of "ixIso" for "H2O" isotopes class
    2425  PUBLIC :: min_qParent, min_qMass, min_ratio             !--- Min. values for various isotopic quantities
    2526  !=== FOR ISOTOPES: Depending on the selected isotopes family
    26   PUBLIC :: isotope, isoKeys                              !--- Selected isotopes database + associated keys (cf. getKey)
    27   PUBLIC :: isoName, isoZone, isoPhas                     !--- Isotopes and tagging zones names, phases
    28   PUBLIC :: niso, nzone, nphas, ntiso              !---  " " numbers + isotopes & tagging tracers number
    29   PUBLIC :: itZonIso                                      !--- idx "it" (in "isoName(1:niso)") = function(tagging idx, isotope idx)
    30   PUBLIC :: iqIsoPha                                      !--- idx "iq" (in "qx") = function(isotope idx, phase idx) + aliases
     27  PUBLIC :: isotope                                       !--- Selected isotopes database (argument of getKey)
     28  PUBLIC :: isoKeys, isoName, isoZone, isoPhas            !--- Isotopes keys & names, tagging zones names, phases
     29  PUBLIC :: niso, ntiso, nzone, nphas            !--- Number of   "   "
     30  PUBLIC :: itZonIso                                      !--- index "it" in "isoName(1:niso)" = f(tagging idx, isotope idx)
     31  PUBLIC :: iqIsoPha                                      !--- index "iq" in "qx"              = f(isotope idx,   phase idx)
    3132  PUBLIC :: isoCheck                                      !--- Run isotopes checking routines
    3233  !=== FOR BOTH TRACERS AND ISOTOPES
     
    3637  !  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    3738  !  | water in different |    water tagging      |  water isotopes | other tracers | additional tracers moments |
    38   !  | phases: H2O_[gls|      isotopes         |                 |               |  for higher order schemes  |
     39  !  | phases: H2O_[glsrb]|      isotopes         |                 |               |  for higher order schemes  |
    3940  !  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    4041  !  |                    |                       |                 |               |                            |
     
    6162  !  |-------------+------------------------------------------------------+-------------+------------------------+
    6263  !  | name        | Name (short)                                         | tname       |                        |
     64  !  | keys        | key/val pairs accessible with "getKey" routine       | /           |                        |
    6365  !  | gen0Name    | Name of the 1st generation ancestor                  | /           |                        |
    6466  !  | parent      | Name of the parent                                   | /           |                        |
    6567  !  | longName    | Long name (with adv. scheme suffix) for outputs      | ttext       |                        |
    6668  !  | type        | Type (so far: tracer or tag)                         | /           | tracer,tag             |
    67   !  | phase       | Phases list ("g"as / "l"iquid / "s"olid)             | /           | [g][l][s]              |
     69  !  | phase       | Phases list ("g"as / "l"iquid / "s"olid              |             | [g|l|s|r|b]            |
     70  !  |             |              "r"(cloud) / "b"lowing)                 | /           |                        |
    6871  !  | component   | Name(s) of the merged/cumulated section(s)           | /           | coma-separated names   |
    6972  !  | iGeneration | Generation (>=1)                                     | /           |                        |
     
    7477  !  | keys        | key/val pairs accessible with "getKey" routine       | /           |                        |
    7578  !  | iadv        | Advection scheme number                              | iadv        | 1,2,10-20(exc.15,19),30|
    76   !  | isAdvected  | advected tracers flag (.TRUE. if iadv >= 0)          | /           | nqtrue  .TRUE. values  |
    77   !  | isInPhysics | tracers not extracted from the main table in physics | /           | nqtottr .TRUE. values  |
     79  !  | isAdvected  | Advected tracers flag (.TRUE. if iadv >= 0)          | /           | nqtrue  .TRUE. values  |
     80  !  | isInPhysics | Tracers not extracted from the main table in physics | /           | nqtottr .TRUE. values  |
    7881  !  | iso_iGroup  | Isotopes group index in isotopes(:)                  | /           | 1:nbIso                |
    7982  !  | iso_iName   | Isotope  name  index in isotopes(iso_iGroup)%trac(:) | iso_indnum  | 1:niso                 |
     
    9194  !  | trac   | ntiso  | Isotopes + tagging tracers list + number         | / | ntraciso       |                 |
    9295  !  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
    93   !  | phase  | nphas  | Phases                     list + number         |                    | [g][l][s], 1:3 |
     96  !  | phase  | nphas  | Phases                     list + number         |                    | [g|l|s|r|b] 1:5 |
    9497  !  | iqIsoPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
    9598  !  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
     
    104107          nqtottr, &                    !--- Number of tracers passed to phytrac (TO BE DELETED ?)
    105108          nqCO2                         !--- Number of tracers of CO2  (ThL)
    106   CHARACTER(LEN = maxlen), SAVE :: type_trac                     !--- Keyword for tracers type
     109  CHARACTER(LEN = maxlen), SAVE :: type_trac                     !--- Keyword for tracers type(s)
    107110
    108111  !=== VARIABLES FOR INCA
    109   INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), &   !--- Convection     activation ; needed for INCA        (nbtr)
    110           pbl_flg(:)      !--- Boundary layer activation ; needed for INCA        (nbtr)
     112  INTEGER, DIMENSION(:), SAVE, ALLOCATABLE :: &
     113          conv_flg, pbl_flg                           !--- Convection / boundary layer activation (nbtr)
    111114
    112115CONTAINS
     
    159162    TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
    160163    TYPE(trac_type), POINTER :: t1, t(:)
    161     CHARACTER(LEN = maxlen), ALLOCATABLE :: types_trac(:)  !--- Keyword for tracers type(s), parsed version
    162 
     164    CHARACTER(LEN = maxlen), ALLOCATABLE :: types_trac(:)             !--- Keywords for tracers type(s), parsed version
    163165    CHARACTER(LEN = *), PARAMETER :: modname = "init_infotrac"
    164166    !------------------------------------------------------------------------------------------------------------------------------
     
    171173    descrq(30) = 'PRA'
    172174
    173     CALL msg('type_trac = "' // TRIM(type_trac) // '"', modname)
    174 
    175175    lerr = strParse(type_trac, '|', types_trac, n = nt)
    176176    IF (nt > 1) THEN
     
    179179    ENDIF
    180180
    181 
     181    CALL msg('type_trac = "' // TRIM(type_trac) // '"', modname)
    182182
    183183    !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
     
    212212
    213213    !==============================================================================================================================
    214     ! 1) Get the numbers of: true (first order only) tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid)
    215     !==============================================================================================================================
    216     texp = type_trac                                                  !=== EXPANDED VERSION OF "type_trac", WITH "|" SEPARATOR
     214    ! 0) DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE AND READ IT
     215    !==============================================================================================================================
     216    texp = type_trac                                                  !=== EXPANDED (WITH "|" SEPARATOR) "type_trac"
    217217    IF(texp == 'inco') texp = 'co2i|inca'
    218218    IF(texp /= 'lmdz') texp = 'lmdz|' // TRIM(texp)
    219 
    220     !=== DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE
    221219    IF(testTracersFiles(modname, texp, fType, .TRUE.)) CALL abort_gcm(modname, 'problem with tracers file(s)', 1)
    222220    ttp = type_trac; IF(fType /= 1) ttp = texp
    223 
    224221    IF(readTracersFiles(ttp, lRepr = type_trac=='repr')) CALL abort_gcm(modname, 'problem with tracers file(s)', 1)
     222    !==============================================================================================================================
     223    ! 1) Get various numbers: "nqtrue" (first order only tracers), "nqo" (water phases), 'nbtr' (tracers passed to physics), etc.
     224    !==============================================================================================================================
     225
    225226    !---------------------------------------------------------------------------------------------------------------------------
    226     IF(fType == 0) CALL abort_gcm(modname, 'Missing tracers file: "traceur.def", "tracer.def" or "tracer_<keyword>.def file.', 1)
     227    IF(fType == 0) CALL abort_gcm(modname, 'Missing "traceur.def", "tracer.def" or "tracer_<keyword>.def tracers file.', 1)
    227228    !---------------------------------------------------------------------------------------------------------------------------
    228229    IF(fType == 1 .AND. ANY(['inca', 'inco']==type_trac)) THEN         !=== FOUND OLD STYLE INCA "traceur.def"
    229230      !---------------------------------------------------------------------------------------------------------------------------
    230       nqo = SIZE(tracers) - nqCO2
    231       CALL init_chem_inca_trac(nqINCA)                               !--- Get nqINCA from INCA
    232       nbtr = nqINCA + nqCO2                                          !--- Number of tracers passed to phytrac
    233       nqtrue = nbtr + nqo                                            !--- Total number of "true" tracers
    234       IF(ALL([2, 3] /= nqo)) CALL abort_gcm(modname, 'Only 2 or 3 water phases allowed ; found nqo=' // TRIM(int2str(nqo)), 1)
    235       ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA))
    236       ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA), pbl_flg_inca(nqINCA))
    237       CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca)
    238       ALLOCATE(ttr(nqtrue))
    239       ttr(1:nqo + nqCO2) = tracers
    240       ttr(1:nqo)%component = 'lmdz'
    241       ttr(1 + nqo:nqCO2 + nqo)%component = 'co2i'
    242       ttr(1 + nqo + nqCO2:nqtrue)%component = 'inca'
    243       ttr(1 + nqo:nqtrue)%name = [('CO2     ', iq = 1, nqCO2), solsym_inca]
    244       ttr(1 + nqo + nqCO2:nqtrue)%parent = tran0
    245       ttr(1 + nqo + nqCO2:nqtrue)%phase = 'g'
    246       lerr = getKey('hadv', had, ky = tracers(:)%keys)
    247       lerr = getKey('vadv', vad, ky = tracers(:)%keys)
    248       hadv(1:nqo + nqCO2) = had(:); hadv(1 + nqo + nqCO2:nqtrue) = hadv_inca
    249       vadv(1:nqo + nqCO2) = vad(:); vadv(1 + nqo + nqCO2:nqtrue) = vadv_inca
    250       CALL MOVE_ALLOC(FROM = ttr, TO = tracers)
    251       DO iq = 1, nqtrue
    252         t1 => tracers(iq)
    253         CALL addKey('name', t1%name, t1%keys)
    254         CALL addKey('component', t1%component, t1%keys)
    255         CALL addKey('parent', t1%parent, t1%keys)
    256         CALL addKey('phase', t1%phase, t1%keys)
    257       END DO
    258       IF(setGeneration(tracers)) CALL abort_gcm(modname, 'See above', 1) !- SET FIELDS %iGeneration, %gen0Name
    259       DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca)
    260       !---------------------------------------------------------------------------------------------------------------------------
     231      IF (CPPKEY_INCA) THEN
     232        nqo = SIZE(tracers) - nqCO2
     233        CALL init_chem_inca_trac(nqINCA)                               !--- Get nqINCA from INCA
     234        nbtr = nqINCA + nqCO2                                          !--- Number of tracers passed to phytrac
     235        nqtrue = nbtr + nqo                                            !--- Total number of "true" tracers
     236        IF(ALL([2, 3] /= nqo)) CALL abort_gcm(modname, 'Only 2 or 3 water phases allowed ; found nqo=' // TRIM(int2str(nqo)), 1)
     237        ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA))
     238        ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA), pbl_flg_inca(nqINCA))
     239        CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca)
     240        ALLOCATE(ttr(nqtrue))
     241        ttr(1:nqo + nqCO2) = tracers
     242        ttr(1:nqo)%component = 'lmdz'
     243        ttr(1 + nqo:nqCO2 + nqo)%component = 'co2i'
     244        ttr(1 + nqo + nqCO2:nqtrue)%component = 'inca'
     245        ttr(1 + nqo:nqtrue)%name = [('CO2     ', iq = 1, nqCO2), solsym_inca]
     246        ttr(1 + nqo + nqCO2:nqtrue)%parent = tran0
     247        ttr(1 + nqo + nqCO2:nqtrue)%phase = 'g'
     248        lerr = getKey('hadv', had, ky = tracers(:)%keys)
     249        lerr = getKey('vadv', vad, ky = tracers(:)%keys)
     250        hadv(1:nqo + nqCO2) = had(:); hadv(1 + nqo + nqCO2:nqtrue) = hadv_inca
     251        vadv(1:nqo + nqCO2) = vad(:); vadv(1 + nqo + nqCO2:nqtrue) = vadv_inca
     252        CALL MOVE_ALLOC(FROM = ttr, TO = tracers)
     253        DO iq = 1, nqtrue
     254          t1 => tracers(iq)
     255          CALL addKey('name', t1%name, t1%keys)
     256          CALL addKey('component', t1%component, t1%keys)
     257          CALL addKey('parent', t1%parent, t1%keys)
     258          CALL addKey('phase', t1%phase, t1%keys)
     259        END DO
     260        IF(setGeneration(tracers)) CALL abort_gcm(modname, 'See above', 1) !- SET FIELDS %iGeneration, %gen0Name
     261        DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca)
     262        !---------------------------------------------------------------------------------------------------------------------------
     263      END IF
    261264    ELSE                                                              !=== OTHER CASES (OLD OR NEW FORMAT, NO INCA MODULE)
    262265      !---------------------------------------------------------------------------------------------------------------------------
    263       nqo = COUNT(delPhase(tracers(:)%name)     == 'H2O' &
    264               .AND. tracers(:)%component == 'lmdz') !--- Number of water phases
    265       nqtrue = SIZE(tracers)                                         !--- Total number of "true" tracers
    266       nbtr = nqtrue - COUNT(delPhase(tracers(:)%gen0Name) == 'H2O' &
    267               .AND. tracers(:)%component == 'lmdz') !--- Number of tracers passed to phytrac
    268       nqINCA = COUNT(tracers(:)%component == 'inca')
    269       lerr = getKey('hadv', hadv, ky = tracers(:)%keys)
    270       lerr = getKey('vadv', vadv, ky = tracers(:)%keys)
     266      nqtrue = SIZE(tracers)                                                                               !--- "true" tracers
     267      nqo = COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%name)     == 'H2O')     !--- Water phases
     268      nbtr = nqtrue - COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%gen0Name) == 'H2O')     !--- Passed to phytrac
     269      nqCO2 = COUNT([type_trac == 'inco', type_trac == 'co2i'])
     270      IF (CPPKEY_INCA) THEN
     271        nqINCA = COUNT(tracers(:)%component == 'inca')
     272      END IF
     273      IF(getKey('hadv', hadv, ky = tracers(:)%keys)) CALL abort_gcm(modname, 'missing key "hadv"', 1)
     274      IF(getKey('vadv', vadv, ky = tracers(:)%keys)) CALL abort_gcm(modname, 'missing key "vadv"', 1)
    271275      !---------------------------------------------------------------------------------------------------------------------------
    272276    END IF
     
    274278
    275279    IF (CPPKEY_REPROBUS) THEN
    276       !--- Transfert the number of tracers to Reprobus
    277280      CALL init_chem_rep_trac(nbtr, nqo, tracers(:)%name)
    278281    END IF
     
    327330      IF(iad == -1) CALL abort_gcm(modname, msg1, 1)
    328331
    329       !--- SET FIELDS %longName, %iadv, %isAdvected, %isInPhysics
     332      !--- SET FIELDS longName, iadv, isAdvected, isInPhysics
    330333      t1%longName = t1%name; IF(iad > 0) t1%longName = TRIM(t1%name) // descrq(iad)
    331334      t1%iadv = iad
    332335      t1%isAdvected = iad >= 0
    333       t1%isInPhysics = delPhase(t1%gen0Name) /= 'H2O' &
    334               .OR. t1%component /= 'lmdz' !=== OTHER EXCEPTIONS TO BE ADDED: CO2i, SURSATURATED WATER CLOUD...
     336      t1%isInPhysics = delPhase(t1%gen0Name) /= 'H2O' .OR. t1%component /= 'lmdz' !=== MORE EXCEPTIONS ? CO2i, SURSAT CLOUD H2O
    335337      ttr(iq) = t1
    336338
     
    342344      ttr(jq + 1:jq + nm) = t1
    343345      ttr(jq + 1:jq + nm)%name = [ (TRIM(t1%name) // '-' // TRIM(suff(im)), im = 1, nm) ]
     346      ttr(jq + 1:jq + nm)%gen0Name = [ (TRIM(t1%name) // '-' // TRIM(suff(im)), im = 1, nm) ]
    344347      ttr(jq + 1:jq + nm)%parent = [ (TRIM(t1%parent) // '-' // TRIM(suff(im)), im = 1, nm) ]
    345348      ttr(jq + 1:jq + nm)%longName = [ (TRIM(t1%longName) // '-' // TRIM(suff(im)), im = 1, nm) ]
     
    351354    CALL MOVE_ALLOC(FROM = ttr, TO = tracers)
    352355
    353     !--- SET FIELDS %iqParent, %nqChildren, %iGeneration, %iqDescen, %nqDescen
     356    !--- SET FIELDS iqParent, iqDescen, nqDescen, nqChildren
    354357    IF(indexUpdate(tracers)) CALL abort_gcm(modname, 'problem with tracers indices update', 1)
    355358
     
    400403    END IF
    401404    t => tracers
    402     CALL msg('Information stored in infotrac :', modname)
    403 
    404     IF(dispTable('isssssssssiiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp', &
    405             'isPh', 'isAd', 'iadv', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'], &
    406             cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component, bool2str(t%isInPhysics), &
    407                     bool2str(t%isAdvected)), &
     405    CALL msg('Information stored in ' // TRIM(modname) // ': ', modname)
     406    IF(dispTable('isssssssiiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp', &
     407            'iAdv', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'], &
     408            cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component), &
    408409            cat([(iq, iq = 1, nqtot)], t%iadv, t%iGeneration, t%iqParent, t%nqDescen, t%nqChildren, t%iso_iGroup, &
    409410                    t%iso_iName, t%iso_iZone, t%iso_iPhase), nColMax = maxTableWidth, nHead = 2, sub = modname))   &
Note: See TracChangeset for help on using the changeset viewer.