Changeset 5221 for LMDZ6/branches


Ignore:
Timestamp:
Sep 23, 2024, 4:12:29 PM (4 weeks ago)
Author:
abarral
Message:

Merge r5196, r5199
Nb: skipping r5197 r5198 as they revert one-another

Location:
LMDZ6/branches/Amaury_dev
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev

  • LMDZ6/branches/Amaury_dev/libf/dyn3d/iniacademic.F90

    r5186 r5221  
    44
    55  USE lmdz_filtreg, ONLY: inifilr
    6   USE lmdz_infotrac, ONLY: nqtot, niso, iqIsoPha, tracers, getKey, isoName
     6  USE lmdz_infotrac, ONLY: nqtot, niso, iqIsoPha, tracers, getKey, isoName, addPhase
    77  USE control_mod, ONLY: day_step, planet_type
    88  USE exner_hyb_m, ONLY: exner_hyb
     
    1515  USE temps_mod, ONLY: annee_ref, day_ini, day_ref
    1616  USE ener_mod, ONLY: etot0, ptot0, ztot0, stot0, ang0
    17   USE lmdz_readTracFiles, ONLY: addPhase
    1817  USE netcdf, ONLY: nf90_nowrite, nf90_open, nf90_noerr, nf90_inq_varid, nf90_close, nf90_get_var
    1918  USE lmdz_ran1, ONLY: ran1
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/lmdz_infotrac.f90

    r5185 r5221  
    55          delPhase, niso, getKey, isot_type, processIsotopes, isotope, maxTableWidth, iqIsoPha, nphas, ixIso, isoPhas, &
    66          addPhase, iH2O, addKey, isoSelect, testTracersFiles, isoKeys, indexUpdate, iqWIsoPha, nbIso, ntiso, isoName, isoCheck
    7 
    8 
    9   IMPLICIT NONE
    10 
    11   PRIVATE
     7  USE lmdz_readTracFiles, ONLY: new2oldH2O, newHNO3, oldHNO3
     8
     9  IMPLICIT NONE; PRIVATE
    1210
    1311  !=== FOR TRACERS:
     
    1614  PUBLIC :: nqtot, nbtr, nqo, nqCO2, nqtottr      !--- Main dimensions
    1715  PUBLIC :: conv_flg, pbl_flg                             !--- Convection & boundary layer activation keys
     16  PUBLIC :: new2oldH2O, newHNO3, oldHNO3                  !--- For backwards compatibility in dynetat0
     17  PUBLIC :: addPhase, delPhase                            !--- Add/remove the phase from the name of a tracer
     18
    1819
    1920  !=== FOR ISOTOPES: General
     
    2122  PUBLIC :: isoSelect, ixIso                              !--- Isotopes family selection tool + selected family index
    2223  !=== FOR ISOTOPES: Specific to water
    23   PUBLIC :: iH2O                                          !--- H2O isotopes class index
     24  PUBLIC :: iH2O                                          !--- Value of "ixIso" for "H2O" isotopes class
    2425  PUBLIC :: min_qParent, min_qMass, min_ratio             !--- Min. values for various isotopic quantities
    2526  !=== FOR ISOTOPES: Depending on the selected isotopes family
    26   PUBLIC :: isotope, isoKeys                              !--- Selected isotopes database + associated keys (cf. getKey)
    27   PUBLIC :: isoName, isoZone, isoPhas                     !--- Isotopes and tagging zones names, phases
    28   PUBLIC :: niso, nzone, nphas, ntiso              !---  " " numbers + isotopes & tagging tracers number
    29   PUBLIC :: itZonIso                                      !--- idx "it" (in "isoName(1:niso)") = function(tagging idx, isotope idx)
    30   PUBLIC :: iqIsoPha                                      !--- idx "iq" (in "qx") = function(isotope idx, phase idx) + aliases
     27  PUBLIC :: isotope                                       !--- Selected isotopes database (argument of getKey)
     28  PUBLIC :: isoKeys, isoName, isoZone, isoPhas            !--- Isotopes keys & names, tagging zones names, phases
     29  PUBLIC :: niso, ntiso, nzone, nphas            !--- Number of   "   "
     30  PUBLIC :: itZonIso                                      !--- index "it" in "isoName(1:niso)" = f(tagging idx, isotope idx)
     31  PUBLIC :: iqIsoPha                                      !--- index "iq" in "qx"              = f(isotope idx,   phase idx)
    3132  PUBLIC :: isoCheck                                      !--- Run isotopes checking routines
    3233  !=== FOR BOTH TRACERS AND ISOTOPES
     
    3637  !  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    3738  !  | water in different |    water tagging      |  water isotopes | other tracers | additional tracers moments |
    38   !  | phases: H2O_[gls|      isotopes         |                 |               |  for higher order schemes  |
     39  !  | phases: H2O_[glsrb]|      isotopes         |                 |               |  for higher order schemes  |
    3940  !  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    4041  !  |                    |                       |                 |               |                            |
     
    6162  !  |-------------+------------------------------------------------------+-------------+------------------------+
    6263  !  | name        | Name (short)                                         | tname       |                        |
     64  !  | keys        | key/val pairs accessible with "getKey" routine       | /           |                        |
    6365  !  | gen0Name    | Name of the 1st generation ancestor                  | /           |                        |
    6466  !  | parent      | Name of the parent                                   | /           |                        |
    6567  !  | longName    | Long name (with adv. scheme suffix) for outputs      | ttext       |                        |
    6668  !  | type        | Type (so far: tracer or tag)                         | /           | tracer,tag             |
    67   !  | phase       | Phases list ("g"as / "l"iquid / "s"olid)             | /           | [g][l][s]              |
     69  !  | phase       | Phases list ("g"as / "l"iquid / "s"olid              |             | [g|l|s|r|b]            |
     70  !  |             |              "r"(cloud) / "b"lowing)                 | /           |                        |
    6871  !  | component   | Name(s) of the merged/cumulated section(s)           | /           | coma-separated names   |
    6972  !  | iGeneration | Generation (>=1)                                     | /           |                        |
     
    7477  !  | keys        | key/val pairs accessible with "getKey" routine       | /           |                        |
    7578  !  | iadv        | Advection scheme number                              | iadv        | 1,2,10-20(exc.15,19),30|
    76   !  | isAdvected  | advected tracers flag (.TRUE. if iadv >= 0)          | /           | nqtrue  .TRUE. values  |
    77   !  | isInPhysics | tracers not extracted from the main table in physics | /           | nqtottr .TRUE. values  |
     79  !  | isAdvected  | Advected tracers flag (.TRUE. if iadv >= 0)          | /           | nqtrue  .TRUE. values  |
     80  !  | isInPhysics | Tracers not extracted from the main table in physics | /           | nqtottr .TRUE. values  |
    7881  !  | iso_iGroup  | Isotopes group index in isotopes(:)                  | /           | 1:nbIso                |
    7982  !  | iso_iName   | Isotope  name  index in isotopes(iso_iGroup)%trac(:) | iso_indnum  | 1:niso                 |
     
    9194  !  | trac   | ntiso  | Isotopes + tagging tracers list + number         | / | ntraciso       |                 |
    9295  !  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
    93   !  | phase  | nphas  | Phases                     list + number         |                    | [g][l][s], 1:3 |
     96  !  | phase  | nphas  | Phases                     list + number         |                    | [g|l|s|r|b] 1:5 |
    9497  !  | iqIsoPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
    9598  !  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
     
    104107          nqtottr, &                    !--- Number of tracers passed to phytrac (TO BE DELETED ?)
    105108          nqCO2                         !--- Number of tracers of CO2  (ThL)
    106   CHARACTER(LEN = maxlen), SAVE :: type_trac                     !--- Keyword for tracers type
     109  CHARACTER(LEN = maxlen), SAVE :: type_trac                     !--- Keyword for tracers type(s)
    107110
    108111  !=== VARIABLES FOR INCA
    109   INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), &   !--- Convection     activation ; needed for INCA        (nbtr)
    110           pbl_flg(:)      !--- Boundary layer activation ; needed for INCA        (nbtr)
     112  INTEGER, DIMENSION(:), SAVE, ALLOCATABLE :: &
     113          conv_flg, pbl_flg                           !--- Convection / boundary layer activation (nbtr)
    111114
    112115CONTAINS
     
    159162    TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
    160163    TYPE(trac_type), POINTER :: t1, t(:)
    161     CHARACTER(LEN = maxlen), ALLOCATABLE :: types_trac(:)  !--- Keyword for tracers type(s), parsed version
    162 
     164    CHARACTER(LEN = maxlen), ALLOCATABLE :: types_trac(:)             !--- Keywords for tracers type(s), parsed version
    163165    CHARACTER(LEN = *), PARAMETER :: modname = "init_infotrac"
    164166    !------------------------------------------------------------------------------------------------------------------------------
     
    171173    descrq(30) = 'PRA'
    172174
    173     CALL msg('type_trac = "' // TRIM(type_trac) // '"', modname)
    174 
    175175    lerr = strParse(type_trac, '|', types_trac, n = nt)
    176176    IF (nt > 1) THEN
     
    179179    ENDIF
    180180
    181 
     181    CALL msg('type_trac = "' // TRIM(type_trac) // '"', modname)
    182182
    183183    !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
     
    212212
    213213    !==============================================================================================================================
    214     ! 1) Get the numbers of: true (first order only) tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid)
    215     !==============================================================================================================================
    216     texp = type_trac                                                  !=== EXPANDED VERSION OF "type_trac", WITH "|" SEPARATOR
     214    ! 0) DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE AND READ IT
     215    !==============================================================================================================================
     216    texp = type_trac                                                  !=== EXPANDED (WITH "|" SEPARATOR) "type_trac"
    217217    IF(texp == 'inco') texp = 'co2i|inca'
    218218    IF(texp /= 'lmdz') texp = 'lmdz|' // TRIM(texp)
    219 
    220     !=== DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE
    221219    IF(testTracersFiles(modname, texp, fType, .TRUE.)) CALL abort_gcm(modname, 'problem with tracers file(s)', 1)
    222220    ttp = type_trac; IF(fType /= 1) ttp = texp
    223 
    224221    IF(readTracersFiles(ttp, lRepr = type_trac=='repr')) CALL abort_gcm(modname, 'problem with tracers file(s)', 1)
     222    !==============================================================================================================================
     223    ! 1) Get various numbers: "nqtrue" (first order only tracers), "nqo" (water phases), 'nbtr' (tracers passed to physics), etc.
     224    !==============================================================================================================================
     225
    225226    !---------------------------------------------------------------------------------------------------------------------------
    226     IF(fType == 0) CALL abort_gcm(modname, 'Missing tracers file: "traceur.def", "tracer.def" or "tracer_<keyword>.def file.', 1)
     227    IF(fType == 0) CALL abort_gcm(modname, 'Missing "traceur.def", "tracer.def" or "tracer_<keyword>.def tracers file.', 1)
    227228    !---------------------------------------------------------------------------------------------------------------------------
    228229    IF(fType == 1 .AND. ANY(['inca', 'inco']==type_trac)) THEN         !=== FOUND OLD STYLE INCA "traceur.def"
    229230      !---------------------------------------------------------------------------------------------------------------------------
    230       nqo = SIZE(tracers) - nqCO2
    231       CALL init_chem_inca_trac(nqINCA)                               !--- Get nqINCA from INCA
    232       nbtr = nqINCA + nqCO2                                          !--- Number of tracers passed to phytrac
    233       nqtrue = nbtr + nqo                                            !--- Total number of "true" tracers
    234       IF(ALL([2, 3] /= nqo)) CALL abort_gcm(modname, 'Only 2 or 3 water phases allowed ; found nqo=' // TRIM(int2str(nqo)), 1)
    235       ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA))
    236       ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA), pbl_flg_inca(nqINCA))
    237       CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca)
    238       ALLOCATE(ttr(nqtrue))
    239       ttr(1:nqo + nqCO2) = tracers
    240       ttr(1:nqo)%component = 'lmdz'
    241       ttr(1 + nqo:nqCO2 + nqo)%component = 'co2i'
    242       ttr(1 + nqo + nqCO2:nqtrue)%component = 'inca'
    243       ttr(1 + nqo:nqtrue)%name = [('CO2     ', iq = 1, nqCO2), solsym_inca]
    244       ttr(1 + nqo + nqCO2:nqtrue)%parent = tran0
    245       ttr(1 + nqo + nqCO2:nqtrue)%phase = 'g'
    246       lerr = getKey('hadv', had, ky = tracers(:)%keys)
    247       lerr = getKey('vadv', vad, ky = tracers(:)%keys)
    248       hadv(1:nqo + nqCO2) = had(:); hadv(1 + nqo + nqCO2:nqtrue) = hadv_inca
    249       vadv(1:nqo + nqCO2) = vad(:); vadv(1 + nqo + nqCO2:nqtrue) = vadv_inca
    250       CALL MOVE_ALLOC(FROM = ttr, TO = tracers)
    251       DO iq = 1, nqtrue
    252         t1 => tracers(iq)
    253         CALL addKey('name', t1%name, t1%keys)
    254         CALL addKey('component', t1%component, t1%keys)
    255         CALL addKey('parent', t1%parent, t1%keys)
    256         CALL addKey('phase', t1%phase, t1%keys)
    257       END DO
    258       IF(setGeneration(tracers)) CALL abort_gcm(modname, 'See above', 1) !- SET FIELDS %iGeneration, %gen0Name
    259       DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca)
    260       !---------------------------------------------------------------------------------------------------------------------------
     231      IF (CPPKEY_INCA) THEN
     232        nqo = SIZE(tracers) - nqCO2
     233        CALL init_chem_inca_trac(nqINCA)                               !--- Get nqINCA from INCA
     234        nbtr = nqINCA + nqCO2                                          !--- Number of tracers passed to phytrac
     235        nqtrue = nbtr + nqo                                            !--- Total number of "true" tracers
     236        IF(ALL([2, 3] /= nqo)) CALL abort_gcm(modname, 'Only 2 or 3 water phases allowed ; found nqo=' // TRIM(int2str(nqo)), 1)
     237        ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA))
     238        ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA), pbl_flg_inca(nqINCA))
     239        CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca)
     240        ALLOCATE(ttr(nqtrue))
     241        ttr(1:nqo + nqCO2) = tracers
     242        ttr(1:nqo)%component = 'lmdz'
     243        ttr(1 + nqo:nqCO2 + nqo)%component = 'co2i'
     244        ttr(1 + nqo + nqCO2:nqtrue)%component = 'inca'
     245        ttr(1 + nqo:nqtrue)%name = [('CO2     ', iq = 1, nqCO2), solsym_inca]
     246        ttr(1 + nqo + nqCO2:nqtrue)%parent = tran0
     247        ttr(1 + nqo + nqCO2:nqtrue)%phase = 'g'
     248        lerr = getKey('hadv', had, ky = tracers(:)%keys)
     249        lerr = getKey('vadv', vad, ky = tracers(:)%keys)
     250        hadv(1:nqo + nqCO2) = had(:); hadv(1 + nqo + nqCO2:nqtrue) = hadv_inca
     251        vadv(1:nqo + nqCO2) = vad(:); vadv(1 + nqo + nqCO2:nqtrue) = vadv_inca
     252        CALL MOVE_ALLOC(FROM = ttr, TO = tracers)
     253        DO iq = 1, nqtrue
     254          t1 => tracers(iq)
     255          CALL addKey('name', t1%name, t1%keys)
     256          CALL addKey('component', t1%component, t1%keys)
     257          CALL addKey('parent', t1%parent, t1%keys)
     258          CALL addKey('phase', t1%phase, t1%keys)
     259        END DO
     260        IF(setGeneration(tracers)) CALL abort_gcm(modname, 'See above', 1) !- SET FIELDS %iGeneration, %gen0Name
     261        DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca)
     262        !---------------------------------------------------------------------------------------------------------------------------
     263      END IF
    261264    ELSE                                                              !=== OTHER CASES (OLD OR NEW FORMAT, NO INCA MODULE)
    262265      !---------------------------------------------------------------------------------------------------------------------------
    263       nqo = COUNT(delPhase(tracers(:)%name)     == 'H2O' &
    264               .AND. tracers(:)%component == 'lmdz') !--- Number of water phases
    265       nqtrue = SIZE(tracers)                                         !--- Total number of "true" tracers
    266       nbtr = nqtrue - COUNT(delPhase(tracers(:)%gen0Name) == 'H2O' &
    267               .AND. tracers(:)%component == 'lmdz') !--- Number of tracers passed to phytrac
    268       nqINCA = COUNT(tracers(:)%component == 'inca')
    269       lerr = getKey('hadv', hadv, ky = tracers(:)%keys)
    270       lerr = getKey('vadv', vadv, ky = tracers(:)%keys)
     266      nqtrue = SIZE(tracers)                                                                               !--- "true" tracers
     267      nqo = COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%name)     == 'H2O')     !--- Water phases
     268      nbtr = nqtrue - COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%gen0Name) == 'H2O')     !--- Passed to phytrac
     269      nqCO2 = COUNT([type_trac == 'inco', type_trac == 'co2i'])
     270      IF (CPPKEY_INCA) THEN
     271        nqINCA = COUNT(tracers(:)%component == 'inca')
     272      END IF
     273      IF(getKey('hadv', hadv, ky = tracers(:)%keys)) CALL abort_gcm(modname, 'missing key "hadv"', 1)
     274      IF(getKey('vadv', vadv, ky = tracers(:)%keys)) CALL abort_gcm(modname, 'missing key "vadv"', 1)
    271275      !---------------------------------------------------------------------------------------------------------------------------
    272276    END IF
     
    274278
    275279    IF (CPPKEY_REPROBUS) THEN
    276       !--- Transfert the number of tracers to Reprobus
    277280      CALL init_chem_rep_trac(nbtr, nqo, tracers(:)%name)
    278281    END IF
     
    327330      IF(iad == -1) CALL abort_gcm(modname, msg1, 1)
    328331
    329       !--- SET FIELDS %longName, %iadv, %isAdvected, %isInPhysics
     332      !--- SET FIELDS longName, iadv, isAdvected, isInPhysics
    330333      t1%longName = t1%name; IF(iad > 0) t1%longName = TRIM(t1%name) // descrq(iad)
    331334      t1%iadv = iad
    332335      t1%isAdvected = iad >= 0
    333       t1%isInPhysics = delPhase(t1%gen0Name) /= 'H2O' &
    334               .OR. t1%component /= 'lmdz' !=== OTHER EXCEPTIONS TO BE ADDED: CO2i, SURSATURATED WATER CLOUD...
     336      t1%isInPhysics = delPhase(t1%gen0Name) /= 'H2O' .OR. t1%component /= 'lmdz' !=== MORE EXCEPTIONS ? CO2i, SURSAT CLOUD H2O
    335337      ttr(iq) = t1
    336338
     
    342344      ttr(jq + 1:jq + nm) = t1
    343345      ttr(jq + 1:jq + nm)%name = [ (TRIM(t1%name) // '-' // TRIM(suff(im)), im = 1, nm) ]
     346      ttr(jq + 1:jq + nm)%gen0Name = [ (TRIM(t1%name) // '-' // TRIM(suff(im)), im = 1, nm) ]
    344347      ttr(jq + 1:jq + nm)%parent = [ (TRIM(t1%parent) // '-' // TRIM(suff(im)), im = 1, nm) ]
    345348      ttr(jq + 1:jq + nm)%longName = [ (TRIM(t1%longName) // '-' // TRIM(suff(im)), im = 1, nm) ]
     
    351354    CALL MOVE_ALLOC(FROM = ttr, TO = tracers)
    352355
    353     !--- SET FIELDS %iqParent, %nqChildren, %iGeneration, %iqDescen, %nqDescen
     356    !--- SET FIELDS iqParent, iqDescen, nqDescen, nqChildren
    354357    IF(indexUpdate(tracers)) CALL abort_gcm(modname, 'problem with tracers indices update', 1)
    355358
     
    400403    END IF
    401404    t => tracers
    402     CALL msg('Information stored in infotrac :', modname)
    403 
    404     IF(dispTable('isssssssssiiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp', &
    405             'isPh', 'isAd', 'iadv', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'], &
    406             cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component, bool2str(t%isInPhysics), &
    407                     bool2str(t%isAdvected)), &
     405    CALL msg('Information stored in ' // TRIM(modname) // ': ', modname)
     406    IF(dispTable('isssssssiiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp', &
     407            'iAdv', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'], &
     408            cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component), &
    408409            cat([(iq, iq = 1, nqtot)], t%iadv, t%iGeneration, t%iqParent, t%nqDescen, t%nqChildren, t%iso_iGroup, &
    409410                    t%iso_iName, t%iso_iZone, t%iso_iPhase), nColMax = maxTableWidth, nHead = 2, sub = modname))   &
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/iniacademic_loc.F90

    r5182 r5221  
    44
    55  USE lmdz_filtreg, ONLY: inifilr
    6   USE lmdz_infotrac, ONLY: nqtot, niso, iqIsoPha, tracers, getKey, isoName
     6  USE lmdz_infotrac, ONLY: nqtot, niso, iqIsoPha, tracers, getKey, isoName, addPhase
    77  USE control_mod, ONLY: day_step, planet_type
    88  USE exner_hyb_m, ONLY: exner_hyb
     
    1616  USE temps_mod, ONLY: annee_ref, day_ini, day_ref
    1717  USE ener_mod, ONLY: etot0, ptot0, ztot0, stot0, ang0
    18   USE lmdz_readTracFiles, ONLY: addPhase
    1918  USE netcdf, ONLY: nf90_nowrite, nf90_open, nf90_noerr, nf90_inq_varid, nf90_close, nf90_get_var
    2019  USE lmdz_ran1, ONLY: ran1
  • LMDZ6/branches/Amaury_dev/libf/phylmd/infotrac_phy.F90

    r5185 r5221  
    66  USE lmdz_readTracFiles, ONLY: trac_type, readTracersFiles, tracers, setGeneration, itZonIso, nzone, tran0, isoZone, &
    77          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
     8          addPhase, iH2O, addKey, isoSelect, testTracersFiles, isoKeys, indexUpdate, iqWIsoPha, nbIso, ntiso, isoName, isoCheck, new2oldH2O
    99  IMPLICIT NONE
    1010
     
    1616  PUBLIC :: nqtot, nbtr, nqo, nqCO2, nqtottr      !--- Main dimensions
    1717  PUBLIC :: conv_flg, pbl_flg                             !--- Convection & boundary layer activation keys
     18  PUBLIC :: new2oldH2O                                    !--- For backwards compatibility in phyetat0
     19   PUBLIC :: addPhase, delPhase                            !--- Add/remove the phase from the name of a tracer
    1820  PUBLIC :: nbtr_bin, nbtr_sulgas                         !--- Number of aerosols bins and sulfur gases for StratAer model
    1921  PUBLIC :: id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat, id_TEST_strat
    2022
    21   !=== FOR WATER
    22   PUBLIC :: ivap, iliq, isol
    23   !=== FOR ISOTOPES: General
     23  !===  FOR ISOTOPES: General
    2424  PUBLIC :: isot_type, nbIso                              !--- Derived type, full isotopes families database + nb of families
    2525  PUBLIC :: isoSelect, ixIso                              !--- Isotopes family selection tool + selected family index
    2626  !=== FOR ISOTOPES: Specific to water
    27   PUBLIC :: iH2O                                          !--- H2O isotopes class index
     27  PUBLIC :: iH2O                                          !--- Value of "ixIso" for "H2O" isotopes class
     28   PUBLIC :: ivap, iliq, isol
    2829  !=== FOR ISOTOPES: Depending on the selected isotopes family
    29   PUBLIC :: isotope, isoKeys                              !--- Selected isotopes database + associated keys (cf. getKey)
    30   PUBLIC :: isoName, isoZone, isoPhas                     !--- Isotopes and tagging zones names, phases
    31   PUBLIC :: niso, nzone, nphas, ntiso              !---  " " numbers + isotopes & tagging tracers number
    32   PUBLIC :: itZonIso                                      !--- idx "it" (in "isoName(1:niso)") = function(tagging idx, isotope idx)
    33   PUBLIC :: iqIsoPha                                      !--- idx "iq" (in "qx") = function(isotope idx, phase idx) + aliases
     30  PUBLIC :: isotope                              !--- Selected isotopes database (argument of getKey)
     31  PUBLIC :: isoKeys, isoName, isoZone, isoPhas            !--- Isotopes keys & names, tagging zones names, phases
     32  PUBLIC :: niso, ntiso,nzone, nphas!--- Number of   "   "
     33  PUBLIC :: itZonIso                                      !--- Index "it" in "isoName(1:niso)" = f(tagging idx, isotope idx)
     34  PUBLIC :: iqIsoPha                                      !--- Index "iq" in "qx"              = f(isotope idx,   phase idx)
    3435  PUBLIC :: iqWIsoPha                                      !--- Same as iqIsoPha but with normal water phases
    3536
     
    4142  !  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    4243  !  | water in different |    water tagging      |  water isotopes | other tracers | additional tracers moments |
    43   !  | phases: H2O_[gls]  |      isotopes         |                 |               |  for higher order schemes  |
     44  !  | phases: H2O_[glsrb]  |      isotopes         |                 |               |  for higher order schemes  |
    4445  !  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    4546  !  |                    |                       |                 |               |                            |
     
    6667  !  |-------------+------------------------------------------------------+-------------+------------------------+
    6768  !  | name        | Name (short)                                         | tname       |                        |
    68   !  | gen0Name    | Name of the 1st generation ancestor                  | /           |                        |
     69  !  | keys        | key/val pairs accessible with "getKey" routine       | /           |                        |
     70!  |gen0Name    | Name of the 1st generation ancestor                  | /           |                        |
    6971  !  | parent      | Name of the parent                                   | /           |                        |
    7072  !  | longName    | Long name (with adv. scheme suffix) for outputs      | ttext       |                        |
    7173  !  | type        | Type (so far: tracer or tag)                         | /           | tracer,tag             |
    72   !  | phase       | Phases list ("g"as / "l"iquid / "s"olid)             | /           | [g][l][s]              |
     74  !  | phase       | Phases list ("g"as / "l"iquid / "s"olid             |             | [g|l|s|r|b]            |
     75!  |             |              "r"(cloud) / "b"lowing)                 | /           |              |
    7376  !  | component   | Name(s) of the merged/cumulated section(s)           | /           | coma-separated names   |
    7477  !  | iGeneration | Generation (>=1)                                     | /           |                        |
     
    7780  !  | nqDescen    | Number of the descendants   (all generations)        | nqdesc      | 1:nqtot                |
    7881  !  | nqChildren  | Number of childs            (1st generation only)    | nqfils      | 1:nqtot                |
    79   !  | keys        | key/val pairs accessible with "getKey" routine       | /           |                        |
    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  |
     82
     83  !  | isAdvected  | Advected tracers flag (.TRUE. if iadv >= 0)          | /           | nqtrue  .TRUE. values  |
     84  !  | isInPhysics | Tracers not extracted from the main table in physics | /           | nqtottr .TRUE. values  |
    8285  !  | iso_iGroup  | Isotopes group index in isotopes(:)                  | /           | 1:nbIso                |
    8386  !  | iso_iName   | Isotope  name  index in isotopes(iso_iGroup)%trac(:) | iso_indnum  | 1:niso                 |
     
    9598  !  | trac   | ntiso  | Isotopes + tagging tracers list + number         | / | ntraciso       |                 |
    9699  !  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
    97   !  | phase  | nphas  | Phases                     list + number         |                    | [g][l][s], 1:3  |
     100  !  | phase  | nphas  | Phases                     list + number         |                    | [g|l|s|r|b] 1:5  |
    98101  !  | iqIsoPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
    99   !  | iqWIsoPha       | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
     102  !  | iqWIsoPha       | Index in "qx"           = f(name(1:ntiso+nqo)),phas) |   /              | 1:nqtot         |
    100103  !  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
    101104  !  +-----------------+--------------------------------------------------+--------------------+-----------------+
    102105
    103   !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
     106  !=== INDICES FOR WATER
     107   INTEGER, SAVE :: ivap, iliq, isol
     108!$OMP THREADPRIVATE(ivap, iliq, isol)
     109
     110   !===DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES
    104111  INTEGER, SAVE :: nqtot, &                     !--- Tracers nb in dynamics (incl. higher moments + H2O)
    105112          nbtr, &                     !--- Tracers nb in physics  (excl. higher moments + H2O)
     
    110117  !$OMP THREADPRIVATE(nqtot, nbtr, nqo, nqtottr, nqCO2, type_trac)
    111118
    112   !=== INDICES OF WATER
    113   INTEGER, SAVE :: ivap, iliq, isol ! Indices for vap, liq and ice
    114   !$OMP THREADPRIVATE(ivap,iliq,isol)
    115 
    116   !=== VARIABLES FOR INCA
    117   INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), &   !--- Convection     activation ; needed for INCA        (nbtr)
    118           pbl_flg(:)      !--- Boundary layer activation ; needed for INCA        (nbtr)
     119  !===  VARIABLES FOR INCA
     120  INTEGER, DIMENSION(:), SAVE, ALLOCATABLE :: &
     121                    conv_flg, pbl_flg                           !--- Convection / boundary layer activation (nbtr)
    119122  !$OMP THREADPRIVATE(conv_flg, pbl_flg)
    120123
     
    167170    CHARACTER(LEN = 2) :: suff(9)                                !--- Suffixes for schemes of order 3 or 4 (Prather)
    168171    CHARACTER(LEN = 3) :: descrq(30)                               !--- Advection scheme description tags
    169     CHARACTER(LEN = maxlen) :: msg1, texp, ttp                          !--- String for messages and expanded tracers type
     172    CHARACTER(LEN = maxlen) :: msg1, texp, ttp                          !--- Strings for messages and expanded tracers type
    170173    INTEGER :: fType                                                  !--- Tracers description file type ; 0: none
    171174    !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def"
    172175    INTEGER :: nqtrue                                                 !--- Tracers nb from tracer.def (no higher order moments)
    173176    INTEGER :: iad                                                    !--- Advection scheme number
    174     INTEGER :: iq, jq, nt, im, nm, k                                 !--- Indexes and temporary variables
     177    INTEGER :: iq, jq, nt, im, nm                                 !--- Indexes and temporary variables
    175178    LOGICAL :: lerr, lInit
    176179    TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:)
    177180    TYPE(trac_type), POINTER :: t1, t(:)
    178     CHARACTER(LEN = maxlen), ALLOCATABLE :: types_trac(:)  !--- Keyword for tracers type(s), parsed version
     181    CHARACTER(LEN = maxlen), ALLOCATABLE :: types_trac(:)  !--- Keywords for tracers type(s), parsed version
    179182
    180183    CHARACTER(LEN = *), PARAMETER :: modname = "init_infotrac_phy"
     
    236239
    237240    !==============================================================================================================================
    238     ! 1) Get the numbers of: true (first order only) tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid)
     241    ! 0) DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE AND READ IT
    239242    !==============================================================================================================================
    240     texp = type_trac                                                  !=== EXPANDED VERSION OF "type_trac", WITH "|" SEPARATOR
     243    texp = type_trac                                                  !=== EXPANDED (WITH "|" SEPARATOR) "type_trac"
    241244    IF(texp == 'inco') texp = 'co2i|inca'
    242245    IF(texp /= 'lmdz') texp = 'lmdz|' // TRIM(texp)
    243246
    244     !=== DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE
     247
    245248    IF(testTracersFiles(modname, texp, fType, lInit)) CALL abort_physic(modname, 'problem with tracers file(s)', 1)
    246249
     
    255258    !##############################################################################################################################
    256259
    257     !---------------------------------------------------------------------------------------------------------------------------
    258     IF(fType == 0) CALL abort_physic(modname, 'Missing tracers file: "traceur.def", "tracer.def" or "tracer_<keyword>.def file.', 1)
     260    !==============================================================================================================================
     261! 1) Get various numbers: "nqtrue" (first order only tracers), "nqo" (water phases), 'nbtr' (tracers passed to physics), etc.
     262!==============================================================================================================================
     263   !---------------------------------------------------------------------------------------------------------------------------
     264    IF(fType == 0) CALL abort_physic(modname, 'Missing "traceur.def", "tracer.def" or "tracer_<keyword>.def tracersfile.', 1)
    259265    !---------------------------------------------------------------------------------------------------------------------------
    260266    IF(fType == 1 .AND. ANY(['inca', 'inco']==type_trac) .AND. lInit) THEN  !=== FOUND OLD STYLE INCA "traceur.def"
    261267      !---------------------------------------------------------------------------------------------------------------------------
     268      IF (CPPKEY_INCA) THEN
    262269      nqo = SIZE(tracers) - nqCO2
    263270      CALL Init_chem_inca_trac(nqINCA)                               !--- Get nqINCA from INCA
     
    273280      ttr(1 + nqo:nqCO2 + nqo)%component = 'co2i'
    274281      ttr(1 + nqo + nqCO2:nqtrue)%component = 'inca'
    275       ttr(1 + nqo:nqtrue)%name = [('CO2     ', k = 1, nqCO2), solsym_inca]
     282      ttr(1 + nqo:nqtrue)%name = [('CO2     ', iq = 1, nqCO2), solsym_inca]
    276283      ttr(1 + nqo + nqCO2:nqtrue)%parent = tran0
    277284      ttr(1 + nqo + nqCO2:nqtrue)%phase = 'g'
     
    290297      IF(setGeneration(tracers)) CALL abort_physic(modname, 'See below', 1) !- SET FIELDS %iGeneration, %gen0Name
    291298      DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca)
     299 END IF
    292300      !---------------------------------------------------------------------------------------------------------------------------
    293301    ELSE                                                              !=== OTHER CASES (OLD OR NEW FORMAT, NO INCA MODULE)
    294302      !---------------------------------------------------------------------------------------------------------------------------
    295       nqo = COUNT(delPhase(tracers(:)%name)     == 'H2O' &
    296               .AND. tracers(:)%component == 'lmdz') !--- Number of water phases
    297       nqtrue = SIZE(tracers)                                         !--- Total number of "true" tracers
    298       nbtr = nqtrue - COUNT(delPhase(tracers(:)%gen0Name) == 'H2O' &
    299               .AND. tracers(:)%component == 'lmdz') !--- Number of tracers passed to phytrac
    300       nqINCA = COUNT(tracers(:)%component == 'inca')
    301       lerr = getKey('hadv', hadv, ky = tracers(:)%keys)
    302       lerr = getKey('vadv', vadv, ky = tracers(:)%keys)
     303      nqtrue = SIZE(tracers)                                                                               !--- "true" tracers
     304   nqo    =      COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%name)     == 'H2O')     !--- Water phases
     305   nbtr = nqtrue-COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%gen0Name) == 'H2O')     !--- Passed to phytrac
     306   nqCO2  =      COUNT( [type_trac == 'inco', type_trac == 'co2i'] )
     307      IF (CPPKEY_INCA) THEN
     308        nqINCA = COUNT(tracers(:)%component == 'inca')
     309      END IF
     310      IF(getKey('hadv', hadv, ky=tracers(:)%keys)) CALL abort_physic(modname, 'missing key "hadv"', 1)
     311   IF(getKey('vadv', vadv, ky=tracers(:)%keys)) CALL abort_physic(modname, 'missing key "vadv"', 1)
    303312      !---------------------------------------------------------------------------------------------------------------------------
    304313    END IF
     
    348357        IF(iad == -1) CALL abort_physic(modname, msg1, 1)
    349358
    350         !--- SET FIELDS %longName, %isAdvected, %isInPhysics
     359        !--- SET FIELDS longName, isAdvected, isInPhysics
    351360        t1%longName = t1%name; IF(iad > 0) t1%longName = TRIM(t1%name) // descrq(iad)
    352361        t1%isAdvected = iad >= 0
    353         t1%isInPhysics = delPhase(t1%gen0Name) /= 'H2O' &
    354                 .OR. t1%component /= 'lmdz' !=== OTHER EXCEPTIONS TO BE ADDED: CO2i, SURSATURATED WATER CLOUD...
     362        t1%isInPhysics= delPhase(t1%gen0Name) /= 'H2O' .OR. t1%component /= 'lmdz' !=== MORE EXCEPTIONS ? CO2i, SURSAT CLOUD H2O
    355363        ttr(iq) = t1
    356364
     
    362370        ttr(jq + 1:jq + nm) = t1
    363371        ttr(jq + 1:jq + nm)%name = [(TRIM(t1%name) // '-' // TRIM(suff(im)), im = 1, nm) ]
     372        ttr(jq+1:jq+nm)%gen0Name    = [ (TRIM(t1%name)    //'-'//TRIM(suff(im)), im=1, nm) ]
    364373        ttr(jq + 1:jq + nm)%parent = [(TRIM(t1%parent) // '-' // TRIM(suff(im)), im = 1, nm) ]
    365374        ttr(jq + 1:jq + nm)%longName = [(TRIM(t1%longName) // '-' // TRIM(suff(im)), im = 1, nm) ]
    366         ttr(jq + 1:jq + nm)%isAdvected = [(.FALSE., im = 1, nm) ]
     375        ttr(jq + 1:jq + nm)%isAdvected = [(.FALSE., im=1, nm) ]
     376      ttr(jq+1:jq+nm)%isInPhysics = [ (.FALSE., im = 1, nm) ]
    367377        jq = jq + nm
    368378      END DO
     
    370380      CALL MOVE_ALLOC(FROM = ttr, TO = tracers)
    371381
    372       !--- SET FIELDS %iqParent, %nqChildren, %iGeneration, %iqDescen, %nqDescen
    373       IF(indexUpdate(tracers)) CALL abort_gcm(modname, 'problem when processing isotopes parameters', 1)
     382      !--- SET FIELDS iqParent, iqDescen, nqDescen, nqChildren, iGeneration
     383      IF(indexUpdate(tracers)) CALL abort_physic(modname, 'problem with tracers indices update', 1)
    374384
    375385      !##############################################################################################################################
     
    393403    !##############################################################################################################################
    394404    !--- Convection / boundary layer activation for all tracers
    395     IF (.NOT.ALLOCATED(conv_flg)) ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1
    396     IF (.NOT.ALLOCATED(pbl_flg)) ALLOCATE(pbl_flg(nbtr));  pbl_flg(1:nbtr) = 1
     405    IF(.NOT.ALLOCATED(conv_flg)) ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1
     406    IF(.NOT.ALLOCATED( pbl_flg)) ALLOCATE(pbl_flg(nbtr));  pbl_flg(1:nbtr) = 1
    397407
    398408    !--- Note: nqtottr can differ from nbtr when nmom/=0
     
    413423    END IF
    414424    t => tracers
    415     CALL msg('Information stored in infotrac_phy :', modname)
    416     IF(dispTable('issssssssiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp', &
    417             'isPh', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'], &
    418             cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component, bool2str(t%isInPhysics)), &
     425    CALL msg('Information stored in '//TRIM(modname)//' :', modname)
     426    IF(dispTable('isssssssssiiiiiiii', ['iq  ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp', &
     427            'isPh', 'isAd', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'], &
     428            cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component, &
     429                                                         bool2str(t%isInPhysics), bool2str(t%isAdvected)), &
    419430            cat([(iq, iq = 1, nqtot)], t%iGeneration, t%iqParent, t%nqDescen, t%nqChildren, t%iso_iGroup, &
    420431                    t%iso_iName, t%iso_iZone, t%iso_iPhase), nColMax = maxTableWidth, nHead = 2, sub = modname))   &
  • LMDZ6/branches/Amaury_dev/libf/phylmd/phyetat0_mod.F90

    r5144 r5221  
    3232    USE lmdz_geometry, 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, tracers
    35     USE lmdz_readTracFiles, ONLY: maxlen, new2oldH2O
     34    USE infotrac_phy, ONLY: nqtot, nbtr, type_trac, tracers, new2oldH2O
     35    USE lmdz_readTracFiles, ONLY: maxlen
    3636    USE traclmdz_mod, ONLY: traclmdz_from_restart
    3737    USE carbon_cycle_mod, ONLY: carbon_cycle_init, carbon_cycle_cpl, carbon_cycle_tr, carbon_cycle_rad, co2_send, RCO2_glo
  • LMDZ6/branches/Amaury_dev/libf/phylmd/physiq_mod.F90

    r5194 r5221  
    3737    USE lmdz_ioipsl_getin_p, ONLY: getin_p
    3838    USE indice_sol_mod
    39     USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type_trac
    40     USE lmdz_readTracFiles, ONLY: addPhase
     39    USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type_trac, addPhase
    4140    USE lmdz_strings, ONLY: strIdx
    4241    USE iophy
  • LMDZ6/branches/Amaury_dev/libf/phylmd/surf_landice_mod.F90

    r5193 r5221  
    457457        DO j = 1, knon
    458458          i=knindex(j)
    459           print*, "tempsmoothlic", tempsmoothlic(i)
     459
    460460          tempsmoothlic(i) = temp_air(j) * coef_tempsmooth + tempsmoothlic(i) * (1. - coef_tempsmooth)
    461461          IF (tempsmoothlic(i) < ta1) THEN
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/isotopes_routines_mod.F90

    r5159 r5221  
    1626816268   USE isotopes_mod,      ONLY: isoName,iso_HDO,iso_eau
    1626916269   USE phyetat0_get_mod,  ONLY: phyetat0_get, phyetat0_srf
    16270    USE lmdz_readTracFiles, ONLY: new2oldH2O
    16271    USE lmdz_strings,       ONLY: strIdx, strTail, maxlen, msg, int2str
     16270   USE infotrac_phy, ONLY: new2oldH2O
     16271   USE lmdz_strings,       ONLY: strIdx, strHead, strTail, maxlen, msg, int2str
    1627216272#ifdef ISOVERIF
    1627316273   USE isotopes_verif_mod
     
    1630816308      outiso = isoName(ixt)
    1630916309      oldIso = strTail(new2oldH2O(outiso), '_')            !--- Remove "H2O_" from "H2O_<iso>[_<tag>]"
    16310       i = INDEX(outiso, '_', .TRUE.)
    16311       oldIso2 = outiso(1:i-1)//outiso(i+1:LEN_TRIM(outiso)) ! CR 2023: on ajoute cette possibilité aussi, elle correspond au cas le plus récent.
     16310      oldIso2= TRIM(strHead(outiso,'_'))//strTail(outiso,'_') ! CR 2023: most recent possibility
    1631216311!      WRITE(*,*) 'tmp 16541:'
    1631316312!      WRITE(*,*) 'outiso=',outiso
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/isotrac_mod.F90

    r5158 r5221  
    33
    44MODULE isotrac_mod
    5   USE infotrac_phy,      ONLY: niso, ntiso, nzone
    6   USE lmdz_readTracFiles, ONLY: delPhase
     5  USE infotrac_phy,      ONLY: niso, ntiso, nzone, delPhase
    76  USE isotopes_mod,      ONLY: ridicule, get_in
    87  USE lmdz_abort_physic, ONLY: abort_physic
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/phyetat0_mod.F90

    r5158 r5221  
    4141  USE lmdz_geometry,     ONLY: longitude_deg, latitude_deg
    4242  USE iostart,          ONLY: close_startphy, get_field, get_var, open_startphy
    43   USE infotrac_phy,     ONLY: nqtot, nbtr, type_trac, tracers
    44   USE lmdz_readTracFiles,ONLY: maxlen, new2oldH2O
     43  USE infotrac_phy,     ONLY: nqtot, nbtr, type_trac, tracers, new2oldH2O
     44  USE lmdz_readTracFiles,ONLY: maxlen
    4545  USE traclmdz_mod,     ONLY: traclmdz_from_restart
    4646  USE carbon_cycle_mod, ONLY: carbon_cycle_init, carbon_cycle_cpl, carbon_cycle_tr, carbon_cycle_rad, co2_send, RCO2_glo
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/physiq_mod.F90

    r5194 r5221  
    3939    USE lmdz_ioipsl_getin_p, ONLY: getin_p
    4040    USE indice_sol_mod
    41     USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type_trac,ivap,iliq,isol
    42     USE lmdz_readTracFiles, ONLY: addPhase
     41    USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type_trac, addPhase, ivap,iliq,isol
    4342    USE lmdz_strings,  ONLY: strIdx
    4443    USE iophy
     
    25852584       ENDDO
    25862585    ENDDO
    2587    
     2586
    25882587    ! Lea Raillard qs_ini for cloud phase param.
    25892588    qs_ini(:,:)=qs_seri(:,:)
     
    58905889       ENDIF
    58915890
    5892        IF (aerosol_couple.AND.config_inca=='aero') THEN 
     5891       IF (aerosol_couple.AND.config_inca=='aero') THEN
    58935892          CALL radlwsw_inca  &
    58945893               (chemistry_couple, kdlon,kflev,dist, rmu0, fract, solaire, &
Note: See TracChangeset for help on using the changeset viewer.