Ignore:
Timestamp:
Jan 23, 2023, 11:28:51 AM (20 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.
File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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
Note: See TracChangeset for help on using the changeset viewer.