Ignore:
Timestamp:
Sep 10, 2024, 5:14:23 PM (2 months ago)
Author:
dcugnet
Message:
  • Remove INCA retro-compatibility with "traceur.def" (containing only water tracers but getting chemical species from an internal INCA routine).
  • The "trac_type" derived type internal to "readTracFiles_mod" is removed because a generic "keys_type" is enough: no explicit key ("%" operator) is needed, even %name.
  • The "trac_type" and "isot_type" derived types are now defined locally in "infotrac" and "infotrac_phy" (and more generally in each context: dynamic, lmdz dynamics, lmdz physics, etc.). The "readTracFiles_mod" module is now only used in these two routines:
    • few internal routines/variables (addPhase, delPhase, new2oldH2O, newHNO3, oldHNO3) are made available through "infotrac" and "infotrac_phy".
    • the "getKey" routine is only used in these two routines to define the explicit keys ("%" operator) of the local derived types "trac_type" and "isot_type". It could be in principle used outside this scope to get tracers parameters (read from "tracer.def") or isotopic parameters (read from "isotopes_params.def" - disabled for now).
  • 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. "ltnat1" is no longer hardcoded but defined with the *.def files parameter "tnat1"
  • Few minor changes:
    • use "infotrac_phy" instead of "infotrac" in calfis* because "tracers(:)%isAdvected" is defined in physics only.
    • "isotopes_mod" now ready for several isotopes classes (currently: only H2O)
    • isotopes class name (the name of the parent of the isotopes) is now %name and no longer %parent.
    • improvement of "getKey"
Location:
LMDZ6/trunk/libf/dyn3d
Files:
4 edited

Legend:

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

    r4984 r5183  
    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
     6   USE ioipsl_getincom, ONLY: getin
    57   IMPLICIT NONE
    68   include "dimensions.h"
     
    2022                      deltaDmin =-999.0, &
    2123                      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.
     24   INTEGER, SAVE :: iso_eau, iso_O17, iso_O18, iso_HDO, iso_HTO
     25   LOGICAL, SAVE :: ltnat1, first=.TRUE.
    2626
    2727   modname='check_isotopes'
     
    3030   IF(niso == 0)        RETURN                   !--- No isotopes => finished
    3131   IF(first) THEN
    32       iso_eau = strIdx(isoName,'H216O')
    33       iso_HDO = strIdx(isoName,'HDO')
    34       iso_O18 = strIdx(isoName,'H218O')
    35       iso_O17 = strIdx(isoName,'H217O')
    36       iso_HTO = strIdx(isoName,'HTO')
    37       if (tnat1) then
    38               tnat(:)=1.0
    39       else
    40          IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1)
    41       endif
     32      ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
     33      ALLOCATE(tnat(niso))
     34      iso_eau = strIdx(isoName,'H216O'); IF(iso_eau /= 0) tnat(iso_eau) = tnat_H216O
     35      iso_O17 = strIdx(isoName,'H217O'); IF(iso_O17 /= 0) tnat(iso_O17) = tnat_H217O
     36      iso_O18 = strIdx(isoName,'H218O'); IF(iso_O18 /= 0) tnat(iso_O18) = tnat_H218O
     37      iso_HDO = strIdx(isoName,'HDO');   IF(iso_HDO /= 0) tnat(iso_HDO) = tnat_HDO
     38      iso_HTO = strIdx(isoName,'HTO');   IF(iso_HTO /= 0) tnat(iso_HTO) = tnat_HTO
     39      IF(ltnat1) tnat(:) = 1.
    4240      first = .FALSE.
    4341   END IF
  • LMDZ6/trunk/libf/dyn3d/dynetat0.F90

    r5084 r5183  
    66! Purpose: Initial state reading.
    77!-------------------------------------------------------------------------------
    8   USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName
     8  USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName, &
     9                         new2oldH2O, newHNO3, oldHNO3
    910  USE strings_mod, ONLY: maxlen, msg, strStack, real2str, int2str
    1011  USE netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQ_VARID, &
    1112                         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_*
    2127
    2228  IMPLICIT NONE
     
    4248  INTEGER :: iq, fID, vID, idecal, iqParent, iName, iZone, iPhase
    4349  REAL    :: time, tnat, alpha_ideal, tab_cntrl(length)    !--- RUN PARAMS TABLE
    44   LOGICAL :: lSkip, ll
    45   LOGICAL,PARAMETER :: tnat1=.TRUE.
     50  LOGICAL :: lSkip, ll, ltnat1
    4651!-------------------------------------------------------------------------------
    4752  modname="dynetat0"
     
    116121  var="temps"
    117122  IF(NF90_INQ_VARID(fID,var,vID)/=NF90_NoErr) THEN
    118     CALL msg('missing field <temps> ; trying with <Time>', modname)
     123    CALL msg('Missing field <temps> ; trying with <Time>', modname)
    119124    var="Time"
    120125    CALL err(NF90_INQ_VARID(fID,var,vID),"inq",var)
     
    133138  ll = NF90_INQ_VARID(fID, 'HNO3tot', vID) /= NF90_NoErr                                 !--- DETECT OLD REPRO start.nc FILE
    134139#endif
     140  ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
    135141  DO iq=1,nqtot
    136142    var = tracers(iq)%name
     
    148154    !--------------------------------------------------------------------------------------------------------------------------
    149155    ELSE IF(NF90_INQ_VARID(fID, oldVar, vID) == NF90_NoErr) THEN                         !=== TRY WITH ALTERNATE NAME
    150       CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to <'//TRIM(oldVar)//'>', modname)
     156      CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to <'//TRIM(oldVar)//'>', modname)
    151157      CALL err(NF90_GET_VAR(fID,vID,q(:,:,:,iq)),"get",oldVar)
    152158    !--------------------------------------------------------------------------------------------------------------------------
     
    156162      iqParent = tracers(iq)%iqParent
    157163      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(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)
     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)
    167179         q(:,:,:,iq) = q(:,:,:,iqParent)*tnat*(q(:,:,:,iqParent)/30.e-3)**(alpha_ideal-1.)
    168180      ELSE
    169          CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to its parent isotope concentration.', modname)
     181         CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to its parent isotope concentration.', modname)
    170182         ! Camille 9 mars 2023: attention!! seuls les tags qui correspondent à
    171183         ! izone=izone_init (définie dans isotrac_mod) sont initialisés comme
     
    181193    !--------------------------------------------------------------------------------------------------------------------------
    182194    ELSE                                                                                 !=== MISSING: SET TO 0
    183       CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to zero', modname)
     195      CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to zero', modname)
    184196      q(:,:,:,iq)=0.
    185197    !--------------------------------------------------------------------------------------------------------------------------
  • LMDZ6/trunk/libf/dyn3d/iniacademic.F90

    r5084 r5183  
    55
    66  USE filtreg_mod, ONLY: inifilr
    7   USE infotrac,    ONLY: nqtot, niso, iqIsoPha, tracers, getKey, isoName
     7  USE infotrac,    ONLY: nqtot, niso, iqIsoPha, tracers, getKey, isoName, addPhase
    88  USE control_mod, ONLY: day_step,planet_type
    99  use exner_hyb_m, only: exner_hyb
     
    2121  USE temps_mod, ONLY: annee_ref, day_ini, day_ref
    2222  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    23   USE readTracFiles_mod, ONLY: addPhase
    2423  use netcdf, only : NF90_NOWRITE,NF90_OPEN,NF90_NOERR,NF90_INQ_VARID
    2524  use netcdf, only : NF90_CLOSE, NF90_GET_VAR
     25  USE iso_params_mod   ! tnat_* and alpha_ideal_*
    2626
    2727
     
    8080
    8181  REAL zdtvr, tnat, alpha_ideal
    82   LOGICAL,PARAMETER :: tnat1=.true.
     82  LOGICAL :: ltnat1
    8383 
    8484  character(len=*),parameter :: modname="iniacademic"
     
    309309        ! bulk initialization of tracers
    310310        if (planet_type=="earth") then
     311           ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
    311312           ! Earth: first two tracers will be water
    312313           do iq=1,nqtot
     
    322323              iqParent = tracers(iq)%iqParent
    323324              IF(tracers(iq)%iso_iZone == 0) THEN
    324                  if (tnat1) then
    325                          tnat=1.0
    326                          alpha_ideal=1.0
    327                          write(*,*) 'Attention dans iniacademic: alpha_ideal=1'
    328                  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)
    331                  endif
     325                 IF(ltnat1) THEN
     326                    tnat = 1.0
     327                    alpha_ideal = 1.0
     328                    WRITE(lunout, *)'In '//TRIM(modname)//': !!!  Beware: alpha_ideal put to 1  !!!'
     329                 ELSE
     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
     339                 END IF
    332340                 q(:,:,iq) = q(:,:,iqParent)*tnat*(q(:,:,iqParent)/30.e-3)**(alpha_ideal-1.)
    333341              ELSE !IF(tracers(iq)%iso_iZone == 0) THEN
  • LMDZ6/trunk/libf/dyn3d/qminimum.F

    r5001 r5183  
    44      SUBROUTINE qminimum( q,nqtot,deltap )
    55
    6       USE infotrac, ONLY: niso, ntiso,iqIsoPha, tracers
     6      USE infotrac, ONLY: niso, ntiso, iqIsoPha, tracers, addPhase
    77      USE strings_mod, ONLY: strIdx
    8       USE readTracFiles_mod, ONLY: addPhase
    98      IMPLICIT none
    109c
Note: See TracChangeset for help on using the changeset viewer.