Changeset 18 for readTracFiles_mod.f90
- Timestamp:
- May 19, 2022, 12:00:22 PM (3 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
readTracFiles_mod.f90
r17 r18 321 321 ky => t(jd)%keys 322 322 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 324 325 END DO 325 326 tt = [t(1:jd-1),t(jd+1:SIZE(t))]; CALL MOVE_ALLOC(FROM=tt, TO=t) !--- Remove the virtual tracer named "defName" … … 413 414 ttr(i)%name = TRIM(ta(itr)) 414 415 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) 416 420 END DO 417 421 END DO … … 863 867 !=== NOTES: ==== 864 868 !=== * Most of the "isot" components have been defined in the calling routine (initIsotopes): ==== 865 !=== parent, nzone, zone(:), niso, keys(:)%name, ntiso, trac(:), nphas, phas, iq TraPha(:,:), itZonPhi(:,:) ====869 !=== parent, nzone, zone(:), niso, keys(:)%name, ntiso, trac(:), nphas, phas, iqIsoPha(:,:), itZonPhi(:,:) ==== 866 870 !=== * Same syntax for isotopes file and "tracer.def": a tracers section contains one line for each of its isotopes ==== 867 871 !=== * Each tracers section can contain a "params" virtual isotope line of isotopes parameters default values ==== … … 983 987 str = PACK(delPhase(t(:)%name), MASK=ll) 984 988 CALL strReduce(str) 985 i%ntiso = i%niso + SIZE(str) !--- Number of isotopes + their geographic tracers [nt raciso]989 i%ntiso = i%niso + SIZE(str) !--- Number of isotopes + their geographic tracers [ntiso] 986 990 ALLOCATE(i%trac(i%ntiso)) 987 991 FORALL(it = 1:i%niso) i%trac(it) = i%keys(it)%name … … 1006 1010 !=== Table used to get iq (index in dyn array, size nqtot) from the isotope and phase indexes ; the full isotopes list 1007 1011 ! (including tagging tracers) is sorted this way: iso1, iso2, ..., iso1_zone1, iso2_zone1, ..., iso1_zoneN, iso2_zoneN 1008 i%iq TraPha = 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)], & 1009 1013 [i%ntiso, i%nphas] ) 1010 1014 !=== Table used to get ix (index in tagging tracers isotopes list, size ntiso) from the zone and isotope indexes … … 1400 1404 CHARACTER(LEN=maxlen), ALLOCATABLE :: tmp(:) 1401 1405 INTEGER :: ix, ip, it, nt 1402 LOGICAL :: lerr 1406 LOGICAL :: lerr, lH2O 1403 1407 newName = oldName 1404 1408 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 1406 1416 lerr = strParse(oldName, '_', tmp, n=nt) 1407 1417 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.