Changeset 4389
- Timestamp:
- Jan 23, 2023, 11:28:51 AM (2 years ago)
- Location:
- LMDZ6/trunk/libf
- Files:
-
- 24 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/dyn3d/dynredem.F90
r4170 r4389 167 167 !------------------------------------------------------------------------------- 168 168 USE strings_mod, ONLY: maxlen 169 USE infotrac, ONLY: nqtot, tracers, type s_trac169 USE infotrac, ONLY: nqtot, tracers, type_trac 170 170 USE control_mod 171 171 USE netcdf, ONLY: NF90_OPEN, NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID, & … … 228 228 !--- Tracers in file "start_trac.nc" (added by Anne) 229 229 lread_inca=.FALSE.; fil="start_trac.nc" 230 IF(ANY(type s_trac=='inca') .OR. ANY(types_trac=='inco')) INQUIRE(FILE=fil,EXIST=lread_inca)230 IF(ANY(type_trac == ['inca','inco'])) INQUIRE(FILE=fil,EXIST=lread_inca) 231 231 IF(lread_inca) CALL err(NF90_OPEN(fil,NF90_NOWRITE,nid_trac),"open") 232 232 -
LMDZ6/trunk/libf/dyn3d_common/infotrac.F90
r4358 r4389 4 4 5 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, n bIso, tran0, delPhase, &7 getKey, isot_type, readIsotopesFile, isotope, maxTableWidth, iqIsoPha, ntiso, ixIso, addPhase, &8 indexUpdate, isoSelect, isoPhas, isoZone, isoName, isoKeys, iH2O, isoCheck, nphas, nzone, niso6 USE readTracFiles_mod, ONLY: trac_type, readTracersFiles, tracers, setGeneration, itZonIso, nzone, tran0, isoZone, & 7 delPhase, niso, getKey, isot_type, readIsotopesFile, isotope, maxTableWidth, iqIsoPha, nphas, ixIso, isoPhas, & 8 addPhase, iH2O, nbIso, isoSelect, testTracersFiles, isoKeys, indexUpdate, isoCheck, nzone, ntiso, isoName 9 9 IMPLICIT NONE 10 10 … … 13 13 !=== FOR TRACERS: 14 14 PUBLIC :: init_infotrac !--- Initialization of the tracers 15 PUBLIC :: tracers, type_trac , types_trac!--- Full tracers database, tracers type keyword15 PUBLIC :: tracers, type_trac !--- Full tracers database, tracers type keyword 16 16 PUBLIC :: nqtot, nbtr, nqo, nqCO2, nqtottr !--- Main dimensions 17 17 PUBLIC :: conv_flg, pbl_flg !--- Convection & boundary layer activation keys … … 104 104 nqtottr, & !--- Number of tracers passed to phytrac (TO BE DELETED ?) 105 105 nqCO2 !--- Number of tracers of CO2 (ThL) 106 CHARACTER(LEN=maxlen), SAVE :: type_trac !--- Keyword for tracers type(s) 107 CHARACTER(LEN=maxlen), SAVE, ALLOCATABLE :: types_trac(:) !--- Keyword for tracers type(s), parsed version 106 CHARACTER(LEN=maxlen), SAVE :: type_trac !--- Keyword for tracers type 108 107 109 108 !=== VARIABLES FOR INCA … … 152 151 CHARACTER(LEN=2) :: suff(9) !--- Suffixes for schemes of order 3 or 4 (Prather) 153 152 CHARACTER(LEN=3) :: descrq(30) !--- Advection scheme description tags 154 CHARACTER(LEN=maxlen) :: msg1 !--- String for messages153 CHARACTER(LEN=maxlen) :: msg1, texp, ttp !--- Strings for messages and expanded tracers type 155 154 INTEGER :: fType !--- Tracers description file type ; 0: none 156 155 !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def" … … 158 157 INTEGER :: iad !--- Advection scheme number 159 158 INTEGER :: ic, iq, jq, it, nt, im, nm, iz, k !--- Indexes and temporary variables 160 LOGICAL :: lerr, ll , lRepr159 LOGICAL :: lerr, ll 161 160 CHARACTER(LEN=1) :: p 162 161 TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:) … … 174 173 175 174 CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname) 176 IF(strParse(type_trac, '|', types_trac, n=nt)) CALL abort_gcm(modname,'can''t parse "type_trac = '//TRIM(type_trac)//'"',1) 177 178 !--------------------------------------------------------------------------------------------------------------------------- 179 DO it = 1, nt !--- nt>1=> "type_trac": coma-separated keywords list 180 !--------------------------------------------------------------------------------------------------------------------------- 181 !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION 182 msg1 = 'For type_trac = "'//TRIM(types_trac(it))//'":' 183 SELECT CASE(types_trac(it)) 184 CASE('inca'); CALL msg(TRIM(msg1)//' coupling with INCA chemistry model', modname) 185 CASE('inco'); CALL msg(TRIM(msg1)//' coupling jointly with INCA and CO2 cycle', modname) 186 CASE('repr'); CALL msg(TRIM(msg1)//' coupling with REPROBUS chemistry model', modname) 187 CASE('co2i'); CALL msg(TRIM(msg1)//' you have chosen to run with CO2 cycle', modname) 188 CASE('coag'); CALL msg(TRIM(msg1)//' tracers are treated for COAGULATION tests', modname) 189 CASE('lmdz'); CALL msg(TRIM(msg1)//' tracers are treated in LMDZ only', modname) 190 CASE DEFAULT; CALL abort_gcm(modname,'type_trac='//TRIM(types_trac(it))//' not possible yet.',1) 191 END SELECT 192 193 !--- COHERENCE TEST BETWEEN "type_trac" AND PREPROCESSING KEYS 194 SELECT CASE(types_trac(it)) 195 CASE('inca', 'inco') 175 176 !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION 177 msg1 = 'For type_trac = "'//TRIM(type_trac)//'":' 178 SELECT CASE(type_trac) 179 CASE('inca'); CALL msg(TRIM(msg1)//' coupling with INCA chemistry model', modname) 180 CASE('inco'); CALL msg(TRIM(msg1)//' coupling jointly with INCA and CO2 cycle', modname) 181 CASE('repr'); CALL msg(TRIM(msg1)//' coupling with REPROBUS chemistry model', modname) 182 CASE('co2i'); CALL msg(TRIM(msg1)//' you have chosen to run with CO2 cycle', modname) 183 CASE('coag'); CALL msg(TRIM(msg1)//' tracers are treated for COAGULATION tests', modname) 184 CASE('lmdz'); CALL msg(TRIM(msg1)//' tracers are treated in LMDZ only', modname) 185 CASE DEFAULT; CALL abort_gcm(modname,'type_trac='//TRIM(type_trac)//' not possible yet.',1) 186 END SELECT 187 188 !--- COHERENCE TEST BETWEEN "type_trac" AND PREPROCESSING KEYS 189 SELECT CASE(type_trac) 190 CASE('inca', 'inco') 196 191 #ifndef INCA 197 198 #endif 199 192 CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1) 193 #endif 194 CASE('repr') 200 195 #ifndef REPROBUS 201 202 #endif 203 196 CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1) 197 #endif 198 CASE('coag') 204 199 #ifndef CPP_StratAer 205 CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1) 206 #endif 207 END SELECT 208 209 !--------------------------------------------------------------------------------------------------------------------------- 210 END DO 211 !--------------------------------------------------------------------------------------------------------------------------- 212 213 nqCO2 = COUNT( [ANY(types_trac == 'inco') .OR. (ANY(types_trac == 'co2i') .AND. ANY(types_trac == 'inca'))] ) 200 CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1) 201 #endif 202 END SELECT 203 204 nqCO2 = COUNT( [type_trac == 'inco', type_trac == 'co2i'] ) 214 205 215 206 !============================================================================================================================== 216 207 ! 1) Get the numbers of: true (first order only) tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid) 217 208 !============================================================================================================================== 218 lRepr = ANY(types_trac(:) == 'repr') 219 IF(readTracersFiles(type_trac, fType, lRepr)) CALL abort_gcm(modname, 'problem with tracers file(s)',1) 209 texp = type_trac !=== EXPANDED VERSION OF "type_trac", WITH "|" SEPARATOR 210 IF(texp == 'inco') texp = 'co2i|inca' 211 IF(texp /= 'lmdz') texp = 'lmdz|'//TRIM(texp) 212 213 !=== DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE 214 IF(testTracersFiles(modname, texp, fType, .TRUE.)) CALL abort_gcm(modname, 'problem with tracers file(s)',1) 215 ttp = type_trac; IF(fType /= 1) ttp = texp 216 217 IF(readTracersFiles(ttp, type_trac == 'repr')) CALL abort_gcm(modname, 'problem with tracers file(s)',1) 220 218 !--------------------------------------------------------------------------------------------------------------------------- 221 219 IF(fType == 0) CALL abort_gcm(modname, 'Missing tracers file: "traceur.def", "tracer.def" or "tracer_<keyword>.def file.',1) 222 220 !--------------------------------------------------------------------------------------------------------------------------- 223 IF(fType == 1 .AND. ANY(['inca','inco'] == type_trac)) THEN !=== FOUND OLD STYLE INCA "traceur.def" (single type_trac)221 IF(fType == 1 .AND. ANY(['inca','inco']==type_trac)) THEN !=== FOUND OLD STYLE INCA "traceur.def" 224 222 !--------------------------------------------------------------------------------------------------------------------------- 225 223 #ifdef INCA … … 233 231 CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca) 234 232 ALLOCATE(ttr(nqtrue)) 235 ttr(1:nqo+nqCO2) 236 ttr(1 : nqo )%component 237 ttr(1+nqo:nqCO2+nqo )%component 238 ttr(1+nqo+nqCO2:nqtrue)%component 239 ttr(1+nqo :nqtrue)%name 240 ttr(1+nqo+nqCO2:nqtrue)%parent 241 ttr(1+nqo+nqCO2:nqtrue)%phase 233 ttr(1:nqo+nqCO2) = tracers 234 ttr(1 : nqo )%component = 'lmdz' 235 ttr(1+nqo:nqCO2+nqo )%component = 'co2i' 236 ttr(1+nqo+nqCO2:nqtrue)%component = 'inca' 237 ttr(1+nqo :nqtrue)%name = [('CO2 ', k=1, nqCO2), solsym_inca] 238 ttr(1+nqo+nqCO2:nqtrue)%parent = tran0 239 ttr(1+nqo+nqCO2:nqtrue)%phase = 'g' 242 240 lerr = getKey('hadv', had, ky=tracers(:)%keys) 243 241 lerr = getKey('vadv', vad, ky=tracers(:)%keys) 244 hadv(1:nqo ) = had(:); hadv(nqo+1:nqtrue) = hadv_inca245 vadv(1:nqo ) = vad(:); vadv(nqo+1:nqtrue) = vadv_inca242 hadv(1:nqo+nqCO2) = had(:); hadv(1+nqo+nqCO2:nqtrue) = hadv_inca 243 vadv(1:nqo+nqCO2) = vad(:); vadv(1+nqo+nqCO2:nqtrue) = vadv_inca 246 244 CALL MOVE_ALLOC(FROM=ttr, TO=tracers) 247 CALL setGeneration(tracers) !--- SET FIELDS %iGeneration, %gen0Name245 IF(setGeneration(tracers)) CALL abort_gcm(modname,'See above',1) !- SET FIELDS %iGeneration, %gen0Name 248 246 DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca) 249 247 #endif -
LMDZ6/trunk/libf/dyn3dmem/dynredem_loc.F90
r4172 r4389 176 176 USE mod_hallo 177 177 USE strings_mod, ONLY: maxlen 178 USE infotrac, ONLY: nqtot, tracers, type s_trac178 USE infotrac, ONLY: nqtot, tracers, type_trac 179 179 USE control_mod 180 180 USE netcdf, ONLY: NF90_OPEN, NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID, & … … 243 243 !$OMP MASTER 244 244 fil="start_trac.nc" 245 IF(ANY(type s_trac=='inca') .OR. ANY(types_trac=='inco')) INQUIRE(FILE=fil,EXIST=lread_inca)245 IF(ANY(type_trac == ['inca','inco'])) INQUIRE(FILE=fil,EXIST=lread_inca) 246 246 IF(lread_inca) CALL err(NF90_OPEN(fil,NF90_NOWRITE,nid_trac),"open") 247 247 !$OMP END MASTER -
LMDZ6/trunk/libf/dyn3dmem/leapfrog_loc.F
r4187 r4389 1519 1519 1520 1520 #ifdef INCA 1521 if (ANY(types_trac == 'inca') .OR. 1522 & ANY(types_trac == 'inco')) CALL finalize_inca 1521 if (ANY(type_trac == ['inca','inco'])) CALL finalize_inca 1523 1522 #endif 1524 1523 #ifdef REPROBUS 1525 if ( ANY(types_trac == 'repr')) CALL finalize_reprobus1524 if (type_trac == 'repr') CALL finalize_reprobus 1526 1525 #endif 1527 1526 … … 1569 1568 1570 1569 #ifdef INCA 1571 if (ANY(types_trac == 'inca') .OR. 1572 & ANY(types_trac == 'inco')) CALL finalize_inca 1570 if (ANY(type_trac == ['inca','inco'])) CALL finalize_inca 1573 1571 #endif 1574 1572 #ifdef REPROBUS 1575 if ( ANY(types_trac == 'repr')) CALL finalize_reprobus1573 if (type_trac == 'repr') CALL finalize_reprobus 1576 1574 #endif 1577 1575 … … 1737 1735 1738 1736 #ifdef INCA 1739 if (ANY(types_trac == 'inca') .OR. 1740 & ANY(types_trac == 'inco')) CALL finalize_inca 1737 if (ANY(type_trac == ['inca','inco'])) CALL finalize_inca 1741 1738 #endif 1742 1739 #ifdef REPROBUS 1743 if ( ANY(types_trac == 'repr')) CALL finalize_reprobus1740 if (type_trac == 'repr') CALL finalize_reprobus 1744 1741 #endif 1745 1742 … … 1845 1842 1846 1843 #ifdef INCA 1847 if (ANY(types_trac == 'inca') .OR. 1848 & ANY(types_trac == 'inco')) CALL finalize_inca 1844 if (ANY(type_trac == ['inca','inco'])) CALL finalize_inca 1849 1845 #endif 1850 1846 #ifdef REPROBUS 1851 if ( ANY(types_trac == 'repr')) CALL finalize_reprobus1847 if (type_trac == 'repr') CALL finalize_reprobus 1852 1848 #endif 1853 1849 -
LMDZ6/trunk/libf/dynphy_lonlat/phylmd/ce0l.F90
r4361 r4389 23 23 USE netcdf, ONLY: NF90_OPEN, NF90_NOWRITE, NF90_CLOSE, NF90_NOERR, & 24 24 NF90_INQUIRE_DIMENSION, NF90_INQ_DIMID, NF90_INQ_VARID, NF90_GET_VAR 25 USE infotrac, ONLY: type_trac,init_infotrac25 USE infotrac, ONLY: init_infotrac 26 26 USE dimphy, ONLY: klon 27 27 USE test_disvert_m, ONLY: test_disvert -
LMDZ6/trunk/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90
r4358 r4389 16 16 USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid) 17 17 USE vertical_layers_mod, ONLY : init_vertical_layers 18 USE infotrac, ONLY: nbtr, type_trac , types_trac18 USE infotrac, ONLY: nbtr, type_trac 19 19 #ifdef CPP_StratAer 20 20 USE infotrac_phy, ONLY: nbtr_bin, nbtr_sulgas, id_OCS_strat, & … … 140 140 141 141 ! Initializations for Reprobus 142 IF ( ANY(types_trac == 'repr')) THEN142 IF (type_trac == 'repr') THEN 143 143 #ifdef REPROBUS 144 144 call Init_chem_rep_phys(klon_omp,nlayer) … … 151 151 152 152 153 IF ( ANY(types_trac == 'repr')) THEN153 IF (type_trac == 'repr') THEN 154 154 #ifdef REPROBUS 155 155 call init_reprobus_para( & … … 166 166 END IF 167 167 168 IF (ANY(type s_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN168 IF (ANY(type_trac == ['inca','inco'])) THEN 169 169 #ifdef INCA 170 170 CALL init_inca_dim_reg(nbp_lon, nbp_lat - 1, & -
LMDZ6/trunk/libf/misc/readTracFiles_mod.f90
r4367 r4389 179 179 ! * If you need to convert a %key/%val pair into a direct-access key, add the corresponding line in "setDirectKeys". 180 180 !============================================================================================================================== 181 LOGICAL FUNCTION readTracersFiles(type_trac, fTyp,lRepr) RESULT(lerr)181 LOGICAL FUNCTION readTracersFiles(type_trac, lRepr) RESULT(lerr) 182 182 !------------------------------------------------------------------------------------------------------------------------------ 183 183 CHARACTER(LEN=*), INTENT(IN) :: type_trac !--- List of components used 184 INTEGER, OPTIONAL, INTENT(OUT) :: fTyp !--- Type of input file found185 184 LOGICAL, OPTIONAL, INTENT(IN) :: lRepr !--- Activate the HNNO3 exceptions for REPROBUS 186 185 CHARACTER(LEN=maxlen), ALLOCATABLE :: s(:), sections(:), trac_files(:) … … 196 195 197 196 !--- Required sections + corresponding files names (new style single section case) for tests 198 IF(test(testTracersFiles(modname, type_trac, fType, .TRUE., trac_files, sections), lerr)) RETURN 199 IF(PRESENT(fTyp)) fTyp = fType 197 IF(test(testTracersFiles(modname, type_trac, fType, .FALSE., trac_files, sections), lerr)) RETURN 200 198 nsec = SIZE(sections) 201 199 … … 290 288 CHARACTER(LEN=*), INTENT(IN) :: modname, type_trac 291 289 INTEGER, INTENT(OUT) :: fType 292 LOGICAL, 290 LOGICAL, OPTIONAL, INTENT(IN) :: lDisp 293 291 CHARACTER(LEN=maxlen), ALLOCATABLE, OPTIONAL, INTENT(OUT) :: tracf(:), sects(:) 294 292 CHARACTER(LEN=maxlen), ALLOCATABLE :: trac_files(:), sections(:) 295 293 LOGICAL, ALLOCATABLE :: ll(:) 294 LOGICAL :: lD 296 295 INTEGER :: is, nsec 297 298 !--- PARSE "type_trac" LIST AND DETERMINE THE TRACERS FILES NAMES (FOR CASE 3: MULTIPLE FILES, SINNGLE SECTION PER FILE) 296 lD = .FALSE.; IF(PRESENT(lDisp)) lD = lDisp 297 lerr = .FALSE. 298 299 !--- PARSE "type_trac" LIST AND DETERMINE THE TRACERS FILES NAMES (FOR CASE 3: MULTIPLE FILES, SINGLE SECTION PER FILE) 300 !--- If type_trac is a scalar (case 1), "sections" and "trac_files" are not usable, but are meaningless for case 1 anyway. 299 301 IF(test(strParse(type_trac, '|', sections, n=nsec), lerr)) RETURN !--- Parse "type_trac" list 300 302 IF(PRESENT(sects)) sects = sections 301 303 ALLOCATE(trac_files(nsec)); DO is=1, nsec; trac_files(is) = 'tracer_'//TRIM(sections(is))//'.def'; END DO 302 304 IF(PRESENT(tracf)) tracf = trac_files 303 304 nsec = SIZE(trac_files, DIM=1)305 305 ll = .NOT.testFile(trac_files) 306 306 fType = 0 307 IF(.NOT.testFile('traceur.def') .AND. nsec==1) fType = 1!--- OLD STYLE FILE308 IF(.NOT.testFile('tracer.def')) fType = 2!--- NEW STYLE ; SINGLE FILE, SEVERAL SECTIONS309 IF(ALL(ll)) fType = 3!--- NEW STYLE ; SEVERAL FILES, SINGLE SECTION USED310 IF(.NOT. test(lDisp, lerr)) RETURN!--- NO CHECKING/DISPLAY NEEDED: JUST GET type_trac,fType307 IF(.NOT.testFile('traceur.def')) fType = 1 !--- OLD STYLE FILE 308 IF(.NOT.testFile('tracer.def')) fType = 2 !--- NEW STYLE ; SINGLE FILE, SEVERAL SECTIONS 309 IF(ALL(ll)) fType = 3 !--- NEW STYLE ; SEVERAL FILES, SINGLE SECTION USED 310 IF(.NOT.lD) RETURN !--- NO CHECKING/DISPLAY NEEDED: JUST GET type_trac,fType 311 311 IF(ANY(ll) .AND. fType/=3) THEN !--- MISSING FILES 312 312 IF(test(checkList(trac_files, .NOT.ll, 'Failed reading tracers description', 'files', 'missing'), lerr)) RETURN 313 313 END IF 314 315 !--- CHECK WHETHER type_trac AND FILE TYPE ARE COMPATIBLE316 IF(test(fmsg('No multiple sections for the old format "traceur.def"', ll = nsec>1 .AND. fType==1), lerr)) RETURN317 314 318 315 !--- TELLS WHAT WAS IS ABOUT TO BE USED -
LMDZ6/trunk/libf/phy_common/physics_distribution_mod.F90
r4263 r4389 13 13 USE mod_grid_phy_lmdz, ONLY: init_grid_phy_lmdz 14 14 USE dimphy, ONLY : Init_dimphy 15 USE infotrac_phy, ONLY : type s_trac15 USE infotrac_phy, ONLY : type_trac 16 16 #ifdef REPROBUS 17 17 USE CHEM_REP, ONLY : Init_chem_rep_phys … … 39 39 #ifdef REPROBUS 40 40 ! Initialization of Reprobus 41 IF ( ANY(types_trac == 'repr')) CALL Init_chem_rep_phys(klon_omp,nbp_lev)41 IF (type_trac == 'repr') CALL Init_chem_rep_phys(klon_omp,nbp_lev) 42 42 #endif 43 43 … … 50 50 ! USE mod_grid_phy_lmdz, ONLY: Init_grid_phy_lmdz!, nbp_lev 51 51 ! USE dimphy, ONLY : Init_dimphy 52 ! USE infotrac_phy, ONLY : type s_trac52 ! USE infotrac_phy, ONLY : type_trac 53 53 !#ifdef REPROBUS 54 54 ! USE CHEM_REP, ONLY : Init_chem_rep_phys … … 71 71 !#ifdef REPROBUS 72 72 !! Initialization of Reprobus 73 ! IF ( ANY(types_trac == 'repr')) CALL Init_chem_rep_phys(klon_omp,nbp_lev)73 ! IF (type_trac == 'repr') CALL Init_chem_rep_phys(klon_omp,nbp_lev) 74 74 ! END IF 75 75 !#endif -
LMDZ6/trunk/libf/phydev/infotrac_phy.F90
r4244 r4389 7 7 INTEGER, SAVE :: nqtot !--- Tracers nb in dynamics (incl. higher moments + H2O) 8 8 CHARACTER(LEN=maxlen), SAVE :: type_trac !--- Keyword for tracers type 9 CHARACTER(LEN=maxlen), SAVE, ALLOCATABLE :: types_trac(:) !--- Parsed version (one or several components name(s)) 10 !$OMP THREADPRIVATE(nqtot, type_trac, types_trac) 9 !$OMP THREADPRIVATE(nqtot, type_trac) 11 10 12 11 CONTAINS 13 12 14 13 SUBROUTINE init_infotrac_phy(nqtot_, type_trac_) 15 USE strings_mod, ONLY: strParse16 14 IMPLICIT NONE 17 15 INTEGER, INTENT(IN) :: nqtot_ … … 20 18 21 19 nqtot = nqtot_ 22 IF(strParse(type_trac, '|', types_trac)) CALL abort_physic(modname,'can''t parse "type_trac = '//TRIM(type_trac)//'"',1)23 20 type_trac = type_trac_ 24 21 -
LMDZ6/trunk/libf/phylmd/Dust/phys_output_write_spl_mod.F90
r4160 r4389 381 381 USE pbl_surface_mod, ONLY: snow 382 382 USE indice_sol_mod, ONLY: nbsrf 383 USE infotrac, ONLY: nqtot, nbtr, tracers , type_trac383 USE infotrac, ONLY: nqtot, nbtr, tracers 384 384 USE geometry_mod, ONLY: cell_area 385 385 USE surface_data, ONLY: type_ocean, version_ocean, ok_veget, landice_opt -
LMDZ6/trunk/libf/phylmd/infotrac_phy.F90
r4358 r4389 13 13 !=== FOR TRACERS: 14 14 PUBLIC :: init_infotrac_phy !--- Initialization of the tracers 15 PUBLIC :: tracers, type_trac , types_trac!--- Full tracers database, tracers type keyword15 PUBLIC :: tracers, type_trac !--- Full tracers database, tracers type keyword 16 16 PUBLIC :: nqtot, nbtr, nqo, nqCO2, nqtottr !--- Main dimensions 17 17 PUBLIC :: conv_flg, pbl_flg !--- Convection & boundary layer activation keys … … 104 104 nqCO2 !--- Number of tracers of CO2 (ThL) 105 105 CHARACTER(LEN=maxlen), SAVE :: type_trac !--- Keyword for tracers type(s) 106 CHARACTER(LEN=maxlen), SAVE, ALLOCATABLE :: types_trac(:) !--- Keyword for tracers type(s), parsed version 107 !$OMP THREADPRIVATE(nqtot, nbtr, nqo, nqtottr, nqCO2, type_trac, types_trac) 106 !$OMP THREADPRIVATE(nqtot, nbtr, nqo, nqtottr, nqCO2, type_trac) 108 107 109 108 !=== VARIABLES FOR INCA … … 164 163 CHARACTER(LEN=2) :: suff(9) !--- Suffixes for schemes of order 3 or 4 (Prather) 165 164 CHARACTER(LEN=3) :: descrq(30) !--- Advection scheme description tags 166 CHARACTER(LEN=maxlen) :: msg1 !--- String for messages165 CHARACTER(LEN=maxlen) :: msg1, texp, ttp !--- String for messages and expanded tracers type 167 166 INTEGER :: fType !--- Tracers description file type ; 0: none 168 167 !--- 1/2/3: "traceur.def"/"tracer.def"/"tracer_*.def" … … 170 169 INTEGER :: iad !--- Advection scheme number 171 170 INTEGER :: ic, iq, jq, it, nt, im, nm, iz, k !--- Indexes and temporary variables 172 LOGICAL :: lerr, ll, l Repr, lInit171 LOGICAL :: lerr, ll, lInit 173 172 CHARACTER(LEN=1) :: p 174 173 TYPE(trac_type), ALLOCATABLE, TARGET :: ttr(:) … … 181 180 !------------------------------------------------------------------------------------------------------------------------------ 182 181 suff = ['x ','y ','z ','xx','xy','xz','yy','yz','zz'] 182 descrq( 1:30) = ' ' 183 183 descrq( 1: 2) = ['LMV','BAK'] 184 184 descrq(10:20) = ['VL1','VLP','FH1','FH2','VLH',' ','PPM','PPS','PPP',' ','SLP'] … … 187 187 CALL getin_p('type_trac',type_trac) 188 188 CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname) 189 IF(strParse(type_trac, '|', types_trac, n=nt)) CALL abort_gcm(modname,'can''t parse "type_trac = '//TRIM(type_trac)//'"',1)190 189 lInit = .NOT.ALLOCATED(tracers) 191 190 … … 193 192 IF(lInit) THEN !=== SKIPED IF ALREADY DONE IN dyn3d_common/infotrac #### 194 193 !############################################################################################################################## 195 !--------------------------------------------------------------------------------------------------------------------------- 196 DO it = 1, nt !--- nt>1=> "type_trac": coma-separated keywords list 197 !--------------------------------------------------------------------------------------------------------------------------- 198 !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION 199 msg1 = 'For type_trac = "'//TRIM(types_trac(it))//'":' 200 SELECT CASE(types_trac(it)) 201 CASE('inca'); CALL msg(TRIM(msg1)//' coupling with INCA chemistry model', modname) 202 CASE('inco'); CALL msg(TRIM(msg1)//' coupling jointly with INCA and CO2 cycle', modname) 203 CASE('repr'); CALL msg(TRIM(msg1)//' coupling with REPROBUS chemistry model', modname) 204 CASE('co2i'); CALL msg(TRIM(msg1)//' you have chosen to run with CO2 cycle', modname) 205 CASE('coag'); CALL msg(TRIM(msg1)//' tracers are treated for COAGULATION tests', modname) 206 CASE('lmdz'); CALL msg(TRIM(msg1)//' tracers are treated in LMDZ only', modname) 207 CASE DEFAULT; CALL abort_gcm(modname,'type_trac='//TRIM(types_trac(it))//' not possible yet.',1) 208 END SELECT 209 210 !--- COHERENCE TEST BETWEEN "type_trac" AND PREPROCESSING KEYS 211 SELECT CASE(types_trac(it)) 212 CASE('inca', 'inco') 194 !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION 195 msg1 = 'For type_trac = "'//TRIM(type_trac)//'":' 196 SELECT CASE(type_trac) 197 CASE('inca'); CALL msg(TRIM(msg1)//' coupling with INCA chemistry model', modname) 198 CASE('inco'); CALL msg(TRIM(msg1)//' coupling jointly with INCA and CO2 cycle', modname) 199 CASE('repr'); CALL msg(TRIM(msg1)//' coupling with REPROBUS chemistry model', modname) 200 CASE('co2i'); CALL msg(TRIM(msg1)//' you have chosen to run with CO2 cycle', modname) 201 CASE('coag'); CALL msg(TRIM(msg1)//' tracers are treated for COAGULATION tests', modname) 202 CASE('lmdz'); CALL msg(TRIM(msg1)//' tracers are treated in LMDZ only', modname) 203 CASE DEFAULT; CALL abort_gcm(modname,'type_trac='//TRIM(type_trac)//' not possible yet.',1) 204 END SELECT 205 206 !--- COHERENCE TEST BETWEEN "type_trac" AND PREPROCESSING KEYS 207 SELECT CASE(type_trac) 208 CASE('inca', 'inco') 213 209 #ifndef INCA 214 215 #endif 216 210 CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code', 1) 211 #endif 212 CASE('repr') 217 213 #ifndef REPROBUS 218 219 #endif 220 214 CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code', 1) 215 #endif 216 CASE('coag') 221 217 #ifndef CPP_StratAer 222 CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1) 223 #endif 224 END SELECT 225 226 !--------------------------------------------------------------------------------------------------------------------------- 227 END DO 228 !--------------------------------------------------------------------------------------------------------------------------- 229 230 !############################################################################################################################## 231 END IF 232 !############################################################################################################################## 233 234 nqCO2 = COUNT( [ANY(types_trac == 'inco') .OR. (ANY(types_trac == 'co2i') .AND. ANY(types_trac == 'inca'))] ) 218 CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code', 1) 219 #endif 220 END SELECT 221 !############################################################################################################################## 222 END IF 223 !############################################################################################################################## 224 225 nqCO2 = COUNT( [type_trac == 'inco', type_trac == 'co2i'] ) 235 226 236 227 !============================================================================================================================== 237 228 ! 1) Get the numbers of: true (first order only) tracers "nqtrue", water tracers "nqo" (vapor/liquid/solid) 238 229 !============================================================================================================================== 239 lRepr = ANY(types_trac(:) == 'repr') 230 texp = type_trac !=== EXPANDED VERSION OF "type_trac", WITH "|" SEPARATOR 231 IF(texp == 'inco') texp = 'co2i|inca' 232 IF(texp /= 'lmdz') texp = 'lmdz|'//TRIM(texp) 233 234 !=== DETERMINE THE TYPE OF THE INPUT TRACERS DESCRIPTION FILE 235 IF(testTracersFiles(modname, texp, fType, lInit)) CALL abort_gcm(modname, 'problem with tracers file(s)',1) 236 ttp = type_trac; IF(fType /= 1) ttp = texp 237 240 238 !############################################################################################################################## 241 239 IF(lInit) THEN 242 IF(readTracersFiles(type_trac, fType, lRepr)) CALL abort_gcm(modname, 'problem with tracers file(s)',1)240 IF(readTracersFiles(ttp, type_trac == 'repr')) CALL abort_gcm(modname, 'problem with tracers file(s)',1) 243 241 ELSE 244 CALL msg('No tracers description file(s) reading needed: already done in the dynamics', modname) 245 IF(testTracersFiles(modname, type_trac, fType, .FALSE.)) CALL abort_gcm(modname, 'problem with tracers file(s)',1) 242 CALL msg('No tracers description file(s) reading needed: already done in the dynamics', modname) 246 243 END IF 247 244 !############################################################################################################################## … … 262 259 CALL init_transport(solsym_inca, conv_flg_inca, pbl_flg_inca, hadv_inca, vadv_inca) 263 260 ALLOCATE(ttr(nqtrue)) 264 ttr(1:nqo+nqCO2) 265 ttr(1 : nqo )%component 266 ttr(1+nqo:nqCO2+nqo )%component 267 ttr(1+nqo+nqCO2:nqtrue)%component 268 ttr(1+nqo :nqtrue)%name 269 ttr(1+nqo+nqCO2:nqtrue)%parent 270 ttr(1+nqo+nqCO2:nqtrue)%phase 261 ttr(1:nqo+nqCO2) = tracers 262 ttr(1 : nqo )%component = 'lmdz' 263 ttr(1+nqo:nqCO2+nqo )%component = 'co2i' 264 ttr(1+nqo+nqCO2:nqtrue)%component = 'inca' 265 ttr(1+nqo :nqtrue)%name = [('CO2 ', k=1, nqCO2), solsym_inca] 266 ttr(1+nqo+nqCO2:nqtrue)%parent = tran0 267 ttr(1+nqo+nqCO2:nqtrue)%phase = 'g' 271 268 lerr = getKey('hadv', had, ky=tracers(:)%keys) 272 269 lerr = getKey('vadv', vad, ky=tracers(:)%keys) 273 hadv(1:nqo ) = had(:); hadv(nqo+1:nqtrue) = hadv_inca274 vadv(1:nqo ) = vad(:); vadv(nqo+1:nqtrue) = vadv_inca270 hadv(1:nqo+nqCO2) = had(:); hadv(1+nqo+nqCO2:nqtrue) = hadv_inca 271 vadv(1:nqo+nqCO2) = vad(:); vadv(1+nqo+nqCO2:nqtrue) = vadv_inca 275 272 CALL MOVE_ALLOC(FROM=ttr, TO=tracers) 276 CALL setGeneration(tracers) !--- SET FIELDS %iGeneration, %gen0Name273 IF(setGeneration(tracers)) CALL abort_gcm(modname,'See below',1) !- SET FIELDS %iGeneration, %gen0Name 277 274 DEALLOCATE(had, hadv_inca, vad, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca) 278 275 #endif … … 424 421 #endif 425 422 #ifdef CPP_StratAer 426 IF ( ANY(types_trac == 'coag')) THEN423 IF (type_trac == 'coag') THEN 427 424 nbtr_bin = COUNT([(tracers(iq)%name(1:3)=='BIN', iq=1, nqtot)]) 428 425 nbtr_sulgas = COUNT([(tracers(iq)%name(1:3)=='GAS', iq=1, nqtot)]) -
LMDZ6/trunk/libf/phylmd/phyetat0_mod.F90
r4370 r4389 32 32 USE geometry_mod, ONLY: longitude_deg, latitude_deg 33 33 USE iostart, ONLY: close_startphy, get_field, get_var, open_startphy 34 USE infotrac_phy, ONLY: nqtot, nbtr, type_trac, t ypes_trac, tracers34 USE infotrac_phy, ONLY: nqtot, nbtr, type_trac, tracers 35 35 USE readTracFiles_mod,ONLY: maxlen, new2oldH2O 36 36 USE traclmdz_mod, ONLY: traclmdz_from_restart … … 471 471 472 472 !--OB now this is for co2i - ThL: and therefore also for inco 473 IF (ANY(type s_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN473 IF (ANY(type_trac == ['co2i','inco'])) THEN 474 474 IF (carbon_cycle_cpl) THEN 475 475 ALLOCATE(co2_send(klon), stat=ierr) -
LMDZ6/trunk/libf/phylmd/phyredem.F90
r4370 r4389 35 35 USE iostart, ONLY: open_restartphy, close_restartphy, enddef_restartphy, put_field, put_var 36 36 USE traclmdz_mod, ONLY : traclmdz_to_restart 37 USE infotrac_phy, ONLY: type_trac, types_trac,nqtot, tracers, nbtr37 USE infotrac_phy, ONLY: type_trac, nqtot, tracers, nbtr 38 38 USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send, carbon_cycle_rad, RCO2_glo 39 39 USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic, epsfra … … 329 329 330 330 331 IF (ANY(type s_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN331 IF (ANY(type_trac == ['co2i','inco'])) THEN 332 332 IF (carbon_cycle_cpl) THEN 333 333 IF (.NOT. ALLOCATED(co2_send)) THEN -
LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90
r4370 r4389 25 25 26 26 USE dimphy, ONLY: klon, klev, klevp1 27 USE infotrac_phy, ONLY: nbtr, nqtot, nqo, type_trac, t ypes_trac, tracers, niso, ntiso27 USE infotrac_phy, ONLY: nbtr, nqtot, nqo, type_trac, tracers, niso, ntiso 28 28 USE strings_mod, ONLY: maxlen 29 29 USE mod_phys_lmdz_para, ONLY: is_north_pole_phy,is_south_pole_phy … … 943 943 CALL histwrite_phy(o_SWupTOAclr, zx_tmp_fi2d) 944 944 945 IF ( ALL(types_trac/='inca').OR. config_inca=='aeNP') THEN945 IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN 946 946 IF (vars_defined) THEN 947 947 zx_tmp_fi2d(:) = swupc0(:,klevp1)*swradcorr(:) … … 1015 1015 CALL histwrite_phy(o_SWupSFCclr, zx_tmp_fi2d) 1016 1016 1017 IF ( ALL(types_trac/='inca').OR. config_inca=='aeNP') THEN1017 IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN 1018 1018 IF (vars_defined) THEN 1019 1019 zx_tmp_fi2d(:) = swupc0(:,1)*swradcorr(:) … … 1032 1032 CALL histwrite_phy(o_SWdnSFCclr, zx_tmp_fi2d) 1033 1033 1034 IF ( ALL(types_trac/='inca').OR. config_inca=='aeNP') THEN1034 IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN 1035 1035 IF (vars_defined) THEN 1036 1036 zx_tmp_fi2d(:) = swdnc0(:,1)*swradcorr(:) … … 1054 1054 CALL histwrite_phy(o_LWdnSFCclr, sollwdownclr) 1055 1055 1056 IF ( ALL(types_trac/='inca').OR. config_inca=='aeNP') THEN1056 IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN 1057 1057 IF (vars_defined) THEN 1058 1058 zx_tmp_fi2d(:) = lwupc0(:,klevp1) … … 1061 1061 ENDIF 1062 1062 1063 IF ( ALL(types_trac/='inca').OR. config_inca=='aeNP') THEN1063 IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN 1064 1064 IF (vars_defined) THEN 1065 1065 zx_tmp_fi2d(:) = -1.*lwdnc0(:,1) … … 1570 1570 !This is warranted by treating INCA aerosols as offline aerosols 1571 1571 IF (flag_aerosol.GT.0) THEN 1572 IF ( ALL(types_trac/='inca').OR. config_inca=='aeNP') THEN1572 IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN 1573 1573 1574 1574 CALL histwrite_phy(o_od443aer, od443aer) … … 1634 1634 1635 1635 #ifdef CPP_StratAer 1636 IF ( ANY(types_trac=='coag')) THEN1636 IF (type_trac=='coag') THEN 1637 1637 CALL histwrite_phy(o_R2SO4, R2SO4) 1638 1638 CALL histwrite_phy(o_OCS_lifetime, OCS_lifetime) … … 1693 1693 CALL histwrite_phy(o_solswad0, zx_tmp_fi2d) 1694 1694 1695 IF ( ALL(types_trac/='inca').OR. config_inca=='aeNP') THEN1695 IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN 1696 1696 1697 1697 CALL histwrite_phy(o_toplwad, toplwad_aero) … … 1770 1770 ! Champs 3D: 1771 1771 IF (ok_ade .OR. ok_aie) then 1772 IF ( ALL(types_trac/='inca').OR. config_inca=='aeNP') THEN1772 IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN 1773 1773 CALL histwrite_phy(o_ec550aer, ec550aer) 1774 1774 ENDIF … … 2229 2229 CALL histwrite_phy(o_rsucs, zx_tmp_fi3d1) 2230 2230 2231 IF ( ALL(types_trac/='inca').OR. config_inca=='aeNP') THEN2231 IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN 2232 2232 IF (vars_defined) THEN 2233 2233 DO k=1, klevp1 … … 2245 2245 CALL histwrite_phy(o_rsdcs, zx_tmp_fi3d1) 2246 2246 2247 IF ( ALL(types_trac/='inca').OR. config_inca=='aeNP') THEN2247 IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN 2248 2248 IF (vars_defined) THEN 2249 2249 DO k=1, klevp1 … … 2491 2491 IF (iflag_phytrac == 1 ) then 2492 2492 ! 2493 IF ( ANY(types_trac == 'co2i')) THEN2493 IF (type_trac == 'co2i') THEN 2494 2494 itr = 0 2495 2495 DO iq = 1, nqtot … … 2520 2520 CALL histwrite_phy(o_flx_co2_bb, fco2_bb) 2521 2521 2522 ELSE IF ( ANY(types_trac == 'inco')) THEN2522 ELSE IF (type_trac == 'inco') THEN 2523 2523 itr = 0 2524 2524 DO iq = 1, nqtot … … 2549 2549 CALL histwrite_phy(o_flx_co2_bb, fco2_bb) 2550 2550 2551 ELSE IF (ANY(type_trac==['lmdz |coag','lmdz ','coag'])) THEN2551 ELSE IF (ANY(type_trac==['lmdz','coag'])) THEN 2552 2552 itr = 0 2553 2553 DO iq = 1, nqtot -
LMDZ6/trunk/libf/phylmd/physiq_mod.F90
r4386 r4389 39 39 USE ioipsl_getin_p_mod, ONLY : getin_p 40 40 USE indice_sol_mod 41 USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type s_trac41 USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type_trac 42 42 USE readTracFiles_mod, ONLY: addPhase 43 43 USE strings_mod, ONLY: strIdx … … 1466 1466 tau_overturning_th(:)=0. 1467 1467 1468 IF (ANY(type s_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN1468 IF (ANY(type_trac == ['inca','inco'])) THEN 1469 1469 ! jg : initialisation jusqu'au ces variables sont dans restart 1470 1470 ccm(:,:,:) = 0. … … 2035 2035 !c ENDDO 2036 2036 ! 2037 IF (ANY(type s_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL2037 IF (ANY(type_trac == ['inca','inco'])) THEN ! ModThL 2038 2038 #ifdef INCA 2039 2039 CALL VTe(VTphysiq) … … 2117 2117 ENDIF 2118 2118 ! 2119 IF ( ANY(types_trac == 'repr')) THEN2119 IF (type_trac == 'repr') THEN 2120 2120 #ifdef REPROBUS 2121 2121 CALL chemini_rep( & … … 2230 2230 2231 2231 ! Update time and other variables in Reprobus 2232 IF ( ANY(types_trac == 'repr')) THEN2232 IF (type_trac == 'repr') THEN 2233 2233 #ifdef REPROBUS 2234 2234 CALL Init_chem_rep_xjour(jD_cur-jD_ref+day_ref) … … 3021 3021 ! 3022 3022 !>jyg 3023 IF ( ANY(types_trac == 'repr')) THEN3023 IF (type_trac == 'repr') THEN 3024 3024 nbtr_tmp=ntra 3025 3025 ELSE … … 3927 3927 ENDDO 3928 3928 3929 IF (ANY(type s_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL3929 IF (ANY(type_trac == ['inca','inco'])) THEN ! ModThL 3930 3930 #ifdef INCA 3931 3931 CALL VTe(VTphysiq) … … 3983 3983 #endif 3984 3984 ENDIF !type_trac = inca or inco 3985 IF ( ANY(types_trac == 'repr')) THEN3985 IF (type_trac == 'repr') THEN 3986 3986 #ifdef REPROBUS 3987 3987 !CALL chemtime_rep(itap+itau_phy-1, date0, dtime, itap) … … 4953 4953 ! 4954 4954 4955 IF ( ANY(types_trac=='repr')) THEN4955 IF (type_trac == 'repr') THEN 4956 4956 !MM pas d'impact, car on recupere q_seri,tr_seri,t_seri via phys_local_var_mod 4957 4957 !MM dans Reprobus … … 5106 5106 ENDDO 5107 5107 ! 5108 IF (ANY(type s_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN5108 IF (ANY(type_trac == ['inca','inco'])) THEN 5109 5109 #ifdef INCA 5110 5110 CALL VTe(VTphysiq) … … 5130 5130 ENDIF 5131 5131 5132 IF ( ANY(types_trac == 'repr')) THEN5132 IF (type_trac == 'repr') THEN 5133 5133 #ifdef REPROBUS 5134 5134 CALL coord_hyb_rep(paprs, pplay, aps, bps, ap, bp, cell_area) … … 5391 5391 5392 5392 #ifdef INCA 5393 if ( ANY(types_trac == 'inca' )) then5393 if (type_trac == 'inca') then 5394 5394 IF (is_omp_master .and. grid_type==unstructured) THEN 5395 5395 CALL finalize_inca -
LMDZ6/trunk/libf/phylmd/phytrac_mod.F90
r4298 r4389 56 56 SUBROUTINE phytrac_init() 57 57 USE dimphy 58 USE infotrac_phy, ONLY: nbtr, type s_trac58 USE infotrac_phy, ONLY: nbtr, type_trac 59 59 USE tracco2i_mod, ONLY: tracco2i_init 60 60 IMPLICIT NONE … … 79 79 !=============================================================================== 80 80 ! -- CO2 interactif -- 81 IF(ANY(type s_trac == 'co2i') .OR. ANY(types_trac == 'inco')) CALL tracco2i_init()82 83 ! -- type s_trac == 'co2i' ! PC81 IF(ANY(type_trac == ['co2i','inco'])) CALL tracco2i_init() 82 83 ! -- type_trac == 'co2i' ! PC 84 84 ! -- CO2 interactif -- 85 85 ! -- source is updated with FF and BB emissions … … 124 124 USE phys_cal_mod, only : hour 125 125 USE dimphy 126 USE infotrac_phy, ONLY: nbtr, nqCO2, type s_trac, type_trac, conv_flg, pbl_flg126 USE infotrac_phy, ONLY: nbtr, nqCO2, type_trac, conv_flg, pbl_flg 127 127 USE strings_mod, ONLY: int2str 128 128 USE mod_grid_phy_lmdz … … 491 491 492 492 ! Initialize module for specific tracers 493 IF( ANY(types_trac == 'inca')) THEN493 IF(type_trac == 'inca') THEN 494 494 source(:,:)=init_source(:,:) 495 495 CALL tracinca_init(aerosol,lessivage) 496 ELSE IF( ANY(types_trac == 'repr')) THEN496 ELSE IF(type_trac == 'repr') THEN 497 497 source(:,:)=0. 498 ELSE IF( ANY(types_trac == 'co2i')) THEN498 ELSE IF(type_trac == 'co2i') THEN 499 499 source(:,:)=0. 500 500 lessivage = .FALSE. … … 504 504 iflag_vdf_trac= 1 505 505 iflag_con_trac= 1 506 ELSE IF( ANY(types_trac == 'inco')) THEN506 ELSE IF(type_trac == 'inco') THEN 507 507 source(:,1:nqCO2) = 0. ! from CO2i ModThL 508 508 source(:,nqCO2+1:nbtr)=init_source(:,:) ! from INCA ModThL … … 514 514 iflag_con_trac = 1 ! From CO2i 515 515 #ifdef CPP_StratAer 516 ELSE IF( ANY(types_trac == 'coag')) THEN516 ELSE IF(type_trac == 'coag') THEN 517 517 source(:,:)=0. 518 518 DO it= 1, nbtr_sulgas … … 524 524 ENDDO 525 525 #endif 526 ELSE IF( ANY(types_trac == 'lmdz')) THEN526 ELSE IF(type_trac == 'lmdz') THEN 527 527 CALL traclmdz_init(pctsrf,xlat,xlon,ftsol,tr_seri,t_seri,pplay,sh,pdtphys,aerosol,lessivage) 528 528 END IF … … 539 539 ! 540 540 DO it=1, nbtr 541 IF( ANY(types_trac == 'repr')) THEN541 IF(type_trac == 'repr') THEN 542 542 flag_cvltr(it)=.FALSE. 543 ELSE IF( ANY(types_trac == 'inca')) THEN543 ELSE IF(type_trac == 'inca') THEN 544 544 ! IF ((it.EQ.id_Rn222) .OR. ((it.GE.id_SO2) .AND. (it.LE.id_NH3)) ) THEN 545 545 ! !--gas-phase species … … 565 565 !--for now we do not scavenge in cvltr 566 566 flag_cvltr(it)=.FALSE. 567 ELSE IF( ANY(types_trac == 'co2i')) THEN567 ELSE IF(type_trac == 'co2i') THEN 568 568 !--co2 tracers are not scavenged 569 569 flag_cvltr(it)=.FALSE. 570 ELSE IF( ANY(types_trac == 'inco')) THEN ! Add ThL570 ELSE IF(type_trac == 'inco') THEN ! Add ThL 571 571 flag_cvltr(it)=.FALSE. 572 572 #ifdef CPP_StratAer 573 ELSE IF( ANY(types_trac == 'coag')) THEN573 ELSE IF(type_trac == 'coag') THEN 574 574 IF (convscav.and.aerosol(it)) THEN 575 575 flag_cvltr(it)=.TRUE. … … 581 581 ENDIF 582 582 #endif 583 ELSE IF( ANY(types_trac == 'lmdz')) THEN583 ELSE IF(type_trac == 'lmdz') THEN 584 584 IF (convscav.and.aerosol(it)) THEN 585 585 flag_cvltr(it)=.TRUE. … … 614 614 write(lunout,*) 'flag_cvltr = ', flag_cvltr 615 615 616 IF (lessivage .AND. (ANY(types_trac == 'inca') .OR. ANY(types_trac=='inco'))) THEN ! Mod ThL616 IF (lessivage .AND. ANY(type_trac == ['inca','inco'])) & 617 617 CALL abort_physic('phytrac', 'lessivage=T config_inca=inca impossible',1) 618 ! STOP619 ENDIF620 618 ! 621 619 ENDIF ! of IF (debutphy) … … 640 638 ! 641 639 !=============================================================================== 642 IF( ANY(types_trac == 'inca')) THEN640 IF(type_trac == 'inca') THEN 643 641 ! -- CHIMIE INCA config_inca = aero or chem -- 644 642 ! Appel fait en fin de phytrac pour avoir les emissions modifiees par 645 643 ! la couche limite et la convection avant le calcul de la chimie 646 644 647 ELSE IF( ANY(types_trac == 'repr')) THEN645 ELSE IF(type_trac == 'repr') THEN 648 646 ! -- CHIMIE REPROBUS -- 649 647 CALL tracreprobus(pdtphys, gmtime, debutphy, julien, & … … 652 650 tr_seri) 653 651 654 ELSE IF( ANY(types_trac == 'co2i')) THEN652 ELSE IF(type_trac == 'co2i') THEN 655 653 ! -- CO2 interactif -- 656 654 ! -- source is updated with FF and BB emissions … … 661 659 xlat, xlon, pphis, pphi, & 662 660 t_seri, pplay, paprs, tr_seri, source) 663 ELSE IF( ANY(types_trac == 'inco')) THEN ! Add ThL661 ELSE IF(type_trac == 'inco') THEN ! Add ThL 664 662 CALL tracco2i(pdtphys, debutphy, & 665 663 xlat, xlon, pphis, pphi, & … … 667 665 668 666 #ifdef CPP_StratAer 669 ELSE IF( ANY(types_trac == 'coag')) THEN667 ELSE IF(type_trac == 'coag') THEN 670 668 ! --STRATOSPHERIC AER IN THE STRAT -- 671 669 CALL traccoag(pdtphys, gmtime, debutphy, julien, & … … 674 672 tr_seri) 675 673 #endif 676 ELSE IF( ANY(types_trac == 'lmdz')) THEN674 ELSE IF(type_trac == 'lmdz') THEN 677 675 ! -- Traitement des traceurs avec traclmdz 678 676 CALL traclmdz(nstep, julien, gmtime, pdtphys, t_seri, paprs, pplay, & … … 748 746 749 747 #ifdef CPP_StratAer 750 IF ( ANY(types_trac=='coag')) THEN748 IF (type_trac=='coag') THEN 751 749 ! initialize wet deposition flux of sulfur 752 750 budg_dep_wet_ocs(:)=0.0 … … 829 827 ! 830 828 #ifdef CPP_StratAer 831 IF ( ANY(types_trac=='coag')) THEN829 IF (type_trac=='coag') THEN 832 830 833 831 ! initialize dry deposition flux of sulfur … … 866 864 ! 867 865 #ifdef CPP_StratAer 868 IF ( ANY(types_trac=='coag')) THEN866 IF (type_trac=='coag') THEN 869 867 ! compute dry deposition flux of sulfur (sum over gases and particles) 870 868 IF (it==id_OCS_strat) THEN … … 951 949 952 950 #ifdef CPP_StratAer 953 IF ( ANY(types_trac=='coag')) THEN951 IF (type_trac=='coag') THEN 954 952 ! compute wet deposition flux of sulfur (sum over gases and 955 953 ! particles) and convert to kg(S)/m2/s … … 1091 1089 1092 1090 ! -- CHIMIE INCA config_inca = aero or chem -- 1093 IF (ANY(type s_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL1091 IF (ANY(type_trac == ['inca','inco'])) THEN ! ModThL 1094 1092 1095 1093 CALL tracinca(& -
LMDZ6/trunk/libf/phylmd/radiation_AR4.F90
r4170 r4389 479 479 USE dimphy 480 480 USE radiation_ar4_param, ONLY: rsun, rray 481 USE infotrac_phy, ONLY: type s_trac481 USE infotrac_phy, ONLY: type_trac 482 482 #ifdef REPROBUS 483 483 USE chem_rep, ONLY: rsuntime, ok_suntime … … 571 571 ! If running with Reporbus, overwrite default values of RSUN. 572 572 ! Otherwise keep default values from radiation_AR4_param module. 573 IF ( ANY(types_trac=='repr')) THEN573 IF (type_trac=='repr') THEN 574 574 #ifdef REPROBUS 575 575 IF (ok_suntime) THEN … … 701 701 USE dimphy 702 702 USE radiation_ar4_param, ONLY: rsun, rray 703 USE infotrac_phy, ONLY: type s_trac703 USE infotrac_phy, ONLY: type_trac 704 704 #ifdef REPROBUS 705 705 USE chem_rep, ONLY: rsuntime, ok_suntime … … 825 825 ! If running with Reporbus, overwrite default values of RSUN. 826 826 ! Otherwise keep default values from radiation_AR4_param module. 827 IF ( ANY(types_trac=='repr')) THEN827 IF (type_trac=='repr') THEN 828 828 #ifdef REPROBUS 829 829 IF (ok_suntime) THEN … … 2313 2313 USE dimphy 2314 2314 USE radiation_ar4_param, ONLY: tref, rt1, raer, at, bt, oct 2315 USE infotrac_phy, ONLY: type s_trac2315 USE infotrac_phy, ONLY: type_trac 2316 2316 #ifdef REPROBUS 2317 2317 USE chem_rep, ONLY: rch42d, rn2o2d, rcfc112d, rcfc122d, ok_rtime2d … … 2621 2621 2622 2622 2623 IF ( ANY(types_trac=='repr')) THEN2623 IF (type_trac=='repr') THEN 2624 2624 #ifdef REPROBUS 2625 2625 IF (ok_rtime2d) THEN -
LMDZ6/trunk/libf/phylmd/radlwsw_m.F90
r4170 r4389 48 48 USE DIMPHY 49 49 USE assert_m, ONLY : assert 50 USE infotrac_phy, ONLY : type s_trac50 USE infotrac_phy, ONLY : type_trac 51 51 USE write_field_phy 52 52 … … 550 550 PSCT = solaire/zdist/zdist 551 551 552 IF ( ANY(types_trac == 'repr')) THEN552 IF (type_trac == 'repr') THEN 553 553 #ifdef REPROBUS 554 554 IF (iflag_rrtm==0) THEN … … 634 634 ENDDO 635 635 636 IF ( ANY(types_trac == 'repr')) THEN636 IF (type_trac == 'repr') THEN 637 637 #ifdef REPROBUS 638 638 ndimozon = size(wo, 3) -
LMDZ6/trunk/libf/phylmd/rrtm/lwu.F90
r4241 r4389 76 76 #ifdef REPROBUS 77 77 USE chem_rep, ONLY: rch42d, rn2o2d, rcfc112d, rcfc122d, ok_rtime2d 78 USE infotrac_phy, ONLY : type s_trac78 USE infotrac_phy, ONLY : type_trac 79 79 #endif 80 80 … … 321 321 PABCU(JL,18,IC)=PABCU(JL,18,ICP1)+ ZUAER(JL,5) *ZDUC(JL,IC)*ZDIFF 322 322 #ifdef REPROBUS 323 IF ( ANY(types_trac=='repr').and. ok_rtime2d) THEN323 IF (type_trac=='repr'.and. ok_rtime2d) THEN 324 324 !- CH4 325 325 PABCU(JL,19,IC)=PABCU(JL,19,ICP1)& -
LMDZ6/trunk/libf/phylmd/tracinca_mod.F90
r4358 r4389 18 18 ! This subroutine initialize some control varaibles. 19 19 20 USE infotrac_phy, ONLY: nbtr, type s_trac20 USE infotrac_phy, ONLY: nbtr, type_trac 21 21 IMPLICIT NONE 22 22 … … 30 30 31 31 !--- COHERENCE TEST BETWEEN "type_trac" AND "config_inca" 32 IF((ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) .AND. ALL(config_inca /= ['aero', 'aeNP', 'chem']))& 33 CALL abort_gcm('tracinca_init', 'INCA enabled, but unknown config_inca = "'//TRIM(config_inca)//'".' & 34 //'Please modify "run.def"', 1) 32 IF(ANY(type_trac == ['inca','inco']) .AND. ALL(config_inca /= ['aero','aeNP','chem'])) CALL abort_gcm('tracinca_init', & 33 'INCA enabled, but unknown config_inca = "'//TRIM(config_inca)//'". Please modify "run.def"', 1) 35 34 36 35 !--- PROBLEM IF "config_inca" DIFFERS FROM "none" AND INCA HAS NOT BEEN ACTIVATED 37 IF(ALL(types_trac /= 'inca') .AND. ALL(types_trac /= 'inco') .AND. config_inca /= 'none') & 38 CALL abort_gcm('tracinca_init', 'INCA disabled, but config_inca = "'//TRIM(config_inca)//'" should be "none".'& 39 //'Please modify "run.def"', 1) 36 IF(ALL(type_trac /= ['inca','inco']) .AND. config_inca /= 'none') CALL abort_gcm('tracinca_init', & 37 'INCA disabled, but config_inca = "'//TRIM(config_inca)//'" should be "none". Please modify "run.def"', 1) 40 38 41 39 END SUBROUTINE tracinca_init -
LMDZ6/trunk/libf/phylmd/traclmdz_mod.F90
r4325 r4389 203 203 tr_seri(:,:,id_pb) = plomb(:,:) 204 204 ELSE 205 WRITE(lunout,*)' Prof. Pb210 does not exist: use restart values'205 WRITE(lunout,*)'prof.pb210 does not exist: use restart values' 206 206 END IF 207 207 CASE("aga") -
LMDZ6/trunk/libf/phylmdiso/phyetat0_mod.F90
r4384 r4389 40 40 USE geometry_mod, ONLY: longitude_deg, latitude_deg 41 41 USE iostart, ONLY: close_startphy, get_field, get_var, open_startphy 42 USE infotrac_phy, ONLY: nqtot, nbtr, type_trac, t ypes_trac, tracers42 USE infotrac_phy, ONLY: nqtot, nbtr, type_trac, tracers 43 43 USE readTracFiles_mod,ONLY: maxlen, new2oldH2O 44 44 USE traclmdz_mod, ONLY: traclmdz_from_restart … … 492 492 493 493 !--OB now this is for co2i - ThL: and therefore also for inco 494 IF (ANY(type s_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN494 IF (ANY(type_trac == ['co2i','inco'])) THEN 495 495 IF (carbon_cycle_cpl) THEN 496 496 ALLOCATE(co2_send(klon), stat=ierr) -
LMDZ6/trunk/libf/phylmdiso/phyredem.F90
r4374 r4389 39 39 USE iostart, ONLY: open_restartphy, close_restartphy, enddef_restartphy, put_field, put_var 40 40 USE traclmdz_mod, ONLY : traclmdz_to_restart 41 USE infotrac_phy, ONLY: type s_trac, nqtot, tracers, nbtr, niso41 USE infotrac_phy, ONLY: type_trac, nqtot, tracers, nbtr, niso 42 42 #ifdef ISO 43 43 #ifdef ISOVERIF … … 176 176 CALL put_field(pass,"FSIC", "fraction glace mer", pctsrf(:, is_sic)) 177 177 178 IF(nbsrf>99) THEN 179 PRINT*, "Trop de sous-mailles"; CALL abort_physic("phyredem", "", 1) 180 END IF 181 IF(nsoilmx>99) THEN 182 PRINT*, "Trop de sous-surfaces"; CALL abort_physic("phyredem", "", 1) 183 END IF 184 IF(nsw>99) THEN 185 PRINT*, "Trop de bandes"; CALL abort_physic("phyredem", "", 1) 186 END IF 178 IF(nbsrf >99) CALL abort_physic("phyredem", "Trop de sous-mailles", 1) 179 IF(nsoilmx>99) CALL abort_physic("phyredem", "Trop de sous-mailles", 1) 180 IF(nsw >99) CALL abort_physic("phyredem", "Trop de bandes", 1) 187 181 188 182 ! Surface variables … … 350 344 351 345 352 IF (ANY(type s_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN346 IF (ANY(type_trac == ['co2i','inco'])) THEN 353 347 IF (carbon_cycle_cpl) THEN 354 348 IF (.NOT. ALLOCATED(co2_send)) THEN … … 361 355 362 356 ! trs from traclmdz_mod 363 ELSE IF ( ANY(types_trac == 'lmdz')) THEN357 ELSE IF (type_trac == 'lmdz') THEN 364 358 CALL traclmdz_to_restart(trs) 365 359 it = 0 -
LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90
r4386 r4389 39 39 USE ioipsl_getin_p_mod, ONLY : getin_p 40 40 USE indice_sol_mod 41 USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type s_trac41 USE infotrac_phy, ONLY: nqtot, nbtr, nqo, tracers, type_trac 42 42 USE readTracFiles_mod, ONLY: addPhase 43 43 USE strings_mod, ONLY: strIdx … … 1570 1570 tau_overturning_th(:)=0. 1571 1571 1572 IF (ANY(type s_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN1572 IF (ANY(type_trac == ['inca','inco'])) THEN 1573 1573 ! jg : initialisation jusqu'au ces variables sont dans restart 1574 1574 ccm(:,:,:) = 0. … … 2187 2187 !c ENDDO 2188 2188 ! 2189 IF (ANY(type s_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL2189 IF (ANY(type_trac == ['inca','inco'])) THEN ! ModThL 2190 2190 #ifdef INCA 2191 2191 CALL VTe(VTphysiq) … … 2269 2269 ENDIF 2270 2270 ! 2271 IF ( ANY(types_trac == 'repr')) THEN2271 IF (type_trac == 'repr') THEN 2272 2272 #ifdef REPROBUS 2273 2273 CALL chemini_rep( & … … 2386 2386 2387 2387 ! Update time and other variables in Reprobus 2388 IF ( ANY(types_trac == 'repr')) THEN2388 IF (type_trac == 'repr') THEN 2389 2389 #ifdef REPROBUS 2390 2390 CALL Init_chem_rep_xjour(jD_cur-jD_ref+day_ref) … … 3654 3654 ! 3655 3655 !>jyg 3656 IF ( ANY(types_trac == 'repr')) THEN3656 IF (type_trac == 'repr') THEN 3657 3657 nbtr_tmp=ntra 3658 3658 ELSE … … 5191 5191 ENDDO 5192 5192 5193 IF (ANY(type s_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN ! ModThL5193 IF (ANY(type_trac == ['inca','inco'])) THEN ! ModThL 5194 5194 #ifdef INCA 5195 5195 CALL VTe(VTphysiq) … … 5247 5247 #endif 5248 5248 ENDIF !type_trac = inca or inco 5249 IF ( ANY(types_trac == 'repr')) THEN5249 IF (type_trac == 'repr') THEN 5250 5250 #ifdef REPROBUS 5251 5251 !CALL chemtime_rep(itap+itau_phy-1, date0, dtime, itap) … … 6336 6336 ! 6337 6337 6338 IF ( ANY(types_trac=='repr')) THEN6338 IF (type_trac=='repr') THEN 6339 6339 !MM pas d'impact, car on recupere q_seri,tr_seri,t_seri via phys_local_var_mod 6340 6340 !MM dans Reprobus … … 6501 6501 #endif 6502 6502 ! 6503 IF (ANY(type s_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN6503 IF (ANY(type_trac == ['inca','inco'])) THEN 6504 6504 #ifdef INCA 6505 6505 CALL VTe(VTphysiq) … … 6525 6525 ENDIF 6526 6526 6527 IF ( ANY(types_trac == 'repr')) THEN6527 IF (type_trac == 'repr') THEN 6528 6528 #ifdef REPROBUS 6529 6529 CALL coord_hyb_rep(paprs, pplay, aps, bps, ap, bp, cell_area) … … 6901 6901 6902 6902 #ifdef INCA 6903 if ( ANY(types_trac == 'inca' )) then6903 if (type_trac == 'inca') then 6904 6904 IF (is_omp_master .and. grid_type==unstructured) THEN 6905 6905 CALL finalize_inca
Note: See TracChangeset
for help on using the changeset viewer.