Ignore:
Timestamp:
Jul 28, 2025, 7:23:15 PM (6 days ago)
Author:
aborella
Message:

Merge with trunk r5789

Location:
LMDZ6/branches/contrails
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails

  • LMDZ6/branches/contrails/libf/dyn3d_common/infotrac.f90

    r5618 r5791  
    33MODULE infotrac
    44
    5    USE       strings_mod, ONLY: msg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse, strCount, strIdx
    6    USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, tracers,  addPhase,  addKey, iH2O,  &
    7        isoSelect,  indexUpdate, isot_type, testTracersFiles, isotope,  delPhase,  getKey, tran0, &
    8        isoKeys, isoName, isoZone, isoPhas, processIsotopes,  isoCheck, itZonIso,  nbIso,         &
    9           niso,   ntiso,   nzone,   nphas,   maxTableWidth,  iqIsoPha, iqWIsoPha, ixIso, new2oldH2O, newHNO3, oldHNO3
     5   USE       strings_mod, ONLY: msg, maxlen, cat, dispTable, num2str, strStack, strParse, strCount, strIdx, maxTableWidth
     6   USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, tracers,  addPhase,  addKey, iH2O,    &
     7       isoSelect,  indexUpdate, isot_type, testTracersFiles, isotope,  delPhase,  getKey, tran0,   &
     8       isoKeys, isoName, isoZone, isoPhas, processIsotopes,  isoCheck, itZonIso,  nbIso, newHNO3,  &
     9          niso,   ntiso,   nzone,   nphas, isoF=>isoFamilies,iqIsoPha, iqWIsoPha, ixIso, oldHNO3, new2oldH2O
    1010   IMPLICIT NONE
    1111
     
    2222   !=== FOR ISOTOPES: General
    2323   PUBLIC :: isot_type, nbIso                              !--- Derived type, full isotopes families database + nb of families
    24    PUBLIC :: isoSelect, ixIso                              !--- Isotopes family selection tool + selected family index
     24   PUBLIC :: isoSelect, ixIso, isoFamilies                 !--- Isotopes families selection tool + selected family index
    2525   !=== FOR ISOTOPES: Specific to water
    2626   PUBLIC :: iH2O                                          !--- Value of "ixIso" for "H2O" isotopes class
     
    8181!  | iso_iName   | Isotope  name  index in isotopes(iso_iGroup)%trac(:) | iso_indnum  | 1:niso                 |
    8282!  | iso_iZone   | Isotope  zone  index in isotopes(iso_iGroup)%zone(:) | zone_num    | 1:nzone                |
    83 !  | iso_iPhas   | Isotope  phase index in isotopes(iso_iGroup)%phas(:) | phase_num   | 1:nphas                |
     83!  | iso_iPhase  | Isotope  phase index in isotopes(iso_iGroup)%phas(:) | phase_num   | 1:nphas                |
    8484!  +-------------+------------------------------------------------------+-------------+------------------------+
    8585!
     
    9898!  +-----------------+--------------------------------------------------+--------------------+-----------------+
    9999
     100   !=== THRESHOLDS FOR WATER
    100101   REAL, PARAMETER :: min_qParent = 1.e-30, min_qMass = 1.e-18, min_ratio = 1.e-16 ! MVals et CRisi
    101102
    102    !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
     103   !=== DIMENSIONS OF THE TRACERS TABLES, TRACERS TYPE(S)
    103104   INTEGER, SAVE :: nqtot                                       !--- Tracers nb in dynamics (incl. higher moments + H2O)
    104105   INTEGER, SAVE :: nbtr                                        !--- Tracers nb in physics  (excl. higher moments + H2O)
     
    111112   INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), pbl_flg(:)        !--- Convection / boundary layer activation (nbtr)
    112113
     114   !=== LIST OF DEFINED ISOTOPES FAMILIES
     115   CHARACTER(LEN=maxlen), SAVE, ALLOCATABLE :: isoFamilies(:)   !--- Generation 0 tracer name for each isotopes family (nbIso)
     116
    113117CONTAINS
    114118
     
    116120   USE iniprint_mod_h
    117121   USE control_mod, ONLY: planet_type
     122   USE ioipsl, ONLY: getin
    118123   USE lmdz_reprobus_wrappers, ONLY: Init_chem_rep_trac
    119124   USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA, CPPKEY_REPROBUS, CPPKEY_STRATAER
    120125   USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    121 IMPLICIT NONE
     126   IMPLICIT NONE
    122127!==============================================================================================================================
    123128!
     
    152157   INTEGER :: nqtrue                                                 !--- Tracers nb from tracer.def (no higher order moments)
    153158   INTEGER :: iad                                                    !--- Advection scheme number
    154    INTEGER :: iq, jq, nt, im, nm, ig                                 !--- Indexes and temporary variables
     159   INTEGER :: iq, jq, it, nt, im, nm, ig                             !--- Indexes and temporary variables
    155160   LOGICAL :: lerr
    156161   TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
     
    256261   IF( nqtot /= nqtrue ) THEN
    257262      CALL msg('The choice of advection scheme for one or more tracers makes it necessary to add tracers')
    258       CALL msg('The number of true tracers is '//TRIM(int2str(nqtrue)))
    259       CALL msg('The total number of tracers needed is '//TRIM(int2str(nqtot)))
     263      CALL msg('The number of true tracers is '//TRIM(num2str(nqtrue)))
     264      CALL msg('The total number of tracers needed is '//TRIM(num2str(nqtot)))
    260265   END IF
    261266
     
    290295      IF(iad == -1) CALL abort_gcm(modname, msg1, 1)
    291296
    292       !--- SET FIELDS longName and iadv
     297      !--- SET FIELDS longName AND iadv
    293298      t1%longName   = t1%name; IF(iad > 0) t1%longName=TRIM(t1%name)//descrq(iad)
    294299      t1%iadv       = iad
     
    319324      ig  = t1%iGeneration
    320325      nam = t1%name
    321       val = 'iadv='//TRIM(int2str(iad))
     326      val = 'iadv='//TRIM(num2str(iad))
    322327
    323328      !--- ONLY TESTED VALUES FOR TRACERS FOR NOW:               iadv = 14, 10 (and 0 for non-transported tracers)
     
    335340   END DO
    336341
    337    !=== READ PHYSICAL PARAMETERS FOR ISOTOPES ; DONE HERE BECAUSE dynetat0 AND iniacademic NEED "tnat" AND "alpha_ideal"
    338    niso = 0; nzone = 0; nphas = nqo; ntiso = 0; isoCheck = .FALSE.
     342   !=== DETERMINE ISOTOPES RELATED PARAMETERS ; DEFINE THE EXPLICIT KEYS iso_i*
    339343   IF(processIsotopes()) CALL abort_gcm(modname, 'problem when processing isotopes parameters', 1)
     344   iH2O = -1
     345   IF(nbIso /= 0) THEN
     346      IF(isoSelect('H2O', .TRUE.)) THEN
     347         IF(isoSelect(1, .TRUE.)) CALL abort_physic(modname, "Can't select the first isotopes family", 1)
     348      ELSE
     349         iH2O = ixIso; CALL getin('ok_iso_verif', isotope%check)
     350      END IF
     351   END IF
     352   isoFamilies = isoF(:)
    340353
    341354   !--- Convection / boundary layer activation for all tracers
     
    356369   !=== DISPLAY THE RESULTS
    357370   IF(.NOT..TRUE.) RETURN
    358    CALL msg('nqo    = '//TRIM(int2str(nqo)),    modname)
    359    CALL msg('nbtr   = '//TRIM(int2str(nbtr)),   modname)
    360    CALL msg('nqtrue = '//TRIM(int2str(nqtrue)), modname)
    361    CALL msg('nqtot  = '//TRIM(int2str(nqtot)),  modname)
    362    CALL msg('niso   = '//TRIM(int2str(niso)),   modname)
    363    CALL msg('ntiso  = '//TRIM(int2str(ntiso)),  modname)
    364    CALL msg('nqCO2  = '//TRIM(int2str(nqCO2)),  modname, CPPKEY_INCA)
    365    CALL msg('nqINCA = '//TRIM(int2str(nqINCA)), modname, CPPKEY_INCA)
     371   CALL msg('nqo    = '//TRIM(num2str(nqo)),    modname)
     372   CALL msg('nbtr   = '//TRIM(num2str(nbtr)),   modname)
     373   CALL msg('nqtrue = '//TRIM(num2str(nqtrue)), modname)
     374   CALL msg('nqtot  = '//TRIM(num2str(nqtot)),  modname)
     375   CALL msg('niso   = '//TRIM(num2str(niso)),   modname)
     376   CALL msg('ntiso  = '//TRIM(num2str(ntiso)),  modname)
     377   CALL msg('nqCO2  = '//TRIM(num2str(nqCO2)),  modname, CPPKEY_INCA)
     378   CALL msg('nqINCA = '//TRIM(num2str(nqINCA)), modname, CPPKEY_INCA)
    366379   t => tracers
    367380   CALL msg('Information stored in '//TRIM(modname)//': ', modname)
     
    374387   CALL msg('No isotopes identified.', modname, nbIso == 0)
    375388   IF(nbIso == 0) RETURN
    376    CALL msg('For isotopes family "H2O":', modname)
    377    CALL msg('  isoKeys%name = '//strStack(isoKeys%name), modname)
    378    CALL msg('  isoName = '//strStack(isoName),      modname)
    379    CALL msg('  isoZone = '//strStack(isoZone),      modname)
    380    CALL msg('  isoPhas = '//TRIM(isoPhas),          modname)
     389   DO it = 1, nbIso
     390      IF(isoSelect(it, .TRUE.)) CALL abort_physic(modname, 'Problem when selecting isotopes class', 1)
     391      CALL msg('For isotopes family "'//TRIM(isoFamilies(it))//'":', modname)
     392      CALL msg('  isoKeys%name = '//strStack(isoKeys%name), modname)
     393      CALL msg('  isoName = '//strStack(isoName), modname)
     394      CALL msg('  isoZone = '//strStack(isoZone), modname)
     395      CALL msg('  isoPhas = '//TRIM(isoPhas),     modname)
     396   END DO
     397   IF(isoSelect(iH2O, .TRUE.)) lerr = isoSelect(1, .TRUE.)
    381398
    382399END SUBROUTINE init_infotrac
Note: See TracChangeset for help on using the changeset viewer.