Ignore:
Timestamp:
Sep 19, 2024, 4:11:02 PM (2 months ago)
Author:
dcugnet
Message:

Replace the hard-coded "tnat1" (TRUE by default) by a variable that can be changed using "tnateq1" in *.def files.
"iso_verif_dyn" now uses also this variable (fix)

Location:
LMDZ6/trunk/libf/dyn3d
Files:
3 edited

Legend:

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

    r5190 r5200  
    2020                      deltaDmin =-999.0, &
    2121                      ridicule  = 1e-12
    22    INTEGER, SAVE :: iso_eau, iso_HDO, iso_O18, &
    23                              iso_O17, iso_HTO
    24    LOGICAL, SAVE :: first=.TRUE.
    25    LOGICAL, PARAMETER :: tnat1=.TRUE.
     22   INTEGER, SAVE :: iso_eau, iso_O17, iso_O18, iso_HDO, iso_HTO
     23   LOGICAL, SAVE :: ltnat1, first=.TRUE.
    2624
    2725   modname='check_isotopes'
     
    3028   IF(niso == 0)        RETURN                   !--- No isotopes => finished
    3129   IF(first) THEN
     30      ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
     31      ALLOCATE(tnat(niso))
    3232      iso_eau = strIdx(isoName,'H216O')
     33      iso_O17 = strIdx(isoName,'H217O')
     34      iso_O18 = strIdx(isoName,'H218O')
    3335      iso_HDO = strIdx(isoName,'HDO')
    34       iso_O18 = strIdx(isoName,'H218O')
    35       iso_O17 = strIdx(isoName,'H217O')
    3636      iso_HTO = strIdx(isoName,'HTO')
    37       if (tnat1) then
    38               tnat(:)=1.0
    39       else
     37      IF(ltnat1) THEN
     38         tnat(:)=1.0
     39      ELSE
    4040         IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1)
    41       endif
     41      END IF
    4242      first = .FALSE.
    4343   END IF
     
    5151         DO k = 1, llm
    5252            DO i = 1, ip1jmp1
    53                IF(ABS(q(i,k,iq)) < borne) CYCLE
     53               IF(ABS(q(i,k,iq)) <= borne) CYCLE
    5454               WRITE(msg1,'(s,"(",i0,",",i0,",",i0,") = ",ES12.4)')TRIM(isoName(ixt)),i,k,iq,q(i,k,iq)
    5555               CALL msg(msg1, modname)
  • LMDZ6/trunk/libf/dyn3d/dynetat0.F90

    r5199 r5200  
    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
    2126
    2227  IMPLICIT NONE
     
    4247  INTEGER :: iq, fID, vID, idecal, iqParent, iName, iZone, iPhase
    4348  REAL    :: time, tnat, alpha_ideal, tab_cntrl(length)    !--- RUN PARAMS TABLE
    44   LOGICAL :: lSkip, ll
    45   LOGICAL,PARAMETER :: tnat1=.TRUE.
     49  LOGICAL :: lSkip, ll, ltnat1
    4650!-------------------------------------------------------------------------------
    4751  modname="dynetat0"
     
    133137  ll = NF90_INQ_VARID(fID, 'HNO3tot', vID) /= NF90_NoErr                                 !--- DETECT OLD REPRO start.nc FILE
    134138#endif
     139  ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
    135140  DO iq=1,nqtot
    136141    var = tracers(iq)%name
     
    156161      iqParent = tracers(iq)%iqParent
    157162      IF(tracers(iq)%iso_iZone == 0) THEN
    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(ltnat1) THEN
     164            tnat = 1.0
     165            alpha_ideal = 1.0
     166            CALL msg(' !!!  Beware: alpha_ideal put to 1  !!!', modname)
     167         ELSE
    163168          IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
    164169            CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
    165          endif
     170         END IF
    166171         CALL msg('Missing tracer <'//TRIM(var)//'> => initialized with a simplified Rayleigh distillation law.', modname)
    167172         q(:,:,:,iq) = q(:,:,:,iqParent)*tnat*(q(:,:,:,iqParent)/30.e-3)**(alpha_ideal-1.)
  • LMDZ6/trunk/libf/dyn3d/iniacademic.F90

    r5199 r5200  
    7979
    8080  REAL zdtvr, tnat, alpha_ideal
    81   LOGICAL,PARAMETER :: tnat1=.true.
     81  LOGICAL :: ltnat1
    8282 
    8383  character(len=*),parameter :: modname="iniacademic"
     
    308308        ! bulk initialization of tracers
    309309        if (planet_type=="earth") then
     310           ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
    310311           ! Earth: first two tracers will be water
    311312           do iq=1,nqtot
     
    321322              iqParent = tracers(iq)%iqParent
    322323              IF(tracers(iq)%iso_iZone == 0) THEN
    323                  if (tnat1) then
    324                          tnat=1.0
    325                          alpha_ideal=1.0
    326                          write(*,*) 'Attention dans iniacademic: alpha_ideal=1'
    327                  else
     324                 IF(ltnat1) THEN
     325                    tnat = 1.0
     326                    alpha_ideal = 1.0
     327                    WRITE(lunout, *)'In '//TRIM(modname)//': !!!  Beware: alpha_ideal put to 1  !!!'
     328                 ELSE
    328329                    IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
    329330                    CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
    330                  endif
     331                 END IF
    331332                 q(:,:,iq) = q(:,:,iqParent)*tnat*(q(:,:,iqParent)/30.e-3)**(alpha_ideal-1.)
    332333              ELSE !IF(tracers(iq)%iso_iZone == 0) THEN
Note: See TracChangeset for help on using the changeset viewer.