Changeset 5475 for LMDZ6/trunk/libf/phylmd
- Timestamp:
- Jan 15, 2025, 12:23:34 AM (6 weeks ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
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.