Ignore:
Timestamp:
Nov 7, 2022, 3:09:43 AM (2 years ago)
Author:
dcugnet
Message:
  • simplify the parser usage:
    • the getKey_init routine is now embedded in the readTracersFile routine.
    • the initIsotopes routine is now embedded in the readIsotopesFile routine.
    • the database is now unique, but can be changed using the get/setKeysDBase.
    • the derived types descriptions, originally located in trac_types_mod, are moved to readTracFiles_mod.
    • few checkings moved from infotrac to the routine testIsotopes, contained in the readIsotopesFile function from readTracFiles_mod.
    • the readTracersFiles and readIsotopesFile routines no longer use a tracers/isotopes argument.
  • remove tnat and alpha_ideal from infotrac ; use instead getKey to get them where they are used (check_isotopes, dynetat0, iniacademic)
  • the trac_type field %Childs is renamed %Children
  • move the isoSelect routine and the corresponding variables routine from infotrac and infotrac_phy to readTracFiles_mod
  • infotrac_phy routine is now fully independant of the (very similar) routine infotrac (init_infotrac_phy has no arguments left).
  • all the explicit keys of the trac_type are now included in the embedded keys database, accessible using the getKey function.
  • the getKey/addKey routines are expanded to handle vectors of integers, reals, logicals or strings.
  • few subroutines converted into functions with error return value.
  • corrections for isotopic tagging tracers mode (to be continued).
Location:
LMDZ6/trunk/libf/dyn3d
Files:
6 edited

Legend:

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

    r4143 r4325  
    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, tnat
     4                          ntiso, iH2O, nzone, tracers, isoName,  itZonIso, getKey
    55   IMPLICIT NONE
    66   include "dimensions.h"
     
    1010   CHARACTER(LEN=maxlen) :: modname, msg1, nm(2)
    1111   INTEGER :: ixt, ipha, k, i, iq, iiso, izon, ieau, iqeau, iqpar
    12    INTEGER, ALLOCATABLE :: ix(:)
     12   INTEGER, ALLOCATABLE ::   ix(:)
     13   REAL,    ALLOCATABLE :: tnat(:)
    1314   REAL    :: xtractot, xiiso, deltaD, q1, q2
    1415   REAL, PARAMETER :: borne     = 1e19,  &
     
    3334      iso_O17 = strIdx(isoName,'H2[17]O')
    3435      iso_HTO = strIdx(isoName,'H[3]HO')
     36      IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1)
    3537      first = .FALSE.
    3638   END IF
  • LMDZ6/trunk/libf/dyn3d/dynetat0.F90

    r4301 r4325  
    66! Purpose: Initial state reading.
    77!-------------------------------------------------------------------------------
    8   USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, tnat, alpha_ideal, iH2O
     8  USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName
    99  USE strings_mod, ONLY: maxlen, msg, strStack, real2str, int2str
    1010  USE netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQ_VARID, &
    1111                         NF90_CLOSE, NF90_GET_VAR, NF90_NoErr
    12   USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3
     12  USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3, getKey
    1313  USE control_mod, ONLY: planet_type
    1414  USE assert_eq_m, ONLY: assert_eq
     
    4141  INTEGER, PARAMETER :: length=100
    4242  INTEGER :: iq, fID, vID, idecal, iqParent, iName, iZone, iPhase
    43   REAL    :: time, tab_cntrl(length)               !--- RUN PARAMS TABLE
     43  REAL    :: time, tnat, alpha_ideal, tab_cntrl(length)    !--- RUN PARAMS TABLE
    4444  LOGICAL :: lSkip, ll
    4545!-------------------------------------------------------------------------------
     
    155155      iqParent = tracers(iq)%iqParent
    156156      IF(tracers(iq)%iso_iZone == 0) THEN
     157         IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
     158            CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
    157159         CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized with a simplified Rayleigh distillation law.', modname)
    158          q(:,:,:,iq) = q(:,:,:,iqParent)*tnat(iName)*(q(:,:,:,iqParent)/30.e-3)**(alpha_ideal(iName)-1.)
     160         q(:,:,:,iq) = q(:,:,:,iqParent)*tnat*(q(:,:,:,iqParent)/30.e-3)**(alpha_ideal-1.)
    159161      ELSE
    160162         CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to its parent isotope concentration.', modname)
  • LMDZ6/trunk/libf/dyn3d/gcm.F90

    r3579 r4325  
    2020
    2121  USE filtreg_mod
    22   USE infotrac
     22  USE infotrac, ONLY: nqtot, init_infotrac
    2323  USE control_mod
    2424  USE mod_const_mpi, ONLY: COMM_LMDZ
     
    205205  !  Choix du nombre de traceurs et du schema pour l'advection
    206206  !  dans fichier traceur.def, par default ou via INCA
    207   call infotrac_init
     207  call init_infotrac
    208208
    209209  ! Allocation de la tableau q : champs advectes   
  • LMDZ6/trunk/libf/dyn3d/iniacademic.F90

    r4143 r4325  
    55
    66  USE filtreg_mod, ONLY: inifilr
    7   USE infotrac,    ONLY: nqtot, niso, tnat, alpha_ideal, iqIsoPha, tracers
     7  USE infotrac,    ONLY: nqtot, niso, iqIsoPha, tracers, getKey, isoName
    88  USE control_mod, ONLY: day_step,planet_type
    99  use exner_hyb_m, only: exner_hyb
     
    7373  integer idum
    7474
    75   REAL zdtvr
     75  REAL zdtvr, tnat, alpha_ideal
    7676 
    7777  character(len=*),parameter :: modname="iniacademic"
     
    286286              iqParent = tracers(iq)%iqParent
    287287              IF(tracers(iq)%iso_iZone == 0) THEN
    288                  q(:,:,iq) = q(:,:,iqParent)*tnat(iName)*(q(:,:,iqParent)/30.e-3)**(alpha_ideal(iName)-1.)
     288                 IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
     289                    CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
     290                 q(:,:,iq) = q(:,:,iqParent)*tnat*(q(:,:,iqParent)/30.e-3)**(alpha_ideal-1.)
    289291              ELSE
    290292                 q(:,:,iq) = q(:,:,iqIsoPha(iName,iPhase))
  • LMDZ6/trunk/libf/dyn3d/vlsplt.F

    r4143 r4325  
    437437        enddo
    438438      enddo
    439       do ifils=1,tracers(iq)%nqChilds
     439      do ifils=1,tracers(iq)%nqChildren
    440440        iq2=tracers(iq)%iqDescen(ifils)
    441441        call vlx(Ratio,pente_max,masseq,u_mq,iq2)
     
    969969! CRisi: appel récursif de l'advection sur les fils.
    970970! Il faut faire ça avant d'avoir mis à jour q et masse
    971       !write(*,*) 'vlsplt 942: iq,nqChilds(iq)=',iq,nqChilds(iq)
     971      !write(*,*) 'vlsplt 942: iq,nqChildren(iq)=',iq,nqChildren(iq)
    972972      do ifils=1,tracers(iq)%nqDescen
    973973        iq2=tracers(iq)%iqDescen(ifils)
     
    987987      enddo
    988988       
    989       do ifils=1,tracers(iq)%nqChilds
     989      do ifils=1,tracers(iq)%nqChildren
    990990        iq2=tracers(iq)%iqDescen(ifils)
    991991        call vlz(Ratio,pente_max,masseq,wq,iq2)
  • LMDZ6/trunk/libf/dyn3d/vlspltqs.F

    r4052 r4325  
    479479! CRisi: appel récursif de l'advection sur les fils.
    480480! Il faut faire ça avant d'avoir mis à jour q et masse
    481       !write(*,*) 'vlspltqs 326: iq,nqChilds(iq)=',iq,tracers(iq)%nqChilds
     481      !write(*,*) 'vlspltqs 326: iq,nqChildren(iq)=',iq,
     482!     &                 tracers(iq)%nqChildren
    482483     
    483484      do ifils=1,tracers(iq)%nqDescen
     
    491492        enddo
    492493      enddo
    493       do ifils=1,tracers(iq)%nqChilds
     494      do ifils=1,tracers(iq)%nqChildren
    494495        iq2=tracers(iq)%iqDescen(ifils)
    495496        call vlx(Ratio,pente_max,masseq,u_mq,iq2)
     
    786787! CRisi: appel récursif de l'advection sur les fils.
    787788! Il faut faire ça avant d'avoir mis à jour q et masse
    788       !write(*,*) 'vlyqs 689: iq,nqChilds(iq)=',iq,tracers(iq)%nqChilds
     789      !write(*,*) 'vlyqs 689: iq,nqChildren(iq)=',iq,
     790!     &              tracers(iq)%nqChildren
    789791   
    790792      do ifils=1,tracers(iq)%nqDescen
     
    797799        enddo
    798800      enddo
    799       do ifils=1,tracers(iq)%nqChilds
     801      do ifils=1,tracers(iq)%nqChildren
    800802        iq2=tracers(iq)%iqDescen(ifils)
    801803        !write(*,*) 'vlyqs 783: appel rec de vly, iq2=',iq2
Note: See TracChangeset for help on using the changeset viewer.