Ignore:
Timestamp:
May 9, 2022, 12:35:40 PM (2 years ago)
Author:
dcugnet
Message:
  • Some variables are renamed or replaced by direct equivalents:
    • iso_indnum -> tracers(:)%iso_iName
    • niso_possibles -> niso
    • iqiso -> iqIsoPha ; index_trac -> itZonIso
    • ok_iso_verif -> isoCheck
    • ntraceurs_zone -> nzone ; ntraciso -> ntiso
    • qperemin -> min_qparent ; masseqmin -> min_qmass ; ratiomin -> min_ratio
  • Some renamed variables are only aliased with the older name (using USE <module>, ONLY: <oldName> => <newName>) in routines where they are repeated many times.
  • Few hard-coded indexes are now computed (examples: ilic, iso, ivap, irneb, iq_vap, iq_liq, iso_H2O, iso_HDO, iso_HTO, iso_O17, iso_O18).
  • The IF(isoCheck) test is now embedded in the check_isotopes_seq and check_isotopes_loc routines (lighter calling).
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/misc/readTracFiles_mod.f90

    r4140 r4143  
    866866!=== NOTES:                                                                                                                ====
    867867!===  * Most of the "isot" components have been defined in the calling routine (initIsotopes):                             ====
    868 !===      parent,  nzone, zone(:),  niso, keys(:)%name,  ntiso, trac(:),  nphas, phas,  iqTraPha(:,:),  itZonPhi(:,:)      ====
     868!===      parent,  nzone, zone(:),  niso, keys(:)%name,  ntiso, trac(:),  nphas, phas,  iqIsoPha(:,:),  itZonPhi(:,:)      ====
    869869!===  * Same syntax for isotopes file and "tracer.def": a tracers section contains one line for each of its isotopes       ====
    870870!===  * Each tracers section can contain a "params" virtual isotope line of isotopes parameters default values             ====
     
    986986    str = PACK(delPhase(t(:)%name), MASK=ll)
    987987    CALL strReduce(str)
    988     i%ntiso = i%niso + SIZE(str)                                     !--- Number of isotopes + their geographic tracers [ntraciso]
     988    i%ntiso = i%niso + SIZE(str)                                     !--- Number of isotopes + their geographic tracers [ntiso]
    989989    ALLOCATE(i%trac(i%ntiso))
    990990    FORALL(it = 1:i%niso) i%trac(it) = i%keys(it)%name
     
    10091009    !=== Table used to get iq (index in dyn array, size nqtot) from the isotope and phase indexes ; the full isotopes list
    10101010    !    (including tagging tracers) is sorted this way:  iso1, iso2, ..., iso1_zone1, iso2_zone1, ..., iso1_zoneN, iso2_zoneN
    1011     i%iqTraPha = RESHAPE( [( (strIdx(t%name,  addPhase(i%trac(it),i%phase(ip:ip))),    it=1, i%ntiso), ip=1, i%nphas)], &
     1011    i%iqIsoPha = RESHAPE( [( (strIdx(t%name,  addPhase(i%trac(it),i%phase(ip:ip))),    it=1, i%ntiso), ip=1, i%nphas)], &
    10121012                         [i%ntiso, i%nphas] )
    10131013    !=== Table used to get ix (index in tagging tracers isotopes list, size ntiso) from the zone and isotope indexes
     
    14071407  IF(PRESENT(iPhase)) iPhase = 1                                               !--- Default: gaseous phase
    14081408  lH2O=.FALSE.
    1409   IF(LEN_TRIM(oldName)>3) THEN
    1410     lH2O = oldName(1:3)=='H2O' .AND. INDEX(old_phases,oldName(4:4))/=0     !---H2O<phase>*, with phase=="v", "l", "i" or "r"
    1411     IF(LEN_TRIM(oldName) > 4) lH2O = lH2O .AND. oldName(5:5)=='_'          !---H2O<phase>_*, with phase=="v", "l", "i" or "r"
     1409  IF(LEN_TRIM(oldName) > 3) THEN
     1410    lH2O = oldName(1:3)=='H2O' .AND. INDEX(old_phases,oldName(4:4))/=0         !--- H2O<phase>*, with phase=="v", "l", "i" or "r"
     1411    IF(LEN_TRIM(oldName) > 4) lH2O = lH2O .AND. oldName(5:5) == '_'            !--- H2O<phase>_*, with phase=="v", "l", "i" or "r"
    14121412  END IF
    14131413  IF(.NOT.lH2O) RETURN
    14141414  IF(LEN_TRIM(oldName)>3) THEN; IF(INDEX(old_Phases,oldName(4:4))==0) RETURN; END IF
    1415 
    1416 
    14171415  lerr = strParse(oldName, '_', tmp, n=nt)
    14181416  ip = strIdx([('H2O'//old_phases(ip:ip), ip=1, nphases)], tmp(1))             !--- Phase index (/=0 if any)
Note: See TracChangeset for help on using the changeset viewer.