Changeset 4389


Ignore:
Timestamp:
Jan 23, 2023, 11:28:51 AM (16 months ago)
Author:
dcugnet
Message:
  • revert to original "type_trac" management:
    • 4 characters keyword (lmdz, Inca, repr, co2i, into, aeNP, coag
    • no longer a list of component with "|" separator
    • the parsed (with "|" separator) version "types_trac" is no longer used
    • the sole routine using a list of component is readTracFiles
  • fix for INCA and CO2Aer modes: setGeneration is now a function, index corrections for had/vadv.
Location:
LMDZ6/trunk/libf
Files:
24 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d/dynredem.F90

    r4170 r4389  
    167167!-------------------------------------------------------------------------------
    168168  USE strings_mod, ONLY: maxlen
    169   USE infotrac, ONLY: nqtot, tracers, types_trac
     169  USE infotrac, ONLY: nqtot, tracers, type_trac
    170170  USE control_mod
    171171  USE netcdf,   ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID,  &
     
    228228!--- Tracers in file "start_trac.nc" (added by Anne)
    229229  lread_inca=.FALSE.; fil="start_trac.nc"
    230   IF(ANY(types_trac=='inca') .OR. ANY(types_trac=='inco')) INQUIRE(FILE=fil,EXIST=lread_inca)
     230  IF(ANY(type_trac == ['inca','inco'])) INQUIRE(FILE=fil,EXIST=lread_inca)
    231231  IF(lread_inca) CALL err(NF90_OPEN(fil,NF90_NOWRITE,nid_trac),"open")
    232232
  • LMDZ6/trunk/libf/dyn3d_common/infotrac.F90

    r4358 r4389  
    44
    55   USE       strings_mod, ONLY: msg, fmsg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse
    6    USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, tracers, setGeneration, itZonIso, nbIso, tran0, delPhase, &
    7                         getKey, isot_type, readIsotopesFile, isotope, maxTableWidth, iqIsoPha, ntiso, ixIso, addPhase, &
    8                    indexUpdate, isoSelect, isoPhas, isoZone, isoName, isoKeys, iH2O, isoCheck, nphas, nzone, niso
     6   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, nbIso,  isoSelect, testTracersFiles, isoKeys, indexUpdate,   isoCheck, nzone, ntiso, isoName
    99   IMPLICIT NONE
    1010
     
    1313   !=== FOR TRACERS:
    1414   PUBLIC :: init_infotrac                                 !--- Initialization of the tracers
    15    PUBLIC :: tracers, type_trac, types_trac                !--- Full tracers database, tracers type keyword
     15   PUBLIC :: tracers, type_trac                            !--- Full tracers database, tracers type keyword
    1616   PUBLIC :: nqtot,   nbtr,   nqo,   nqCO2,   nqtottr      !--- Main dimensions
    1717   PUBLIC :: conv_flg, pbl_flg                             !--- Convection & boundary layer activation keys
     
    104104                                  nqtottr, &                    !--- Number of tracers passed to phytrac (TO BE DELETED ?)
    105105                                  nqCO2                         !--- Number of tracers of CO2  (ThL)
    106    CHARACTER(LEN=maxlen), SAVE :: type_trac                     !--- Keyword for tracers type(s)
    107    CHARACTER(LEN=maxlen), SAVE, ALLOCATABLE :: types_trac(:)    !--- Keyword for tracers type(s), parsed version
     106   CHARACTER(LEN=maxlen), SAVE :: type_trac                     !--- Keyword for tracers type
    108107
    109108   !=== VARIABLES FOR INCA
     
    152151   CHARACTER(LEN=2)      ::   suff(9)                                !--- Suffixes for schemes of order 3 or 4 (Prather)
    153152   CHARACTER(LEN=3)      :: descrq(30)                               !--- Advection scheme description tags
    154    CHARACTER(LEN=maxlen) :: msg1                                     !--- String for messages
     153   CHARACTER(LEN=maxlen) :: msg1, texp, ttp                          !--- Strings for messages and expanded tracers type
    155154   INTEGER :: fType                                                  !--- Tracers description file type ; 0: none
    156155                                                                     !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def"
     
    158157   INTEGER :: iad                                                    !--- Advection scheme number
    159158   INTEGER :: ic, iq, jq, it, nt, im, nm, iz, k                      !--- Indexes and temporary variables
    160    LOGICAL :: lerr, ll, lRepr
     159   LOGICAL :: lerr, ll
    161160   CHARACTER(LEN=1) :: p
    162161   TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
     
    174173   
    175174   CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname)
    176    IF(strParse(type_trac, '|', types_trac, n=nt)) CALL abort_gcm(modname,'can''t parse "type_trac = '//TRIM(type_trac)//'"',1)
    177 
    178    !---------------------------------------------------------------------------------------------------------------------------
    179    DO it = 1, nt                                                          !--- nt>1=> "type_trac": coma-separated keywords list
    180    !---------------------------------------------------------------------------------------------------------------------------
    181       !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
    182       msg1 = 'For type_trac = "'//TRIM(types_trac(it))//'":'
    183       SELECT CASE(types_trac(it))
    184          CASE('inca'); CALL msg(TRIM(msg1)//' coupling with INCA chemistry model',        modname)
    185          CASE('inco'); CALL msg(TRIM(msg1)//' coupling jointly with INCA and CO2 cycle',  modname)
    186          CASE('repr'); CALL msg(TRIM(msg1)//' coupling with REPROBUS chemistry model',    modname)
    187          CASE('co2i'); CALL msg(TRIM(msg1)//' you have chosen to run with CO2 cycle',     modname)
    188          CASE('coag'); CALL msg(TRIM(msg1)//' tracers are treated for COAGULATION tests', modname)
    189          CASE('lmdz'); CALL msg(TRIM(msg1)//' tracers are treated in LMDZ only',          modname)
    190          CASE DEFAULT; CALL abort_gcm(modname,'type_trac='//TRIM(types_trac(it))//' not possible yet.',1)
    191       END SELECT
    192 
    193       !--- COHERENCE TEST BETWEEN "type_trac" AND PREPROCESSING KEYS
    194       SELECT CASE(types_trac(it))
    195          CASE('inca', 'inco')
     175
     176   !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
     177   msg1 = 'For type_trac = "'//TRIM(type_trac)//'":'
     178   SELECT CASE(type_trac)
     179      CASE('inca'); CALL msg(TRIM(msg1)//' coupling with INCA chemistry model',        modname)
     180      CASE('inco'); CALL msg(TRIM(msg1)//' coupling jointly with INCA and CO2 cycle',  modname)
     181      CASE('repr'); CALL msg(TRIM(msg1)//' coupling with REPROBUS chemistry model',    modname)
     182      CASE('co2i'); CALL msg(TRIM(msg1)//' you have chosen to run with CO2 cycle',     modname)
     183      CASE('coag'); CALL msg(TRIM(msg1)//' tracers are treated for COAGULATION tests', modname)
     184      CASE('lmdz'); CALL msg(TRIM(msg1)//' tracers are treated in LMDZ only',          modname)
     185      CASE DEFAULT; CALL abort_gcm(modname,'type_trac='//TRIM(type_trac)//' not possible yet.',1)
     186   END SELECT
     187
     188   !--- COHERENCE TEST BETWEEN "type_trac" AND PREPROCESSING KEYS
     189   SELECT CASE(type_trac)
     190      CASE('inca', 'inco')
    196191#ifndef INCA
    197             CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1)
    198 #endif
    199          CASE('repr')
     192         CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1)
     193#endif
     194      CASE('repr')
    200195#ifndef REPROBUS
    201             CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1)
    202 #endif
    203          CASE('coag')
     196         CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1)
     197#endif
     198      CASE('coag')
    204199#ifndef CPP_StratAer
    205             CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1)
    206 #endif
    207       END SELECT
    208 
    209    !---------------------------------------------------------------------------------------------------------------------------
    210    END DO
    211    !---------------------------------------------------------------------------------------------------------------------------
    212 
    213    nqCO2 = COUNT( [ANY(types_trac == 'inco') .OR. (ANY(types_trac == 'co2i') .AND. ANY(types_trac == 'inca'))] )
     200         CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1)
     201#endif
     202   END SELECT
     203
     204   nqCO2 = COUNT( [type_trac == 'inco', type_trac == 'co2i'] )
    214205
    215206!==============================================================================================================================
    216207! 1) Get the numbers of: true (first order only) tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid)
    217208!==============================================================================================================================
    218    lRepr = ANY(types_trac(:) == 'repr')
    219    IF(readTracersFiles(type_trac, fType, lRepr)) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
     209   texp = type_trac                                                  !=== EXPANDED VERSION OF "type_trac", WITH "|" SEPARATOR
     210   IF(texp == 'inco') texp = 'co2i|inca'
     211   IF(texp /= 'lmdz') texp = 'lmdz|'//TRIM(texp)
     212
     213   !=== DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE
     214   IF(testTracersFiles(modname, texp, fType, .TRUE.)) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
     215   ttp = type_trac; IF(fType /= 1) ttp = texp
     216
     217   IF(readTracersFiles(ttp, type_trac == 'repr'))     CALL abort_gcm(modname, 'problem with tracers file(s)',1)
    220218   !---------------------------------------------------------------------------------------------------------------------------
    221219   IF(fType == 0) CALL abort_gcm(modname, 'Missing tracers file: "traceur.def", "tracer.def" or "tracer_<keyword>.def file.',1)
    222220   !---------------------------------------------------------------------------------------------------------------------------
    223    IF(fType == 1 .AND. ANY(['inca','inco'] == type_trac)) THEN       !=== FOUND OLD STYLE INCA "traceur.def" (single type_trac)
     221   IF(fType == 1 .AND. ANY(['inca','inco']==type_trac)) THEN         !=== FOUND OLD STYLE INCA "traceur.def"
    224222   !---------------------------------------------------------------------------------------------------------------------------
    225223#ifdef INCA
     
    233231      CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca)
    234232      ALLOCATE(ttr(nqtrue))
    235       ttr(1:nqo+nqCO2)                    = tracers
    236       ttr(1    :      nqo   )%component   = 'lmdz'
    237       ttr(1+nqo:nqCO2+nqo   )%component   = 'co2i'
    238       ttr(1+nqo+nqCO2:nqtrue)%component   = 'inca'
    239       ttr(1+nqo      :nqtrue)%name        = [('CO2     ', k=1, nqCO2), solsym_inca]
    240       ttr(1+nqo+nqCO2:nqtrue)%parent      = tran0
    241       ttr(1+nqo+nqCO2:nqtrue)%phase       = 'g'
     233      ttr(1:nqo+nqCO2)                  = tracers
     234      ttr(1    :      nqo   )%component = 'lmdz'
     235      ttr(1+nqo:nqCO2+nqo   )%component = 'co2i'
     236      ttr(1+nqo+nqCO2:nqtrue)%component = 'inca'
     237      ttr(1+nqo      :nqtrue)%name      = [('CO2     ', k=1, nqCO2), solsym_inca]
     238      ttr(1+nqo+nqCO2:nqtrue)%parent    = tran0
     239      ttr(1+nqo+nqCO2:nqtrue)%phase     = 'g'
    242240      lerr = getKey('hadv', had, ky=tracers(:)%keys)
    243241      lerr = getKey('vadv', vad, ky=tracers(:)%keys)
    244       hadv(1:nqo) = had(:); hadv(nqo+1:nqtrue) = hadv_inca
    245       vadv(1:nqo) = vad(:); vadv(nqo+1:nqtrue) = vadv_inca
     242      hadv(1:nqo+nqCO2) = had(:); hadv(1+nqo+nqCO2:nqtrue) = hadv_inca
     243      vadv(1:nqo+nqCO2) = vad(:); vadv(1+nqo+nqCO2:nqtrue) = vadv_inca
    246244      CALL MOVE_ALLOC(FROM=ttr, TO=tracers)
    247       CALL setGeneration(tracers)                                    !--- SET FIELDS %iGeneration, %gen0Name
     245      IF(setGeneration(tracers)) CALL abort_gcm(modname,'See above',1) !- SET FIELDS %iGeneration, %gen0Name
    248246      DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca)
    249247#endif
  • LMDZ6/trunk/libf/dyn3dmem/dynredem_loc.F90

    r4172 r4389  
    176176  USE mod_hallo
    177177  USE strings_mod, ONLY: maxlen
    178   USE infotrac, ONLY: nqtot, tracers, types_trac
     178  USE infotrac, ONLY: nqtot, tracers, type_trac
    179179  USE control_mod
    180180  USE netcdf,   ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID,  &
     
    243243!$OMP MASTER
    244244  fil="start_trac.nc"
    245   IF(ANY(types_trac=='inca') .OR. ANY(types_trac=='inco')) INQUIRE(FILE=fil,EXIST=lread_inca)
     245  IF(ANY(type_trac == ['inca','inco'])) INQUIRE(FILE=fil,EXIST=lread_inca)
    246246  IF(lread_inca) CALL err(NF90_OPEN(fil,NF90_NOWRITE,nid_trac),"open")
    247247!$OMP END MASTER
  • LMDZ6/trunk/libf/dyn3dmem/leapfrog_loc.F

    r4187 r4389  
    15191519
    15201520#ifdef INCA
    1521          if (ANY(types_trac == 'inca') .OR.
    1522      &       ANY(types_trac == 'inco')) CALL finalize_inca
     1521         if (ANY(type_trac == ['inca','inco'])) CALL finalize_inca
    15231522#endif
    15241523#ifdef REPROBUS
    1525          if (ANY(types_trac == 'repr')) CALL finalize_reprobus
     1524         if (type_trac == 'repr') CALL finalize_reprobus
    15261525#endif
    15271526
     
    15691568
    15701569#ifdef INCA
    1571               if (ANY(types_trac == 'inca') .OR.
    1572      &            ANY(types_trac == 'inco')) CALL finalize_inca
     1570              if (ANY(type_trac == ['inca','inco'])) CALL finalize_inca
    15731571#endif
    15741572#ifdef REPROBUS
    1575               if (ANY(types_trac == 'repr')) CALL finalize_reprobus
     1573              if (type_trac == 'repr') CALL finalize_reprobus
    15761574#endif
    15771575
     
    17371735
    17381736#ifdef INCA
    1739                  if (ANY(types_trac == 'inca') .OR.
    1740      &               ANY(types_trac == 'inco')) CALL finalize_inca
     1737              if (ANY(type_trac == ['inca','inco'])) CALL finalize_inca
    17411738#endif
    17421739#ifdef REPROBUS
    1743                  if (ANY(types_trac == 'repr')) CALL finalize_reprobus
     1740                 if (type_trac == 'repr') CALL finalize_reprobus
    17441741#endif
    17451742
     
    18451842
    18461843#ifdef INCA
    1847       if (ANY(types_trac == 'inca') .OR.
    1848      &    ANY(types_trac == 'inco')) CALL finalize_inca
     1844      if (ANY(type_trac == ['inca','inco'])) CALL finalize_inca
    18491845#endif
    18501846#ifdef REPROBUS
    1851       if (ANY(types_trac == 'repr')) CALL finalize_reprobus
     1847      if (type_trac == 'repr') CALL finalize_reprobus
    18521848#endif
    18531849
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/ce0l.F90

    r4361 r4389  
    2323  USE netcdf,         ONLY: NF90_OPEN, NF90_NOWRITE, NF90_CLOSE, NF90_NOERR,    &
    2424         NF90_INQUIRE_DIMENSION, NF90_INQ_DIMID, NF90_INQ_VARID, NF90_GET_VAR
    25   USE infotrac,       ONLY: type_trac, init_infotrac
     25  USE infotrac,       ONLY: init_infotrac
    2626  USE dimphy,         ONLY: klon
    2727  USE test_disvert_m, ONLY: test_disvert
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90

    r4358 r4389  
    1616  USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
    1717  USE vertical_layers_mod, ONLY : init_vertical_layers
    18   USE infotrac, ONLY: nbtr, type_trac, types_trac
     18  USE infotrac, ONLY: nbtr, type_trac
    1919#ifdef CPP_StratAer
    2020  USE infotrac_phy, ONLY: nbtr_bin, nbtr_sulgas, id_OCS_strat, &
     
    140140
    141141  ! Initializations for Reprobus
    142   IF (ANY(types_trac == 'repr')) THEN
     142  IF (type_trac == 'repr') THEN
    143143#ifdef REPROBUS
    144144    call Init_chem_rep_phys(klon_omp,nlayer)
     
    151151
    152152
    153   IF (ANY(types_trac == 'repr')) THEN
     153  IF (type_trac == 'repr') THEN
    154154#ifdef REPROBUS
    155155    call init_reprobus_para( &
     
    166166  END IF
    167167
    168   IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN
     168  IF (ANY(type_trac == ['inca','inco'])) THEN
    169169#ifdef INCA
    170170     CALL init_inca_dim_reg(nbp_lon, nbp_lat - 1, &
  • LMDZ6/trunk/libf/misc/readTracFiles_mod.f90

    r4367 r4389  
    179179!     * If you need to convert a %key/%val pair into a direct-access key, add the corresponding line in "setDirectKeys".
    180180!==============================================================================================================================
    181 LOGICAL FUNCTION readTracersFiles(type_trac, fTyp, lRepr) RESULT(lerr)
     181LOGICAL FUNCTION readTracersFiles(type_trac, lRepr) RESULT(lerr)
    182182!------------------------------------------------------------------------------------------------------------------------------
    183183  CHARACTER(LEN=*),  INTENT(IN)  :: type_trac                        !--- List of components used
    184   INTEGER, OPTIONAL, INTENT(OUT) :: fTyp                             !--- Type of input file found
    185184  LOGICAL, OPTIONAL, INTENT(IN)  :: lRepr                            !--- Activate the HNNO3 exceptions for REPROBUS
    186185  CHARACTER(LEN=maxlen),  ALLOCATABLE :: s(:), sections(:), trac_files(:)
     
    196195
    197196  !--- Required sections + corresponding files names (new style single section case) for tests
    198   IF(test(testTracersFiles(modname, type_trac, fType, .TRUE., trac_files, sections), lerr)) RETURN
    199   IF(PRESENT(fTyp)) fTyp = fType
     197  IF(test(testTracersFiles(modname, type_trac, fType, .FALSE., trac_files, sections), lerr)) RETURN
    200198  nsec = SIZE(sections)
    201199
     
    290288  CHARACTER(LEN=*),                             INTENT(IN)  :: modname, type_trac
    291289  INTEGER,                                      INTENT(OUT) :: fType
    292   LOGICAL,                                      INTENT(IN)  :: lDisp
     290  LOGICAL,                            OPTIONAL, INTENT(IN)  :: lDisp
    293291  CHARACTER(LEN=maxlen), ALLOCATABLE, OPTIONAL, INTENT(OUT) :: tracf(:), sects(:)
    294292  CHARACTER(LEN=maxlen), ALLOCATABLE :: trac_files(:), sections(:)
    295293  LOGICAL, ALLOCATABLE :: ll(:)
     294  LOGICAL :: lD
    296295  INTEGER :: is, nsec
    297 
    298   !--- PARSE "type_trac" LIST AND DETERMINE THE TRACERS FILES NAMES (FOR CASE 3: MULTIPLE FILES, SINNGLE SECTION PER FILE)
     296  lD = .FALSE.; IF(PRESENT(lDisp)) lD = lDisp
     297  lerr = .FALSE.
     298
     299  !--- PARSE "type_trac" LIST AND DETERMINE THE TRACERS FILES NAMES (FOR CASE 3: MULTIPLE FILES, SINGLE SECTION PER FILE)
     300  !--- If type_trac is a scalar (case 1), "sections" and "trac_files" are not usable, but are meaningless for case 1 anyway.
    299301  IF(test(strParse(type_trac, '|', sections,  n=nsec), lerr)) RETURN !--- Parse "type_trac" list
    300302  IF(PRESENT(sects)) sects = sections
    301303  ALLOCATE(trac_files(nsec)); DO is=1, nsec; trac_files(is) = 'tracer_'//TRIM(sections(is))//'.def'; END DO
    302304  IF(PRESENT(tracf)) tracf = trac_files
    303 
    304   nsec = SIZE(trac_files, DIM=1)
    305305  ll = .NOT.testFile(trac_files)
    306306  fType = 0
    307   IF(.NOT.testFile('traceur.def') .AND. nsec==1) fType = 1           !--- OLD STYLE FILE
    308   IF(.NOT.testFile('tracer.def'))                fType = 2           !--- NEW STYLE ; SINGLE  FILE, SEVERAL SECTIONS
    309   IF(ALL(ll))                                    fType = 3           !--- NEW STYLE ; SEVERAL FILES, SINGLE SECTION USED
    310   IF(.NOT.test(lDisp, lerr)) RETURN                                  !--- NO CHECKING/DISPLAY NEEDED: JUST GET type_trac,fType
     307  IF(.NOT.testFile('traceur.def')) fType = 1                         !--- OLD STYLE FILE
     308  IF(.NOT.testFile('tracer.def'))  fType = 2                         !--- NEW STYLE ; SINGLE  FILE, SEVERAL SECTIONS
     309  IF(ALL(ll))                      fType = 3                         !--- NEW STYLE ; SEVERAL FILES, SINGLE SECTION USED
     310  IF(.NOT.lD) RETURN                                                 !--- NO CHECKING/DISPLAY NEEDED: JUST GET type_trac,fType
    311311  IF(ANY(ll) .AND. fType/=3) THEN                                    !--- MISSING FILES
    312312    IF(test(checkList(trac_files, .NOT.ll, 'Failed reading tracers description', 'files', 'missing'), lerr)) RETURN
    313313  END IF
    314 
    315   !--- CHECK WHETHER type_trac AND FILE TYPE ARE COMPATIBLE
    316   IF(test(fmsg('No multiple sections for the old format "traceur.def"', ll = nsec>1 .AND. fType==1), lerr)) RETURN
    317314
    318315  !--- TELLS WHAT WAS IS ABOUT TO BE USED
  • LMDZ6/trunk/libf/phy_common/physics_distribution_mod.F90

    r4263 r4389  
    1313  USE mod_grid_phy_lmdz, ONLY: init_grid_phy_lmdz
    1414  USE dimphy, ONLY : Init_dimphy
    15   USE infotrac_phy, ONLY : types_trac
     15  USE infotrac_phy, ONLY : type_trac
    1616#ifdef REPROBUS
    1717  USE CHEM_REP, ONLY : Init_chem_rep_phys
     
    3939#ifdef REPROBUS
    4040! Initialization of Reprobus
    41     IF (ANY(types_trac == 'repr')) CALL Init_chem_rep_phys(klon_omp,nbp_lev)
     41    IF (type_trac == 'repr') CALL Init_chem_rep_phys(klon_omp,nbp_lev)
    4242#endif
    4343
     
    5050!  USE mod_grid_phy_lmdz, ONLY: Init_grid_phy_lmdz!, nbp_lev
    5151!  USE dimphy, ONLY : Init_dimphy
    52 !  USE infotrac_phy, ONLY : types_trac
     52!  USE infotrac_phy, ONLY : type_trac
    5353!#ifdef REPROBUS
    5454!  USE CHEM_REP, ONLY : Init_chem_rep_phys
     
    7171!#ifdef REPROBUS
    7272!! Initialization of Reprobus
    73 !    IF (ANY(types_trac == 'repr')) CALL Init_chem_rep_phys(klon_omp,nbp_lev)
     73!    IF (type_trac == 'repr') CALL Init_chem_rep_phys(klon_omp,nbp_lev)
    7474!    END IF
    7575!#endif
  • LMDZ6/trunk/libf/phydev/infotrac_phy.F90

    r4244 r4389  
    77   INTEGER,                 SAVE :: nqtot                       !--- Tracers nb in dynamics (incl. higher moments + H2O)
    88   CHARACTER(LEN=maxlen),   SAVE :: type_trac                   !--- Keyword for tracers type
    9    CHARACTER(LEN=maxlen),   SAVE, ALLOCATABLE :: types_trac(:)  !--- Parsed version (one or several components name(s))
    10 !$OMP THREADPRIVATE(nqtot, type_trac, types_trac)
     9!$OMP THREADPRIVATE(nqtot, type_trac)
    1110
    1211CONTAINS
    1312
    1413SUBROUTINE init_infotrac_phy(nqtot_, type_trac_)
    15    USE strings_mod, ONLY: strParse
    1614   IMPLICIT NONE
    1715   INTEGER,          INTENT(IN) :: nqtot_
     
    2018
    2119   nqtot = nqtot_
    22    IF(strParse(type_trac, '|', types_trac)) CALL abort_physic(modname,'can''t parse "type_trac = '//TRIM(type_trac)//'"',1)
    2320   type_trac = type_trac_
    2421
  • LMDZ6/trunk/libf/phylmd/Dust/phys_output_write_spl_mod.F90

    r4160 r4389  
    381381    USE pbl_surface_mod, ONLY: snow
    382382    USE indice_sol_mod, ONLY: nbsrf
    383     USE infotrac, ONLY: nqtot, nbtr, tracers, type_trac
     383    USE infotrac, ONLY: nqtot, nbtr, tracers
    384384    USE geometry_mod, ONLY: cell_area
    385385    USE surface_data, ONLY: type_ocean, version_ocean, ok_veget, landice_opt
  • LMDZ6/trunk/libf/phylmd/infotrac_phy.F90

    r4358 r4389  
    1313   !=== FOR TRACERS:
    1414   PUBLIC :: init_infotrac_phy                             !--- Initialization of the tracers
    15    PUBLIC :: tracers, type_trac, types_trac                !--- Full tracers database, tracers type keyword
     15   PUBLIC :: tracers, type_trac                            !--- Full tracers database, tracers type keyword
    1616   PUBLIC :: nqtot,   nbtr,   nqo,   nqCO2,   nqtottr      !--- Main dimensions
    1717   PUBLIC :: conv_flg, pbl_flg                             !--- Convection & boundary layer activation keys
     
    104104                                  nqCO2                         !--- Number of tracers of CO2  (ThL)
    105105   CHARACTER(LEN=maxlen), SAVE :: type_trac                     !--- Keyword for tracers type(s)
    106    CHARACTER(LEN=maxlen), SAVE, ALLOCATABLE :: types_trac(:)    !--- Keyword for tracers type(s), parsed version
    107 !$OMP THREADPRIVATE(nqtot, nbtr, nqo, nqtottr, nqCO2, type_trac, types_trac)
     106!$OMP THREADPRIVATE(nqtot, nbtr, nqo, nqtottr, nqCO2, type_trac)
    108107
    109108   !=== VARIABLES FOR INCA
     
    164163   CHARACTER(LEN=2)      ::   suff(9)                                !--- Suffixes for schemes of order 3 or 4 (Prather)
    165164   CHARACTER(LEN=3)      :: descrq(30)                               !--- Advection scheme description tags
    166    CHARACTER(LEN=maxlen) :: msg1                                     !--- String for messages
     165   CHARACTER(LEN=maxlen) :: msg1, texp, ttp                          !--- String for messages and expanded tracers type
    167166   INTEGER :: fType                                                  !--- Tracers description file type ; 0: none
    168167                                                                     !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def"
     
    170169   INTEGER :: iad                                                    !--- Advection scheme number
    171170   INTEGER :: ic, iq, jq, it, nt, im, nm, iz, k                      !--- Indexes and temporary variables
    172    LOGICAL :: lerr, ll, lRepr, lInit
     171   LOGICAL :: lerr, ll, lInit
    173172   CHARACTER(LEN=1) :: p
    174173   TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
     
    181180!------------------------------------------------------------------------------------------------------------------------------
    182181   suff          = ['x ','y ','z ','xx','xy','xz','yy','yz','zz']
     182   descrq( 1:30) =  '   '
    183183   descrq( 1: 2) = ['LMV','BAK']
    184184   descrq(10:20) = ['VL1','VLP','FH1','FH2','VLH','   ','PPM','PPS','PPP','   ','SLP']
     
    187187   CALL getin_p('type_trac',type_trac)
    188188   CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname)
    189    IF(strParse(type_trac, '|', types_trac, n=nt)) CALL abort_gcm(modname,'can''t parse "type_trac = '//TRIM(type_trac)//'"',1)
    190189   lInit = .NOT.ALLOCATED(tracers)
    191190
     
    193192   IF(lInit) THEN                                                    !=== SKIPED IF ALREADY DONE IN dyn3d_common/infotrac  ####
    194193!##############################################################################################################################
    195    !---------------------------------------------------------------------------------------------------------------------------
    196    DO it = 1, nt                                                     !--- nt>1=> "type_trac": coma-separated keywords list
    197    !---------------------------------------------------------------------------------------------------------------------------
    198       !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
    199       msg1 = 'For type_trac = "'//TRIM(types_trac(it))//'":'
    200       SELECT CASE(types_trac(it))
    201          CASE('inca'); CALL msg(TRIM(msg1)//' coupling with INCA chemistry model',        modname)
    202          CASE('inco'); CALL msg(TRIM(msg1)//' coupling jointly with INCA and CO2 cycle',  modname)
    203          CASE('repr'); CALL msg(TRIM(msg1)//' coupling with REPROBUS chemistry model',    modname)
    204          CASE('co2i'); CALL msg(TRIM(msg1)//' you have chosen to run with CO2 cycle',     modname)
    205          CASE('coag'); CALL msg(TRIM(msg1)//' tracers are treated for COAGULATION tests', modname)
    206          CASE('lmdz'); CALL msg(TRIM(msg1)//' tracers are treated in LMDZ only',          modname)
    207          CASE DEFAULT; CALL abort_gcm(modname,'type_trac='//TRIM(types_trac(it))//' not possible yet.',1)
    208       END SELECT
    209 
    210       !--- COHERENCE TEST BETWEEN "type_trac" AND PREPROCESSING KEYS
    211       SELECT CASE(types_trac(it))
    212          CASE('inca', 'inco')
     194   !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
     195   msg1 = 'For type_trac = "'//TRIM(type_trac)//'":'
     196   SELECT CASE(type_trac)
     197      CASE('inca'); CALL msg(TRIM(msg1)//' coupling with INCA chemistry model',        modname)
     198      CASE('inco'); CALL msg(TRIM(msg1)//' coupling jointly with INCA and CO2 cycle',  modname)
     199      CASE('repr'); CALL msg(TRIM(msg1)//' coupling with REPROBUS chemistry model',    modname)
     200      CASE('co2i'); CALL msg(TRIM(msg1)//' you have chosen to run with CO2 cycle',     modname)
     201      CASE('coag'); CALL msg(TRIM(msg1)//' tracers are treated for COAGULATION tests', modname)
     202      CASE('lmdz'); CALL msg(TRIM(msg1)//' tracers are treated in LMDZ only',          modname)
     203      CASE DEFAULT; CALL abort_gcm(modname,'type_trac='//TRIM(type_trac)//' not possible yet.',1)
     204   END SELECT
     205
     206   !--- COHERENCE TEST BETWEEN "type_trac" AND PREPROCESSING KEYS
     207   SELECT CASE(type_trac)
     208      CASE('inca', 'inco')
    213209#ifndef INCA
    214             CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1)
    215 #endif
    216          CASE('repr')
     210         CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1)
     211#endif
     212      CASE('repr')
    217213#ifndef REPROBUS
    218             CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1)
    219 #endif
    220          CASE('coag')
     214         CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1)
     215#endif
     216      CASE('coag')
    221217#ifndef CPP_StratAer
    222             CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1)
    223 #endif
    224       END SELECT
    225 
    226    !---------------------------------------------------------------------------------------------------------------------------
    227    END DO
    228    !---------------------------------------------------------------------------------------------------------------------------
    229 
    230 !##############################################################################################################################
    231    END IF
    232 !##############################################################################################################################
    233 
    234    nqCO2 = COUNT( [ANY(types_trac == 'inco') .OR. (ANY(types_trac == 'co2i') .AND. ANY(types_trac == 'inca'))] )
     218         CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1)
     219#endif
     220   END SELECT
     221!##############################################################################################################################
     222   END IF
     223!##############################################################################################################################
     224
     225   nqCO2 = COUNT( [type_trac == 'inco', type_trac == 'co2i'] )
    235226
    236227!==============================================================================================================================
    237228! 1) Get the numbers of: true (first order only) tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid)
    238229!==============================================================================================================================
    239    lRepr = ANY(types_trac(:) == 'repr')
     230   texp = type_trac                                                  !=== EXPANDED VERSION OF "type_trac", WITH "|" SEPARATOR
     231   IF(texp == 'inco') texp = 'co2i|inca'
     232   IF(texp /= 'lmdz') texp = 'lmdz|'//TRIM(texp)
     233
     234   !=== DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE
     235   IF(testTracersFiles(modname, texp, fType, lInit)) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
     236   ttp = type_trac; IF(fType /= 1) ttp = texp
     237
    240238!##############################################################################################################################
    241239   IF(lInit) THEN
    242      IF(readTracersFiles(type_trac,  fType,  lRepr)) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
     240      IF(readTracersFiles(ttp, type_trac == 'repr')) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
    243241   ELSE
    244      CALL msg('No tracers description file(s) reading needed: already done in the dynamics', modname)
    245      IF(testTracersFiles(modname, type_trac, fType, .FALSE.)) CALL abort_gcm(modname, 'problem with tracers file(s)',1)
     242      CALL msg('No tracers description file(s) reading needed: already done in the dynamics', modname)
    246243   END IF
    247244!##############################################################################################################################
     
    262259      CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca)
    263260      ALLOCATE(ttr(nqtrue))
    264       ttr(1:nqo+nqCO2)                    = tracers
    265       ttr(1    :      nqo   )%component   = 'lmdz'
    266       ttr(1+nqo:nqCO2+nqo   )%component   = 'co2i'
    267       ttr(1+nqo+nqCO2:nqtrue)%component   = 'inca'
    268       ttr(1+nqo      :nqtrue)%name        = [('CO2     ', k=1, nqCO2), solsym_inca]
    269       ttr(1+nqo+nqCO2:nqtrue)%parent      = tran0
    270       ttr(1+nqo+nqCO2:nqtrue)%phase       = 'g'
     261      ttr(1:nqo+nqCO2)                  = tracers
     262      ttr(1    :      nqo   )%component = 'lmdz'
     263      ttr(1+nqo:nqCO2+nqo   )%component = 'co2i'
     264      ttr(1+nqo+nqCO2:nqtrue)%component = 'inca'
     265      ttr(1+nqo      :nqtrue)%name      = [('CO2     ', k=1, nqCO2), solsym_inca]
     266      ttr(1+nqo+nqCO2:nqtrue)%parent    = tran0
     267      ttr(1+nqo+nqCO2:nqtrue)%phase     = 'g'
    271268      lerr = getKey('hadv', had, ky=tracers(:)%keys)
    272269      lerr = getKey('vadv', vad, ky=tracers(:)%keys)
    273       hadv(1:nqo) = had(:); hadv(nqo+1:nqtrue) = hadv_inca
    274       vadv(1:nqo) = vad(:); vadv(nqo+1:nqtrue) = vadv_inca
     270      hadv(1:nqo+nqCO2) = had(:); hadv(1+nqo+nqCO2:nqtrue) = hadv_inca
     271      vadv(1:nqo+nqCO2) = vad(:); vadv(1+nqo+nqCO2:nqtrue) = vadv_inca
    275272      CALL MOVE_ALLOC(FROM=ttr, TO=tracers)
    276       CALL setGeneration(tracers)                                    !--- SET FIELDS %iGeneration, %gen0Name
     273      IF(setGeneration(tracers)) CALL abort_gcm(modname,'See below',1) !- SET FIELDS %iGeneration, %gen0Name
    277274      DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca)
    278275#endif
     
    424421#endif
    425422#ifdef CPP_StratAer
    426    IF (ANY(types_trac == 'coag')) THEN
     423   IF (type_trac == 'coag') THEN
    427424      nbtr_bin    = COUNT([(tracers(iq)%name(1:3)=='BIN', iq=1, nqtot)])
    428425      nbtr_sulgas = COUNT([(tracers(iq)%name(1:3)=='GAS', iq=1, nqtot)])
  • LMDZ6/trunk/libf/phylmd/phyetat0_mod.F90

    r4370 r4389  
    3232  USE geometry_mod,     ONLY: longitude_deg, latitude_deg
    3333  USE iostart,          ONLY: close_startphy, get_field, get_var, open_startphy
    34   USE infotrac_phy,     ONLY: nqtot, nbtr, type_trac, types_trac, tracers
     34  USE infotrac_phy,     ONLY: nqtot, nbtr, type_trac, tracers
    3535  USE readTracFiles_mod,ONLY: maxlen, new2oldH2O
    3636  USE traclmdz_mod,     ONLY: traclmdz_from_restart
     
    471471
    472472!--OB now this is for co2i - ThL: and therefore also for inco
    473   IF (ANY(types_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN
     473  IF (ANY(type_trac == ['co2i','inco'])) THEN
    474474     IF (carbon_cycle_cpl) THEN
    475475        ALLOCATE(co2_send(klon), stat=ierr)
  • LMDZ6/trunk/libf/phylmd/phyredem.F90

    r4370 r4389  
    3535  USE iostart, ONLY: open_restartphy, close_restartphy, enddef_restartphy, put_field, put_var
    3636  USE traclmdz_mod, ONLY : traclmdz_to_restart
    37   USE infotrac_phy, ONLY: type_trac, types_trac, nqtot, tracers, nbtr
     37  USE infotrac_phy, ONLY: type_trac, nqtot, tracers, nbtr
    3838  USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send, carbon_cycle_rad, RCO2_glo
    3939  USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic, epsfra
     
    329329
    330330
    331     IF (ANY(types_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN
     331    IF (ANY(type_trac == ['co2i','inco'])) THEN
    332332       IF (carbon_cycle_cpl) THEN
    333333          IF (.NOT. ALLOCATED(co2_send)) THEN
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r4370 r4389  
    2525
    2626    USE dimphy, ONLY: klon, klev, klevp1
    27     USE infotrac_phy, ONLY: nbtr, nqtot, nqo, type_trac, types_trac, tracers, niso, ntiso
     27    USE infotrac_phy, ONLY: nbtr, nqtot, nqo, type_trac, tracers, niso, ntiso
    2828    USE strings_mod,  ONLY: maxlen
    2929    USE mod_phys_lmdz_para, ONLY: is_north_pole_phy,is_south_pole_phy
     
    943943       CALL histwrite_phy(o_SWupTOAclr, zx_tmp_fi2d)
    944944
    945        IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
     945       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
    946946          IF (vars_defined) THEN
    947947             zx_tmp_fi2d(:) = swupc0(:,klevp1)*swradcorr(:)
     
    10151015       CALL histwrite_phy(o_SWupSFCclr, zx_tmp_fi2d)
    10161016
    1017        IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
     1017       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
    10181018          IF (vars_defined) THEN
    10191019             zx_tmp_fi2d(:) = swupc0(:,1)*swradcorr(:)
     
    10321032       CALL histwrite_phy(o_SWdnSFCclr, zx_tmp_fi2d)
    10331033
    1034        IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
     1034       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
    10351035          IF (vars_defined) THEN
    10361036             zx_tmp_fi2d(:) = swdnc0(:,1)*swradcorr(:)
     
    10541054       CALL histwrite_phy(o_LWdnSFCclr, sollwdownclr)
    10551055
    1056        IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
     1056       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
    10571057          IF (vars_defined) THEN
    10581058             zx_tmp_fi2d(:) = lwupc0(:,klevp1)
     
    10611061       ENDIF
    10621062
    1063        IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
     1063       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
    10641064          IF (vars_defined) THEN
    10651065             zx_tmp_fi2d(:) = -1.*lwdnc0(:,1)
     
    15701570!This is warranted by treating INCA aerosols as offline aerosols
    15711571       IF (flag_aerosol.GT.0) THEN
    1572           IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
     1572          IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
    15731573
    15741574             CALL histwrite_phy(o_od443aer, od443aer)
     
    16341634
    16351635#ifdef CPP_StratAer
    1636        IF (ANY(types_trac=='coag')) THEN
     1636       IF (type_trac=='coag') THEN
    16371637          CALL histwrite_phy(o_R2SO4, R2SO4)
    16381638          CALL histwrite_phy(o_OCS_lifetime, OCS_lifetime)
     
    16931693          CALL histwrite_phy(o_solswad0, zx_tmp_fi2d)
    16941694         
    1695           IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
     1695          IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
    16961696
    16971697             CALL histwrite_phy(o_toplwad, toplwad_aero)
     
    17701770       ! Champs 3D:
    17711771       IF (ok_ade .OR. ok_aie) then
    1772           IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
     1772          IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
    17731773             CALL histwrite_phy(o_ec550aer, ec550aer)
    17741774          ENDIF
     
    22292229       CALL histwrite_phy(o_rsucs, zx_tmp_fi3d1)
    22302230
    2231        IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
     2231       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
    22322232          IF (vars_defined) THEN
    22332233             DO k=1, klevp1
     
    22452245       CALL histwrite_phy(o_rsdcs, zx_tmp_fi3d1)
    22462246
    2247        IF (ALL(types_trac/='inca') .OR. config_inca=='aeNP') THEN
     2247       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
    22482248          IF (vars_defined) THEN
    22492249             DO k=1, klevp1
     
    24912491       IF (iflag_phytrac == 1 ) then
    24922492!
    2493          IF (ANY(types_trac == 'co2i')) THEN
     2493         IF (type_trac == 'co2i') THEN
    24942494           itr = 0
    24952495           DO iq = 1, nqtot
     
    25202520           CALL histwrite_phy(o_flx_co2_bb,    fco2_bb)
    25212521
    2522          ELSE IF (ANY(types_trac == 'inco')) THEN
     2522         ELSE IF (type_trac == 'inco') THEN
    25232523           itr = 0
    25242524           DO iq = 1, nqtot
     
    25492549           CALL histwrite_phy(o_flx_co2_bb,    fco2_bb)
    25502550
    2551          ELSE IF (ANY(type_trac==['lmdz|coag','lmdz     ','coag     '])) THEN
     2551         ELSE IF (ANY(type_trac==['lmdz','coag'])) THEN
    25522552           itr = 0
    25532553           DO iq = 1, nqtot
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r4386 r4389  
    3939    USE ioipsl_getin_p_mod, ONLY : getin_p
    4040    USE indice_sol_mod
    41     USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, types_trac
     41    USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type_trac
    4242    USE readTracFiles_mod, ONLY: addPhase
    4343    USE strings_mod,  ONLY: strIdx
     
    14661466       tau_overturning_th(:)=0.
    14671467
    1468        IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN
     1468       IF (ANY(type_trac == ['inca','inco'])) THEN
    14691469          ! jg : initialisation jusqu'au ces variables sont dans restart
    14701470          ccm(:,:,:) = 0.
     
    20352035       !c         ENDDO
    20362036       !
    2037        IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL
     2037       IF (ANY(type_trac == ['inca','inco'])) THEN ! ModThL
    20382038#ifdef INCA
    20392039          CALL VTe(VTphysiq)
     
    21172117       ENDIF
    21182118       !
    2119        IF (ANY(types_trac == 'repr')) THEN
     2119       IF (type_trac == 'repr') THEN
    21202120#ifdef REPROBUS
    21212121          CALL chemini_rep(  &
     
    22302230
    22312231    ! Update time and other variables in Reprobus
    2232     IF (ANY(types_trac == 'repr')) THEN
     2232    IF (type_trac == 'repr') THEN
    22332233#ifdef REPROBUS
    22342234       CALL Init_chem_rep_xjour(jD_cur-jD_ref+day_ref)
     
    30213021          !
    30223022          !>jyg
    3023           IF (ANY(types_trac == 'repr')) THEN
     3023          IF (type_trac == 'repr') THEN
    30243024             nbtr_tmp=ntra
    30253025          ELSE
     
    39273927    ENDDO
    39283928
    3929     IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL
     3929    IF (ANY(type_trac == ['inca','inco'])) THEN ! ModThL
    39303930#ifdef INCA
    39313931       CALL VTe(VTphysiq)
     
    39833983#endif
    39843984    ENDIF !type_trac = inca or inco
    3985     IF (ANY(types_trac == 'repr')) THEN
     3985    IF (type_trac == 'repr') THEN
    39863986#ifdef REPROBUS
    39873987    !CALL chemtime_rep(itap+itau_phy-1, date0, dtime, itap)
     
    49534953    !
    49544954
    4955     IF (ANY(types_trac=='repr')) THEN
     4955    IF (type_trac == 'repr') THEN
    49564956!MM pas d'impact, car on recupere q_seri,tr_seri,t_seri via phys_local_var_mod
    49574957!MM                               dans Reprobus
     
    51065106    ENDDO
    51075107    !
    5108     IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN
     5108    IF (ANY(type_trac == ['inca','inco'])) THEN
    51095109#ifdef INCA
    51105110       CALL VTe(VTphysiq)
     
    51305130    ENDIF
    51315131
    5132     IF (ANY(types_trac == 'repr')) THEN
     5132    IF (type_trac == 'repr') THEN
    51335133#ifdef REPROBUS
    51345134        CALL coord_hyb_rep(paprs, pplay, aps, bps, ap, bp, cell_area)
     
    53915391
    53925392#ifdef INCA
    5393        if (ANY(types_trac == 'inca' )) then
     5393       if (type_trac == 'inca') then
    53945394          IF (is_omp_master .and. grid_type==unstructured) THEN
    53955395             CALL finalize_inca
  • LMDZ6/trunk/libf/phylmd/phytrac_mod.F90

    r4298 r4389  
    5656  SUBROUTINE phytrac_init()
    5757    USE dimphy
    58     USE infotrac_phy, ONLY: nbtr, types_trac
     58    USE infotrac_phy, ONLY: nbtr, type_trac
    5959    USE tracco2i_mod, ONLY: tracco2i_init
    6060    IMPLICIT NONE
     
    7979    !===============================================================================
    8080    !   -- CO2 interactif --
    81     IF(ANY(types_trac == 'co2i') .OR. ANY(types_trac == 'inco')) CALL tracco2i_init()
    82 
    83        !   -- types_trac == 'co2i' ! PC
     81    IF(ANY(type_trac == ['co2i','inco'])) CALL tracco2i_init()
     82
     83       !   -- type_trac == 'co2i' ! PC
    8484       !   -- CO2 interactif --
    8585       !   -- source is updated with FF and BB emissions
     
    124124    USE phys_cal_mod, only : hour
    125125    USE dimphy
    126     USE infotrac_phy, ONLY: nbtr, nqCO2, types_trac, type_trac, conv_flg, pbl_flg
     126    USE infotrac_phy, ONLY: nbtr, nqCO2, type_trac, conv_flg, pbl_flg
    127127    USE strings_mod,  ONLY: int2str
    128128    USE mod_grid_phy_lmdz
     
    491491
    492492       ! Initialize module for specific tracers
    493        IF(ANY(types_trac == 'inca')) THEN
     493       IF(type_trac == 'inca') THEN
    494494          source(:,:)=init_source(:,:)
    495495          CALL tracinca_init(aerosol,lessivage)
    496        ELSE IF(ANY(types_trac == 'repr')) THEN
     496       ELSE IF(type_trac == 'repr') THEN
    497497          source(:,:)=0.
    498        ELSE IF(ANY(types_trac == 'co2i')) THEN
     498       ELSE IF(type_trac == 'co2i') THEN
    499499          source(:,:)=0.
    500500          lessivage  = .FALSE.
     
    504504          iflag_vdf_trac= 1
    505505          iflag_con_trac= 1
    506        ELSE IF(ANY(types_trac == 'inco')) THEN
     506       ELSE IF(type_trac == 'inco') THEN
    507507          source(:,1:nqCO2) = 0.                          ! from CO2i ModThL
    508508          source(:,nqCO2+1:nbtr)=init_source(:,:)         ! from INCA ModThL
     
    514514          iflag_con_trac = 1                              ! From CO2i
    515515#ifdef CPP_StratAer
    516        ELSE IF(ANY(types_trac == 'coag')) THEN
     516       ELSE IF(type_trac == 'coag') THEN
    517517          source(:,:)=0.
    518518          DO it= 1, nbtr_sulgas
     
    524524          ENDDO
    525525#endif
    526        ELSE IF(ANY(types_trac == 'lmdz')) THEN
     526       ELSE IF(type_trac == 'lmdz') THEN
    527527          CALL traclmdz_init(pctsrf,xlat,xlon,ftsol,tr_seri,t_seri,pplay,sh,pdtphys,aerosol,lessivage)
    528528       END IF
     
    539539          !
    540540          DO it=1, nbtr
    541              IF(ANY(types_trac == 'repr')) THEN
     541             IF(type_trac == 'repr') THEN
    542542                 flag_cvltr(it)=.FALSE.
    543              ELSE IF(ANY(types_trac == 'inca')) THEN
     543             ELSE IF(type_trac == 'inca') THEN
    544544!                IF ((it.EQ.id_Rn222) .OR. ((it.GE.id_SO2) .AND. (it.LE.id_NH3)) ) THEN
    545545!                   !--gas-phase species
     
    565565                !--for now we do not scavenge in cvltr
    566566                flag_cvltr(it)=.FALSE.
    567              ELSE IF(ANY(types_trac == 'co2i')) THEN
     567             ELSE IF(type_trac == 'co2i') THEN
    568568                !--co2 tracers are not scavenged
    569569                flag_cvltr(it)=.FALSE.
    570              ELSE IF(ANY(types_trac == 'inco')) THEN     ! Add ThL
     570             ELSE IF(type_trac == 'inco') THEN     ! Add ThL
    571571                flag_cvltr(it)=.FALSE.
    572572#ifdef CPP_StratAer
    573              ELSE IF(ANY(types_trac == 'coag')) THEN
     573             ELSE IF(type_trac == 'coag') THEN
    574574                IF (convscav.and.aerosol(it)) THEN
    575575                   flag_cvltr(it)=.TRUE.
     
    581581                ENDIF
    582582#endif
    583              ELSE IF(ANY(types_trac == 'lmdz')) THEN
     583             ELSE IF(type_trac == 'lmdz') THEN
    584584                IF (convscav.and.aerosol(it)) THEN
    585585                   flag_cvltr(it)=.TRUE.
     
    614614       write(lunout,*)  'flag_cvltr    = ', flag_cvltr
    615615
    616        IF (lessivage .AND. (ANY(types_trac == 'inca') .OR. ANY(types_trac=='inco'))) THEN     ! Mod ThL
     616       IF (lessivage .AND. ANY(type_trac == ['inca','inco'])) &
    617617          CALL abort_physic('phytrac', 'lessivage=T config_inca=inca impossible',1)
    618 !          STOP
    619        ENDIF
    620618       !
    621619    ENDIF ! of IF (debutphy)
     
    640638    !     
    641639    !===============================================================================
    642     IF(ANY(types_trac == 'inca')) THEN
     640    IF(type_trac == 'inca') THEN
    643641       !    -- CHIMIE INCA  config_inca = aero or chem --
    644642       ! Appel fait en fin de phytrac pour avoir les emissions modifiees par
    645643       ! la couche limite et la convection avant le calcul de la chimie
    646644
    647     ELSE IF(ANY(types_trac == 'repr')) THEN
     645    ELSE IF(type_trac == 'repr') THEN
    648646       !   -- CHIMIE REPROBUS --
    649647       CALL tracreprobus(pdtphys, gmtime, debutphy, julien, &
     
    652650            tr_seri)
    653651
    654     ELSE IF(ANY(types_trac == 'co2i')) THEN
     652    ELSE IF(type_trac == 'co2i') THEN
    655653       !   -- CO2 interactif --
    656654       !   -- source is updated with FF and BB emissions
     
    661659            xlat, xlon, pphis, pphi, &
    662660            t_seri, pplay, paprs, tr_seri, source)
    663     ELSE IF(ANY(types_trac == 'inco')) THEN      ! Add ThL
     661    ELSE IF(type_trac == 'inco') THEN      ! Add ThL
    664662       CALL tracco2i(pdtphys, debutphy, &
    665663            xlat, xlon, pphis, pphi, &
     
    667665
    668666#ifdef CPP_StratAer
    669     ELSE IF(ANY(types_trac == 'coag')) THEN
     667    ELSE IF(type_trac == 'coag') THEN
    670668       !   --STRATOSPHERIC AER IN THE STRAT --
    671669       CALL traccoag(pdtphys, gmtime, debutphy, julien, &
     
    674672            tr_seri)
    675673#endif
    676     ELSE IF(ANY(types_trac == 'lmdz')) THEN
     674    ELSE IF(type_trac == 'lmdz') THEN
    677675       !    -- Traitement des traceurs avec traclmdz
    678676       CALL traclmdz(nstep, julien, gmtime, pdtphys, t_seri, paprs, pplay, &
     
    748746
    749747#ifdef CPP_StratAer
    750        IF (ANY(types_trac=='coag')) THEN
     748       IF (type_trac=='coag') THEN
    751749         ! initialize wet deposition flux of sulfur
    752750         budg_dep_wet_ocs(:)=0.0
     
    829827       !
    830828#ifdef CPP_StratAer
    831        IF (ANY(types_trac=='coag')) THEN
     829       IF (type_trac=='coag') THEN
    832830
    833831         ! initialize dry deposition flux of sulfur
     
    866864             !
    867865#ifdef CPP_StratAer
    868              IF (ANY(types_trac=='coag')) THEN
     866             IF (type_trac=='coag') THEN
    869867               ! compute dry deposition flux of sulfur (sum over gases and particles)
    870868               IF (it==id_OCS_strat) THEN
     
    951949
    952950#ifdef CPP_StratAer
    953          IF (ANY(types_trac=='coag')) THEN
     951         IF (type_trac=='coag') THEN
    954952           ! compute wet deposition flux of sulfur (sum over gases and
    955953           ! particles) and convert to kg(S)/m2/s
     
    10911089
    10921090    !    -- CHIMIE INCA  config_inca = aero or chem --
    1093     IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN  ! ModThL
     1091    IF (ANY(type_trac == ['inca','inco'])) THEN  ! ModThL
    10941092
    10951093       CALL tracinca(&
  • LMDZ6/trunk/libf/phylmd/radiation_AR4.F90

    r4170 r4389  
    479479  USE dimphy
    480480  USE radiation_ar4_param, ONLY: rsun, rray
    481   USE infotrac_phy, ONLY: types_trac
     481  USE infotrac_phy, ONLY: type_trac
    482482#ifdef REPROBUS
    483483  USE chem_rep, ONLY: rsuntime, ok_suntime
     
    571571  ! If running with Reporbus, overwrite default values of RSUN.
    572572  ! Otherwise keep default values from radiation_AR4_param module.
    573   IF (ANY(types_trac=='repr')) THEN
     573  IF (type_trac=='repr') THEN
    574574#ifdef REPROBUS
    575575    IF (ok_suntime) THEN
     
    701701  USE dimphy
    702702  USE radiation_ar4_param, ONLY: rsun, rray
    703   USE infotrac_phy, ONLY: types_trac
     703  USE infotrac_phy, ONLY: type_trac
    704704#ifdef REPROBUS
    705705  USE chem_rep, ONLY: rsuntime, ok_suntime
     
    825825  ! If running with Reporbus, overwrite default values of RSUN.
    826826  ! Otherwise keep default values from radiation_AR4_param module.
    827   IF (ANY(types_trac=='repr')) THEN
     827  IF (type_trac=='repr') THEN
    828828#ifdef REPROBUS
    829829    IF (ok_suntime) THEN
     
    23132313  USE dimphy
    23142314  USE radiation_ar4_param, ONLY: tref, rt1, raer, at, bt, oct
    2315   USE infotrac_phy, ONLY: types_trac
     2315  USE infotrac_phy, ONLY: type_trac
    23162316#ifdef REPROBUS
    23172317  USE chem_rep, ONLY: rch42d, rn2o2d, rcfc112d, rcfc122d, ok_rtime2d
     
    26212621
    26222622
    2623         IF (ANY(types_trac=='repr')) THEN
     2623        IF (type_trac=='repr') THEN
    26242624#ifdef REPROBUS
    26252625          IF (ok_rtime2d) THEN
  • LMDZ6/trunk/libf/phylmd/radlwsw_m.F90

    r4170 r4389  
    4848  USE DIMPHY
    4949  USE assert_m, ONLY : assert
    50   USE infotrac_phy, ONLY : types_trac
     50  USE infotrac_phy, ONLY : type_trac
    5151  USE write_field_phy
    5252
     
    550550  PSCT = solaire/zdist/zdist
    551551
    552   IF (ANY(types_trac == 'repr')) THEN
     552  IF (type_trac == 'repr') THEN
    553553#ifdef REPROBUS
    554554    IF (iflag_rrtm==0) THEN
     
    634634    ENDDO
    635635
    636     IF (ANY(types_trac == 'repr')) THEN
     636    IF (type_trac == 'repr') THEN
    637637#ifdef REPROBUS
    638638       ndimozon = size(wo, 3)
  • LMDZ6/trunk/libf/phylmd/rrtm/lwu.F90

    r4241 r4389  
    7676#ifdef REPROBUS
    7777USE chem_rep, ONLY: rch42d, rn2o2d, rcfc112d, rcfc122d, ok_rtime2d
    78 USE infotrac_phy, ONLY : types_trac
     78USE infotrac_phy, ONLY : type_trac
    7979#endif
    8080
     
    321321      PABCU(JL,18,IC)=PABCU(JL,18,ICP1)+ ZUAER(JL,5)    *ZDUC(JL,IC)*ZDIFF
    322322#ifdef REPROBUS
    323         IF (ANY(types_trac=='repr').and. ok_rtime2d) THEN
     323        IF (type_trac=='repr'.and. ok_rtime2d) THEN
    324324!- CH4
    325325      PABCU(JL,19,IC)=PABCU(JL,19,ICP1)&
  • LMDZ6/trunk/libf/phylmd/tracinca_mod.F90

    r4358 r4389  
    1818    ! This subroutine initialize some control varaibles.
    1919
    20     USE infotrac_phy, ONLY: nbtr, types_trac
     20    USE infotrac_phy, ONLY: nbtr, type_trac
    2121    IMPLICIT NONE
    2222   
     
    3030
    3131    !--- COHERENCE TEST BETWEEN "type_trac" AND "config_inca"
    32     IF((ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) .AND. ALL(config_inca /= ['aero', 'aeNP', 'chem']))&
    33        CALL abort_gcm('tracinca_init', 'INCA enabled, but unknown config_inca = "'//TRIM(config_inca)//'".'          &
    34                              //'Please modify "run.def"', 1)
     32    IF(ANY(type_trac == ['inca','inco']) .AND. ALL(config_inca /= ['aero','aeNP','chem'])) CALL abort_gcm('tracinca_init', &
     33       'INCA enabled, but unknown config_inca = "'//TRIM(config_inca)//'". Please modify "run.def"', 1)
    3534
    3635    !--- PROBLEM IF "config_inca" DIFFERS FROM "none" AND INCA HAS NOT BEEN ACTIVATED
    37     IF(ALL(types_trac /= 'inca') .AND. ALL(types_trac /= 'inco')  .AND.     config_inca /= 'none') &
    38        CALL abort_gcm('tracinca_init', 'INCA disabled, but config_inca = "'//TRIM(config_inca)//'" should be "none".'&
    39                              //'Please modify "run.def"', 1)
     36    IF(ALL(type_trac /= ['inca','inco'])  .AND.    config_inca /= 'none')                  CALL abort_gcm('tracinca_init', &
     37       'INCA disabled, but config_inca = "'//TRIM(config_inca)//'" should be "none". Please modify "run.def"', 1)
    4038
    4139  END SUBROUTINE tracinca_init
  • LMDZ6/trunk/libf/phylmd/traclmdz_mod.F90

    r4325 r4389  
    203203             tr_seri(:,:,id_pb) = plomb(:,:)
    204204           ELSE
    205              WRITE(lunout,*)'Prof. Pb210 does not exist: use restart values'
     205             WRITE(lunout,*)'prof.pb210 does not exist: use restart values'
    206206           END IF
    207207         CASE("aga")
  • LMDZ6/trunk/libf/phylmdiso/phyetat0_mod.F90

    r4384 r4389  
    4040  USE geometry_mod,     ONLY: longitude_deg, latitude_deg
    4141  USE iostart,          ONLY: close_startphy, get_field, get_var, open_startphy
    42   USE infotrac_phy,     ONLY: nqtot, nbtr, type_trac, types_trac, tracers
     42  USE infotrac_phy,     ONLY: nqtot, nbtr, type_trac, tracers
    4343  USE readTracFiles_mod,ONLY: maxlen, new2oldH2O
    4444  USE traclmdz_mod,     ONLY: traclmdz_from_restart
     
    492492
    493493!--OB now this is for co2i - ThL: and therefore also for inco
    494   IF (ANY(types_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN
     494  IF (ANY(type_trac == ['co2i','inco'])) THEN
    495495     IF (carbon_cycle_cpl) THEN
    496496        ALLOCATE(co2_send(klon), stat=ierr)
  • LMDZ6/trunk/libf/phylmdiso/phyredem.F90

    r4374 r4389  
    3939  USE iostart, ONLY: open_restartphy, close_restartphy, enddef_restartphy, put_field, put_var
    4040  USE traclmdz_mod, ONLY : traclmdz_to_restart
    41   USE infotrac_phy, ONLY: types_trac, nqtot, tracers, nbtr, niso
     41  USE infotrac_phy, ONLY: type_trac, nqtot, tracers, nbtr, niso
    4242#ifdef ISO
    4343#ifdef ISOVERIF
     
    176176    CALL put_field(pass,"FSIC", "fraction glace mer", pctsrf(:, is_sic))
    177177
    178     IF(nbsrf>99) THEN
    179       PRINT*, "Trop de sous-mailles";  CALL abort_physic("phyredem", "", 1)
    180     END IF
    181     IF(nsoilmx>99) THEN
    182       PRINT*, "Trop de sous-surfaces"; CALL abort_physic("phyredem", "", 1)
    183     END IF
    184     IF(nsw>99) THEN
    185       PRINT*, "Trop de bandes"; CALL abort_physic("phyredem", "", 1)
    186     END IF
     178    IF(nbsrf  >99) CALL abort_physic("phyredem", "Trop de sous-mailles", 1)
     179    IF(nsoilmx>99) CALL abort_physic("phyredem", "Trop de sous-mailles", 1)
     180    IF(nsw    >99) CALL abort_physic("phyredem", "Trop de bandes", 1)
    187181
    188182!    Surface variables
     
    350344
    351345
    352     IF (ANY(types_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN
     346    IF (ANY(type_trac == ['co2i','inco'])) THEN
    353347       IF (carbon_cycle_cpl) THEN
    354348          IF (.NOT. ALLOCATED(co2_send)) THEN
     
    361355
    362356    ! trs from traclmdz_mod
    363     ELSE IF (ANY(types_trac == 'lmdz')) THEN
     357    ELSE IF (type_trac == 'lmdz') THEN
    364358       CALL traclmdz_to_restart(trs)
    365359       it = 0
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r4386 r4389  
    3939    USE ioipsl_getin_p_mod, ONLY : getin_p
    4040    USE indice_sol_mod
    41     USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, types_trac
     41    USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type_trac
    4242    USE readTracFiles_mod, ONLY: addPhase
    4343    USE strings_mod,  ONLY: strIdx
     
    15701570       tau_overturning_th(:)=0.
    15711571
    1572        IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN
     1572       IF (ANY(type_trac == ['inca','inco'])) THEN
    15731573          ! jg : initialisation jusqu'au ces variables sont dans restart
    15741574          ccm(:,:,:) = 0.
     
    21872187       !c         ENDDO
    21882188       !
    2189        IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL
     2189       IF (ANY(type_trac == ['inca','inco'])) THEN ! ModThL
    21902190#ifdef INCA
    21912191          CALL VTe(VTphysiq)
     
    22692269       ENDIF
    22702270       !
    2271        IF (ANY(types_trac == 'repr')) THEN
     2271       IF (type_trac == 'repr') THEN
    22722272#ifdef REPROBUS
    22732273          CALL chemini_rep(  &
     
    23862386
    23872387    ! Update time and other variables in Reprobus
    2388     IF (ANY(types_trac == 'repr')) THEN
     2388    IF (type_trac == 'repr') THEN
    23892389#ifdef REPROBUS
    23902390       CALL Init_chem_rep_xjour(jD_cur-jD_ref+day_ref)
     
    36543654          !
    36553655          !>jyg
    3656           IF (ANY(types_trac == 'repr')) THEN
     3656          IF (type_trac == 'repr') THEN
    36573657             nbtr_tmp=ntra
    36583658          ELSE
     
    51915191    ENDDO
    51925192
    5193     IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL
     5193    IF (ANY(type_trac == ['inca','inco'])) THEN ! ModThL
    51945194#ifdef INCA
    51955195       CALL VTe(VTphysiq)
     
    52475247#endif
    52485248    ENDIF !type_trac = inca or inco
    5249     IF (ANY(types_trac == 'repr')) THEN
     5249    IF (type_trac == 'repr') THEN
    52505250#ifdef REPROBUS
    52515251    !CALL chemtime_rep(itap+itau_phy-1, date0, dtime, itap)
     
    63366336    !
    63376337
    6338     IF (ANY(types_trac=='repr')) THEN
     6338    IF (type_trac=='repr') THEN
    63396339!MM pas d'impact, car on recupere q_seri,tr_seri,t_seri via phys_local_var_mod
    63406340!MM                               dans Reprobus
     
    65016501#endif
    65026502    !
    6503     IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN
     6503    IF (ANY(type_trac == ['inca','inco'])) THEN
    65046504#ifdef INCA
    65056505       CALL VTe(VTphysiq)
     
    65256525    ENDIF
    65266526
    6527     IF (ANY(types_trac == 'repr')) THEN
     6527    IF (type_trac == 'repr') THEN
    65286528#ifdef REPROBUS
    65296529        CALL coord_hyb_rep(paprs, pplay, aps, bps, ap, bp, cell_area)
     
    69016901
    69026902#ifdef INCA
    6903        if (ANY(types_trac == 'inca' )) then
     6903       if (type_trac == 'inca') then
    69046904          IF (is_omp_master .and. grid_type==unstructured) THEN
    69056905             CALL finalize_inca
Note: See TracChangeset for help on using the changeset viewer.