Ignore:
Timestamp:
Sep 10, 2024, 5:14:23 PM (3 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/dyn3dmem
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3dmem/check_isotopes_loc.F90

    r4984 r5183  
    33   USE strings_mod, ONLY: maxlen, msg, strIdx, strStack, int2str, real2str
    44   USE infotrac,    ONLY: nqtot, niso, nphas, isotope, isoCheck, iqIsoPha, isoSelect, &
    5                           ntiso, iH2O, nzone, tracers, isoName,  itZonIso, getKey
     5                          ntiso, iH2O, nzone, tracers, isoName,  itZonIso
     6   USE iso_params_mod, ONLY: tnat_H216O, tnat_H217O, tnat_H218O, tnat_HDO, tnat_HTO
     7#ifdef CPP_IOIPSL
     8   USE ioipsl,          ONLY: getin
     9#else
     10   USE ioipsl_getincom, ONLY: getin
     11#endif
    612   IMPLICIT NONE
    713   include "dimensions.h"
     
    2127                      deltaDmin =-999.0, &
    2228                      ridicule  = 1e-12
    23    INTEGER, SAVE :: iso_eau, iso_HDO, iso_O18, & !--- OpenMP shared variables
    24                              iso_O17, iso_HTO
     29   INTEGER, SAVE :: iso_eau, iso_HDO, iso_O18, iso_O17, iso_HTO
     30!$OMP THREADPRIVATE(iso_eau, iso_HDO, iso_O18, iso_O17, iso_HTO)
     31   LOGICAL       :: ltnat1
    2532   LOGICAL, SAVE :: first=.TRUE.
    26    LOGICAL, PARAMETER :: tnat1=.TRUE.
    2733!$OMP THREADPRIVATE(first)
    2834
     
    3238   IF(niso == 0)        RETURN                   !--- No isotopes => finished
    3339   IF(first) THEN
    34 !$OMP MASTER
    35       iso_eau = strIdx(isoName,'H216O')
    36       iso_HDO = strIdx(isoName,'HDO')
    37       iso_O18 = strIdx(isoName,'H218O')
    38       iso_O17 = strIdx(isoName,'H217O')
    39       iso_HTO = strIdx(isoName,'HTO')
    40       if (tnat1) then
    41               tnat(:)=1.0
    42       else
    43          IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1)
    44       endif
    45 !$OMP END MASTER
    46 !$OMP BARRIER
     40      ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
     41      iso_eau = strIdx(isoName,'H216O'); IF(iso_eau /= 0) tnat(iso_eau) = tnat_H216O
     42      iso_O17 = strIdx(isoName,'H217O'); IF(iso_O17 /= 0) tnat(iso_O17) = tnat_H217O
     43      iso_O18 = strIdx(isoName,'H218O'); IF(iso_O18 /= 0) tnat(iso_O18) = tnat_H218O
     44      iso_HDO = strIdx(isoName,'HDO');   IF(iso_HDO /= 0) tnat(iso_HDO) = tnat_HDO
     45      iso_HTO = strIdx(isoName,'HTO');   IF(iso_HTO /= 0) tnat(iso_HTO) = tnat_HTO
     46      IF(ltnat1) tnat(:) = 1.0
    4747      first = .FALSE.
    4848   END IF
  • LMDZ6/trunk/libf/dyn3dmem/dynetat0_loc.F90

    r5084 r5183  
    77!-------------------------------------------------------------------------------
    88  USE parallel_lmdz
    9   USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName
     9  USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName, &
     10                         new2oldH2O, newHNO3, oldHNO3
    1011  USE strings_mod, ONLY: maxlen, msg, strStack, real2str, int2str, strIdx
    1112  USE netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQUIRE_DIMENSION, NF90_INQ_VARID, &
    1213                         NF90_CLOSE, NF90_GET_VAR, NF90_INQUIRE_VARIABLE,  NF90_NoErr
    13   USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3, getKey
    1414  USE control_mod, ONLY: planet_type
    1515  USE assert_eq_m, ONLY: assert_eq
     
    2020  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn, start_time
    2121  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
     22#ifdef CPP_IOIPSL
     23  USE IOIPSL,   ONLY: getin
     24#else
     25  USE ioipsl_getincom, ONLY: getin
     26#endif
     27  USE iso_params_mod   ! tnat_* and alpha_ideal_*
    2228
    2329  IMPLICIT NONE
     
    4753  REAL,             ALLOCATABLE :: ucov_glo(:,:),    q_glo(:,:), phis_glo(:)
    4854  REAL,             ALLOCATABLE :: teta_glo(:,:)
    49   LOGICAL :: lSkip, ll
    50   LOGICAL,PARAMETER :: tnat1=.TRUE.
     55  LOGICAL :: lSkip, ll, ltnat1
    5156!-------------------------------------------------------------------------------
    5257  modname="dynetat0_loc"
     
    158163  ll = NF90_INQ_VARID(fID, 'HNO3tot', vID) /= NF90_NoErr                                 !--- DETECT OLD REPRO start.nc FILE
    159164#endif
     165  ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
    160166  DO iq=1,nqtot
    161167    var = tracers(iq)%name
     
    173179    !--------------------------------------------------------------------------------------------------------------------------
    174180    ELSE IF(NF90_INQ_VARID(fID, oldVar, vID) == NF90_NoErr) THEN                         !=== TRY WITH ALTERNATE NAME
    175       CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to <'//TRIM(oldVar)//'>', modname)
     181      CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to <'//TRIM(oldVar)//'>', modname)
    176182      CALL get_var2(oldVar, q_glo); q(ijb_u:ije_u,:,iq)=q_glo(ijb_u:ije_u,:)
    177183    !--------------------------------------------------------------------------------------------------------------------------
     
    181187      iqParent = tracers(iq)%iqParent
    182188      IF(tracers(iq)%iso_iZone == 0) THEN
    183          if (tnat1) then
    184                  tnat=1.0
    185                  alpha_ideal=1.0
    186                  write(*,*) 'attention dans dynetat0: les alpha_ideal sont a 1'
    187          else
    188           IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
    189             CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
    190          endif
    191          CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized with a simplified Rayleigh distillation law.', modname)
     189         IF(ltnat1) THEN
     190            tnat = 1.0
     191            alpha_ideal = 1.0
     192            CALL msg(' !!!  Beware: alpha_ideal put to 1  !!!', modname)
     193         ELSE
     194            SELECT CASE(isoName(iName))
     195              CASE('H216O'); tnat = tnat_H216O; alpha_ideal = alpha_ideal_H216O
     196              CASE('H217O'); tnat = tnat_H217O; alpha_ideal = alpha_ideal_H217O
     197              CASE('H218O'); tnat = tnat_H218O; alpha_ideal = alpha_ideal_H218O
     198              CASE('HDO');   tnat = tnat_HDO;   alpha_ideal = alpha_ideal_HDO
     199              CASE('HTO');   tnat = tnat_HTO;   alpha_ideal = alpha_ideal_HTO
     200              CASE DEFAULT; CALL abort_gcm(TRIM(modname),'unknown isotope "'//TRIM(isoName(iName))//'" ; check tracer.def file',1)
     201            END SELECT
     202         END IF
     203         CALL msg('Missing tracer <'//TRIM(var)//'> => initialized with a simplified Rayleigh distillation law.', modname)
    192204         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.)
    193205         ! Camille 9 mars 2023: point de vigilence: initialisation incohérente
    194206         ! avec celle de xt_ancien dans la physiq.
    195207      ELSE
    196          CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to its parent isotope concentration.', modname)
     208         CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to its parent isotope concentration.', modname)
    197209         ! Camille 9 mars 2023: attention!! seuls les tags qui correspondent à
    198210         ! izone=izone_init (définie dans isotrac_mod) sont initialisés comme
     
    208220    !--------------------------------------------------------------------------------------------------------------------------
    209221    ELSE                                                                                 !=== MISSING: SET TO 0
    210       CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to zero', modname)
     222      CALL msg('missing tracer <'//TRIM(var)//'> => initialized to zero', modname)
    211223      q(ijb_u:ije_u,:,iq)=0.
    212224    !--------------------------------------------------------------------------------------------------------------------------
  • LMDZ6/trunk/libf/dyn3dmem/iniacademic_loc.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, addPhase, isoName
    88  USE control_mod, ONLY: day_step,planet_type
    99  use exner_hyb_m, only: exner_hyb
     
    2222  USE temps_mod, ONLY: annee_ref, day_ini, day_ref
    2323  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    24   USE readTracFiles_mod, ONLY: addPhase
    2524  use netcdf, only : NF90_NOWRITE,NF90_OPEN,NF90_NOERR,NF90_INQ_VARID
    2625  use netcdf, only : NF90_CLOSE, NF90_GET_VAR
     26  USE iso_params_mod   ! tnat_* and alpha_ideal_*
    2727
    2828
     
    8585
    8686  REAL zdtvr, tnat, alpha_ideal
    87   LOGICAL,PARAMETER :: tnat1=.true.
     87  LOGICAL :: ltnat1
    8888 
    8989  character(len=*),parameter :: modname="iniacademic"
     
    311311        ! bulk initialization of tracers
    312312        if (planet_type=="earth") then
     313           ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
    313314           ! Earth: first two tracers will be water
    314315           do iq=1,nqtot
     
    324325              iqParent = tracers(iq)%iqParent
    325326              IF(tracers(iq)%iso_iZone == 0) THEN
    326                  if (tnat1) then
    327                          tnat=1.0
    328                          alpha_ideal=1.0
    329                          write(*,*) 'Attention dans iniacademic: alpha_ideal=1'
    330                  else
    331                     IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
    332                     CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
    333                  endif
     327                 IF(ltnat1) THEN
     328                    tnat = 1.0
     329                    alpha_ideal = 1.0
     330                    WRITE(lunout, *) 'In '//TRIM(modname)//': !!!  Beware: alpha_ideal put to 1  !!!'
     331                 ELSE
     332                    SELECT CASE(isoName(iName))
     333                      CASE('H216O'); tnat = tnat_H216O; alpha_ideal = alpha_ideal_H216O
     334                      CASE('H217O'); tnat = tnat_H217O; alpha_ideal = alpha_ideal_H217O
     335                      CASE('H218O'); tnat = tnat_H218O; alpha_ideal = alpha_ideal_H218O
     336                      CASE('HDO');   tnat = tnat_HDO;   alpha_ideal = alpha_ideal_HDO
     337                      CASE('HTO');   tnat = tnat_HTO;   alpha_ideal = alpha_ideal_HTO
     338                      CASE DEFAULT
     339                         CALL abort_gcm(TRIM(modname),'unknown isotope "'//TRIM(isoName(iName))//'" ; check tracer.def file',1)
     340                    END SELECT
     341                 END IF
    334342                 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.)
    335343              ELSE !IF(tracers(iq)%iso_iZone == 0) THEN
  • LMDZ6/trunk/libf/dyn3dmem/qminimum_loc.F

    r5001 r5183  
    44      SUBROUTINE qminimum_loc( q,nqtot,deltap )
    55      USE parallel_lmdz
    6       USE infotrac, ONLY: niso, ntiso, iqIsoPha, tracers,
     6      USE infotrac, ONLY: niso, ntiso, iqIsoPha, tracers, addPhase,
    77     &                    isoCheck, min_qParent
    88      USE strings_mod, ONLY: strIdx
    9       USE readTracFiles_mod, ONLY: addPhase
    109      IMPLICIT none
    1110c
Note: See TracChangeset for help on using the changeset viewer.