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/dyn3d_common/infotrac.F90

    r4039 r4046  
    22!
    33MODULE infotrac
     4
     5  USE readTracFiles_mod, ONLY: trac_type, isot_type, maxlen, ancestor, delPhase
    46
    57! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
     
    2628  INTEGER, SAVE :: nqCO2
    2729
    28 ! Name variables
    29   INTEGER,PARAMETER :: tname_lenmax=128
    30   CHARACTER(len=tname_lenmax), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
    31   CHARACTER(len=tname_lenmax+3), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
     30! DC: derived types containing informations about tracers and isotopes
     31  TYPE(trac_type), TARGET,  SAVE, ALLOCATABLE ::  tracers(:)    !=== TRACERS DESCRIPTORS VECTOR
     32  TYPE(isot_type), TARGET,  SAVE, ALLOCATABLE :: isotopes(:)    !=== ISOTOPES PARAMETERS VECTOR
    3233
    3334! iadv  : index of trasport schema for each tracer
     
    119120    CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: solsym_inca
    120121
    121     CHARACTER(len=tname_lenmax), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
    122     CHARACTER(len=tname_lenmax), ALLOCATABLE, DIMENSION(:) :: tnom_transp ! transporting fluid short name: CRisi
     122    CHARACTER(len=maxlen), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
     123    CHARACTER(len=maxlen), ALLOCATABLE, DIMENSION(:) :: tnom_transp ! transporting fluid short name: CRisi
    123124    CHARACTER(len=3), DIMENSION(30) :: descrq
    124125    CHARACTER(len=1), DIMENSION(3)  :: txts
    125126    CHARACTER(len=2), DIMENSION(9)  :: txtp
    126     CHARACTER(len=tname_lenmax)               :: str1,str2
     127    CHARACTER(len=maxlen)           :: str1,str2
    127128 
    128129    INTEGER :: nqtrue  ! number of tracers read from tracer.def, without higer order of moment
     
    131132    LOGICAL :: continu,nouveau_traceurdef
    132133    INTEGER :: IOstatus ! gestion de la retrocompatibilite de traceur.def
    133     CHARACTER(len=2*tname_lenmax+1) :: tchaine   
     134    CHARACTER(len=maxlen) :: tchaine   
    134135
    135136    character(len=*),parameter :: modname="infotrac_init"
     
    349350             if (nouveau_traceurdef) then
    350351                write(lunout,*) 'C''est la nouvelle version de traceur.def'
    351                 tnom_0(iq)=tchaine(1:iiq-1)
    352                 tnom_transp(iq)=tchaine(iiq+1:)
     352                tnom_0(iq)=TRIM(tchaine(1:iiq-1))
     353                tnom_transp(iq)=TRIM(tchaine(iiq+1:))
    353354             else
    354355                write(lunout,*) 'C''est l''ancienne version de traceur.def'
     
    563564! Allocate variables with total number of tracers, nqtot
    564565!
    565     ALLOCATE(tname(nqtot), ttext(nqtot))
     566    ALLOCATE(tracers(nqtot))
    566567    ALLOCATE(iadv(nqtot), niadv(nqtot))
    567568
     
    587588     
    588589       str1=tnom_0(iq)
    589        tname(new_iq)= tnom_0(iq)
     590       tracers(new_iq)%name=TRIM(tnom_0(iq))
    590591       IF (iadv(new_iq)==0) THEN
    591           ttext(new_iq)=trim(str1)
     592          tracers(new_iq)%longName=trim(str1)
    592593       ELSE
    593           ttext(new_iq)=trim(tnom_0(iq))//descrq(iadv(new_iq))
     594          tracers(new_iq)%longName=trim(tnom_0(iq))//descrq(iadv(new_iq))
    594595       ENDIF
    595596
    596597       ! schemas tenant compte des moments d'ordre superieur
    597        str2=ttext(new_iq)
     598       str2=TRIM(tracers(new_iq)%longName)
    598599       IF (iadv(new_iq)==20) THEN
    599600          DO jq=1,3
    600601             new_iq=new_iq+1
    601602             iadv(new_iq)=-20
    602              ttext(new_iq)=trim(str2)//txts(jq)
    603              tname(new_iq)=trim(str1)//txts(jq)
     603             tracers(new_iq)%longName=trim(str2)//txts(jq)
     604             tracers(new_iq)%name=trim(str1)//txts(jq)
    604605          END DO
    605606       ELSE IF (iadv(new_iq)==30) THEN
     
    607608             new_iq=new_iq+1
    608609             iadv(new_iq)=-30
    609              ttext(new_iq)=trim(str2)//txtp(jq)
    610              tname(new_iq)=trim(str1)//txtp(jq)
     610             tracers(new_iq)%longName=trim(str2)//txtp(jq)
     611             tracers(new_iq)%name=trim(str1)//txtp(jq)
    611612          END DO
    612613       ENDIF
     
    628629
    629630    WRITE(lunout,*) trim(modname),': Information stored in infotrac :'
    630     WRITE(lunout,*) trim(modname),': iadv  niadv tname  ttext :'
     631    WRITE(lunout,*) trim(modname),': iadv  niadv  name  long_name :'
    631632
    632633    DO iq=1,nqtot
    633        WRITE(lunout,*) iadv(iq),niadv(iq), ' ',trim(tname(iq)),' ',trim(ttext(iq))
     634       WRITE(lunout,*) iadv(iq),niadv(iq), ' ',trim(tracers(iq)%name),' ',trim(tracers(iq)%longName)
    634635    END DO
    635636
     
    802803    INTEGER, ALLOCATABLE,DIMENSION(:) :: nb_isoind
    803804    INTEGER :: ntraceurs_zone_prec,iq,phase,ixt,iiso,izone
    804     CHARACTER(len=tname_lenmax) :: tnom_trac
     805    CHARACTER(len=maxlen) :: tnom_trac
    805806    INCLUDE "iniprint.h"
    806807
Note: See TracChangeset for help on using the changeset viewer.