Ignore:
Timestamp:
Jul 3, 2025, 3:25:59 PM (3 days ago)
Author:
dcugnet
Message:

Add "isoFamilies", the list of defined isotopes families (==H2O? for now).

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/infotrac_phy.F90

    r5748 r5756  
    33MODULE infotrac_phy
    44
    5    USE       strings_mod, ONLY: msg, maxlen, cat, dispTable, num2str, strStack, strParse, strCount, strIdx
     5   USE       strings_mod, ONLY: msg, maxlen, cat, dispTable, num2str, strStack, strParse, strCount, strIdx, maxTableWidth
    66   USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, tracers,  addPhase,  addKey, iH2O,  &
    77       isoSelect,  indexUpdate, isot_type, testTracersFiles, isotope,  delPhase,  getKey, tran0, &
    88       isoKeys, isoName, isoZone, isoPhas, processIsotopes,  isoCheck, itZonIso,  nbIso,         &
    9           niso,   ntiso,   nzone,   nphas,   maxTableWidth,  iqIsoPha, iqWIsoPha, ixIso, new2oldH2O
     9          niso,   ntiso,   nzone,   nphas, isoF=>isoFamilies,iqIsoPha, iqWIsoPha, ixIso, new2oldH2O
    1010   IMPLICIT NONE
    1111
     
    2424   !=== FOR ISOTOPES: General
    2525   PUBLIC :: isot_type, nbIso                              !--- Derived type, full isotopes families database + nb of families
    26    PUBLIC :: isoSelect, ixIso                              !--- Isotopes family selection tool + selected family index
     26   PUBLIC :: isoSelect, ixIso, isoFamilies                 !--- Isotopes family selection tool + selected family index
    2727   !=== FOR ISOTOPES: Specific to water
    2828   PUBLIC :: iH2O                                          !--- Value of "ixIso" for "H2O" isotopes class
     
    8484!  | iso_iName   | Isotope  name  index in isotopes(iso_iGroup)%trac(:) | iso_indnum  | 1:niso                 |
    8585!  | iso_iZone   | Isotope  zone  index in isotopes(iso_iGroup)%zone(:) | zone_num    | 1:nzone                |
    86 !  | iso_iPhas   | Isotope  phase index in isotopes(iso_iGroup)%phas(:) | phase_num   | 1:nphas                |
     86!  | iso_iPhase  | Isotope  phase index in isotopes(iso_iGroup)%phas(:) | phase_num   | 1:nphas                |
    8787!  +-------------+------------------------------------------------------+-------------+------------------------+
    8888!
     
    106106!$OMP THREADPRIVATE(ivap, iliq, isol, ibs, icf, irvc)
    107107
    108    !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
     108   !=== DIMENSIONS OF THE TRACERS TABLES, TRACERS TYPE(S)
    109109   INTEGER, SAVE :: nqtot                                       !--- Tracers nb in dynamics (incl. higher moments + H2O)
    110110   INTEGER, SAVE :: nbtr                                        !--- Tracers nb in physics  (excl. higher moments + H2O)
     
    118118   INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), pbl_flg(:)        !--- Convection / boundary layer activation (nbtr)
    119119!$OMP THREADPRIVATE(conv_flg, pbl_flg)
     120
     121   !=== LIST OF DEFINED ISOTOPES FAMILIES
     122   CHARACTER(LEN=maxlen), SAVE, ALLOCATABLE :: isoFamilies(:)   !--- Generation 0 tracer name for each isotopes family (nbIso)
     123!$OMP THREADPRIVATE(isoFamilies)
    120124
    121125  !=== SPECIFIC TO STRATOSPHERIC AEROSOLS (CK/OB)
     
    167171   INTEGER :: nqtrue                                                 !--- Tracers nb from tracer.def (no higher order moments)
    168172   INTEGER :: iad                                                    !--- Advection scheme number
    169    INTEGER :: iq, jq, nt, im, nm                                     !--- Indexes and temporary variables
     173   INTEGER :: iq, jq, it, nt, im, nm                                 !--- Indexes and temporary variables
    170174   LOGICAL :: lerr, lInit
    171175   TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
     
    294298      IF(iad == -1) CALL abort_physic(modname, msg1, 1)
    295299
    296       !--- SET FIELDS longName, isInPhysics
     300      !--- SET FIELDS longName AND isInPhysics
    297301      t1%longName   = t1%name; IF(iad > 0) t1%longName=TRIM(t1%name)//descrq(iad)
    298302      t1%isInPhysics= iad >= 0 .AND. (delPhase(t1%gen0Name) /= 'H2O' .OR. t1%component /= 'lmdz')
     
    315319   CALL MOVE_ALLOC(FROM=ttr, TO=tracers)
    316320
    317    !--- SET FIELDS iqParent, iqDescen, nqDescen, nqChildren, iGeneration
     321   !--- SET FIELDS iqParent, iqDescen, nqDescen, nqChildren
    318322   IF(indexUpdate(tracers)) CALL abort_physic(modname, 'problem with tracers indices update', 1)
    319323
    320    !=== READ PHYSICAL PARAMETERS FOR ISOTOPES
    321    niso = 0; nzone = 0; nphas = nqo; ntiso = 0; isoCheck = .FALSE.
     324   !=== DETERMINE ISOTOPES RELATED PARAMETERS ; DEFINE THE EXPLICIT KEYS iso_i*
    322325   IF(processIsotopes()) CALL abort_physic(modname, 'Problem when processing isotopes parameters', 1)
     326   iH2O = -1
     327   IF(nbIso /= 0) THEN
     328      IF(isoSelect('H2O', .TRUE.)) THEN
     329         IF(isoSelect(1, .TRUE.)) CALL abort_physic(modname, "Can't select the first isotopes family", 1)
     330      ELSE
     331         iH2O = ixIso; CALL getin_p('ok_iso_verif', isotope%check)
     332      END IF
     333   END IF
    323334
    324335!##############################################################################################################################
     
    326337!##############################################################################################################################
    327338   DO iq = 1, nqtrue
    328       t1 => tracers(iq)
    329339      IF(hadv(iq)     ==    vadv(iq)    ) iad = hadv(iq)
    330340      IF(hadv(iq)==10 .AND. vadv(iq)==16) iad = 11
    331       tracers(iq)%isInPhysics= iad >= 0 .AND. (delPhase(t1%gen0Name) /= 'H2O' .OR. t1%component /= 'lmdz')
     341      tracers(iq)%isInPhysics= iad >= 0 .AND. (delPhase(tracers(iq)%gen0Name) /= 'H2O' .OR. tracers(iq)%component /= 'lmdz')
    332342   END DO
    333 !##############################################################################################################################
    334    END IF
    335 !##############################################################################################################################
     343   tracers(nqtrue+1:nqtot)%isInPhysics = .FALSE.
     344!##############################################################################################################################
     345   END IF
     346!##############################################################################################################################
     347   isoFamilies = isoF(:)
    336348
    337349   !--- Convection / boundary layer activation for all tracers
     
    377389   IF(dispTable('issssssssiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp',      &
    378390                              'isPh', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'],     &
    379       cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component, num2str(t%isInPhysics)), &
     391      cat(t%name, t%longName,  t%gen0Name, t%parent, t%type, t%phase, t%component, num2str(t%isInPhysics)),&
    380392      cat([(iq, iq=1, nqtot)], t%iGeneration, t%iqParent, t%nqDescen, t%nqChildren, t%iso_iGroup,          &
    381393                  t%iso_iName, t%iso_iZone, t%iso_iPhase), nColMax=maxTableWidth, nHead=2, sub=modname))   &
     
    383395   CALL msg('No isotopes identified.', modname, nbIso == 0)
    384396   IF(nbIso == 0) RETURN
    385    CALL msg('For isotopes family "H2O":', modname)
    386    CALL msg('  isoKeys%name = '//strStack(isoKeys%name), modname)
    387    CALL msg('  isoName = '//strStack(isoName),      modname)
    388    CALL msg('  isoZone = '//strStack(isoZone),      modname)
    389    CALL msg('  isoPhas = '//TRIM(isoPhas),          modname)
     397   DO it = 1, nbIso
     398      IF(isoSelect(it, .TRUE.)) CALL abort_physic(modname, 'Problem when selecting isotopes class', 1)
     399      CALL msg('For isotopes family "'//TRIM(isoFamilies(it))//'":', modname)
     400      CALL msg('  isoKeys%name = '//strStack(isoKeys%name), modname)
     401      CALL msg('  isoName = '//strStack(isoName), modname)
     402      CALL msg('  isoZone = '//strStack(isoZone), modname)
     403      CALL msg('  isoPhas = '//TRIM(isoPhas),     modname)
     404   END DO
     405   IF(isoSelect(iH2O, .TRUE.)) lerr = isoSelect(1, .TRUE.)
    390406
    391407   IF(CPPKEY_STRATAER .AND. type_trac == 'coag') THEN
Note: See TracChangeset for help on using the changeset viewer.