Ignore:
Timestamp:
Nov 7, 2022, 3:09:43 AM (3 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/dyn3dmem
Files:
6 edited

Legend:

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

    r4143 r4325  
    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, tnat
     5                          ntiso, iH2O, nzone, tracers, isoName,  itZonIso, getKey
    66   IMPLICIT NONE
    77   include "dimensions.h"
     
    1111   CHARACTER(LEN=maxlen) :: modname, msg1, nm(2)
    1212   INTEGER :: ixt, ipha, k, i, iq, iiso, izon, ieau, iqeau, iqpar
    13    INTEGER, ALLOCATABLE :: ix(:)
     13   INTEGER, ALLOCATABLE ::   ix(:)
     14   REAL,    ALLOCATABLE :: tnat(:)               !--- OpenMP shared variable
    1415   REAL    :: xtractot, xiiso, deltaD, q1, q2
    1516   REAL, PARAMETER :: borne     = 1e19,  &
     
    3637      iso_O17 = strIdx(isoName,'H2[17]O')
    3738      iso_HTO = strIdx(isoName,'H[3]HO')
     39      IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1)
    3840!$OMP END MASTER
    3941!$OMP BARRIER
  • LMDZ6/trunk/libf/dyn3dmem/dynetat0_loc.F90

    r4301 r4325  
    77!-------------------------------------------------------------------------------
    88  USE parallel_lmdz
    9   USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, tnat, alpha_ideal, iH2O
     9  USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName
    1010  USE strings_mod, ONLY: maxlen, msg, strStack, real2str, int2str
    1111  USE netcdf,      ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_INQUIRE_DIMENSION, NF90_INQ_VARID, &
    1212                         NF90_CLOSE, NF90_GET_VAR, NF90_INQUIRE_VARIABLE,  NF90_NoErr
    13   USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3
     13  USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3, getKey
    1414  USE control_mod, ONLY: planet_type
    1515  USE assert_eq_m, ONLY: assert_eq
     
    4242  INTEGER, PARAMETER :: length=100
    4343  INTEGER :: iq, fID, vID, idecal, ierr, iqParent, iName, iZone, iPhase, ix
    44   REAL    :: time, tab_cntrl(length)               !--- RUN PARAMS TABLE
     44  REAL    :: time, tnat, alpha_ideal, tab_cntrl(length)    !--- RUN PARAMS TABLE
    4545  REAL,             ALLOCATABLE :: vcov_glo(:,:),masse_glo(:,:),   ps_glo(:)
    4646  REAL,             ALLOCATABLE :: ucov_glo(:,:),    q_glo(:,:), phis_glo(:)
     
    179179      iqParent = tracers(iq)%iqParent
    180180      IF(tracers(iq)%iso_iZone == 0) THEN
     181         IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
     182            CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
    181183         CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized with a simplified Rayleigh distillation law.', modname)
    182          q(ijb_u:ije_u,:,iq)= q(ijb_u:ije_u,:,iqParent)*tnat(iName)*(q(ijb_u:ije_u,:,iqParent)/30.e-3)**(alpha_ideal(iName)-1.)
     184         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.)
    183185      ELSE
    184186         CALL msg('Tracer <'//TRIM(var)//'> is missing => initialized to its parent isotope concentration.', modname)
  • LMDZ6/trunk/libf/dyn3dmem/gcm.F90

    r4146 r4325  
    1111  USE mod_const_mpi, ONLY: init_const_mpi
    1212  USE parallel_lmdz
    13   USE infotrac, ONLY: nqtot, infotrac_init
     13  USE infotrac, ONLY: nqtot, init_infotrac
    1414!#ifdef CPP_PHYS
    1515!  USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
     
    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/dyn3dmem/iniacademic_loc.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
     
    7777  integer idum
    7878
    79   REAL zdtvr
     79  REAL zdtvr, tnat, alpha_ideal
    8080 
    8181  character(len=*),parameter :: modname="iniacademic"
     
    290290              iqParent = tracers(iq)%iqParent
    291291              IF(tracers(iq)%iso_iZone == 0) THEN
    292                  q(ijb_u:ije_u,:,iq) = q(ijb_u:ije_u,:,iqParent)*tnat(iName) &
    293                                      *(q(ijb_u:ije_u,:,iqParent)/30.e-3)**(alpha_ideal(iName)-1.)
     292                 IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) &
     293                    CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1)
     294                 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.)
    294295              ELSE
    295296                 q(ijb_u:ije_u,:,iq) = q(ijb_u:ije_u,:,iqIsoPha(iName,iPhase))
  • LMDZ6/trunk/libf/dyn3dmem/vlsplt_loc.F

    r4143 r4325  
    351351c$OMP END DO NOWAIT
    352352      enddo !do ifils=1,tracers(iq)%nqDescen
    353       do ifils=1,tracers(iq)%nqChilds
     353      do ifils=1,tracers(iq)%nqChildren
    354354        iq2=tracers(iq)%iqDescen(ifils)
    355355        call vlx_loc(Ratio,pente_max,masse,u_mq,ijb_x,ije_x,iq2)
     
    726726! CRisi: appel récursif de l'advection sur les fils.
    727727! Il faut faire ça avant d'avoir mis à jour q et masse
    728       !write(*,*) 'vly 689: iq,nqChilds(iq)=',iq,tracers(iq)%nqChilds
     728!     write(*,*)'vly 689: iq,nqChildren(iq)=',iq,tracers(iq)%nqChildren
    729729
    730730      ijb=ij_begin-2*iip1
     
    761761      enddo
    762762
    763       do ifils=1,tracers(iq)%nqChilds
     763      do ifils=1,tracers(iq)%nqChildren
    764764        iq2=tracers(iq)%iqDescen(ifils)
    765765        call vly_loc(Ratio,pente_max,masse,qbyv,iq2)
     
    11481148! CRisi: appel récursif de l'advection sur les fils.
    11491149! Il faut faire ça avant d'avoir mis à jour q et masse
    1150       !write(*,*) 'vlsplt 942: iq,nqChilds(iq)=',iq,tracers(iq)%nqChilds
     1150!     write(*,*)'vlsplt 942: iq,nqChildren(iq)=',iq,tracers(iq)%nqChildren
    11511151      do ifils=1,tracers(iq)%nqDescen
    11521152        iq2=tracers(iq)%iqDescen(ifils)
     
    11691169c$OMP BARRIER
    11701170
    1171       do ifils=1,tracers(iq)%nqChilds
     1171      do ifils=1,tracers(iq)%nqChildren
    11721172        iq2=tracers(iq)%iqDescen(ifils)
    11731173        call vlz_loc(Ratio,pente_max,masse,w,ijb_x,ije_x,iq2)
  • LMDZ6/trunk/libf/dyn3dmem/vlspltqs_loc.F

    r4143 r4325  
    337337! CRisi: appel recursif de l'advection sur les fils.
    338338! Il faut faire ca avant d'avoir mis a jour q et masse
    339       !write(*,*) 'vlspltqs 336: iq,ijb_x,nqChilds(iq)=',
    340 !     &     iq,ijb_x,tracers(iq)%nqChilds
     339      !write(*,*) 'vlspltqs 336: iq,ijb_x,nqChildren(iq)=',
     340!     &     iq,ijb_x,tracers(iq)%nqChildren
    341341
    342342      do ifils=1,tracers(iq)%nqDescen
     
    356356c$OMP END DO NOWAIT
    357357      enddo
    358       do ifils=1,tracers(iq)%nqChilds
     358      do ifils=1,tracers(iq)%nqChildren
    359359        iq2=tracers(iq)%iqDescen(ifils)
    360360        !write(*,*) 'vlxqs 349: on appelle vlx pour iq2=',iq2
     
    729729! CRisi: appel recursif de l'advection sur les fils.
    730730! Il faut faire ca avant d'avoir mis a jour q et masse
    731       !write(*,*) 'vlyqs 689: iq,nqChilds(iq)=',iq,tracers(iq)%nqChilds
     731!     write(*,*)'vlyqs 689: iq,nqChildren(iq)=',iq,
     732!    &             tracers(iq)%nqChildren
    732733     
    733734      ijb=ij_begin-2*iip1
     
    767768c$OMP END DO NOWAIT
    768769      enddo
    769       do ifils=1,tracers(iq)%nqChilds
     770      do ifils=1,tracers(iq)%nqChildren
    770771        iq2=tracers(iq)%iqDescen(ifils)
    771772        !write(lunout,*) 'vly: appel recursiv vly iq2=',iq2
Note: See TracChangeset for help on using the changeset viewer.