Changeset 5791 for LMDZ6/branches/contrails/libf/dyn3d_common/infotrac.f90
- Timestamp:
- Jul 28, 2025, 7:23:15 PM (6 days ago)
- Location:
- LMDZ6/branches/contrails
- Files:
-
- 2 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/contrails
- Property svn:mergeinfo changed
/LMDZ6/trunk merged: 5654-5683,5685-5690,5692-5715,5718-5721,5726-5727,5729,5744-5761,5763-5778,5780,5785-5789
- Property svn:mergeinfo changed
-
LMDZ6/branches/contrails/libf/dyn3d_common/infotrac.f90
r5618 r5791 3 3 MODULE infotrac 4 4 5 USE strings_mod, ONLY: msg, maxlen, cat, dispTable, int2str, bool2str, strStack, strParse, strCount, strIdx6 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, oldHNO35 USE strings_mod, ONLY: msg, maxlen, cat, dispTable, num2str, strStack, strParse, strCount, strIdx, maxTableWidth 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, newHNO3, & 9 niso, ntiso, nzone, nphas, isoF=>isoFamilies,iqIsoPha, iqWIsoPha, ixIso, oldHNO3, new2oldH2O 10 10 IMPLICIT NONE 11 11 … … 22 22 !=== FOR ISOTOPES: General 23 23 PUBLIC :: isot_type, nbIso !--- Derived type, full isotopes families database + nb of families 24 PUBLIC :: isoSelect, ixIso !--- Isotopes familyselection tool + selected family index24 PUBLIC :: isoSelect, ixIso, isoFamilies !--- Isotopes families selection tool + selected family index 25 25 !=== FOR ISOTOPES: Specific to water 26 26 PUBLIC :: iH2O !--- Value of "ixIso" for "H2O" isotopes class … … 81 81 ! | iso_iName | Isotope name index in isotopes(iso_iGroup)%trac(:) | iso_indnum | 1:niso | 82 82 ! | iso_iZone | Isotope zone index in isotopes(iso_iGroup)%zone(:) | zone_num | 1:nzone | 83 ! | iso_iPhas 83 ! | iso_iPhase | Isotope phase index in isotopes(iso_iGroup)%phas(:) | phase_num | 1:nphas | 84 84 ! +-------------+------------------------------------------------------+-------------+------------------------+ 85 85 ! … … 98 98 ! +-----------------+--------------------------------------------------+--------------------+-----------------+ 99 99 100 !=== THRESHOLDS FOR WATER 100 101 REAL, PARAMETER :: min_qParent = 1.e-30, min_qMass = 1.e-18, min_ratio = 1.e-16 ! MVals et CRisi 101 102 102 !=== DIMENSIONS OF THE TRACERS TABLES AND OTHER SCALAR VARIABLES103 !=== DIMENSIONS OF THE TRACERS TABLES, TRACERS TYPE(S) 103 104 INTEGER, SAVE :: nqtot !--- Tracers nb in dynamics (incl. higher moments + H2O) 104 105 INTEGER, SAVE :: nbtr !--- Tracers nb in physics (excl. higher moments + H2O) … … 111 112 INTEGER, SAVE, ALLOCATABLE :: conv_flg(:), pbl_flg(:) !--- Convection / boundary layer activation (nbtr) 112 113 114 !=== LIST OF DEFINED ISOTOPES FAMILIES 115 CHARACTER(LEN=maxlen), SAVE, ALLOCATABLE :: isoFamilies(:) !--- Generation 0 tracer name for each isotopes family (nbIso) 116 113 117 CONTAINS 114 118 … … 116 120 USE iniprint_mod_h 117 121 USE control_mod, ONLY: planet_type 122 USE ioipsl, ONLY: getin 118 123 USE lmdz_reprobus_wrappers, ONLY: Init_chem_rep_trac 119 124 USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA, CPPKEY_REPROBUS, CPPKEY_STRATAER 120 125 USE dimensions_mod, ONLY: iim, jjm, llm, ndm 121 IMPLICIT NONE126 IMPLICIT NONE 122 127 !============================================================================================================================== 123 128 ! … … 152 157 INTEGER :: nqtrue !--- Tracers nb from tracer.def (no higher order moments) 153 158 INTEGER :: iad !--- Advection scheme number 154 INTEGER :: iq, jq, nt, im, nm, ig!--- Indexes and temporary variables159 INTEGER :: iq, jq, it, nt, im, nm, ig !--- Indexes and temporary variables 155 160 LOGICAL :: lerr 156 161 TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:) … … 256 261 IF( nqtot /= nqtrue ) THEN 257 262 CALL msg('The choice of advection scheme for one or more tracers makes it necessary to add tracers') 258 CALL msg('The number of true tracers is '//TRIM( int2str(nqtrue)))259 CALL msg('The total number of tracers needed is '//TRIM( int2str(nqtot)))263 CALL msg('The number of true tracers is '//TRIM(num2str(nqtrue))) 264 CALL msg('The total number of tracers needed is '//TRIM(num2str(nqtot))) 260 265 END IF 261 266 … … 290 295 IF(iad == -1) CALL abort_gcm(modname, msg1, 1) 291 296 292 !--- SET FIELDS longName andiadv297 !--- SET FIELDS longName AND iadv 293 298 t1%longName = t1%name; IF(iad > 0) t1%longName=TRIM(t1%name)//descrq(iad) 294 299 t1%iadv = iad … … 319 324 ig = t1%iGeneration 320 325 nam = t1%name 321 val = 'iadv='//TRIM( int2str(iad))326 val = 'iadv='//TRIM(num2str(iad)) 322 327 323 328 !--- ONLY TESTED VALUES FOR TRACERS FOR NOW: iadv = 14, 10 (and 0 for non-transported tracers) … … 335 340 END DO 336 341 337 !=== READ PHYSICAL PARAMETERS FOR ISOTOPES ; DONE HERE BECAUSE dynetat0 AND iniacademic NEED "tnat" AND "alpha_ideal" 338 niso = 0; nzone = 0; nphas = nqo; ntiso = 0; isoCheck = .FALSE. 342 !=== DETERMINE ISOTOPES RELATED PARAMETERS ; DEFINE THE EXPLICIT KEYS iso_i* 339 343 IF(processIsotopes()) CALL abort_gcm(modname, 'problem when processing isotopes parameters', 1) 344 iH2O = -1 345 IF(nbIso /= 0) THEN 346 IF(isoSelect('H2O', .TRUE.)) THEN 347 IF(isoSelect(1, .TRUE.)) CALL abort_physic(modname, "Can't select the first isotopes family", 1) 348 ELSE 349 iH2O = ixIso; CALL getin('ok_iso_verif', isotope%check) 350 END IF 351 END IF 352 isoFamilies = isoF(:) 340 353 341 354 !--- Convection / boundary layer activation for all tracers … … 356 369 !=== DISPLAY THE RESULTS 357 370 IF(.NOT..TRUE.) RETURN 358 CALL msg('nqo = '//TRIM( int2str(nqo)), modname)359 CALL msg('nbtr = '//TRIM( int2str(nbtr)), modname)360 CALL msg('nqtrue = '//TRIM( int2str(nqtrue)), modname)361 CALL msg('nqtot = '//TRIM( int2str(nqtot)), modname)362 CALL msg('niso = '//TRIM( int2str(niso)), modname)363 CALL msg('ntiso = '//TRIM( int2str(ntiso)), modname)364 CALL msg('nqCO2 = '//TRIM( int2str(nqCO2)), modname, CPPKEY_INCA)365 CALL msg('nqINCA = '//TRIM( int2str(nqINCA)), modname, CPPKEY_INCA)371 CALL msg('nqo = '//TRIM(num2str(nqo)), modname) 372 CALL msg('nbtr = '//TRIM(num2str(nbtr)), modname) 373 CALL msg('nqtrue = '//TRIM(num2str(nqtrue)), modname) 374 CALL msg('nqtot = '//TRIM(num2str(nqtot)), modname) 375 CALL msg('niso = '//TRIM(num2str(niso)), modname) 376 CALL msg('ntiso = '//TRIM(num2str(ntiso)), modname) 377 CALL msg('nqCO2 = '//TRIM(num2str(nqCO2)), modname, CPPKEY_INCA) 378 CALL msg('nqINCA = '//TRIM(num2str(nqINCA)), modname, CPPKEY_INCA) 366 379 t => tracers 367 380 CALL msg('Information stored in '//TRIM(modname)//': ', modname) … … 374 387 CALL msg('No isotopes identified.', modname, nbIso == 0) 375 388 IF(nbIso == 0) RETURN 376 CALL msg('For isotopes family "H2O":', modname) 377 CALL msg(' isoKeys%name = '//strStack(isoKeys%name), modname) 378 CALL msg(' isoName = '//strStack(isoName), modname) 379 CALL msg(' isoZone = '//strStack(isoZone), modname) 380 CALL msg(' isoPhas = '//TRIM(isoPhas), modname) 389 DO it = 1, nbIso 390 IF(isoSelect(it, .TRUE.)) CALL abort_physic(modname, 'Problem when selecting isotopes class', 1) 391 CALL msg('For isotopes family "'//TRIM(isoFamilies(it))//'":', modname) 392 CALL msg(' isoKeys%name = '//strStack(isoKeys%name), modname) 393 CALL msg(' isoName = '//strStack(isoName), modname) 394 CALL msg(' isoZone = '//strStack(isoZone), modname) 395 CALL msg(' isoPhas = '//TRIM(isoPhas), modname) 396 END DO 397 IF(isoSelect(iH2O, .TRUE.)) lerr = isoSelect(1, .TRUE.) 381 398 382 399 END SUBROUTINE init_infotrac
Note: See TracChangeset
for help on using the changeset viewer.