Ignore:
Timestamp:
Oct 20, 2022, 1:57:21 PM (20 months ago)
Author:
dcugnet
Message:
  • for REPROBUS: simplify (and fix) the handling of exceptions for old HNO3 convention.
  • cleaning + comments added in readTracFiles_mod.
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d_common/infotrac.F90

    r4193 r4301  
    55   USE       strings_mod, ONLY: msg, find, strIdx,  strFind, strParse, dispTable, int2str,  reduceExpr, &
    66                          cat, fmsg, test, strTail, strHead, strStack, strReduce, bool2str, maxlen, testFile
    7    USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, addPhase, indexUpdate,  nphases, ancestor,  &
    8                                 isot_type, old2newName,      delPhase,               getKey_init, tran0, &
    9                                 keys_type, initIsotopes,     getPhase, known_phases, getKey, setGeneration, &
    10                                 maxTableWidth
     7   USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, indexUpdate, addPhase, getKey, maxTableWidth, keys_type, &
     8                                isot_type, setGeneration,   initIsotopes, delPhase, getKey_init, ancestor, tran0
     9                               
    1110   IMPLICIT NONE
    1211
     
    182181   INTEGER :: iad                                                    !--- Advection scheme number
    183182   INTEGER :: ic, ip, np, iq, jq, it, nt, im, nm, ix, iz, nz, k      !--- Indexes and temporary variables
    184    LOGICAL :: lerr, ll
     183   LOGICAL :: lerr, ll, lRepr
    185184   CHARACTER(LEN=1) :: p
    186185   TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
    187186   TYPE(trac_type), POINTER             :: t1, t(:)
    188187   TYPE(isot_type), POINTER             :: iso
    189 
    190    CHARACTER(LEN=maxlen), ALLOCATABLE :: tnom_0(:), tnom_transp(:)   !--- Tracer short name + transporting fluid name
    191    CHARACTER(LEN=maxlen)              :: tchaine
    192188   INTEGER :: ierr
    193189
     
    247243         modname, ALL(types_trac /= 'inca') .AND. ALL(types_trac /= 'inco') .AND. config_inca /= 'none')) config_inca = 'none'
    248244
    249    nqCO2 = 0; IF(ANY(types_trac == 'inco')) nqCO2 = 1
     245   nqCO2 = COUNT( [ANY(types_trac == 'inco') .OR. (ANY(types_trac == 'co2i') .AND. ANY(types_trac == 'inca'))] )
    250246
    251247!==============================================================================================================================
    252248! 1) Get the numbers of: true (first order only) tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid)
    253249!==============================================================================================================================
    254    IF(readTracersFiles(type_trac, fType, tracers)) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
     250   lRepr = ANY(types_trac(:) == 'repr')
     251   IF(readTracersFiles(type_trac, fType, tracers, lRepr)) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
     252   !---------------------------------------------------------------------------------------------------------------------------
    255253   IF(fType == 0) CALL abort_gcm(modname, 'Missing tracers file: "traceur.def", "tracer.def" or "tracer_<keyword>.def file.',1)
    256254   !---------------------------------------------------------------------------------------------------------------------------
     
    258256   !---------------------------------------------------------------------------------------------------------------------------
    259257#ifdef INCA
    260       nqo = SIZE(tracers)
    261       IF(nqCO2==1 .AND. nqo==4) nqo = 3                              !--- Force nqo to 3 (ThL)
     258      nqo = SIZE(tracers) - nqCO2
    262259      CALL Init_chem_inca_trac(nqINCA)                               !--- Get nqINCA from INCA
    263260      nbtr = nqINCA + nqCO2                                          !--- Number of tracers passed to phytrac
     
    284281#endif
    285282   !---------------------------------------------------------------------------------------------------------------------------
    286    ELSE                                                              !=== FOUND NEW STYLE TRACERS CONFIGURATION FILE(S)
     283   ELSE                                                              !=== OTHER CASES (OLD OR NEW FORMAT, NO INCA MODULE)
    287284   !---------------------------------------------------------------------------------------------------------------------------
    288285      nqo    =        COUNT(delPhase(tracers(:)%name)     == 'H2O' &
     
    407404   IF(initIsotopes(tracers, isotopes)) CALL abort_gcm(modname, 'Problem when reading isotopes parameters', 1)
    408405   nbIso = SIZE(isotopes)
    409    nqtottr = nqtot - COUNT(tracers%gen0Name == 'H2O' .AND. tracers%component == 'lmdz')
     406   nqtottr = nqtot - COUNT(delPhase(tracers%gen0Name) == 'H2O' .AND. tracers%component == 'lmdz')
    410407   IF(nbIso/=0) THEN                        !--- ISOTOPES FOUND
    411408
     
    442439
    443440   !--- Note: nqtottr can differ from nbtr when nmom/=0
    444 !   IF(COUNT(tracers%iso_iName == 0) - COUNT(delPhase(tracers%name) == 'H2O' .AND. tracers%component == 'lmdz') /= nqtottr) &
    445 !      CALL abort_gcm('infotrac_init', 'pb dans le calcul de nqtottr', 1)
     441   IF(COUNT(tracers%iso_iName == 0) - COUNT(delPhase(tracers%name) == 'H2O' .AND. tracers%component == 'lmdz') /= nqtottr) &
     442      CALL abort_gcm('infotrac_init', 'pb dans le calcul de nqtottr', 1)
    446443
    447444   !=== DISPLAY THE RESULTS
     
    486483LOGICAL FUNCTION isoSelectByName(iName, lVerbose) RESULT(lerr)
    487484   IMPLICIT NONE
    488    CHARACTER(LEN=*),  INTENT(IN)  :: iName
     485   CHARACTER(LEN=*),  INTENT(IN) :: iName
    489486   LOGICAL, OPTIONAL, INTENT(IN) :: lVerbose
    490487   INTEGER :: iIso
Note: See TracChangeset for help on using the changeset viewer.