Changeset 4


Ignore:
Timestamp:
Dec 13, 2021, 10:22:32 AM (3 years ago)
Author:
dcugnet
Message:
  • fix in strings_od for strLower and strUpper (the routines were swapped).
  • few additional TRIM (just in case...)
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • readTracFiles_mod.f90

    r3 r4  
    138138      CALL msg('This file is for air tracers only',           modname, ns == 3 .AND. it == 1)
    139139      CALL msg('This files specifies the transporting fluid', modname, ns == 4 .AND. it == 1)
    140       tracs(it)%name = s(3); tracs(it)%phase = known_phases(1:1)     !--- Default: name, gazeous phase "g"
     140      tracs(it)%name = TRIM(s(3))                                    !--- Name of the tracer
     141      tracs(it)%phase = known_phases(1:1)                            !--- Phase (default: "g" for gazeous)
    141142      DO ip = 1, nphases                                             !--- Deal with old water names
    142143        IF(s(3) /= 'H2O'//old_phases(ip:ip)) CYCLE
     
    401402      DO itr=1,ntr                                                   !--- Loop on tracers list elts
    402403        i = iq+itr-1+(ipr-1)*ntr
    403         ttr(i)%name = ta(itr); ttr(i)%parent = pa(ipr)
     404        ttr(i)%name = TRIM(ta(itr)); ttr(i)%parent = pa(ipr)
    404405        ttr(i)%keys = keys_type(ta(itr), tr(it)%keys%key, tr(it)%keys%val)
    405406      END DO
     
    502503  tdup(:) = ''
    503504  DO iq=1,nq; IF(lTag(iq)) CYCLE                                     !--- Tags can be repeated
    504     tnam = tr(iq)%name
    505     ll = tr(:)%name==tnam                                            !--- Mask for current tracer name
     505    tnam = TRIM(tr(iq)%name)
     506    ll = tr(:)%name==TRIM(tnam)                                      !--- Mask for current tracer name
    506507    IF(COUNT(ll)==1 ) CYCLE                                          !--- Tracer is not repeated
    507508    IF(tr(iq)%iGeneration>1) THEN
     
    548549  DO iq = 1, nq                                                      !--- Loop on "tr(:)" indexes
    549550    lTg = tr(iq)%type=='tag'                                         !--- Current tracer is a tag
    550     i0 = strFind(tr(:)%name, tr(iq)%gen0Name, n)                     !--- Indexes of first generation ancestor copies
     551    i0 = strFind(tr(:)%name, TRIM(tr(iq)%gen0Name), n)               !--- Indexes of first generation ancestor copies
    551552    np = SUM( [( LEN_TRIM(tr(i0(i))%phase),i=1,n )],1)               !--- Number of phases for current tracer tr(iq)
    552553    lEx = np>1                                                       !--- Need of a phase suffix
     
    562563        IF(lTg) nam = TRIM(nam)//'_'//TRIM(trn)                      !--- <parent>_<name> for tags
    563564        ttr(it) = tr(iq)                                             !--- Same <key>=<val> pairs
    564         ttr(it)%name = nam                                           !--- Name with possibly phase suffix
    565         ttr(it)%keys%name = nam                                      !--- Name inside the keys decriptor
     565        ttr(it)%name = TRIM(nam)                                     !--- Name with possibly phase suffix
     566        ttr(it)%keys%name = TRIM(nam)                                !--- Name inside the keys decriptor
    566567        ttr(it)%phase = pha(ip:ip)                                   !--- Single phase entry
    567568        IF(lEx.AND.tr(iq)%iGeneration>1) THEN
     
    605606      ix(iq) = jq                                                    !--- First generation ancestor index first
    606607      iq = iq + 1
    607       iy = strFind(tr(:)%gen0Name, tr(jq)%name)                      !--- Indexes of "tr(jq)" childs in "tr(:)"
     608      iy = strFind(tr(:)%gen0Name, TRIM(tr(jq)%name))                !--- Indexes of "tr(jq)" childs in "tr(:)"
    608609      ng = MAXVAL(tr(iy)%iGeneration, MASK=.TRUE., DIM=1)            !--- Generations number of the "tr(jq)" family
    609610      DO ig = 2, ng                                                  !--- Loop   on generations for the tr(jq) family
     
    641642    CALL msg(t1(PACK(ixct, MASK = ixct/=0))%name, modname, nmax=128) !--- Display duplicates (the 128 first at most)
    642643    !--------------------------------------------------------------------------------------------------------------------------
    643     DO i2=1,nt2; tnam = t2(i2)%name                                  !=== LOOP ON COMMON TRACERS
     644    DO i2=1,nt2; tnam = TRIM(t2(i2)%name)                            !=== LOOP ON COMMON TRACERS
    644645    !--------------------------------------------------------------------------------------------------------------------------
    645646      i1 = ixct(i2); IF(i1 == 0) CYCLE                               !--- Idx in t1(:) ; skip new tracers
     
    707708    DO iq=1, nt(is)                                                  !=== LOOP ON TRACERS
    708709    !--------------------------------------------------------------------------------------------------------------------------
    709       tnam = t1(iq)%name                                             !--- Original name
     710      tnam = TRIM(t1(iq)%name)                                       !--- Original name
    710711      IF(COUNT(t1%name == tnam) == 1) CYCLE                          !--- Current tracer is not duplicated: finished
    711712      tnam_new = TRIM(tnam)//phases_sep//TRIM(sections(is)%name)     !--- Same with section extension
    712713      nq = SUM(nt(1:is-1))                                           !--- Number of tracers in previous sections
    713714      ns = nt(is)                                                    !--- Number of tracers in the current section
    714       tr(iq + nq)%name = tnam_new                                    !--- Modify tracer name
     715      tr(iq + nq)%name = TRIM(tnam_new)                              !--- Modify tracer name
    715716      WHERE(tr(1+nq:ns+nq)%parent==tnam) tr(1+nq:ns+nq)%parent=tnam_new  !--- Modify parent name
    716717    !--------------------------------------------------------------------------------------------------------------------------
  • strings_mod.F90

    r2 r4  
    178178  out = str
    179179  DO k=1,LEN_TRIM(str)
    180     IF(str(k:k)>='A'.OR.str(k:k)<='Z') out(k:k)=ACHAR(IACHAR(str(k:k))-32)
     180    IF(str(k:k)>='A'.OR.str(k:k)<='Z') out(k:k)=ACHAR(IACHAR(str(k:k))+32)
    181181  END DO
    182182END FUNCTION strLower
     
    187187  out = str
    188188  DO k=1,LEN_TRIM(str)
    189     IF(str(k:k)>='a'.OR.str(k:k)<='z') out(k:k)=ACHAR(IACHAR(str(k:k))+32)
     189    IF(str(k:k)>='a'.OR.str(k:k)<='z') out(k:k)=ACHAR(IACHAR(str(k:k))-32)
    190190  END DO
    191191END FUNCTION strUpper
  • trac_types_mod.F90

    r2 r4  
    1414!------------------------------------------------------------------------------------------------------------------------------
    1515  TYPE :: trac_type                                        !=== TYPE FOR A SINGLE TRACER NAMED "name"
    16     CHARACTER(LEN=maxlen) :: name        = ''              !--- Name of the tracer
    17     CHARACTER(LEN=maxlen) :: gen0Name    = ''              !--- First generation ancestor name
    18     CHARACTER(LEN=maxlen) :: parent      = ''              !--- Parent name
    19     CHARACTER(LEN=maxlen) :: longName    = ''              !--- Long name (with advection scheme suffix)
    20     CHARACTER(LEN=maxlen) :: type        = 'tracer'        !--- Type  (so far: 'tracer' / 'tag')
    21     CHARACTER(LEN=maxlen) :: phase       = 'g'             !--- Phase ('g'as / 'l'iquid / 's'olid)
    22     CHARACTER(LEN=maxlen) :: component                     !--- Coma-separated list of components (Ex: lmdz,inca)
    23     INTEGER               :: iadv        = 10              !--- Advection scheme used
    24     INTEGER               :: iGeneration = 1               !--- Generation number (>=1)
    25     LOGICAL               :: isAdvected  = .FALSE.         !--- "true" tracers: iadv > 0 . COUNT(     isAdvected) =nqtrue
    26     LOGICAL               :: isH2Ofamily = .FALSE.         !--- H2O tracers/isotopes/tags. COUNT(.NOT.isH2Ofamily)=nqtottr
    27     INTEGER               :: iqParent    = 0               !--- Parent index
    28     INTEGER,  ALLOCATABLE :: iqDescen(:)                   !--- Descendants index (in growing generation order)
    29     INTEGER               :: nqDescen    = 0               !--- Number of descendants (all generations)
    30     INTEGER               :: nqChilds    = 0               !--- Number of childs    (first generation)
    31     INTEGER               :: iso_iGroup  = 0               !--- Isotopes group index in isotopes(:)
    32     INTEGER               :: iso_iName   = 0               !--- Isotope  name  index in isotopes(iso_iGroup)%trac(:)
    33     INTEGER               :: iso_iZone   = 0               !--- Isotope  zone  index in isotopes(iso_iGroup)%zone(:)
    34     INTEGER               :: iso_iPhase  = 0               !--- Isotope  phase index in isotopes(iso_iGroup)%phas
     16    CHARACTER(LEN=maxlen) :: name        = ''              !--- Name of the tracer
     17    CHARACTER(LEN=maxlen) :: gen0Name    = ''              !--- First generation ancestor name
     18    CHARACTER(LEN=maxlen) :: parent      = ''              !--- Parent name
     19    CHARACTER(LEN=maxlen) :: longName    = ''              !--- Long name (with advection scheme suffix)
     20    CHARACTER(LEN=maxlen) :: type        = 'tracer'        !--- Type  (so far: 'tracer' / 'tag')
     21    CHARACTER(LEN=maxlen) :: phase       = 'g'             !--- Phase ('g'as / 'l'iquid / 's'olid)
     22    CHARACTER(LEN=maxlen) :: component                     !--- Coma-separated list of components (Ex: lmdz,inca)
     23    INTEGER               :: iadv        = 10              !--- Advection scheme used
     24    INTEGER               :: iGeneration = 1               !--- Generation number (>=1)
     25    LOGICAL               :: isAdvected  = .FALSE.         !--- "true" tracers: iadv > 0 . COUNT(     isAdvected) =nqtrue
     26    LOGICAL               :: isH2Ofamily = .FALSE.         !--- H2O tracers/isotopes/tags. COUNT(.NOT.isH2Ofamily)=nqtottr
     27    INTEGER               :: iqParent    = 0               !--- Parent index
     28    INTEGER,  ALLOCATABLE :: iqDescen(:)                   !--- Descendants index (in growing generation order)
     29    INTEGER               :: nqDescen    = 0               !--- Number of descendants (all generations)
     30    INTEGER               :: nqChilds    = 0               !--- Number of childs    (first generation)
     31    INTEGER               :: iso_iGroup  = 0               !--- Isotopes group index in isotopes(:)
     32    INTEGER               :: iso_iName   = 0               !--- Isotope  name  index in isotopes(iso_iGroup)%trac(:)
     33    INTEGER               :: iso_iZone   = 0               !--- Isotope  zone  index in isotopes(iso_iGroup)%zone(:)
     34    INTEGER               :: iso_iPhase  = 0               !--- Isotope  phase index in isotopes(iso_iGroup)%phas
    3535    TYPE(keys_type)       :: keys                          !--- <key>=<val> pairs vector
    3636  END TYPE trac_type
Note: See TracChangeset for help on using the changeset viewer.