Changeset 18 for readTracFiles_mod.f90


Ignore:
Timestamp:
May 19, 2022, 12:00:22 PM (3 years ago)
Author:
dcugnet
Message:
  • Replace the "addKey_m" calling in readTracFiles_mod:addDefault with several "addKey_1" callings to avoid a gfortran-specific crash.
  • Replace the derived type constructor usage "keys_type" with individual components evaluation.
  • "iqTraPha" is renamed "iqIsoPha"
  • Corrections in "old2newName" function to take correctly into account tracers different from water with names starting with H2O.
File:
1 edited

Legend:

Unmodified
Added
Removed
  • readTracFiles_mod.f90

    r17 r18  
    321321  ky => t(jd)%keys
    322322  DO k = 1, SIZE(ky%key)                                             !--- Loop on the keys of the tracer named "defName"
    323     CALL addKey_m(ky%key(k), ky%val(k), t(:)%keys)                   !--- Add key to all the tracers (no overwriting)
     323!   CALL addKey_m(ky%key(k), ky%val(k), t(:)%keys)                   !--- Add key to all the tracers (no overwriting)
     324    DO it = 1, SIZE(t); CALL addKey_1(ky%key(k), ky%val(k), t(it)%keys); END DO
    324325  END DO
    325326  tt = [t(1:jd-1),t(jd+1:SIZE(t))]; CALL MOVE_ALLOC(FROM=tt, TO=t)   !--- Remove the virtual tracer named "defName"
     
    413414        ttr(i)%name   = TRIM(ta(itr))
    414415        ttr(i)%parent = TRIM(pa(ipr))
    415         ttr(i)%keys   = keys_type(ta(itr), tr(it)%keys%key, tr(it)%keys%val)
     416        ttr(i)%keys%name = ta(itr)
     417        ttr(i)%keys%key  = tr(it)%keys%key
     418        ttr(i)%keys%val  = tr(it)%keys%val
     419!        ttr(i)%keys   = keys_type(ta(itr), tr(it)%keys%key, tr(it)%keys%val)
    416420      END DO
    417421    END DO
     
    863867!=== NOTES:                                                                                                                ====
    864868!===  * Most of the "isot" components have been defined in the calling routine (initIsotopes):                             ====
    865 !===      parent,  nzone, zone(:),  niso, keys(:)%name,  ntiso, trac(:),  nphas, phas,  iqTraPha(:,:),  itZonPhi(:,:)      ====
     869!===      parent,  nzone, zone(:),  niso, keys(:)%name,  ntiso, trac(:),  nphas, phas,  iqIsoPha(:,:),  itZonPhi(:,:)      ====
    866870!===  * Same syntax for isotopes file and "tracer.def": a tracers section contains one line for each of its isotopes       ====
    867871!===  * Each tracers section can contain a "params" virtual isotope line of isotopes parameters default values             ====
     
    983987    str = PACK(delPhase(t(:)%name), MASK=ll)
    984988    CALL strReduce(str)
    985     i%ntiso = i%niso + SIZE(str)                                     !--- Number of isotopes + their geographic tracers [ntraciso]
     989    i%ntiso = i%niso + SIZE(str)                                     !--- Number of isotopes + their geographic tracers [ntiso]
    986990    ALLOCATE(i%trac(i%ntiso))
    987991    FORALL(it = 1:i%niso) i%trac(it) = i%keys(it)%name
     
    10061010    !=== Table used to get iq (index in dyn array, size nqtot) from the isotope and phase indexes ; the full isotopes list
    10071011    !    (including tagging tracers) is sorted this way:  iso1, iso2, ..., iso1_zone1, iso2_zone1, ..., iso1_zoneN, iso2_zoneN
    1008     i%iqTraPha = RESHAPE( [( (strIdx(t%name,  addPhase(i%trac(it),i%phase(ip:ip))),    it=1, i%ntiso), ip=1, i%nphas)], &
     1012    i%iqIsoPha = RESHAPE( [( (strIdx(t%name,  addPhase(i%trac(it),i%phase(ip:ip))),    it=1, i%ntiso), ip=1, i%nphas)], &
    10091013                         [i%ntiso, i%nphas] )
    10101014    !=== Table used to get ix (index in tagging tracers isotopes list, size ntiso) from the zone and isotope indexes
     
    14001404  CHARACTER(LEN=maxlen), ALLOCATABLE :: tmp(:)
    14011405  INTEGER :: ix, ip, it, nt
    1402   LOGICAL :: lerr
     1406  LOGICAL :: lerr, lH2O
    14031407  newName = oldName
    14041408  IF(PRESENT(iPhase)) iPhase = 1                                               !--- Default: gaseous phase
    1405   IF(oldName(1:MIN(3,LEN_TRIM(oldName))) /= 'H2O') RETURN                      !--- Not a water descendant
     1409  lH2O=.FALSE.
     1410  IF(LEN_TRIM(oldName) > 3) THEN
     1411    lH2O = oldName(1:3)=='H2O' .AND. INDEX(old_phases,oldName(4:4))/=0         !--- H2O<phase>*,  with phase=="v", "l", "i" or "r"
     1412    IF(LEN_TRIM(oldName) > 4) lH2O = lH2O .AND. oldName(5:5) == '_'            !--- H2O<phase>_*, with phase=="v", "l", "i" or "r"
     1413  END IF
     1414  IF(.NOT.lH2O) RETURN
     1415  IF(LEN_TRIM(oldName)>3) THEN; IF(INDEX(old_Phases,oldName(4:4))==0) RETURN; END IF
    14061416  lerr = strParse(oldName, '_', tmp, n=nt)
    14071417  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.