Changeset 4005


Ignore:
Timestamp:
Nov 10, 2021, 10:40:20 AM (2 years ago)
Author:
Ehouarn Millour
Message:

Some cleanup around tracer name string length, and anticipate future needs and make default string max length larger (128 characters instead of 20).
EM

Location:
LMDZ6/trunk/libf
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d_common/infotrac.F90

    r3998 r4005  
    2727
    2828! Name variables
    29   CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
    30   CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
     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
    3132
    3233! iadv  : index of trasport schema for each tracer
     
    118119    CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: solsym_inca
    119120
    120     CHARACTER(len=30), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
    121     CHARACTER(len=30), ALLOCATABLE, DIMENSION(:) :: tnom_transp ! transporting fluid short name: CRisi
     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
    122123    CHARACTER(len=3), DIMENSION(30) :: descrq
    123124    CHARACTER(len=1), DIMENSION(3)  :: txts
    124125    CHARACTER(len=2), DIMENSION(9)  :: txtp
    125     CHARACTER(len=23)               :: str1,str2
     126    CHARACTER(len=tname_lenmax)               :: str1,str2
    126127 
    127128    INTEGER :: nqtrue  ! number of tracers read from tracer.def, without higer order of moment
     
    130131    LOGICAL :: continu,nouveau_traceurdef
    131132    INTEGER :: IOstatus ! gestion de la retrocompatibilite de traceur.def
    132     CHARACTER(len=30) :: tchaine   
     133    CHARACTER(len=2*tname_lenmax+1) :: tchaine   
    133134
    134135    character(len=*),parameter :: modname="infotrac_init"
     
    349350                write(lunout,*) 'C''est la nouvelle version de traceur.def'
    350351                tnom_0(iq)=tchaine(1:iiq-1)
    351                 tnom_transp(iq)=tchaine(iiq+1:30)
     352                tnom_transp(iq)=tchaine(iiq+1:)
    352353             else
    353354                write(lunout,*) 'C''est l''ancienne version de traceur.def'
     
    366367       WRITE(lunout,*) trim(modname),': nombre total de traceurs ',nqtrue
    367368       DO iq=1,nqtrue
    368           WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq),tnom_transp(iq)
     369          WRITE(lunout,*) hadv(iq),vadv(iq),' ',trim(tnom_0(iq)),' ',trim(tnom_transp(iq))
    369370       END DO
    370371
     
    479480                write(lunout,*) 'C''est la nouvelle version de traceur.def'
    480481                tnom_0(iq)=tchaine(1:iiq-1)
    481                 tnom_transp(iq)=tchaine(iiq+1:30)
     482                tnom_transp(iq)=tchaine(iiq+1:)
    482483             else
    483484                write(lunout,*) 'C''est l''ancienne version de traceur.def'
     
    793794 
    794795    ! inputs
    795     INTEGER nqtrue
    796     CHARACTER(len=30) tnom_0(nqtrue)
     796    INTEGER,INTENT(IN) :: nqtrue
     797    CHARACTER(len=*),INTENT(IN) :: tnom_0(nqtrue)
    797798   
    798799    ! locals   
     
    801802    INTEGER, ALLOCATABLE,DIMENSION(:) :: nb_isoind
    802803    INTEGER :: ntraceurs_zone_prec,iq,phase,ixt,iiso,izone
    803     CHARACTER(len=19) :: tnom_trac
     804    CHARACTER(len=tname_lenmax) :: tnom_trac
    804805    INCLUDE "iniprint.h"
    805806
  • LMDZ6/trunk/libf/phylmd/infotrac_phy.F90

    r3924 r4005  
    4242
    4343! Name variables
    44   CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
    45   CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
     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
    4647!$OMP THREADPRIVATE(tname,ttext)
    4748
     
    138139    INTEGER,INTENT(IN) :: id_BIN01_strat_
    139140#endif
    140     CHARACTER(len=20),INTENT(IN) :: tname_(nqtot_) ! tracer short name for restart and diagnostics
    141     CHARACTER(len=23),INTENT(IN) :: ttext_(nqtot_) ! tracer long name for diagnostics
    142     CHARACTER(len=4),INTENT(IN) :: type_trac_
     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
     143    CHARACTER(len=*),INTENT(IN) :: type_trac_
    143144    INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique
    144145    INTEGER,INTENT(IN) :: conv_flg_(nbtr_)
    145146    INTEGER,INTENT(IN) :: pbl_flg_(nbtr_)
    146     CHARACTER(len=8),INTENT(IN) :: solsym_(nbtr_)
     147    CHARACTER(len=*),INTENT(IN) :: solsym_(nbtr_)
    147148    ! Isotopes:
    148149    INTEGER,INTENT(IN) :: nqfils_(nqtot_)
Note: See TracChangeset for help on using the changeset viewer.