Changeset 5190 for LMDZ6/trunk/libf/dyn3d_common
- Timestamp:
- Sep 15, 2024, 10:38:32 AM (5 months ago)
- Location:
- LMDZ6/trunk/libf/dyn3d_common
- Files:
-
- 2 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/dyn3d_common/infotrac.F90
r5183 r5190 3 3 MODULE infotrac 4 4 5 USE strings_mod, ONLY: msg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse, strCount, strIdx 6 USE readTracFiles_mod, ONLY: readTracersFiles, maxTableWidth, tisot=>isot_type, addPhase, addKey, iH2O, & 7 indexUpdate, keys_type, testTracersFiles, processIsotopes, trac=>tracers, delPhase, getKey, tran0 8 USE readTracFiles_mod, ONLY: new2oldH2O, newHNO3, oldHNO3 9 5 USE strings_mod, ONLY: msg, fmsg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse 6 USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, tracers, setGeneration, itZonIso, nzone, tran0, isoZone, & 7 delPhase, niso, getKey, isot_type, processIsotopes, isotope, maxTableWidth, iqIsoPha, nphas, ixIso, isoPhas, & 8 addPhase, iH2O, addKey, isoSelect, testTracersFiles, isoKeys, indexUpdate, iqWIsoPha, nbIso, ntiso, isoName, isoCheck 10 9 IMPLICIT NONE 11 10 … … 17 16 PUBLIC :: nqtot, nbtr, nqo, nqCO2, nqtottr !--- Main dimensions 18 17 PUBLIC :: conv_flg, pbl_flg !--- Convection & boundary layer activation keys 19 PUBLIC :: new2oldH2O, newHNO3, oldHNO3 !--- For backwards compatibility in dynetat020 PUBLIC :: addPhase, delPhase !--- Add/remove the phase from the name of a tracer21 18 22 19 !=== FOR ISOTOPES: General 23 20 PUBLIC :: isot_type, nbIso !--- Derived type, full isotopes families database + nb of families 24 PUBLIC :: isoSelect, ixIso , isoFamilies !--- Isotopes families selection tool + selected index + list21 PUBLIC :: isoSelect, ixIso !--- Isotopes family selection tool + selected family index 25 22 !=== FOR ISOTOPES: Specific to water 26 PUBLIC :: iH2O !--- Value of "ixIso" for "H2O" isotopes class23 PUBLIC :: iH2O !--- H2O isotopes class index 27 24 PUBLIC :: min_qParent, min_qMass, min_ratio !--- Min. values for various isotopic quantities 28 25 !=== FOR ISOTOPES: Depending on the selected isotopes family 29 PUBLIC :: isotope !--- Selected isotopes database (argument ofgetKey)30 PUBLIC :: iso Keys, isoName, isoZone, isoPhas !--- Isotopes keys & names,tagging zones names, phases31 PUBLIC :: niso, ntiso, nzone, nphas !--- Number of " "32 PUBLIC :: itZonIso !--- i ndex "it" in "isoName(1:niso)" = f(tagging idx, isotope idx)33 PUBLIC :: iqIsoPha !--- i ndex "iq" in "qx" = f(isotope idx, phase idx)26 PUBLIC :: isotope, isoKeys !--- Selected isotopes database + associated keys (cf. getKey) 27 PUBLIC :: isoName, isoZone, isoPhas !--- Isotopes and tagging zones names, phases 28 PUBLIC :: niso, nzone, nphas, ntiso !--- " " numbers + isotopes & tagging tracers number 29 PUBLIC :: itZonIso !--- idx "it" (in "isoName(1:niso)") = function(tagging idx, isotope idx) 30 PUBLIC :: iqIsoPha !--- idx "iq" (in "qx") = function(isotope idx, phase idx) + aliases 34 31 PUBLIC :: isoCheck !--- Run isotopes checking routines 35 32 !=== FOR BOTH TRACERS AND ISOTOPES … … 39 36 ! |--------------------+-----------------------+-----------------+---------------+----------------------------| 40 37 ! | water in different | water tagging | water isotopes | other tracers | additional tracers moments | 41 ! | phases: H2O_[gls rb]| isotopes | | | for higher order schemes |38 ! | phases: H2O_[gls] | isotopes | | | for higher order schemes | 42 39 ! |--------------------+-----------------------+-----------------+---------------+----------------------------| 43 40 ! | | | | | | … … 53 50 ! |-----------------------------------------------------------------------------------------------------------| 54 51 ! NOTES FOR THIS TABLE: 55 ! * Used "niso", "nzone" and "ntiso" are components of "isotopes(ip)" for water (isotopes(ip)% name== 'H2O'),52 ! * Used "niso", "nzone" and "ntiso" are components of "isotopes(ip)" for water (isotopes(ip)%parent == 'H2O'), 56 53 ! since water is so far the sole tracers family, except passive CO2, removed from the main tracers table. 57 54 ! * For water, "nqo" is equal to the more general field "isotopes(ip)%nphas". 58 55 ! * "niso", "nzone", "ntiso", "nphas" are defined for other isotopic tracers families, if any. 59 ! * If you deal with an isotopes family other than "H2O" ("Sulf" in the example), a good practice is to keep 60 ! track of the isotopes class (of its index) before switching to it at the beginning of the dedicated code: 61 ! - first time (use selection by name and compute the corresponding index iSulf) : 62 ! i0=ixIso; IF(.NOT.isoSelect('Sulf')) CALL abort_gcm("Can't select isotopes class", modname, 1); iS=ixIso 63 ! - next times (use selection by index - "iS" has been computed at first call): 64 ! i0=ixIso; IF(.NOT.isoSelect(iS)) CALL abort_gcm("Can't select isotopes class", modname, 1) 65 ! and to switch back to the original category when you're done with "Sulf": 66 ! IF(.NOT.isoSelect(i0)) CALL abort_gcm("Can't select isotopes class", modname, 1) 67 ! to restore the original isotopes category (before dealing with "Sulf" (most of the time "H2O"). 68 ! 69 !=== LOCAL DERIVED TYPE "trac_type" EMBEDDING MOST OF THE TRACERS-RELATED QUANTITIES (LENGTH: nqtot) 56 ! 57 !=== DERIVED TYPE EMBEDDING MOST OF THE TRACERS-RELATED QUANTITIES (LENGTH: nqtot) 70 58 ! Each entry is accessible using "%" sign. 71 59 ! |-------------+------------------------------------------------------+-------------+------------------------+ … … 73 61 ! |-------------+------------------------------------------------------+-------------+------------------------+ 74 62 ! | name | Name (short) | tname | | 75 ! | keys | key/val pairs accessible with "getKey" routine | / | |76 63 ! | gen0Name | Name of the 1st generation ancestor | / | | 77 64 ! | parent | Name of the parent | / | | 78 65 ! | longName | Long name (with adv. scheme suffix) for outputs | ttext | | 79 66 ! | type | Type (so far: tracer or tag) | / | tracer,tag | 80 ! | phase | Phases list ("g"as / "l"iquid / "s"olid | | [g|l|s|r|b] | 81 ! | | "r"(cloud) / "b"lowing) | / | | 67 ! | phase | Phases list ("g"as / "l"iquid / "s"olid) | / | [g][l][s] | 82 68 ! | component | Name(s) of the merged/cumulated section(s) | / | coma-separated names | 83 69 ! | iGeneration | Generation (>=1) | / | | … … 86 72 ! | nqDescen | Number of the descendants (all generations) | nqdesc | 1:nqtot | 87 73 ! | nqChildren | Number of childs (1st generation only) | nqfils | 1:nqtot | 74 ! | keys | key/val pairs accessible with "getKey" routine | / | | 88 75 ! | iadv | Advection scheme number | iadv | 1,2,10-20(exc.15,19),30| 76 ! | isAdvected | advected tracers flag (.TRUE. if iadv >= 0) | / | nqtrue .TRUE. values | 77 ! | isInPhysics | tracers not extracted from the main table in physics | / | nqtottr .TRUE. values | 89 78 ! | iso_iGroup | Isotopes group index in isotopes(:) | / | 1:nbIso | 90 79 ! | iso_iName | Isotope name index in isotopes(iso_iGroup)%trac(:) | iso_indnum | 1:niso | … … 98 87 ! | entry | length | Meaning | Former name | Possible values | 99 88 ! |-----------------+--------------------------------------------------+--------------------+-----------------+ 100 ! | name | Name of the isotopes class (family)| | |89 ! | parent | Parent tracer (isotopes family name) | | | 101 90 ! | keys | niso | Isotopes keys/values pairs list + number | | | 102 91 ! | trac | ntiso | Isotopes + tagging tracers list + number | / | ntraciso | | 103 92 ! | zone | nzone | Geographic tagging zones list + number | / | ntraceurs_zone | | 104 ! | phase | nphas | Phases list + number | | [g |l|s|r|b] 1:5|93 ! | phase | nphas | Phases list + number | | [g][l][s], 1:3 | 105 94 ! | iqIsoPha | Index in "qx" = f(name(1:ntiso)),phas) | iqiso | 1:nqtot | 106 95 ! | itZonIso | Index in "trac(1:ntiso)"= f(zone, name(1:niso)) | index_trac | 1:ntiso | 107 96 ! +-----------------+--------------------------------------------------+--------------------+-----------------+ 108 97 109 !------------------------------------------------------------------------------------------------------------------------------110 TYPE :: trac_type !=== TYPE FOR A SINGLE TRACER NAMED "name"111 CHARACTER(LEN=maxlen) :: name = '' !--- Name of the tracer112 TYPE(keys_type) :: keys !--- <key>=<val> pairs vector (general container)113 CHARACTER(LEN=maxlen) :: gen0Name = '' !--- First generation ancestor name114 CHARACTER(LEN=maxlen) :: parent = '' !--- Parent name115 CHARACTER(LEN=maxlen) :: longName = '' !--- Long name (with advection scheme suffix)116 CHARACTER(LEN=maxlen) :: type = 'tracer' !--- Type (so far: 'tracer' / 'tag')117 CHARACTER(LEN=maxlen) :: phase = 'g' !--- Phase ('g'as / 'l'iquid / 's'olid)118 CHARACTER(LEN=maxlen) :: component = '' !--- Coma-separated list of components (Ex: lmdz,inca)119 INTEGER :: iGeneration = -1 !--- Generation number (>=0)120 INTEGER :: iqParent = 0 !--- Parent index121 INTEGER, ALLOCATABLE :: iqDescen(:) !--- Descendants index (in growing generation order)122 INTEGER :: nqDescen = 0 !--- Number of descendants (all generations)123 INTEGER :: nqChildren = 0 !--- Number of children (first generation)124 INTEGER :: iadv = 10 !--- Advection scheme used125 INTEGER :: iso_iGroup = 0 !--- Isotopes group index in isotopes(:)126 INTEGER :: iso_iName = 0 !--- Isotope name index in isotopes(iso_iGroup)%trac(:)127 INTEGER :: iso_iZone = 0 !--- Isotope zone index in isotopes(iso_iGroup)%zone(:)128 INTEGER :: iso_iPhase = 0 !--- Isotope phase index in isotopes(iso_iGroup)%phase129 END TYPE trac_type130 !------------------------------------------------------------------------------------------------------------------------------131 TYPE :: isot_type !=== TYPE FOR THE ISOTOPES FAMILY DESCENDING ON TRACER "name"132 CHARACTER(LEN=maxlen) :: name !--- Isotopes family name (ex: H2O)133 TYPE(keys_type), ALLOCATABLE :: keys(:) !--- Isotopes keys/values pairs list (length: niso)134 LOGICAL :: check=.FALSE. !--- Flag for checking routines triggering135 CHARACTER(LEN=maxlen), ALLOCATABLE :: trac(:) !--- Isotopes + tagging tracers list (length: ntiso)136 CHARACTER(LEN=maxlen), ALLOCATABLE :: zone(:) !--- Geographic tagging zones names list (length: nzone)137 CHARACTER(LEN=maxlen) :: phase = 'g' !--- Phases list: [g|l|s|r|b] (length: nphas)138 INTEGER :: niso = 0 !--- Number of isotopes, excluding tagging tracers139 INTEGER :: ntiso = 0 !--- Number of isotopes, including tagging tracers140 INTEGER :: nzone = 0 !--- Number of geographic tagging zones141 INTEGER :: nphas = 0 !--- Number of phases142 INTEGER, ALLOCATABLE :: iqIsoPha(:,:) !--- Idx in "tracers(1:nqtot)" = f( name(1:ntiso) ,phas)143 INTEGER, ALLOCATABLE :: itZonIso(:,:) !--- Idx in "trac(1:ntiso)" = f(zone,name(1:niso))144 END TYPE isot_type145 !------------------------------------------------------------------------------------------------------------------------------146 INTERFACE isoSelect; MODULE PROCEDURE isoSelectByIndex, isoSelectByName; END INTERFACE isoSelect147 !------------------------------------------------------------------------------------------------------------------------------148 149 !=== THRESHOLDS FOR WATER150 98 REAL, PARAMETER :: min_qParent = 1.e-30, min_qMass = 1.e-18, min_ratio = 1.e-16 ! MVals et CRisi 151 99 152 100 !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES 153 INTEGER, SAVE :: nqtot, &!--- Tracers nb in dynamics (incl. higher moments + H2O)154 nbtr, &!--- Tracers nb in physics (excl. higher moments + H2O)155 nqo, &!--- Number of water phases101 INTEGER, SAVE :: nqtot, & !--- Tracers nb in dynamics (incl. higher moments + H2O) 102 nbtr, & !--- Tracers nb in physics (excl. higher moments + H2O) 103 nqo, & !--- Number of water phases 156 104 nqtottr, & !--- Number of tracers passed to phytrac (TO BE DELETED ?) 157 105 nqCO2 !--- Number of tracers of CO2 (ThL) 158 CHARACTER(LEN=maxlen), SAVE :: type_trac !--- Keyword for tracers type(s) 159 160 !=== NUMBER AND LIST OF DEFINED ISOTOPES FAMILIES 161 INTEGER, SAVE :: nbIso !--- Number of defined isotopes classes 162 CHARACTER(LEN=maxlen), SAVE, ALLOCATABLE :: isoFamilies(:) !--- Generation 0 tracer name for each isotopes family (nbIso) 163 164 !=== QUANTITIES RELATED TO THE CURRENTLY SELECTED ISOTOPES CLASS (USUALLY H2O) 165 TYPE(isot_type), SAVE, POINTER :: isotope !--- Selected isotopes database (=isotopes(ixIso)) 166 TYPE(keys_type), SAVE, POINTER :: isoKeys(:) !--- Database to get isotopes keys using "getKey" (niso) 167 CHARACTER(LEN=maxlen), SAVE, POINTER :: isoName(:), & !--- Isotopes list including tagging tracers, no phase (ntiso) 168 isoZone(:), & !--- Geographic tagging zones list (nzone) 169 isoPhas !--- Used phases names ([g|l|s|r|b]) (nphas) 170 INTEGER, SAVE, POINTER :: itZonIso(:,:), & !--- Idx "it" in isoName(1:niso) = f(tagging idx, isotope idx) 171 iqIsoPha(:,:) !--- Idx "iq" in qx = f(isotope idx, phase idx) 172 INTEGER, SAVE :: ixIso, & !--- Idx in "isoFamilies" of currently selectd class 173 niso, & !--- Number of isotopes 174 ntiso, & !--- Number of isotopes + tagging tracers 175 nzone, & !--- Number of tagging zones 176 nphas !--- Number of phases 177 LOGICAL, SAVE :: isoCheck !--- Isotopes checking routines triggering flag 106 CHARACTER(LEN=maxlen), SAVE :: type_trac !--- Keyword for tracers type 178 107 179 108 !=== VARIABLES FOR INCA 180 INTEGER, DIMENSION(:), SAVE, ALLOCATABLE :: & 181 conv_flg, pbl_flg !--- Convection / boundary layer activation (nbtr) 182 183 !=== TRACERS/ISOTOPES DESCRIPTORS: EFFECTIVE STORAGE (LOCAL DERIVED TYPES) 184 TYPE(trac_type), SAVE, ALLOCATABLE, TARGET :: tracers(:) 185 TYPE(isot_type), SAVE, ALLOCATABLE, TARGET :: isotopes(:) 109 INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), & !--- Convection activation ; needed for INCA (nbtr) 110 pbl_flg(:) !--- Boundary layer activation ; needed for INCA (nbtr) 186 111 187 112 CONTAINS … … 189 114 SUBROUTINE init_infotrac 190 115 USE control_mod, ONLY: planet_type 191 #ifdef CPP_IOIPSL192 USE IOIPSL, ONLY: getin193 #else194 USE ioipsl_getincom, only: getin195 #endif196 #ifdef CPP_PARA197 USE parallel_lmdz, ONLY: is_master198 #endif199 116 #ifdef REPROBUS 200 USE CHEM_REP, ONLY: Init_chem_rep_trac117 USE CHEM_REP, ONLY: Init_chem_rep_trac 201 118 #endif 202 119 IMPLICIT NONE … … 225 142 !------------------------------------------------------------------------------------------------------------------------------ 226 143 ! Local variables 227 INTEGER, ALLOCATABLE :: hadv(:), vadv(:) , itmp(:)!--- Horizontal/vertical transport scheme number144 INTEGER, ALLOCATABLE :: hadv(:), vadv(:) !--- Horizontal/vertical transport scheme number 228 145 #ifdef INCA 229 146 INTEGER, ALLOCATABLE :: had (:), hadv_inca(:), conv_flg_inca(:), &!--- Variables specific to INCA … … 232 149 INTEGER :: nqINCA 233 150 #endif 234 #ifndef CPP_PARA235 LOGICAL :: is_master=.TRUE.236 #endif237 151 CHARACTER(LEN=2) :: suff(9) !--- Suffixes for schemes of order 3 or 4 (Prather) 238 152 CHARACTER(LEN=3) :: descrq(30) !--- Advection scheme description tags 239 CHARACTER(LEN=maxlen) :: msg1, texp, ttp , ky, nam, val!--- Strings for messages and expanded tracers type153 CHARACTER(LEN=maxlen) :: msg1, texp, ttp !--- Strings for messages and expanded tracers type 240 154 INTEGER :: fType !--- Tracers description file type ; 0: none 241 155 !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def" 242 156 INTEGER :: nqtrue !--- Tracers nb from tracer.def (no higher order moments) 243 157 INTEGER :: iad !--- Advection scheme number 244 INTEGER :: iq, jq, it, nt, im, nm, ig !--- Indexes and temporary variables 245 LOGICAL :: lerr, lInit 246 TYPE(keys_type), ALLOCATABLE, TARGET :: tra(:) !--- Tracers descriptor as in readTracFiles_mod 247 TYPE(tisot), ALLOCATABLE :: iso(:) !--- Isotopes descriptor as in readTracFiles_mod 158 INTEGER :: iq, jq, nt, im, nm !--- Indexes and temporary variables 159 LOGICAL :: lerr, ll 248 160 TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:) 249 TYPE(trac_type), POINTER :: t (:), t1250 TYPE(keys_type), POINTER :: k(:)251 CHARACTER(LEN=maxlen), ALLOCATABLE :: types_trac(:) !--- Keywords for tracers type(s), parsed version 161 TYPE(trac_type), POINTER :: t1, t(:) 162 CHARACTER(LEN=maxlen), ALLOCATABLE :: types_trac(:) !--- Keyword for tracers type(s), parsed version 163 252 164 CHARACTER(LEN=*), PARAMETER :: modname="init_infotrac" 253 165 !------------------------------------------------------------------------------------------------------------------------------ … … 259 171 descrq(10:20) = ['VL1','VLP','FH1','FH2','VLH',' ','PPM','PPS','PPP',' ','SLP'] 260 172 descrq(30) = 'PRA' 261 262 CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname, is_master) 263 IF(strCount(type_trac, '|', nt)) CALL abort_gcm(modname, 'Could''nt parse the "type_trac" string with delimiter "|"', 1) 264 IF(nt >= 3) CALL abort_gcm(modname, 'you need to modify type_trac, this version is not supported by lmdz', 1) 265 IF(strParse(type_trac, '|', types_trac, n=nt)) CALL abort_gcm(modname, "couldn't parse "//'"type_trac"', 1) 266 IF(nt == 2) type_trac = types_trac(2) ! TO BE DELETED SOON 267 268 lInit = .NOT.ALLOCATED(trac) 269 270 !############################################################################################################################## 271 IF(lInit .AND. is_master) THEN !=== SKIPED IF ALREADY DONE 272 !############################################################################################################################## 173 174 CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname) 175 176 lerr=strParse(type_trac, '|', types_trac, n=nt) 177 IF (nt .GT. 1) THEN 178 IF (nt .GT. 2) CALL abort_gcm(modname, 'you need to modify type_trac, this version is not supported by lmdz', 1) 179 if (nt .EQ. 2) type_trac=types_trac(2) 180 ENDIF 181 182 183 273 184 !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION 274 185 msg1 = 'For type_trac = "'//TRIM(type_trac)//'":' … … 298 209 #endif 299 210 END SELECT 300 !############################################################################################################################## 301 END IF 302 !############################################################################################################################## 303 304 !============================================================================================================================== 305 ! 0) DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE AND READ IT ; TRANSFER THE NEEDED QUANTITIES TO LOCAL "tracers". 306 !============================================================================================================================== 307 texp = type_trac !=== EXPANDED (WITH "|" SEPARATOR) "type_trac" 211 212 nqCO2 = COUNT( [type_trac == 'inco', type_trac == 'co2i'] ) 213 214 !============================================================================================================================== 215 ! 1) Get the numbers of: true (first order only) tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid) 216 !============================================================================================================================== 217 texp = type_trac !=== EXPANDED VERSION OF "type_trac", WITH "|" SEPARATOR 308 218 IF(texp == 'inco') texp = 'co2i|inca' 309 219 IF(texp /= 'lmdz') texp = 'lmdz|'//TRIM(texp) 310 IF(testTracersFiles(modname, texp, fType, lInit.AND.is_master)) CALL abort_gcm(modname, 'problem with tracers file(s)',1) 220 221 !=== DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE 222 IF(testTracersFiles(modname, texp, fType, .TRUE.)) CALL abort_gcm(modname, 'problem with tracers file(s)',1) 311 223 ttp = type_trac; IF(fType /= 1) ttp = texp 312 !--------------------------------------------------------------------------------------------------------------------------- 313 IF(fType == 0) CALL abort_gcm(modname, 'Missing "traceur.def", "tracer.def" or "tracer_<keyword>.def tracers file.',1) 314 !--------------------------------------------------------------------------------------------------------------------------- 315 IF(fType == 1 .AND. ANY(['inca', 'inco'] == type_trac) .AND. lInit) & !=== FOUND OLD STYLE INCA "traceur.def" 316 CALL abort_gcm(modname, 'retro-compatibility with old-style INCA traceur.def files has been disabled.', 1) 317 !--------------------------------------------------------------------------------------------------------------------------- 318 319 !############################################################################################################################## 320 IF(lInit) THEN 321 IF(readTracersFiles(ttp, tra, type_trac == 'repr')) CALL abort_gcm(modname, 'problem with tracers file(s)',1) 322 ELSE 323 tra = trac 224 225 IF(readTracersFiles(ttp, lRepr=type_trac=='repr')) CALL abort_gcm(modname, 'problem with tracers file(s)',1) 226 !--------------------------------------------------------------------------------------------------------------------------- 227 IF(fType == 0) CALL abort_gcm(modname, 'Missing tracers file: "traceur.def", "tracer.def" or "tracer_<keyword>.def file.',1) 228 !--------------------------------------------------------------------------------------------------------------------------- 229 IF(fType == 1 .AND. ANY(['inca','inco']==type_trac)) THEN !=== FOUND OLD STYLE INCA "traceur.def" 230 !--------------------------------------------------------------------------------------------------------------------------- 231 #ifdef INCA 232 nqo = SIZE(tracers) - nqCO2 233 CALL Init_chem_inca_trac(nqINCA) !--- Get nqINCA from INCA 234 nbtr = nqINCA + nqCO2 !--- Number of tracers passed to phytrac 235 nqtrue = nbtr + nqo !--- Total number of "true" tracers 236 IF(ALL([2,3] /= nqo)) CALL abort_gcm(modname, 'Only 2 or 3 water phases allowed ; found nqo='//TRIM(int2str(nqo)), 1) 237 ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA)) 238 ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA), pbl_flg_inca(nqINCA)) 239 CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca) 240 ALLOCATE(ttr(nqtrue)) 241 ttr(1:nqo+nqCO2) = tracers 242 ttr(1 : nqo )%component = 'lmdz' 243 ttr(1+nqo:nqCO2+nqo )%component = 'co2i' 244 ttr(1+nqo+nqCO2:nqtrue)%component = 'inca' 245 ttr(1+nqo :nqtrue)%name = [('CO2 ', iq=1, nqCO2), solsym_inca] 246 ttr(1+nqo+nqCO2:nqtrue)%parent = tran0 247 ttr(1+nqo+nqCO2:nqtrue)%phase = 'g' 248 lerr = getKey('hadv', had, ky=tracers(:)%keys) 249 lerr = getKey('vadv', vad, ky=tracers(:)%keys) 250 hadv(1:nqo+nqCO2) = had(:); hadv(1+nqo+nqCO2:nqtrue) = hadv_inca 251 vadv(1:nqo+nqCO2) = vad(:); vadv(1+nqo+nqCO2:nqtrue) = vadv_inca 252 CALL MOVE_ALLOC(FROM=ttr, TO=tracers) 253 DO iq = 1, nqtrue 254 t1 => tracers(iq) 255 CALL addKey('name', t1%name, t1%keys) 256 CALL addKey('component', t1%component, t1%keys) 257 CALL addKey('parent', t1%parent, t1%keys) 258 CALL addKey('phase', t1%phase, t1%keys) 259 END DO 260 IF(setGeneration(tracers)) CALL abort_gcm(modname,'See above',1) !- SET FIELDS %iGeneration, %gen0Name 261 DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca) 262 #endif 263 !--------------------------------------------------------------------------------------------------------------------------- 264 ELSE !=== OTHER CASES (OLD OR NEW FORMAT, NO INCA MODULE) 265 !--------------------------------------------------------------------------------------------------------------------------- 266 nqo = COUNT(delPhase(tracers(:)%name) == 'H2O' & 267 .AND. tracers(:)%component == 'lmdz') !--- Number of water phases 268 nqtrue = SIZE(tracers) !--- Total number of "true" tracers 269 nbtr = nqtrue-COUNT(delPhase(tracers(:)%gen0Name) == 'H2O' & 270 .AND. tracers(:)%component == 'lmdz') !--- Number of tracers passed to phytrac 271 #ifdef INCA 272 nqINCA = COUNT(tracers(:)%component == 'inca') 273 #endif 274 lerr = getKey('hadv', hadv, ky=tracers(:)%keys) 275 lerr = getKey('vadv', vadv, ky=tracers(:)%keys) 276 !--------------------------------------------------------------------------------------------------------------------------- 324 277 END IF 325 CALL msg('No tracers description file(s) reading needed: already done', modname, .NOT.lInit.AND.is_master) 326 !############################################################################################################################## 327 328 !--- POPULATE SOME EXPLICIT (ACCESSIBLE THROUGH "%") KEYS OF THE LOCAL TRACERS DESCRIPTION DERIVED TYPE 329 ! To be defined: iqParent, iq/nqDescen, nqChildren (in indexUpdate), longName, iso_i*, iadv (later) 330 ALLOCATE(tracers(SIZE(tra))) 331 DO iq = 1, SIZE(tra); t1 => tracers(iq) 332 t1%keys = tra(iq) 333 msg1 = '" for tracer nr. '//TRIM(int2str(iq)) 334 ky='name '; IF(getKey(ky, t1%name, iq, tra)) CALL abort_gcm(modname, 'No key "'//TRIM(ky)//TRIM(msg1), 1) 335 msg1 = '" for "'//TRIM(t1%name)//'"' 336 ky='gen0Name '; IF(getKey(ky, t1%gen0Name, iq, tra)) CALL abort_gcm(modname, 'No key "'//TRIM(ky)//TRIM(msg1), 1) 337 ky='parent '; IF(getKey(ky, t1%parent, iq, tra)) CALL abort_gcm(modname, 'No key "'//TRIM(ky)//TRIM(msg1), 1) 338 ky='type '; IF(getKey(ky, t1%type, iq, tra)) CALL abort_gcm(modname, 'No key "'//TRIM(ky)//TRIM(msg1), 1) 339 ky='phase '; IF(getKey(ky, t1%phase, iq, tra)) CALL abort_gcm(modname, 'No key "'//TRIM(ky)//TRIM(msg1), 1) 340 ky='component '; IF(getKey(ky, t1%component, iq, tra)) CALL abort_gcm(modname, 'No key "'//TRIM(ky)//TRIM(msg1), 1) 341 ky='iGeneration'; IF(getKey(ky, t1%iGeneration, iq, tra)) CALL abort_gcm(modname, 'No key "'//TRIM(ky)//TRIM(msg1), 1) 342 END DO 343 344 !============================================================================================================================== 345 ! 1) Get various numbers: "nqtrue" (first order only tracers), "nqo" (water phases), 'nbtr' (tracers passed to physics), etc. 346 !============================================================================================================================== 347 nqtrue = SIZE(tracers) !--- "true" tracers 348 nqo = COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%name) == 'H2O') !--- Water phases 349 nbtr = nqtrue-COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%gen0Name) == 'H2O') !--- Passed to phytrac 350 nqCO2 = COUNT( [type_trac == 'inco', type_trac == 'co2i'] ) 351 #ifdef INCA 352 nqINCA = COUNT(tracers(:)%component == 'inca') 353 #endif 278 !--------------------------------------------------------------------------------------------------------------------------- 279 354 280 #ifdef REPROBUS 355 CALL Init_chem_rep_trac(nbtr, nqo, tracers(:)%name) !--- Transfert the number of tracers to Reprobus 356 #endif 357 281 !--- Transfert the number of tracers to Reprobus 282 CALL Init_chem_rep_trac(nbtr, nqo, tracers(:)%name) 283 284 #endif 358 285 !============================================================================================================================== 359 286 ! 2) Calculate nqtot, number of tracers needed (greater if advection schemes 20 or 30 have been chosen). 360 287 !============================================================================================================================== 361 IF(getKey('hadv', hadv, ky=tra)) CALL abort_gcm(modname, 'missing key "hadv"', 1)362 IF(getKey('vadv', vadv, ky=tra)) CALL abort_gcm(modname, 'missing key "vadv"', 1)363 288 DO iq = 1, nqtrue 364 289 IF( hadv(iq)<20 .OR. (ANY(hadv(iq)==[20,30]) .AND. hadv(iq)==vadv(iq)) ) CYCLE … … 378 303 379 304 !============================================================================================================================== 380 ! 3) Determine the advection scheme choice for water and tracers "iadv" and the fields long name .305 ! 3) Determine the advection scheme choice for water and tracers "iadv" and the fields long name, isAdvected. 381 306 ! iadv = 1 "LMDZ-specific humidity transport" (for H2O vapour) LMV 382 307 ! iadv = 2 backward (for H2O liquid) BAK … … 396 321 !============================================================================================================================== 397 322 ALLOCATE(ttr(nqtot)) 398 jq = nqtrue+1 323 jq = nqtrue+1; tracers(:)%iadv = -1 399 324 DO iq = 1, nqtrue 400 325 t1 => tracers(iq) … … 407 332 IF(iad == -1) CALL abort_gcm(modname, msg1, 1) 408 333 409 !--- SET FIELDS longName, iadv 334 !--- SET FIELDS %longName, %iadv, %isAdvected, %isInPhysics 335 t1%longName = t1%name; IF(iad > 0) t1%longName=TRIM(t1%name)//descrq(iad) 410 336 t1%iadv = iad 411 t1%longName = t1%name; IF(iad > 0) t1%longName=TRIM(t1%name)//descrq(iad) 337 t1%isAdvected = iad >= 0 338 t1%isInPhysics= delPhase(t1%gen0Name) /= 'H2O' & 339 .OR. t1%component /= 'lmdz' !=== OTHER EXCEPTIONS TO BE ADDED: CO2i, SURSATURATED WATER CLOUD... 412 340 ttr(iq) = t1 413 341 … … 419 347 ttr(jq+1:jq+nm) = t1 420 348 ttr(jq+1:jq+nm)%name = [ (TRIM(t1%name) //'-'//TRIM(suff(im)), im=1, nm) ] 421 ttr(jq+1:jq+nm)%gen0Name = [ (TRIM(t1%name) //'-'//TRIM(suff(im)), im=1, nm) ]422 349 ttr(jq+1:jq+nm)%parent = [ (TRIM(t1%parent) //'-'//TRIM(suff(im)), im=1, nm) ] 423 350 ttr(jq+1:jq+nm)%longName = [ (TRIM(t1%longName)//'-'//TRIM(suff(im)), im=1, nm) ] 424 351 ttr(jq+1:jq+nm)%iadv = [ (-iad, im=1, nm) ] 352 ttr(jq+1:jq+nm)%isAdvected = [ (.FALSE., im=1, nm) ] 425 353 jq = jq + nm 426 354 END DO … … 428 356 CALL MOVE_ALLOC(FROM=ttr, TO=tracers) 429 357 430 !--- SET FIELDS iqParent, iqDescen, nqDescen, nqChildren 431 IF(indexUpdate(tracers%keys)) CALL abort_gcm(modname, 'problem with tracers indices update', 1) 432 k => tracers(:)%keys 433 DO iq = 1, SIZE(tracers); t1 => tracers(iq); msg1 = '" for "'//TRIM(t1%name)//'"' 434 ky='iqParent '; IF(getKey(ky, t1%iqParent, iq, k)) CALL abort_gcm(modname, 'missing key "'//TRIM(ky)//TRIM(msg1), 1) 435 ky='iqDescen '; IF(getKey(ky, t1%iqDescen, iq, k)) CALL abort_gcm(modname, 'missing key "'//TRIM(ky)//TRIM(msg1), 1) 436 ky='nqDescen '; IF(getKey(ky, t1%nqDescen, iq, k)) CALL abort_gcm(modname, 'missing key "'//TRIM(ky)//TRIM(msg1), 1) 437 ky='nqChildren'; IF(getKey(ky, t1%nqChildren, iq, k)) CALL abort_gcm(modname, 'missing key "'//TRIM(ky)//TRIM(msg1), 1) 358 !--- SET FIELDS %iqParent, %nqChildren, %iGeneration, %iqDescen, %nqDescen 359 IF(indexUpdate(tracers)) CALL abort_gcm(modname, 'problem with tracers indices update', 1) 360 361 !=== TEST ADVECTION SCHEME 362 DO iq=1,nqtot ; t1 => tracers(iq); iad = t1%iadv 363 364 !--- ONLY TESTED VALUES FOR TRACERS FOR NOW: iadv = 14, 10 (and 0 for non-transported tracers) 365 IF(ALL([10,14,0] /= iad)) & 366 CALL abort_gcm(modname, 'Not tested for iadv='//TRIM(int2str(iad))//' ; 10 or 14 only are allowed !', 1) 367 368 !--- ONLY TESTED VALUES FOR PARENTS HAVING CHILDS FOR NOW: iadv = 14, 10 (PARENTS: TRACERS OF GENERATION 1) 369 IF(ALL([10,14] /= iad) .AND. t1%iGeneration == 1 .AND. ANY(tracers(:)%iGeneration > 1)) & 370 CALL abort_gcm(modname, 'iadv='//TRIM(int2str(iad))//' not implemented for parents ; 10 or 14 only are allowed !', 1) 371 372 !--- ONLY TESTED VALUES FOR CHILDS FOR NOW: iadv = 10 (CHILDS: TRACERS OF GENERATION GREATER THAN 1) 373 IF(fmsg('WARNING ! iadv='//TRIM(int2str(iad))//' not implemented for childs. Setting iadv=10 for "'//TRIM(t1%name)//'"',& 374 modname, iad /= 10 .AND. t1%iGeneration > 1)) t1%iadv = 10 375 376 !--- ONLY VALID SCHEME NUMBER FOR WATER VAPOUR: iadv = 14 377 ll = t1%name /= addPhase('H2O','g') 378 IF(fmsg('WARNING ! iadv=14 is valid for water vapour only. Setting iadv=10 for "'//TRIM(t1%name)//'".', & 379 modname, iad == 14 .AND. ll)) t1%iadv = 10 438 380 END DO 439 381 440 !=== TEST ADVECTION SCHEME 441 DO iq = 1, nqtot ; t1 => tracers(iq) 442 iad = t1%iadv 443 ig = t1%iGeneration 444 nam = t1%name 445 val = 'iadv='//TRIM(int2str(iad)) 446 447 !--- ONLY TESTED VALUES FOR TRACERS FOR NOW: iadv = 14, 10 (and 0 for non-transported tracers) 448 IF(ALL([10,14,0] /= iad)) CALL abort_gcm(modname, TRIM(val)//' has not been tested yet ; 10 or 14 only are allowed !', 1) 449 450 !--- ONLY TESTED VALUES SO FAR FOR PARENTS HAVING CHILDREN: iadv = 14, 10 (PARENTS: TRACERS OF GENERATION 0) 451 IF(ALL([10,14] /= iad) .AND. ig == 0 .AND. ANY(tracers(:)%parent==nam)) & 452 CALL abort_gcm(modname, TRIM(val)//' is not implemented for parents ; 10 or 14 only are allowed !', 1) 453 454 !--- ONLY TESTED VALUES SO FAR FOR DESCENDANTS (TRACERS OF GENERATION > 0): iadv = 10 ; WATER VAPOUR: iadv = 14 455 lerr = iad /= 10 .AND. ig > 0; IF(lerr) tracers(iq)%iadv = 10 456 CALL msg('WARNING! '//TRIM(val)// ' not implemented for children. Setting iadv=10 for "'//TRIM(nam)//'"', modname, lerr) 457 lerr = iad == 14 .AND. nam /= addPhase('H2O','g'); IF(lerr) tracers(iq)%iadv = 10 458 CALL msg('WARNING! '//TRIM(val)//' is valid for water vapour only. Setting iadv=10 for "'//TRIM(nam)//'"', modname, lerr) 459 END DO 460 461 !=== DETERMINE ISOTOPES RELATED PARAMETERS ; DEFINE THE EXPLICIT KEYS iso_i* 462 IF(processIsotopes(tracers%keys, iso)) CALL abort_gcm(modname, 'problem while processing isotopes parameters', 1) 463 464 !--- POPULATE SOME EXPLICIT (ACCESSIBLE THROUGH "%") KEYS OF THE LOCAL ISOTOPES DESCRIPTION DERIVED TYPE 465 nbIso = SIZE(iso) 466 ALLOCATE(isotopes(nbIso)) 467 IF(nbIso /= 0) THEN 468 k => tracers(:)%keys 469 IF(getKey('iso_iGroup', itmp, ky=k)) CALL abort_gcm(modname, 'missing key "iso_iGroup"', 1); tracers%iso_iGroup=itmp 470 IF(getKey('iso_iName', itmp, ky=k)) CALL abort_gcm(modname, 'missing key "iso_iName"', 1); tracers%iso_iName =itmp 471 IF(getKey('iso_iZone', itmp, ky=k)) CALL abort_gcm(modname, 'missing key "iso_iZone"', 1); tracers%iso_iZone =itmp 472 IF(getKey('iso_iPhas', itmp, ky=k)) CALL abort_gcm(modname, 'missing key "iso_iPhas"', 1); tracers%iso_iPhase=itmp 473 isotopes(:)%name = iso(:)%name !--- Isotopes family name (ex: H2O) 474 isotopes(:)%phase = iso(:)%phase !--- Phases list: [g][l][s] (length: nphas) 475 isotopes(:)%niso = iso(:)%niso !--- Number of isotopes, excluding tagging tracers 476 isotopes(:)%ntiso = iso(:)%ntiso !--- Number of isotopes, including tagging tracers 477 isotopes(:)%nzone = iso(:)%nzone !--- Number of geographic tagging zones 478 isotopes(:)%nphas = iso(:)%nphas !--- Number of phases 479 isotopes(:)%check = .FALSE. !--- Flag for checking routines triggering 480 CALL getin('ok_iso_verif', isotopes(:)%check) 481 DO it = 1, nbIso 482 isotopes(it)%keys = iso(it)%keys !--- Isotopes keys/values pairs list (length: niso) 483 isotopes(it)%trac = iso(it)%trac !--- Isotopes + tagging tracers list (length: ntiso) 484 isotopes(it)%zone = iso(it)%zone !--- Geographic tagging zones names list (length: nzone) 485 isotopes(it)%iqIsoPha = iso(it)%iqIsoPha(:,:) !--- Idx in "tracers(1:nqtot)" = f(name(1:ntiso)),phas) 486 isotopes(it)%itZonIso = iso(it)%itZonIso(:,:) !--- Idx in "tracers(1:ntiso)" = f( zone,name(1:niso)) 487 END DO 488 IF(isoSelect(1, .TRUE.)) CALL abort_gcm(modname, "Can't select the first isotopes family", 1) 489 IF(.NOT.isoSelect('H2O', .TRUE.)) iH2O = ixIso 490 END IF 491 isoFamilies = isotopes(:)%name 382 !=== READ PHYSICAL PARAMETERS FOR ISOTOPES ; DONE HERE BECAUSE dynetat0 AND iniacademic NEED "tnat" AND "alpha_ideal" 383 niso = 0; nzone = 0; nphas = nqo; ntiso = 0; isoCheck = .FALSE. 384 IF(processIsotopes()) CALL abort_gcm(modname, 'problem when processing isotopes parameters', 1) 492 385 493 386 !--- Convection / boundary layer activation for all tracers 494 IF(.NOT.ALLOCATED(conv_flg))ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1495 IF(.NOT.ALLOCATED( pbl_flg))ALLOCATE( pbl_flg(nbtr)); pbl_flg(1:nbtr) = 1387 ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1 388 ALLOCATE( pbl_flg(nbtr)); pbl_flg(1:nbtr) = 1 496 389 497 390 !--- Note: nqtottr can differ from nbtr when nmom/=0 … … 501 394 502 395 !=== DISPLAY THE RESULTS 503 IF(.NOT.is_master) RETURN504 396 CALL msg('nqo = '//TRIM(int2str(nqo)), modname) 505 397 CALL msg('nbtr = '//TRIM(int2str(nbtr)), modname) … … 513 405 #endif 514 406 t => tracers 515 CALL msg('Information stored in '//TRIM(modname)//': ', modname) 516 IF(dispTable('isssssssiiiiiiiii', ['iq ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp', & 517 'iAdv', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'], & 518 cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component), & 407 CALL msg('Information stored in infotrac :', modname) 408 409 IF(dispTable('isssssssssiiiiiiiii', ['iq ', 'name', 'lNam', 'g0Nm', 'prnt', 'type', 'phas', 'comp', & 410 'isPh', 'isAd', 'iadv', 'iGen', 'iqPr', 'nqDe', 'nqCh', 'iGrp', 'iNam', 'iZon', 'iPha'], & 411 cat(t%name, t%longName, t%gen0Name, t%parent, t%type, t%phase, t%component, bool2str(t%isInPhysics), & 412 bool2str(t%isAdvected)), & 519 413 cat([(iq, iq=1, nqtot)], t%iadv, t%iGeneration, t%iqParent, t%nqDescen, t%nqChildren, t%iso_iGroup, & 520 414 t%iso_iName, t%iso_iZone, t%iso_iPhase), nColMax=maxTableWidth, nHead=2, sub=modname)) & 521 415 CALL abort_gcm(modname, "problem with the tracers table content", 1) 522 CALL msg('No isotopes identified.', modname, nbIso == 0) 523 IF(nbIso == 0) RETURN 524 DO it = 1, nbIso 525 IF(isoSelect(it, .TRUE.)) CALL abort_gcm(modname, 'Problem when selecting isotopes class', 1) 526 CALL msg('For isotopes family "'//TRIM(isoFamilies(it))//'":', modname) 527 CALL msg(' isoName = '//strStack(isotope%trac), modname) 528 CALL msg(' isoZone = '//strStack(isotope%zone), modname) 529 CALL msg(' isoPhas = '// TRIM(isotope%phase), modname) 530 END DO 531 IF(isoSelect('H2O', .TRUE.)) THEN 532 IF(isoSelect(1, .TRUE.)) CALL abort_gcm(modname, 'Problem when selecting isotopes class', 1) 416 IF(niso > 0) THEN 417 CALL msg('Where, for isotopes family "'//TRIM(isotope%parent)//'":', modname) 418 CALL msg(' isoKeys%name = '//strStack(isoKeys%name), modname) 419 CALL msg(' isoName = '//strStack(isoName), modname) 420 CALL msg(' isoZone = '//strStack(isoZone), modname) 421 CALL msg(' isoPhas = '//TRIM(isoPhas), modname) 533 422 ELSE 534 iH2O = ixIso423 CALL msg('No isotopes identified.', modname) 535 424 END IF 536 IF(ALLOCATED(isotope%keys(ixIso)%key)) & 537 CALL msg(' isoKeys('//TRIM(int2str(ixIso))//') = '//TRIM(strStack(isotope%keys(ixIso)%key)), modname) 425 CALL msg('end', modname) 538 426 539 427 END SUBROUTINE init_infotrac 540 428 541 !==============================================================================================================================542 LOGICAL FUNCTION isoSelectByName(iClass, lVerbose) RESULT(lerr)543 IMPLICIT NONE544 CHARACTER(LEN=*), INTENT(IN) :: iClass545 LOGICAL, OPTIONAL, INTENT(IN) :: lVerbose546 INTEGER :: iIso547 LOGICAL :: lV548 lV = .FALSE.; IF(PRESENT(lVerbose)) lV = lVerbose549 iIso = strIdx(isotopes(:)%name, iClass)550 lerr = iIso == 0551 IF(lerr) THEN552 niso = 0; ntiso = 0; nzone = 0; nphas = 0; isoCheck=.FALSE.553 CALL msg('no isotope family named "'//TRIM(iClass)//'"', ll=lV)554 RETURN555 END IF556 lerr = isoSelectByIndex(iIso, lV)557 END FUNCTION isoSelectByName558 !==============================================================================================================================559 LOGICAL FUNCTION isoSelectByIndex(iIso, lVerbose) RESULT(lerr)560 IMPLICIT NONE561 INTEGER, INTENT(IN) :: iIso562 LOGICAL, OPTIONAL, INTENT(IN) :: lVerbose563 LOGICAL :: lV564 lV = .FALSE.; IF(PRESENT(lVerbose)) lV = lVerbose565 lerr = .FALSE.566 IF(iIso == ixIso) RETURN !--- Nothing to do if the index is already OK567 lerr = iIso<=0 .OR. iIso>SIZE(isotopes)568 CALL msg('Inconsistent isotopes family index '//TRIM(int2str(iIso))//': should be > 0 and <= '&569 //TRIM(int2str(SIZE(isotopes)))//'"', ll = lerr .AND. lV)570 IF(lerr) RETURN571 ixIso = iIso !--- Update currently selected family index572 isotope => isotopes(ixIso) !--- Select corresponding component573 isoKeys => isotope%keys; niso = isotope%niso574 isoName => isotope%trac; ntiso = isotope%ntiso575 isoZone => isotope%zone; nzone = isotope%nzone576 isoPhas => isotope%phase; nphas = isotope%nphas577 itZonIso => isotope%itZonIso; isoCheck = isotope%check578 iqIsoPha => isotope%iqIsoPha579 END FUNCTION isoSelectByIndex580 !==============================================================================================================================581 582 429 END MODULE infotrac -
LMDZ6/trunk/libf/dyn3d_common/iso_verif_dyn.F
r5183 r5190 64 64 function iso_verif_aberrant_nostop 65 65 : (x,iso,q,err_msg) 66 #ifdef CPP_IOIPSL 67 USE IOIPSL, ONLY: getin 68 #else 69 USE ioipsl_getincom, ONLY: getin 70 #endif 71 USE iso_params_mod, ONLY: tnat_HDO 66 USE infotrac, ONLY: isoName, getKey 72 67 implicit none 73 68 … … 79 74 ! locals 80 75 real qmin,deltaD 81 real deltaDmax,deltaDmin 76 real deltaDmax,deltaDmin,tnat 82 77 parameter (qmin=1e-11) 83 78 parameter (deltaDmax=200.0,deltaDmin=-999.9) 84 LOGICAL :: ltnat185 LOGICAL, SAVE :: lFirst=.TRUE.86 REAL, SAVE :: tnat87 79 88 80 ! output 89 81 integer iso_verif_aberrant_nostop 90 82 91 IF(lFirst) THEN92 ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1)93 tnat = tnat_HDO; IF(ltnat1) tnat = 1.094 lFirst = .FALSE.95 END IF96 83 iso_verif_aberrant_nostop=0 97 84 98 85 ! verifier que HDO est raisonable 99 86 if (q.gt.qmin) then 87 IF(getKey('tnat', tnat, isoName(iso))) THEN 88 err_msg = 'Missing isotopic parameter "tnat"' 89 iso_verif_aberrant_nostop=1 90 RETURN 91 END IF 100 92 deltaD=(x/q/tnat-1)*1000 101 93 if ((deltaD.gt.deltaDmax).or.(deltaD.lt.deltaDmin)) then
Note: See TracChangeset
for help on using the changeset viewer.