Ignore:
Timestamp:
Sep 22, 2024, 10:07:56 PM (2 months ago)
Author:
dcugnet
Message:

The fortran parameters file "iso_params_mod.F90" is introduced so that "tnat" and "alpha_ideal" are defined in a single place but used in several.
The "getKey" routine is only used in "infotrac" and "infotrac_phy" routines, but could be used outside this scope to get tracers parameters (read from "tracer.def") or isotopic parameters (read from "isotopes_params.def" - disabled for now).

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

Legend:

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

    r5201 r5214  
    22   USE strings_mod, ONLY: maxlen, msg, strIdx, strStack, int2str, real2str
    33   USE infotrac,    ONLY: nqtot, niso, nphas, isotope, isoCheck, iqIsoPha, isoSelect, &
    4                           ntiso, iH2O, nzone, tracers, isoName,  itZonIso, getKey
     4                          ntiso, iH2O, nzone, tracers, isoName,  itZonIso
     5   USE iso_params_mod,  ONLY: tnat_H216O, tnat_H217O, tnat_H218O, tnat_HDO, tnat_HTO
    56#ifdef CPP_IOIPSL
    67   USE ioipsl,          ONLY: getin
     
    1516   CHARACTER(LEN=maxlen) :: modname, msg1, nm(2)
    1617   INTEGER :: ixt, ipha, k, i, iq, iiso, izon, ieau, iqeau, iqpar
    17    INTEGER, ALLOCATABLE ::   ix(:)
     18   INTEGER, ALLOCATABLE       ::   ix(:)
    1819   REAL,    ALLOCATABLE, SAVE :: tnat(:)
    19    REAL    :: xtractot, xiiso, deltaD, q1, q2
     20   REAL :: xtractot, xiiso, deltaD, q1, q2
    2021   REAL, PARAMETER :: borne     = 1e19,  &
    2122                      errmax    = 1e-8,  &       !--- Max. absolute error
     
    2627                      ridicule  = 1e-12
    2728   INTEGER, SAVE :: iso_eau, iso_O17, iso_O18, iso_HDO, iso_HTO
    28    LOGICAL, SAVE :: ltnat1, first=.TRUE.
     29   LOGICAL       :: ltnat1
     30   LOGICAL, SAVE :: first=.TRUE.
    2931
    3032   modname='check_isotopes'
     
    3537      ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
    3638      ALLOCATE(tnat(niso))
    37       iso_eau = strIdx(isoName,'H216O')
    38       iso_O17 = strIdx(isoName,'H217O')
    39       iso_O18 = strIdx(isoName,'H218O')
    40       iso_HDO = strIdx(isoName,'HDO')
    41       iso_HTO = strIdx(isoName,'HTO')
    42       IF(ltnat1) THEN
    43          tnat(:)=1.0
    44       ELSE
    45          IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1)
    46       END IF
     39      iso_eau = strIdx(isoName,'H216O'); IF(iso_eau /= 0) tnat(iso_eau) = tnat_H216O
     40      iso_O17 = strIdx(isoName,'H217O'); IF(iso_O17 /= 0) tnat(iso_O17) = tnat_H217O
     41      iso_O18 = strIdx(isoName,'H218O'); IF(iso_O18 /= 0) tnat(iso_O18) = tnat_H218O
     42      iso_HDO = strIdx(isoName,'HDO');   IF(iso_HDO /= 0) tnat(iso_HDO) = tnat_HDO
     43      iso_HTO = strIdx(isoName,'HTO');   IF(iso_HTO /= 0) tnat(iso_HTO) = tnat_HTO
     44      IF(ltnat1) tnat(:) = 1.
    4745      first = .FALSE.
    4846   END IF
     
    5654         DO k = 1, llm
    5755            DO i = 1, ip1jmp1
    58                IF(ABS(q(i,k,iq)) <= borne) CYCLE
     56               IF(ABS(q(i,k,iq)) < borne) CYCLE
    5957               WRITE(msg1,'(s,"(",i0,",",i0,",",i0,") = ",ES12.4)')TRIM(isoName(ixt)),i,k,iq,q(i,k,iq)
    6058               CALL msg(msg1, modname)
  • LMDZ6/trunk/libf/dyn3d/dynetat0.F90

    r5200 r5214  
    77!-------------------------------------------------------------------------------
    88  USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName, &
    9                          new2oldH2O, newHNO3, oldHNO3, getKey
     9                         new2oldH2O, newHNO3, oldHNO3
    1010  USE strings_mod, ONLY: maxlen, msg, strStack, real2str, int2str
    1111  USE netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQ_VARID, &
     
    2424  USE ioipsl_getincom, ONLY: getin
    2525#endif
     26  USE iso_params_mod   ! tnat_* and alpha_ideal_*
    2627
    2728  IMPLICIT NONE
     
    166167            CALL msg(' !!!  Beware: alpha_ideal put to 1  !!!', modname)
    167168         ELSE
    168           IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
    169             CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
     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
    170177         END IF
    171178         CALL msg('Missing tracer <'//TRIM(var)//'> => initialized with a simplified Rayleigh distillation law.', modname)
  • LMDZ6/trunk/libf/dyn3d/iniacademic.F90

    r5200 r5214  
    55
    66  USE filtreg_mod, ONLY: inifilr
    7   USE infotrac,    ONLY: nqtot, niso, iqIsoPha, tracers, getKey, isoName, addPhase
     7  USE infotrac,    ONLY: nqtot, niso, iqIsoPha, tracers, isoName, addPhase
    88  USE control_mod, ONLY: day_step,planet_type
    99  use exner_hyb_m, only: exner_hyb
     
    2323  use netcdf, only : NF90_NOWRITE,NF90_OPEN,NF90_NOERR,NF90_INQ_VARID
    2424  use netcdf, only : NF90_CLOSE, NF90_GET_VAR
     25  USE iso_params_mod   ! tnat_* and alpha_ideal_*
    2526
    2627
     
    327328                    WRITE(lunout, *)'In '//TRIM(modname)//': !!!  Beware: alpha_ideal put to 1  !!!'
    328329                 ELSE
    329                     IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
    330                     CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
     330                    SELECT CASE(isoName(iName))
     331                      CASE('H216O'); tnat = tnat_H216O; alpha_ideal = alpha_ideal_H216O
     332                      CASE('H217O'); tnat = tnat_H217O; alpha_ideal = alpha_ideal_H217O
     333                      CASE('H218O'); tnat = tnat_H218O; alpha_ideal = alpha_ideal_H218O
     334                      CASE('HDO');   tnat = tnat_HDO;   alpha_ideal = alpha_ideal_HDO
     335                      CASE('HTO');   tnat = tnat_HTO;   alpha_ideal = alpha_ideal_HTO
     336                      CASE DEFAULT
     337                         CALL abort_gcm(TRIM(modname),'unknown isotope "'//TRIM(isoName(iName))//'" ; check tracer.def file',1)
     338                    END SELECT
    331339                 END IF
    332340                 q(:,:,iq) = q(:,:,iqParent)*tnat*(q(:,:,iqParent)/30.e-3)**(alpha_ideal-1.)
Note: See TracChangeset for help on using the changeset viewer.