Changeset 5475
- Timestamp:
- Jan 15, 2025, 12:23:34 AM (6 hours ago)
- Location:
- LMDZ6/trunk/libf
- Files:
-
- 2 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/dyn3d_common/infotrac.f90
r5282 r5475 3 3 MODULE infotrac 4 4 5 USE strings_mod, ONLY: msg, fmsg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse6 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, isoCheck9 USE readTracFiles_mod, ONLY:new2oldH2O, newHNO3, oldHNO35 USE strings_mod, ONLY: msg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse, strCount, strIdx 6 USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, tracers, addPhase, addKey, iH2O, & 7 isoSelect, indexUpdate, isot_type, testTracersFiles, isotope, delPhase, getKey, tran0, & 8 isoKeys, isoName, isoZone, isoPhas, processIsotopes, isoCheck, itZonIso, nbIso, & 9 niso, ntiso, nzone, nphas, maxTableWidth, iqIsoPha, iqWIsoPha, ixIso, new2oldH2O, newHNO3, oldHNO3 10 10 IMPLICIT NONE 11 11 … … 30 30 PUBLIC :: isoKeys, isoName, isoZone, isoPhas !--- Isotopes keys & names, tagging zones names, phases 31 31 PUBLIC :: niso, ntiso, nzone, nphas !--- Number of " " 32 PUBLIC :: itZonIso !--- index "it" in "isoName(1:niso)" = f(tagging idx, isotope idx)33 PUBLIC :: iqIsoPha !--- index "iq" in "qx" = f(isotope idx, phase idx)32 PUBLIC :: itZonIso !--- Index "it" in "isoName(1:niso)" = f(tagging idx, isotope idx) 33 PUBLIC :: iqIsoPha !--- Index "iq" in "qx" = f(isotope idx, phase idx) 34 34 PUBLIC :: isoCheck !--- Run isotopes checking routines 35 35 !=== FOR BOTH TRACERS AND ISOTOPES … … 103 103 104 104 !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES 105 INTEGER, SAVE :: nqtot, &!--- Tracers nb in dynamics (incl. higher moments + H2O)106 nbtr, &!--- Tracers nb in physics (excl. higher moments + H2O)107 nqo, &!--- Number of water phases108 nqtottr, &!--- Number of tracers passed to phytrac (TO BE DELETED ?)109 nqCO2!--- Number of tracers of CO2 (ThL)105 INTEGER, SAVE :: nqtot !--- Tracers nb in dynamics (incl. higher moments + H2O) 106 INTEGER, SAVE :: nbtr !--- Tracers nb in physics (excl. higher moments + H2O) 107 INTEGER, SAVE :: nqo !--- Number of water phases 108 INTEGER, SAVE :: nqtottr !--- Number of tracers passed to phytrac (TO BE DELETED ?) 109 INTEGER, SAVE :: nqCO2 !--- Number of tracers of CO2 (ThL) 110 110 CHARACTER(LEN=maxlen), SAVE :: type_trac !--- Keyword for tracers type(s) 111 111 112 112 !=== VARIABLES FOR INCA 113 INTEGER, DIMENSION(:), SAVE, ALLOCATABLE :: & 114 conv_flg, pbl_flg !--- Convection / boundary layer activation (nbtr) 113 INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), pbl_flg(:) !--- Convection / boundary layer activation (nbtr) 115 114 116 115 CONTAINS … … 153 152 CHARACTER(LEN=2) :: suff(9) !--- Suffixes for schemes of order 3 or 4 (Prather) 154 153 CHARACTER(LEN=3) :: descrq(30) !--- Advection scheme description tags 155 CHARACTER(LEN=maxlen) :: msg1, texp, ttp 154 CHARACTER(LEN=maxlen) :: msg1, texp, ttp, nam, val !--- Strings for messages and expanded tracers type 156 155 INTEGER :: fType !--- Tracers description file type ; 0: none 157 156 !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def" 158 157 INTEGER :: nqtrue !--- Tracers nb from tracer.def (no higher order moments) 159 158 INTEGER :: iad !--- Advection scheme number 160 INTEGER :: iq, jq, nt, im, nm 161 LOGICAL :: lerr , ll159 INTEGER :: iq, jq, nt, im, nm, ig !--- Indexes and temporary variables 160 LOGICAL :: lerr 162 161 TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:) 163 162 TYPE(trac_type), POINTER :: t1, t(:) … … 173 172 descrq(30) = 'PRA' 174 173 175 lerr=strParse(type_trac, '|', types_trac, n=nt)176 IF (nt .GT. 1) THEN177 IF (nt .GT. 2) CALL abort_gcm(modname, 'you need to modify type_trac, this version is not supported by lmdz', 1)178 IF (nt .EQ. 2) type_trac=types_trac(2)179 ENDIF180 181 174 CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname) 182 183 175 IF(strCount(type_trac, '|', nt)) CALL abort_gcm(modname, 'Could''nt parse the "type_trac" string with delimiter "|"', 1) 176 IF(nt >= 3) CALL abort_gcm(modname, 'you need to modify type_trac, this version is not supported by lmdz', 1) 177 IF(strParse(type_trac, '|', types_trac, n=nt)) CALL abort_gcm(modname, "couldn't parse "//'"type_trac"', 1) 178 IF(nt == 2) type_trac = types_trac(2) ! TO BE DELETED SOON 179 180 CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname) 181 182 !############################################################################################################################## 183 IF(.TRUE.) THEN !=== SKIPED IF ALREADY DONE IN dyn3d_common/infotrac #### 184 !############################################################################################################################## 184 185 !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION 185 186 msg1 = 'For type_trac = "'//TRIM(type_trac)//'":' … … 197 198 SELECT CASE(type_trac) 198 199 CASE('inca', 'inco') 199 IF (.NOT. CPPKEY_INCA) THEN 200 CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1) 201 END IF 200 IF(.NOT.CPPKEY_INCA) CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1) 202 201 CASE('repr') 203 IF (.NOT. CPPKEY_REPROBUS) THEN 204 CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1) 205 END IF 202 IF(.NOT.CPPKEY_REPROBUS) CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1) 206 203 CASE('coag') 207 IF (.NOT. CPPKEY_STRATAER) THEN 208 CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1) 209 END IF 204 IF(.NOT.CPPKEY_STRATAER) CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1) 210 205 END SELECT 211 212 nqCO2 = COUNT( [type_trac == 'inco', type_trac == 'co2i'] ) 206 !############################################################################################################################## 207 END IF 208 !############################################################################################################################## 213 209 214 210 !============================================================================================================================== 215 211 ! 0) DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE AND READ IT 216 212 !============================================================================================================================== 217 texp = type_trac 213 texp = type_trac !=== EXPANDED (WITH "|" SEPARATOR) "type_trac" 218 214 IF(texp == 'inco') texp = 'co2i|inca' 219 215 IF(texp /= 'lmdz') texp = 'lmdz|'//TRIM(texp) 220 216 IF(testTracersFiles(modname, texp, fType, .TRUE.)) CALL abort_gcm(modname, 'problem with tracers file(s)',1) 221 217 ttp = type_trac; IF(fType /= 1) ttp = texp 222 IF(readTracersFiles(ttp, lRepr=type_trac=='repr')) CALL abort_gcm(modname, 'problem with tracers file(s)',1)223 224 !==============================================================================================================================225 ! 1) Get various numbers: "nqtrue" (first order only tracers), "nqo" (water phases), 'nbtr' (tracers passed to physics), etc.226 !==============================================================================================================================227 218 !--------------------------------------------------------------------------------------------------------------------------- 228 219 IF(fType == 0) CALL abort_gcm(modname, 'Missing "traceur.def", "tracer.def" or "tracer_<keyword>.def tracers file.',1) 229 220 !--------------------------------------------------------------------------------------------------------------------------- 230 IF(fType == 1 .AND. ANY(['inca', 'inco'] == type_trac)) THEN !=== FOUND OLD STYLE INCA "traceur.def" 221 IF(fType == 1 .AND. ANY(['inca', 'inco'] == type_trac)) & !=== FOUND OLD STYLE INCA "traceur.def" 222 CALL abort_gcm(modname, 'retro-compatibility with old-style INCA traceur.def files has been disabled.', 1) 231 223 !--------------------------------------------------------------------------------------------------------------------------- 232 IF (CPPKEY_INCA) THEN 233 nqo = SIZE(tracers) - nqCO2 234 CALL Init_chem_inca_trac(nqINCA) !--- Get nqINCA from INCA 235 nbtr = nqINCA + nqCO2 !--- Number of tracers passed to phytrac 236 nqtrue = nbtr + nqo !--- Total number of "true" tracers 237 IF(ALL([2,3] /= nqo)) CALL abort_gcm(modname, 'Only 2 or 3 water phases allowed ; found nqo='//TRIM(int2str(nqo)), 1) 238 ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA)) 239 ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA), pbl_flg_inca(nqINCA)) 240 CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca) 241 ALLOCATE(ttr(nqtrue)) 242 ttr(1:nqo+nqCO2) = tracers 243 ttr(1 : nqo )%component = 'lmdz' 244 ttr(1+nqo:nqCO2+nqo )%component = 'co2i' 245 ttr(1+nqo+nqCO2:nqtrue)%component = 'inca' 246 ttr(1+nqo :nqtrue)%name = [('CO2 ', iq=1, nqCO2), solsym_inca] 247 ttr(1+nqo+nqCO2:nqtrue)%parent = tran0 248 ttr(1+nqo+nqCO2:nqtrue)%phase = 'g' 249 lerr = getKey('hadv', had, ky=tracers(:)%keys) 250 lerr = getKey('vadv', vad, ky=tracers(:)%keys) 251 hadv(1:nqo+nqCO2) = had(:); hadv(1+nqo+nqCO2:nqtrue) = hadv_inca 252 vadv(1:nqo+nqCO2) = vad(:); vadv(1+nqo+nqCO2:nqtrue) = vadv_inca 253 CALL MOVE_ALLOC(FROM=ttr, TO=tracers) 254 DO iq = 1, nqtrue 255 t1 => tracers(iq) 256 CALL addKey('name', t1%name, t1%keys) 257 CALL addKey('component', t1%component, t1%keys) 258 CALL addKey('parent', t1%parent, t1%keys) 259 CALL addKey('phase', t1%phase, t1%keys) 260 END DO 261 IF(setGeneration(tracers)) CALL abort_gcm(modname,'See above',1) !- SET FIELDS %iGeneration, %gen0Name 262 DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca) 263 END IF 264 !--------------------------------------------------------------------------------------------------------------------------- 265 ELSE !=== OTHER CASES (OLD OR NEW FORMAT, NO INCA MODULE) 266 !--------------------------------------------------------------------------------------------------------------------------- 224 225 !############################################################################################################################## 226 IF(readTracersFiles(ttp, lRepr=type_trac == 'repr')) CALL abort_gcm(modname, 'problem with tracers file(s)',1) 227 !############################################################################################################################## 228 229 !============================================================================================================================== 230 ! 1) Get various numbers: "nqtrue" (first order only tracers), "nqo" (water phases), 'nbtr' (tracers passed to physics), etc. 231 !============================================================================================================================== 267 232 nqtrue = SIZE(tracers) !--- "true" tracers 268 233 nqo = COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%name) == 'H2O') !--- Water phases 269 234 nbtr = nqtrue-COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%gen0Name) == 'H2O') !--- Passed to phytrac 270 235 nqCO2 = COUNT( [type_trac == 'inco', type_trac == 'co2i'] ) 271 IF (CPPKEY_INCA) THEN 236 IF(CPPKEY_INCA) & 272 237 nqINCA = COUNT(tracers(:)%component == 'inca') 273 END IF 238 IF(CPPKEY_REPROBUS) CALL Init_chem_rep_trac(nbtr, nqo, tracers(:)%name) 239 240 !============================================================================================================================== 241 ! 2) Calculate nqtot, number of tracers needed (greater if advection schemes 20 or 30 have been chosen). 242 !============================================================================================================================== 274 243 IF(getKey('hadv', hadv, ky=tracers(:)%keys)) CALL abort_gcm(modname, 'missing key "hadv"', 1) 275 244 IF(getKey('vadv', vadv, ky=tracers(:)%keys)) CALL abort_gcm(modname, 'missing key "vadv"', 1) 276 !---------------------------------------------------------------------------------------------------------------------------277 END IF278 !---------------------------------------------------------------------------------------------------------------------------279 280 IF (CPPKEY_REPROBUS) THEN281 CALL Init_chem_rep_trac(nbtr, nqo, tracers(:)%name)282 END IF283 284 !==============================================================================================================================285 ! 2) Calculate nqtot, number of tracers needed (greater if advection schemes 20 or 30 have been chosen).286 !==============================================================================================================================287 245 DO iq = 1, nqtrue 288 246 IF( hadv(iq)<20 .OR. (ANY(hadv(iq)==[20,30]) .AND. hadv(iq)==vadv(iq)) ) CYCLE … … 359 317 360 318 !=== TEST ADVECTION SCHEME 361 DO iq = 1, nqtot ; t1 => tracers(iq); iad = t1%iadv 319 DO iq = 1, nqtot ; t1 => tracers(iq) 320 iad = t1%iadv 321 ig = t1%iGeneration 322 nam = t1%name 323 val = 'iadv='//TRIM(int2str(iad)) 362 324 363 325 !--- ONLY TESTED VALUES FOR TRACERS FOR NOW: iadv = 14, 10 (and 0 for non-transported tracers) 364 IF(ALL([10,14,0] /= iad)) & 365 CALL abort_gcm(modname, 'Not tested for iadv='//TRIM(int2str(iad))//' ; 10 or 14 only are allowed !', 1) 366 367 !--- ONLY TESTED VALUES FOR PARENTS HAVING CHILDS FOR NOW: iadv = 14, 10 (PARENTS: TRACERS OF GENERATION 1) 368 IF(ALL([10,14] /= iad) .AND. t1%iGeneration == 1 .AND. ANY(tracers(:)%iGeneration > 1)) & 369 CALL abort_gcm(modname, 'iadv='//TRIM(int2str(iad))//' not implemented for parents ; 10 or 14 only are allowed !', 1) 370 371 !--- ONLY TESTED VALUES FOR CHILDS FOR NOW: iadv = 10 (CHILDS: TRACERS OF GENERATION GREATER THAN 1) 372 IF(fmsg('WARNING ! iadv='//TRIM(int2str(iad))//' not implemented for childs. Setting iadv=10 for "'//TRIM(t1%name)//'"',& 373 modname, iad /= 10 .AND. t1%iGeneration > 1)) t1%iadv = 10 374 375 !--- ONLY VALID SCHEME NUMBER FOR WATER VAPOUR: iadv = 14 376 ll = t1%name /= addPhase('H2O','g') 377 IF(fmsg('WARNING ! iadv=14 is valid for water vapour only. Setting iadv=10 for "'//TRIM(t1%name)//'".', & 378 modname, iad == 14 .AND. ll)) t1%iadv = 10 326 IF(ALL([10,14,0] /= iad)) CALL abort_gcm(modname, TRIM(val)//' has not been tested yet ; 10 or 14 only are allowed !', 1) 327 328 !--- ONLY TESTED VALUES SO FAR FOR PARENTS HAVING CHILDREN: iadv = 14, 10 (PARENTS: TRACERS OF GENERATION 0) 329 IF(ALL([10,14] /= iad) .AND. ig == 0 .AND. ANY(tracers(:)%parent==nam)) & 330 CALL abort_gcm(modname, TRIM(val)//' is not implemented for parents ; 10 or 14 only are allowed !', 1) 331 332 !--- ONLY TESTED VALUES SO FAR FOR DESCENDANTS (TRACERS OF GENERATION > 0): iadv = 10 ; WATER VAPOUR: iadv = 14 333 lerr = iad /= 10 .AND. ig > 0; IF(lerr) tracers(iq)%iadv = 10 334 CALL msg('WARNING! '//TRIM(val)// ' not implemented for children. Setting iadv=10 for "'//TRIM(nam)//'"', modname, lerr) 335 lerr = iad == 14 .AND. nam /= addPhase('H2O','g'); IF(lerr) tracers(iq)%iadv = 10 336 CALL msg('WARNING! '//TRIM(val)//' is valid for water vapour only. Setting iadv=10 for "'//TRIM(nam)//'"', modname, lerr) 379 337 END DO 380 338 … … 384 342 385 343 !--- Convection / boundary layer activation for all tracers 386 ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1387 ALLOCATE( pbl_flg(nbtr)); pbl_flg(1:nbtr) = 1344 IF(.NOT.ALLOCATED(conv_flg)) ALLOCATE(conv_flg(nbtr)); conv_flg(1:nbtr) = 1 345 IF(.NOT.ALLOCATED( pbl_flg)) ALLOCATE( pbl_flg(nbtr)); pbl_flg(1:nbtr) = 1 388 346 389 347 !--- Note: nqtottr can differ from nbtr when nmom/=0 … … 393 351 394 352 !=== DISPLAY THE RESULTS 353 IF(.NOT..TRUE.) RETURN 395 354 CALL msg('nqo = '//TRIM(int2str(nqo)), modname) 396 355 CALL msg('nbtr = '//TRIM(int2str(nbtr)), modname) … … 399 358 CALL msg('niso = '//TRIM(int2str(niso)), modname) 400 359 CALL msg('ntiso = '//TRIM(int2str(ntiso)), modname) 401 IF (CPPKEY_INCA) THEN 402 CALL msg('nqCO2 = '//TRIM(int2str(nqCO2)), modname) 403 CALL msg('nqINCA = '//TRIM(int2str(nqINCA)), modname) 404 END IF 360 CALL msg('nqCO2 = '//TRIM(int2str(nqCO2)), modname, CPPKEY_INCA) 361 CALL msg('nqINCA = '//TRIM(int2str(nqINCA)), modname, CPPKEY_INCA) 405 362 t => tracers 406 363 CALL msg('Information stored in '//TRIM(modname)//': ', modname) … … 411 368 t%iso_iName, t%iso_iZone, t%iso_iPhase), nColMax=maxTableWidth, nHead=2, sub=modname)) & 412 369 CALL abort_gcm(modname, "problem with the tracers table content", 1) 413 IF(niso > 0) THEN 414 CALL msg('Where, for isotopes family "'//TRIM(isotope%parent)//'":', modname) 415 CALL msg(' isoKeys%name = '//strStack(isoKeys%name), modname) 416 CALL msg(' isoName = '//strStack(isoName), modname) 417 CALL msg(' isoZone = '//strStack(isoZone), modname) 418 CALL msg(' isoPhas = '//TRIM(isoPhas), modname) 419 ELSE 420 CALL msg('No isotopes identified.', modname) 421 END IF 422 CALL msg('end', modname) 370 CALL msg('No isotopes identified.', modname, nbIso == 0) 371 IF(nbIso == 0) RETURN 372 CALL msg('For isotopes family "H2O":', modname) 373 CALL msg(' isoKeys%name = '//strStack(isoKeys%name), modname) 374 CALL msg(' isoName = '//strStack(isoName), modname) 375 CALL msg(' isoZone = '//strStack(isoZone), modname) 376 CALL msg(' isoPhas = '//TRIM(isoPhas), modname) 423 377 424 378 END SUBROUTINE init_infotrac -
LMDZ6/trunk/libf/phylmd/infotrac_phy.F90
r5474 r5475 3 3 MODULE infotrac_phy 4 4 5 USE strings_mod, ONLY: msg, fmsg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse, strIdx6 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, isoCheck9 USE readTracFiles_mod, ONLY:new2oldH2O5 USE strings_mod, ONLY: msg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse, strCount, strIdx 6 USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, tracers, addPhase, addKey, iH2O, & 7 isoSelect, indexUpdate, isot_type, testTracersFiles, isotope, delPhase, getKey, tran0, & 8 isoKeys, isoName, isoZone, isoPhas, processIsotopes, isoCheck, itZonIso, nbIso, & 9 niso, ntiso, nzone, nphas, maxTableWidth, iqIsoPha, iqWIsoPha, ixIso, new2oldH2O 10 10 IMPLICIT NONE 11 11 … … 108 108 109 109 !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES 110 INTEGER, SAVE :: nqtot!--- Tracers nb in dynamics (incl. higher moments + H2O)111 INTEGER, SAVE :: nbtr!--- Tracers nb in physics (excl. higher moments + H2O)112 INTEGER, SAVE :: nqo!--- Number of water phases113 INTEGER, SAVE :: nqtottr!--- Number of tracers passed to phytrac (TO BE DELETED ?)114 INTEGER, SAVE :: nqCO2!--- Number of tracers of CO2 (ThL)110 INTEGER, SAVE :: nqtot !--- Tracers nb in dynamics (incl. higher moments + H2O) 111 INTEGER, SAVE :: nbtr !--- Tracers nb in physics (excl. higher moments + H2O) 112 INTEGER, SAVE :: nqo !--- Number of water phases 113 INTEGER, SAVE :: nqtottr !--- Number of tracers passed to phytrac (TO BE DELETED ?) 114 INTEGER, SAVE :: nqCO2 !--- Number of tracers of CO2 (ThL) 115 115 CHARACTER(LEN=maxlen), SAVE :: type_trac !--- Keyword for tracers type(s) 116 116 !$OMP THREADPRIVATE(nqtot, nbtr, nqo, nqtottr, nqCO2, type_trac) 117 117 118 118 !=== VARIABLES FOR INCA 119 INTEGER, DIMENSION(:), SAVE, ALLOCATABLE :: conv_flg, pbl_flg!--- Convection / boundary layer activation (nbtr)119 INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), pbl_flg(:) !--- Convection / boundary layer activation (nbtr) 120 120 !$OMP THREADPRIVATE(conv_flg, pbl_flg) 121 121 … … 133 133 USE lmdz_reprobus_wrappers, ONLY: Init_chem_rep_trac 134 134 USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA, CPPKEY_REPROBUS, CPPKEY_STRATAER 135 IMPLICIT NONE 135 USE mod_phys_lmdz_para, ONLY: is_master, is_omp_master 136 IMPLICIT NONE 136 137 !============================================================================================================================== 137 138 ! … … 187 188 CALL getin_p('type_trac',type_trac) 188 189 189 lerr=strParse(type_trac, '|', types_trac, n=nt)190 IF (nt .GT. 1) THEN191 IF (nt .GT. 2) CALL abort_physic(modname, 'you need to modify type_trac, this version is not supported by lmdz', 1)192 IF (nt .EQ. 2) type_trac=types_trac(2)193 ENDIF190 CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname, is_master) 191 IF(strCount(type_trac, '|', nt)) CALL abort_physic(modname, 'Could''nt parse the "type_trac" string with delimiter "|"', 1) 192 IF(nt >= 3) CALL abort_physic(modname, 'you need to modify type_trac, this version is not supported by lmdz', 1) 193 IF(strParse(type_trac, '|', types_trac, n=nt)) CALL abort_physic(modname, "couldn't parse "//'"type_trac"', 1) 194 IF(nt == 2) type_trac = types_trac(2) ! TO BE DELETED SOON 194 195 195 196 CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname) … … 197 198 198 199 !############################################################################################################################## 199 IF(lInit ) THEN!=== SKIPED IF ALREADY DONE IN dyn3d_common/infotrac ####200 IF(lInit .AND. is_master) THEN !=== SKIPED IF ALREADY DONE IN dyn3d_common/infotrac #### 200 201 !############################################################################################################################## 201 202 !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION … … 224 225 !############################################################################################################################## 225 226 226 nqCO2 = COUNT( [type_trac == 'inco', type_trac == 'co2i'] )227 228 227 !============================================================================================================================== 229 228 ! 0) DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE AND READ IT 230 229 !============================================================================================================================== 231 texp = type_trac 230 texp = type_trac !=== EXPANDED (WITH "|" SEPARATOR) "type_trac" 232 231 IF(texp == 'inco') texp = 'co2i|inca' 233 232 IF(texp /= 'lmdz') texp = 'lmdz|'//TRIM(texp) 234 IF(testTracersFiles(modname, texp, fType, lInit )) CALL abort_physic(modname, 'problem with tracers file(s)',1)233 IF(testTracersFiles(modname, texp, fType, lInit.AND.is_master)) CALL abort_physic(modname, 'problem with tracers file(s)',1) 235 234 ttp = type_trac; IF(fType /= 1) ttp = texp 236 237 !##############################################################################################################################238 IF(lInit) THEN239 IF(readTracersFiles(ttp, lRepr=type_trac=='repr')) CALL abort_physic(modname, 'problem with tracers file(s)',1)240 ELSE241 CALL msg('No tracers description file(s) reading needed: already done in the dynamics', modname)242 END IF243 !##############################################################################################################################244 245 !==============================================================================================================================246 ! 1) Get various numbers: "nqtrue" (first order only tracers), "nqo" (water phases), 'nbtr' (tracers passed to physics), etc.247 !==============================================================================================================================248 235 !--------------------------------------------------------------------------------------------------------------------------- 249 236 IF(fType == 0) CALL abort_physic(modname, 'Missing "traceur.def", "tracer.def" or "tracer_<keyword>.def tracers file.',1) 250 237 !--------------------------------------------------------------------------------------------------------------------------- 251 IF(fType == 1 .AND. ANY(['inca', 'inco'] == type_trac) .AND. lInit) THEN !=== FOUND OLD STYLE INCA "traceur.def" 238 IF(fType == 1 .AND. ANY(['inca', 'inco'] == type_trac)) & !=== FOUND OLD STYLE INCA "traceur.def" 239 CALL abort_physic(modname, 'retro-compatibility with old-style INCA traceur.def files has been disabled.', 1) 252 240 !--------------------------------------------------------------------------------------------------------------------------- 253 IF (CPPKEY_INCA) THEN 254 nqo = SIZE(tracers) - nqCO2 255 CALL Init_chem_inca_trac(nqINCA) !--- Get nqINCA from INCA 256 nbtr = nqINCA + nqCO2 !--- Number of tracers passed to phytrac 257 nqtrue = nbtr + nqo !--- Total number of "true" tracers 258 IF(ALL([2,3] /= nqo)) CALL abort_physic(modname, 'Only 2 or 3 water phases allowed ; found nqo='//TRIM(int2str(nqo)), 1) 259 ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA)) 260 ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA), pbl_flg_inca(nqINCA)) 261 CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca) 262 ALLOCATE(ttr(nqtrue)) 263 ttr(1:nqo+nqCO2) = tracers 264 ttr(1 : nqo )%component = 'lmdz' 265 ttr(1+nqo:nqCO2+nqo )%component = 'co2i' 266 ttr(1+nqo+nqCO2:nqtrue)%component = 'inca' 267 ttr(1+nqo :nqtrue)%name = [('CO2 ', iq=1, nqCO2), solsym_inca] 268 ttr(1+nqo+nqCO2:nqtrue)%parent = tran0 269 ttr(1+nqo+nqCO2:nqtrue)%phase = 'g' 270 lerr = getKey('hadv', had, ky=tracers(:)%keys) 271 lerr = getKey('vadv', vad, ky=tracers(:)%keys) 272 hadv(1:nqo+nqCO2) = had(:); hadv(1+nqo+nqCO2:nqtrue) = hadv_inca 273 vadv(1:nqo+nqCO2) = vad(:); vadv(1+nqo+nqCO2:nqtrue) = vadv_inca 274 CALL MOVE_ALLOC(FROM=ttr, TO=tracers) 275 DO iq = 1, nqtrue 276 t1 => tracers(iq) 277 CALL addKey('name', t1%name, t1%keys) 278 CALL addKey('component', t1%component, t1%keys) 279 CALL addKey('parent', t1%parent, t1%keys) 280 CALL addKey('phase', t1%phase, t1%keys) 281 END DO 282 IF(setGeneration(tracers)) CALL abort_physic(modname,'See below',1) !- SET FIELDS %iGeneration, %gen0Name 283 DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca) 284 END IF 285 !--------------------------------------------------------------------------------------------------------------------------- 286 ELSE !=== OTHER CASES (OLD OR NEW FORMAT, NO INCA MODULE) 287 !--------------------------------------------------------------------------------------------------------------------------- 241 242 !############################################################################################################################## 243 IF(lInit) THEN 244 IF(readTracersFiles(ttp, lRepr=type_trac == 'repr')) CALL abort_physic(modname, 'problem with tracers file(s)',1) 245 END IF 246 CALL msg('No tracers description file(s) reading needed: already done', modname, .NOT.lInit.AND.is_master) 247 !############################################################################################################################## 248 249 !============================================================================================================================== 250 ! 1) Get various numbers: "nqtrue" (first order only tracers), "nqo" (water phases), 'nbtr' (tracers passed to physics), etc. 251 !============================================================================================================================== 288 252 nqtrue = SIZE(tracers) !--- "true" tracers 289 253 nqo = COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%name) == 'H2O') !--- Water phases 290 254 nbtr = nqtrue-COUNT(tracers(:)%component == 'lmdz' .AND. delPhase(tracers(:)%gen0Name) == 'H2O') !--- Passed to phytrac 291 255 nqCO2 = COUNT( [type_trac == 'inco', type_trac == 'co2i'] ) 292 IF (CPPKEY_INCA) THEN 256 IF(CPPKEY_INCA) & 293 257 nqINCA = COUNT(tracers(:)%component == 'inca') 294 END IF 258 IF(CPPKEY_REPROBUS) CALL Init_chem_rep_trac(nbtr, nqo, tracers(:)%name) !--- Transfert the number of tracers to Reprobus 259 260 !############################################################################################################################## 261 IF(lInit) THEN !=== SKIPED IF ALREADY DONE IN dyn3d_common/infotrac #### 262 !############################################################################################################################## 263 264 !============================================================================================================================== 265 ! 2) Calculate nqtot, number of tracers needed (greater if advection schemes 20 or 30 have been chosen). 266 !============================================================================================================================== 295 267 IF(getKey('hadv', hadv, ky=tracers(:)%keys)) CALL abort_physic(modname, 'missing key "hadv"', 1) 296 268 IF(getKey('vadv', vadv, ky=tracers(:)%keys)) CALL abort_physic(modname, 'missing key "vadv"', 1) 297 !---------------------------------------------------------------------------------------------------------------------------298 END IF299 !---------------------------------------------------------------------------------------------------------------------------300 301 IF (CPPKEY_REPROBUS) THEN302 CALL Init_chem_rep_trac(nbtr, nqo, tracers(:)%name) !--- Transfert the number of tracers to Reprobus303 END IF304 305 !##############################################################################################################################306 IF(lInit) THEN !=== SKIPED IF ALREADY DONE IN dyn3d_common/infotrac ####307 !##############################################################################################################################308 309 !==============================================================================================================================310 ! 2) Calculate nqtot, number of tracers needed (greater if advection schemes 20 or 30 have been chosen).311 !==============================================================================================================================312 269 DO iq = 1, nqtrue 313 270 IF( hadv(iq)<20 .OR. (ANY(hadv(iq)==[20,30]) .AND. hadv(iq)==vadv(iq)) ) CYCLE … … 415 372 416 373 !=== DISPLAY THE RESULTS 374 IF(.NOT.is_master) RETURN 417 375 CALL msg('nqo = '//TRIM(int2str(nqo)), modname) 418 376 CALL msg('nbtr = '//TRIM(int2str(nbtr)), modname) … … 421 379 CALL msg('niso = '//TRIM(int2str(niso)), modname) 422 380 CALL msg('ntiso = '//TRIM(int2str(ntiso)), modname) 423 IF (CPPKEY_INCA) THEN 424 CALL msg('nqCO2 = '//TRIM(int2str(nqCO2)), modname) 425 CALL msg('nqINCA = '//TRIM(int2str(nqINCA)), modname) 426 END IF 381 CALL msg('nqCO2 = '//TRIM(int2str(nqCO2)), modname, CPPKEY_INCA) 382 CALL msg('nqINCA = '//TRIM(int2str(nqINCA)), modname, CPPKEY_INCA) 427 383 t => tracers 428 384 CALL msg('Information stored in '//TRIM(modname)//': ', modname) … … 434 390 t%iso_iName, t%iso_iZone, t%iso_iPhase), nColMax=maxTableWidth, nHead=2, sub=modname)) & 435 391 CALL abort_physic(modname, "problem with the tracers table content", 1) 436 IF(niso > 0) THEN 437 CALL msg('Where, for isotopes family "'//TRIM(isotope%parent)//'":', modname) 438 CALL msg(' isoKeys%name = '//strStack(isoKeys%name), modname) 439 CALL msg(' isoName = '//strStack(isoName), modname) 440 CALL msg(' isoZone = '//strStack(isoZone), modname) 441 CALL msg(' isoPhas = '//TRIM(isoPhas), modname) 442 ELSE 443 CALL msg('No isotopes identified.', modname) 444 END IF 445 446 #ifdef ISOVERIF 447 CALL msg('iso_iName = '//strStack(int2str(PACK(tracers(:)%iso_iName, MASK=tracers(:)%iso_iGroup==iH2O))), modname) 448 #endif 392 CALL msg('No isotopes identified.', modname, nbIso == 0) 393 IF(nbIso == 0) RETURN 394 CALL msg('For isotopes family "H2O":', modname) 395 CALL msg(' isoKeys%name = '//strStack(isoKeys%name), modname) 396 CALL msg(' isoName = '//strStack(isoName), modname) 397 CALL msg(' isoZone = '//strStack(isoZone), modname) 398 CALL msg(' isoPhas = '//TRIM(isoPhas), modname) 399 449 400 IF(CPPKEY_STRATAER .AND. type_trac == 'coag') THEN 450 401 CALL msg('nbtr_bin ='//TRIM(int2str(nbtr_bin )), modname)
Note: See TracChangeset
for help on using the changeset viewer.