Ignore:
Timestamp:
Sep 20, 2024, 12:32:04 PM (8 weeks 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/phylmd/infotrac_phy.F90

    r4638 r5202  
    55   USE       strings_mod, ONLY: msg, fmsg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse, strIdx
    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
     
    2020   PUBLIC :: id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat
    2121#endif
    22 #ifdef REPROBUS
    23    PUBLIC :: nbtr_bin, nbtr_sulgas
    24    PUBLIC :: id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, &
    25              id_TEST_strat
    26 #endif
    27 
     22
     23   !=== FOR WATER
     24   PUBLIC :: ivap, iliq, isol
    2825   !=== FOR ISOTOPES: General
    2926   PUBLIC :: isot_type, nbIso                              !--- Derived type, full isotopes families database + nb of families
     
    3734   PUBLIC :: itZonIso                                      !--- idx "it" (in "isoName(1:niso)") = function(tagging idx, isotope idx)
    3835   PUBLIC :: iqIsoPha                                      !--- idx "iq" (in "qx") = function(isotope idx, phase idx) + aliases
     36   PUBLIC :: iqWIsoPha                                      !--- Same as iqIsoPha but with normal water phases
     37
    3938   PUBLIC :: isoCheck                                      !--- Run isotopes checking routines
    4039   !=== FOR BOTH TRACERS AND ISOTOPES
     
    7372!  | longName    | Long name (with adv. scheme suffix) for outputs      | ttext       |                        |
    7473!  | type        | Type (so far: tracer or tag)                         | /           | tracer,tag             |
    75 !  | phase       | Phases list ("g"as / "l"iquid / "s"olid / "b"lowing) | /           | [g][l][s][b]           |
     74!  | phase       | Phases list ("g"as / "l"iquid / "s"olid)             | /           | [g][l][s]              |
    7675!  | component   | Name(s) of the merged/cumulated section(s)           | /           | coma-separated names   |
    7776!  | iGeneration | Generation (>=1)                                     | /           |                        |
     
    9897!  | trac   | ntiso  | Isotopes + tagging tracers list + number         | / | ntraciso       |                 |
    9998!  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
    100 !  | phase  | nphas  | Phases                     list + number         |                    |[g][l][s][b] 1:4 |
     99!  | phase  | nphas  | Phases                     list + number         |                    | [g][l][s], 1:3 |
    101100!  | iqIsoPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
     101!  | iqWIsoPha       | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
    102102!  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
    103103!  +-----------------+--------------------------------------------------+--------------------+-----------------+
     
    112112!$OMP THREADPRIVATE(nqtot, nbtr, nqo, nqtottr, nqCO2, type_trac)
    113113
     114   !=== INDICES OF WATER
     115   INTEGER,               SAVE :: ivap,iliq,isol ! Indices for vap, liq and ice
     116!$OMP THREADPRIVATE(ivap,iliq,isol)
     117
    114118   !=== VARIABLES FOR INCA
    115119   INTEGER,               SAVE, ALLOCATABLE :: conv_flg(:), &   !--- Convection     activation ; needed for INCA        (nbtr)
     
    123127  INTEGER, SAVE ::  id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat
    124128!$OMP THREADPRIVATE(id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat)
    125 #endif
    126 #ifdef REPROBUS
    127   INTEGER, SAVE ::  nbtr_bin, nbtr_sulgas
    128 !$OMP THREADPRIVATE(nbtr_bin, nbtr_sulgas)
    129   INTEGER, SAVE ::  id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat,&
    130                     id_TEST_strat
    131 !$OMP THREADPRIVATE(id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat)
    132 !$OMP THREADPRIVATE(id_TEST_strat)
    133129#endif
    134130
     
    182178   INTEGER :: nqtrue                                                 !--- Tracers nb from tracer.def (no higher order moments)
    183179   INTEGER :: iad                                                    !--- Advection scheme number
    184    INTEGER :: ic, iq, jq, it, nt, im, nm, iz, k                      !--- Indexes and temporary variables
    185    LOGICAL :: lerr, ll, lInit
    186    CHARACTER(LEN=1) :: p
     180   INTEGER :: iq, jq, nt, im, nm, k                                 !--- Indexes and temporary variables
     181   LOGICAL :: lerr, lInit
    187182   TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
    188183   TYPE(trac_type), POINTER             :: t1, t(:)
    189    INTEGER :: ierr
    190184   CHARACTER(LEN=maxlen),   ALLOCATABLE :: types_trac(:)  !--- Keyword for tracers type(s), parsed version
    191185   
     
    262256!##############################################################################################################################
    263257   IF(lInit) THEN
    264       IF(readTracersFiles(ttp, type_trac == 'repr')) CALL abort_physic(modname, 'problem with tracers file(s)',1)
     258      IF(readTracersFiles(ttp, lRepr=type_trac=='repr')) CALL abort_physic(modname, 'problem with tracers file(s)',1)
    265259   ELSE
    266260      CALL msg('No tracers description file(s) reading needed: already done in the dynamics', modname)
     
    388382
    389383   !--- SET FIELDS %iqParent, %nqChildren, %iGeneration, %iqDescen, %nqDescen
    390    CALL indexUpdate(tracers)
     384   IF(indexUpdate(tracers)) CALL abort_gcm(modname, 'problem when processing isotopes parameters', 1)
    391385
    392386!##############################################################################################################################
     
    404398   !=== READ PHYSICAL PARAMETERS FOR ISOTOPES
    405399   niso = 0; nzone = 0; nphas = nqo; ntiso = 0; isoCheck = .FALSE.
    406    IF(readIsotopesFile()) CALL abort_physic(modname, 'Problem when reading isotopes parameters', 1)
     400   IF(processIsotopes()) CALL abort_physic(modname, 'Problem when processing isotopes parameters', 1)
    407401
    408402!##############################################################################################################################
     
    416410   nqtottr = nqtot - COUNT(delPhase(tracers%gen0Name) == 'H2O' .AND. tracers%component == 'lmdz')
    417411   IF(COUNT(tracers%iso_iName == 0) - COUNT(delPhase(tracers%name) == 'H2O' .AND. tracers%component == 'lmdz') /= nqtottr) &
    418       CALL abort_physic(modname, 'pb dans le calcul de nqtottr', 1)
     412      CALL abort_physic(modname, 'problem with the computation of nqtottr', 1)
    419413
    420414   !=== DISPLAY THE RESULTS
     
    431425   t => tracers
    432426   CALL msg('Information stored in infotrac_phy :', modname)
    433    IF(dispTable('issssssssiiiiiiii', &
    434       ['iq    ', 'name  ', 'lName ', 'gen0N ', 'parent', 'type  ', 'phase ', 'compon', 'isPhy ',           &
    435                  'iGen  ', 'iqPar ', 'nqDes ', 'nqChld', 'iGroup', 'iName ', 'iZone ', 'iPhase'],          &
     427   IF(dispTable('issssssssiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp',      &
     428                              'isPh', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'],     &
    436429      cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component, bool2str(t%isInPhysics)),&
    437430      cat([(iq, iq=1, nqtot)], t%iGeneration, t%iqParent, t%nqDescen, t%nqChildren, t%iso_iGroup,          &
Note: See TracChangeset for help on using the changeset viewer.