Ignore:
Timestamp:
Sep 20, 2024, 12:32:04 PM (16 hours ago)
Author:
Laurent Fairhead
Message:

Updating cirrus branch to trunk revision 5171

Location:
LMDZ6/branches/cirrus
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/cirrus

  • LMDZ6/branches/cirrus/libf/dyn3d_common/infotrac.F90

    r4638 r5202  
    55   USE       strings_mod, ONLY: msg, fmsg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse
    66   USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, tracers, setGeneration, itZonIso, nzone, tran0, isoZone, &
    7         delPhase, niso, getKey, isot_type, readIsotopesFile, isotope, maxTableWidth, iqIsoPha, nphas, ixIso, isoPhas, &
    8         addPhase, iH2O, addKey, isoSelect, testTracersFiles, isoKeys, indexUpdate,   isoCheck, nbIso, ntiso, isoName
     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
    99   IMPLICIT NONE
    1010
     
    3636!  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    3737!  | water in different |    water tagging      |  water isotopes | other tracers | additional tracers moments |
    38 !  | phases: H2O_[glsb] |      isotopes         |                 |               |  for higher order schemes  |
     38!  | phases: H2O_[gls] |      isotopes         |                 |               |  for higher order schemes  |
    3939!  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    4040!  |                    |                       |                 |               |                            |
     
    6565!  | longName    | Long name (with adv. scheme suffix) for outputs      | ttext       |                        |
    6666!  | type        | Type (so far: tracer or tag)                         | /           | tracer,tag             |
    67 !  | phase       | Phases list ("g"as / "l"iquid / "s"olid / "b"lowing) | /           | [g][l][s][b]           |
     67!  | phase       | Phases list ("g"as / "l"iquid / "s"olid)             | /           | [g][l][s]              |
    6868!  | component   | Name(s) of the merged/cumulated section(s)           | /           | coma-separated names   |
    6969!  | iGeneration | Generation (>=1)                                     | /           |                        |
     
    9191!  | trac   | ntiso  | Isotopes + tagging tracers list + number         | / | ntraciso       |                 |
    9292!  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
    93 !  | phase  | nphas  | Phases                     list + number         |                    |[g][l][s][b],1:4 |
     93!  | phase  | nphas  | Phases                     list + number         |                    | [g][l][s], 1:3 |
    9494!  | iqIsoPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
    9595!  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
     
    156156   INTEGER :: nqtrue                                                 !--- Tracers nb from tracer.def (no higher order moments)
    157157   INTEGER :: iad                                                    !--- Advection scheme number
    158    INTEGER :: ic, iq, jq, it, nt, im, nm, iz, k                      !--- Indexes and temporary variables
     158   INTEGER :: iq, jq, nt, im, nm                                     !--- Indexes and temporary variables
    159159   LOGICAL :: lerr, ll
    160    CHARACTER(LEN=1) :: p
    161160   TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
    162161   TYPE(trac_type), POINTER             :: t1, t(:)
    163    INTEGER :: ierr
    164162   CHARACTER(LEN=maxlen),   ALLOCATABLE :: types_trac(:)  !--- Keyword for tracers type(s), parsed version
    165163
     
    225223   ttp = type_trac; IF(fType /= 1) ttp = texp
    226224
    227    IF(readTracersFiles(ttp, type_trac == 'repr'))    CALL abort_gcm(modname, 'problem with tracers file(s)',1)
     225   IF(readTracersFiles(ttp, lRepr=type_trac=='repr')) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
    228226   !---------------------------------------------------------------------------------------------------------------------------
    229227   IF(fType == 0) CALL abort_gcm(modname, 'Missing tracers file: "traceur.def", "tracer.def" or "tracer_<keyword>.def file.',1)
     
    236234      nbtr = nqINCA + nqCO2                                          !--- Number of tracers passed to phytrac
    237235      nqtrue = nbtr + nqo                                            !--- Total number of "true" tracers
    238       IF(ALL([2,3,4,5] /= nqo)) CALL abort_gcm(modname, 'Only 2, 3, 4 , 5 water phases allowed ; found nqo='//TRIM(int2str(nqo)), 1)
     236      IF(ALL([2,3] /= nqo)) CALL abort_gcm(modname, 'Only 2 or 3 water phases allowed ; found nqo='//TRIM(int2str(nqo)), 1)
    239237      ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA))
    240238      ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA),  pbl_flg_inca(nqINCA))
     
    245243      ttr(1+nqo:nqCO2+nqo   )%component = 'co2i'
    246244      ttr(1+nqo+nqCO2:nqtrue)%component = 'inca'
    247       ttr(1+nqo      :nqtrue)%name      = [('CO2     ', k=1, nqCO2), solsym_inca]
     245      ttr(1+nqo      :nqtrue)%name      = [('CO2     ', iq=1, nqCO2), solsym_inca]
    248246      ttr(1+nqo+nqCO2:nqtrue)%parent    = tran0
    249247      ttr(1+nqo+nqCO2:nqtrue)%phase     = 'g'
     
    348346      IF(nm == 0) CYCLE                                              !--- No higher moments
    349347      ttr(jq+1:jq+nm)             = t1
    350       ttr(jq+1:jq+nm)%name        = [(TRIM(t1%name)    //'-'//TRIM(suff(im)), im=1, nm) ]
    351       ttr(jq+1:jq+nm)%parent      = [(TRIM(t1%parent)  //'-'//TRIM(suff(im)), im=1, nm) ]
    352       ttr(jq+1:jq+nm)%longName    = [(TRIM(t1%longName)//'-'//TRIM(suff(im)), im=1, nm) ]
    353       ttr(jq+1:jq+nm)%iadv        = [(-iad,    im=1, nm) ]
    354       ttr(jq+1:jq+nm)%isAdvected  = [(.FALSE., im=1, nm) ]
     348      ttr(jq+1:jq+nm)%name        = [ (TRIM(t1%name)    //'-'//TRIM(suff(im)), im=1, nm) ]
     349      ttr(jq+1:jq+nm)%parent      = [ (TRIM(t1%parent)  //'-'//TRIM(suff(im)), im=1, nm) ]
     350      ttr(jq+1:jq+nm)%longName    = [ (TRIM(t1%longName)//'-'//TRIM(suff(im)), im=1, nm) ]
     351      ttr(jq+1:jq+nm)%iadv        = [ (-iad,    im=1, nm) ]
     352      ttr(jq+1:jq+nm)%isAdvected  = [ (.FALSE., im=1, nm) ]
    355353      jq = jq + nm
    356354   END DO
     
    359357
    360358   !--- SET FIELDS %iqParent, %nqChildren, %iGeneration, %iqDescen, %nqDescen
    361    CALL indexUpdate(tracers)
     359   IF(indexUpdate(tracers)) CALL abort_gcm(modname, 'problem with tracers indices update', 1)
    362360
    363361   !=== TEST ADVECTION SCHEME
     
    384382   !=== READ PHYSICAL PARAMETERS FOR ISOTOPES ; DONE HERE BECAUSE dynetat0 AND iniacademic NEED "tnat" AND "alpha_ideal"
    385383   niso = 0; nzone = 0; nphas = nqo; ntiso = 0; isoCheck = .FALSE.
    386    IF(readIsotopesFile()) CALL abort_gcm(modname, 'Problem when reading isotopes parameters', 1)
     384   IF(processIsotopes()) CALL abort_gcm(modname, 'problem when processing isotopes parameters', 1)
    387385
    388386   !--- Convection / boundary layer activation for all tracers
     
    393391   nqtottr = nqtot - COUNT(delPhase(tracers%gen0Name) == 'H2O' .AND. tracers%component == 'lmdz')
    394392   IF(COUNT(tracers%iso_iName == 0) - COUNT(delPhase(tracers%name) == 'H2O' .AND. tracers%component == 'lmdz') /= nqtottr) &
    395       CALL abort_gcm(modname, 'pb dans le calcul de nqtottr', 1)
     393      CALL abort_gcm(modname, 'problem with the computation of nqtottr', 1)
    396394
    397395   !=== DISPLAY THE RESULTS
     
    408406   t => tracers
    409407   CALL msg('Information stored in infotrac :', modname)
    410    IF(dispTable('isssssssssiiiiiiiii', &
    411       ['iq    ', 'name  ', 'lName ', 'gen0N ', 'parent', 'type  ', 'phase ', 'compon', 'isPhy ', 'isAdv ', &
    412        'iadv  ', 'iGen  ', 'iqPar ', 'nqDes ', 'nqChld', 'iGroup', 'iName ', 'iZone ', 'iPhase'],          &
     408
     409   IF(dispTable('isssssssssiiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp',    &
     410                'isPh', 'isAd', 'iadv', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'],   &
    413411      cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component, bool2str(t%isInPhysics), &
    414412                                                                                  bool2str(t%isAdvected)), &
Note: See TracChangeset for help on using the changeset viewer.