Ignore:
Timestamp:
Apr 15, 2025, 11:56:45 AM (2 months ago)
Author:
aborella
Message:

Merge with trunk testing r5597. We have convergence in prod and debug in NPv7.0.1c

Location:
LMDZ6/branches/contrails
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails

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

    r5609 r5618  
    33MODULE infotrac
    44
    5    USE       strings_mod, ONLY: msg, fmsg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse
    6    USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, tracers, setGeneration, itZonIso, nzone, tran0, isoZone, &
    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
    9    USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3
     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
    1010   IMPLICIT NONE
    1111
     
    3030   PUBLIC :: isoKeys, isoName, isoZone, isoPhas            !--- Isotopes keys & names, tagging zones names, phases
    3131   PUBLIC ::    niso,   ntiso,   nzone,   nphas            !--- Number of   "   "
    32    PUBLIC :: itZonIso                                      !--- index "it" in "isoName(1:niso)" = f(tagging idx, isotope idx)
    33    PUBLIC :: iqIsoPha                                      !--- index "iq" in "qx"              = f(isotope idx,   phase idx)
     32   PUBLIC :: itZonIso                                      !--- Index "it" in "isoName(1:niso)" = f(tagging idx, isotope idx)
     33   PUBLIC :: iqIsoPha                                      !--- Index "iq" in "qx"              = f(isotope idx,   phase idx)
    3434   PUBLIC :: isoCheck                                      !--- Run isotopes checking routines
    3535   !=== FOR BOTH TRACERS AND ISOTOPES
     
    7878!  | nqChildren  | Number of childs            (1st generation only)    | nqfils      | 1:nqtot                |
    7979!  | iadv        | Advection scheme number                              | iadv        | 1,2,10-20(exc.15,19),30|
    80 !  | isAdvected  | Advected tracers flag (.TRUE. if iadv >= 0)          | /           | nqtrue  .TRUE. values  |
    81 !  | isInPhysics | Tracers not extracted from the main table in physics | /           | nqtottr .TRUE. values  |
    8280!  | iso_iGroup  | Isotopes group index in isotopes(:)                  | /           | 1:nbIso                |
    8381!  | iso_iName   | Isotope  name  index in isotopes(iso_iGroup)%trac(:) | iso_indnum  | 1:niso                 |
     
    103101
    104102   !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
    105    INTEGER,               SAVE :: nqtot,   &                    !--- Tracers nb in dynamics (incl. higher moments + H2O)
    106                                   nbtr,    &                    !--- Tracers nb in physics  (excl. higher moments + H2O)
    107                                   nqo,     &                    !--- Number of water phases
    108                                   nqtottr, &                    !--- Number of tracers passed to phytrac (TO BE DELETED ?)
    109                                   nqCO2                         !--- Number of tracers of CO2  (ThL)
     103   INTEGER, SAVE :: nqtot                                       !--- Tracers nb in dynamics (incl. higher moments + H2O)
     104   INTEGER, SAVE :: nbtr                                        !--- Tracers nb in physics  (excl. higher moments + H2O)
     105   INTEGER, SAVE :: nqo                                         !--- Number of water phases
     106   INTEGER, SAVE :: nqtottr                                     !--- Number of tracers passed to phytrac (TO BE DELETED ?)
     107   INTEGER, SAVE :: nqCO2                                       !--- Number of tracers of CO2  (ThL)
    110108   CHARACTER(LEN=maxlen), SAVE :: type_trac                     !--- Keyword for tracers type(s)
    111109
    112110   !=== VARIABLES FOR INCA
    113    INTEGER, DIMENSION(:), SAVE, ALLOCATABLE :: &
    114                     conv_flg, pbl_flg                           !--- Convection / boundary layer activation (nbtr)
     111   INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), pbl_flg(:)        !--- Convection / boundary layer activation (nbtr)
    115112
    116113CONTAINS
     
    147144! Local variables
    148145   INTEGER, ALLOCATABLE :: hadv(:), vadv(:)                          !--- Horizontal/vertical transport scheme number
    149    INTEGER, ALLOCATABLE :: had (:), hadv_inca(:), conv_flg_inca(:), &!--- Variables specific to INCA
    150                            vad (:), vadv_inca(:),  pbl_flg_inca(:)
    151    CHARACTER(LEN=8), ALLOCATABLE :: solsym_inca(:)                   !--- Tracers names for INCA
    152146   INTEGER :: nqINCA
    153147   CHARACTER(LEN=2)      ::   suff(9)                                !--- Suffixes for schemes of order 3 or 4 (Prather)
    154148   CHARACTER(LEN=3)      :: descrq(30)                               !--- Advection scheme description tags
    155    CHARACTER(LEN=maxlen) :: msg1, texp, ttp                          !--- Strings for messages and expanded tracers type
     149   CHARACTER(LEN=maxlen) :: msg1, texp, ttp, nam, val                !--- Strings for messages and expanded tracers type
    156150   INTEGER :: fType                                                  !--- Tracers description file type ; 0: none
    157151                                                                     !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def"
    158152   INTEGER :: nqtrue                                                 !--- Tracers nb from tracer.def (no higher order moments)
    159153   INTEGER :: iad                                                    !--- Advection scheme number
    160    INTEGER :: iq, jq, nt, im, nm                                     !--- Indexes and temporary variables
    161    LOGICAL :: lerr, ll
     154   INTEGER :: iq, jq, nt, im, nm, ig                                 !--- Indexes and temporary variables
     155   LOGICAL :: lerr
    162156   TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
    163157   TYPE(trac_type), POINTER             :: t1, t(:)
     
    173167   descrq(30)    =  'PRA'
    174168
    175    lerr=strParse(type_trac, '|', types_trac, n=nt)
    176    IF (nt .GT. 1) THEN
    177       IF (nt .GT. 2) CALL abort_gcm(modname, 'you need to modify type_trac, this version is not supported by lmdz', 1)
    178       IF (nt .EQ. 2) type_trac=types_trac(2)
    179    ENDIF
    180 
    181169   CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname)
    182 
    183    
     170   IF(strCount(type_trac, '|', nt)) CALL abort_gcm(modname, 'Could''nt parse the "type_trac" string with delimiter "|"', 1)
     171   IF(nt >= 3) CALL abort_gcm(modname, 'you need to modify type_trac, this version is not supported by lmdz', 1)
     172   IF(strParse(type_trac, '|', types_trac, n=nt)) CALL abort_gcm(modname, "couldn't parse "//'"type_trac"', 1)
     173   IF(nt == 2) type_trac = types_trac(2) ! TO BE DELETED SOON
     174
     175   CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname)
     176
     177!##############################################################################################################################
     178   IF(.TRUE.) THEN                                                   !=== SKIPED IF ALREADY DONE IN dyn3d_common/infotrac  ####
     179!##############################################################################################################################
    184180   !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
    185181   msg1 = 'For type_trac = "'//TRIM(type_trac)//'":'
     
    197193   SELECT CASE(type_trac)
    198194      CASE('inca', 'inco')
    199 IF (.NOT. CPPKEY_INCA) THEN
    200          CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1)
    201 END IF
     195         IF(.NOT.CPPKEY_INCA)     CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1)
    202196      CASE('repr')
    203 IF (.NOT. CPPKEY_REPROBUS) THEN
    204          CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1)
    205 END IF
     197         IF(.NOT.CPPKEY_REPROBUS) CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1)
    206198      CASE('coag')
    207 IF (.NOT. CPPKEY_STRATAER) THEN
    208          CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1)
    209 END IF
     199         IF(.NOT.CPPKEY_STRATAER) CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1)
    210200   END SELECT
    211 
    212    nqCO2 = COUNT( [type_trac == 'inco', type_trac == 'co2i'] )
     201!##############################################################################################################################
     202   END IF
     203!##############################################################################################################################
    213204
    214205!==============================================================================================================================
    215206! 0) DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE AND READ IT
    216207!==============================================================================================================================
    217    texp = type_trac                                                            !=== EXPANDED (WITH "|" SEPARATOR) "type_trac"
     208   texp = type_trac                                                  !=== EXPANDED (WITH "|" SEPARATOR) "type_trac"
    218209   IF(texp == 'inco') texp = 'co2i|inca'
    219210   IF(texp /= 'lmdz') texp = 'lmdz|'//TRIM(texp)
    220211   IF(testTracersFiles(modname, texp, fType, .TRUE.)) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
    221212   ttp = type_trac; IF(fType /= 1) ttp = texp
    222    IF(readTracersFiles(ttp, lRepr=type_trac=='repr')) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
    223 
    224 !==============================================================================================================================
    225 ! 1) Get various numbers: "nqtrue" (first order only tracers), "nqo" (water phases), 'nbtr' (tracers passed to physics), etc.
    226 !==============================================================================================================================
    227213   !---------------------------------------------------------------------------------------------------------------------------
    228214   IF(fType == 0) CALL abort_gcm(modname, 'Missing "traceur.def", "tracer.def" or "tracer_<keyword>.def tracers file.',1)
    229215   !---------------------------------------------------------------------------------------------------------------------------
    230    IF(fType == 1 .AND. ANY(['inca', 'inco'] == type_trac)) THEN      !=== FOUND OLD STYLE INCA "traceur.def"
     216   IF(fType == 1 .AND. ANY(['inca', 'inco'] == type_trac)) &         !=== FOUND OLD STYLE INCA "traceur.def"
     217      CALL abort_gcm(modname, 'retro-compatibility with old-style INCA traceur.def files has been disabled.', 1)
    231218   !---------------------------------------------------------------------------------------------------------------------------
    232 IF (CPPKEY_INCA) THEN
    233       nqo = SIZE(tracers) - nqCO2
    234       CALL Init_chem_inca_trac(nqINCA)                               !--- Get nqINCA from INCA
    235       nbtr = nqINCA + nqCO2                                          !--- Number of tracers passed to phytrac
    236       nqtrue = nbtr + nqo                                            !--- Total number of "true" tracers
    237       IF(ALL([2,3] /= nqo)) CALL abort_gcm(modname, 'Only 2 or 3 water phases allowed ; found nqo='//TRIM(int2str(nqo)), 1)
    238       ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA))
    239       ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA),  pbl_flg_inca(nqINCA))
    240       CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca)
    241       ALLOCATE(ttr(nqtrue))
    242       ttr(1:nqo+nqCO2)                  = tracers
    243       ttr(1    :      nqo   )%component = 'lmdz'
    244       ttr(1+nqo:nqCO2+nqo   )%component = 'co2i'
    245       ttr(1+nqo+nqCO2:nqtrue)%component = 'inca'
    246       ttr(1+nqo      :nqtrue)%name      = [('CO2     ', iq=1, nqCO2), solsym_inca]
    247       ttr(1+nqo+nqCO2:nqtrue)%parent    = tran0
    248       ttr(1+nqo+nqCO2:nqtrue)%phase     = 'g'
    249       lerr = getKey('hadv', had, ky=tracers(:)%keys)
    250       lerr = getKey('vadv', vad, ky=tracers(:)%keys)
    251       hadv(1:nqo+nqCO2) = had(:); hadv(1+nqo+nqCO2:nqtrue) = hadv_inca
    252       vadv(1:nqo+nqCO2) = vad(:); vadv(1+nqo+nqCO2:nqtrue) = vadv_inca
    253       CALL MOVE_ALLOC(FROM=ttr, TO=tracers)
    254       DO iq = 1, nqtrue
    255          t1 => tracers(iq)
    256          CALL addKey('name',      t1%name,      t1%keys)
    257          CALL addKey('component', t1%component, t1%keys)
    258          CALL addKey('parent',    t1%parent,    t1%keys)
    259          CALL addKey('phase',     t1%phase,     t1%keys)
    260       END DO
    261       IF(setGeneration(tracers)) CALL abort_gcm(modname,'See above',1) !- SET FIELDS %iGeneration, %gen0Name
    262       DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca)
    263 END IF
    264    !---------------------------------------------------------------------------------------------------------------------------
    265    ELSE                                                              !=== OTHER CASES (OLD OR NEW FORMAT, NO INCA MODULE)
    266    !---------------------------------------------------------------------------------------------------------------------------
     219
     220!##############################################################################################################################
     221   IF(readTracersFiles(ttp, lRepr=type_trac == 'repr')) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
     222!##############################################################################################################################
     223
     224!==============================================================================================================================
     225! 1) Get various numbers: "nqtrue" (first order only tracers), "nqo" (water phases), 'nbtr' (tracers passed to physics), etc.
     226!==============================================================================================================================
    267227   nqtrue = SIZE(tracers)                                                                               !--- "true" tracers
    268228!   nqo    =      COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%name)     == 'H2O')     !--- Water phases
     
    275235        (delPhase(tracers(:)%gen0Name)     == 'CLDFRA')))
    276236   nqCO2  =      COUNT( [type_trac == 'inco', type_trac == 'co2i'] )
    277 IF (CPPKEY_INCA) THEN
     237   IF(CPPKEY_INCA) &
    278238   nqINCA =      COUNT(tracers(:)%component == 'inca')
    279 END IF
     239   IF(CPPKEY_REPROBUS) CALL Init_chem_rep_trac(nbtr, nqo, tracers(:)%name)
     240
     241!==============================================================================================================================
     242! 2) Calculate nqtot, number of tracers needed (greater if advection schemes 20 or 30 have been chosen).
     243!==============================================================================================================================
    280244   IF(getKey('hadv', hadv, ky=tracers(:)%keys)) CALL abort_gcm(modname, 'missing key "hadv"', 1)
    281245   IF(getKey('vadv', vadv, ky=tracers(:)%keys)) CALL abort_gcm(modname, 'missing key "vadv"', 1)
    282    !---------------------------------------------------------------------------------------------------------------------------
    283    END IF
    284    !---------------------------------------------------------------------------------------------------------------------------
    285 
    286 IF (CPPKEY_REPROBUS) THEN
    287    CALL Init_chem_rep_trac(nbtr, nqo, tracers(:)%name)
    288 END IF
    289 
    290 !==============================================================================================================================
    291 ! 2) Calculate nqtot, number of tracers needed (greater if advection schemes 20 or 30 have been chosen).
    292 !==============================================================================================================================
    293246   DO iq = 1, nqtrue
    294247      IF( hadv(iq)<20 .OR. (ANY(hadv(iq)==[20,30]) .AND. hadv(iq)==vadv(iq)) ) CYCLE
     
    308261
    309262!==============================================================================================================================
    310 ! 3) Determine the advection scheme choice for water and tracers "iadv" and the fields long name, isAdvected.
     263! 3) Determine the advection scheme choice for water and tracers "iadv" and the field "long name".
    311264!     iadv = 1    "LMDZ-specific humidity transport" (for H2O vapour)          LMV
    312265!     iadv = 2    backward                           (for H2O liquid)          BAK
     
    326279!==============================================================================================================================
    327280   ALLOCATE(ttr(nqtot))
    328    jq = nqtrue+1; tracers(:)%iadv = -1
     281   jq = nqtrue+1
    329282   DO iq = 1, nqtrue
    330283      t1 => tracers(iq)
     
    337290      IF(iad == -1) CALL abort_gcm(modname, msg1, 1)
    338291
    339       !--- SET FIELDS longName, iadv, isAdvected, isInPhysics
     292      !--- SET FIELDS longName and iadv
    340293      t1%longName   = t1%name; IF(iad > 0) t1%longName=TRIM(t1%name)//descrq(iad)
    341294      t1%iadv       = iad
    342       t1%isAdvected = iad >= 0
    343 !      t1%isInPhysics= delPhase(t1%gen0Name) /= 'H2O' .OR. t1%component /= 'lmdz' !=== MORE EXCEPTIONS ? CO2i, SURSAT CLOUD H2O
    344       t1%isInPhysics=((delPhase(t1%gen0Name) /= 'H2O') .AND. &
    345                       (delPhase(t1%gen0Name) /= 'CLDFRA')) .OR. t1%component /= 'lmdz'
    346295      ttr(iq)       = t1
    347296
     
    357306      ttr(jq+1:jq+nm)%longName    = [ (TRIM(t1%longName)//'-'//TRIM(suff(im)), im=1, nm) ]
    358307      ttr(jq+1:jq+nm)%iadv        = [ (-iad,    im=1, nm) ]
    359       ttr(jq+1:jq+nm)%isAdvected  = [ (.FALSE., im=1, nm) ]
    360308      jq = jq + nm
    361309   END DO
     
    367315
    368316   !=== TEST ADVECTION SCHEME
    369    DO iq = 1, nqtot ; t1 => tracers(iq); iad = t1%iadv
     317   DO iq = 1, nqtot ; t1 => tracers(iq)
     318      iad = t1%iadv
     319      ig  = t1%iGeneration
     320      nam = t1%name
     321      val = 'iadv='//TRIM(int2str(iad))
    370322
    371323      !--- ONLY TESTED VALUES FOR TRACERS FOR NOW:               iadv = 14, 10 (and 0 for non-transported tracers)
    372       IF(ALL([10,14,0] /= iad)) &
    373          CALL abort_gcm(modname, 'Not tested for iadv='//TRIM(int2str(iad))//' ; 10 or 14 only are allowed !', 1)
    374 
    375       !--- ONLY TESTED VALUES FOR PARENTS HAVING CHILDS FOR NOW: iadv = 14, 10 (PARENTS: TRACERS OF GENERATION 1)
    376       IF(ALL([10,14] /= iad) .AND. t1%iGeneration == 1 .AND. ANY(tracers(:)%iGeneration > 1)) &
    377          CALL abort_gcm(modname, 'iadv='//TRIM(int2str(iad))//' not implemented for parents ; 10 or 14 only are allowed !', 1)
    378 
    379       !--- ONLY TESTED VALUES FOR CHILDS FOR NOW:                iadv = 10     (CHILDS:  TRACERS OF GENERATION GREATER THAN 1)
    380       IF(fmsg('WARNING ! iadv='//TRIM(int2str(iad))//' not implemented for childs. Setting iadv=10 for "'//TRIM(t1%name)//'"',&
    381          modname, iad /= 10 .AND. t1%iGeneration > 1)) t1%iadv = 10
    382 
    383       !--- ONLY VALID SCHEME NUMBER FOR WATER VAPOUR:            iadv = 14
    384       ll = t1%name /= addPhase('H2O','g')
    385       IF(fmsg('WARNING ! iadv=14 is valid for water vapour only. Setting iadv=10 for "'//TRIM(t1%name)//'".', &
    386          modname, iad == 14 .AND. ll))                 t1%iadv = 10
     324      IF(ALL([10,14,0] /= iad)) CALL abort_gcm(modname, TRIM(val)//' has not been tested yet ; 10 or 14 only are allowed !', 1)
     325
     326      !--- ONLY TESTED VALUES SO FAR FOR PARENTS HAVING CHILDREN: iadv = 14, 10 (PARENTS: TRACERS OF GENERATION 0)
     327      IF(ALL([10,14] /= iad) .AND. ig == 0 .AND. ANY(tracers(:)%parent==nam)) &
     328         CALL abort_gcm(modname, TRIM(val)//' is not implemented for parents ; 10 or 14 only are allowed !', 1)
     329
     330      !--- ONLY TESTED VALUES SO FAR FOR DESCENDANTS (TRACERS OF GENERATION > 0): iadv = 10 ; WATER VAPOUR: iadv = 14
     331      lerr = iad /= 10 .AND. ig > 0;                     IF(lerr) tracers(iq)%iadv = 10
     332      CALL msg('WARNING! '//TRIM(val)//  ' not implemented for children. Setting iadv=10 for "'//TRIM(nam)//'"', modname, lerr)
     333      lerr = iad == 14 .AND. nam /= addPhase('H2O','g'); IF(lerr) tracers(iq)%iadv = 10
     334      CALL msg('WARNING! '//TRIM(val)//' is valid for water vapour only. Setting iadv=10 for "'//TRIM(nam)//'"', modname, lerr)
    387335   END DO
    388336
     
    392340
    393341   !--- Convection / boundary layer activation for all tracers
    394    ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1
    395    ALLOCATE( pbl_flg(nbtr));  pbl_flg(1:nbtr) = 1
     342   IF(.NOT.ALLOCATED(conv_flg)) ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1
     343   IF(.NOT.ALLOCATED( pbl_flg)) ALLOCATE( pbl_flg(nbtr));  pbl_flg(1:nbtr) = 1
    396344
    397345   !--- Note: nqtottr can differ from nbtr when nmom/=0
     
    401349        (delPhase(tracers(:)%gen0Name)     == 'CLDFRA')))
    402350!   IF(COUNT(tracers%iso_iName == 0) - COUNT(delPhase(tracers%name) == 'H2O' .AND. tracers%component == 'lmdz') /= nqtottr) &
    403 !   IF(COUNT(tracers%iso_iName == 0) - COUNT(tracers(:)%component == 'lmdz' .AND. &
    404 !       ((delPhase(tracers(:)%name)     == 'H2O') .OR. &
    405 !        (delPhase(tracers(:)%name)     == 'CLDFRA') /= nqtottr) &
    406 !      CALL abort_gcm(modname, 'problem with the computation of nqtottr', 1)
     351   IF(COUNT(tracers%iso_iName == 0) - COUNT(tracers(:)%component == 'lmdz' .AND. &
     352       ((delPhase(tracers(:)%name)     == 'H2O') .OR. &
     353        (delPhase(tracers(:)%name)     == 'CLDFRA'))) /= nqtottr) &
     354      CALL abort_gcm(modname, 'problem with the computation of nqtottr', 1)
    407355
    408356   !=== DISPLAY THE RESULTS
     357   IF(.NOT..TRUE.) RETURN
    409358   CALL msg('nqo    = '//TRIM(int2str(nqo)),    modname)
    410359   CALL msg('nbtr   = '//TRIM(int2str(nbtr)),   modname)
     
    413362   CALL msg('niso   = '//TRIM(int2str(niso)),   modname)
    414363   CALL msg('ntiso  = '//TRIM(int2str(ntiso)),  modname)
    415 IF (CPPKEY_INCA) THEN
    416    CALL msg('nqCO2  = '//TRIM(int2str(nqCO2)),  modname)
    417    CALL msg('nqINCA = '//TRIM(int2str(nqINCA)), modname)
    418 END IF
     364   CALL msg('nqCO2  = '//TRIM(int2str(nqCO2)),  modname, CPPKEY_INCA)
     365   CALL msg('nqINCA = '//TRIM(int2str(nqINCA)), modname, CPPKEY_INCA)
    419366   t => tracers
    420367   CALL msg('Information stored in '//TRIM(modname)//': ', modname)
     
    425372                  t%iso_iName, t%iso_iZone, t%iso_iPhase), nColMax=maxTableWidth, nHead=2, sub=modname))   &
    426373      CALL abort_gcm(modname, "problem with the tracers table content", 1)
    427    IF(niso > 0) THEN
    428       CALL msg('Where, for isotopes family "'//TRIM(isotope%parent)//'":', modname)
    429       CALL msg('  isoKeys%name = '//strStack(isoKeys%name), modname)
    430       CALL msg('  isoName = '//strStack(isoName),      modname)
    431       CALL msg('  isoZone = '//strStack(isoZone),      modname)
    432       CALL msg('  isoPhas = '//TRIM(isoPhas),          modname)
    433    ELSE
    434       CALL msg('No isotopes identified.', modname)
    435    END IF
    436    CALL msg('end', modname)
     374   CALL msg('No isotopes identified.', modname, nbIso == 0)
     375   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)
    437381
    438382END SUBROUTINE init_infotrac
Note: See TracChangeset for help on using the changeset viewer.