Ignore:
Timestamp:
Sep 20, 2024, 1:10:18 PM (4 months ago)
Author:
Laurent Fairhead
Message:

Merge with trunk revision 5202 before reintegration to trunk

Location:
LMDZ6/branches/cirrus
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/cirrus

  • LMDZ6/branches/cirrus/libf/dyn3d/check_isotopes.F90

    r5202 r5203  
    33   USE infotrac,    ONLY: nqtot, niso, nphas, isotope, isoCheck, iqIsoPha, isoSelect, &
    44                          ntiso, iH2O, nzone, tracers, isoName,  itZonIso, getKey
     5#ifdef CPP_IOIPSL
     6   USE ioipsl,          ONLY: getin
     7#else
     8   USE ioipsl_getincom, ONLY: getin
     9#endif
    510   IMPLICIT NONE
    611   include "dimensions.h"
     
    2025                      deltaDmin =-999.0, &
    2126                      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.
     27   INTEGER, SAVE :: iso_eau, iso_O17, iso_O18, iso_HDO, iso_HTO
     28   LOGICAL, SAVE :: ltnat1, first=.TRUE.
    2629
    2730   modname='check_isotopes'
     
    3033   IF(niso == 0)        RETURN                   !--- No isotopes => finished
    3134   IF(first) THEN
     35      ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
     36      ALLOCATE(tnat(niso))
    3237      iso_eau = strIdx(isoName,'H216O')
     38      iso_O17 = strIdx(isoName,'H217O')
     39      iso_O18 = strIdx(isoName,'H218O')
    3340      iso_HDO = strIdx(isoName,'HDO')
    34       iso_O18 = strIdx(isoName,'H218O')
    35       iso_O17 = strIdx(isoName,'H217O')
    3641      iso_HTO = strIdx(isoName,'HTO')
    37       if (tnat1) then
    38               tnat(:)=1.0
    39       else
     42      IF(ltnat1) THEN
     43         tnat(:)=1.0
     44      ELSE
    4045         IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1)
    41       endif
     46      END IF
    4247      first = .FALSE.
    4348   END IF
     
    5156         DO k = 1, llm
    5257            DO i = 1, ip1jmp1
    53                IF(ABS(q(i,k,iq)) < borne) CYCLE
     58               IF(ABS(q(i,k,iq)) <= borne) CYCLE
    5459               WRITE(msg1,'(s,"(",i0,",",i0,",",i0,") = ",ES12.4)')TRIM(isoName(ixt)),i,k,iq,q(i,k,iq)
    5560               CALL msg(msg1, modname)
  • LMDZ6/branches/cirrus/libf/dyn3d/dynetat0.F90

    r5202 r5203  
    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, getKey
    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
    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"
     
    116120  var="temps"
    117121  IF(NF90_INQ_VARID(fID,var,vID)/=NF90_NoErr) THEN
    118     CALL msg('missing field <temps> ; trying with <Time>', modname)
     122    CALL msg('Missing field <temps> ; trying with <Time>', modname)
    119123    var="Time"
    120124    CALL err(NF90_INQ_VARID(fID,var,vID),"inq",var)
     
    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
     
    148153    !--------------------------------------------------------------------------------------------------------------------------
    149154    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)
     155      CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to <'//TRIM(oldVar)//'>', modname)
    151156      CALL err(NF90_GET_VAR(fID,vID,q(:,:,:,iq)),"get",oldVar)
    152157    !--------------------------------------------------------------------------------------------------------------------------
     
    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
    166          CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized with a simplified Rayleigh distillation law.', modname)
     170         END IF
     171         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.)
    168173      ELSE
    169          CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to its parent isotope concentration.', modname)
     174         CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to its parent isotope concentration.', modname)
    170175         ! Camille 9 mars 2023: attention!! seuls les tags qui correspondent à
    171176         ! izone=izone_init (définie dans isotrac_mod) sont initialisés comme
     
    181186    !--------------------------------------------------------------------------------------------------------------------------
    182187    ELSE                                                                                 !=== MISSING: SET TO 0
    183       CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to zero', modname)
     188      CALL msg('Missing tracer <'//TRIM(var)//'> => initialized to zero', modname)
    184189      q(:,:,:,iq)=0.
    185190    !--------------------------------------------------------------------------------------------------------------------------
  • LMDZ6/branches/cirrus/libf/dyn3d/iniacademic.F90

    r5202 r5203  
    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
     
    8079
    8180  REAL zdtvr, tnat, alpha_ideal
    82   LOGICAL,PARAMETER :: tnat1=.true.
     81  LOGICAL :: ltnat1
    8382 
    8483  character(len=*),parameter :: modname="iniacademic"
     
    309308        ! bulk initialization of tracers
    310309        if (planet_type=="earth") then
     310           ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)
    311311           ! Earth: first two tracers will be water
    312312           do iq=1,nqtot
     
    322322              iqParent = tracers(iq)%iqParent
    323323              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
     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
    329329                    IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
    330330                    CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
    331                  endif
     331                 END IF
    332332                 q(:,:,iq) = q(:,:,iqParent)*tnat*(q(:,:,iqParent)/30.e-3)**(alpha_ideal-1.)
    333333              ELSE !IF(tracers(iq)%iso_iZone == 0) THEN
  • LMDZ6/branches/cirrus/libf/dyn3d/qminimum.F

    r5202 r5203  
    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.