Changeset 1926 for trunk/LMDZ.TITAN/libf
- Timestamp:
- May 28, 2018, 11:47:03 PM (7 years ago)
- Location:
- trunk/LMDZ.TITAN/libf
- Files:
-
- 1 added
- 8 edited
Legend:
- Unmodified
- Added
- Removed
-
TabularUnified trunk/LMDZ.TITAN/libf/muphytitan/mm_microphysic.f90 ¶
r1897 r1926 202 202 !! microphysics is disabled (see [[mm_globals(module):mm_w_clouds(variable)]] documentation). 203 203 REAL(kind=mm_wp), INTENT(out), OPTIONAL :: aer_prec !! Aerosols precipitations (both modes) (m). 204 REAL(kind=mm_wp), INTENT(out), OPTIONAL :: ccn_prec !! CCN precipitations (m).205 204 REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:) :: aer_s_flux !! Spherical aerosol mass flux (\(kg.m^{-2}.s^{-1}\)). 206 205 REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:) :: aer_f_flux !! Fractal aerosol mass flux (\(kg.m^{-2}.s^{-1}\)). 206 REAL(kind=mm_wp), INTENT(out), OPTIONAL :: ccn_prec !! CCN precipitations (m). 207 207 REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:) :: ccn_flux !! CCN mass flux (\(kg.m^{-2}.s^{-1}\)). 208 REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:) :: ice_prec !! Ice precipitations (m). 208 209 REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: ice_fluxes !! Ice sedimentation fluxes (\(kg.m^{-2}.s^{-1}\)). 209 210 REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: gazs_sat !! Condensible gaz saturation ratios (--). 210 REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:) :: ice_prec !! Ice precipitations (m).211 211 212 212 IF (PRESENT(aer_prec)) aer_prec = ABS(mm_aer_prec) -
TabularUnified trunk/LMDZ.TITAN/libf/muphytitan/mmp_gcm.f90 ¶
r1897 r1926 93 93 INTEGER :: i 94 94 TYPE(cfgparser) :: cparser 95 CHARACTER(len=st_slen) :: spcpath,pssfile,mqfile 95 CHARACTER(len=st_slen) :: spcpath,pssfile,mqfile,opt_file 96 96 CHARACTER(len=st_slen), DIMENSION(:), ALLOCATABLE :: species 97 97 REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: tmp … … 138 138 err = mm_check_opt(cfg_get_value(cparser,"haze_coag_interactions",coag_choice),coag_choice,7,mm_log) 139 139 140 ! optic look-up table file path. 141 mmp_optic_file = '' 142 opt_file = '' 143 err = mm_check_opt(cfg_get_value(cparser,"optics/optic_file",opt_file),opt_file,'',mm_log) 144 IF (err /= 0) THEN 145 WRITE(*,'(a)') "Warning: I was unable to retrieve the path of the optic look-up table file:" 146 WRITE(*,'(a)') " The GCM may abort if it uses YAMMS optical properties calculation module !" 147 ELSE 148 mmp_optic_file = TRIM(opt_file) 149 ENDIF 150 140 151 ! Retrieve clouds species configuration file 141 152 spcpath = '' -
TabularUnified trunk/LMDZ.TITAN/libf/muphytitan/mmp_globals.f90 ¶
r1897 r1926 92 92 !> Aerosol electric charge correction control flag. 93 93 LOGICAL, SAVE :: mmp_w_qe = .true. 94 94 !> Optic look-up table file path. 95 CHARACTER(len=:), ALLOCATABLE, SAVE :: mmp_optic_file 95 96 96 97 CONTAINS -
TabularUnified trunk/LMDZ.TITAN/libf/muphytitan/mmp_optics.f90 ¶
r1897 r1926 62 62 63 63 PRIVATE 64 PUBLIC :: mmp_optic_file ! from mmp_globals :) 64 65 PUBLIC :: mmp_initialize_optics 65 66 PUBLIC :: mmp_sph_optics_vis,mmp_sph_optics_ir -
TabularUnified trunk/LMDZ.TITAN/libf/phytitan/calmufi.F90 ¶
r1908 r1926 20 20 USE comcstfi_mod, only : g 21 21 USE callkeys_mod, only : callclouds 22 USE muphy_diag 22 23 IMPLICIT NONE 23 24 … … 141 142 call abort_program(error("mm_muphys aborted -> initialization not done !",-1)) 142 143 ENDIF 144 ! save diags (if no clouds, relevant arrays will be set to 0 !) 145 call mm_diagnostics(mmd_aer_prec(ilon),mmd_aer_s_flux(ilon,:),mmd_aer_f_flux(ilon,:), & 146 mmd_ccn_prec(ilon),mmd_ccn_flux(ilon,:), mmd_ice_prec(ilon,:), & 147 mmd_ice_fluxes(ilon,:,:),mmd_gazs_sat(ilon,:,:)) 148 call mm_get_radii(mmd_rc_sph(ilon,:),mmd_rc_fra(ilon,:),mmd_rc_cld(ilon,:)) 143 149 144 150 ! Convert tracers back to intensives ( except for gazs where we work with molar mass ratio ) -
TabularUnified trunk/LMDZ.TITAN/libf/phytitan/inimufi.F90 ¶
r1897 r1926 1 subroutine inimufi( nq,ptimestep)1 subroutine inimufi(ptimestep) 2 2 3 3 use mmp_gcm … … 31 31 real, intent(in) :: ptimestep ! Timestep (s) 32 32 33 integer, intent(in) :: nq ! Total number of tracers34 35 33 integer :: i,idx 36 34 character(len=20), dimension(4), parameter :: aernames = & … … 49 47 ! --------------------------------------------------- 50 48 51 call mmp_initialize(ptimestep,p_prod,tx_prod,rc_prod, & 49 ! enable log for what it's worth... 50 ! mm_log = .true. 51 52 call mmp_initialize(ptimestep,p_prod,tx_prod,rc_prod, & 52 53 rad,g,air_rad,mugaz,callclouds,config_mufi) 53 54 -
TabularUnified trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90 ¶
r1915 r1926 1 #define USE_QTEST2 3 1 module physiq_mod 4 2 … … 19 17 use radcommon_h, only: sigma, glat, grav, BWNV 20 18 use surfdat_h, only: phisfi, zmea, zstd, zsig, zgam, zthe 21 use comchem_h, only: nkim 19 use comchem_h, only: nkim, cnames 22 20 use comdiurn_h, only: coslat, sinlat, coslon, sinlon 23 21 use comsaison_h, only: mu0, fract, dist_star, declin, right_ascen … … 50 48 #endif 51 49 use MMP_OPTICS 50 use muphy_diag 52 51 implicit none 53 52 … … 80 79 ! 81 80 ! V. Tracers 82 ! V.1. Chemistry83 ! V.2. Microphysics81 ! V.1. Microphysics 82 ! V.2. Chemistry 84 83 ! V.3. Updates (pressure variations, surface budget). 85 84 ! V.4. Surface Tracer Update. … … 291 290 292 291 real zdqmufi(ngrid,nlayer,nq) ! Microphysical tendency. 292 293 real zdqfibar(ngrid,nlayer,nq) ! For 2D chemistry 294 real zdqmufibar(ngrid,nlayer,nq) ! For 2D chemistry 293 295 294 296 ! For Winds : (m/s/s) … … 372 374 ! Chemical tracers in molar fraction 373 375 real, dimension(ngrid,nlayer,nkim) :: ychim ! (mol/mol) 376 real, dimension(ngrid,nlayer,nkim) :: ychimbar ! For 2D chemistry 374 377 375 378 ! Molar fraction tendencies ( chemistry and condensation ) for tracers (mol/mol/s) 376 379 real, dimension(ngrid,nlayer,nq) :: dyccond ! All tracers, we want to use indx on it. 380 real, dimension(ngrid,nlayer,nq) :: dyccondbar ! For 2D chemistry 377 381 real, dimension(:,:,:), allocatable, save :: dycchi ! Only for chem tracers. Saved since chemistry is not called every step. 378 382 !$OMP THREADPRIVATE(dycchi) … … 393 397 ! -----******----- END FOR MUPHYS OPTICS -----******----- 394 398 399 real,dimension(:,:), allocatable :: i2e2d ! factor to convert X.kg-1 in X.m-3 (for microphysics diags) 400 395 401 real,save,dimension(:,:,:), allocatable :: tpq ! Tracers for decoupled microphysical tests ( temporary in 01/18 ) 396 402 !$OMP THREADPRIVATE(tpq) … … 432 438 ! Initialisation of nmicro as well as tracers names, indexes ... 433 439 if (ngrid.ne.1) then ! Already done in rcm1d 434 call initracer2(nq,nametrac) 440 call initracer2(nq,nametrac) ! WARNING JB (27/03/2018): should be wrapped in an OMP SINGLE statement (see module notes) 435 441 endif 436 442 … … 539 545 540 546 IF ( callmufi ) THEN 541 542 call inimufi(nq,ptimestep) 543 547 ! WARNING JB (27/03/2018): inimufi AND mmp_initialize_optics should be wrapped in an OMP SINGLE statement. 548 call inimufi(ptimestep) 544 549 ! Optical coupling of YAMMS is plugged but inactivated for now 545 550 ! as long as the microphysics only isn't fully debugged -- JVO 01/18 546 IF (.NOT.uncoupl_optic_haze) call mmp_initialize_optics("/path/to/mmp_optic_table.nc") 551 ! NOTE JB (03/18): mmp_optic_file is initialized in inimufi => mmp_initialize_optics must be called AFTER inimufi 552 IF (.NOT.uncoupl_optic_haze) call mmp_initialize_optics(mmp_optic_file) 553 554 ! initialize microphysics diagnostics arrays. 555 call ini_diag_arrays(ngrid,nlayer,nice) 547 556 548 557 ENDIF … … 1068 1077 if (tracer) then 1069 1078 1070 ! -------------------------1071 ! V.1. Chemistry1072 ! -------------------------1073 1074 if (callchim) then1075 1076 ! o. Convert updated tracers to molar fraction1077 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~1078 do iq = 1,nkim1079 ychim(:,:,iq) = ( pq(:,:,iq+nmicro) + pdq(:,:,iq+nmicro) ) / rat_mmol(iq+nmicro)1080 enddo1081 1082 ! i. Condensation after the transport1083 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~1084 do iq=1,nkim1085 do l=1,nlayer1086 do ig=1,ngrid1087 if ( ychim(ig,l,iq).gt.qysat(l,iq) ) then1088 dyccond(ig,l,iq+nmicro) = ( -ychim(ig,l,iq)+qysat(l,iq) ) / ptimestep1089 else1090 dyccond(ig,l,iq+nmicro) = 0.0 ! since array not saved1091 endif1092 enddo1093 enddo1094 enddo1095 1096 if ( callclouds ) dyccond(:,:,ices_indx) = 0.0 ! Condensation will be calculated in the cloud microphysics1097 1098 do iq=1,nkim1099 ychim(:,:,iq) = ychim(:,:,iq) + dyccond(:,:,iq+nmicro) ! update molar ychim for following calchim1100 zdqcond(:,:,iq+nmicro) = dyccond(:,:,iq+nmicro)*rat_mmol(iq+nmicro) ! convert tendencies to mass mixing ratio1101 enddo1102 1103 pdq(:,:,:) = pdq(:,:,:) + zdqcond(:,:,:)1104 1105 ! ii. Photochemistry1106 ! ~~~~~~~~~~~~~~~~~~1107 if( mod(icount-1,ichim).eq.0. ) then1108 1109 print *, "We enter in the chemistry ..."1110 1111 if (moyzon_ch) then ! 2D zonally averaged chemistry1112 1113 do iq = 1,nkim ! In this case we send zonal average from dynamics to chem. module1114 ychim(:,:,iq) = zqfibar(:,:,iq+nmicro) / rat_mmol(iq+nmicro)1115 enddo1116 1117 call calchim(ngrid,ychim,declin,ctimestep,ztfibar,zphibar, &1118 zplaybar,zplevbar,zzlaybar,zzlevbar,dycchi)1119 1120 else ! 3D chemistry (or 1D run)1121 call calchim(ngrid,ychim,declin,ctimestep,pt,pphi, &1122 pplay,pplev,zzlay,zzlev,dycchi)1123 endif ! if moyzon1124 1125 endif1126 1127 do iq=1,nkim1128 zdqchi(:,:,iq+nmicro) = dycchi(:,:,iq)*rat_mmol(iq+nmicro) ! convert tendencies to mass mixing ratio1129 1130 where( (pq(:,:,iq+nmicro)+zdqchi(:,:,iq+nmicro) ).LT.1e-40) & ! When using zonal means we set the same tendency1131 zdqchi(:,:,iq+nmicro) = 1e-40 - ( pq(:,:,iq+nmicro) ) ! everywhere in longitude -> can lead to negs !1132 enddo1133 1134 pdq(:,:,:) = pdq(:,:,:) + zdqchi(:,:,:)1135 1136 endif ! end of 'callchim'1137 1138 1079 ! ------------------- 1139 ! V. 2Microphysics1080 ! V.1 Microphysics 1140 1081 ! ------------------- 1082 1083 ! JVO 05/18 : We must call microphysics before chemistry, for condensation ! 1141 1084 1142 1085 if (callmufi) then … … 1149 1092 pdq(:,:,:) = pdq(:,:,:) + zdqmufi(:,:,:) 1150 1093 #endif 1151 endif 1152 1094 1095 ! Microphysics condensation for 2D fields to sent non-saturated fields to photochem 1096 if ( callclouds .and. moyzon_ch .and. mod(icount-1,ichim).eq.0 ) then 1097 zdqfibar(:,:,:) = 0.0 ! We work in zonal average -> forget processes other than condensation 1098 call calmufi(ptimestep,zplevbar,zzlevbar,zplaybar,zzlaybar, & 1099 ztfibar,zqfibar,zdqfibar,zdqmufibar) 1100 endif 1101 1102 endif 1103 1104 ! ----------------- 1105 ! V.2. Chemistry 1106 ! ----------------- 1107 ! NB : Must be call last ( brings fields back to an equilibrium ) 1108 1109 ! Known bug ? ( JVO 18 ) : If you try to use chimi_indx instead of iq+nmicro 1110 ! it leads to weird results / crash on dev mod ( ok in debug ) ... Why ? Idk ... 1111 1112 if (callchim) then 1113 1114 ! o. Convert updated tracers to molar fraction 1115 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 1116 do iq = 1,nkim 1117 ychim(:,:,iq) = ( pq(:,:,iq+nmicro) + pdq(:,:,iq+nmicro) ) / rat_mmol(iq+nmicro) 1118 enddo 1119 1120 ! JVO 05/18 : We update zonally averaged fields with condensation 1121 ! as it is compulsory to have correct photochem production. But for other 1122 ! processes ( convadj ... ) we miss them in any case as we work in zonally/diurnal 1123 ! mean -> no fine diurnal/short time evolution, only seasonal evolution only. 1124 if ( moyzon_ch .and. mod(icount-1,ichim).eq. 0 ) then 1125 do iq = 1,nkim 1126 ychimbar(:,:,iq) = zqfibar(:,:,iq+nmicro) / rat_mmol(iq+nmicro) 1127 if ( callclouds ) then 1128 ychimbar(:,:,iq) = ychimbar(:,:,iq) + ( zdqmufibar(:,:,iq+nmicro) / rat_mmol(iq+nmicro) ) 1129 endif 1130 enddo 1131 endif 1132 1133 ! i. Condensation after the transport 1134 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 1135 do iq=1,nkim 1136 do l=1,nlayer 1137 do ig=1,ngrid 1138 if ( ychim(ig,l,iq).gt.qysat(l,iq) ) then 1139 dyccond(ig,l,iq+nmicro) = ( -ychim(ig,l,iq)+qysat(l,iq) ) / ptimestep 1140 else 1141 dyccond(ig,l,iq+nmicro) = 0.0 1142 endif 1143 enddo 1144 enddo 1145 enddo 1146 1147 if ( callclouds ) dyccond(:,:,ices_indx) = 0.0 ! Condensation have been calculated in the cloud microphysics 1148 1149 do iq=1,nkim 1150 ychim(:,:,iq) = ychim(:,:,iq) + dyccond(:,:,iq+nmicro) ! update molar ychim for following calchim 1151 zdqcond(:,:,iq+nmicro) = dyccond(:,:,iq+nmicro)*rat_mmol(iq+nmicro) ! convert tendencies to mass mixing ratio 1152 enddo 1153 1154 pdq(:,:,:) = pdq(:,:,:) + zdqcond(:,:,:) 1155 1156 ! 2D zonally averaged fields needed to condense before photochem 1157 if ( moyzon_ch .and. mod(icount-1,ichim).eq. 0 ) then 1158 do iq = 1,nkim 1159 do l=1,nlayer 1160 do ig=1,ngrid 1161 if ( ychimbar(ig,l,iq).gt.qysat(l,iq) ) then 1162 dyccondbar(ig,l,iq+nmicro) = ( -ychimbar(ig,l,iq)+qysat(l,iq) ) / ptimestep 1163 else 1164 dyccondbar(ig,l,iq+nmicro) = 0.0 1165 endif 1166 enddo 1167 enddo 1168 enddo 1169 1170 if ( callclouds ) dyccondbar(:,:,ices_indx) = 0.0 ! Condensation have been calculated in the cloud microphysics 1171 1172 do iq=1,nkim 1173 ychimbar(:,:,iq) = ychimbar(:,:,iq) + dyccondbar(:,:,iq+nmicro) 1174 enddo 1175 1176 endif ! if ( moyzon_ch .and. mod(icount-1,ichim).eq. 0 ) 1177 1178 ! ii. Photochemistry ( must be call after condensation) 1179 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 1180 if( mod(icount-1,ichim).eq.0. ) then 1181 1182 print *, "We enter in the chemistry ..." 1183 1184 if (moyzon_ch) then ! 2D zonally averaged chemistry 1185 1186 ! Here we send zonal average fields ( corrected with cond ) from dynamics to chem. module 1187 call calchim(ngrid,ychimbar,declin,ctimestep,ztfibar,zphibar, & 1188 zplaybar,zplevbar,zzlaybar,zzlevbar,dycchi) 1189 else ! 3D chemistry (or 1D run) 1190 call calchim(ngrid,ychim,declin,ctimestep,pt,pphi, & 1191 pplay,pplev,zzlay,zzlev,dycchi) 1192 endif ! if moyzon 1193 1194 endif 1195 1196 do iq=1,nkim 1197 zdqchi(:,:,iq+nmicro) = dycchi(:,:,iq)*rat_mmol(iq+nmicro) ! convert tendencies to mass mixing ratio 1198 1199 where( (pq(:,:,iq+nmicro) + ( pdq(:,:,iq+nmicro)+zdqchi(:,:,iq+nmicro) )*ptimestep ) .LT. 0.) & ! When using zonal means we set the same tendency 1200 zdqchi(:,:,iq+nmicro) = 1.e-30 - pdq(:,:,iq+nmicro) - pq(:,:,iq+nmicro)/ptimestep ! everywhere in longitude -> could lead to negs ! 1201 enddo 1202 1203 pdq(:,:,:) = pdq(:,:,:) + zdqchi(:,:,:) 1204 1205 endif ! end of 'callchim' 1206 1153 1207 ! --------------- 1154 1208 ! V.3 Updates … … 1224 1278 1225 1279 ! Note : For output only: the actual model integration is performed in the dynamics. 1226 1227 1228 1280 1229 1281 ! Temperature, zonal and meridional winds. … … 1457 1509 if (tracer) then 1458 1510 1459 if (callmufi) then ! For now we assume an given order for tracers ! 1511 if (callmufi) then 1512 ! Microphysical tracers are expressed in unit/m3. 1513 ! convert X.kg-1 --> X.m-3 1514 ALLOCATE(i2e2d(ngrid,nlayer)) 1515 i2e2d(:,:) = ( pplev(:,1:nlayer)-pplev(:,2:nlayer+1) ) / g /(zzlev(:,2:nlayer+1)-zzlev(:,1:nlayer)) 1516 1460 1517 #ifdef USE_QTEST 1461 1518 ! Microphysical tracers passed through dyn+phys(except mufi) 1462 call writediagfi(ngrid,"mu_m0as_dp","Dynphys only spherical mode 0th order moment",' kg/kg',3,zq(:,:,1))1463 call writediagfi(ngrid,"mu_m3as_dp","Dynphys only spherical mode 3rd order moment",' kg/kg',3,zq(:,:,2))1464 call writediagfi(ngrid,"mu_m0af_dp","Dynphys only fractal mode 0th order moment",' kg/kg',3,zq(:,:,3))1465 call writediagfi(ngrid,"mu_m3af_dp","Dynphys only fractal mode 3rd order moment",' kg/kg',3,zq(:,:,4))1519 call writediagfi(ngrid,"mu_m0as_dp","Dynphys only spherical mode 0th order moment",'m-3',3,zq(:,:,micro_indx(1))*i2e2d) 1520 call writediagfi(ngrid,"mu_m3as_dp","Dynphys only spherical mode 3rd order moment",'m3/m3',3,zq(:,:,micro_indx(2))*i2e2d) 1521 call writediagfi(ngrid,"mu_m0af_dp","Dynphys only fractal mode 0th order moment",'m-3',3,zq(:,:,micro_indx(3))*i2e2d) 1522 call writediagfi(ngrid,"mu_m3af_dp","Dynphys only fractal mode 3rd order moment",'m3/m3',3,zq(:,:,micro_indx(4))*i2e2d) 1466 1523 ! Microphysical tracers passed through mufi only 1467 call writediagfi(ngrid,"mu_m0as_mo","Mufi only spherical mode 0th order moment",' kg/kg',3,tpq(:,:,1))1468 call writediagfi(ngrid,"mu_m3as_mo","Mufi only spherical mode 3rd order moment",' kg/kg',3,tpq(:,:,2))1469 call writediagfi(ngrid,"mu_m0af_mo","Mufi only fractal mode 0th order moment",' kg/kg',3,tpq(:,:,3))1470 call writediagfi(ngrid,"mu_m3af_mo","Mufi only fractal mode 3rd order moment",' kg/kg',3,tpq(:,:,4))1524 call writediagfi(ngrid,"mu_m0as_mo","Mufi only spherical mode 0th order moment",'m-3',3,tpq(:,:,micro_indx(1))*i2e2d) 1525 call writediagfi(ngrid,"mu_m3as_mo","Mufi only spherical mode 3rd order moment",'m3/m3',3,tpq(:,:,micro_indx(2))*i2e2d) 1526 call writediagfi(ngrid,"mu_m0af_mo","Mufi only fractal mode 0th order moment",'m-3',3,tpq(:,:,micro_indx(3))*i2e2d) 1527 call writediagfi(ngrid,"mu_m3af_mo","Mufi only fractal mode 3rd order moment",'m3/m3',3,tpq(:,:,micro_indx(4))*i2e2d) 1471 1528 #else 1472 call writediagfi(ngrid,"mu_m0as","Spherical mode 0th order moment",' kg/kg',3,zq(:,:,1))1473 call writediagfi(ngrid,"mu_m3as","Spherical mode 3rd order moment",' kg/kg',3,zq(:,:,2))1474 call writediagfi(ngrid,"mu_m0af","Fractal mode 0th order moment",' kg/kg',3,zq(:,:,3))1475 call writediagfi(ngrid,"mu_m3af","Fractal mode 3rd order moment",' kg/kg',3,zq(:,:,4))1529 call writediagfi(ngrid,"mu_m0as","Spherical mode 0th order moment",'m-3',3,zq(:,:,micro_indx(1))*i2e2d) 1530 call writediagfi(ngrid,"mu_m3as","Spherical mode 3rd order moment",'m3/m3',3,zq(:,:,micro_indx(2))*i2e2d) 1531 call writediagfi(ngrid,"mu_m0af","Fractal mode 0th order moment",'m-3',3,zq(:,:,micro_indx(3))*i2e2d) 1532 call writediagfi(ngrid,"mu_m3af","Fractal mode 3rd order moment",'m3/m3',3,zq(:,:,micro_indx(4))*i2e2d) 1476 1533 #endif 1534 1535 DEALLOCATE(i2e2d) 1536 1537 ! Microphysical diagnostics 1538 call writediagfi(ngrid,"mmd_aer_prec","Total aerosols precipitations",'m',2,mmd_aer_prec) 1539 call writediagfi(ngrid,"mmd_aer_s_flux","Spherical aerosols sedimentation flux",'kg.m-2.s-1',3,mmd_aer_s_flux) 1540 call writediagfi(ngrid,"mmd_aer_f_flux","Fractal aerosols sedimentation flux",'kg.m-2.s-1',3,mmd_aer_f_flux) 1541 call writediagfi(ngrid,"mmd_rc_sph","Spherical mode caracteristic radius",'m',3,mmd_rc_sph) 1542 call writediagfi(ngrid,"mmd_rc_fra","Fractal mode caracteristic radius",'m',3,mmd_rc_fra) 1543 1477 1544 endif ! end of 'callmufi' 1478 1545 1479 if ( callchim .and. (.not. callmufi) ) then 1480 call writediagfi(ngrid,"C2H2","C2H2",'kg/kg',3,zq(:,:,10)) 1481 call writediagfi(ngrid,"C2H4","C2H4",'kg/kg',3,zq(:,:,12)) 1482 call writediagfi(ngrid,"C2H6","C2H6",'kg/kg',3,zq(:,:,14)) 1483 call writediagfi(ngrid,"C4H2","C4H2",'kg/kg',3,zq(:,:,26)) 1484 call writediagfi(ngrid,"HCN","HCN",'kg/kg',3,zq(:,:,36)) 1485 call writediagfi(ngrid,"HC3N","HC3N",'kg/kg',3,zq(:,:,42)) 1486 else if ( callchim .and. callmufi ) then 1487 call writediagfi(ngrid,"C2H2","C2H2",'kg/kg',3,zq(:,:,14)) 1488 call writediagfi(ngrid,"C2H4","C2H4",'kg/kg',3,zq(:,:,16)) 1489 call writediagfi(ngrid,"C2H6","C2H6",'kg/kg',3,zq(:,:,18)) 1490 call writediagfi(ngrid,"C4H2","C4H2",'kg/kg',3,zq(:,:,30)) 1491 call writediagfi(ngrid,"HCN","HCN",'kg/kg',3,zq(:,:,40)) 1492 call writediagfi(ngrid,"HC3N","HC3N",'kg/kg',3,zq(:,:,46)) 1493 endif 1546 ! Chemical tracers 1547 if (callchim) then 1548 do iq=1,nkim 1549 call writediagfi(ngrid,cnames(iq),cnames(iq),'mol/mol',3,zq(:,:,iq+nmicro)/rat_mmol(iq+nmicro)) 1550 enddo 1551 endif 1494 1552 1495 1553 endif ! end of 'tracer' … … 1532 1590 CALL send_xios_field("dtrad",dtrad) 1533 1591 CALL send_xios_field("dtdyn",zdtdyn) 1534 1592 1593 ! Chemical tracers 1594 if (callchim) then 1595 do iq=1,nkim 1596 CALL send_xios_field(cnames(iq),zq(:,:,iq+nmicro)/rat_mmol(iq+nmicro)) 1597 enddo 1598 endif 1599 1600 ! Microphysical tracers 1601 if (callmufi) then 1602 CALL send_xios_field("mu_m0as",zq(:,:,micro_indx(1))*i2e2d) 1603 CALL send_xios_field("mu_m3as",zq(:,:,micro_indx(2))*i2e2d) 1604 CALL send_xios_field("mu_m0af",zq(:,:,micro_indx(3))*i2e2d) 1605 CALL send_xios_field("mu_m3af",zq(:,:,micro_indx(4))*i2e2d) 1606 endif 1607 1535 1608 if (lastcall.and.is_omp_master) then 1536 1609 write(*,*) "physiq: call xios_context_finalize" -
TabularUnified trunk/LMDZ.TITAN/libf/phytitan/tracer_h.F90 ¶
r1903 r1926 1 1 ! WARNING (JB 27/03/2018) 2 ! 3 ! OpenMP directives in this module are inconsistent: 4 ! - sizes (nmicro...) are thread private \___ BUT BOTH ARE INITIALIZED IN THE SAME ROUTINE 5 ! - indexes array are common / 6 ! 7 ! Tracers sizes do not need to be private. 8 ! In such case, OMP THREADPRIVATE should be removed and initracer2 should be called within an OMP SINGLE statement. 9 ! 2 10 MODULE tracer_h 3 11 !! Stores data related to physics tracers. … … 51 59 !! dynamics counterpart. 52 60 !! 53 !! In addition, it initializes arrays of indexes for the different sub-process s of the physics:61 !! In addition, it initializes arrays of indexes for the different sub-processes of the physics: 54 62 !! 55 63 !! - tracers_h:micro_indxs, the array of tracers indexes used for the microphysics.
Note: See TracChangeset
for help on using the changeset viewer.