Changeset 3682 for trunk/LMDZ.TITAN/libf/muphytitan/mm_clouds.f90
- Timestamp:
- Mar 14, 2025, 2:27:06 PM (3 months ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.TITAN/libf/muphytitan/mm_clouds.f90
r3496 r3682 101 101 IF (mm_w_cloud_nucond) THEN 102 102 ! Calls condensation/nucleation (and update saturation ratio diagnostic) 103 call mm_cloud_nucond(dm0a,dm3a,dm0n,dm3n,dm3i,dgazs,mm_gazs_sat) 103 ! ADDED : Extraction of nucleation and growth rates 104 call mm_cloud_nucond(dm0a,dm3a,dm0n,dm3n,dm3i,dgazs,mm_gazs_sat,mm_nrate,mm_grate) 104 105 ENDIF 105 106 … … 134 135 !----------------------------------------------------------------------------- 135 136 136 SUBROUTINE mm_cloud_nucond(dm0a,dm3a,dm0n,dm3n,dm3i,dgazs,gazsat )137 SUBROUTINE mm_cloud_nucond(dm0a,dm3a,dm0n,dm3n,dm3i,dgazs,gazsat,nrate,grate) 137 138 !! Get moments tendencies through nucleation/condensation/evaporation. 138 139 !! … … 166 167 REAL(kind=mm_wp), DIMENSION(:,:), INTENT(out) :: gazsat 167 168 !! Saturation ratio of each condensible specie. 169 170 ! ADDED : Extraction of the nucleation and growth rate 171 REAL(kind=mm_wp), DIMENSION(:,:),INTENT(out) :: nrate 172 !! Nucleation rate values of each condensible species (\(m^{-2}.s^{-1}\)). 173 REAL(kind=mm_wp), DIMENSION(:,:),INTENT(out) :: grate 174 !! Growth rate values of each condensible species (\(m^{2}.s^{-1}\)). 175 168 176 INTEGER :: i,idx 169 177 REAL(kind=mm_wp), DIMENSION(:,:), ALLOCATABLE :: zdm0a,zdm3a,zdm0n,zdm3n … … 175 183 DO i = 1, mm_nesp 176 184 call nc_esp(mm_xESPS(i),mm_gazs(:,i),mm_m3ice(:,i),dgazs(:,i),dm3i(:,i), & 177 zdm0a(:,i),zdm3a(:,i),zdm0n(:,i),zdm3n(:,i),gazsat(:,i)) 185 zdm0a(:,i),zdm3a(:,i),zdm0n(:,i),zdm3n(:,i),gazsat(:,i),nrate(:,i),grate(:,i)) 186 ! ADDED : Extraction of nucleation and growth rates 178 187 ENDDO 179 188 … … 200 209 END SUBROUTINE mm_cloud_nucond 201 210 202 SUBROUTINE nc_esp(xESP,vapX,m3iX,dvapX,dm3iX,dm0aer,dm3aer,dm0ccn,dm3ccn,Xsat )211 SUBROUTINE nc_esp(xESP,vapX,m3iX,dvapX,dm3iX,dm0aer,dm3aer,dm0ccn,dm3ccn,Xsat,Xnrate,Xgrate) ! ADDED : arguments nrate, grate 203 212 !! Get moments tendencies through nucleation/condensation/evaporation of a given condensible specie. 204 213 !! … … 230 239 REAL(kind=mm_wp),INTENT(out), DIMENSION(:) :: Xsat 231 240 !! Saturation ratio values on the vertical grid (--). 241 242 ! ADDED : Extraction of the nucleation and growth rate 243 REAL(kind=mm_wp),INTENT(out), DIMENSION(:) :: Xnrate 244 !! Nucleation rate values on the vertical grid for the species X (\(m^{-2}.s^{-1}\)). 245 REAL(kind=mm_wp),INTENT(out), DIMENSION(:) :: Xgrate 246 !! Growth rate values on the vertical grid for the species X (\(m^{2}.s^{-1}\)). 247 248 232 249 INTEGER :: i 233 250 REAL(kind=mm_wp) :: bef,aft … … 281 298 ! Then, from eq. 2: 282 299 ! Mn(k)[t+dt] = Mn(k)[t] + CST_M(k)/(1+CST_M(k))*Ma(k)[t] (4) 300 301 ! Copies the nucleation rate into an output variable 302 Xnrate = nucr 303 283 304 cm0 = 4._mm_wp*mm_pi*nucr/mm_rm*mm_alpha_f(3._mm_wp)*mm_rcf**3*mm_dt 284 305 cm3 = 4._mm_wp*mm_pi*nucr/mm_rm*mm_alpha_f(6._mm_wp)/mm_alpha_f(3._mm_wp)*mm_rcf**3*mm_dt … … 317 338 ! gets "true" growth rate 318 339 grate = grate * (newvap/qsat - seq) 340 ! Copies the growth rate into an output variable 341 Xgrate = grate 319 342 320 343 ! computes tendencies through condensation … … 377 400 REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: sat !! Saturation ratio of given specie (--). 378 401 TYPE(mm_esp), INTENT(in) :: xESP !! X specie properties (--). 379 REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: rate !! The nucleation rate (\(m^ -{2}.s^{-1}\)).402 REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: rate !! The nucleation rate (\(m^{-2}.s^{-1}\)). 380 403 INTEGER :: i 381 404 REAL(kind=mm_wp) :: r,t,s,sig,nX,rstar,gstar,x,zeldov,deltaf,fsh,fstar
Note: See TracChangeset
for help on using the changeset viewer.