Ignore:
Timestamp:
Sep 23, 2024, 4:12:29 PM (4 weeks 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/phylmd/infotrac_phy.F90

    r5185 r5221  
    66  USE lmdz_readTracFiles, ONLY: trac_type, readTracersFiles, tracers, setGeneration, itZonIso, nzone, tran0, isoZone, &
    77          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
     8          addPhase, iH2O, addKey, isoSelect, testTracersFiles, isoKeys, indexUpdate, iqWIsoPha, nbIso, ntiso, isoName, isoCheck, new2oldH2O
    99  IMPLICIT NONE
    1010
     
    1616  PUBLIC :: nqtot, nbtr, nqo, nqCO2, nqtottr      !--- Main dimensions
    1717  PUBLIC :: conv_flg, pbl_flg                             !--- Convection & boundary layer activation keys
     18  PUBLIC :: new2oldH2O                                    !--- For backwards compatibility in phyetat0
     19   PUBLIC :: addPhase, delPhase                            !--- Add/remove the phase from the name of a tracer
    1820  PUBLIC :: nbtr_bin, nbtr_sulgas                         !--- Number of aerosols bins and sulfur gases for StratAer model
    1921  PUBLIC :: id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat
    2022
    21   !=== FOR WATER
    22   PUBLIC :: ivap, iliq, isol
    23   !=== FOR ISOTOPES: General
     23  !===  FOR ISOTOPES: General
    2424  PUBLIC :: isot_type, nbIso                              !--- Derived type, full isotopes families database + nb of families
    2525  PUBLIC :: isoSelect, ixIso                              !--- Isotopes family selection tool + selected family index
    2626  !=== FOR ISOTOPES: Specific to water
    27   PUBLIC :: iH2O                                          !--- H2O isotopes class index
     27  PUBLIC :: iH2O                                          !--- Value of "ixIso" for "H2O" isotopes class
     28   PUBLIC :: ivap, iliq, isol
    2829  !=== 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
     30  PUBLIC :: isotope                              !--- Selected isotopes database (argument of getKey)
     31  PUBLIC :: isoKeys, isoName, isoZone, isoPhas            !--- Isotopes keys & names, tagging zones names, phases
     32  PUBLIC :: niso, ntiso,nzone, nphas!--- Number of   "   "
     33  PUBLIC :: itZonIso                                      !--- Index "it" in "isoName(1:niso)" = f(tagging idx, isotope idx)
     34  PUBLIC :: iqIsoPha                                      !--- Index "iq" in "qx"              = f(isotope idx,   phase idx)
    3435  PUBLIC :: iqWIsoPha                                      !--- Same as iqIsoPha but with normal water phases
    3536
     
    4142  !  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    4243  !  | water in different |    water tagging      |  water isotopes | other tracers | additional tracers moments |
    43   !  | phases: H2O_[gls]  |      isotopes         |                 |               |  for higher order schemes  |
     44  !  | phases: H2O_[glsrb]  |      isotopes         |                 |               |  for higher order schemes  |
    4445  !  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    4546  !  |                    |                       |                 |               |                            |
     
    6667  !  |-------------+------------------------------------------------------+-------------+------------------------+
    6768  !  | name        | Name (short)                                         | tname       |                        |
    68   !  | gen0Name    | Name of the 1st generation ancestor                  | /           |                        |
     69  !  | keys        | key/val pairs accessible with "getKey" routine       | /           |                        |
     70!  |gen0Name    | Name of the 1st generation ancestor                  | /           |                        |
    6971  !  | parent      | Name of the parent                                   | /           |                        |
    7072  !  | longName    | Long name (with adv. scheme suffix) for outputs      | ttext       |                        |
    7173  !  | type        | Type (so far: tracer or tag)                         | /           | tracer,tag             |
    72   !  | phase       | Phases list ("g"as / "l"iquid / "s"olid)             | /           | [g][l][s]              |
     74  !  | phase       | Phases list ("g"as / "l"iquid / "s"olid             |             | [g|l|s|r|b]            |
     75!  |             |              "r"(cloud) / "b"lowing)                 | /           |              |
    7376  !  | component   | Name(s) of the merged/cumulated section(s)           | /           | coma-separated names   |
    7477  !  | iGeneration | Generation (>=1)                                     | /           |                        |
     
    7780  !  | nqDescen    | Number of the descendants   (all generations)        | nqdesc      | 1:nqtot                |
    7881  !  | 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
     83  !  | isAdvected  | Advected tracers flag (.TRUE. if iadv >= 0)          | /           | nqtrue  .TRUE. values  |
     84  !  | isInPhysics | Tracers not extracted from the main table in physics | /           | nqtottr .TRUE. values  |
    8285  !  | iso_iGroup  | Isotopes group index in isotopes(:)                  | /           | 1:nbIso                |
    8386  !  | iso_iName   | Isotope  name  index in isotopes(iso_iGroup)%trac(:) | iso_indnum  | 1:niso                 |
     
    9598  !  | trac   | ntiso  | Isotopes + tagging tracers list + number         | / | ntraciso       |                 |
    9699  !  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
    97   !  | phase  | nphas  | Phases                     list + number         |                    | [g][l][s], 1:3  |
     100  !  | phase  | nphas  | Phases                     list + number         |                    | [g|l|s|r|b] 1:5  |
    98101  !  | 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         |
     102  !  | iqWIsoPha       | Index in "qx"           = f(name(1:ntiso+nqo)),phas) |   /              | 1:nqtot         |
    100103  !  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
    101104  !  +-----------------+--------------------------------------------------+--------------------+-----------------+
    102105
    103   !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
     106  !=== INDICES FOR WATER
     107   INTEGER, SAVE :: ivap, iliq, isol
     108!$OMP THREADPRIVATE(ivap, iliq, isol)
     109
     110   !===DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
    104111  INTEGER, SAVE :: nqtot, &                     !--- Tracers nb in dynamics (incl. higher moments + H2O)
    105112          nbtr, &                     !--- Tracers nb in physics  (excl. higher moments + H2O)
     
    110117  !$OMP THREADPRIVATE(nqtot, nbtr, nqo, nqtottr, nqCO2, type_trac)
    111118
    112   !=== INDICES OF WATER
    113   INTEGER, SAVE :: ivap, iliq, isol ! Indices for vap, liq and ice
    114   !$OMP THREADPRIVATE(ivap,iliq,isol)
    115 
    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  !===  VARIABLES FOR INCA
     120  INTEGER, DIMENSION(:), SAVE, ALLOCATABLE :: &
     121                    conv_flg, pbl_flg                           !--- Convection / boundary layer activation (nbtr)
    119122  !$OMP THREADPRIVATE(conv_flg, pbl_flg)
    120123
     
    167170    CHARACTER(LEN = 2) :: suff(9)                                !--- Suffixes for schemes of order 3 or 4 (Prather)
    168171    CHARACTER(LEN = 3) :: descrq(30)                               !--- Advection scheme description tags
    169     CHARACTER(LEN = maxlen) :: msg1, texp, ttp                          !--- String for messages and expanded tracers type
     172    CHARACTER(LEN = maxlen) :: msg1, texp, ttp                          !--- Strings for messages and expanded tracers type
    170173    INTEGER :: fType                                                  !--- Tracers description file type ; 0: none
    171174    !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def"
    172175    INTEGER :: nqtrue                                                 !--- Tracers nb from tracer.def (no higher order moments)
    173176    INTEGER :: iad                                                    !--- Advection scheme number
    174     INTEGER :: iq, jq, nt, im, nm, k                                 !--- Indexes and temporary variables
     177    INTEGER :: iq, jq, nt, im, nm                                 !--- Indexes and temporary variables
    175178    LOGICAL :: lerr, lInit
    176179    TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
    177180    TYPE(trac_type), POINTER :: t1, t(:)
    178     CHARACTER(LEN = maxlen), ALLOCATABLE :: types_trac(:)  !--- Keyword for tracers type(s), parsed version
     181    CHARACTER(LEN = maxlen), ALLOCATABLE :: types_trac(:)  !--- Keywords for tracers type(s), parsed version
    179182
    180183    CHARACTER(LEN = *), PARAMETER :: modname = "init_infotrac_phy"
     
    236239
    237240    !==============================================================================================================================
    238     ! 1) Get the numbers of: true (first order only) tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid)
     241    ! 0) DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE AND READ IT
    239242    !==============================================================================================================================
    240     texp = type_trac                                                  !=== EXPANDED VERSION OF "type_trac", WITH "|" SEPARATOR
     243    texp = type_trac                                                  !=== EXPANDED (WITH "|" SEPARATOR) "type_trac"
    241244    IF(texp == 'inco') texp = 'co2i|inca'
    242245    IF(texp /= 'lmdz') texp = 'lmdz|' // TRIM(texp)
    243246
    244     !=== DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE
     247
    245248    IF(testTracersFiles(modname, texp, fType, lInit)) CALL abort_physic(modname, 'problem with tracers file(s)', 1)
    246249
     
    255258    !##############################################################################################################################
    256259
    257     !---------------------------------------------------------------------------------------------------------------------------
    258     IF(fType == 0) CALL abort_physic(modname, 'Missing tracers file: "traceur.def", "tracer.def" or "tracer_<keyword>.def file.', 1)
     260    !==============================================================================================================================
     261! 1) Get various numbers: "nqtrue" (first order only tracers), "nqo" (water phases), 'nbtr' (tracers passed to physics), etc.
     262!==============================================================================================================================
     263   !---------------------------------------------------------------------------------------------------------------------------
     264    IF(fType == 0) CALL abort_physic(modname, 'Missing "traceur.def", "tracer.def" or "tracer_<keyword>.def tracersfile.', 1)
    259265    !---------------------------------------------------------------------------------------------------------------------------
    260266    IF(fType == 1 .AND. ANY(['inca', 'inco']==type_trac) .AND. lInit) THEN  !=== FOUND OLD STYLE INCA "traceur.def"
    261267      !---------------------------------------------------------------------------------------------------------------------------
     268      IF (CPPKEY_INCA) THEN
    262269      nqo = SIZE(tracers) - nqCO2
    263270      CALL Init_chem_inca_trac(nqINCA)                               !--- Get nqINCA from INCA
     
    273280      ttr(1 + nqo:nqCO2 + nqo)%component = 'co2i'
    274281      ttr(1 + nqo + nqCO2:nqtrue)%component = 'inca'
    275       ttr(1 + nqo:nqtrue)%name = [('CO2     ', k = 1, nqCO2), solsym_inca]
     282      ttr(1 + nqo:nqtrue)%name = [('CO2     ', iq = 1, nqCO2), solsym_inca]
    276283      ttr(1 + nqo + nqCO2:nqtrue)%parent = tran0
    277284      ttr(1 + nqo + nqCO2:nqtrue)%phase = 'g'
     
    290297      IF(setGeneration(tracers)) CALL abort_physic(modname, 'See below', 1) !- SET FIELDS %iGeneration, %gen0Name
    291298      DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca)
     299 END IF
    292300      !---------------------------------------------------------------------------------------------------------------------------
    293301    ELSE                                                              !=== OTHER CASES (OLD OR NEW FORMAT, NO INCA MODULE)
    294302      !---------------------------------------------------------------------------------------------------------------------------
    295       nqo = COUNT(delPhase(tracers(:)%name)     == 'H2O' &
    296               .AND. tracers(:)%component == 'lmdz') !--- Number of water phases
    297       nqtrue = SIZE(tracers)                                         !--- Total number of "true" tracers
    298       nbtr = nqtrue - COUNT(delPhase(tracers(:)%gen0Name) == 'H2O' &
    299               .AND. tracers(:)%component == 'lmdz') !--- Number of tracers passed to phytrac
    300       nqINCA = COUNT(tracers(:)%component == 'inca')
    301       lerr = getKey('hadv', hadv, ky = tracers(:)%keys)
    302       lerr = getKey('vadv', vadv, ky = tracers(:)%keys)
     303      nqtrue = SIZE(tracers)                                                                               !--- "true" tracers
     304   nqo    =      COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%name)     == 'H2O')     !--- Water phases
     305   nbtr = nqtrue-COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%gen0Name) == 'H2O')     !--- Passed to phytrac
     306   nqCO2  =      COUNT( [type_trac == 'inco', type_trac == 'co2i'] )
     307      IF (CPPKEY_INCA) THEN
     308        nqINCA = COUNT(tracers(:)%component == 'inca')
     309      END IF
     310      IF(getKey('hadv', hadv, ky=tracers(:)%keys)) CALL abort_physic(modname, 'missing key "hadv"', 1)
     311   IF(getKey('vadv', vadv, ky=tracers(:)%keys)) CALL abort_physic(modname, 'missing key "vadv"', 1)
    303312      !---------------------------------------------------------------------------------------------------------------------------
    304313    END IF
     
    348357        IF(iad == -1) CALL abort_physic(modname, msg1, 1)
    349358
    350         !--- SET FIELDS %longName, %isAdvected, %isInPhysics
     359        !--- SET FIELDS longName, isAdvected, isInPhysics
    351360        t1%longName = t1%name; IF(iad > 0) t1%longName = TRIM(t1%name) // descrq(iad)
    352361        t1%isAdvected = iad >= 0
    353         t1%isInPhysics = delPhase(t1%gen0Name) /= 'H2O' &
    354                 .OR. t1%component /= 'lmdz' !=== OTHER EXCEPTIONS TO BE ADDED: CO2i, SURSATURATED WATER CLOUD...
     362        t1%isInPhysics= delPhase(t1%gen0Name) /= 'H2O' .OR. t1%component /= 'lmdz' !=== MORE EXCEPTIONS ? CO2i, SURSAT CLOUD H2O
    355363        ttr(iq) = t1
    356364
     
    362370        ttr(jq + 1:jq + nm) = t1
    363371        ttr(jq + 1:jq + nm)%name = [(TRIM(t1%name) // '-' // TRIM(suff(im)), im = 1, nm) ]
     372        ttr(jq+1:jq+nm)%gen0Name    = [ (TRIM(t1%name)    //'-'//TRIM(suff(im)), im=1, nm) ]
    364373        ttr(jq + 1:jq + nm)%parent = [(TRIM(t1%parent) // '-' // TRIM(suff(im)), im = 1, nm) ]
    365374        ttr(jq + 1:jq + nm)%longName = [(TRIM(t1%longName) // '-' // TRIM(suff(im)), im = 1, nm) ]
    366         ttr(jq + 1:jq + nm)%isAdvected = [(.FALSE., im = 1, nm) ]
     375        ttr(jq + 1:jq + nm)%isAdvected = [(.FALSE., im=1, nm) ]
     376      ttr(jq+1:jq+nm)%isInPhysics = [ (.FALSE., im = 1, nm) ]
    367377        jq = jq + nm
    368378      END DO
     
    370380      CALL MOVE_ALLOC(FROM = ttr, TO = tracers)
    371381
    372       !--- SET FIELDS %iqParent, %nqChildren, %iGeneration, %iqDescen, %nqDescen
    373       IF(indexUpdate(tracers)) CALL abort_gcm(modname, 'problem when processing isotopes parameters', 1)
     382      !--- SET FIELDS iqParent, iqDescen, nqDescen, nqChildren, iGeneration
     383      IF(indexUpdate(tracers)) CALL abort_physic(modname, 'problem with tracers indices update', 1)
    374384
    375385      !##############################################################################################################################
     
    393403    !##############################################################################################################################
    394404    !--- Convection / boundary layer activation for all tracers
    395     IF (.NOT.ALLOCATED(conv_flg)) ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1
    396     IF (.NOT.ALLOCATED(pbl_flg)) ALLOCATE(pbl_flg(nbtr));  pbl_flg(1:nbtr) = 1
     405    IF(.NOT.ALLOCATED(conv_flg)) ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1
     406    IF(.NOT.ALLOCATED( pbl_flg)) ALLOCATE(pbl_flg(nbtr));  pbl_flg(1:nbtr) = 1
    397407
    398408    !--- Note: nqtottr can differ from nbtr when nmom/=0
     
    413423    END IF
    414424    t => tracers
    415     CALL msg('Information stored in infotrac_phy :', modname)
    416     IF(dispTable('issssssssiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp', &
    417             'isPh', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'], &
    418             cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component, bool2str(t%isInPhysics)), &
     425    CALL msg('Information stored in '//TRIM(modname)//' :', modname)
     426    IF(dispTable('isssssssssiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp', &
     427            'isPh', 'isAd', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'], &
     428            cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component, &
     429                                                         bool2str(t%isInPhysics), bool2str(t%isAdvected)), &
    419430            cat([(iq, iq = 1, nqtot)], t%iGeneration, t%iqParent, t%nqDescen, t%nqChildren, t%iso_iGroup, &
    420431                    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.