Ignore:
Timestamp:
Sep 15, 2024, 10:38:32 AM (7 days ago)
Author:
dcugnet
Message:

Revert to r5182 because r5183 still craches with gfortran for unclear reasons.
r5188 and r5189 have been included.

File:
1 edited

Legend:

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

    r5183 r5190  
    66! Purpose: Initial state reading.
    77!-------------------------------------------------------------------------------
    8   USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName, &
    9                          new2oldH2O, newHNO3, oldHNO3
     8  USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName
    109  USE strings_mod, ONLY: maxlen, msg, strStack, real2str, int2str
    1110  USE netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQ_VARID, &
    1211                         NF90_CLOSE, NF90_GET_VAR, NF90_NoErr
     12  USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3, getKey
    1313  USE control_mod, ONLY: planet_type
    1414  USE assert_eq_m, ONLY: assert_eq
     
    1919  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn, start_time
    2020  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    21 #ifdef CPP_IOIPSL
    22   USE IOIPSL,   ONLY: getin
    23 #else
    24   USE ioipsl_getincom, ONLY: getin
    25 #endif
    26   USE iso_params_mod   ! tnat_* and alpha_ideal_*
    2721
    2822  IMPLICIT NONE
     
    4842  INTEGER :: iq, fID, vID, idecal, iqParent, iName, iZone, iPhase
    4943  REAL    :: time, tnat, alpha_ideal, tab_cntrl(length)    !--- RUN PARAMS TABLE
    50   LOGICAL :: lSkip, ll, ltnat1
     44  LOGICAL :: lSkip, ll
     45  LOGICAL,PARAMETER :: tnat1=.TRUE.
    5146!-------------------------------------------------------------------------------
    5247  modname="dynetat0"
     
    121116  var="temps"
    122117  IF(NF90_INQ_VARID(fID,var,vID)/=NF90_NoErr) THEN
    123     CALL msg('Missing field <temps> ; trying with <Time>', modname)
     118    CALL msg('missing field <temps> ; trying with <Time>', modname)
    124119    var="Time"
    125120    CALL err(NF90_INQ_VARID(fID,var,vID),"inq",var)
     
    138133  ll = NF90_INQ_VARID(fID, 'HNO3tot', vID) /= NF90_NoErr                                 !--- DETECT OLD REPRO start.nc FILE
    139134#endif
    140   ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
    141135  DO iq=1,nqtot
    142136    var = tracers(iq)%name
     
    154148    !--------------------------------------------------------------------------------------------------------------------------
    155149    ELSE IF(NF90_INQ_VARID(fID, oldVar, vID) == NF90_NoErr) THEN                         !=== TRY WITH ALTERNATE NAME
    156       CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to <'//TRIM(oldVar)//'>', modname)
     150      CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to <'//TRIM(oldVar)//'>', modname)
    157151      CALL err(NF90_GET_VAR(fID,vID,q(:,:,:,iq)),"get",oldVar)
    158152    !--------------------------------------------------------------------------------------------------------------------------
     
    162156      iqParent = tracers(iq)%iqParent
    163157      IF(tracers(iq)%iso_iZone == 0) THEN
    164          IF(ltnat1) THEN
    165             tnat = 1.0
    166             alpha_ideal = 1.0
    167             CALL msg(' !!!  Beware: alpha_ideal put to 1  !!!', modname)
    168          ELSE
    169             SELECT CASE(isoName(iName))
    170               CASE('H216O'); tnat = tnat_H216O; alpha_ideal = alpha_ideal_H216O
    171               CASE('H217O'); tnat = tnat_H217O; alpha_ideal = alpha_ideal_H217O
    172               CASE('H218O'); tnat = tnat_H218O; alpha_ideal = alpha_ideal_H218O
    173               CASE('HDO');   tnat = tnat_HDO;   alpha_ideal = alpha_ideal_HDO
    174               CASE('HTO');   tnat = tnat_HTO;   alpha_ideal = alpha_ideal_HTO
    175               CASE DEFAULT; CALL abort_gcm(TRIM(modname),'unknown isotope "'//TRIM(isoName(iName))//'" ; check tracer.def file',1)
    176             END SELECT
    177          END IF
    178          CALL msg('Missing tracer <'//TRIM(var)//'> => initialized with a simplified Rayleigh distillation law.', modname)
     158         if (tnat1) then
     159                 tnat=1.0
     160                 alpha_ideal=1.0
     161                 write(*,*) 'attention dans dynetat0: les alpha_ideal sont a 1'
     162         else
     163          IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
     164            CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
     165         endif
     166         CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized with a simplified Rayleigh distillation law.', modname)
    179167         q(:,:,:,iq) = q(:,:,:,iqParent)*tnat*(q(:,:,:,iqParent)/30.e-3)**(alpha_ideal-1.)
    180168      ELSE
    181          CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to its parent isotope concentration.', modname)
     169         CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to its parent isotope concentration.', modname)
    182170         ! Camille 9 mars 2023: attention!! seuls les tags qui correspondent à
    183171         ! izone=izone_init (définie dans isotrac_mod) sont initialisés comme
     
    193181    !--------------------------------------------------------------------------------------------------------------------------
    194182    ELSE                                                                                 !=== MISSING: SET TO 0
    195       CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to zero', modname)
     183      CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to zero', modname)
    196184      q(:,:,:,iq)=0.
    197185    !--------------------------------------------------------------------------------------------------------------------------
Note: See TracChangeset for help on using the changeset viewer.