Ignore:
Timestamp:
Dec 15, 2021, 11:18:49 PM (2 years ago)
Author:
dcugnet
Message:

First commit for new tracers.

  • parser routines readTracFiles, strings_mod and tracer_types added in misc using revision 4 of https://svn.lmd.jussieu.fr/tracers-parser
  • tested in sequential and parallel mode using ioipsl.
  • for now, only two fields of "tracers(:)" derived type vector are used: "name" and "longName".
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmdiso/infotrac_phy.F90

    r4026 r4046  
    77! the dynamics (could be further cleaned) and is initialized using values
    88! provided by the dynamics
     9
     10  USE readTracFiles_mod, ONLY: trac_type, maxlen, delPhase
    911
    1012! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
     
    4143!$OMP THREADPRIVATE(nqperes)
    4244
    43 ! Name variables
    44   INTEGER,PARAMETER :: tname_lenmax=128
    45   CHARACTER(len=tname_lenmax), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
    46   CHARACTER(len=tname_lenmax+3), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
    47 !$OMP THREADPRIVATE(tname,ttext)
    48 
    49 !! iadv  : index of trasport schema for each tracer
    50 !  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iadv
     45! Tracers parameters
     46  TYPE(trac_type), TARGET, ALLOCATABLE, SAVE :: tracers(:)
     47!$OMP THREADPRIVATE(tracers)
    5148
    5249! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
     
    107104CONTAINS
    108105
    109   SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,nqtottr_,nqCO2_,tname_,ttext_,type_trac_,&
     106  SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,nqtottr_,nqCO2_,tracers_,type_trac_,&
    110107                               niadv_,conv_flg_,pbl_flg_,solsym_,&
    111108                               nqfils_,nqdesc_,nqdesc_tot_,iqfils_,iqpere_,&
     
    139136    INTEGER,INTENT(IN) :: id_BIN01_strat_
    140137#endif
    141     CHARACTER(len=*),INTENT(IN) :: tname_(nqtot_) ! tracer short name for restart and diagnostics
    142     CHARACTER(len=*),INTENT(IN) :: ttext_(nqtot_) ! tracer long name for diagnostics
     138    CHARACTER(len=*),INTENT(IN) :: tracers_(nqtot_) ! tracers descriptors
    143139    CHARACTER(len=*),INTENT(IN) :: type_trac_
    144140    INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique
     
    179175    nqCO2=nqCO2_
    180176    nqtottr=nqtottr_
     177    ALLOCATE(tracers(nqtot)); tracers(:) = tracers_(:)
    181178#ifdef CPP_StratAer
    182179    nbtr_bin=nbtr_bin_
     
    187184    id_BIN01_strat=id_BIN01_strat_
    188185#endif
    189     ALLOCATE(tname(nqtot))
    190     tname(:) = tname_(:)
    191     ALLOCATE(ttext(nqtot))
    192     ttext(:) = ttext_(:)
    193186    type_trac = type_trac_
    194187    ALLOCATE(niadv(nqtot))
Note: See TracChangeset for help on using the changeset viewer.