Ignore:
Timestamp:
Feb 12, 2025, 10:08:35 AM (3 days ago)
Author:
aborella
Message:

Revert merge with trunk

Location:
LMDZ6/branches/contrails
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails

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

    r5489 r5536  
    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, 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
    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  |
    8082!  | iso_iGroup  | Isotopes group index in isotopes(:)                  | /           | 1:nbIso                |
    8183!  | iso_iName   | Isotope  name  index in isotopes(iso_iGroup)%trac(:) | iso_indnum  | 1:niso                 |
     
    101103
    102104   !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
    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)
     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)
    108110   CHARACTER(LEN=maxlen), SAVE :: type_trac                     !--- Keyword for tracers type(s)
    109111
    110112   !=== VARIABLES FOR INCA
    111    INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), pbl_flg(:)        !--- Convection / boundary layer activation (nbtr)
     113   INTEGER, DIMENSION(:), SAVE, ALLOCATABLE :: &
     114                    conv_flg, pbl_flg                           !--- Convection / boundary layer activation (nbtr)
    112115
    113116CONTAINS
     
    144147! Local variables
    145148   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
    146152   INTEGER :: nqINCA
    147153   CHARACTER(LEN=2)      ::   suff(9)                                !--- Suffixes for schemes of order 3 or 4 (Prather)
    148154   CHARACTER(LEN=3)      :: descrq(30)                               !--- Advection scheme description tags
    149    CHARACTER(LEN=maxlen) :: msg1, texp, ttp, nam, val                !--- Strings for messages and expanded tracers type
     155   CHARACTER(LEN=maxlen) :: msg1, texp, ttp                          !--- Strings for messages and expanded tracers type
    150156   INTEGER :: fType                                                  !--- Tracers description file type ; 0: none
    151157                                                                     !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def"
    152158   INTEGER :: nqtrue                                                 !--- Tracers nb from tracer.def (no higher order moments)
    153159   INTEGER :: iad                                                    !--- Advection scheme number
    154    INTEGER :: iq, jq, nt, im, nm, ig                                 !--- Indexes and temporary variables
    155    LOGICAL :: lerr
     160   INTEGER :: iq, jq, nt, im, nm                                     !--- Indexes and temporary variables
     161   LOGICAL :: lerr, ll
    156162   TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
    157163   TYPE(trac_type), POINTER             :: t1, t(:)
     
    167173   descrq(30)    =  'PRA'
    168174
     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
    169181   CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname)
    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 !##############################################################################################################################
     182
     183   
    180184   !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
    181185   msg1 = 'For type_trac = "'//TRIM(type_trac)//'":'
     
    193197   SELECT CASE(type_trac)
    194198      CASE('inca', 'inco')
    195          IF(.NOT.CPPKEY_INCA)     CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1)
     199IF (.NOT. CPPKEY_INCA) THEN
     200         CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1)
     201END IF
    196202      CASE('repr')
    197          IF(.NOT.CPPKEY_REPROBUS) CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1)
     203IF (.NOT. CPPKEY_REPROBUS) THEN
     204         CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1)
     205END IF
    198206      CASE('coag')
    199          IF(.NOT.CPPKEY_STRATAER) CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1)
     207IF (.NOT. CPPKEY_STRATAER) THEN
     208         CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1)
     209END IF
    200210   END SELECT
    201 !##############################################################################################################################
    202    END IF
    203 !##############################################################################################################################
     211
     212   nqCO2 = COUNT( [type_trac == 'inco', type_trac == 'co2i'] )
    204213
    205214!==============================================================================================================================
    206215! 0) DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE AND READ IT
    207216!==============================================================================================================================
    208    texp = type_trac                                                  !=== EXPANDED (WITH "|" SEPARATOR) "type_trac"
     217   texp = type_trac                                                            !=== EXPANDED (WITH "|" SEPARATOR) "type_trac"
    209218   IF(texp == 'inco') texp = 'co2i|inca'
    210219   IF(texp /= 'lmdz') texp = 'lmdz|'//TRIM(texp)
    211220   IF(testTracersFiles(modname, texp, fType, .TRUE.)) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
    212221   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!==============================================================================================================================
    213227   !---------------------------------------------------------------------------------------------------------------------------
    214228   IF(fType == 0) CALL abort_gcm(modname, 'Missing "traceur.def", "tracer.def" or "tracer_<keyword>.def tracers file.',1)
    215229   !---------------------------------------------------------------------------------------------------------------------------
    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)
    218    !---------------------------------------------------------------------------------------------------------------------------
    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 !==============================================================================================================================
     230   IF(fType == 1 .AND. ANY(['inca', 'inco'] == type_trac)) THEN      !=== FOUND OLD STYLE INCA "traceur.def"
     231   !---------------------------------------------------------------------------------------------------------------------------
     232IF (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)
     263END IF
     264   !---------------------------------------------------------------------------------------------------------------------------
     265   ELSE                                                              !=== OTHER CASES (OLD OR NEW FORMAT, NO INCA MODULE)
     266   !---------------------------------------------------------------------------------------------------------------------------
    227267   nqtrue = SIZE(tracers)                                                                               !--- "true" tracers
    228268   nqo    =      COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%name)     == 'H2O')     !--- Water phases
    229269   nbtr = nqtrue-COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%gen0Name) == 'H2O')     !--- Passed to phytrac
    230270   nqCO2  =      COUNT( [type_trac == 'inco', type_trac == 'co2i'] )
    231    IF(CPPKEY_INCA) &
     271IF (CPPKEY_INCA) THEN
    232272   nqINCA =      COUNT(tracers(:)%component == 'inca')
    233    IF(CPPKEY_REPROBUS) CALL Init_chem_rep_trac(nbtr, nqo, tracers(:)%name)
    234 
    235 !==============================================================================================================================
    236 ! 2) Calculate nqtot, number of tracers needed (greater if advection schemes 20 or 30 have been chosen).
    237 !==============================================================================================================================
     273END IF
    238274   IF(getKey('hadv', hadv, ky=tracers(:)%keys)) CALL abort_gcm(modname, 'missing key "hadv"', 1)
    239275   IF(getKey('vadv', vadv, ky=tracers(:)%keys)) CALL abort_gcm(modname, 'missing key "vadv"', 1)
     276   !---------------------------------------------------------------------------------------------------------------------------
     277   END IF
     278   !---------------------------------------------------------------------------------------------------------------------------
     279
     280IF (CPPKEY_REPROBUS) THEN
     281   CALL Init_chem_rep_trac(nbtr, nqo, tracers(:)%name)
     282END IF
     283
     284!==============================================================================================================================
     285! 2) Calculate nqtot, number of tracers needed (greater if advection schemes 20 or 30 have been chosen).
     286!==============================================================================================================================
    240287   DO iq = 1, nqtrue
    241288      IF( hadv(iq)<20 .OR. (ANY(hadv(iq)==[20,30]) .AND. hadv(iq)==vadv(iq)) ) CYCLE
     
    255302
    256303!==============================================================================================================================
    257 ! 3) Determine the advection scheme choice for water and tracers "iadv" and the field "long name".
     304! 3) Determine the advection scheme choice for water and tracers "iadv" and the fields long name, isAdvected.
    258305!     iadv = 1    "LMDZ-specific humidity transport" (for H2O vapour)          LMV
    259306!     iadv = 2    backward                           (for H2O liquid)          BAK
     
    273320!==============================================================================================================================
    274321   ALLOCATE(ttr(nqtot))
    275    jq = nqtrue+1
     322   jq = nqtrue+1; tracers(:)%iadv = -1
    276323   DO iq = 1, nqtrue
    277324      t1 => tracers(iq)
     
    284331      IF(iad == -1) CALL abort_gcm(modname, msg1, 1)
    285332
    286       !--- SET FIELDS longName and iadv
     333      !--- SET FIELDS longName, iadv, isAdvected, isInPhysics
    287334      t1%longName   = t1%name; IF(iad > 0) t1%longName=TRIM(t1%name)//descrq(iad)
    288335      t1%iadv       = iad
     336      t1%isAdvected = iad >= 0
     337      t1%isInPhysics= delPhase(t1%gen0Name) /= 'H2O' .OR. t1%component /= 'lmdz' !=== MORE EXCEPTIONS ? CO2i, SURSAT CLOUD H2O
    289338      ttr(iq)       = t1
    290339
     
    300349      ttr(jq+1:jq+nm)%longName    = [ (TRIM(t1%longName)//'-'//TRIM(suff(im)), im=1, nm) ]
    301350      ttr(jq+1:jq+nm)%iadv        = [ (-iad,    im=1, nm) ]
     351      ttr(jq+1:jq+nm)%isAdvected  = [ (.FALSE., im=1, nm) ]
    302352      jq = jq + nm
    303353   END DO
     
    309359
    310360   !=== TEST ADVECTION SCHEME
    311    DO iq = 1, nqtot ; t1 => tracers(iq)
    312       iad = t1%iadv
    313       ig  = t1%iGeneration
    314       nam = t1%name
    315       val = 'iadv='//TRIM(int2str(iad))
     361   DO iq = 1, nqtot ; t1 => tracers(iq); iad = t1%iadv
    316362
    317363      !--- ONLY TESTED VALUES FOR TRACERS FOR NOW:               iadv = 14, 10 (and 0 for non-transported tracers)
    318       IF(ALL([10,14,0] /= iad)) CALL abort_gcm(modname, TRIM(val)//' has not been tested yet ; 10 or 14 only are allowed !', 1)
    319 
    320       !--- ONLY TESTED VALUES SO FAR FOR PARENTS HAVING CHILDREN: iadv = 14, 10 (PARENTS: TRACERS OF GENERATION 0)
    321       IF(ALL([10,14] /= iad) .AND. ig == 0 .AND. ANY(tracers(:)%parent==nam)) &
    322          CALL abort_gcm(modname, TRIM(val)//' is not implemented for parents ; 10 or 14 only are allowed !', 1)
    323 
    324       !--- ONLY TESTED VALUES SO FAR FOR DESCENDANTS (TRACERS OF GENERATION > 0): iadv = 10 ; WATER VAPOUR: iadv = 14
    325       lerr = iad /= 10 .AND. ig > 0;                     IF(lerr) tracers(iq)%iadv = 10
    326       CALL msg('WARNING! '//TRIM(val)//  ' not implemented for children. Setting iadv=10 for "'//TRIM(nam)//'"', modname, lerr)
    327       lerr = iad == 14 .AND. nam /= addPhase('H2O','g'); IF(lerr) tracers(iq)%iadv = 10
    328       CALL msg('WARNING! '//TRIM(val)//' is valid for water vapour only. Setting iadv=10 for "'//TRIM(nam)//'"', modname, lerr)
     364      IF(ALL([10,14,0] /= iad)) &
     365         CALL abort_gcm(modname, 'Not tested for iadv='//TRIM(int2str(iad))//' ; 10 or 14 only are allowed !', 1)
     366
     367      !--- ONLY TESTED VALUES FOR PARENTS HAVING CHILDS FOR NOW: iadv = 14, 10 (PARENTS: TRACERS OF GENERATION 1)
     368      IF(ALL([10,14] /= iad) .AND. t1%iGeneration == 1 .AND. ANY(tracers(:)%iGeneration > 1)) &
     369         CALL abort_gcm(modname, 'iadv='//TRIM(int2str(iad))//' not implemented for parents ; 10 or 14 only are allowed !', 1)
     370
     371      !--- ONLY TESTED VALUES FOR CHILDS FOR NOW:                iadv = 10     (CHILDS:  TRACERS OF GENERATION GREATER THAN 1)
     372      IF(fmsg('WARNING ! iadv='//TRIM(int2str(iad))//' not implemented for childs. Setting iadv=10 for "'//TRIM(t1%name)//'"',&
     373         modname, iad /= 10 .AND. t1%iGeneration > 1)) t1%iadv = 10
     374
     375      !--- ONLY VALID SCHEME NUMBER FOR WATER VAPOUR:            iadv = 14
     376      ll = t1%name /= addPhase('H2O','g')
     377      IF(fmsg('WARNING ! iadv=14 is valid for water vapour only. Setting iadv=10 for "'//TRIM(t1%name)//'".', &
     378         modname, iad == 14 .AND. ll))                 t1%iadv = 10
    329379   END DO
    330380
     
    334384
    335385   !--- Convection / boundary layer activation for all tracers
    336    IF(.NOT.ALLOCATED(conv_flg)) ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1
    337    IF(.NOT.ALLOCATED( pbl_flg)) ALLOCATE( pbl_flg(nbtr));  pbl_flg(1:nbtr) = 1
     386   ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1
     387   ALLOCATE( pbl_flg(nbtr));  pbl_flg(1:nbtr) = 1
    338388
    339389   !--- Note: nqtottr can differ from nbtr when nmom/=0
     
    343393
    344394   !=== DISPLAY THE RESULTS
    345    IF(.NOT..TRUE.) RETURN
    346395   CALL msg('nqo    = '//TRIM(int2str(nqo)),    modname)
    347396   CALL msg('nbtr   = '//TRIM(int2str(nbtr)),   modname)
     
    350399   CALL msg('niso   = '//TRIM(int2str(niso)),   modname)
    351400   CALL msg('ntiso  = '//TRIM(int2str(ntiso)),  modname)
    352    CALL msg('nqCO2  = '//TRIM(int2str(nqCO2)),  modname, CPPKEY_INCA)
    353    CALL msg('nqINCA = '//TRIM(int2str(nqINCA)), modname, CPPKEY_INCA)
     401IF (CPPKEY_INCA) THEN
     402   CALL msg('nqCO2  = '//TRIM(int2str(nqCO2)),  modname)
     403   CALL msg('nqINCA = '//TRIM(int2str(nqINCA)), modname)
     404END IF
    354405   t => tracers
    355406   CALL msg('Information stored in '//TRIM(modname)//': ', modname)
     
    360411                  t%iso_iName, t%iso_iZone, t%iso_iPhase), nColMax=maxTableWidth, nHead=2, sub=modname))   &
    361412      CALL abort_gcm(modname, "problem with the tracers table content", 1)
    362    CALL msg('No isotopes identified.', modname, nbIso == 0)
    363    IF(nbIso == 0) RETURN
    364    CALL msg('For isotopes family "H2O":', modname)
    365    CALL msg('  isoKeys%name = '//strStack(isoKeys%name), modname)
    366    CALL msg('  isoName = '//strStack(isoName),      modname)
    367    CALL msg('  isoZone = '//strStack(isoZone),      modname)
    368    CALL msg('  isoPhas = '//TRIM(isoPhas),          modname)
     413   IF(niso > 0) THEN
     414      CALL msg('Where, for isotopes family "'//TRIM(isotope%parent)//'":', modname)
     415      CALL msg('  isoKeys%name = '//strStack(isoKeys%name), modname)
     416      CALL msg('  isoName = '//strStack(isoName),      modname)
     417      CALL msg('  isoZone = '//strStack(isoZone),      modname)
     418      CALL msg('  isoPhas = '//TRIM(isoPhas),          modname)
     419   ELSE
     420      CALL msg('No isotopes identified.', modname)
     421   END IF
     422   CALL msg('end', modname)
    369423
    370424END SUBROUTINE init_infotrac
Note: See TracChangeset for help on using the changeset viewer.