Changeset 3153 for trunk/LMDZ.MARS
- Timestamp:
- Dec 9, 2023, 6:13:21 PM (12 months ago)
- Location:
- trunk/LMDZ.MARS
- Files:
-
- 3 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.MARS/changelog.txt
r3151 r3153 4388 4388 4389 4389 == 07/12/2023 == LL 4390 4391 4390 Switching pbl_parameter.F into a module. Cleaning of unused variables/sections in it. 4392 4391 Correction in the computations of ustar, thetastar as it was done in a different way compare to vdif_cd. It is now self-consistent. 4393 4392 Maybe pbl_surface in the MCD needs also to be changed ? In discussion with Ehouarn and Aymeric. 4393 4394 == 09/12/2023 == LL 4395 Add the possibility to compute Cd; Ch based on the virtual potential temperature to account for water flotability. 4396 To do so, a boolean "virtual", set to false by default, must be set to true (for now hard coded as future modifications will follow). -
trunk/LMDZ.MARS/libf/phymars/vdif_cd_mod.F90
r3150 r3153 16 16 CONTAINS 17 17 18 SUBROUTINE vdif_cd(ngrid,nlay,pz0,pg,pz,p u,pv,wstar,pts,ph,pcdv,pcdh)18 SUBROUTINE vdif_cd(ngrid,nlay,pz0,pg,pz,pp,pu,pv,wstar,pts,ph,virtual,mumean,pqvap,pqsurf,pcdv,pcdh) 19 19 20 20 use comcstfi_h 21 21 use turb_mod, only: turb_resolved 22 22 use watersat_mod, only: watersat 23 23 24 24 IMPLICIT NONE … … 38 38 ! inputs: 39 39 ! ------ 40 ! ngrid size of the horizontal grid 41 ! pg gravity (m s -2) 42 ! pz(ngrid,nlay) height of layers 43 ! pu(ngrid,nlay) u component of the wind 44 ! pv(ngrid,nlay) v component of the wind 45 ! pts(ngrid) surface temperature 46 ! ph(ngrid) potential temperature T*(p/ps)^kappa 40 ! ngrid size of the horizontal grid 41 ! pg gravity (m s -2) 42 ! pz(ngrid,nlay) height of layers 43 ! pp(ngrid,nlay) pressure of layers 44 ! pu(ngrid,nlay) u component of the wind 45 ! pv(ngrid,nlay) v component of the wind 46 ! pts(ngrid) surface temperature 47 ! ph(ngrid) potential temperature T*(p/ps)^kappa 48 ! virtual Boolean to account for vapor flottability 49 ! mumean Molecular mass of the atmosphere (kg/mol) 50 ! pqvap(ngrid,nlay) Water vapor mixing ratio (kg/kg) to account for vapor flottability 51 ! pqsurf(ngrid) Water ice frost on the surface(kg/m^2) to account for vapor flottability 47 52 ! 48 53 ! outputs: … … 67 72 INTEGER, INTENT(IN) :: ngrid,nlay ! Number of points in the physical grid and atmospheric grid 68 73 REAL, INTENT(IN) :: pz0(ngrid) ! Surface Roughness (m) 69 REAL, INTENT(IN) :: pg,pz(ngrid,nlay) ! Mars gravity (m/s^2) 74 REAL, INTENT(IN) :: pg ! Mars gravity (m/s^2) 75 REAL, INTENT(IN) :: pz(ngrid,nlay),pp(ngrid,nlay) ! Layers pseudo altitudes (m) and pressure (Pa) 70 76 REAL, INTENT(IN) :: pu(ngrid,nlay),pv(ngrid,nlay) ! Zonal and Meriditionnal winds (m/s) 71 77 REAL, INTENT(IN) :: pts(ngrid),ph(ngrid,nlay) ! Surface Temperature and atmospheric temperature (K) 72 78 REAL, INTENT(IN) :: wstar(ngrid) ! Vertical velocity due to turbulence (m/s) 79 LOGICAL, INTENT(IN) :: virtual ! Boolean to account for vapor flottability 80 REAL, INTENT(IN) :: mumean(ngrid) ! Molecular mass of the atmosphere (kg/mol) 81 REAL, INTENT(IN) :: pqvap(ngrid,nlay) ! Water vapor mixing ratio (kg/kg) to account for vapor flottability 82 REAL, INTENT(IN) :: pqsurf(ngrid) ! Water ice frost on the surface (kg/m^2) to account for vapor flottability 73 83 74 84 ! Outputs: … … 117 127 REAL z1z0,z1z0t ! ratios z1/z0 and z1/z0T 118 128 REAL z1,zcd0 ! Neutral roughness (m) and Cd/Ch coefficient when call richls is not called 119 129 REAL tsurf_v(ngrid) ! Virtual surface temperature, accounting for vapor flottability 130 REAL temp_v(ngrid) ! Potential virtual air temperature in the frist layer, accounting for vapor flottability 131 REAL mu_h2o ! Molecular mass of water vapor (kg/mol) 132 REAL tol_frost ! Tolerance to consider the effect of frost on the surface 133 REAL qsat(ngrid) ! saturated mixing ratio of water vapor 134 120 135 ! Code: 121 136 ! -------- … … 124 139 itemax= 10 125 140 tol_iter = 0.01 141 mu_h2o = 18e-3 142 126 143 reynolds(:) = 0. 127 144 pz0t = 0. … … 141 158 142 159 ric = betah/(betam**2) 160 161 IF(virtual) then 162 DO ig = 1,ngrid 163 temp_v(ig) = ph(ig,1)*(1.+pqvap(ig,1)/(mu_h2o/mumean(ig)))/(1.+pqvap(ig,1)) 164 call watersat(1,pts(ig),pp(ig,1),qsat(ig)) 165 tsurf_v(ig) = pts(ig)*(1.+qsat(ig)/(mu_h2o/mumean(ig)))/(1.+qsat(ig)) 166 ENDDO 167 ELSE 168 tsurf_v(:) = pts(:) 169 temp_v(:) = ph(:,1) 170 ENDIF 143 171 144 172 IF(.not.callrichsl) then … … 170 198 IF(turb_resolved) zu2(ig)=MAX(zu2(ig),1.) 171 199 ! Richardson number formulation proposed by D.E. England et al. (1995) 172 rib(ig) = (pg/ pts(ig))*sqrt(pz(ig,1)*pz0(ig))*(((log(pz(ig,1)/pz0(ig)))**2)/(log(pz(ig,1)/pz0t)))*(ph(ig,1)-pts(ig))/zu2(ig)200 rib(ig) = (pg/tsurf_v(ig))*sqrt(pz(ig,1)*pz0(ig))*(((log(pz(ig,1)/pz0(ig)))**2)/(log(pz(ig,1)/pz0t)))*(temp_v(ig)-tsurf_v(ig))/zu2(ig) 173 201 ELSE 174 202 print*,'warning, infinite Richardson at surface' -
trunk/LMDZ.MARS/libf/phymars/vdifc_mod.F
r3150 r3153 208 208 REAL,SAVE :: m_co2, m_noco2, A , B 209 209 REAL vmr_co2(ngrid,nlay) 210 REAL qco2,mmean 210 REAL qco2,mmean(ngrid,nlay) 211 211 212 212 !$OMP THREADPRIVATE(ico2,m_co2,m_noco2,A,B) … … 235 235 REAL zdqsdif_tot(ngrid) ! subtimestep pdqsdif for water ice 236 236 LOGICAL :: writeoutput ! boolean to say to soilexchange.F if we are at the last iteration and thus if he can write in the diagsoil 237 238 !! Water buyoncy 239 LOGICAL :: virtual 240 241 237 242 238 243 c ** un petit test de coherence … … 297 302 zdqsdif_tot(1:ngrid)=0 298 303 h2o_ice_depth(1:ngrid,1:nslope)=1 304 305 virtual = .false. 306 299 307 c ** calcul de rho*dz et dt*rho/dz=dt*rho**2 g/dp 300 308 c avec rho=p/RT=p/ (R Theta) (p/ps)**kappa … … 354 362 & ,pq(ig,ilev,ico2)+pdqfi(ig,ilev,ico2)*ptimestep) 355 363 c Mean air molecular mass = 1/(q(ico2)/m_co2 + (1-q(ico2))/m_noco2) 356 mmean =1/(A*qco2 +B)357 vmr_co2(ig,ilev) = qco2*mmean /m_co2364 mmean(ig,ilev)=1/(A*qco2 +B) 365 vmr_co2(ig,ilev) = qco2*mmean(ig,ilev)/m_co2 358 366 ENDDO 359 367 ENDDO … … 412 420 c --------------------- 413 421 414 CALL vdif_cd(ngrid,nlay,pz0,g,pzlay,pu,pv,wstar,ptsrf_tmp 415 & ,ph,zcdv_true,zcdh_true) 422 CALL vdif_cd(ngrid,nlay,pz0,g,pzlay,pplay,pu,pv,wstar,ptsrf_tmp, 423 & ph,virtual,mmean(:,1),zq(:,:,igcm_h2o_vap), 424 & pqsurf(:,igcm_h2o_ice,major_slope(:)), 425 & zcdv_true,zcdh_true) 416 426 417 427 zu2(:)=pu(:,1)*pu(:,1)+pv(:,1)*pv(:,1)
Note: See TracChangeset
for help on using the changeset viewer.