Changeset 4046 for LMDZ6/trunk/libf/dyn3d_common
- Timestamp:
- Dec 15, 2021, 11:18:49 PM (3 years ago)
- Location:
- LMDZ6/trunk/libf/dyn3d_common
- Files:
-
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/dyn3d_common/infotrac.F90
r4039 r4046 2 2 ! 3 3 MODULE infotrac 4 5 USE readTracFiles_mod, ONLY: trac_type, isot_type, maxlen, ancestor, delPhase 4 6 5 7 ! nqtot : total number of tracers and higher order of moment, water vapor and liquid included … … 26 28 INTEGER, SAVE :: nqCO2 27 29 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 32 33 33 34 ! iadv : index of trasport schema for each tracer … … 119 120 CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: solsym_inca 120 121 121 CHARACTER(len= tname_lenmax), ALLOCATABLE, DIMENSION(:) :: tnom_0 ! tracer short name122 CHARACTER(len= tname_lenmax), ALLOCATABLE, DIMENSION(:) :: tnom_transp ! transporting fluid short name: CRisi122 CHARACTER(len=maxlen), ALLOCATABLE, DIMENSION(:) :: tnom_0 ! tracer short name 123 CHARACTER(len=maxlen), ALLOCATABLE, DIMENSION(:) :: tnom_transp ! transporting fluid short name: CRisi 123 124 CHARACTER(len=3), DIMENSION(30) :: descrq 124 125 CHARACTER(len=1), DIMENSION(3) :: txts 125 126 CHARACTER(len=2), DIMENSION(9) :: txtp 126 CHARACTER(len= tname_lenmax):: str1,str2127 CHARACTER(len=maxlen) :: str1,str2 127 128 128 129 INTEGER :: nqtrue ! number of tracers read from tracer.def, without higer order of moment … … 131 132 LOGICAL :: continu,nouveau_traceurdef 132 133 INTEGER :: IOstatus ! gestion de la retrocompatibilite de traceur.def 133 CHARACTER(len= 2*tname_lenmax+1) :: tchaine134 CHARACTER(len=maxlen) :: tchaine 134 135 135 136 character(len=*),parameter :: modname="infotrac_init" … … 349 350 if (nouveau_traceurdef) then 350 351 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:)) 353 354 else 354 355 write(lunout,*) 'C''est l''ancienne version de traceur.def' … … 563 564 ! Allocate variables with total number of tracers, nqtot 564 565 ! 565 ALLOCATE(t name(nqtot), ttext(nqtot))566 ALLOCATE(tracers(nqtot)) 566 567 ALLOCATE(iadv(nqtot), niadv(nqtot)) 567 568 … … 587 588 588 589 str1=tnom_0(iq) 589 t name(new_iq)= tnom_0(iq)590 tracers(new_iq)%name=TRIM(tnom_0(iq)) 590 591 IF (iadv(new_iq)==0) THEN 591 t text(new_iq)=trim(str1)592 tracers(new_iq)%longName=trim(str1) 592 593 ELSE 593 t text(new_iq)=trim(tnom_0(iq))//descrq(iadv(new_iq))594 tracers(new_iq)%longName=trim(tnom_0(iq))//descrq(iadv(new_iq)) 594 595 ENDIF 595 596 596 597 ! schemas tenant compte des moments d'ordre superieur 597 str2= ttext(new_iq)598 str2=TRIM(tracers(new_iq)%longName) 598 599 IF (iadv(new_iq)==20) THEN 599 600 DO jq=1,3 600 601 new_iq=new_iq+1 601 602 iadv(new_iq)=-20 602 t text(new_iq)=trim(str2)//txts(jq)603 t name(new_iq)=trim(str1)//txts(jq)603 tracers(new_iq)%longName=trim(str2)//txts(jq) 604 tracers(new_iq)%name=trim(str1)//txts(jq) 604 605 END DO 605 606 ELSE IF (iadv(new_iq)==30) THEN … … 607 608 new_iq=new_iq+1 608 609 iadv(new_iq)=-30 609 t text(new_iq)=trim(str2)//txtp(jq)610 t name(new_iq)=trim(str1)//txtp(jq)610 tracers(new_iq)%longName=trim(str2)//txtp(jq) 611 tracers(new_iq)%name=trim(str1)//txtp(jq) 611 612 END DO 612 613 ENDIF … … 628 629 629 630 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 :' 631 632 632 633 DO iq=1,nqtot 633 WRITE(lunout,*) iadv(iq),niadv(iq), ' ',trim(t name(iq)),' ',trim(ttext(iq))634 WRITE(lunout,*) iadv(iq),niadv(iq), ' ',trim(tracers(iq)%name),' ',trim(tracers(iq)%longName) 634 635 END DO 635 636 … … 802 803 INTEGER, ALLOCATABLE,DIMENSION(:) :: nb_isoind 803 804 INTEGER :: ntraceurs_zone_prec,iq,phase,ixt,iiso,izone 804 CHARACTER(len= tname_lenmax) :: tnom_trac805 CHARACTER(len=maxlen) :: tnom_trac 805 806 INCLUDE "iniprint.h" 806 807 -
LMDZ6/trunk/libf/dyn3d_common/initdynav.F90
r2622 r4046 6 6 USE IOIPSL 7 7 #endif 8 USE infotrac, ONLY : nqtot , ttext8 USE infotrac, ONLY : nqtot 9 9 use com_io_dyn_mod, only : histaveid,histvaveid,histuaveid, & 10 10 dynhistave_file,dynhistvave_file,dynhistuave_file … … 158 158 159 159 ! DO iq=1,nqtot 160 ! call histdef(histaveid, ttext(iq), ttext(iq), '-', & 160 ! call histdef(histaveid, tracers(iq)%name, & 161 ! tracers(iq)%longName, '-', & 161 162 ! iip1, jjp1, thoriid, llm, 1, llm, zvertiid, & 162 163 ! 32, 'ave(X)', t_ops, t_wrt) -
LMDZ6/trunk/libf/dyn3d_common/inithist.F
r2622 r4046 7 7 USE IOIPSL 8 8 #endif 9 USE infotrac, ONLY : nqtot , ttext9 USE infotrac, ONLY : nqtot 10 10 use com_io_dyn_mod, only : histid,histvid,histuid, & 11 11 & dynhist_file,dynhistv_file,dynhistu_file … … 157 157 ! 158 158 ! DO iq=1,nqtot 159 ! call histdef(histid, ttext(iq), ttext(iq), '-', 159 ! call histdef(histid, tracers(iq)%name, 160 ! tracers(iq)%longName, '-', 160 161 ! . iip1, jjp1, thoriid, llm, 1, llm, zvertiid, 161 162 ! . 32, 'inst(X)', t_ops, t_wrt) -
LMDZ6/trunk/libf/dyn3d_common/writedynav.F90
r2622 r4046 6 6 USE ioipsl 7 7 #endif 8 USE infotrac, ONLY : nqtot , ttext8 USE infotrac, ONLY : nqtot 9 9 use com_io_dyn_mod, only : histaveid, histvaveid, histuaveid 10 10 USE comconst_mod, ONLY: cpp … … 106 106 107 107 ! DO iq=1, nqtot 108 ! call histwrite(histaveid, t text(iq), itau_w, q(:, :, iq), &109 ! iip1*jjp1*llm, ndexu)108 ! call histwrite(histaveid, tracers(iq)%longName, itau_w, & 109 ! q(:, :, iq), iip1*jjp1*llm, ndexu) 110 110 ! enddo 111 111 -
LMDZ6/trunk/libf/dyn3d_common/writehist.F
r2622 r4046 7 7 USE ioipsl 8 8 #endif 9 USE infotrac, ONLY : nqtot , ttext9 USE infotrac, ONLY : nqtot 10 10 use com_io_dyn_mod, only : histid,histvid,histuid 11 11 USE temps_mod, ONLY: itau_dyn … … 100 100 C 101 101 ! DO iq=1,nqtot 102 ! call histwrite(histid, t text(iq), itau_w, q(:,:,iq),103 ! . iip1*jjp1*llm, ndexu)102 ! call histwrite(histid, tracers(iq)%longName, itau_w, 103 ! . q(:,:,iq), iip1*jjp1*llm, ndexu) 104 104 ! enddo 105 105 !C
Note: See TracChangeset
for help on using the changeset viewer.