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

Merge r5200

Location:
LMDZ6/branches/Amaury_dev
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev

  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/dynetat0_loc.f90

    r5222 r5223  
    88  USE parallel_lmdz
    99  USE lmdz_infotrac, ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName, &
    10                          new2oldH2O, newHNO3, oldHNO3, getKey
     10          new2oldH2O, newHNO3, oldHNO3, getKey
    1111  USE lmdz_strings, ONLY: maxlen, msg, strStack, real2str, int2str, strIdx
    1212  USE netcdf, ONLY: nf90_open, nf90_nowrite, nf90_inquire_dimension, nf90_inq_varid, &
     
    4949  REAL, ALLOCATABLE :: ucov_glo(:, :), q_glo(:, :), phis_glo(:)
    5050  REAL, ALLOCATABLE :: teta_glo(:, :)
    51   LOGICAL :: lSkip, ll
    52   LOGICAL, PARAMETER :: tnat1 = .TRUE.
     51  LOGICAL :: lSkip, ll, ltnat1
    5352  !-------------------------------------------------------------------------------
    5453  modname = "dynetat0_loc"
     
    160159    ll = nf90_inq_varid(fID, 'HNO3tot', vID) /= nf90_noerr                                 !--- DETECT OLD REPRO start.nc FILE
    161160  END IF
     161  ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
    162162  DO iq = 1, nqtot
    163163    var = tracers(iq)%name
     
    175175      !--------------------------------------------------------------------------------------------------------------------------
    176176    ELSE IF(nf90_inq_varid(fID, oldVar, vID) == nf90_noerr) THEN                         !=== TRY WITH ALTERNATE NAME
    177       CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to <' // TRIM(oldVar) // '>', modname)
     177      CALL msg('Missing tracer <' // TRIM(var) // '> => initialized to <' // TRIM(oldVar) // '>', modname)
    178178      CALL get_var2(oldVar, q_glo); q(ijb_u:ije_u, :, iq) = q_glo(ijb_u:ije_u, :)
    179179      !--------------------------------------------------------------------------------------------------------------------------
     
    183183      iqParent = tracers(iq)%iqParent
    184184      IF(tracers(iq)%iso_iZone == 0) THEN
    185         IF (tnat1) THEN
     185        IF(ltnat1) THEN
    186186          tnat = 1.0
    187187          alpha_ideal = 1.0
    188           WRITE(*, *) 'attention dans dynetat0: les alpha_ideal sont a 1'
    189         else
     188          CALL msg(' !!!  Beware: alpha_ideal put to 1  !!!', modname)
     189        ELSE
    190190          IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
    191191                  CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
    192         endif
    193         CALL msg('Missing tracer <'//TRIM(var)//'> => initialized with a simplified Rayleigh distillation law.', modname)
     192        END IF
     193        CALL msg('Missing tracer <' // TRIM(var) // '> => initialized with a simplified Rayleigh distillation law.', modname)
    194194        q(ijb_u:ije_u, :, iq) = q(ijb_u:ije_u, :, iqParent) * tnat * (q(ijb_u:ije_u, :, iqParent) / 30.e-3)**(alpha_ideal - 1.)
    195195        ! Camille 9 mars 2023: point de vigilence: initialisation incohérente
    196196        ! avec celle de xt_ancien dans la physiq.
    197197      ELSE
    198         CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to its parent isotope concentration.', modname)
     198        CALL msg('Missing tracer <' // TRIM(var) // '> => initialized to its parent isotope concentration.', modname)
    199199        ! Camille 9 mars 2023: attention!! seuls les tags qui correspondent à
    200200        ! izone=izone_init (définie dans isotrac_mod) sont initialisés comme
     
    210210      !--------------------------------------------------------------------------------------------------------------------------
    211211    ELSE                                                                                 !=== MISSING: SET TO 0
    212       CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to zero', modname)
     212      CALL msg('Missing tracer <' // TRIM(var) // '> => initialized to zero', modname)
    213213      q(ijb_u:ije_u, :, iq) = 0.
    214214      !--------------------------------------------------------------------------------------------------------------------------
Note: See TracChangeset for help on using the changeset viewer.