Changeset 3682 for trunk/LMDZ.TITAN
- Timestamp:
- Mar 14, 2025, 2:27:06 PM (3 months ago)
- Location:
- trunk/LMDZ.TITAN/libf
- Files:
-
- 6 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 -
trunk/LMDZ.TITAN/libf/muphytitan/mm_globals.f90
r3657 r3682 522 522 REAL(kind=mm_wp), DIMENSION(:,:), ALLOCATABLE, SAVE :: mm_ice_fluxes 523 523 524 !> Condensible components nucleation rates. 525 !! 526 !! It is a 2D-array with the vertical layers in first dimension and the number of condensible 527 !! species in the second. 528 !! It is updated in [[mm_clouds(module):mm_cloud_microphysics(subroutine)]]. 529 REAL(kind=mm_wp), DIMENSION(:,:), ALLOCATABLE, SAVE :: mm_nrate 530 531 !> Condensible components growth rates. 532 !! 533 !! It is a 2D-array with the vertical layers in first dimension and the number of condensible 534 !! species in the second. 535 !! It is updated in [[mm_clouds(module):mm_cloud_microphysics(subroutine)]]. 536 REAL(kind=mm_wp), DIMENSION(:,:), ALLOCATABLE, SAVE :: mm_grate 537 524 538 !> Condensible species saturation ratio (--). 525 539 !! … … 583 597 !$OMP THREADPRIVATE(mm_rcs,mm_rcf,mm_drad,mm_drho) 584 598 !$OMP THREADPRIVATE(mm_m0as_vsed,mm_m3as_vsed,mm_m0af_vsed,mm_m3af_vsed) 585 !$OMP THREADPRIVATE(mm_aer_s_flux,mm_aer_f_flux,mm_ccn_vsed,mm_ccn_flux,mm_ice_prec,mm_ice_fluxes,mm_gazs_sat )599 !$OMP THREADPRIVATE(mm_aer_s_flux,mm_aer_f_flux,mm_ccn_vsed,mm_ccn_flux,mm_ice_prec,mm_ice_fluxes,mm_gazs_sat, mm_nrate, mm_grate) 586 600 !$OMP THREADPRIVATE(mm_m0as_min,mm_m3as_min,mm_rcs_min,mm_m0af_min,mm_m3af_min,mm_rcf_min,mm_m0n_min,mm_m3cld_min) 587 601 !$OMP THREADPRIVATE(mm_nla,mm_nle) … … 1251 1265 ALLOCATE(mm_gazs_sat(mm_nla,mm_nesp)) ; mm_gazs_sat(:,:) = 0._mm_wp 1252 1266 ENDIF 1267 ! ADDED : Allocate memory for nucleation and growth rate 1268 IF (.NOT.ALLOCATED(mm_nrate)) THEN 1269 ALLOCATE(mm_nrate(mm_nla,mm_nesp)) ; mm_nrate(:,:) = 0._mm_wp 1270 ENDIF 1271 IF (.NOT.ALLOCATED(mm_grate)) THEN 1272 ALLOCATE(mm_grate(mm_nla,mm_nesp)) ; mm_grate(:,:) = 0._mm_wp 1273 ENDIF 1253 1274 1254 1275 ! note mm_dzlev already from top to ground -
trunk/LMDZ.TITAN/libf/muphytitan/mm_microphysic.f90
r3496 r3682 163 163 END FUNCTION muphys_nocld 164 164 165 SUBROUTINE mm_diagnostics(dt,aer_prec,aer_s_w,aer_f_w,aer_s_flux,aer_f_flux,ccn_prec,ccn_w,ccn_flux,ice_prec,ice_fluxes,gazs_sat )165 SUBROUTINE mm_diagnostics(dt,aer_prec,aer_s_w,aer_f_w,aer_s_flux,aer_f_flux,ccn_prec,ccn_w,ccn_flux,ice_prec,ice_fluxes,gazs_sat,nrate,grate) 166 166 !! Get various diagnostic fields of the microphysics. 167 167 !! … … 171 171 !! - Settling velocity (aerosols -total-, CCN and ices) 172 172 !! - Precipitations (aerosols -total-, CCN and ices) 173 !! - condensible gazes saturation ratio 173 !! - Condensible gazes saturation ratio 174 !! - Nucleation and growth rates 174 175 !! 175 176 !! @note … … 197 198 REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: gazs_sat !! Condensible gaz saturation ratios (--). 198 199 REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:) :: ice_prec !! Ice precipitations (\(kg.m^{-2}.s^{-1}\)). 200 ! Nucleation and growth rates 201 REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: nrate !! Nucleation rate (\(m^{-2}.s^{-1}\)). 202 REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: grate !! Growth rate (\(m^{2}.s^{-1}\)). 199 203 200 204 IF (PRESENT(aer_prec)) aer_prec = ABS(mm_aer_prec) / dt … … 211 215 IF (PRESENT(ice_fluxes)) ice_fluxes = mm_ice_fluxes(mm_nla:1:-1,:) 212 216 IF (PRESENT(gazs_sat)) gazs_sat = mm_gazs_sat(mm_nla:1:-1,:) 217 ! Nucleation and growth rates 218 IF (PRESENT(nrate)) nrate = mm_nrate(mm_nla:1:-1,:) 219 IF (PRESENT(grate)) grate = mm_grate(mm_nla:1:-1,:) 213 220 ELSE 214 221 IF (PRESENT(ccn_prec)) ccn_prec = 0._mm_wp … … 218 225 IF (PRESENT(ice_fluxes)) ice_fluxes = 0._mm_wp 219 226 IF (PRESENT(gazs_sat)) gazs_sat = 0._mm_wp 227 ! Nucleation and growth rates 228 IF (PRESENT(nrate)) nrate = 0._mm_wp 229 IF (PRESENT(grate)) grate = 0._mm_wp 220 230 ENDIF 221 231 END SUBROUTINE mm_diagnostics -
trunk/LMDZ.TITAN/libf/phytitan/calmufi.F90
r3656 r3682 167 167 call mm_diagnostics(dt,mmd_aer_prec(ilon),mmd_aer_s_w(ilon,:),mmd_aer_f_w(ilon,:),mmd_aer_s_flux(ilon,:),mmd_aer_f_flux(ilon,:), & 168 168 mmd_ccn_prec(ilon),mmd_ccn_w(ilon,:),mmd_ccn_flux(ilon,:),mmd_ice_prec(ilon,:), & 169 mmd_ice_fluxes(ilon,:,:),mmd_gazs_sat(ilon,:,:)) 169 mmd_ice_fluxes(ilon,:,:),mmd_gazs_sat(ilon,:,:),mmd_nrate(ilon,:,:),mmd_grate(ilon,:,:)) 170 ! ADDED ABOVE : Nucleation and growth rates 170 171 call mm_get_radii(mmd_rc_sph(ilon,:),mmd_rc_fra(ilon,:),mmd_rc_cld(ilon,:)) 171 172 -
trunk/LMDZ.TITAN/libf/phytitan/muphy_diag.F90
r3497 r3682 26 26 REAL(kind=8), ALLOCATABLE, DIMENSION(:,:) :: mmd_rc_fra !! Fractal mode characteristic radius (m). 27 27 REAL(kind=8), ALLOCATABLE, DIMENSION(:,:) :: mmd_rc_cld !! Cloud drop radius (m). 28 ! Nucleation and growth rates 29 REAL(kind=8), ALLOCATABLE, DIMENSION(:,:,:) :: mmd_nrate !! Condensible species nucleation rate (\(m^{-2}.s^{-1}\)). 30 REAL(kind=8), ALLOCATABLE, DIMENSION(:,:,:) :: mmd_grate !! Condensible species growth rate (\(m^{2}.s^{-1}\)). 28 31 29 32 !$OMP THREADPRIVATE(mmd_aer_prec,mmd_ccn_prec,mmd_aer_s_w,mmd_aer_f_w,mmd_ccn_w,mmd_aer_s_flux,mmd_aer_f_flux,mmd_ccn_flux,mmd_ice_fluxes) … … 51 54 ALLOCATE(mmd_rc_fra(ngrid,nlayer)) 52 55 ALLOCATE(mmd_rc_cld(ngrid,nlayer)) 56 ! Nucleation and growth rates 57 ALLOCATE(mmd_nrate(ngrid,nlayer,nices)) 58 ALLOCATE(mmd_grate(ngrid,nlayer,nices)) 53 59 54 60 mmd_aer_prec(:) = 0d0 … … 66 72 mmd_rc_fra(:,:) = 0d0 67 73 mmd_rc_cld(:,:) = 0d0 74 ! Nucleation and growth rates 75 mmd_nrate(:,:,:) = 0d0 76 mmd_grate(:,:,:) = 0d0 68 77 69 78 END SUBROUTINE ini_diag_arrays … … 85 94 IF (ALLOCATED(mmd_rc_fra)) DEALLOCATE(mmd_rc_fra) 86 95 IF (ALLOCATED(mmd_rc_cld)) DEALLOCATE(mmd_rc_cld) 96 ! Nucleation and growth rates 97 IF (ALLOCATED(mmd_nrate)) DEALLOCATE(mmd_nrate) 98 IF (ALLOCATED(mmd_grate)) DEALLOCATE(mmd_grate) 87 99 END SUBROUTINE free_diag_arrays 88 100 END MODULE muphy_diag -
trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90
r3661 r3682 1814 1814 CALL send_xios_field('ttauhv_15',zpopthv(:,:,15,2)) ! 15 --> 1.000 um 1815 1815 CALL send_xios_field('ttauhv_20',zpopthv(:,:,20,2)) ! 20 --> 0.671 um 1816 CALL send_xios_field('ttauhv_2 3',zpopthv(:,:,23,2)) ! 23 --> 0.346um1816 CALL send_xios_field('ttauhv_21',zpopthv(:,:,21,2)) ! 21 --> 0.55 um 1817 1817 CALL send_xios_field('ttauhi_02',zpopthi(:,:,2,2)) ! 02 --> 175.3 um 1818 1818 CALL send_xios_field('ttauhi_17',zpopthi(:,:,17,2)) ! 17 --> 11.00 um … … 1822 1822 CALL send_xios_field('kkhv_15',zpopthv(:,:,15,3)) 1823 1823 CALL send_xios_field('kkhv_20',zpopthv(:,:,20,3)) 1824 CALL send_xios_field('kkhv_2 3',zpopthv(:,:,23,3))1824 CALL send_xios_field('kkhv_21',zpopthv(:,:,21,3)) 1825 1825 CALL send_xios_field('kkhi_02',zpopthi(:,:,2,3)) 1826 1826 CALL send_xios_field('kkhi_17',zpopthi(:,:,17,3)) … … 1830 1830 CALL send_xios_field('wwhv_15',zpopthv(:,:,15,4)) 1831 1831 CALL send_xios_field('wwhv_20',zpopthv(:,:,20,4)) 1832 CALL send_xios_field('wwhv_2 3',zpopthv(:,:,23,4))1832 CALL send_xios_field('wwhv_21',zpopthv(:,:,21,4)) 1833 1833 CALL send_xios_field('wwhi_02',zpopthi(:,:,2,4)) 1834 1834 CALL send_xios_field('wwhi_17',zpopthi(:,:,17,4)) … … 1838 1838 CALL send_xios_field('gghv_15',zpopthv(:,:,15,5)) 1839 1839 CALL send_xios_field('gghv_20',zpopthv(:,:,20,5)) 1840 CALL send_xios_field('gghv_2 3',zpopthv(:,:,23,5))1840 CALL send_xios_field('gghv_21',zpopthv(:,:,21,5)) 1841 1841 CALL send_xios_field('gghi_02',zpopthi(:,:,2,5)) 1842 1842 CALL send_xios_field('gghi_17',zpopthi(:,:,17,5)) … … 1849 1849 CALL send_xios_field('ttauv_15',zpopttv(:,:,15,2)) ! 15 --> 1.000 um 1850 1850 CALL send_xios_field('ttauv_20',zpopttv(:,:,20,2)) ! 20 --> 0.671 um 1851 CALL send_xios_field('ttauv_2 3',zpopttv(:,:,23,2)) ! 23 --> 0.346um1851 CALL send_xios_field('ttauv_21',zpopttv(:,:,21,2)) ! 21 --> 0.55 um 1852 1852 CALL send_xios_field('ttaui_02',zpoptti(:,:,2,2)) ! 02 --> 175.3 um 1853 1853 CALL send_xios_field('ttaui_17',zpoptti(:,:,17,2)) ! 17 --> 11.00 um … … 1857 1857 CALL send_xios_field('kkv_15',zpopttv(:,:,15,3)) 1858 1858 CALL send_xios_field('kkv_20',zpopttv(:,:,20,3)) 1859 CALL send_xios_field('kkv_2 3',zpopttv(:,:,23,3))1859 CALL send_xios_field('kkv_21',zpopttv(:,:,21,3)) 1860 1860 CALL send_xios_field('kki_02',zpoptti(:,:,2,3)) 1861 1861 CALL send_xios_field('kki_17',zpoptti(:,:,17,3)) … … 1865 1865 CALL send_xios_field('wwv_15',zpopttv(:,:,15,4)) 1866 1866 CALL send_xios_field('wwv_20',zpopttv(:,:,20,4)) 1867 CALL send_xios_field('wwv_2 3',zpopttv(:,:,23,4))1867 CALL send_xios_field('wwv_21',zpopttv(:,:,21,4)) 1868 1868 CALL send_xios_field('wwi_02',zpoptti(:,:,2,4)) 1869 1869 CALL send_xios_field('wwi_17',zpoptti(:,:,17,4)) … … 1873 1873 CALL send_xios_field('ggv_15',zpopttv(:,:,15,5)) 1874 1874 CALL send_xios_field('ggv_20',zpopttv(:,:,20,5)) 1875 CALL send_xios_field('ggv_2 3',zpopttv(:,:,23,5))1875 CALL send_xios_field('ggv_21',zpopttv(:,:,21,5)) 1876 1876 CALL send_xios_field('ggi_02',zpoptti(:,:,2,5)) 1877 1877 CALL send_xios_field('ggi_17',zpoptti(:,:,17,5)) … … 1942 1942 CALL send_xios_field('flux_i'//TRIM(nameOfTracer(gazs_indx(iq))),mmd_ice_fluxes(:,:,iq)) 1943 1943 CALL send_xios_field(TRIM(nameOfTracer(gazs_indx(iq)))//'_sat',mmd_gazs_sat(:,:,iq)) 1944 CALL send_xios_field(TRIM(nameOfTracer(gazs_indx(iq)))//'_nrate',mmd_nrate(:,:,iq)) 1945 CALL send_xios_field(TRIM(nameOfTracer(gazs_indx(iq)))//'_grate',mmd_grate(:,:,iq)) 1944 1946 ENDDO 1945 1947 ENDIF
Note: See TracChangeset
for help on using the changeset viewer.