PageRenderTime 107ms CodeModel.GetById 30ms RepoModel.GetById 0ms app.codeStats 2ms

/wrfv2_fire/phys/module_cu_g3.F

http://github.com/jbeezley/wrf-fire
FORTRAN Legacy | 5313 lines | 3667 code | 294 blank | 1352 comment | 275 complexity | 39bd7e8616606edac6d7d990e6a7ef28 MD5 | raw file
Possible License(s): AGPL-1.0
  1. !WRF:MODEL_LAYER:PHYSICS
  2. !
  3. MODULE module_cu_g3
  4. CONTAINS
  5. !-------------------------------------------------------------
  6. SUBROUTINE G3DRV( &
  7. DT,itimestep,DX &
  8. ,rho,RAINCV,PRATEC &
  9. ,U,V,t,W,q,p,pi &
  10. ,dz8w,p8w,XLV,CP,G,r_v &
  11. ,STEPCU,htop,hbot &
  12. ,CU_ACT_FLAG,warm_rain &
  13. ,APR_GR,APR_W,APR_MC,APR_ST,APR_AS &
  14. ,APR_CAPMA,APR_CAPME,APR_CAPMI &
  15. ,MASS_FLUX,XF_ENS,PR_ENS,HT,XLAND,gsw,edt_out &
  16. ,GDC,GDC2 ,kpbl,k22_shallow,kbcon_shallow &
  17. ,ktop_shallow,xmb_shallow &
  18. ,cugd_tten,cugd_qvten ,cugd_qcten &
  19. ,cugd_ttens,cugd_qvtens,cugd_avedx,imomentum &
  20. ,ensdim,maxiens,maxens,maxens2,maxens3,ichoice &
  21. ,ishallow_g3,ids,ide, jds,jde, kds,kde &
  22. ,ims,ime, jms,jme, kms,kme &
  23. ,ips,ipe, jps,jpe, kps,kpe &
  24. ,its,ite, jts,jte, kts,kte &
  25. ,periodic_x,periodic_y &
  26. ,RQVCUTEN,RQCCUTEN,RQICUTEN &
  27. ,RQVFTEN,RTHFTEN,RTHCUTEN &
  28. ,rqvblten,rthblten &
  29. ,F_QV ,F_QC ,F_QR ,F_QI ,F_QS &
  30. #if ( WRF_DFI_RADAR == 1 )
  31. ! Optional CAP suppress option
  32. ,do_capsuppress,cap_suppress_loc &
  33. #endif
  34. )
  35. !-------------------------------------------------------------
  36. IMPLICIT NONE
  37. !-------------------------------------------------------------
  38. INTEGER, INTENT(IN ) :: &
  39. ids,ide, jds,jde, kds,kde, &
  40. ims,ime, jms,jme, kms,kme, &
  41. ips,ipe, jps,jpe, kps,kpe, &
  42. its,ite, jts,jte, kts,kte
  43. LOGICAL periodic_x,periodic_y
  44. integer, parameter :: ens4_spread = 3 ! max(3,cugd_avedx)
  45. integer, parameter :: ens4=ens4_spread*ens4_spread
  46. integer, intent (in ) :: &
  47. ensdim,maxiens,maxens,maxens2,maxens3,ichoice
  48. INTEGER, INTENT(IN ) :: STEPCU, ITIMESTEP,cugd_avedx, &
  49. ishallow_g3,imomentum
  50. LOGICAL, INTENT(IN ) :: warm_rain
  51. REAL, INTENT(IN ) :: XLV, R_v
  52. REAL, INTENT(IN ) :: CP,G
  53. REAL, DIMENSION( ims:ime , kms:kme , jms:jme ) , &
  54. INTENT(IN ) :: &
  55. U, &
  56. V, &
  57. W, &
  58. pi, &
  59. t, &
  60. q, &
  61. p, &
  62. dz8w, &
  63. p8w, &
  64. rho
  65. REAL, DIMENSION( ims:ime , kms:kme , jms:jme ) , &
  66. OPTIONAL , &
  67. INTENT(INOUT ) :: &
  68. GDC,GDC2
  69. REAL, DIMENSION( ims:ime , jms:jme ),INTENT(IN) :: GSW,HT,XLAND
  70. INTEGER, DIMENSION( ims:ime , jms:jme ),INTENT(IN) :: KPBL
  71. INTEGER, DIMENSION( ims:ime , jms:jme ),INTENT(INOUT) :: k22_shallow, &
  72. kbcon_shallow,ktop_shallow
  73. !
  74. REAL, INTENT(IN ) :: DT, DX
  75. !
  76. REAL, DIMENSION( ims:ime , jms:jme ), &
  77. INTENT(INOUT) :: pratec,RAINCV, MASS_FLUX, &
  78. APR_GR,APR_W,APR_MC,APR_ST,APR_AS, &
  79. edt_out,APR_CAPMA,APR_CAPME,APR_CAPMI, &
  80. htop,hbot,xmb_shallow
  81. !+lxz
  82. ! REAL, DIMENSION( ims:ime , jms:jme ) :: & !, INTENT(INOUT) :: &
  83. ! HTOP, &! highest model layer penetrated by cumulus since last reset in radiation_driver
  84. ! HBOT ! lowest model layer penetrated by cumulus since last reset in radiation_driver
  85. ! ! HBOT>HTOP follow physics leveling convention
  86. LOGICAL, DIMENSION( ims:ime , jms:jme ), &
  87. INTENT(INOUT) :: CU_ACT_FLAG
  88. !
  89. ! Optionals
  90. !
  91. REAL, DIMENSION( ims:ime , kms:kme , jms:jme ), &
  92. OPTIONAL, &
  93. INTENT(INOUT) :: RTHFTEN, &
  94. cugd_tten,cugd_qvten,cugd_qcten, &
  95. cugd_ttens,cugd_qvtens, &
  96. RQVFTEN
  97. REAL, DIMENSION( ims:ime , kms:kme , jms:jme ), &
  98. OPTIONAL, &
  99. INTENT(INOUT) :: &
  100. RTHCUTEN, &
  101. RQVCUTEN, &
  102. RQVBLTEN, &
  103. RTHBLTEN, &
  104. RQCCUTEN, &
  105. RQICUTEN
  106. !
  107. ! Flags relating to the optional tendency arrays declared above
  108. ! Models that carry the optional tendencies will provdide the
  109. ! optional arguments at compile time; these flags all the model
  110. ! to determine at run-time whether a particular tracer is in
  111. ! use or not.
  112. !
  113. LOGICAL, OPTIONAL :: &
  114. F_QV &
  115. ,F_QC &
  116. ,F_QR &
  117. ,F_QI &
  118. ,F_QS
  119. #if ( WRF_DFI_RADAR == 1 )
  120. !
  121. ! option of cap suppress:
  122. ! do_capsuppress = 1 do
  123. ! do_capsuppress = other don't
  124. !
  125. !
  126. INTEGER, INTENT(IN ) ,OPTIONAL :: do_capsuppress
  127. REAL, DIMENSION( ims:ime, jms:jme ),INTENT(IN ),OPTIONAL :: cap_suppress_loc
  128. REAL, DIMENSION( its:ite ) :: cap_suppress_j
  129. #endif
  130. ! LOCAL VARS
  131. real, dimension(ims:ime,jms:jme,1:ensdim),intent(inout) :: &
  132. xf_ens,pr_ens
  133. real, dimension ( its:ite , jts:jte , 1:ensdim) :: &
  134. massflni,xfi_ens,pri_ens
  135. REAL, DIMENSION( its:ite , jts:jte ) :: MASSI_FLX, &
  136. APRi_GR,APRi_W,APRi_MC,APRi_ST,APRi_AS, &
  137. edti_out,APRi_CAPMA,APRi_CAPME,APRi_CAPMI,gswi
  138. real, dimension (its:ite,kts:kte) :: &
  139. SUBT,SUBQ,OUTT,OUTQ,OUTQC,phh,subm,cupclw,dhdt, &
  140. outts,outqs
  141. real, dimension (its:ite) :: &
  142. pret, ter11, aa0, fp,xlandi
  143. !+lxz
  144. integer, dimension (its:ite) :: &
  145. kbcon, ktop,kpbli,k22s,kbcons,ktops
  146. !.lxz
  147. integer, dimension (its:ite,jts:jte) :: &
  148. iact_old_gr
  149. integer :: iens,ibeg,iend,jbeg,jend,n,nn,ens4n
  150. integer :: ibegh,iendh,jbegh,jendh
  151. integer :: ibegc,iendc,jbegc,jendc
  152. !
  153. ! basic environmental input includes moisture convergence (mconv)
  154. ! omega (omeg), windspeed (us,vs), and a flag (aaeq) to turn off
  155. ! convection for this call only and at that particular gridpoint
  156. !
  157. real, dimension (its:ite,kts:kte) :: &
  158. T2d,q2d,PO,P2d,US,VS,tn,qo,tshall,qshall
  159. real, dimension (ips-2:ipe+2,kps:kpe,jps-2:jpe+2) :: &
  160. ave_f_t,ave_f_q
  161. real, dimension (its:ite,kts:kte,1:ens4) :: &
  162. omeg,tx,qx
  163. real, dimension (its:ite) :: &
  164. Z1,PSUR,AAEQ,direction,cuten,umean,vmean,pmean,xmbs
  165. real, dimension (its:ite,1:ens4) :: &
  166. mconv
  167. INTEGER :: i,j,k,ICLDCK,ipr,jpr
  168. REAL :: tcrit,tscl_KF,dp,dq,sub_spread,subcenter
  169. INTEGER :: itf,jtf,ktf,iss,jss,nbegin,nend
  170. INTEGER :: high_resolution
  171. REAL :: rkbcon,rktop !-lxz
  172. ! ruc variable
  173. real, dimension (its:ite) :: tkm
  174. ! A. Betts for shallow convection: suggestion for the KF timescale < DELTAX / 25 m/s
  175. tscl_kf=dx/25.
  176. !
  177. ! write(0,*)'ishallow = ',ishallow_g3
  178. high_resolution=0
  179. if(cugd_avedx.gt.1) high_resolution=1
  180. subcenter=0.
  181. ! subcenter=1./float(cugd_avedx)
  182. sub_spread=max(1.,float(cugd_avedx*cugd_avedx-1))
  183. sub_spread=(1.-subcenter)/sub_spread
  184. iens=1
  185. ipr=43
  186. jpr=1
  187. ipr=0
  188. jpr=0
  189. ! if(itimestep.eq.8)then
  190. ! ipr=37
  191. ! jpr=16
  192. ! endif
  193. IF ( periodic_x ) THEN
  194. ibeg=max(its,ids)
  195. iend=min(ite,ide-1)
  196. ibegc=max(its,ids)
  197. iendc=min(ite,ide-1)
  198. ELSE
  199. ibeg=max(its,ids)
  200. iend=min(ite,ide-1)
  201. ibegc=max(its,ids+4)
  202. iendc=min(ite,ide-5)
  203. END IF
  204. IF ( periodic_y ) THEN
  205. jbeg=max(jts,jds)
  206. jend=min(jte,jde-1)
  207. jbegc=max(jts,jds)
  208. jendc=min(jte,jde-1)
  209. ELSE
  210. jbeg=max(jts,jds)
  211. jend=min(jte,jde-1)
  212. jbegc=max(jts,jds+4)
  213. jendc=min(jte,jde-5)
  214. END IF
  215. do j=jts,jte
  216. do i=its,ite
  217. k22_shallow(i,j)=0
  218. kbcon_shallow(i,j)=0
  219. ktop_shallow(i,j)=0
  220. xmb_shallow(i,j)=0
  221. enddo
  222. enddo
  223. tcrit=258.
  224. ave_f_t=0.
  225. ave_f_q=0.
  226. itf=MIN(ite,ide-1)
  227. ktf=MIN(kte,kde-1)
  228. jtf=MIN(jte,jde-1)
  229. !
  230. #if ( EM_CORE == 1 )
  231. if(high_resolution.eq.1)then
  232. !
  233. ! calculate these on the halo...the incominh tendencies have been exchanged on a 24pt halo
  234. ! only neede for high resolution run
  235. !
  236. ibegh=its
  237. jbegh=jts
  238. iendh=ite
  239. jendh=jte
  240. if(its.eq.ips)ibegh=max(its-1,ids)
  241. if(jts.eq.jps)jbegh=max(jts-1,jds)
  242. if(jte.eq.jpe)jendh=min(jte+1,jde-1)
  243. if(ite.eq.ipe)iendh=min(ite+1,ide-1)
  244. DO J = jbegh,jendh
  245. DO k= kts,ktf
  246. DO I= ibegh,iendh
  247. ave_f_t(i,k,j)=(rthften(i-1,k,j-1)+rthften(i-1,k,j) + rthften(i-1,k,j+1)+ &
  248. rthften(i,k,j-1) +rthften(i,k,j) +rthften(i,k,j+1)+ &
  249. rthften(i+1,k,j-1) +rthften(i+1,k,j) +rthften(i+1,k,j+1))/9.
  250. ave_f_q(i,k,j)=(rqvften(i-1,k,j-1)+rqvften(i-1,k,j) + rqvften(i-1,k,j+1)+ &
  251. rqvften(i,k,j-1) +rqvften(i,k,j) +rqvften(i,k,j+1)+ &
  252. rqvften(i+1,k,j-1) +rqvften(i+1,k,j) +rqvften(i+1,k,j+1))/9.
  253. ! ave_f_t(i,k,j)=rthften(i,k,j)
  254. ! ave_f_q(i,k,j)=rqvften(i,k,j)
  255. ENDDO
  256. ENDDO
  257. ENDDO
  258. endif
  259. #endif
  260. DO 100 J = jts,jtf
  261. DO n= 1,ensdim
  262. DO I= its,itf
  263. xfi_ens(i,j,n)=0.
  264. pri_ens(i,j,n)=0.
  265. ! xfi_ens(i,j,n)=xf_ens(i,j,n)
  266. ! pri_ens(i,j,n)=pr_ens(i,j,n)
  267. ENDDO
  268. ENDDO
  269. DO I= its,itf
  270. kbcon(i)=0
  271. ktop(i)=0
  272. tkm(i)=0.
  273. HBOT(I,J) =REAL(KTE)
  274. HTOP(I,J) =REAL(KTS)
  275. iact_old_gr(i,j)=0
  276. mass_flux(i,j)=0.
  277. massi_flx(i,j)=0.
  278. raincv(i,j)=0.
  279. pratec (i,j)=0.
  280. edt_out(i,j)=0.
  281. edti_out(i,j)=0.
  282. gswi(i,j)=gsw(i,j)
  283. xlandi(i)=xland(i,j)
  284. APRi_GR(i,j)=apr_gr(i,j)
  285. APRi_w(i,j)=apr_w(i,j)
  286. APRi_mc(i,j)=apr_mc(i,j)
  287. APRi_st(i,j)=apr_st(i,j)
  288. APRi_as(i,j)=apr_as(i,j)
  289. APRi_capma(i,j)=apr_capma(i,j)
  290. APRi_capme(i,j)=apr_capme(i,j)
  291. APRi_capmi(i,j)=apr_capmi(i,j)
  292. CU_ACT_FLAG(i,j) = .true.
  293. ENDDO
  294. do k=kts,kte
  295. DO I= its,itf
  296. cugd_tten(i,k,j)=0.
  297. cugd_ttens(i,k,j)=0.
  298. cugd_qvten(i,k,j)=0.
  299. cugd_qvtens(i,k,j)=0.
  300. cugd_qcten(i,k,j)=0.
  301. ENDDO
  302. ENDDO
  303. DO n=1,ens4
  304. DO I= its,itf
  305. mconv(i,n)=0.
  306. ENDDO
  307. do k=kts,kte
  308. DO I= its,itf
  309. omeg(i,k,n)=0.
  310. tx(i,k,n)=0.
  311. qx(i,k,n)=0.
  312. ENDDO
  313. ENDDO
  314. ENDDO
  315. DO k=1,ensdim
  316. DO I= its,itf
  317. massflni(i,j,k)=0.
  318. ENDDO
  319. ENDDO
  320. ! put hydrostatic pressure on half levels
  321. DO K=kts,ktf
  322. DO I=ITS,ITF
  323. phh(i,k) = p(i,k,j)
  324. ENDDO
  325. ENDDO
  326. DO I=ITS,ITF
  327. PSUR(I)=p8w(I,1,J)*.01
  328. ! PSUR(I)=p(I,1,J)*.01
  329. TER11(I)=HT(i,j)
  330. aaeq(i)=0.
  331. direction(i)=0.
  332. pret(i)=0.
  333. umean(i)=0.
  334. vmean(i)=0.
  335. pmean(i)=0.
  336. kpbli(i)=kpbl(i,j)
  337. ENDDO
  338. ! if(j.eq.jpr)write(0,*)'psur(ipr),ter11(ipr),kpbli(ipr)'
  339. ! if(j.eq.jpr)write(0,*)psur(ipr),ter11(ipr),kpbli(ipr),r_v
  340. DO K=kts,ktf
  341. DO I=ITS,ITF
  342. po(i,k)=phh(i,k)*.01
  343. subm(i,k)=0.
  344. P2d(I,K)=PO(i,k)
  345. US(I,K) =u(i,k,j)
  346. VS(I,K) =v(i,k,j)
  347. T2d(I,K)=t(i,k,j)
  348. q2d(I,K)=q(i,k,j)
  349. IF(Q2d(I,K).LT.1.E-08)Q2d(I,K)=1.E-08
  350. SUBT(I,K)=0.
  351. SUBQ(I,K)=0.
  352. OUTT(I,K)=0.
  353. OUTQ(I,K)=0.
  354. OUTQC(I,K)=0.
  355. OUTTS(I,K)=0.
  356. OUTQS(I,K)=0.
  357. TN(I,K)=t2d(i,k)+RTHFTEN(i,k,j)*dt
  358. QO(I,K)=q2d(i,k)+RQVFTEN(i,k,j)*dt
  359. TSHALL(I,K)=t2d(i,k)+RTHBLTEN(i,k,j)*pi(i,k,j)*dt
  360. DHDT(I,K)=cp*RTHBLTEN(i,k,j)*pi(i,k,j)+ XLV*RQVBLTEN(i,k,j)
  361. QSHALL(I,K)=q2d(i,k)+RQVBLTEN(i,k,j)*dt
  362. if(high_resolution.eq.1)then
  363. TN(I,K)=t2d(i,k)+ave_f_t(i,k,j)*dt
  364. QO(I,K)=q2d(i,k)+ave_f_q(i,k,j)*dt
  365. endif
  366. IF(TN(I,K).LT.200.)TN(I,K)=T2d(I,K)
  367. IF(QO(I,K).LT.1.E-08)QO(I,K)=1.E-08
  368. ! if(i.eq.ipr.and.j.eq.jpr)then
  369. ! write(0,123)k,p2d(i,k),t2d(i,k),tn(i,k),q2d(i,k),QO(i,k),RTHBLTEN(i,k,j),RQVBLTEN(i,k,j)
  370. ! endif
  371. ENDDO
  372. ENDDO
  373. 123 format(1x,i2,f8.0,1x,2(1x,f8.3),4(1x,e12.4))
  374. ens4n=0
  375. nbegin=0
  376. nend=0
  377. if(ens4_spread.gt.1)then
  378. nbegin=-ens4_spread/2
  379. nend=ens4_spread/2
  380. endif
  381. do nn=nbegin,nend,1
  382. jss=max(j+nn,jds+0)
  383. jss=min(jss,jde-1)
  384. do n=nbegin,nend,1
  385. ens4n=ens4n+1
  386. DO K=kts,ktf
  387. DO I=ITS,ITF
  388. iss=max(i+n,ids+0)
  389. iss=min(iss,ide-1)
  390. omeg(I,K,ens4n)= -g*rho(i,k,j)*w(iss,k,jss)
  391. ! omeg(I,K,ens4n)= -g*rho(i,k,j)*w(i,k,j)
  392. Tx(I,K,ens4n)=t2d(i,k)+RTHFTEN(iss,k,jss)*dt
  393. ! Tx(I,K,ens4n)=t2d(i,k)+RTHFTEN(i,k,j)*dt
  394. if(high_resolution.eq.1)Tx(I,K,ens4n)=t2d(i,k)+ave_f_t(iss,k,jss)*dt
  395. IF(Tx(I,K,ens4n).LT.200.)Tx(I,K,ens4n)=T2d(I,K)
  396. Qx(I,K,ens4n)=q2d(i,k)+RQVFTEN(iss,k,jss)*dt
  397. Qx(I,K,ens4n)=q2d(i,k)+RQVFTEN(i,k,j)*dt
  398. if(high_resolution.eq.1)qx(I,K,ens4n)=q2d(i,k)+ave_f_q(iss,k,jss)*dt
  399. IF(Qx(I,K,ens4n).LT.1.E-08)Qx(I,K,ens4n)=1.E-08
  400. enddo
  401. enddo
  402. enddo !n
  403. enddo !nn
  404. do k= kts+1,ktf-1
  405. DO I = its,itf
  406. if((p2d(i,1)-p2d(i,k)).gt.150.and.p2d(i,k).gt.300)then
  407. dp=-.5*(p2d(i,k+1)-p2d(i,k-1))
  408. umean(i)=umean(i)+us(i,k)*dp
  409. vmean(i)=vmean(i)+vs(i,k)*dp
  410. pmean(i)=pmean(i)+dp
  411. endif
  412. enddo
  413. enddo
  414. DO I = its,itf
  415. umean(i)=umean(i)/pmean(i)
  416. vmean(i)=vmean(i)/pmean(i)
  417. direction(i)=(atan2(umean(i),vmean(i))+3.1415926)*57.29578
  418. if(direction(i).gt.360.)direction(i)=direction(i)-360.
  419. ENDDO
  420. do n=1,ens4
  421. DO K=kts,ktf-1
  422. DO I = its,itf
  423. dq=(q2d(i,k+1)-q2d(i,k))
  424. mconv(i,n)=mconv(i,n)+omeg(i,k,n)*dq/g
  425. enddo
  426. ENDDO
  427. ENDDO
  428. do n=1,ens4
  429. DO I = its,itf
  430. if(mconv(i,n).lt.0.)mconv(i,n)=0.
  431. ENDDO
  432. ENDDO
  433. !
  434. !---- CALL CUMULUS PARAMETERIZATION
  435. !
  436. #if ( WRF_DFI_RADAR == 1 )
  437. if(do_capsuppress == 1 ) then
  438. DO I= its,itf
  439. cap_suppress_j(i)=cap_suppress_loc(i,j)
  440. ENDDO
  441. endif
  442. #endif
  443. CALL CUP_enss_3d(outqc,j,AAEQ,T2d,Q2d,TER11,subm,TN,QO,PO,PRET,&
  444. P2d,OUTT,OUTQ,DT,itimestep,tkm,PSUR,US,VS,tcrit,iens,tx,qx, &
  445. tshall,qshall,kpbli,DHDT,outts,outqs,tscl_kf, &
  446. k22s,kbcons,ktops,xmbs, &
  447. mconv,massflni,iact_old_gr,omeg,direction,MASSi_FLX, &
  448. maxiens,maxens,maxens2,maxens3,ensdim, &
  449. APRi_GR,APRi_W,APRi_MC,APRi_ST,APRi_AS, &
  450. APRi_CAPMA,APRi_CAPME,APRi_CAPMI,kbcon,ktop,cupclw, &
  451. xfi_ens,pri_ens,XLANDi,gswi,edti_out,subt,subq, &
  452. ! ruc lv_p,rv_p,cpd_p,g0_p,ichoice,ipr,jpr, &
  453. xlv,r_v,cp,g,ichoice,ipr,jpr,ens4,high_resolution, &
  454. ishallow_g3,itf,jtf,ktf, &
  455. its,ite, jts,jte, kts,kte &
  456. #if ( WRF_DFI_RADAR == 1 )
  457. ,do_capsuppress,cap_suppress_j &
  458. #endif
  459. )
  460. if(j.lt.jbegc.or.j.gt.jendc)go to 100
  461. DO I=ibegc,iendc
  462. xmb_shallow(i,j)=xmbs(i)
  463. k22_shallow(i,j)=k22s(i)
  464. kbcon_shallow(i,j)=kbcons(i)
  465. ktop_shallow(i,j)=ktops(i)
  466. cuten(i)=0.
  467. if(pret(i).gt.0.)then
  468. cuten(i)=1.
  469. ! raincv(i,j)=pret(i)*dt
  470. endif
  471. ENDDO
  472. ! if(j.eq.jpr)write(0,*)'precip,ktop,kbcon = ',pret(ipr),ktop(ipr),kbcon(ipr)
  473. DO I=ibegc,iendc
  474. DO K=kts,ktf
  475. cugd_ttens(I,K,J)=subt(i,k)*cuten(i)*sub_spread
  476. cugd_qvtens(I,K,J)=subq(i,k)*cuten(i)*sub_spread
  477. ! cugd_tten(I,K,J)=outt(i,k)*cuten(i)
  478. ! cugd_qvten(I,K,J)=outq(i,k)*cuten(i)
  479. cugd_tten(I,K,J)=outts(i,k)+outt(i,k)*cuten(i)
  480. cugd_qvten(I,K,J)=outqs(i,k)+outq(i,k)*cuten(i)
  481. cugd_qcten(I,K,J)=outqc(i,k)*cuten(i)
  482. ! if(i.eq.ipr.and.j.eq.jpr)then
  483. ! write(0,*)subt(i,k)+outt(i,k),subq(i,k)+outq(i,k),outts(i,k),outqs(i,k)
  484. ! endif
  485. ENDDO
  486. ENDDO
  487. DO I=ibegc,iendc
  488. if(pret(i).gt.0.)then
  489. raincv(i,j)=pret(i)*dt
  490. pratec(i,j)=pret(i)
  491. rkbcon = kte+kts - kbcon(i)
  492. rktop = kte+kts - ktop(i)
  493. if (ktop(i) > HTOP(i,j)) HTOP(i,j) = ktop(i)+.001
  494. if (kbcon(i) < HBOT(i,j)) HBOT(i,j) = kbcon(i)+.001
  495. endif
  496. ENDDO
  497. DO n= 1,ensdim
  498. DO I= ibegc,iendc
  499. xf_ens(i,j,n)=xfi_ens(i,j,n)
  500. pr_ens(i,j,n)=pri_ens(i,j,n)
  501. ENDDO
  502. ENDDO
  503. DO I= ibegc,iendc
  504. APR_GR(i,j)=apri_gr(i,j)
  505. APR_w(i,j)=apri_w(i,j)
  506. APR_mc(i,j)=apri_mc(i,j)
  507. APR_st(i,j)=apri_st(i,j)
  508. APR_as(i,j)=apri_as(i,j)
  509. APR_capma(i,j)=apri_capma(i,j)
  510. APR_capme(i,j)=apri_capme(i,j)
  511. APR_capmi(i,j)=apri_capmi(i,j)
  512. mass_flux(i,j)=massi_flx(i,j)
  513. edt_out(i,j)=edti_out(i,j)
  514. ENDDO
  515. IF(PRESENT(RQCCUTEN)) THEN
  516. IF ( F_QC ) THEN
  517. DO K=kts,ktf
  518. DO I=ibegc,iendc
  519. RQCCUTEN(I,K,J)=outqc(I,K)*cuten(i)
  520. IF ( PRESENT( GDC ) ) GDC(I,K,J)=CUPCLW(I,K)*cuten(i)
  521. IF ( PRESENT( GDC2 ) ) GDC2(I,K,J)=0.
  522. ENDDO
  523. ENDDO
  524. ENDIF
  525. ENDIF
  526. !...... QSTEN STORES GRAUPEL TENDENCY IF IT EXISTS, OTHERISE SNOW (V2)
  527. IF(PRESENT(RQICUTEN).AND.PRESENT(RQCCUTEN))THEN
  528. IF (F_QI) THEN
  529. DO K=kts,ktf
  530. DO I=ibegc,iendc
  531. if(t2d(i,k).lt.258.)then
  532. RQICUTEN(I,K,J)=outqc(I,K)*cuten(i)
  533. cugd_qcten(i,k,j)=0.
  534. RQCCUTEN(I,K,J)=0.
  535. IF ( PRESENT( GDC2 ) ) GDC2(I,K,J)=CUPCLW(I,K)*cuten(i)
  536. else
  537. RQICUTEN(I,K,J)=0.
  538. RQCCUTEN(I,K,J)=outqc(I,K)*cuten(i)
  539. IF ( PRESENT( GDC ) ) GDC(I,K,J)=CUPCLW(I,K)*cuten(i)
  540. endif
  541. ENDDO
  542. ENDDO
  543. ENDIF
  544. ENDIF
  545. 100 continue
  546. END SUBROUTINE G3DRV
  547. SUBROUTINE CUP_enss_3d(OUTQC,J,AAEQ,T,Q,Z1,sub_mas, &
  548. TN,QO,PO,PRE,P,OUTT,OUTQ,DTIME,ktau,tkmax,PSUR,US,VS, &
  549. TCRIT,iens,tx,qx, &
  550. tshall,qshall,kpbl,dhdt,outts,outqs,tscl_kf, &
  551. k23,kbcon3,ktop3,xmb3, &
  552. mconv,massfln,iact, &
  553. omeg,direction,massflx,maxiens, &
  554. maxens,maxens2,maxens3,ensdim, &
  555. APR_GR,APR_W,APR_MC,APR_ST,APR_AS, &
  556. APR_CAPMA,APR_CAPME,APR_CAPMI,kbcon,ktop,cupclw, & !-lxz
  557. xf_ens,pr_ens,xland,gsw,edt_out,subt,subq, &
  558. xl,rv,cp,g,ichoice,ipr,jpr,ens4,high_resolution, &
  559. ishallow_g3,itf,jtf,ktf, &
  560. its,ite, jts,jte, kts,kte &
  561. #if ( WRF_DFI_RADAR == 1 )
  562. ! Optional CAP suppress option
  563. ,do_capsuppress,cap_suppress_j &
  564. #endif
  565. )
  566. IMPLICIT NONE
  567. integer &
  568. ,intent (in ) :: &
  569. itf,jtf,ktf,ktau, &
  570. its,ite, jts,jte, kts,kte,ipr,jpr,ens4,high_resolution
  571. integer, intent (in ) :: &
  572. j,ensdim,maxiens,ishallow_g3,maxens,maxens2,maxens3,ichoice,iens
  573. !
  574. !
  575. !
  576. real, dimension (its:ite,jts:jte,1:ensdim) &
  577. ,intent (inout) :: &
  578. massfln,xf_ens,pr_ens
  579. real, dimension (its:ite,jts:jte) &
  580. ,intent (inout ) :: &
  581. APR_GR,APR_W,APR_MC,APR_ST,APR_AS,APR_CAPMA, &
  582. APR_CAPME,APR_CAPMI,massflx,edt_out
  583. real, dimension (its:ite,jts:jte) &
  584. ,intent (in ) :: &
  585. gsw
  586. integer, dimension (its:ite,jts:jte) &
  587. ,intent (in ) :: &
  588. iact
  589. ! outtem = output temp tendency (per s)
  590. ! outq = output q tendency (per s)
  591. ! outqc = output qc tendency (per s)
  592. ! pre = output precip
  593. real, dimension (its:ite,kts:kte) &
  594. ,intent (inout ) :: &
  595. DHDT,OUTT,OUTQ,OUTQC,subt,subq,sub_mas,cupclw,outts,outqs
  596. real, dimension (its:ite) &
  597. ,intent (out ) :: &
  598. pre,xmb3
  599. integer, dimension (its:ite) &
  600. ,intent (out ) :: &
  601. kbcon,ktop,k23,kbcon3,ktop3
  602. integer, dimension (its:ite) &
  603. ,intent (in ) :: &
  604. kpbl
  605. !
  606. ! basic environmental input includes moisture convergence (mconv)
  607. ! omega (omeg), windspeed (us,vs), and a flag (aaeq) to turn off
  608. ! convection for this call only and at that particular gridpoint
  609. !
  610. real, dimension (its:ite,kts:kte) &
  611. ,intent (in ) :: &
  612. T,PO,P,US,VS,tn,tshall,qshall
  613. real, dimension (its:ite,kts:kte,1:ens4) &
  614. ,intent (inout ) :: &
  615. omeg,tx,qx
  616. real, dimension (its:ite,kts:kte) &
  617. ,intent (inout) :: &
  618. Q,QO
  619. real, dimension (its:ite) &
  620. ,intent (in ) :: &
  621. Z1,PSUR,AAEQ,direction,tkmax,xland
  622. real, dimension (its:ite,1:ens4) &
  623. ,intent (in ) :: &
  624. mconv
  625. real &
  626. ,intent (in ) :: &
  627. dtime,tcrit,xl,cp,rv,g,tscl_kf
  628. #if ( WRF_DFI_RADAR == 1 )
  629. !
  630. ! option of cap suppress:
  631. ! do_capsuppress = 1 do
  632. ! do_capsuppress = other don't
  633. !
  634. !
  635. INTEGER, INTENT(IN ) ,OPTIONAL :: do_capsuppress
  636. REAL, DIMENSION( its:ite ),INTENT(IN ) ,OPTIONAL :: cap_suppress_j
  637. #endif
  638. !
  639. ! local ensemble dependent variables in this routine
  640. !
  641. real, dimension (its:ite,1:maxens) :: &
  642. xaa0_ens
  643. real, dimension (1:maxens) :: &
  644. mbdt_ens
  645. real, dimension (1:maxens2) :: &
  646. edt_ens
  647. real, dimension (its:ite,1:maxens2) :: &
  648. edtc
  649. real, dimension (its:ite,kts:kte,1:maxens2) :: &
  650. dellat_ens,dellaqc_ens,dellaq_ens,pwo_ens,subt_ens,subq_ens
  651. !
  652. !
  653. !
  654. !***************** the following are your basic environmental
  655. ! variables. They carry a "_cup" if they are
  656. ! on model cloud levels (staggered). They carry
  657. ! an "o"-ending (z becomes zo), if they are the forced
  658. ! variables. They are preceded by x (z becomes xz)
  659. ! to indicate modification by some typ of cloud
  660. !
  661. ! z = heights of model levels
  662. ! q = environmental mixing ratio
  663. ! qes = environmental saturation mixing ratio
  664. ! t = environmental temp
  665. ! p = environmental pressure
  666. ! he = environmental moist static energy
  667. ! hes = environmental saturation moist static energy
  668. ! z_cup = heights of model cloud levels
  669. ! q_cup = environmental q on model cloud levels
  670. ! qes_cup = saturation q on model cloud levels
  671. ! t_cup = temperature (Kelvin) on model cloud levels
  672. ! p_cup = environmental pressure
  673. ! he_cup = moist static energy on model cloud levels
  674. ! hes_cup = saturation moist static energy on model cloud levels
  675. ! gamma_cup = gamma on model cloud levels
  676. !
  677. !
  678. ! hcd = moist static energy in downdraft
  679. ! zd normalized downdraft mass flux
  680. ! dby = buoancy term
  681. ! entr = entrainment rate
  682. ! zd = downdraft normalized mass flux
  683. ! entr= entrainment rate
  684. ! hcd = h in model cloud
  685. ! bu = buoancy term
  686. ! zd = normalized downdraft mass flux
  687. ! gamma_cup = gamma on model cloud levels
  688. ! mentr_rate = entrainment rate
  689. ! qcd = cloud q (including liquid water) after entrainment
  690. ! qrch = saturation q in cloud
  691. ! pwd = evaporate at that level
  692. ! pwev = total normalized integrated evaoprate (I2)
  693. ! entr= entrainment rate
  694. ! z1 = terrain elevation
  695. ! entr = downdraft entrainment rate
  696. ! jmin = downdraft originating level
  697. ! kdet = level above ground where downdraft start detraining
  698. ! psur = surface pressure
  699. ! z1 = terrain elevation
  700. ! pr_ens = precipitation ensemble
  701. ! xf_ens = mass flux ensembles
  702. ! massfln = downdraft mass flux ensembles used in next timestep
  703. ! omeg = omega from large scale model
  704. ! mconv = moisture convergence from large scale model
  705. ! zd = downdraft normalized mass flux
  706. ! zu = updraft normalized mass flux
  707. ! dir = "storm motion"
  708. ! mbdt = arbitrary numerical parameter
  709. ! dtime = dt over which forcing is applied
  710. ! iact_gr_old = flag to tell where convection was active
  711. ! kbcon = LFC of parcel from k22
  712. ! k22 = updraft originating level
  713. ! icoic = flag if only want one closure (usually set to zero!)
  714. ! dby = buoancy term
  715. ! ktop = cloud top (output)
  716. ! xmb = total base mass flux
  717. ! hc = cloud moist static energy
  718. ! hkb = moist static energy at originating level
  719. ! mentr_rate = entrainment rate
  720. real, dimension (its:ite,kts:kte) :: &
  721. he3,hes3,qes3,z3,zdo3,zu3_0,hc3_0,dby3_0,gamma3_0_cup, &
  722. qes3_cup,q3_cup,he3_cup,hes3_cup,z3_cup,gamma3_cup,t3_cup, &
  723. xhe3,xhes3,xqes3,xz3,xt3,xq3, &
  724. xqes3_cup,xq3_cup,xhe3_cup,xhes3_cup,xz3_cup,xgamma3_cup, &
  725. xt3_cup, &
  726. xdby3,xqc3,xhc3,xqrc3,xzu3, &
  727. dby3,qc3,pw3,hc3,qrc3,zu3,cd3,DELLAH3,DELLAQ3, &
  728. dsubt3,dsubq3,DELLAT3,DELLAQC3
  729. real, dimension (its:ite,kts:kte) :: &
  730. he,hes,qes,z, &
  731. heo,heso,qeso,zo, &
  732. xhe,xhes,xqes,xz,xt,xq, &
  733. qes_cup,q_cup,he_cup,hes_cup,z_cup,p_cup,gamma_cup,t_cup, &
  734. qeso_cup,qo_cup,heo_cup,heso_cup,zo_cup,po_cup,gammao_cup, &
  735. tn_cup, &
  736. xqes_cup,xq_cup,xhe_cup,xhes_cup,xz_cup,xp_cup,xgamma_cup, &
  737. xt_cup, &
  738. dby,qc,qrcd,pwd,pw,hcd,qcd,dbyd,hc,qrc,zu,zd,clw_all, &
  739. dbyo,qco,qrcdo,pwdo,pwo,hcdo,qcdo,dbydo,hco,qrco,zuo,zdo, &
  740. xdby,xqc,xqrcd,xpwd,xpw,xhcd,xqcd,xhc,xqrc,xzu,xzd, &
  741. ! cd = detrainment function for updraft
  742. ! cdd = detrainment function for downdraft
  743. ! dellat = change of temperature per unit mass flux of cloud ensemble
  744. ! dellaq = change of q per unit mass flux of cloud ensemble
  745. ! dellaqc = change of qc per unit mass flux of cloud ensemble
  746. cd,cdd,scr1,DELLAH,DELLAQ,DELLAT,DELLAQC,dsubt,dsubq
  747. ! aa0 cloud work function for downdraft
  748. ! edt = epsilon
  749. ! aa0 = cloud work function without forcing effects
  750. ! aa1 = cloud work function with forcing effects
  751. ! xaa0 = cloud work function with cloud effects (ensemble dependent)
  752. ! edt = epsilon
  753. real, dimension (its:ite) :: &
  754. aa3_0,aa3,hkb3,qkb3,pwav3,bu3,xaa3,xhkb3, &
  755. hkb3_0,edt,edto,edtx,AA1,AA0,XAA0,HKB, &
  756. HKBO,aad,XHKB,QKB,QKBO,edt3, &
  757. XMB,XPWAV,XPWEV,PWAV,PWEV,PWAVO, &
  758. PWEVO,BU,BUO,cap_max,xland1, &
  759. cap_max_increment,closure_n,cap_max3
  760. real, dimension (its:ite,1:ens4) :: &
  761. axx
  762. integer, dimension (its:ite) :: &
  763. kzdown,KDET,K22,KB,JMIN,kstabi,kstabm,K22x,jmin3,kdet3, & !-lxz
  764. KBCONx,KBx,KTOPx,ierr,ierr2,ierr3,KBMAX,ierr5,ierr5_0
  765. integer :: &
  766. nall,iedt,nens,nens3,ki,I,K,KK,iresult
  767. real :: &
  768. day,dz,mbdt,mbdt_s,entr_rate,radius,entrd_rate,mentr_rate,mentrd_rate, &
  769. zcutdown,edtmax,edtmin,depth_min,zkbmax,z_detr,zktop, &
  770. massfld,dh,cap_maxs,trash,entr_rate3,mentr_rate3
  771. integer :: jmini
  772. logical :: keep_going
  773. real xff_shal(9),blqe,xkshal
  774. day=86400.
  775. do i=its,itf
  776. xmb3(i)=0.
  777. closure_n(i)=16.
  778. xland1(i)=1.
  779. if(xland(i).gt.1.5)xland1(i)=0.
  780. ! cap_max_increment(i)=50.
  781. cap_max_increment(i)=25.
  782. enddo
  783. !
  784. !--- specify entrainmentrate and detrainmentrate
  785. !
  786. if(iens.le.4)then
  787. radius=14000.-float(iens)*2000.
  788. else
  789. radius=12000.
  790. endif
  791. !
  792. !--- gross entrainment rate (these may be changed later on in the
  793. !--- program, depending what your detrainment is!!)
  794. !
  795. entr_rate =.2/radius
  796. entr_rate3=.2/200.
  797. !
  798. !--- entrainment of mass
  799. !
  800. mentrd_rate=0.
  801. mentr_rate=entr_rate
  802. mentr_rate3=entr_rate3
  803. !
  804. !--- initial detrainmentrates
  805. !
  806. do k=kts,ktf
  807. do i=its,itf
  808. cupclw(i,k)=0.
  809. cd(i,k)=0.01*entr_rate
  810. cd3(i,k)=entr_rate3
  811. cdd(i,k)=0.
  812. zdo3(i,k)=0.
  813. hcdo(i,k)=0.
  814. qrcdo(i,k)=0.
  815. dellaqc(i,k)=0.
  816. enddo
  817. enddo
  818. !
  819. !--- max/min allowed value for epsilon (ratio downdraft base mass flux/updraft
  820. ! base mass flux
  821. !
  822. edtmax=1.
  823. edtmin=.2
  824. !
  825. !--- minimum depth (m), clouds must have
  826. !
  827. depth_min=500.
  828. !
  829. !--- maximum depth (mb) of capping
  830. !--- inversion (larger cap = no convection)
  831. !
  832. ! cap_maxs=125.
  833. cap_maxs=75.
  834. DO i=its,itf
  835. kbmax(i)=1
  836. jmin3(i)=0
  837. kdet3(i)=0
  838. aa0(i)=0.
  839. aa3_0(i)=0.
  840. aa1(i)=0.
  841. aa3(i)=0.
  842. aad(i)=0.
  843. edt(i)=0.
  844. edt3(i)=0.
  845. kstabm(i)=ktf-1
  846. IERR(i)=0
  847. IERR2(i)=0
  848. IERR3(i)=0
  849. IERR5(i)=0
  850. IERR5_0(i)=0
  851. enddo
  852. !
  853. !--- first check for upstream convection
  854. !
  855. #if ( WRF_DFI_RADAR == 1 )
  856. if(do_capsuppress == 1) then
  857. do i=its,itf
  858. cap_max(i)=cap_maxs
  859. cap_max3(i)=25.
  860. if(gsw(i,j).lt.1.or.high_resolution.eq.1)cap_max(i)=25.
  861. if (abs(cap_suppress_j(i) - 1.0 ) < 0.1 ) then
  862. cap_max(i)=cap_maxs+75.
  863. elseif (abs(cap_suppress_j(i) - 0.0 ) < 0.1 ) then
  864. cap_max(i)=10.0
  865. endif
  866. iresult=0
  867. enddo
  868. else
  869. do i=its,itf
  870. cap_max(i)=cap_maxs
  871. cap_max3(i)=25.
  872. if(gsw(i,j).lt.1.or.high_resolution.eq.1)cap_max(i)=25.
  873. iresult=0
  874. enddo
  875. endif
  876. do i=its,itf
  877. edt_out(i,j)=cap_max(i)
  878. enddo
  879. #else
  880. do i=its,itf
  881. cap_max(i)=cap_maxs
  882. cap_max3(i)=25.
  883. if(gsw(i,j).lt.1.or.high_resolution.eq.1)cap_max(i)=25.
  884. iresult=0
  885. enddo
  886. #endif
  887. !
  888. !--- max height(m) above ground where updraft air can originate
  889. !
  890. zkbmax=4000.
  891. !
  892. !--- height(m) above which no downdrafts are allowed to originate
  893. !
  894. zcutdown=3000.
  895. !
  896. !--- depth(m) over which downdraft detrains all its mass
  897. !
  898. z_detr=1250.
  899. !
  900. do nens=1,maxens
  901. mbdt_ens(nens)=(float(nens)-3.)*dtime*1.e-3+dtime*5.E-03
  902. enddo
  903. do nens=1,maxens2
  904. edt_ens(nens)=.95-float(nens)*.01
  905. enddo
  906. !
  907. !--- environmental conditions, FIRST HEIGHTS
  908. !
  909. do i=its,itf
  910. if(ierr(i).ne.20)then
  911. do k=1,maxens*maxens2*maxens3
  912. xf_ens(i,j,(iens-1)*maxens*maxens2*maxens3+k)=0.
  913. pr_ens(i,j,(iens-1)*maxens*maxens2*maxens3+k)=0.
  914. enddo
  915. endif
  916. enddo
  917. !
  918. !--- calculate moist static energy, heights, qes
  919. !
  920. call cup_env(z,qes,he,hes,t,q,p,z1, &
  921. psur,ierr,tcrit,0,xl,cp, &
  922. itf,jtf,ktf, &
  923. its,ite, jts,jte, kts,kte)
  924. call cup_env(zo,qeso,heo,heso,tn,qo,po,z1, &
  925. psur,ierr,tcrit,0,xl,cp, &
  926. itf,jtf,ktf, &
  927. its,ite, jts,jte, kts,kte)
  928. !
  929. !--- environmental values on cloud levels
  930. !
  931. call cup_env_clev(t,qes,q,he,hes,z,p,qes_cup,q_cup,he_cup, &
  932. hes_cup,z_cup,p_cup,gamma_cup,t_cup,psur, &
  933. ierr,z1,xl,rv,cp, &
  934. itf,jtf,ktf, &
  935. its,ite, jts,jte, kts,kte)
  936. call cup_env_clev(tn,qeso,qo,heo,heso,zo,po,qeso_cup,qo_cup, &
  937. heo_cup,heso_cup,zo_cup,po_cup,gammao_cup,tn_cup,psur, &
  938. ierr,z1,xl,rv,cp, &
  939. itf,jtf,ktf, &
  940. its,ite, jts,jte, kts,kte)
  941. do i=its,itf
  942. if(aaeq(i).lt.-0.1)then
  943. ierr(i)=20
  944. endif
  945. ! if(ierr(i).eq.0)then
  946. !
  947. do k=kts,ktf
  948. if(zo_cup(i,k).gt.zkbmax+z1(i))then
  949. kbmax(i)=k
  950. go to 25
  951. endif
  952. enddo
  953. 25 continue
  954. !
  955. !--- level where detrainment for downdraft starts
  956. !
  957. do k=kts,ktf
  958. if(zo_cup(i,k).gt.z_detr+z1(i))then
  959. kdet(i)=k
  960. go to 26
  961. endif
  962. enddo
  963. 26 continue
  964. !
  965. ! endif
  966. enddo
  967. !
  968. !
  969. !
  970. !------- DETERMINE LEVEL WITH HIGHEST MOIST STATIC ENERGY CONTENT - K22
  971. !
  972. CALL cup_MAXIMI(HEO_CUP,3,KBMAX,K22,ierr, &
  973. itf,jtf,ktf, &
  974. its,ite, jts,jte, kts,kte)
  975. DO 36 i=its,itf
  976. IF(ierr(I).eq.0.)THEN
  977. IF(K22(I).GE.KBMAX(i))ierr(i)=2
  978. endif
  979. 36 CONTINUE
  980. !
  981. !--- DETERMINE THE LEVEL OF CONVECTIVE CLOUD BASE - KBCON
  982. !
  983. call cup_kbcon(cap_max_increment,1,k22,kbcon,heo_cup,heso_cup, &
  984. ierr,kbmax,po_cup,cap_max, &
  985. itf,jtf,ktf, &
  986. its,ite, jts,jte, kts,kte)
  987. !
  988. !--- increase detrainment in stable layers
  989. !
  990. CALL cup_minimi(HEso_cup,Kbcon,kstabm,kstabi,ierr, &
  991. itf,jtf,ktf, &
  992. its,ite, jts,jte, kts,kte)
  993. do i=its,itf
  994. IF(ierr(I).eq.0.)THEN
  995. if(kstabm(i)-1.gt.kstabi(i))then
  996. do k=kstabi(i),kstabm(i)-1
  997. cd(i,k)=cd(i,k-1)+.15*entr_rate
  998. if(cd(i,k).gt.1.0*entr_rate)cd(i,k)=1.0*entr_rate
  999. enddo
  1000. ENDIF
  1001. ENDIF
  1002. ENDDO
  1003. !
  1004. !--- calculate incloud moist static energy
  1005. !
  1006. call cup_up_he(k22,hkb,z_cup,cd,mentr_rate,he_cup,hc, &
  1007. kbcon,ierr,dby,he,hes_cup,'deep', &
  1008. itf,jtf,ktf, &
  1009. its,ite, jts,jte, kts,kte)
  1010. call cup_up_he(k22,hkbo,zo_cup,cd,mentr_rate,heo_cup,hco, &
  1011. kbcon,ierr,dbyo,heo,heso_cup,'deep', &
  1012. itf,jtf,ktf, &
  1013. its,ite, jts,jte, kts,kte)
  1014. !--- DETERMINE CLOUD TOP - KTOP
  1015. !
  1016. call cup_ktop(1,dbyo,kbcon,ktop,ierr, &
  1017. itf,jtf,ktf, &
  1018. its,ite, jts,jte, kts,kte)
  1019. DO 37 i=its,itf
  1020. kzdown(i)=0
  1021. if(ierr(i).eq.0)then
  1022. zktop=(zo_cup(i,ktop(i))-z1(i))*.6
  1023. zktop=min(zktop+z1(i),zcutdown+z1(i))
  1024. do k=kts,kte
  1025. if(zo_cup(i,k).gt.zktop)then
  1026. kzdown(i)=k
  1027. go to 37
  1028. endif
  1029. enddo
  1030. endif
  1031. 37 CONTINUE
  1032. !
  1033. !--- DOWNDRAFT ORIGINATING LEVEL - JMIN
  1034. !
  1035. call cup_minimi(HEso_cup,K22,kzdown,JMIN,ierr, &
  1036. itf,jtf,ktf, &
  1037. its,ite, jts,jte, kts,kte)
  1038. DO 100 i=its,ite
  1039. IF(ierr(I).eq.0.)THEN
  1040. !
  1041. !--- check whether it would have buoyancy, if there where
  1042. !--- no entrainment/detrainment
  1043. !
  1044. jmini = jmin(i)
  1045. keep_going = .TRUE.
  1046. do while ( keep_going )
  1047. keep_going = .FALSE.
  1048. if ( jmini - 1 .lt. kdet(i) ) kdet(i) = jmini-1
  1049. if ( jmini .ge. ktop(i)-1 ) jmini = ktop(i) - 2
  1050. ki = jmini
  1051. hcdo(i,ki)=heso_cup(i,ki)
  1052. DZ=Zo_cup(i,Ki+1)-Zo_cup(i,Ki)
  1053. dh=0.
  1054. do k=ki-1,1,-1
  1055. hcdo(i,k)=heso_cup(i,jmini)
  1056. DZ=Zo_cup(i,K+1)-Zo_cup(i,K)
  1057. dh=dh+dz*(HCDo(i,K)-heso_cup(i,k))
  1058. if(dh.gt.0.)then
  1059. jmini=jmini-1
  1060. if ( jmini .gt. 3 ) then
  1061. keep_going = .TRUE.
  1062. else
  1063. ierr(i) = 9
  1064. exit
  1065. endif
  1066. endif
  1067. enddo
  1068. enddo
  1069. jmin(i) = jmini
  1070. if ( jmini .le. 3 ) then
  1071. ierr(i)=4
  1072. endif
  1073. ENDIF
  1074. 100 continue
  1075. !
  1076. ! - Must have at least depth_min m between cloud convective base
  1077. ! and cloud top.
  1078. !
  1079. do i=its,itf
  1080. IF(ierr(I).eq.0.)THEN
  1081. IF(-zo_cup(I,KBCON(I))+zo_cup(I,KTOP(I)).LT.depth_min)then
  1082. ierr(i)=6
  1083. endif
  1084. endif
  1085. enddo
  1086. !
  1087. !c--- normalized updraft mass flux profile
  1088. !
  1089. call cup_up_nms(zu,z_cup,mentr_rate,cd,kbcon,ktop,ierr,k22, &
  1090. itf,jtf,ktf, &
  1091. its,ite, jts,jte, kts,kte)
  1092. call cup_up_nms(zuo,zo_cup,mentr_rate,cd,kbcon,ktop,ierr,k22, &
  1093. itf,jtf,ktf, &
  1094. its,ite, jts,jte, kts,kte)
  1095. !
  1096. !c--- normalized downdraft mass flux profile,also work on bottom detrainment
  1097. !--- in this routine
  1098. !
  1099. call cup_dd_nms(zd,z_cup,cdd,mentrd_rate,jmin,ierr, &
  1100. 0,kdet,z1, &
  1101. itf,jtf,ktf, &
  1102. its,ite, jts,jte, kts,kte)
  1103. call cup_dd_nms(zdo,zo_cup,cdd,mentrd_rate,jmin,ierr, &
  1104. 1,kdet,z1, &
  1105. itf,jtf,ktf, &
  1106. its,ite, jts,jte, kts,kte)
  1107. !
  1108. !--- downdraft moist static energy
  1109. !
  1110. call cup_dd_he(hes_cup,zd,hcd,z_cup,cdd,mentrd_rate, &
  1111. jmin,ierr,he,dbyd,he_cup, &
  1112. itf,jtf,ktf, &
  1113. its,ite, jts,jte, kts,kte)
  1114. call cup_dd_he(heso_cup,zdo,hcdo,zo_cup,cdd,mentrd_rate, &
  1115. jmin,ierr,heo,dbydo,he_cup,&
  1116. itf,jtf,ktf, &
  1117. its,ite, jts,jte, kts,kte)
  1118. !
  1119. !--- calculate moisture properties of downdraft
  1120. !
  1121. call cup_dd_moisture_3d(zd,hcd,hes_cup,qcd,qes_cup, &
  1122. pwd,q_cup,z_cup,cdd,mentrd_rate,jmin,ierr,gamma_cup, &
  1123. pwev,bu,qrcd,q,he,t_cup,2,xl,high_resolution, &
  1124. itf,jtf,ktf, &
  1125. its,ite, jts,jte, kts,kte)
  1126. call cup_dd_moisture_3d(zdo,hcdo,heso_cup,qcdo,qeso_cup, &
  1127. pwdo,qo_cup,zo_cup,cdd,mentrd_rate,jmin,ierr,gammao_cup, &
  1128. pwevo,bu,qrcdo,qo,heo,tn_cup,1,xl,high_resolution, &
  1129. itf,jtf,ktf, &
  1130. its,ite, jts,jte, kts,kte)
  1131. !
  1132. !--- calculate moisture properties of updraft
  1133. !
  1134. call cup_up_moisture('deep',ierr,z_cup,qc,qrc,pw,pwav, &
  1135. kbcon,ktop,cd,dby,mentr_rate,clw_all, &
  1136. q,GAMMA_cup,zu,qes_cup,k22,q_cup,xl, &
  1137. itf,jtf,ktf, &
  1138. its,ite, jts,jte, kts,kte)
  1139. do k=kts,ktf
  1140. do i=its,itf
  1141. cupclw(i,k)=qrc(i,k)
  1142. enddo
  1143. enddo
  1144. call cup_up_moisture('deep',ierr,zo_cup,qco,qrco,pwo,pwavo, &
  1145. kbcon,ktop,cd,dbyo,mentr_rate,clw_all, &
  1146. qo,GAMMAo_cup,zuo,qeso_cup,k22,qo_cup,xl,&
  1147. itf,jtf,ktf, &
  1148. its,ite, jts,jte, kts,kte)
  1149. !
  1150. !--- calculate workfunctions for updrafts
  1151. !
  1152. call cup_up_aa0(aa0,z,zu,dby,GAMMA_CUP,t_cup, &
  1153. kbcon,ktop,ierr, &
  1154. itf,jtf,ktf, &
  1155. its,ite, jts,jte, kts,kte)
  1156. call cup_up_aa0(aa1,zo,zuo,dbyo,GAMMAo_CUP,tn_cup, &
  1157. kbcon,ktop,ierr, &
  1158. itf,jtf,ktf, &
  1159. its,ite, jts,jte, kts,kte)
  1160. do i=its,itf
  1161. if(ierr(i).eq.0)then
  1162. if(aa1(i).eq.0.)then
  1163. ierr(i)=17
  1164. endif
  1165. endif
  1166. enddo
  1167. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  1168. ! NEXT section for shallow convection
  1169. !
  1170. if(ishallow_g3.eq.1)then
  1171. ! write(0,*)'now do shallow for j = ',j
  1172. call cup_env(z3,qes3,he3,hes3,tshall,qshall,po,z1, &
  1173. psur,ierr5,tcrit,0,xl,cp, &
  1174. itf,jtf,ktf, &
  1175. its,ite, jts,jte, kts,kte)
  1176. call cup_env_clev(tshall,qes3,qshall,he3,hes3,z3,po,qes3_cup,q3_cup, &
  1177. he3_cup,hes3_cup,z3_cup,po_cup,gamma3_cup,t3_cup,psur, &
  1178. ierr5,z1,xl,rv,cp, &
  1179. itf,jtf,ktf, &
  1180. its,ite, jts,jte, kts,kte)
  1181. CALL cup_MAXIMI(HE3_CUP,1,kbmax,K23,ierr5, &
  1182. itf,jtf,ktf, &
  1183. its,ite, jts,jte, kts,kte)
  1184. DO i=its,itf
  1185. if(kpbl(i).gt.5)cap_max3(i)=po_cup(i,kpbl(i))
  1186. IF(ierr5(I).eq.0.)THEN
  1187. IF(K23(I).Gt.Kbmax(i))ierr5(i)=2
  1188. if(kpbl(i).gt.5)k23(i)=kpbl(i)
  1189. endif
  1190. ierr5_0(i)=ierr5(i)
  1191. ENDDO
  1192. call cup_kbcon(cap_max_increment,5,k23,kbcon3,he3_cup,hes3_cup, &
  1193. ierr5,kbmax,po_cup,cap_max3, &
  1194. ! ierr5,kpbl,po_cup,cap_max3, &
  1195. itf,jtf,ktf, &
  1196. its,ite, jts,jte, kts,kte)
  1197. call cup_up_he(k23,hkb3,z3_cup,cd3,mentr_rate3,he3_cup,hc3, &
  1198. kbcon3,ierr5,dby3,he3,hes3_cup,'shallow', &
  1199. itf,jtf,ktf, &
  1200. its,ite, jts,jte, kts,kte)
  1201. call cup_up_he(k23,hkb3_0,z_cup,cd3,mentr_rate3,he_cup,hc3_0, &
  1202. kbcon3,ierr5,dby3_0,he,hes_cup,'shallow', &
  1203. itf,jtf,ktf, &
  1204. its,ite, jts,jte, kts,kte)
  1205. call cup_ktop(1,dby3,kbcon3,ktop3,ierr5, &
  1206. itf,jtf,ktf, &
  1207. its,ite, jts,jte, kts,kte)
  1208. call cup_up_nms(zu3,z3_cup,mentr_rate3,cd3,kbcon3,ktop3, &
  1209. ierr5,k23, &
  1210. itf,jtf,ktf, &
  1211. its,ite, jts,jte, kts,kte)
  1212. call cup_up_nms(zu3_0,z_cup,mentr_rate3,cd3,kbcon3,ktop3, &
  1213. ierr5,k23, &
  1214. itf,jtf,ktf, &
  1215. its,ite, jts,jte, kts,kte)
  1216. !
  1217. ! first calculate aa3_0_cup
  1218. !
  1219. call cup_up_aa0(aa3_0,z,zu3_0,dby3_0,GAMMA3_0_CUP,t_cup, &
  1220. kbcon3,ktop3,ierr5, &
  1221. itf,jtf,ktf, &
  1222. its,ite, jts,jte, kts,kte)
  1223. !
  1224. ! now what is necessary for aa3 and feedbacks
  1225. !
  1226. call cup_up_moisture('shallow',ierr5,z3_cup,qc3,qrc3,pw3,pwav3, &
  1227. kbcon3,ktop3,cd3,dby3,mentr_rate3,clw_all, &
  1228. qshall,GAMMA3_cup,zu3,qes3_cup,k23,q3_cup,xl,&
  1229. itf,jtf,ktf, &
  1230. its,ite, jts,jte, kts,kte)
  1231. call cup_up_aa0(aa3,z3,zu3,dby3,GAMMA3_CUP,t3_cup, &
  1232. kbcon3,ktop3,ierr5, &
  1233. itf,jtf,ktf, &
  1234. its,ite, jts,jte, kts,kte)
  1235. ! do i=its,itf
  1236. ! if(ierr5(i).eq.0)then
  1237. ! if(aa3(i).eq.0.)then
  1238. ! ierr5(i)=17
  1239. ! endif
  1240. ! endif
  1241. ! enddo
  1242. ! call cup_dellabot('shallow',ipr,jpr,q3_cup,ierr5,z3_cup,po,qrcdo,edto, &
  1243. ! zdo,cdd,q3,dellaq3,dsubq,j,mentrd_rate,z3,g,&
  1244. ! itf,jtf,ktf, &
  1245. ! its,ite, jts,jte, kts,kte)
  1246. call cup_dellas_3d(ierr5,z3_cup,po_cup,hcdo,edt3,zdo3,cdd, &
  1247. he3,dellah3,dsubt3,j,mentrd_rate,zu3,g, &
  1248. cd3,hc3,ktop3,k23,kbcon3,mentr_rate3,jmin,he3_cup,kdet, &
  1249. k23,ipr,jpr,'shallow',0, &
  1250. itf,jtf,ktf, &
  1251. its,ite, jts,jte, kts,kte)
  1252. call cup_dellas_3d(ierr5,z3_cup,po_cup,qrcdo,edt3,zdo3,cdd, &
  1253. qshall,dellaq3,dsubq3,j,mentrd_rate,zu3,g, &
  1254. cd3,qc3,ktop3,k23,kbcon3,mentr_rate3,jmin,q3_cup,kdet, &
  1255. k23,ipr,jpr,'shallow',0, &
  1256. itf,jtf,ktf, &
  1257. its,ite, jts,jte, kts,kte )
  1258. mbdt_s=1.e-1*mbdt_ens(1)
  1259. do k=kts,ktf
  1260. do i=its,itf
  1261. dellat3(i,k)=0.
  1262. if(ierr5(i).eq.0)then
  1263. trash=dsubt3(i,k)
  1264. XHE3(I,K)=(dsubt3(i,k)+DELLAH3(I,K))*MBDT_S+HE3(I,K)
  1265. XQ3(I,K)=(dsubq3(i,k)+DELLAQ3(I,K))*MBDT_S+QSHALL(I,K)
  1266. DELLAT3(I,K)=(1./cp)*(DELLAH3(I,K)-xl*DELLAQ3(I,K))
  1267. dSUBT3(I,K)=(1./cp)*(dsubt3(i,k)-xl*dsubq3(i,k))
  1268. XT3(I,K)= (DELLAT3(I,K)+dsubt3(i,k))*MBDT_S+TSHALL(I,K)
  1269. IF(XQ3(I,K).LE.0.)XQ3(I,K)=1.E-08
  1270. ! if(i.eq.ipr.and.j.eq.jpr)then
  1271. ! write(0,*)k,trash,DELLAQ3(I,K),dsubq3(I,K),dsubt3(i,k)
  1272. ! endif
  1273. ENDIF
  1274. enddo
  1275. enddo
  1276. do i=its,itf
  1277. if(ierr5(i).eq.0)then
  1278. XHE3(I,ktf)=HE3(I,ktf)
  1279. XQ3(I,ktf)=QSHALL(I,ktf)
  1280. XT3(I,ktf)=TSHALL(I,ktf)
  1281. IF(XQ3(I,ktf).LE.0.)XQ3(I,ktf)=1.E-08
  1282. endif
  1283. enddo
  1284. !
  1285. !--- calculate moist static energy, heights, qes
  1286. !
  1287. call cup_env(xz3,xqes3,xhe3,xhes3,xt3,xq3,po,z1, &
  1288. psur,ierr5,tcrit,2,xl,cp, &
  1289. itf,jtf,ktf, &
  1290. its,ite, jts,jte, kts,kte)
  1291. !
  1292. !--- environmental values on cloud levels
  1293. !
  1294. call cup_env_clev(xt3,xqes3,xq3,xhe3,xhes3,xz3,po,xqes3_cup,xq3_cup, &
  1295. xhe3_cup,xhes3_cup,xz3_cup,po_cup,gamma3_cup,xt3_cup,psur, &
  1296. ierr5,z1,xl,rv,cp, &
  1297. itf,jtf,ktf, &
  1298. its,ite, jts,jte, kts,kte)
  1299. !
  1300. !
  1301. !**************************** static control
  1302. !
  1303. !--- moist static energy inside cloud
  1304. !
  1305. do i=its,itf
  1306. if(ierr5(i).eq.0)then
  1307. xhkb3(i)=xhe3(i,k23(i))
  1308. endif
  1309. enddo
  1310. call cup_up_he(k23,xhkb3,xz3_cup,cd3,mentr_rate3,xhe3_cup,xhc3, &
  1311. kbcon3,ierr5,xdby3,xhe3,xhes3_cup,'shallow', &
  1312. itf,jtf,ktf, &
  1313. its,ite, jts,jte, kts,kte)
  1314. !
  1315. !c--- normalized mass flux profile and CWF
  1316. !
  1317. call cup_up_nms(xzu3,xz3_cup,mentr_rate3,cd3,kbcon3,ktop3,ierr5,k23, &
  1318. itf,jtf,ktf, &
  1319. its,ite, jts,jte, kts,kte)
  1320. call cup_up_aa0(xaa3,xz3,xzu3,xdby3,GAMMA3_CUP,xt3_cup, &
  1321. kbcon3,ktop3,ierr5, &
  1322. itf,jtf,ktf, &
  1323. its,ite, jts,jte, kts,kte)
  1324. !
  1325. ! now for shallow forcing
  1326. !
  1327. do i=its,itf
  1328. xmb3(i)=0.
  1329. xff_shal(1:9)=0.
  1330. if(ierr5(i).eq.0)then
  1331. xkshal=(xaa3(i)-aa3(i))/mbdt_s
  1332. if(xkshal.ge.0.)xkshal=+1.e6
  1333. if(xkshal.gt.-1.e-4 .and. xkshal.lt.0.)xkshal=-1.e-4
  1334. xff_shal(1)=max(0.,-(aa3(i)-aa3_0(i))/(xkshal*dtime))
  1335. xff_shal(2)=max(0.,-(aa3(i)-aa3_0(i))/(xkshal*dtime))
  1336. xff_shal(3)=max(0.,-(aa3(i)-aa3_0(i))/(xkshal*dtime))
  1337. if(aa3_0(i).le.0)then
  1338. xff_shal(1)=0.
  1339. xff_shal(2)=0.
  1340. xff_shal(3)=0.
  1341. endif
  1342. if(aa3(i)-aa3_0(i).le.0.)then
  1343. xff_shal(1)=0.
  1344. xff_shal(2)=0.
  1345. xff_shal(3)=0.
  1346. endif
  1347. ! boundary layer QE (from Saulo Freitas)
  1348. blqe=0.
  1349. trash=0.
  1350. if(k23(i).lt.kpbl(i)+1)then
  1351. do k=1,kbcon3(i)-1
  1352. blqe=blqe+100.*dhdt(i,k)*(p_cup(i,k)-p_cup(i,k+1))/g
  1353. enddo
  1354. trash=max((hc3(i,kbcon3(i))-he_cup(i,kbcon3(i))),1.e1)
  1355. xff_shal(7)=max(0.,blqe/trash)
  1356. xff_shal(7)=min(0.1,xff_shal(7))
  1357. else
  1358. xff_shal(7)=0.
  1359. endif
  1360. if((xkshal.lt.-1.1e-04) .and. &
  1361. ((aa3(i)-aa3_0(i).gt.0.) .or. (xff_shal(7).gt.0)))then
  1362. xff_shal(4)=max(0.,-aa3(i)/(xkshal*tscl_KF))
  1363. xff_shal(4)=min(0.1,xff_shal(4))
  1364. xff_shal(5)=xff_shal(4)
  1365. xff_shal(6)=xff_shal(4)
  1366. else
  1367. xff_shal(4)=0.
  1368. xff_shal(5)=0.
  1369. xff_shal(6)=0.
  1370. endif
  1371. ! write(0,888)'i0=',i,j,kpbl(i),blqe,xff_shal(7)
  1372. 888 format(a3,3(1x,i3),2e12.4)
  1373. xff_shal(8)= xff_shal(7)
  1374. xff_shal(9)= xff_shal(7)
  1375. do k=1,9
  1376. xmb3(i)=xmb3(i)+xff_shal(k)
  1377. enddo
  1378. xmb3(i)=min(.1,xmb3(i)/9.)
  1379. ! if(xmb3(i).eq.10.1 )then
  1380. ! write(0,*)'i0,xmb3,blqe,xkshal = ',i,j,xmb3(i),blqe,xkshal
  1381. ! if(xff_shal(7).ge.0.1)then
  1382. ! write(0,*)'i1,blqe,trash = ',blqe,trash
  1383. ! endif
  1384. ! if(xff_shal(7).eq.0 .and. xff_shal(1).ge.0.1)then
  1385. ! write(0,*)'i2,aa3_0(i),aa3(i),xaa3(i) = ',aa3_0(i),aa3(i),xaa3(i)
  1386. ! endif
  1387. ! if(xff_shal(5).ge.0.1)then
  1388. ! write(0,*)'i3,aa3(i),a0,xkshal= ',aa3(i),aa3_0(i),xkshal
  1389. ! endif
  1390. ! write(0,*)'i0, xff_shallow = ',xff_shal
  1391. ! endif
  1392. !! if(xff_shal(7).eq.0 .and. xff_shal(4).gt.0 .and. xmb3(i).eq.0.5)then
  1393. !! write(0,*)'i4,xmb3 = ',i,j,xmb3(i),xkshal
  1394. !! write(0,*)'xff_shallow = ',xff_shal
  1395. !! write(0,*)aa3(i),xaa3(i),blqe
  1396. !! endif
  1397. if(xmb3(i).eq.0.)ierr5(i)=22
  1398. if(xmb3(i).lt.0.)then
  1399. ierr5(i)=21
  1400. ! write(0,*)'neg xmb,i,j,xmb3 for shallow = ',i,j,k23(i),ktop3(i),kbcon3(i),kpbl(i)
  1401. endif
  1402. endif
  1403. ! if(ierr5(i).eq.0)write(0,*)'i,j,xmb3 for shallow = ',i,j,xmb3(i),k23(i),ktop3(i)
  1404. ! if(ierr5(i).eq.0.and.i.eq.12.and.j.eq.25)write(0,*)'i,j,xmb3 for shallow = ',k23(i),ktop3(i),kbcon3(i),kpbl(i)
  1405. ! if(ierr5(i).eq.0)write(0,*)'i,j,xmb3 for shallow = ',i,j,k23(i),ktop3(i),kbcon3(i),kpbl(i)
  1406. if(ierr5(i).ne.0)then
  1407. k23(i)=0
  1408. kbcon3(i)=0
  1409. ktop3(i)=0
  1410. xmb3(i)=0
  1411. do k=kts,ktf
  1412. outts(i,k)=0.
  1413. outqs(i,k)=0.
  1414. enddo
  1415. else if(ierr5(i).eq.0)then
  1416. !
  1417. ! got the mass flux, sanity check, first for heating rates
  1418. !
  1419. trash=0.
  1420. do k=2,ktop3(i)
  1421. trash=max(trash,86400.*(dsubt3(i,k)+dellat3(i,k))*xmb3(i))
  1422. enddo
  1423. if(trash.gt.150.)xmb3(i)=xmb3(i)*150./trash
  1424. !
  1425. ! sanity check on moisture tendencies: do not allow anything that may allow neg tendencies
  1426. !
  1427. do k=2,ktop3(i)
  1428. trash=q(i,k)+(dsubq3(i,k)+dellaq3(i,k))*xmb3(i)*dtime
  1429. if(trash.lt.1.e-12)then
  1430. ! max allowable tendency over tendency that would lead to too small mix ratios
  1431. !
  1432. trash=((1.e-12-q(i,k))/dtime) &
  1433. /((dsubq3(i,k)+dellaq3(i,k))*xmb3(i))
  1434. trash=max(0.,trash)
  1435. trash=min(1.,trash)
  1436. xmb3(i)=trash*xmb3(i)
  1437. endif
  1438. enddo
  1439. !
  1440. ! final tendencies
  1441. !
  1442. do k=2,ktop3(i)
  1443. outts(i,k)=(dsubt3(i,k)+dellat3(i,k))*xmb3(i)
  1444. outqs(i,k)=(dsubq3(i,k)+dellaq3(i,k))*xmb3(i)
  1445. enddo
  1446. endif
  1447. enddo
  1448. ! if(j.eq.-25)then
  1449. !! write(0,*)'!!!!!!!! j = ',j,' !!!!!!!!!!!!!!!!!!!!'
  1450. i=12
  1451. ! write(0,*)k23(i),kbcon3(i),ktop3(i)
  1452. ! write(0,*)kpbl(i),ierr5(i),ierr(i)
  1453. ! write(0,*)xmb3(i),xff_shal(1:9)
  1454. ! write(0,*)xaa3(i),aa1(i),aa0(i),aa3(i)
  1455. ! do k=1,ktf
  1456. ! write(0,*)po(i,k),he3(i,k),hes3(i,k),dellah3(i,k)
  1457. ! enddo
  1458. ! do k=1,ktf
  1459. ! write(0,*)zu3(i,k),hc3(i,k),dsubt3(i,k),dellat3(i,k)
  1460. ! enddo
  1461. ! do k=1,ktop3(i)+1
  1462. ! blqe=cp*outts(i,k)+xl*outqs(i,k)
  1463. ! write(0,*)outts(i,k),outqs(i,k),blqe
  1464. ! enddo
  1465. ! endif
  1466. !
  1467. ! done shallow
  1468. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  1469. ENDIF
  1470. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  1471. call cup_axx(tcrit,kbmax,z1,p,psur,xl,rv,cp,tx,qx,axx,ierr, &
  1472. cap_max,cap_max_increment,entr_rate,mentr_rate,&
  1473. j,itf,jtf,ktf, &
  1474. its,ite, jts,jte, kts,kte,ens4)
  1475. !
  1476. !--- DETERMINE DOWNDRAFT STRENGTH IN TERMS OF WINDSHEAR
  1477. !
  1478. call cup_dd_edt(ierr,us,vs,zo,ktop,kbcon,edt,po,pwavo, &
  1479. pwevo,edtmax,edtmin,maxens2,edtc, &
  1480. itf,jtf,ktf, &
  1481. its,ite, jts,jte, kts,kte)
  1482. do 250 iedt=1,maxens2
  1483. do i=its,itf
  1484. if(ierr(i).eq.0)then
  1485. edt(i)=edtc(i,iedt)
  1486. edto(i)=edtc(i,iedt)
  1487. edtx(i)=edtc(i,iedt)
  1488. edt_out(i,j)=edtc(i,2)
  1489. if(high_resolution.eq.1)then
  1490. edt(i)=edtc(i,3)
  1491. edto(i)=edtc(i,3)
  1492. edtx(i)=edtc(i,3)
  1493. edt_out(i,j)=edtc(i,3)
  1494. endif
  1495. endif
  1496. enddo
  1497. do k=kts,ktf
  1498. do i=its,itf
  1499. subt_ens(i,k,iedt)=0.
  1500. subq_ens(i,k,iedt)=0.
  1501. dellat_ens(i,k,iedt)=0.
  1502. dellaq_ens(i,k,iedt)=0.
  1503. dellaqc_ens(i,k,iedt)=0.
  1504. pwo_ens(i,k,iedt)=0.
  1505. enddo
  1506. enddo
  1507. !
  1508. ! if(j.eq.jpr.and.iedt.eq.1.and.ipr.gt.its.and.ipr.lt.ite)then
  1509. !! if(j.eq.jpr)then
  1510. ! i=ipr
  1511. !! write(0,*)'in 250 loop ',iedt,edt(ipr),ierr(ipr)
  1512. !! if(ierr(i).eq.0.or.ierr(i).eq.3)then
  1513. ! write(0,*)'250',k22(I),kbcon(i),ktop(i),jmin(i)
  1514. ! write(0,*)edt(i),aa0(i),aa1(i)
  1515. ! do k=kts,ktf
  1516. ! write(0,*)k,z(i,k),he(i,k),hes(i,k)
  1517. ! enddo
  1518. ! write(0,*)'end 250 loop ',iedt,edt(ipr),ierr(ipr)
  1519. ! do k=1,ktop(i)+1
  1520. ! write(0,*)zu(i,k),zd(i,k),pw(i,k),pwd(i,k)
  1521. ! enddo
  1522. !! endif
  1523. ! endif
  1524. do i=its,itf
  1525. aad(i)=0.
  1526. enddo
  1527. !
  1528. !--- change per unit mass that a model cloud would modify the environment
  1529. !
  1530. !--- 1. in bottom layer
  1531. !
  1532. call cup_dellabot('deep',ipr,jpr,heo_cup,ierr,zo_cup,po,hcdo,edto, &
  1533. zdo,cdd,heo,dellah,dsubt,j,mentrd_rate,zo,g, &
  1534. itf,jtf,ktf, &
  1535. its,ite, jts,jte, kts,kte)
  1536. call cup_dellabot('deep',ipr,jpr,qo_cup,ierr,zo_cup,po,qrcdo,edto, &
  1537. zdo,cdd,qo,dellaq,dsubq,j,mentrd_rate,zo,g,&
  1538. itf,jtf,ktf, &
  1539. its,ite, jts,jte, kts,kte)
  1540. !
  1541. !--- 2. everywhere else
  1542. !
  1543. call cup_dellas_3d(ierr,zo_cup,po_cup,hcdo,edto,zdo,cdd, &
  1544. heo,dellah,dsubt,j,mentrd_rate,zuo,g, &
  1545. cd,hco,ktop,k22,kbcon,mentr_rate,jmin,heo_cup,kdet, &
  1546. k22,ipr,jpr,'deep',high_resolution, &
  1547. itf,jtf,ktf, &
  1548. its,ite, jts,jte, kts,kte)
  1549. !
  1550. !-- take out cloud liquid water for detrainment
  1551. !
  1552. !?? do k=kts,ktf
  1553. do k=kts,ktf-1
  1554. do i=its,itf
  1555. scr1(i,k)=0.
  1556. dellaqc(i,k)=0.
  1557. if(ierr(i).eq.0)then
  1558. scr1(i,k)=qco(i,k)-qrco(i,k)
  1559. if(k.eq.ktop(i)-0)dellaqc(i,k)= &
  1560. .01*zuo(i,ktop(i))*qrco(i,ktop(i))* &
  1561. 9.81/(po_cup(i,k)-po_cup(i,k+1))
  1562. if(k.lt.ktop(i).and.k.gt.kbcon(i))then
  1563. dz=zo_cup(i,k+1)-zo_cup(i,k)
  1564. dellaqc(i,k)=.01*9.81*cd(i,k)*dz*zuo(i,k) &
  1565. *.5*(qrco(i,k)+qrco(i,k+1))/ &
  1566. (po_cup(i,k)-po_cup(i,k+1))
  1567. endif
  1568. endif
  1569. enddo
  1570. enddo
  1571. call cup_dellas_3d(ierr,zo_cup,po_cup,qrcdo,edto,zdo,cdd, &
  1572. qo,dellaq,dsubq,j,mentrd_rate,zuo,g, &
  1573. cd,qco,ktop,k22,kbcon,mentr_rate,jmin,qo_cup,kdet, &
  1574. k22,ipr,jpr,'deep',high_resolution, &
  1575. itf,jtf,ktf, &
  1576. its,ite, jts,jte, kts,kte )
  1577. !
  1578. !--- using dellas, calculate changed environmental profiles
  1579. !
  1580. ! do 200 nens=1,maxens
  1581. mbdt=mbdt_ens(2)
  1582. do i=its,itf
  1583. xaa0_ens(i,1)=0.
  1584. xaa0_ens(i,2)=0.
  1585. xaa0_ens(i,3)=0.
  1586. enddo
  1587. ! if(j.eq.jpr)then
  1588. ! write(0,*)'xt',xl,'DELLAH(I,K),DELLAQ(I,K),dsubq(I,K),dsubt(i,k)'
  1589. ! endif
  1590. do k=kts,ktf
  1591. do i=its,itf
  1592. dellat(i,k)=0.
  1593. if(ierr(i).eq.0)then
  1594. trash=dsubt(i,k)
  1595. XHE(I,K)=(dsubt(i,k)+DELLAH(I,K))*MBDT+HEO(I,K)
  1596. XQ(I,K)=(dsubq(i,k)+DELLAQ(I,K))*MBDT+QO(I,K)
  1597. DELLAT(I,K)=(1./cp)*(DELLAH(I,K)-xl*DELLAQ(I,K))
  1598. dSUBT(I,K)=(1./cp)*(dsubt(i,k)-xl*dsubq(i,k))
  1599. XT(I,K)= (DELLAT(I,K)+dsubt(i,k))*MBDT+TN(I,K)
  1600. IF(XQ(I,K).LE.0.)XQ(I,K)=1.E-08
  1601. ! if(i.eq.ipr.and.j.eq.jpr)then
  1602. ! write(0,*)k,trash,DELLAQ(I,K),dsubq(I,K),dsubt(i,k)
  1603. ! endif
  1604. ENDIF
  1605. enddo
  1606. enddo
  1607. do i=its,itf
  1608. if(ierr(i).eq.0)then
  1609. XHE(I,ktf)=HEO(I,ktf)
  1610. XQ(I,ktf)=QO(I,ktf)
  1611. XT(I,ktf)=TN(I,ktf)
  1612. IF(XQ(I,ktf).LE.0.)XQ(I,ktf)=1.E-08
  1613. endif
  1614. enddo
  1615. !
  1616. !--- calculate moist static energy, heights, qes
  1617. !
  1618. call cup_env(xz,xqes,xhe,xhes,xt,xq,po,z1, &
  1619. psur,ierr,tcrit,2,xl,cp, &
  1620. itf,jtf,ktf, &
  1621. its,ite, jts,jte, kts,kte)
  1622. !
  1623. !--- environmental values on cloud levels
  1624. !
  1625. call cup_env_clev(xt,xqes,xq,xhe,xhes,xz,po,xqes_cup,xq_cup, &
  1626. xhe_cup,xhes_cup,xz_cup,po_cup,gamma_cup,xt_cup,psur, &
  1627. ierr,z1,xl,rv,cp, &
  1628. itf,jtf,ktf, &
  1629. its,ite, jts,jte, kts,kte)
  1630. !
  1631. !
  1632. !**************************** static control
  1633. !
  1634. !--- moist static energy inside cloud
  1635. !
  1636. do i=its,itf
  1637. if(ierr(i).eq.0)then
  1638. xhkb(i)=xhe(i,k22(i))
  1639. endif
  1640. enddo
  1641. call cup_up_he(k22,xhkb,xz_cup,cd,mentr_rate,xhe_cup,xhc, &
  1642. kbcon,ierr,xdby,xhe,xhes_cup,'deep', &
  1643. itf,jtf,ktf, &
  1644. its,ite, jts,jte, kts,kte)
  1645. !
  1646. !c--- normalized mass flux profile
  1647. !
  1648. call cup_up_nms(xzu,xz_cup,mentr_rate,cd,kbcon,ktop,ierr,k22, &
  1649. itf,jtf,ktf, &
  1650. its,ite, jts,jte, kts,kte)
  1651. !
  1652. !--- moisture downdraft
  1653. !
  1654. call cup_dd_nms(xzd,xz_cup,cdd,mentrd_rate,jmin,ierr, &
  1655. 1,kdet,z1, &
  1656. itf,jtf,ktf, &
  1657. its,ite, jts,jte, kts,kte)
  1658. call cup_dd_he(xhes_cup,xzd,xhcd,xz_cup,cdd,mentrd_rate, &
  1659. jmin,ierr,xhe,dbyd,xhe_cup,&
  1660. itf,jtf,ktf, &
  1661. its,ite, jts,jte, kts,kte)
  1662. call cup_dd_moisture_3d(xzd,xhcd,xhes_cup,xqcd,xqes_cup, &
  1663. xpwd,xq_cup,xz_cup,cdd,mentrd_rate,jmin,ierr,gamma_cup, &
  1664. xpwev,bu,xqrcd,xq,xhe,xt_cup,3,xl,high_resolution, &
  1665. itf,jtf,ktf, &
  1666. its,ite, jts,jte, kts,kte)
  1667. !
  1668. !------- MOISTURE updraft
  1669. !
  1670. call cup_up_moisture('deep',ierr,xz_cup,xqc,xqrc,xpw,xpwav, &
  1671. kbcon,ktop,cd,xdby,mentr_rate,clw_all, &
  1672. xq,GAMMA_cup,xzu,xqes_cup,k22,xq_cup,xl, &
  1673. itf,jtf,ktf, &
  1674. its,ite, jts,jte, kts,kte)
  1675. !
  1676. !--- workfunctions for updraft
  1677. !
  1678. call cup_up_aa0(xaa0,xz,xzu,xdby,GAMMA_CUP,xt_cup, &
  1679. kbcon,ktop,ierr, &
  1680. itf,jtf,ktf, &
  1681. its,ite, jts,jte, kts,kte)
  1682. do 200 nens=1,maxens
  1683. do i=its,itf
  1684. if(ierr(i).eq.0)then
  1685. xaa0_ens(i,nens)=xaa0(i)
  1686. nall=(iens-1)*maxens3*maxens*maxens2 &
  1687. +(iedt-1)*maxens*maxens3 &
  1688. +(nens-1)*maxens3
  1689. do k=kts,ktf
  1690. if(k.le.ktop(i))then
  1691. do nens3=1,maxens3
  1692. if(nens3.eq.7)then
  1693. !--- b=0
  1694. pr_ens(i,j,nall+nens3)=pr_ens(i,j,nall+nens3) &
  1695. +edto(i)*pwdo(i,k) &
  1696. +pwo(i,k)
  1697. !--- b=beta
  1698. else if(nens3.eq.8)then
  1699. pr_ens(i,j,nall+nens3)=pr_ens(i,j,nall+nens3)+ &
  1700. pwo(i,k)
  1701. !--- b=beta/2
  1702. else if(nens3.eq.9)then
  1703. pr_ens(i,j,nall+nens3)=pr_ens(i,j,nall+nens3) &
  1704. +.5*edto(i)*pwdo(i,k) &
  1705. + pwo(i,k)
  1706. else
  1707. pr_ens(i,j,nall+nens3)=pr_ens(i,j,nall+nens3)+ &
  1708. pwo(i,k)+edto(i)*pwdo(i,k)
  1709. endif
  1710. enddo
  1711. endif
  1712. enddo
  1713. if(pr_ens(i,j,nall+7).lt.1.e-6)then
  1714. ierr(i)=18
  1715. do nens3=1,maxens3
  1716. pr_ens(i,j,nall+nens3)=0.
  1717. enddo
  1718. endif
  1719. do nens3=1,maxens3
  1720. if(pr_ens(i,j,nall+nens3).lt.1.e-4)then
  1721. pr_ens(i,j,nall+nens3)=0.
  1722. endif
  1723. enddo
  1724. endif
  1725. enddo
  1726. 200 continue
  1727. !
  1728. !--- LARGE SCALE FORCING
  1729. !
  1730. !
  1731. !------- CHECK wether aa0 should have been zero
  1732. !
  1733. !
  1734. CALL cup_MAXIMI(HEO_CUP,3,KBMAX,K22x,ierr, &
  1735. itf,jtf,ktf, &
  1736. its,ite, jts,jte, kts,kte)
  1737. do i=its,itf
  1738. ierr2(i)=ierr(i)
  1739. ierr3(i)=ierr(i)
  1740. enddo
  1741. call cup_kbcon(cap_max_increment,2,k22x,kbconx,heo_cup, &
  1742. heso_cup,ierr2,kbmax,po_cup,cap_max, &
  1743. itf,jtf,ktf, &
  1744. its,ite, jts,jte, kts,kte)
  1745. call cup_kbcon(cap_max_increment,3,k22x,kbconx,heo_cup, &
  1746. heso_cup,ierr3,kbmax,po_cup,cap_max, &
  1747. itf,jtf,ktf, &
  1748. its,ite, jts,jte, kts,kte)
  1749. !
  1750. !--- DETERMINE THE LEVEL OF CONVECTIVE CLOUD BASE - KBCON
  1751. !
  1752. call cup_forcing_ens_3d(closure_n,xland1,aa0,aa1,xaa0_ens,mbdt_ens,dtime, &
  1753. ierr,ierr2,ierr3,xf_ens,j,'deeps',axx, &
  1754. maxens,iens,iedt,maxens2,maxens3,mconv, &
  1755. po_cup,ktop,omeg,zdo,k22,zuo,pr_ens,edto,kbcon, &
  1756. massflx,iact,direction,ensdim,massfln,ichoice,edt_out, &
  1757. high_resolution,itf,jtf,ktf, &
  1758. its,ite, jts,jte, kts,kte,ens4,ktau)
  1759. !
  1760. do k=kts,ktf
  1761. do i=its,itf
  1762. if(ierr(i).eq.0)then
  1763. subt_ens(i,k,iedt)=dsubt(i,k)
  1764. subq_ens(i,k,iedt)=dsubq(i,k)
  1765. dellat_ens(i,k,iedt)=dellat(i,k)
  1766. dellaq_ens(i,k,iedt)=dellaq(i,k)
  1767. dellaqc_ens(i,k,iedt)=dellaqc(i,k)
  1768. pwo_ens(i,k,iedt)=pwo(i,k)+edt(i)*pwdo(i,k)
  1769. else
  1770. subt_ens(i,k,iedt)=0.
  1771. subq_ens(i,k,iedt)=0.
  1772. dellat_ens(i,k,iedt)=0.
  1773. dellaq_ens(i,k,iedt)=0.
  1774. dellaqc_ens(i,k,iedt)=0.
  1775. pwo_ens(i,k,iedt)=0.
  1776. endif
  1777. ! if(i.eq.ipr.and.j.eq.jpr)then
  1778. ! write(0,*)'1',iens,iedt,dellat(i,k),dellat_ens(i,k,iedt), &
  1779. ! dellaq(i,k), dellaqc(i,k)
  1780. ! write(0,*)'2',k,subt_ens(i,k,iedt),subq_ens(i,k,iedt)
  1781. ! endif
  1782. enddo
  1783. enddo
  1784. 250 continue
  1785. !
  1786. !--- FEEDBACK
  1787. !
  1788. call cup_output_ens_3d(xf_ens,ierr,dellat_ens,dellaq_ens, &
  1789. dellaqc_ens,subt_ens,subq_ens,subt,subq,outt, &
  1790. outq,outqc,zuo,sub_mas,pre,pwo_ens,xmb,ktop, &
  1791. j,'deep',maxens2,maxens,iens,ierr2,ierr3, &
  1792. pr_ens,maxens3,ensdim,massfln, &
  1793. APR_GR,APR_W,APR_MC,APR_ST,APR_AS, &
  1794. APR_CAPMA,APR_CAPME,APR_CAPMI,closure_n,xland1, &
  1795. itf,jtf,ktf, &
  1796. its,ite, jts,jte, kts,kte)
  1797. k=1
  1798. do i=its,itf
  1799. if(ierr(i).eq.0.and.ierr5(i).eq.0.and.kbcon(i).lt.ktop3(i)+1)then
  1800. ! write(0,*)'both ier and ier5=0 at i,j=',i,j,kbcon(i),ktop3(i)
  1801. if(high_resolution.eq.1)then
  1802. outts(i,kts:kte)=0.
  1803. outqs(i,kts:kte)=0.
  1804. endif
  1805. elseif (ierr5(i).eq.0)then
  1806. ! write(0,*)'ier5=0 at i,j=',i,j,k23(i),ktop3(i)
  1807. endif
  1808. PRE(I)=MAX(PRE(I),0.)
  1809. ! if(i.eq.ipr.and.j.eq.jpr)then
  1810. ! write(0,*)'i,j,pre(i),aa0(i),aa1(i)'
  1811. ! write(0,*)i,j,pre(i),aa0(i)
  1812. ! endif
  1813. enddo
  1814. !
  1815. !---------------------------done------------------------------
  1816. !
  1817. ! do i=its,itf
  1818. ! if(ierr(i).eq.0)then
  1819. ! if(i.eq.ipr.and.j.eq.jpr)then
  1820. ! write(0,*)'on output, pre =',pre(i),its,itf,kts,ktf
  1821. ! do k=kts,ktf
  1822. ! write(0,*)z(i,k),outt(i,k)*86400.,subt(i,k)*86400.
  1823. ! enddo
  1824. ! write(0,*)i,j,(axx(i,k),k=1,ens4)
  1825. ! endif
  1826. ! endif
  1827. ! enddo
  1828. ! print *,'ierr(i) = ',ierr(i),pre(i)
  1829. END SUBROUTINE CUP_enss_3d
  1830. SUBROUTINE cup_dd_aa0(edt,ierr,aa0,jmin,gamma_cup,t_cup, &
  1831. hcd,hes_cup,z,zd, &
  1832. itf,jtf,ktf, &
  1833. its,ite, jts,jte, kts,kte )
  1834. IMPLICIT NONE
  1835. !
  1836. ! on input
  1837. !
  1838. ! only local wrf dimensions are need as of now in this routine
  1839. integer &
  1840. ,intent (in ) :: &
  1841. itf,jtf,ktf, &
  1842. its,ite, jts,jte, kts,kte
  1843. ! aa0 cloud work function for downdraft
  1844. ! gamma_cup = gamma on model cloud levels
  1845. ! t_cup = temperature (Kelvin) on model cloud levels
  1846. ! hes_cup = saturation moist static energy on model cloud levels
  1847. ! hcd = moist static energy in downdraft
  1848. ! edt = epsilon
  1849. ! zd normalized downdraft mass flux
  1850. ! z = heights of model levels
  1851. ! ierr error value, maybe modified in this routine
  1852. !
  1853. real, dimension (its:ite,kts:kte) &
  1854. ,intent (in ) :: &
  1855. z,zd,gamma_cup,t_cup,hes_cup,hcd
  1856. real, dimension (its:ite) &
  1857. ,intent (in ) :: &
  1858. edt
  1859. integer, dimension (its:ite) &
  1860. ,intent (in ) :: &
  1861. jmin
  1862. !
  1863. ! input and output
  1864. !
  1865. integer, dimension (its:ite) &
  1866. ,intent (inout) :: &
  1867. ierr
  1868. real, dimension (its:ite) &
  1869. ,intent (out ) :: &
  1870. aa0
  1871. !
  1872. ! local variables in this routine
  1873. !
  1874. integer :: &
  1875. i,k,kk
  1876. real :: &
  1877. dz
  1878. !
  1879. do i=its,itf
  1880. aa0(i)=0.
  1881. enddo
  1882. !
  1883. !?? DO k=kts,kte-1
  1884. DO k=kts,ktf-1
  1885. do i=its,itf
  1886. IF(ierr(I).eq.0.and.k.lt.jmin(i))then
  1887. KK=JMIN(I)-K
  1888. !
  1889. !--- ORIGINAL
  1890. !
  1891. DZ=(Z(I,KK)-Z(I,KK+1))
  1892. AA0(I)=AA0(I)+zd(i,kk)*EDT(I)*DZ*(9.81/(1004.*T_cup(I,KK))) &
  1893. *((hcd(i,kk)-hes_cup(i,kk))/(1.+GAMMA_cup(i,kk)))
  1894. endif
  1895. enddo
  1896. enddo
  1897. END SUBROUTINE CUP_dd_aa0
  1898. SUBROUTINE cup_dd_edt(ierr,us,vs,z,ktop,kbcon,edt,p,pwav, &
  1899. pwev,edtmax,edtmin,maxens2,edtc, &
  1900. itf,jtf,ktf, &
  1901. its,ite, jts,jte, kts,kte )
  1902. IMPLICIT NONE
  1903. integer &
  1904. ,intent (in ) :: &
  1905. itf,jtf,ktf, &
  1906. its,ite, jts,jte, kts,kte
  1907. integer, intent (in ) :: &
  1908. maxens2
  1909. !
  1910. ! ierr error value, maybe modified in this routine
  1911. !
  1912. real, dimension (its:ite,kts:kte) &
  1913. ,intent (in ) :: &
  1914. us,vs,z,p
  1915. real, dimension (its:ite,1:maxens2) &
  1916. ,intent (out ) :: &
  1917. edtc
  1918. real, dimension (its:ite) &
  1919. ,intent (out ) :: &
  1920. edt
  1921. real, dimension (its:ite) &
  1922. ,intent (in ) :: &
  1923. pwav,pwev
  1924. real &
  1925. ,intent (in ) :: &
  1926. edtmax,edtmin
  1927. integer, dimension (its:ite) &
  1928. ,intent (in ) :: &
  1929. ktop,kbcon
  1930. integer, dimension (its:ite) &
  1931. ,intent (inout) :: &
  1932. ierr
  1933. !
  1934. ! local variables in this routine
  1935. !
  1936. integer i,k,kk
  1937. real einc,pef,pefb,prezk,zkbc
  1938. real, dimension (its:ite) :: &
  1939. vshear,sdp,vws
  1940. !
  1941. !--- DETERMINE DOWNDRAFT STRENGTH IN TERMS OF WINDSHEAR
  1942. !
  1943. ! */ calculate an average wind shear over the depth of the cloud
  1944. !
  1945. do i=its,itf
  1946. edt(i)=0.
  1947. vws(i)=0.
  1948. sdp(i)=0.
  1949. vshear(i)=0.
  1950. enddo
  1951. do k=1,maxens2
  1952. do i=its,itf
  1953. edtc(i,k)=0.
  1954. enddo
  1955. enddo
  1956. do kk = kts,ktf-1
  1957. do 62 i=its,itf
  1958. IF(ierr(i).ne.0)GO TO 62
  1959. if (kk .le. min0(ktop(i),ktf) .and. kk .ge. kbcon(i)) then
  1960. vws(i) = vws(i)+ &
  1961. (abs((us(i,kk+1)-us(i,kk))/(z(i,kk+1)-z(i,kk))) &
  1962. + abs((vs(i,kk+1)-vs(i,kk))/(z(i,kk+1)-z(i,kk)))) * &
  1963. (p(i,kk) - p(i,kk+1))
  1964. sdp(i) = sdp(i) + p(i,kk) - p(i,kk+1)
  1965. endif
  1966. if (kk .eq. ktf-1)vshear(i) = 1.e3 * vws(i) / sdp(i)
  1967. 62 continue
  1968. end do
  1969. do i=its,itf
  1970. IF(ierr(i).eq.0)then
  1971. pef=(1.591-.639*VSHEAR(I)+.0953*(VSHEAR(I)**2) &
  1972. -.00496*(VSHEAR(I)**3))
  1973. if(pef.gt.1.)pef=1.
  1974. if(pef.lt.0.)pef=0.
  1975. !
  1976. !--- cloud base precip efficiency
  1977. !
  1978. zkbc=z(i,kbcon(i))*3.281e-3
  1979. prezk=.02
  1980. if(zkbc.gt.3.)then
  1981. prezk=.96729352+zkbc*(-.70034167+zkbc*(.162179896+zkbc &
  1982. *(- 1.2569798E-2+zkbc*(4.2772E-4-zkbc*5.44E-6))))
  1983. endif
  1984. if(zkbc.gt.25)then
  1985. prezk=2.4
  1986. endif
  1987. pefb=1./(1.+prezk)
  1988. if(pefb.gt.1.)pefb=1.
  1989. if(pefb.lt.0.)pefb=0.
  1990. EDT(I)=1.-.5*(pefb+pef)
  1991. !--- edt here is 1-precipeff!
  1992. einc=.2*edt(i)
  1993. do k=1,maxens2
  1994. edtc(i,k)=edt(i)+float(k-2)*einc
  1995. enddo
  1996. endif
  1997. enddo
  1998. do i=its,itf
  1999. IF(ierr(i).eq.0)then
  2000. do k=1,maxens2
  2001. EDTC(I,K)=-EDTC(I,K)*PWAV(I)/PWEV(I)
  2002. IF(EDTC(I,K).GT.edtmax)EDTC(I,K)=edtmax
  2003. IF(EDTC(I,K).LT.edtmin)EDTC(I,K)=edtmin
  2004. enddo
  2005. endif
  2006. enddo
  2007. END SUBROUTINE cup_dd_edt
  2008. SUBROUTINE cup_dd_he(hes_cup,zd,hcd,z_cup,cdd,entr, &
  2009. jmin,ierr,he,dby,he_cup, &
  2010. itf,jtf,ktf, &
  2011. its,ite, jts,jte, kts,kte )
  2012. IMPLICIT NONE
  2013. !
  2014. ! on input
  2015. !
  2016. ! only local wrf dimensions are need as of now in this routine
  2017. integer &
  2018. ,intent (in ) :: &
  2019. itf,jtf,ktf, &
  2020. its,ite, jts,jte, kts,kte
  2021. ! hcd = downdraft moist static energy
  2022. ! he = moist static energy on model levels
  2023. ! he_cup = moist static energy on model cloud levels
  2024. ! hes_cup = saturation moist static energy on model cloud levels
  2025. ! dby = buoancy term
  2026. ! cdd= detrainment function
  2027. ! z_cup = heights of model cloud levels
  2028. ! entr = entrainment rate
  2029. ! zd = downdraft normalized mass flux
  2030. !
  2031. real, dimension (its:ite,kts:kte) &
  2032. ,intent (in ) :: &
  2033. he,he_cup,hes_cup,z_cup,cdd,zd
  2034. ! entr= entrainment rate
  2035. real &
  2036. ,intent (in ) :: &
  2037. entr
  2038. integer, dimension (its:ite) &
  2039. ,intent (in ) :: &
  2040. jmin
  2041. !
  2042. ! input and output
  2043. !
  2044. ! ierr error value, maybe modified in this routine
  2045. integer, dimension (its:ite) &
  2046. ,intent (inout) :: &
  2047. ierr
  2048. real, dimension (its:ite,kts:kte) &
  2049. ,intent (out ) :: &
  2050. hcd,dby
  2051. !
  2052. ! local variables in this routine
  2053. !
  2054. integer :: &
  2055. i,k,ki
  2056. real :: &
  2057. dz
  2058. do k=kts+1,ktf
  2059. do i=its,itf
  2060. dby(i,k)=0.
  2061. IF(ierr(I).eq.0)then
  2062. hcd(i,k)=hes_cup(i,k)
  2063. endif
  2064. enddo
  2065. enddo
  2066. !
  2067. do 100 i=its,itf
  2068. IF(ierr(I).eq.0)then
  2069. k=jmin(i)
  2070. hcd(i,k)=hes_cup(i,k)
  2071. dby(i,k)=hcd(i,jmin(i))-hes_cup(i,k)
  2072. !
  2073. do ki=jmin(i)-1,1,-1
  2074. DZ=Z_cup(i,Ki+1)-Z_cup(i,Ki)
  2075. HCD(i,Ki)=(HCD(i,Ki+1)*(1.-.5*CDD(i,Ki)*DZ) &
  2076. +entr*DZ*HE(i,Ki) &
  2077. )/(1.+entr*DZ-.5*CDD(i,Ki)*DZ)
  2078. dby(i,ki)=HCD(i,Ki)-hes_cup(i,ki)
  2079. enddo
  2080. !
  2081. endif
  2082. !--- end loop over i
  2083. 100 continue
  2084. END SUBROUTINE cup_dd_he
  2085. SUBROUTINE cup_dd_moisture_3d(zd,hcd,hes_cup,qcd,qes_cup, &
  2086. pwd,q_cup,z_cup,cdd,entr,jmin,ierr, &
  2087. gamma_cup,pwev,bu,qrcd, &
  2088. q,he,t_cup,iloop,xl,high_resolution, &
  2089. itf,jtf,ktf, &
  2090. its,ite, jts,jte, kts,kte )
  2091. IMPLICIT NONE
  2092. integer &
  2093. ,intent (in ) :: &
  2094. itf,jtf,ktf, &
  2095. its,ite, jts,jte, kts,kte,high_resolution
  2096. ! cdd= detrainment function
  2097. ! q = environmental q on model levels
  2098. ! q_cup = environmental q on model cloud levels
  2099. ! qes_cup = saturation q on model cloud levels
  2100. ! hes_cup = saturation h on model cloud levels
  2101. ! hcd = h in model cloud
  2102. ! bu = buoancy term
  2103. ! zd = normalized downdraft mass flux
  2104. ! gamma_cup = gamma on model cloud levels
  2105. ! mentr_rate = entrainment rate
  2106. ! qcd = cloud q (including liquid water) after entrainment
  2107. ! qrch = saturation q in cloud
  2108. ! pwd = evaporate at that level
  2109. ! pwev = total normalized integrated evaoprate (I2)
  2110. ! entr= entrainment rate
  2111. !
  2112. real, dimension (its:ite,kts:kte) &
  2113. ,intent (in ) :: &
  2114. zd,t_cup,hes_cup,hcd,qes_cup,q_cup,z_cup,cdd,gamma_cup,q,he
  2115. real &
  2116. ,intent (in ) :: &
  2117. entr,xl
  2118. integer &
  2119. ,intent (in ) :: &
  2120. iloop
  2121. integer, dimension (its:ite) &
  2122. ,intent (in ) :: &
  2123. jmin
  2124. integer, dimension (its:ite) &
  2125. ,intent (inout) :: &
  2126. ierr
  2127. real, dimension (its:ite,kts:kte) &
  2128. ,intent (out ) :: &
  2129. qcd,qrcd,pwd
  2130. real, dimension (its:ite) &
  2131. ,intent (out ) :: &
  2132. pwev,bu
  2133. !
  2134. ! local variables in this routine
  2135. !
  2136. integer :: &
  2137. i,k,ki
  2138. real :: &
  2139. dh,dz,dqeva
  2140. do i=its,itf
  2141. bu(i)=0.
  2142. pwev(i)=0.
  2143. enddo
  2144. do k=kts,ktf
  2145. do i=its,itf
  2146. qcd(i,k)=0.
  2147. qrcd(i,k)=0.
  2148. pwd(i,k)=0.
  2149. enddo
  2150. enddo
  2151. !
  2152. !
  2153. !
  2154. do 100 i=its,itf
  2155. IF(ierr(I).eq.0)then
  2156. k=jmin(i)
  2157. DZ=Z_cup(i,K+1)-Z_cup(i,K)
  2158. qcd(i,k)=q_cup(i,k)
  2159. if(high_resolution.eq.1)qcd(i,k)=.5*(qes_cup(i,k)+q_cup(i,k))
  2160. qrcd(i,k)=qes_cup(i,k)
  2161. pwd(i,jmin(i))=min(0.,qcd(i,k)-qrcd(i,k))
  2162. pwev(i)=pwev(i)+pwd(i,jmin(i))
  2163. qcd(i,k)=qes_cup(i,k)
  2164. !
  2165. DH=HCD(I,k)-HES_cup(I,K)
  2166. bu(i)=dz*dh
  2167. do ki=jmin(i)-1,1,-1
  2168. DZ=Z_cup(i,Ki+1)-Z_cup(i,Ki)
  2169. QCD(i,Ki)=(qCD(i,Ki+1)*(1.-.5*CDD(i,Ki)*DZ) &
  2170. +entr*DZ*q(i,Ki) &
  2171. )/(1.+entr*DZ-.5*CDD(i,Ki)*DZ)
  2172. !
  2173. !--- to be negatively buoyant, hcd should be smaller than hes!
  2174. !
  2175. DH=HCD(I,ki)-HES_cup(I,Ki)
  2176. bu(i)=bu(i)+dz*dh
  2177. QRCD(I,Ki)=qes_cup(i,ki)+(1./XL)*(GAMMA_cup(i,ki) &
  2178. /(1.+GAMMA_cup(i,ki)))*DH
  2179. dqeva=qcd(i,ki)-qrcd(i,ki)
  2180. if(dqeva.gt.0.)dqeva=0.
  2181. pwd(i,ki)=zd(i,ki)*dqeva
  2182. qcd(i,ki)=qrcd(i,ki)
  2183. pwev(i)=pwev(i)+pwd(i,ki)
  2184. ! if(iloop.eq.1.and.i.eq.102.and.j.eq.62)then
  2185. ! print *,'in cup_dd_moi ', hcd(i,ki),HES_cup(I,Ki),dh,dqeva
  2186. ! endif
  2187. enddo
  2188. !
  2189. !--- end loop over i
  2190. if(pwev(I).eq.0.and.iloop.eq.1)then
  2191. ! print *,'problem with buoy in cup_dd_moisture',i
  2192. ierr(i)=7
  2193. endif
  2194. if(BU(I).GE.0.and.iloop.eq.1)then
  2195. ! print *,'problem with buoy in cup_dd_moisture',i
  2196. ierr(i)=7
  2197. endif
  2198. endif
  2199. 100 continue
  2200. END SUBROUTINE cup_dd_moisture_3d
  2201. SUBROUTINE cup_dd_nms(zd,z_cup,cdd,entr,jmin,ierr, &
  2202. itest,kdet,z1, &
  2203. itf,jtf,ktf, &
  2204. its,ite, jts,jte, kts,kte )
  2205. IMPLICIT NONE
  2206. !
  2207. ! on input
  2208. !
  2209. ! only local wrf dimensions are need as of now in this routine
  2210. integer &
  2211. ,intent (in ) :: &
  2212. itf,jtf,ktf, &
  2213. its,ite, jts,jte, kts,kte
  2214. ! z_cup = height of cloud model level
  2215. ! z1 = terrain elevation
  2216. ! entr = downdraft entrainment rate
  2217. ! jmin = downdraft originating level
  2218. ! kdet = level above ground where downdraft start detraining
  2219. ! itest = flag to whether to calculate cdd
  2220. real, dimension (its:ite,kts:kte) &
  2221. ,intent (in ) :: &
  2222. z_cup
  2223. real, dimension (its:ite) &
  2224. ,intent (in ) :: &
  2225. z1
  2226. real &
  2227. ,intent (in ) :: &
  2228. entr
  2229. integer, dimension (its:ite) &
  2230. ,intent (in ) :: &
  2231. jmin,kdet
  2232. integer &
  2233. ,intent (in ) :: &
  2234. itest
  2235. !
  2236. ! input and output
  2237. !
  2238. ! ierr error value, maybe modified in this routine
  2239. integer, dimension (its:ite) &
  2240. ,intent (inout) :: &
  2241. ierr
  2242. ! zd is the normalized downdraft mass flux
  2243. ! cdd is the downdraft detrainmen function
  2244. real, dimension (its:ite,kts:kte) &
  2245. ,intent (out ) :: &
  2246. zd
  2247. real, dimension (its:ite,kts:kte) &
  2248. ,intent (inout) :: &
  2249. cdd
  2250. !
  2251. ! local variables in this routine
  2252. !
  2253. integer :: &
  2254. i,k,ki
  2255. real :: &
  2256. a,perc,dz
  2257. !
  2258. !--- perc is the percentage of mass left when hitting the ground
  2259. !
  2260. perc=.03
  2261. do k=kts,ktf
  2262. do i=its,itf
  2263. zd(i,k)=0.
  2264. if(itest.eq.0)cdd(i,k)=0.
  2265. enddo
  2266. enddo
  2267. a=1.-perc
  2268. !
  2269. !
  2270. !
  2271. do 100 i=its,itf
  2272. IF(ierr(I).eq.0)then
  2273. zd(i,jmin(i))=1.
  2274. !
  2275. !--- integrate downward, specify detrainment(cdd)!
  2276. !
  2277. do ki=jmin(i)-1,1,-1
  2278. DZ=Z_cup(i,Ki+1)-Z_cup(i,Ki)
  2279. if(ki.le.kdet(i).and.itest.eq.0)then
  2280. cdd(i,ki)=entr+(1.- (a*(z_cup(i,ki)-z1(i)) &
  2281. +perc*(z_cup(i,kdet(i))-z1(i)) ) &
  2282. /(a*(z_cup(i,ki+1)-z1(i)) &
  2283. +perc*(z_cup(i,kdet(i))-z1(i))))/dz
  2284. endif
  2285. zd(i,ki)=zd(i,ki+1)*(1.+(entr-cdd(i,ki))*dz)
  2286. enddo
  2287. !
  2288. endif
  2289. !--- end loop over i
  2290. 100 continue
  2291. END SUBROUTINE cup_dd_nms
  2292. SUBROUTINE cup_dellabot(name,ipr,jpr,he_cup,ierr,z_cup,p_cup, &
  2293. hcd,edt,zd,cdd,he,della,subs,j,mentrd_rate,z,g, &
  2294. itf,jtf,ktf, &
  2295. its,ite, jts,jte, kts,kte )
  2296. IMPLICIT NONE
  2297. integer &
  2298. ,intent (in ) :: &
  2299. itf,jtf,ktf, &
  2300. its,ite, jts,jte, kts,kte
  2301. integer, intent (in ) :: &
  2302. j,ipr,jpr
  2303. character *(*), intent (in) :: &
  2304. name
  2305. !
  2306. ! ierr error value, maybe modified in this routine
  2307. !
  2308. real, dimension (its:ite,kts:kte) &
  2309. ,intent (out ) :: &
  2310. della,subs
  2311. real, dimension (its:ite,kts:kte) &
  2312. ,intent (in ) :: &
  2313. z_cup,p_cup,hcd,zd,cdd,he,z,he_cup
  2314. real, dimension (its:ite) &
  2315. ,intent (in ) :: &
  2316. edt
  2317. real &
  2318. ,intent (in ) :: &
  2319. g,mentrd_rate
  2320. integer, dimension (its:ite) &
  2321. ,intent (inout) :: &
  2322. ierr
  2323. !
  2324. ! local variables in this routine
  2325. !
  2326. integer i
  2327. real detdo,detdo1,detdo2,entdo,dp,dz,subin, &
  2328. totmas
  2329. !
  2330. !
  2331. ! if(name.eq.'shallow')then
  2332. ! edt(:)=0.
  2333. ! cdd(:,:)=0.
  2334. ! endif
  2335. do 100 i=its,itf
  2336. della(i,1)=0.
  2337. subs(i,1)=0.
  2338. if(ierr(i).ne.0)go to 100
  2339. dz=z_cup(i,2)-z_cup(i,1)
  2340. DP=100.*(p_cup(i,1)-P_cup(i,2))
  2341. detdo1=edt(i)*zd(i,2)*CDD(i,1)*DZ
  2342. detdo2=edt(i)*zd(i,1)
  2343. entdo=edt(i)*zd(i,2)*mentrd_rate*dz
  2344. subin=-EDT(I)*zd(i,2)
  2345. detdo=detdo1+detdo2-entdo+subin
  2346. DELLA(I,1)=(detdo1*.5*(HCD(i,1)+HCD(i,2)) &
  2347. +detdo2*hcd(i,1) &
  2348. +subin*he_cup(i,2) &
  2349. -entdo*he(i,1))*g/dp
  2350. SUBS(I,1)=0.
  2351. ! if(i.eq.ipr.and.j.eq.jpr)then
  2352. ! write(0,*)'db1',della(i,1),subs(i,1),subin,entdo
  2353. ! write(0,*)'db2',detdo1,detdo2,detdo1+detdo2-entdo+subin
  2354. ! endif
  2355. 100 CONTINUE
  2356. END SUBROUTINE cup_dellabot
  2357. SUBROUTINE cup_dellas_3d(ierr,z_cup,p_cup,hcd,edt,zd,cdd, &
  2358. he,della,subs,j,mentrd_rate,zu,g, &
  2359. cd,hc,ktop,k22,kbcon,mentr_rate,jmin,he_cup,kdet,kpbl, &
  2360. ipr,jpr,name,high_res, &
  2361. itf,jtf,ktf, &
  2362. its,ite, jts,jte, kts,kte )
  2363. IMPLICIT NONE
  2364. integer &
  2365. ,intent (in ) :: &
  2366. itf,jtf,ktf, &
  2367. its,ite, jts,jte, kts,kte
  2368. integer, intent (in ) :: &
  2369. j,ipr,jpr,high_res
  2370. !
  2371. ! ierr error value, maybe modified in this routine
  2372. !
  2373. real, dimension (its:ite,kts:kte) &
  2374. ,intent (out ) :: &
  2375. della,subs
  2376. real, dimension (its:ite,kts:kte) &
  2377. ,intent (in ) :: &
  2378. z_cup,p_cup,hcd,zd,cdd,he,hc,cd,zu,he_cup
  2379. real, dimension (its:ite) &
  2380. ,intent (in ) :: &
  2381. edt
  2382. real &
  2383. ,intent (in ) :: &
  2384. g,mentrd_rate,mentr_rate
  2385. integer, dimension (its:ite) &
  2386. ,intent (in ) :: &
  2387. kbcon,ktop,k22,jmin,kdet,kpbl
  2388. integer, dimension (its:ite) &
  2389. ,intent (inout) :: &
  2390. ierr
  2391. character *(*), intent (in) :: &
  2392. name
  2393. !
  2394. ! local variables in this routine
  2395. !
  2396. integer i,k,kstart
  2397. real detdo1,detdo2,entdo,dp,dz,subin,detdo,entup, &
  2398. detup,subdown,entdoj,entupk,detupk,totmas
  2399. !
  2400. i=ipr
  2401. kstart=kts+1
  2402. if(name.eq.'shallow')kstart=kts
  2403. DO K=kstart,ktf
  2404. do i=its,itf
  2405. della(i,k)=0.
  2406. subs(i,k)=0.
  2407. enddo
  2408. enddo
  2409. !
  2410. ! no downdrafts for shallow convection
  2411. !
  2412. DO 100 k=kts+1,ktf-1
  2413. DO 100 i=its,ite
  2414. IF(ierr(i).ne.0)GO TO 100
  2415. IF(K.Gt.KTOP(I))GO TO 100
  2416. if(k.lt.k22(i)-1.and.name.eq.'shallow')GO TO 100
  2417. !
  2418. !--- SPECIFY DETRAINMENT OF DOWNDRAFT, HAS TO BE CONSISTENT
  2419. !--- WITH ZD CALCULATIONS IN SOUNDD.
  2420. !
  2421. DZ=Z_cup(I,K+1)-Z_cup(I,K)
  2422. detdo=edt(i)*CDD(i,K)*DZ*ZD(i,k+1)
  2423. entdo=edt(i)*mentrd_rate*dz*zd(i,k+1)
  2424. !3d subin=zu(i,k+1)-zd(i,k+1)*edt(i)
  2425. subin=-zd(i,k+1)*edt(i)
  2426. entup=0.
  2427. detup=0.
  2428. if(k.ge.kbcon(i).and.k.lt.ktop(i))then
  2429. entup=mentr_rate*dz*zu(i,k)
  2430. detup=CD(i,K+1)*DZ*ZU(i,k)
  2431. endif
  2432. !3d subdown=(zu(i,k)-zd(i,k)*edt(i))
  2433. subdown=-zd(i,k)*edt(i)
  2434. entdoj=0.
  2435. entupk=0.
  2436. detupk=0.
  2437. !
  2438. if(k.eq.jmin(i))then
  2439. entdoj=edt(i)*zd(i,k)
  2440. endif
  2441. if(k.eq.k22(i)-1)then
  2442. entupk=zu(i,kpbl(i))
  2443. subin=zu(i,k+1)-zd(i,k+1)*edt(i)
  2444. if(high_res.eq.1)subin=-zd(i,k+1)*edt(i)
  2445. ! subin=-zd(i,k+1)*edt(i)
  2446. endif
  2447. if(k.gt.kdet(i))then
  2448. detdo=0.
  2449. endif
  2450. if(k.eq.ktop(i)-0)then
  2451. detupk=zu(i,ktop(i))
  2452. subin=0.
  2453. !
  2454. ! this subsidene for ktop now in subs term!
  2455. ! subdown=zu(i,k)
  2456. subdown=0.
  2457. endif
  2458. if(k.lt.kbcon(i))then
  2459. detup=0.
  2460. endif
  2461. !C
  2462. !C--- CHANGED DUE TO SUBSIDENCE AND ENTRAINMENT
  2463. !C
  2464. totmas=subin-subdown+detup-entup-entdo+ &
  2465. detdo-entupk-entdoj+detupk
  2466. ! if(j.eq.jpr.and.i.eq.ipr)print *,'k,totmas,sui,sud = ',k,
  2467. ! 1 totmas,subin,subdown
  2468. ! if(j.eq.jpr.and.i.eq.ipr)print *,'updr stuff = ',detup,
  2469. ! 1 entup,entupk,detupk
  2470. ! if(j.eq.jpr.and.i.eq.ipr)print *,'dddr stuff = ',entdo,
  2471. ! 1 detdo,entdoj
  2472. if(abs(totmas).gt.1.e-6)then
  2473. ! print *,'*********************',i,j,k,totmas,name
  2474. ! print *,kpbl(i),k22(i),kbcon(i),ktop(i)
  2475. !c print *,'updr stuff = ',subin,
  2476. !c 1 subdown,detup,entup,entupk,detupk
  2477. !c print *,'dddr stuff = ',entdo,
  2478. !c 1 detdo,entdoj
  2479. ! call wrf_error_fatal ( 'totmas .gt.1.e-6' )
  2480. endif
  2481. dp=100.*(p_cup(i,k-1)-p_cup(i,k))
  2482. della(i,k)=(detup*.5*(HC(i,K+1)+HC(i,K)) &
  2483. +detdo*.5*(HCD(i,K+1)+HCD(i,K)) &
  2484. -entup*he(i,k) &
  2485. -entdo*he(i,k) &
  2486. +subin*he_cup(i,k+1) &
  2487. -subdown*he_cup(i,k) &
  2488. +detupk*(hc(i,ktop(i))-he_cup(i,ktop(i))) &
  2489. -entupk*he_cup(i,k22(i)) &
  2490. -entdoj*he_cup(i,jmin(i)) &
  2491. )*g/dp
  2492. if(high_res.eq.1)then
  2493. ! the first term includes entr and detr into/from updraft as well as (entup-detup)*he(i,k) from
  2494. ! neighbouring point, to make things mass consistent....
  2495. ! if(k.ge.k22(i))then
  2496. della(i,k)=( &
  2497. detup*.5*(HC(i,K+1)+HC(i,K))-entup*he(i,k)+(entup-detup)*he(i,k) &
  2498. +detdo*.5*(HCD(i,K+1)+HCD(i,K)) &
  2499. -entdo*he(i,k) &
  2500. +subin*he_cup(i,k+1) &
  2501. -subdown*he_cup(i,k) &
  2502. +detupk*(hc(i,ktop(i))-he(i,ktop(i))) &
  2503. -entdoj*he_cup(i,jmin(i)) &
  2504. -entupk*he_cup(i,k22(i))+entupk*he(i,k) &
  2505. )*g/dp
  2506. ! else if(k.eq.k22(i)-1)then
  2507. ! della(i,k)=(-entupk*he_cup(i,k22(i))+entupk*he(i,k))*g/dp
  2508. endif
  2509. !3d subin=zu(i,k+1)-zd(i,k+1)*edt(i)
  2510. !
  2511. ! updraft subsidence only
  2512. !
  2513. if(k.ge.k22(i).and.k.lt.ktop(i))then
  2514. subs(i,k)=(zu(i,k+1)*he_cup(i,k+1) &
  2515. -zu(i,k)*he_cup(i,k))*g/dp
  2516. ! else if(k.eq.ktop(i))then
  2517. ! subs(i,k)=-detupk*he_cup(i,k)*g/dp
  2518. endif
  2519. !
  2520. ! in igh res case, subsidence terms are for meighbouring points only. This has to be
  2521. ! done mass consistent with the della term
  2522. if(high_res.eq.1)then
  2523. if(k.ge.k22(i).and.k.lt.ktop(i))then
  2524. subs(i,k)=(zu(i,k+1)*he_cup(i,k+1)-zu(i,k)*he_cup(i,k)-(entup-detup)*he(i,k))*g/dp
  2525. else if(k.eq.ktop(i))then
  2526. subs(i,k)=detupk*(he(i,ktop(i))-he_cup(i,ktop(i)))*g/dp
  2527. else if(k.eq.k22(i)-1)then
  2528. subs(i,k)=(entupk*he(i,k)-entupk*he_cup(i,k))*g/dp
  2529. endif
  2530. endif
  2531. ! if(i.eq.ipr.and.j.eq.jpr)then
  2532. ! write(0,*)'d',k,della(i,k),subs(i,k),subin,subdown
  2533. !! write(0,*)'d',detup,entup,entdo,entupk,entdoj
  2534. !! print *,k,della(i,k),subin*he_cup(i,k+1),subdown*he_cup(i,k),
  2535. !! 1 detdo*.5*(HCD(i,K+1)+HCD(i,K))
  2536. !! print *,k,detup*.5*(HC(i,K+1)+HC(i,K)),detupk*hc(i,ktop(i)),
  2537. !! 1 entup*he(i,k),entdo*he(i,k)
  2538. !! print *,k,he_cup(i,k+1),he_cup(i,k),entupk*he_cup(i,k)
  2539. ! endif
  2540. 100 CONTINUE
  2541. END SUBROUTINE cup_dellas_3d
  2542. SUBROUTINE cup_direction2(i,j,dir,id,massflx, &
  2543. iresult,imass,massfld, &
  2544. itf,jtf,ktf, &
  2545. its,ite, jts,jte, kts,kte )
  2546. IMPLICIT NONE
  2547. integer &
  2548. ,intent (in ) :: &
  2549. itf,jtf,ktf, &
  2550. its,ite, jts,jte, kts,kte
  2551. integer, intent (in ) :: &
  2552. i,j,imass
  2553. integer, intent (out ) :: &
  2554. iresult
  2555. !
  2556. ! ierr error value, maybe modified in this routine
  2557. !
  2558. integer, dimension (its:ite,jts:jte) &
  2559. ,intent (in ) :: &
  2560. id
  2561. real, dimension (its:ite,jts:jte) &
  2562. ,intent (in ) :: &
  2563. massflx
  2564. real, dimension (its:ite) &
  2565. ,intent (inout) :: &
  2566. dir
  2567. real &
  2568. ,intent (out ) :: &
  2569. massfld
  2570. !
  2571. ! local variables in this routine
  2572. !
  2573. integer k,ia,ja,ib,jb
  2574. real diff
  2575. !
  2576. !
  2577. !
  2578. if(imass.eq.1)then
  2579. massfld=massflx(i,j)
  2580. endif
  2581. iresult=0
  2582. ! return
  2583. diff=22.5
  2584. if(dir(i).lt.22.5)dir(i)=360.+dir(i)
  2585. if(id(i,j).eq.1)iresult=1
  2586. ! ja=max(2,j-1)
  2587. ! ia=max(2,i-1)
  2588. ! jb=min(mjx-1,j+1)
  2589. ! ib=min(mix-1,i+1)
  2590. ja=j-1
  2591. ia=i-1
  2592. jb=j+1
  2593. ib=i+1
  2594. if(dir(i).gt.90.-diff.and.dir(i).le.90.+diff)then
  2595. !--- steering flow from the east
  2596. if(id(ib,j).eq.1)then
  2597. iresult=1
  2598. if(imass.eq.1)then
  2599. massfld=max(massflx(ib,j),massflx(i,j))
  2600. endif
  2601. return
  2602. endif
  2603. else if(dir(i).gt.135.-diff.and.dir(i).le.135.+diff)then
  2604. !--- steering flow from the south-east
  2605. if(id(ib,ja).eq.1)then
  2606. iresult=1
  2607. if(imass.eq.1)then
  2608. massfld=max(massflx(ib,ja),massflx(i,j))
  2609. endif
  2610. return
  2611. endif
  2612. !--- steering flow from the south
  2613. else if(dir(i).gt.180.-diff.and.dir(i).le.180.+diff)then
  2614. if(id(i,ja).eq.1)then
  2615. iresult=1
  2616. if(imass.eq.1)then
  2617. massfld=max(massflx(i,ja),massflx(i,j))
  2618. endif
  2619. return
  2620. endif
  2621. !--- steering flow from the south west
  2622. else if(dir(i).gt.225.-diff.and.dir(i).le.225.+diff)then
  2623. if(id(ia,ja).eq.1)then
  2624. iresult=1
  2625. if(imass.eq.1)then
  2626. massfld=max(massflx(ia,ja),massflx(i,j))
  2627. endif
  2628. return
  2629. endif
  2630. !--- steering flow from the west
  2631. else if(dir(i).gt.270.-diff.and.dir(i).le.270.+diff)then
  2632. if(id(ia,j).eq.1)then
  2633. iresult=1
  2634. if(imass.eq.1)then
  2635. massfld=max(massflx(ia,j),massflx(i,j))
  2636. endif
  2637. return
  2638. endif
  2639. !--- steering flow from the north-west
  2640. else if(dir(i).gt.305.-diff.and.dir(i).le.305.+diff)then
  2641. if(id(ia,jb).eq.1)then
  2642. iresult=1
  2643. if(imass.eq.1)then
  2644. massfld=max(massflx(ia,jb),massflx(i,j))
  2645. endif
  2646. return
  2647. endif
  2648. !--- steering flow from the north
  2649. else if(dir(i).gt.360.-diff.and.dir(i).le.360.+diff)then
  2650. if(id(i,jb).eq.1)then
  2651. iresult=1
  2652. if(imass.eq.1)then
  2653. massfld=max(massflx(i,jb),massflx(i,j))
  2654. endif
  2655. return
  2656. endif
  2657. !--- steering flow from the north-east
  2658. else if(dir(i).gt.45.-diff.and.dir(i).le.45.+diff)then
  2659. if(id(ib,jb).eq.1)then
  2660. iresult=1
  2661. if(imass.eq.1)then
  2662. massfld=max(massflx(ib,jb),massflx(i,j))
  2663. endif
  2664. return
  2665. endif
  2666. endif
  2667. END SUBROUTINE cup_direction2
  2668. SUBROUTINE cup_env(z,qes,he,hes,t,q,p,z1, &
  2669. psur,ierr,tcrit,itest,xl,cp, &
  2670. itf,jtf,ktf, &
  2671. its,ite, jts,jte, kts,kte )
  2672. IMPLICIT NONE
  2673. integer &
  2674. ,intent (in ) :: &
  2675. itf,jtf,ktf, &
  2676. its,ite, jts,jte, kts,kte
  2677. !
  2678. ! ierr error value, maybe modified in this routine
  2679. ! q = environmental mixing ratio
  2680. ! qes = environmental saturation mixing ratio
  2681. ! t = environmental temp
  2682. ! tv = environmental virtual temp
  2683. ! p = environmental pressure
  2684. ! z = environmental heights
  2685. ! he = environmental moist static energy
  2686. ! hes = environmental saturation moist static energy
  2687. ! psur = surface pressure
  2688. ! z1 = terrain elevation
  2689. !
  2690. !
  2691. real, dimension (its:ite,kts:kte) &
  2692. ,intent (in ) :: &
  2693. p,t,q
  2694. real, dimension (its:ite,kts:kte) &
  2695. ,intent (out ) :: &
  2696. he,hes,qes
  2697. real, dimension (its:ite,kts:kte) &
  2698. ,intent (inout) :: &
  2699. z
  2700. real, dimension (its:ite) &
  2701. ,intent (in ) :: &
  2702. psur,z1
  2703. real &
  2704. ,intent (in ) :: &
  2705. xl,cp
  2706. integer, dimension (its:ite) &
  2707. ,intent (inout) :: &
  2708. ierr
  2709. integer &
  2710. ,intent (in ) :: &
  2711. itest
  2712. !
  2713. ! local variables in this routine
  2714. !
  2715. integer :: &
  2716. i,k,iph
  2717. real, dimension (1:2) :: AE,BE,HT
  2718. real, dimension (its:ite,kts:kte) :: tv
  2719. real :: tcrit,e,tvbar
  2720. HT(1)=XL/CP
  2721. HT(2)=2.834E6/CP
  2722. BE(1)=.622*HT(1)/.286
  2723. AE(1)=BE(1)/273.+ALOG(610.71)
  2724. BE(2)=.622*HT(2)/.286
  2725. AE(2)=BE(2)/273.+ALOG(610.71)
  2726. ! print *, 'TCRIT = ', tcrit,its,ite
  2727. DO k=kts,ktf
  2728. do i=its,itf
  2729. if(ierr(i).eq.0)then
  2730. !Csgb - IPH is for phase, dependent on TCRIT (water or ice)
  2731. IPH=1
  2732. IF(T(I,K).LE.TCRIT)IPH=2
  2733. ! print *, 'AE(IPH),BE(IPH) = ',AE(IPH),BE(IPH),AE(IPH)-BE(IPH),T(i,k),i,k
  2734. E=EXP(AE(IPH)-BE(IPH)/T(I,K))
  2735. ! print *, 'P, E = ', P(I,K), E
  2736. QES(I,K)=.622*E/(100.*P(I,K)-E)
  2737. IF(QES(I,K).LE.1.E-08)QES(I,K)=1.E-08
  2738. IF(QES(I,K).LT.Q(I,K))QES(I,K)=Q(I,K)
  2739. ! IF(Q(I,K).GT.QES(I,K))Q(I,K)=QES(I,K)
  2740. TV(I,K)=T(I,K)+.608*Q(I,K)*T(I,K)
  2741. endif
  2742. enddo
  2743. enddo
  2744. !
  2745. !--- z's are calculated with changed h's and q's and t's
  2746. !--- if itest=2
  2747. !
  2748. if(itest.ne.2)then
  2749. do i=its,itf
  2750. if(ierr(i).eq.0)then
  2751. Z(I,1)=max(0.,Z1(I))-(ALOG(P(I,1))- &
  2752. ALOG(PSUR(I)))*287.*TV(I,1)/9.81
  2753. endif
  2754. enddo
  2755. ! --- calculate heights
  2756. DO K=kts+1,ktf
  2757. do i=its,itf
  2758. if(ierr(i).eq.0)then
  2759. TVBAR=.5*TV(I,K)+.5*TV(I,K-1)
  2760. Z(I,K)=Z(I,K-1)-(ALOG(P(I,K))- &
  2761. ALOG(P(I,K-1)))*287.*TVBAR/9.81
  2762. endif
  2763. enddo
  2764. enddo
  2765. else
  2766. do k=kts,ktf
  2767. do i=its,itf
  2768. if(ierr(i).eq.0)then
  2769. z(i,k)=(he(i,k)-1004.*t(i,k)-2.5e6*q(i,k))/9.81
  2770. z(i,k)=max(1.e-3,z(i,k))
  2771. endif
  2772. enddo
  2773. enddo
  2774. endif
  2775. !
  2776. !--- calculate moist static energy - HE
  2777. ! saturated moist static energy - HES
  2778. !
  2779. DO k=kts,ktf
  2780. do i=its,itf
  2781. if(ierr(i).eq.0)then
  2782. if(itest.eq.0)HE(I,K)=9.81*Z(I,K)+1004.*T(I,K)+2.5E06*Q(I,K)
  2783. HES(I,K)=9.81*Z(I,K)+1004.*T(I,K)+2.5E06*QES(I,K)
  2784. IF(HE(I,K).GE.HES(I,K))HE(I,K)=HES(I,K)
  2785. endif
  2786. enddo
  2787. enddo
  2788. END SUBROUTINE cup_env
  2789. SUBROUTINE cup_env_clev(t,qes,q,he,hes,z,p,qes_cup,q_cup, &
  2790. he_cup,hes_cup,z_cup,p_cup,gamma_cup,t_cup,psur, &
  2791. ierr,z1,xl,rv,cp, &
  2792. itf,jtf,ktf, &
  2793. its,ite, jts,jte, kts,kte )
  2794. IMPLICIT NONE
  2795. integer &
  2796. ,intent (in ) :: &
  2797. itf,jtf,ktf, &
  2798. its,ite, jts,jte, kts,kte
  2799. !
  2800. ! ierr error value, maybe modified in this routine
  2801. ! q = environmental mixing ratio
  2802. ! q_cup = environmental mixing ratio on cloud levels
  2803. ! qes = environmental saturation mixing ratio
  2804. ! qes_cup = environmental saturation mixing ratio on cloud levels
  2805. ! t = environmental temp
  2806. ! t_cup = environmental temp on cloud levels
  2807. ! p = environmental pressure
  2808. ! p_cup = environmental pressure on cloud levels
  2809. ! z = environmental heights
  2810. ! z_cup = environmental heights on cloud levels
  2811. ! he = environmental moist static energy
  2812. ! he_cup = environmental moist static energy on cloud levels
  2813. ! hes = environmental saturation moist static energy
  2814. ! hes_cup = environmental saturation moist static energy on cloud levels
  2815. ! gamma_cup = gamma on cloud levels
  2816. ! psur = surface pressure
  2817. ! z1 = terrain elevation
  2818. !
  2819. !
  2820. real, dimension (its:ite,kts:kte) &
  2821. ,intent (in ) :: &
  2822. qes,q,he,hes,z,p,t
  2823. real, dimension (its:ite,kts:kte) &
  2824. ,intent (out ) :: &
  2825. qes_cup,q_cup,he_cup,hes_cup,z_cup,p_cup,gamma_cup,t_cup
  2826. real, dimension (its:ite) &
  2827. ,intent (in ) :: &
  2828. psur,z1
  2829. real &
  2830. ,intent (in ) :: &
  2831. xl,rv,cp
  2832. integer, dimension (its:ite) &
  2833. ,intent (inout) :: &
  2834. ierr
  2835. !
  2836. ! local variables in this routine
  2837. !
  2838. integer :: &
  2839. i,k
  2840. do k=kts+1,ktf
  2841. do i=its,itf
  2842. if(ierr(i).eq.0)then
  2843. qes_cup(i,k)=.5*(qes(i,k-1)+qes(i,k))
  2844. q_cup(i,k)=.5*(q(i,k-1)+q(i,k))
  2845. hes_cup(i,k)=.5*(hes(i,k-1)+hes(i,k))
  2846. he_cup(i,k)=.5*(he(i,k-1)+he(i,k))
  2847. if(he_cup(i,k).gt.hes_cup(i,k))he_cup(i,k)=hes_cup(i,k)
  2848. z_cup(i,k)=.5*(z(i,k-1)+z(i,k))
  2849. p_cup(i,k)=.5*(p(i,k-1)+p(i,k))
  2850. t_cup(i,k)=.5*(t(i,k-1)+t(i,k))
  2851. gamma_cup(i,k)=(xl/cp)*(xl/(rv*t_cup(i,k) &
  2852. *t_cup(i,k)))*qes_cup(i,k)
  2853. endif
  2854. enddo
  2855. enddo
  2856. do i=its,itf
  2857. if(ierr(i).eq.0)then
  2858. qes_cup(i,1)=qes(i,1)
  2859. q_cup(i,1)=q(i,1)
  2860. hes_cup(i,1)=hes(i,1)
  2861. he_cup(i,1)=he(i,1)
  2862. z_cup(i,1)=.5*(z(i,1)+z1(i))
  2863. p_cup(i,1)=.5*(p(i,1)+psur(i))
  2864. t_cup(i,1)=t(i,1)
  2865. gamma_cup(i,1)=xl/cp*(xl/(rv*t_cup(i,1) &
  2866. *t_cup(i,1)))*qes_cup(i,1)
  2867. endif
  2868. enddo
  2869. END SUBROUTINE cup_env_clev
  2870. SUBROUTINE cup_forcing_ens_3d(closure_n,xland,aa0,aa1,xaa0,mbdt,dtime,ierr,ierr2,ierr3,&
  2871. xf_ens,j,name,axx,maxens,iens,iedt,maxens2,maxens3,mconv, &
  2872. p_cup,ktop,omeg,zd,k22,zu,pr_ens,edt,kbcon,massflx, &
  2873. iact_old_gr,dir,ensdim,massfln,icoic,edt_out, &
  2874. high_resolution,itf,jtf,ktf, &
  2875. its,ite, jts,jte, kts,kte,ens4,ktau )
  2876. IMPLICIT NONE
  2877. integer &
  2878. ,intent (in ) :: &
  2879. itf,jtf,ktf, &
  2880. its,ite, jts,jte, kts,kte,ens4,high_resolution,ktau
  2881. integer, intent (in ) :: &
  2882. j,ensdim,maxens,iens,iedt,maxens2,maxens3
  2883. !
  2884. ! ierr error value, maybe modified in this routine
  2885. ! pr_ens = precipitation ensemble
  2886. ! xf_ens = mass flux ensembles
  2887. ! massfln = downdraft mass flux ensembles used in next timestep
  2888. ! omeg = omega from large scale model
  2889. ! mconv = moisture convergence from large scale model
  2890. ! zd = downdraft normalized mass flux
  2891. ! zu = updraft normalized mass flux
  2892. ! aa0 = cloud work function without forcing effects
  2893. ! aa1 = cloud work function with forcing effects
  2894. ! xaa0 = cloud work function with cloud effects (ensemble dependent)
  2895. ! edt = epsilon
  2896. ! dir = "storm motion"
  2897. ! mbdt = arbitrary numerical parameter
  2898. ! dtime = dt over which forcing is applied
  2899. ! iact_gr_old = flag to tell where convection was active
  2900. ! kbcon = LFC of parcel from k22
  2901. ! k22 = updraft originating level
  2902. ! icoic = flag if only want one closure (usually set to zero!)
  2903. ! name = deep or shallow convection flag
  2904. !
  2905. real, dimension (its:ite,jts:jte,1:ensdim) &
  2906. ,intent (inout) :: &
  2907. pr_ens
  2908. real, dimension (its:ite,jts:jte,1:ensdim) &
  2909. ,intent (out ) :: &
  2910. xf_ens,massfln
  2911. real, dimension (its:ite,jts:jte) &
  2912. ,intent (inout ) :: &
  2913. edt_out
  2914. real, dimension (its:ite,jts:jte) &
  2915. ,intent (in ) :: &
  2916. massflx
  2917. real, dimension (its:ite,kts:kte) &
  2918. ,intent (in ) :: &
  2919. zd,zu,p_cup
  2920. real, dimension (its:ite,kts:kte,1:ens4) &
  2921. ,intent (in ) :: &
  2922. omeg
  2923. real, dimension (its:ite,1:maxens) &
  2924. ,intent (in ) :: &
  2925. xaa0
  2926. real, dimension (its:ite) &
  2927. ,intent (in ) :: &
  2928. aa1,edt,dir,xland
  2929. real, dimension (its:ite,1:ens4) &
  2930. ,intent (in ) :: &
  2931. mconv,axx
  2932. real, dimension (its:ite) &
  2933. ,intent (inout) :: &
  2934. aa0,closure_n
  2935. real, dimension (1:maxens) &
  2936. ,intent (in ) :: &
  2937. mbdt
  2938. real &
  2939. ,intent (in ) :: &
  2940. dtime
  2941. integer, dimension (its:ite,jts:jte) &
  2942. ,intent (in ) :: &
  2943. iact_old_gr
  2944. integer, dimension (its:ite) &
  2945. ,intent (in ) :: &
  2946. k22,kbcon,ktop
  2947. integer, dimension (its:ite) &
  2948. ,intent (inout) :: &
  2949. ierr,ierr2,ierr3
  2950. integer &
  2951. ,intent (in ) :: &
  2952. icoic
  2953. character *(*), intent (in) :: &
  2954. name
  2955. !
  2956. ! local variables in this routine
  2957. !
  2958. real, dimension (1:maxens3) :: &
  2959. xff_ens3
  2960. real, dimension (1:maxens) :: &
  2961. xk
  2962. integer :: &
  2963. i,k,nall,n,ne,nens,nens3,iresult,iresultd,iresulte,mkxcrt,kclim
  2964. parameter (mkxcrt=15)
  2965. real :: &
  2966. fens4,a1,massfld,a_ave,xff0,xff00,xxx,xomg,aclim1,aclim2,aclim3,aclim4
  2967. real, dimension(1:mkxcrt) :: &
  2968. pcrit,acrit,acritt
  2969. integer :: nall2,ixxx,irandom
  2970. integer, dimension (12) :: seed
  2971. DATA PCRIT/850.,800.,750.,700.,650.,600.,550.,500.,450.,400., &
  2972. 350.,300.,250.,200.,150./
  2973. DATA ACRIT/.0633,.0445,.0553,.0664,.075,.1082,.1521,.2216, &
  2974. .3151,.3677,.41,.5255,.7663,1.1686,1.6851/
  2975. ! GDAS DERIVED ACRIT
  2976. DATA ACRITT/.203,.515,.521,.566,.625,.665,.659,.688, &
  2977. .743,.813,.886,.947,1.138,1.377,1.896/
  2978. !
  2979. seed=0
  2980. seed(2)=j
  2981. seed(3)=ktau
  2982. nens=0
  2983. irandom=1
  2984. if(high_resolution.eq.1)irandom=0
  2985. irandom=0
  2986. fens4=float(ens4)
  2987. !--- LARGE SCALE FORCING
  2988. !
  2989. DO 100 i=its,itf
  2990. if(name.eq.'deeps'.and.ierr(i).gt.995)then
  2991. aa0(i)=0.
  2992. ierr(i)=0
  2993. endif
  2994. IF(ierr(i).eq.0)then
  2995. !
  2996. !---
  2997. !
  2998. if(name.eq.'deeps')then
  2999. !
  3000. a_ave=0.
  3001. do ne=1,ens4
  3002. a_ave=a_ave+axx(i,ne)
  3003. enddo
  3004. a_ave=max(0.,a_ave/fens4)
  3005. a_ave=min(a_ave,aa1(i))
  3006. a_ave=max(0.,a_ave)
  3007. do ne=1,16
  3008. xff_ens3(ne)=0.
  3009. enddo
  3010. xff0= (AA1(I)-AA0(I))/DTIME
  3011. if(high_resolution.eq.1)xff0= (a_ave-AA0(I))/DTIME
  3012. xff_ens3(1)=(AA1(I)-AA0(I))/dtime
  3013. xff_ens3(2)=(a_ave-AA0(I))/dtime
  3014. if(irandom.eq.1)then
  3015. seed(1)=i
  3016. call random_seed (PUT=seed)
  3017. call random_number (xxx)
  3018. ixxx=min(ens4,max(1,int(fens4*xxx+1.e-8)))
  3019. xff_ens3(3)=(axx(i,ixxx)-AA0(I))/dtime
  3020. call random_number (xxx)
  3021. ixxx=min(ens4,max(1,int(fens4*xxx+1.e-8)))
  3022. xff_ens3(13)=(axx(i,ixxx)-AA0(I))/dtime
  3023. else
  3024. xff_ens3(3)=(AA1(I)-AA0(I))/dtime
  3025. xff_ens3(13)=(AA1(I)-AA0(I))/dtime
  3026. endif
  3027. if(high_resolution.eq.1)then
  3028. xff_ens3(1)=(a_ave-AA0(I))/dtime
  3029. xff_ens3(2)=(a_ave-AA0(I))/dtime
  3030. xff_ens3(3)=(a_ave-AA0(I))/dtime
  3031. xff_ens3(13)=(a_ave-AA0(I))/dtime
  3032. endif
  3033. !
  3034. !--- more original Arakawa-Schubert (climatologic value of aa0)
  3035. !
  3036. !
  3037. !--- omeg is in bar/s, mconv done with omeg in Pa/s
  3038. ! more like Brown (1979), or Frank-Cohen (199?)
  3039. !
  3040. xff_ens3(14)=0.
  3041. do ne=1,ens4
  3042. xff_ens3(14)=xff_ens3(14)-omeg(i,k22(i),ne)/(fens4*9.81)
  3043. enddo
  3044. if(xff_ens3(14).lt.0.)xff_ens3(14)=0.
  3045. xff_ens3(5)=0.
  3046. do ne=1,ens4
  3047. xff_ens3(5)=xff_ens3(5)-omeg(i,kbcon(i),ne)/(fens4*9.81)
  3048. enddo
  3049. if(xff_ens3(5).lt.0.)xff_ens3(5)=0.
  3050. !
  3051. ! minimum below kbcon
  3052. !
  3053. if(high_resolution.eq.0)then
  3054. xff_ens3(4)=-omeg(i,2,1)/9.81
  3055. do k=2,kbcon(i)-1
  3056. do ne=1,ens4
  3057. xomg=-omeg(i,k,ne)/9.81
  3058. if(xomg.lt.xff_ens3(4))xff_ens3(4)=xomg
  3059. enddo
  3060. enddo
  3061. if(xff_ens3(4).lt.0.)xff_ens3(4)=0.
  3062. !
  3063. ! max below kbcon
  3064. xff_ens3(6)=-omeg(i,2,1)/9.81
  3065. do k=2,kbcon(i)-1
  3066. do ne=1,ens4
  3067. xomg=-omeg(i,k,ne)/9.81
  3068. if(xomg.gt.xff_ens3(6))xff_ens3(6)=xomg
  3069. enddo
  3070. enddo
  3071. if(xff_ens3(6).lt.0.)xff_ens3(6)=0.
  3072. endif
  3073. if(high_resolution.eq.1)then
  3074. xff_ens3(5)=min(xff_ens3(5),xff_ens3(14))
  3075. xff_ens3(4)=xff_ens3(5)
  3076. xff_ens3(6)=xff_ens3(5)
  3077. endif
  3078. !
  3079. !--- more like Krishnamurti et al.; pick max and average values
  3080. !
  3081. xff_ens3(7)=mconv(i,1)
  3082. xff_ens3(8)=mconv(i,1)
  3083. xff_ens3(9)=mconv(i,1)
  3084. if(ens4.gt.1)then
  3085. do ne=2,ens4
  3086. if (mconv(i,ne).gt.xff_ens3(7))xff_ens3(7)=mconv(i,ne)
  3087. enddo
  3088. do ne=2,ens4
  3089. if (mconv(i,ne).lt.xff_ens3(8))xff_ens3(8)=mconv(i,ne)
  3090. enddo
  3091. do ne=2,ens4
  3092. xff_ens3(9)=xff_ens3(9)+mconv(i,ne)
  3093. enddo
  3094. xff_ens3(9)=xff_ens3(9)/fens4
  3095. endif
  3096. if(high_resolution.eq.1)then
  3097. xff_ens3(7)=xff_ens3(9)
  3098. xff_ens3(8)=xff_ens3(9)
  3099. xff_ens3(15)=xff_ens3(9)
  3100. endif
  3101. !
  3102. if(high_resolution.eq.0)then
  3103. if(irandom.eq.1)then
  3104. seed(1)=i
  3105. call random_seed (PUT=seed)
  3106. call random_number (xxx)
  3107. ixxx=min(ens4,max(1,int(fens4*xxx+1.e-8)))
  3108. xff_ens3(15)=mconv(i,ixxx)
  3109. else
  3110. xff_ens3(15)=mconv(i,1)
  3111. endif
  3112. endif
  3113. !
  3114. !--- more like Fritsch Chappel or Kain Fritsch (plus triggers)
  3115. !
  3116. xff_ens3(10)=A_AVE/(60.*40.)
  3117. xff_ens3(11)=AA1(I)/(60.*40.)
  3118. if(irandom.eq.1)then
  3119. seed(1)=i
  3120. call random_seed (PUT=seed)
  3121. call random_number (xxx)
  3122. ixxx=min(ens4,max(1,int(fens4*xxx+1.e-8)))
  3123. xff_ens3(12)=AXX(I,ixxx)/(60.*40.)
  3124. else
  3125. xff_ens3(12)=AA1(I)/(60.*40.)
  3126. endif
  3127. if(high_resolution.eq.1)then
  3128. xff_ens3(11)=xff_ens3(10)
  3129. xff_ens3(12)=xff_ens3(10)
  3130. endif
  3131. !
  3132. !--- more original Arakawa-Schubert (climatologic value of aa0)
  3133. !
  3134. ! edt_out(i,j)=xff0
  3135. if(icoic.eq.0)then
  3136. if(xff0.lt.0.)then
  3137. xff_ens3(1)=0.
  3138. xff_ens3(2)=0.
  3139. xff_ens3(3)=0.
  3140. xff_ens3(13)=0.
  3141. xff_ens3(10)=0.
  3142. xff_ens3(11)=0.
  3143. xff_ens3(12)=0.
  3144. endif
  3145. endif
  3146. do nens=1,maxens
  3147. XK(nens)=(XAA0(I,nens)-AA1(I))/MBDT(2)
  3148. if(xk(nens).le.0.and.xk(nens).gt.-1.e-6) &
  3149. xk(nens)=-1.e-6
  3150. if(xk(nens).gt.0.and.xk(nens).lt.1.e-6) &
  3151. xk(nens)=1.e-6
  3152. enddo
  3153. !
  3154. !--- add up all ensembles
  3155. !
  3156. do 350 ne=1,maxens
  3157. !
  3158. !--- for every xk, we have maxens3 xffs
  3159. !--- iens is from outermost ensemble (most expensive!
  3160. !
  3161. !--- iedt (maxens2 belongs to it)
  3162. !--- is from second, next outermost, not so expensive
  3163. !
  3164. !--- so, for every outermost loop, we have maxens*maxens2*3
  3165. !--- ensembles!!! nall would be 0, if everything is on first
  3166. !--- loop index, then ne would start counting, then iedt, then iens....
  3167. !
  3168. iresult=0
  3169. iresultd=0
  3170. iresulte=0
  3171. nall=(iens-1)*maxens3*maxens*maxens2 &
  3172. +(iedt-1)*maxens*maxens3 &
  3173. +(ne-1)*maxens3
  3174. !
  3175. ! over water, enfor!e small cap for some of the closures
  3176. !
  3177. if(xland(i).lt.0.1)then
  3178. if(ierr2(i).gt.0.or.ierr3(i).gt.0)then
  3179. xff_ens3(1) =0.
  3180. massfln(i,j,nall+1)=0.
  3181. xff_ens3(2) =0.
  3182. massfln(i,j,nall+2)=0.
  3183. xff_ens3(3) =0.
  3184. massfln(i,j,nall+3)=0.
  3185. xff_ens3(10) =0.
  3186. massfln(i,j,nall+10)=0.
  3187. xff_ens3(11) =0.
  3188. massfln(i,j,nall+11)=0.
  3189. xff_ens3(12) =0.
  3190. massfln(i,j,nall+12)=0.
  3191. xff_ens3(7) =0.
  3192. massfln(i,j,nall+7)=0.
  3193. xff_ens3(8) =0.
  3194. massfln(i,j,nall+8)=0.
  3195. xff_ens3(9) =0.
  3196. massfln(i,j,nall+9)=0.
  3197. xff_ens3(13) =0.
  3198. massfln(i,j,nall+13)=0.
  3199. xff_ens3(15) =0.
  3200. massfln(i,j,nall+15)=0.
  3201. endif
  3202. endif
  3203. !
  3204. ! end water treatment
  3205. !
  3206. !
  3207. !--- check for upwind convection
  3208. ! iresult=0
  3209. massfld=0.
  3210. ! call cup_direction2(i,j,dir,iact_old_gr, &
  3211. ! massflx,iresult,1, &
  3212. ! massfld, &
  3213. ! itf,jtf,ktf, &
  3214. ! ims,ime, jms,jme, kms,kme, &
  3215. ! its,ite, jts,jte, kts,kte )
  3216. ! if(i.eq.ipr.and.j.eq.jpr.and.iedt.eq.1.and.ne.eq.1)then
  3217. ! if(iedt.eq.1.and.ne.eq.1)then
  3218. ! print *,massfld,ne,iedt,iens
  3219. ! print *,xk(ne),xff_ens3(1),xff_ens3(2),xff_ens3(3)
  3220. ! endif
  3221. ! print *,i,j,massfld,aa0(i),aa1(i)
  3222. IF(XK(ne).lt.0.and.xff0.gt.0.)iresultd=1
  3223. iresulte=max(iresult,iresultd)
  3224. iresulte=1
  3225. if(iresulte.eq.1)then
  3226. !
  3227. !--- special treatment for stability closures
  3228. !
  3229. if(xff0.ge.0.)then
  3230. xf_ens(i,j,nall+1)=massfld
  3231. xf_ens(i,j,nall+2)=massfld
  3232. xf_ens(i,j,nall+3)=massfld
  3233. xf_ens(i,j,nall+13)=massfld
  3234. if(xff_ens3(1).gt.0)xf_ens(i,j,nall+1)=max(0.,-xff_ens3(1)/xk(ne)) &
  3235. +massfld
  3236. if(xff_ens3(2).gt.0)xf_ens(i,j,nall+2)=max(0.,-xff_ens3(2)/xk(ne)) &
  3237. +massfld
  3238. if(xff_ens3(3).gt.0)xf_ens(i,j,nall+3)=max(0.,-xff_ens3(3)/xk(ne)) &
  3239. +massfld
  3240. if(xff_ens3(13).gt.0)xf_ens(i,j,nall+13)=max(0.,-xff_ens3(13)/xk(ne)) &
  3241. +massfld
  3242. ! endif
  3243. else
  3244. xf_ens(i,j,nall+1)=massfld
  3245. xf_ens(i,j,nall+2)=massfld
  3246. xf_ens(i,j,nall+3)=massfld
  3247. xf_ens(i,j,nall+13)=massfld
  3248. endif
  3249. !
  3250. !--- if iresult.eq.1, following independent of xff0
  3251. !
  3252. xf_ens(i,j,nall+4)=max(0.,xff_ens3(4) &
  3253. +massfld)
  3254. xf_ens(i,j,nall+5)=max(0.,xff_ens3(5) &
  3255. +massfld)
  3256. xf_ens(i,j,nall+6)=max(0.,xff_ens3(6) &
  3257. +massfld)
  3258. xf_ens(i,j,nall+14)=max(0.,xff_ens3(14) &
  3259. +massfld)
  3260. a1=max(1.e-3,pr_ens(i,j,nall+7))
  3261. xf_ens(i,j,nall+7)=max(0.,xff_ens3(7) &
  3262. /a1)
  3263. a1=max(1.e-3,pr_ens(i,j,nall+8))
  3264. xf_ens(i,j,nall+8)=max(0.,xff_ens3(8) &
  3265. /a1)
  3266. a1=max(1.e-3,pr_ens(i,j,nall+9))
  3267. xf_ens(i,j,nall+9)=max(0.,xff_ens3(9) &
  3268. /a1)
  3269. a1=max(1.e-3,pr_ens(i,j,nall+15))
  3270. xf_ens(i,j,nall+15)=max(0.,xff_ens3(15) &
  3271. /a1)
  3272. if(XK(ne).lt.0.)then
  3273. xf_ens(i,j,nall+10)=max(0., &
  3274. -xff_ens3(10)/xk(ne)) &
  3275. +massfld
  3276. xf_ens(i,j,nall+11)=max(0., &
  3277. -xff_ens3(11)/xk(ne)) &
  3278. +massfld
  3279. xf_ens(i,j,nall+12)=max(0., &
  3280. -xff_ens3(12)/xk(ne)) &
  3281. +massfld
  3282. else
  3283. xf_ens(i,j,nall+10)=massfld
  3284. xf_ens(i,j,nall+11)=massfld
  3285. xf_ens(i,j,nall+12)=massfld
  3286. endif
  3287. if(icoic.ge.1)then
  3288. closure_n(i)=0.
  3289. xf_ens(i,j,nall+1)=xf_ens(i,j,nall+icoic)
  3290. xf_ens(i,j,nall+2)=xf_ens(i,j,nall+icoic)
  3291. xf_ens(i,j,nall+3)=xf_ens(i,j,nall+icoic)
  3292. xf_ens(i,j,nall+4)=xf_ens(i,j,nall+icoic)
  3293. xf_ens(i,j,nall+5)=xf_ens(i,j,nall+icoic)
  3294. xf_ens(i,j,nall+6)=xf_ens(i,j,nall+icoic)
  3295. xf_ens(i,j,nall+7)=xf_ens(i,j,nall+icoic)
  3296. xf_ens(i,j,nall+8)=xf_ens(i,j,nall+icoic)
  3297. xf_ens(i,j,nall+9)=xf_ens(i,j,nall+icoic)
  3298. xf_ens(i,j,nall+10)=xf_ens(i,j,nall+icoic)
  3299. xf_ens(i,j,nall+11)=xf_ens(i,j,nall+icoic)
  3300. xf_ens(i,j,nall+12)=xf_ens(i,j,nall+icoic)
  3301. xf_ens(i,j,nall+13)=xf_ens(i,j,nall+icoic)
  3302. xf_ens(i,j,nall+14)=xf_ens(i,j,nall+icoic)
  3303. xf_ens(i,j,nall+15)=xf_ens(i,j,nall+icoic)
  3304. xf_ens(i,j,nall+16)=xf_ens(i,j,nall+icoic)
  3305. endif
  3306. !
  3307. ! 16 is a randon pick from the oher 15
  3308. !
  3309. if(irandom.eq.1)then
  3310. call random_number (xxx)
  3311. ixxx=min(15,max(1,int(15.*xxx+1.e-8)))
  3312. xf_ens(i,j,nall+16)=xf_ens(i,j,nall+ixxx)
  3313. else
  3314. xf_ens(i,j,nall+16)=xf_ens(i,j,nall+1)
  3315. endif
  3316. !
  3317. !
  3318. !--- store new for next time step
  3319. !
  3320. do nens3=1,maxens3
  3321. massfln(i,j,nall+nens3)=edt(i) &
  3322. *xf_ens(i,j,nall+nens3)
  3323. massfln(i,j,nall+nens3)=max(0., &
  3324. massfln(i,j,nall+nens3))
  3325. enddo
  3326. !
  3327. !
  3328. !--- do some more on the caps!!! ne=1 for 175, ne=2 for 100,....
  3329. !
  3330. ! do not care for caps here for closure groups 1 and 5,
  3331. ! they are fine, do not turn them off here
  3332. !
  3333. !
  3334. if(ne.eq.2.and.ierr2(i).gt.0)then
  3335. xf_ens(i,j,nall+1) =0.
  3336. xf_ens(i,j,nall+2) =0.
  3337. xf_ens(i,j,nall+3) =0.
  3338. xf_ens(i,j,nall+4) =0.
  3339. xf_ens(i,j,nall+5) =0.
  3340. xf_ens(i,j,nall+6) =0.
  3341. xf_ens(i,j,nall+7) =0.
  3342. xf_ens(i,j,nall+8) =0.
  3343. xf_ens(i,j,nall+9) =0.
  3344. xf_ens(i,j,nall+10)=0.
  3345. xf_ens(i,j,nall+11)=0.
  3346. xf_ens(i,j,nall+12)=0.
  3347. xf_ens(i,j,nall+13)=0.
  3348. xf_ens(i,j,nall+14)=0.
  3349. xf_ens(i,j,nall+15)=0.
  3350. xf_ens(i,j,nall+16)=0.
  3351. massfln(i,j,nall+1)=0.
  3352. massfln(i,j,nall+2)=0.
  3353. massfln(i,j,nall+3)=0.
  3354. massfln(i,j,nall+4)=0.
  3355. massfln(i,j,nall+5)=0.
  3356. massfln(i,j,nall+6)=0.
  3357. massfln(i,j,nall+7)=0.
  3358. massfln(i,j,nall+8)=0.
  3359. massfln(i,j,nall+9)=0.
  3360. massfln(i,j,nall+10)=0.
  3361. massfln(i,j,nall+11)=0.
  3362. massfln(i,j,nall+12)=0.
  3363. massfln(i,j,nall+13)=0.
  3364. massfln(i,j,nall+14)=0.
  3365. massfln(i,j,nall+15)=0.
  3366. massfln(i,j,nall+16)=0.
  3367. endif
  3368. if(ne.eq.3.and.ierr3(i).gt.0)then
  3369. xf_ens(i,j,nall+1) =0.
  3370. xf_ens(i,j,nall+2) =0.
  3371. xf_ens(i,j,nall+3) =0.
  3372. xf_ens(i,j,nall+4) =0.
  3373. xf_ens(i,j,nall+5) =0.
  3374. xf_ens(i,j,nall+6) =0.
  3375. xf_ens(i,j,nall+7) =0.
  3376. xf_ens(i,j,nall+8) =0.
  3377. xf_ens(i,j,nall+9) =0.
  3378. xf_ens(i,j,nall+10)=0.
  3379. xf_ens(i,j,nall+11)=0.
  3380. xf_ens(i,j,nall+12)=0.
  3381. xf_ens(i,j,nall+13)=0.
  3382. xf_ens(i,j,nall+14)=0.
  3383. xf_ens(i,j,nall+15)=0.
  3384. xf_ens(i,j,nall+16)=0.
  3385. massfln(i,j,nall+1)=0.
  3386. massfln(i,j,nall+2)=0.
  3387. massfln(i,j,nall+3)=0.
  3388. massfln(i,j,nall+4)=0.
  3389. massfln(i,j,nall+5)=0.
  3390. massfln(i,j,nall+6)=0.
  3391. massfln(i,j,nall+7)=0.
  3392. massfln(i,j,nall+8)=0.
  3393. massfln(i,j,nall+9)=0.
  3394. massfln(i,j,nall+10)=0.
  3395. massfln(i,j,nall+11)=0.
  3396. massfln(i,j,nall+12)=0.
  3397. massfln(i,j,nall+13)=0.
  3398. massfln(i,j,nall+14)=0.
  3399. massfln(i,j,nall+15)=0.
  3400. massfln(i,j,nall+16)=0.
  3401. endif
  3402. endif
  3403. 350 continue
  3404. ! ne=1, cap=175
  3405. !
  3406. nall=(iens-1)*maxens3*maxens*maxens2 &
  3407. +(iedt-1)*maxens*maxens3
  3408. ! ne=2, cap=100
  3409. !
  3410. nall2=(iens-1)*maxens3*maxens*maxens2 &
  3411. +(iedt-1)*maxens*maxens3 &
  3412. +(2-1)*maxens3
  3413. xf_ens(i,j,nall+4) = xf_ens(i,j,nall2+4)
  3414. xf_ens(i,j,nall+5) =xf_ens(i,j,nall2+5)
  3415. xf_ens(i,j,nall+6) =xf_ens(i,j,nall2+6)
  3416. xf_ens(i,j,nall+14) =xf_ens(i,j,nall2+14)
  3417. xf_ens(i,j,nall+7) =xf_ens(i,j,nall2+7)
  3418. xf_ens(i,j,nall+8) =xf_ens(i,j,nall2+8)
  3419. xf_ens(i,j,nall+9) =xf_ens(i,j,nall2+9)
  3420. xf_ens(i,j,nall+15) =xf_ens(i,j,nall2+15)
  3421. xf_ens(i,j,nall+10)=xf_ens(i,j,nall2+10)
  3422. xf_ens(i,j,nall+11)=xf_ens(i,j,nall2+11)
  3423. xf_ens(i,j,nall+12)=xf_ens(i,j,nall2+12)
  3424. go to 100
  3425. endif
  3426. elseif(ierr(i).ne.20.and.ierr(i).ne.0)then
  3427. do n=1,ensdim
  3428. xf_ens(i,j,n)=0.
  3429. massfln(i,j,n)=0.
  3430. enddo
  3431. endif
  3432. 100 continue
  3433. END SUBROUTINE cup_forcing_ens_3d
  3434. SUBROUTINE cup_kbcon(cap_inc,iloop,k22,kbcon,he_cup,hes_cup, &
  3435. ierr,kbmax,p_cup,cap_max, &
  3436. itf,jtf,ktf, &
  3437. its,ite, jts,jte, kts,kte )
  3438. IMPLICIT NONE
  3439. !
  3440. ! only local wrf dimensions are need as of now in this routine
  3441. integer &
  3442. ,intent (in ) :: &
  3443. itf,jtf,ktf, &
  3444. its,ite, jts,jte, kts,kte
  3445. !
  3446. !
  3447. !
  3448. ! ierr error value, maybe modified in this routine
  3449. !
  3450. real, dimension (its:ite,kts:kte) &
  3451. ,intent (in ) :: &
  3452. he_cup,hes_cup,p_cup
  3453. real, dimension (its:ite) &
  3454. ,intent (in ) :: &
  3455. cap_max,cap_inc
  3456. integer, dimension (its:ite) &
  3457. ,intent (in ) :: &
  3458. kbmax
  3459. integer, dimension (its:ite) &
  3460. ,intent (inout) :: &
  3461. kbcon,k22,ierr
  3462. integer &
  3463. ,intent (in ) :: &
  3464. iloop
  3465. !
  3466. ! local variables in this routine
  3467. !
  3468. integer :: &
  3469. i,k
  3470. real :: &
  3471. pbcdif,plus,hetest
  3472. !
  3473. !--- DETERMINE THE LEVEL OF CONVECTIVE CLOUD BASE - KBCON
  3474. !
  3475. DO 27 i=its,itf
  3476. kbcon(i)=1
  3477. IF(ierr(I).ne.0)GO TO 27
  3478. KBCON(I)=K22(I)
  3479. GO TO 32
  3480. 31 CONTINUE
  3481. KBCON(I)=KBCON(I)+1
  3482. IF(KBCON(I).GT.KBMAX(i)+2)THEN
  3483. if(iloop.ne.4)ierr(i)=3
  3484. ! if(iloop.lt.4)ierr(i)=997
  3485. GO TO 27
  3486. ENDIF
  3487. 32 CONTINUE
  3488. hetest=HE_cup(I,K22(I))
  3489. if(iloop.eq.5)then
  3490. do k=1,k22(i)
  3491. hetest=max(hetest,he_cup(i,k))
  3492. enddo
  3493. endif
  3494. IF(HETEST.LT.HES_cup(I,KBCON(I)))GO TO 31
  3495. ! cloud base pressure and max moist static energy pressure
  3496. ! i.e., the depth (in mb) of the layer of negative buoyancy
  3497. if(KBCON(I)-K22(I).eq.1)go to 27
  3498. PBCDIF=-P_cup(I,KBCON(I))+P_cup(I,K22(I))
  3499. plus=max(25.,cap_max(i)-float(iloop-1)*cap_inc(i))
  3500. if(iloop.eq.4)plus=cap_max(i)
  3501. !
  3502. ! for shallow convection, if cap_max is greater than 25, it is the pressure at pbltop
  3503. if(iloop.eq.5)plus=25.
  3504. if(iloop.eq.5.and.cap_max(i).gt.25)pbcdif=-P_cup(I,KBCON(I))+cap_max(i)
  3505. IF(PBCDIF.GT.plus)THEN
  3506. K22(I)=K22(I)+1
  3507. KBCON(I)=K22(I)
  3508. GO TO 32
  3509. ENDIF
  3510. 27 CONTINUE
  3511. END SUBROUTINE cup_kbcon
  3512. SUBROUTINE cup_ktop(ilo,dby,kbcon,ktop,ierr, &
  3513. itf,jtf,ktf, &
  3514. its,ite, jts,jte, kts,kte )
  3515. IMPLICIT NONE
  3516. !
  3517. ! on input
  3518. !
  3519. ! only local wrf dimensions are need as of now in this routine
  3520. integer &
  3521. ,intent (in ) :: &
  3522. itf,jtf,ktf, &
  3523. its,ite, jts,jte, kts,kte
  3524. ! dby = buoancy term
  3525. ! ktop = cloud top (output)
  3526. ! ilo = flag
  3527. ! ierr error value, maybe modified in this routine
  3528. !
  3529. real, dimension (its:ite,kts:kte) &
  3530. ,intent (inout) :: &
  3531. dby
  3532. integer, dimension (its:ite) &
  3533. ,intent (in ) :: &
  3534. kbcon
  3535. integer &
  3536. ,intent (in ) :: &
  3537. ilo
  3538. integer, dimension (its:ite) &
  3539. ,intent (out ) :: &
  3540. ktop
  3541. integer, dimension (its:ite) &
  3542. ,intent (inout) :: &
  3543. ierr
  3544. !
  3545. ! local variables in this routine
  3546. !
  3547. integer :: &
  3548. i,k
  3549. !
  3550. DO 42 i=its,itf
  3551. ktop(i)=1
  3552. IF(ierr(I).EQ.0)then
  3553. DO 40 K=KBCON(I)+1,ktf-1
  3554. IF(DBY(I,K).LE.0.)THEN
  3555. KTOP(I)=K-1
  3556. GO TO 41
  3557. ENDIF
  3558. 40 CONTINUE
  3559. if(ilo.eq.1)ierr(i)=5
  3560. ! if(ilo.eq.2)ierr(i)=998
  3561. GO TO 42
  3562. 41 CONTINUE
  3563. do k=ktop(i)+1,ktf
  3564. dby(i,k)=0.
  3565. enddo
  3566. endif
  3567. 42 CONTINUE
  3568. END SUBROUTINE cup_ktop
  3569. SUBROUTINE cup_MAXIMI(ARRAY,KS,KE,MAXX,ierr, &
  3570. itf,jtf,ktf, &
  3571. its,ite, jts,jte, kts,kte )
  3572. IMPLICIT NONE
  3573. !
  3574. ! on input
  3575. !
  3576. ! only local wrf dimensions are need as of now in this routine
  3577. integer &
  3578. ,intent (in ) :: &
  3579. itf,jtf,ktf, &
  3580. its,ite, jts,jte, kts,kte
  3581. ! array input array
  3582. ! x output array with return values
  3583. ! kt output array of levels
  3584. ! ks,kend check-range
  3585. real, dimension (its:ite,kts:kte) &
  3586. ,intent (in ) :: &
  3587. array
  3588. integer, dimension (its:ite) &
  3589. ,intent (in ) :: &
  3590. ierr,ke
  3591. integer &
  3592. ,intent (in ) :: &
  3593. ks
  3594. integer, dimension (its:ite) &
  3595. ,intent (out ) :: &
  3596. maxx
  3597. real, dimension (its:ite) :: &
  3598. x
  3599. real :: &
  3600. xar
  3601. integer :: &
  3602. i,k
  3603. DO 200 i=its,itf
  3604. MAXX(I)=KS
  3605. if(ierr(i).eq.0)then
  3606. X(I)=ARRAY(I,KS)
  3607. !
  3608. DO 100 K=KS,KE(i)
  3609. XAR=ARRAY(I,K)
  3610. IF(XAR.GE.X(I)) THEN
  3611. X(I)=XAR
  3612. MAXX(I)=K
  3613. ENDIF
  3614. 100 CONTINUE
  3615. endif
  3616. 200 CONTINUE
  3617. END SUBROUTINE cup_MAXIMI
  3618. SUBROUTINE cup_minimi(ARRAY,KS,KEND,KT,ierr, &
  3619. itf,jtf,ktf, &
  3620. its,ite, jts,jte, kts,kte )
  3621. IMPLICIT NONE
  3622. !
  3623. ! on input
  3624. !
  3625. ! only local wrf dimensions are need as of now in this routine
  3626. integer &
  3627. ,intent (in ) :: &
  3628. itf,jtf,ktf, &
  3629. its,ite, jts,jte, kts,kte
  3630. ! array input array
  3631. ! x output array with return values
  3632. ! kt output array of levels
  3633. ! ks,kend check-range
  3634. real, dimension (its:ite,kts:kte) &
  3635. ,intent (in ) :: &
  3636. array
  3637. integer, dimension (its:ite) &
  3638. ,intent (in ) :: &
  3639. ierr,ks,kend
  3640. integer, dimension (its:ite) &
  3641. ,intent (out ) :: &
  3642. kt
  3643. real, dimension (its:ite) :: &
  3644. x
  3645. integer :: &
  3646. i,k,kstop
  3647. DO 200 i=its,itf
  3648. KT(I)=KS(I)
  3649. if(ierr(i).eq.0)then
  3650. X(I)=ARRAY(I,KS(I))
  3651. KSTOP=MAX(KS(I)+1,KEND(I))
  3652. !
  3653. DO 100 K=KS(I)+1,KSTOP
  3654. IF(ARRAY(I,K).LT.X(I)) THEN
  3655. X(I)=ARRAY(I,K)
  3656. KT(I)=K
  3657. ENDIF
  3658. 100 CONTINUE
  3659. endif
  3660. 200 CONTINUE
  3661. END SUBROUTINE cup_MINIMI
  3662. SUBROUTINE cup_output_ens_3d(xf_ens,ierr,dellat,dellaq,dellaqc, &
  3663. subt_ens,subq_ens,subt,subq,outtem,outq,outqc, &
  3664. zu,sub_mas,pre,pw,xmb,ktop, &
  3665. j,name,nx,nx2,iens,ierr2,ierr3,pr_ens, &
  3666. maxens3,ensdim,massfln, &
  3667. APR_GR,APR_W,APR_MC,APR_ST,APR_AS, &
  3668. APR_CAPMA,APR_CAPME,APR_CAPMI,closure_n,xland1, &
  3669. itf,jtf,ktf, &
  3670. its,ite, jts,jte, kts,kte)
  3671. IMPLICIT NONE
  3672. !
  3673. ! on input
  3674. !
  3675. ! only local wrf dimensions are need as of now in this routine
  3676. integer &
  3677. ,intent (in ) :: &
  3678. itf,jtf,ktf, &
  3679. its,ite, jts,jte, kts,kte
  3680. integer, intent (in ) :: &
  3681. j,ensdim,nx,nx2,iens,maxens3
  3682. ! xf_ens = ensemble mass fluxes
  3683. ! pr_ens = precipitation ensembles
  3684. ! dellat = change of temperature per unit mass flux of cloud ensemble
  3685. ! dellaq = change of q per unit mass flux of cloud ensemble
  3686. ! dellaqc = change of qc per unit mass flux of cloud ensemble
  3687. ! outtem = output temp tendency (per s)
  3688. ! outq = output q tendency (per s)
  3689. ! outqc = output qc tendency (per s)
  3690. ! pre = output precip
  3691. ! xmb = total base mass flux
  3692. ! xfac1 = correction factor
  3693. ! pw = pw -epsilon*pd (ensemble dependent)
  3694. ! ierr error value, maybe modified in this routine
  3695. !
  3696. real, dimension (its:ite,jts:jte,1:ensdim) &
  3697. ,intent (inout) :: &
  3698. xf_ens,pr_ens,massfln
  3699. real, dimension (its:ite,jts:jte) &
  3700. ,intent (inout) :: &
  3701. APR_GR,APR_W,APR_MC,APR_ST,APR_AS,APR_CAPMA, &
  3702. APR_CAPME,APR_CAPMI
  3703. real, dimension (its:ite,kts:kte) &
  3704. ,intent (out ) :: &
  3705. outtem,outq,outqc,subt,subq,sub_mas
  3706. real, dimension (its:ite,kts:kte) &
  3707. ,intent (in ) :: &
  3708. zu
  3709. real, dimension (its:ite) &
  3710. ,intent (out ) :: &
  3711. pre,xmb
  3712. real, dimension (its:ite) &
  3713. ,intent (inout ) :: &
  3714. closure_n,xland1
  3715. real, dimension (its:ite,kts:kte,1:nx) &
  3716. ,intent (in ) :: &
  3717. subt_ens,subq_ens,dellat,dellaqc,dellaq,pw
  3718. integer, dimension (its:ite) &
  3719. ,intent (in ) :: &
  3720. ktop
  3721. integer, dimension (its:ite) &
  3722. ,intent (inout) :: &
  3723. ierr,ierr2,ierr3
  3724. !
  3725. ! local variables in this routine
  3726. !
  3727. integer :: &
  3728. i,k,n,ncount
  3729. real :: &
  3730. outtes,ddtes,dtt,dtq,dtqc,dtpw,tuning,prerate,clos_wei,xmbhelp
  3731. real :: &
  3732. dtts,dtqs
  3733. real, dimension (its:ite) :: &
  3734. xfac1,xfac2
  3735. real, dimension (its:ite):: &
  3736. xmb_ske,xmb_ave,xmb_std,xmb_cur,xmbweight
  3737. real, dimension (its:ite):: &
  3738. pr_ske,pr_ave,pr_std,pr_cur
  3739. real, dimension (its:ite,jts:jte):: &
  3740. pr_gr,pr_w,pr_mc,pr_st,pr_as,pr_capma, &
  3741. pr_capme,pr_capmi
  3742. real, dimension (5) :: weight,wm,wm1,wm2,wm3
  3743. real, dimension (its:ite,5) :: xmb_w
  3744. !
  3745. character *(*), intent (in) :: &
  3746. name
  3747. !
  3748. weight(1) = -999. !this will turn off weights
  3749. wm(1)=-999.
  3750. tuning=0.
  3751. !
  3752. !
  3753. DO k=kts,ktf
  3754. do i=its,itf
  3755. outtem(i,k)=0.
  3756. outq(i,k)=0.
  3757. outqc(i,k)=0.
  3758. subt(i,k)=0.
  3759. subq(i,k)=0.
  3760. sub_mas(i,k)=0.
  3761. enddo
  3762. enddo
  3763. do i=its,itf
  3764. pre(i)=0.
  3765. xmb(i)=0.
  3766. xfac1(i)=0.
  3767. xfac2(i)=0.
  3768. xmbweight(i)=1.
  3769. enddo
  3770. do i=its,itf
  3771. IF(ierr(i).eq.0)then
  3772. do n=(iens-1)*nx*nx2*maxens3+1,iens*nx*nx2*maxens3
  3773. if(pr_ens(i,j,n).le.0.)then
  3774. xf_ens(i,j,n)=0.
  3775. endif
  3776. enddo
  3777. endif
  3778. enddo
  3779. !
  3780. !--- calculate ensemble average mass fluxes
  3781. !
  3782. call massflx_stats(xf_ens,ensdim,nx2,nx,maxens3, &
  3783. xmb_ave,xmb_std,xmb_cur,xmb_ske,j,ierr,1, &
  3784. APR_GR,APR_W,APR_MC,APR_ST,APR_AS, &
  3785. APR_CAPMA,APR_CAPME,APR_CAPMI, &
  3786. pr_gr,pr_w,pr_mc,pr_st,pr_as, &
  3787. pr_capma,pr_capme,pr_capmi, &
  3788. itf,jtf,ktf, &
  3789. its,ite, jts,jte, kts,kte )
  3790. xmb_w=0.
  3791. call massflx_stats(pr_ens,ensdim,nx2,nx,maxens3, &
  3792. pr_ave,pr_std,pr_cur,pr_ske,j,ierr,2, &
  3793. APR_GR,APR_W,APR_MC,APR_ST,APR_AS, &
  3794. APR_CAPMA,APR_CAPME,APR_CAPMI, &
  3795. pr_gr,pr_w,pr_mc,pr_st,pr_as, &
  3796. pr_capma,pr_capme,pr_capmi, &
  3797. itf,jtf,ktf, &
  3798. its,ite, jts,jte, kts,kte )
  3799. !
  3800. !-- now do feedback
  3801. !
  3802. ddtes=100.
  3803. do i=its,itf
  3804. if(ierr(i).eq.0)then
  3805. if(xmb_ave(i).le.0.)then
  3806. ierr(i)=13
  3807. xmb_ave(i)=0.
  3808. endif
  3809. xmb(i)=max(.1*xmb_ave(i),xmb_ave(i)-tuning*xmb_std(i))
  3810. ! --- Now use proper count of how many closures were actually
  3811. ! used in cup_forcing_ens (including screening of some
  3812. ! closures over water) to properly normalize xmb
  3813. clos_wei=16./max(1.,closure_n(i))
  3814. if (xland1(i).lt.0.5)xmb(i)=xmb(i)*clos_wei
  3815. if(xmb(i).eq.0.)then
  3816. ierr(i)=19
  3817. endif
  3818. if(xmb(i).gt.100.)then
  3819. ierr(i)=19
  3820. endif
  3821. xfac1(i)=xmb(i)
  3822. xfac2(i)=xmb(i)
  3823. endif
  3824. ! if(weight(1).lt.-100.)xfac1(i)=xmb_ave(i)
  3825. ! if(weight(1).lt.-100.)xfac2(i)=xmb_ave(i)
  3826. ENDDO
  3827. DO k=kts,ktf
  3828. do i=its,itf
  3829. dtt=0.
  3830. dtts=0.
  3831. dtq=0.
  3832. dtqs=0.
  3833. dtqc=0.
  3834. dtpw=0.
  3835. IF(ierr(i).eq.0.and.k.le.ktop(i))then
  3836. do n=1,nx
  3837. dtt=dtt+dellat(i,k,n)
  3838. dtts=dtts+subt_ens(i,k,n)
  3839. dtq=dtq+dellaq(i,k,n)
  3840. dtqs=dtqs+subq_ens(i,k,n)
  3841. dtqc=dtqc+dellaqc(i,k,n)
  3842. dtpw=dtpw+pw(i,k,n)
  3843. enddo
  3844. OUTTEM(I,K)=XMB(I)*dtt/float(nx)
  3845. SUBT(I,K)=XMB(I)*dtts/float(nx)
  3846. OUTQ(I,K)=XMB(I)*dtq/float(nx)
  3847. SUBQ(I,K)=XMB(I)*dtqs/float(nx)
  3848. OUTQC(I,K)=XMB(I)*dtqc/float(nx)
  3849. PRE(I)=PRE(I)+XMB(I)*dtpw/float(nx)
  3850. sub_mas(i,k)=zu(i,k)*xmb(i)
  3851. endif
  3852. enddo
  3853. enddo
  3854. do i=its,itf
  3855. if(ierr(i).eq.0)then
  3856. do k=(iens-1)*nx*nx2*maxens3+1,iens*nx*nx2*maxens3
  3857. massfln(i,j,k)=massfln(i,j,k)*xfac1(i)
  3858. xf_ens(i,j,k)=xf_ens(i,j,k)*xfac1(i)
  3859. enddo
  3860. endif
  3861. ENDDO
  3862. END SUBROUTINE cup_output_ens_3d
  3863. SUBROUTINE cup_up_aa0(aa0,z,zu,dby,GAMMA_CUP,t_cup, &
  3864. kbcon,ktop,ierr, &
  3865. itf,jtf,ktf, &
  3866. its,ite, jts,jte, kts,kte )
  3867. IMPLICIT NONE
  3868. !
  3869. ! on input
  3870. !
  3871. ! only local wrf dimensions are need as of now in this routine
  3872. integer &
  3873. ,intent (in ) :: &
  3874. itf,jtf,ktf, &
  3875. its,ite, jts,jte, kts,kte
  3876. ! aa0 cloud work function
  3877. ! gamma_cup = gamma on model cloud levels
  3878. ! t_cup = temperature (Kelvin) on model cloud levels
  3879. ! dby = buoancy term
  3880. ! zu= normalized updraft mass flux
  3881. ! z = heights of model levels
  3882. ! ierr error value, maybe modified in this routine
  3883. !
  3884. real, dimension (its:ite,kts:kte) &
  3885. ,intent (in ) :: &
  3886. z,zu,gamma_cup,t_cup,dby
  3887. integer, dimension (its:ite) &
  3888. ,intent (in ) :: &
  3889. kbcon,ktop
  3890. !
  3891. ! input and output
  3892. !
  3893. integer, dimension (its:ite) &
  3894. ,intent (inout) :: &
  3895. ierr
  3896. real, dimension (its:ite) &
  3897. ,intent (out ) :: &
  3898. aa0
  3899. !
  3900. ! local variables in this routine
  3901. !
  3902. integer :: &
  3903. i,k
  3904. real :: &
  3905. dz,da
  3906. !
  3907. do i=its,itf
  3908. aa0(i)=0.
  3909. enddo
  3910. DO 100 k=kts+1,ktf
  3911. DO 100 i=its,itf
  3912. IF(ierr(i).ne.0)GO TO 100
  3913. IF(K.LE.KBCON(I))GO TO 100
  3914. IF(K.Gt.KTOP(I))GO TO 100
  3915. DZ=Z(I,K)-Z(I,K-1)
  3916. da=zu(i,k)*DZ*(9.81/(1004.*( &
  3917. (T_cup(I,K)))))*DBY(I,K-1)/ &
  3918. (1.+GAMMA_CUP(I,K))
  3919. IF(K.eq.KTOP(I).and.da.le.0.)go to 100
  3920. AA0(I)=AA0(I)+da
  3921. if(aa0(i).lt.0.)aa0(i)=0.
  3922. 100 continue
  3923. END SUBROUTINE cup_up_aa0
  3924. SUBROUTINE cup_up_he(k22,hkb,z_cup,cd,entr,he_cup,hc, &
  3925. kbcon,ierr,dby,he,hes_cup,name, &
  3926. itf,jtf,ktf, &
  3927. its,ite, jts,jte, kts,kte )
  3928. IMPLICIT NONE
  3929. !
  3930. ! on input
  3931. !
  3932. ! only local wrf dimensions are need as of now in this routine
  3933. integer &
  3934. ,intent (in ) :: &
  3935. itf,jtf,ktf, &
  3936. its,ite, jts,jte, kts,kte
  3937. character *(*), intent (in) :: &
  3938. name
  3939. ! hc = cloud moist static energy
  3940. ! hkb = moist static energy at originating level
  3941. ! he = moist static energy on model levels
  3942. ! he_cup = moist static energy on model cloud levels
  3943. ! hes_cup = saturation moist static energy on model cloud levels
  3944. ! dby = buoancy term
  3945. ! cd= detrainment function
  3946. ! z_cup = heights of model cloud levels
  3947. ! entr = entrainment rate
  3948. !
  3949. real, dimension (its:ite,kts:kte) &
  3950. ,intent (in ) :: &
  3951. he,he_cup,hes_cup,z_cup,cd
  3952. ! entr= entrainment rate
  3953. real &
  3954. ,intent (in ) :: &
  3955. entr
  3956. integer, dimension (its:ite) &
  3957. ,intent (in ) :: &
  3958. kbcon,k22
  3959. !
  3960. ! input and output
  3961. !
  3962. ! ierr error value, maybe modified in this routine
  3963. integer, dimension (its:ite) &
  3964. ,intent (inout) :: &
  3965. ierr
  3966. real, dimension (its:ite,kts:kte) &
  3967. ,intent (out ) :: &
  3968. hc,dby
  3969. real, dimension (its:ite) &
  3970. ,intent (out ) :: &
  3971. hkb
  3972. !
  3973. ! local variables in this routine
  3974. !
  3975. integer :: &
  3976. i,k
  3977. real :: &
  3978. dz
  3979. !
  3980. !--- moist static energy inside cloud
  3981. !
  3982. do k=kts,ktf
  3983. do i=its,itf
  3984. hc(i,k)=0.
  3985. DBY(I,K)=0.
  3986. enddo
  3987. enddo
  3988. do i=its,itf
  3989. hkb(i)=0.
  3990. enddo
  3991. do i=its,itf
  3992. if(ierr(i).eq.0.)then
  3993. hkb(i)=he_cup(i,k22(i))
  3994. if(name.eq.'shallow')then
  3995. do k=1,k22(i)
  3996. hkb(i)=max(hkb(i),he_cup(i,k))
  3997. enddo
  3998. endif
  3999. do k=1,k22(i)
  4000. hc(i,k)=he_cup(i,k)
  4001. enddo
  4002. do k=k22(i),kbcon(i)-1
  4003. hc(i,k)=hkb(i)
  4004. enddo
  4005. k=kbcon(i)
  4006. hc(i,k)=hkb(i)
  4007. DBY(I,Kbcon(i))=Hkb(I)-HES_cup(I,K)
  4008. endif
  4009. enddo
  4010. do k=kts+1,ktf
  4011. do i=its,itf
  4012. if(k.gt.kbcon(i).and.ierr(i).eq.0.)then
  4013. DZ=Z_cup(i,K)-Z_cup(i,K-1)
  4014. HC(i,K)=(HC(i,K-1)*(1.-.5*CD(i,K)*DZ)+entr* &
  4015. DZ*HE(i,K-1))/(1.+entr*DZ-.5*cd(i,k)*dz)
  4016. DBY(I,K)=HC(I,K)-HES_cup(I,K)
  4017. endif
  4018. enddo
  4019. enddo
  4020. END SUBROUTINE cup_up_he
  4021. SUBROUTINE cup_up_moisture(name,ierr,z_cup,qc,qrc,pw,pwav, &
  4022. kbcon,ktop,cd,dby,mentr_rate,clw_all, &
  4023. q,GAMMA_cup,zu,qes_cup,k22,qe_cup,xl, &
  4024. itf,jtf,ktf, &
  4025. its,ite, jts,jte, kts,kte )
  4026. IMPLICIT NONE
  4027. !
  4028. ! on input
  4029. !
  4030. ! only local wrf dimensions are need as of now in this routine
  4031. integer &
  4032. ,intent (in ) :: &
  4033. itf,jtf,ktf, &
  4034. its,ite, jts,jte, kts,kte
  4035. ! cd= detrainment function
  4036. ! q = environmental q on model levels
  4037. ! qe_cup = environmental q on model cloud levels
  4038. ! qes_cup = saturation q on model cloud levels
  4039. ! dby = buoancy term
  4040. ! cd= detrainment function
  4041. ! zu = normalized updraft mass flux
  4042. ! gamma_cup = gamma on model cloud levels
  4043. ! mentr_rate = entrainment rate
  4044. !
  4045. real, dimension (its:ite,kts:kte) &
  4046. ,intent (in ) :: &
  4047. q,zu,gamma_cup,qe_cup,dby,qes_cup,z_cup,cd
  4048. ! entr= entrainment rate
  4049. real &
  4050. ,intent (in ) :: &
  4051. mentr_rate,xl
  4052. integer, dimension (its:ite) &
  4053. ,intent (in ) :: &
  4054. kbcon,ktop,k22
  4055. !
  4056. ! input and output
  4057. !
  4058. ! ierr error value, maybe modified in this routine
  4059. integer, dimension (its:ite) &
  4060. ,intent (inout) :: &
  4061. ierr
  4062. character *(*), intent (in) :: &
  4063. name
  4064. ! qc = cloud q (including liquid water) after entrainment
  4065. ! qrch = saturation q in cloud
  4066. ! qrc = liquid water content in cloud after rainout
  4067. ! pw = condensate that will fall out at that level
  4068. ! pwav = totan normalized integrated condensate (I1)
  4069. ! c0 = conversion rate (cloud to rain)
  4070. real, dimension (its:ite,kts:kte) &
  4071. ,intent (out ) :: &
  4072. qc,qrc,pw,clw_all
  4073. real, dimension (its:ite) &
  4074. ,intent (out ) :: &
  4075. pwav
  4076. !
  4077. ! local variables in this routine
  4078. !
  4079. integer :: &
  4080. iall,i,k
  4081. real :: &
  4082. dh,qrch,c0,dz,radius
  4083. !
  4084. iall=0
  4085. c0=.002
  4086. !
  4087. !--- no precip for small clouds
  4088. !
  4089. if(name.eq.'shallow')c0=0.
  4090. do i=its,itf
  4091. pwav(i)=0.
  4092. enddo
  4093. do k=kts,ktf
  4094. do i=its,itf
  4095. pw(i,k)=0.
  4096. qc(i,k)=0.
  4097. if(ierr(i).eq.0)qc(i,k)=qes_cup(i,k)
  4098. clw_all(i,k)=0.
  4099. qrc(i,k)=0.
  4100. enddo
  4101. enddo
  4102. do i=its,itf
  4103. if(ierr(i).eq.0.)then
  4104. do k=k22(i),kbcon(i)-1
  4105. qc(i,k)=qe_cup(i,k22(i))
  4106. enddo
  4107. endif
  4108. enddo
  4109. DO 100 k=kts+1,ktf
  4110. DO 100 i=its,itf
  4111. IF(ierr(i).ne.0)GO TO 100
  4112. IF(K.Lt.KBCON(I))GO TO 100
  4113. IF(K.Gt.KTOP(I))GO TO 100
  4114. DZ=Z_cup(i,K)-Z_cup(i,K-1)
  4115. !
  4116. !------ 1. steady state plume equation, for what could
  4117. !------ be in cloud without condensation
  4118. !
  4119. !
  4120. QC(i,K)=(QC(i,K-1)*(1.-.5*CD(i,K)*DZ)+mentr_rate* &
  4121. DZ*Q(i,K-1))/(1.+mentr_rate*DZ-.5*cd(i,k)*dz)
  4122. !
  4123. !--- saturation in cloud, this is what is allowed to be in it
  4124. !
  4125. QRCH=QES_cup(I,K)+(1./XL)*(GAMMA_cup(i,k) &
  4126. /(1.+GAMMA_cup(i,k)))*DBY(I,K)
  4127. !
  4128. !------- LIQUID WATER CONTENT IN cloud after rainout
  4129. !
  4130. clw_all(i,k)=QC(I,K)-QRCH
  4131. QRC(I,K)=(QC(I,K)-QRCH)/(1.+C0*DZ*zu(i,k))
  4132. if(qrc(i,k).lt.0.)then
  4133. qrc(i,k)=0.
  4134. endif
  4135. !
  4136. !------- 3.Condensation
  4137. !
  4138. PW(i,k)=c0*dz*QRC(I,K)*zu(i,k)
  4139. if(iall.eq.1)then
  4140. qrc(i,k)=0.
  4141. pw(i,k)=(QC(I,K)-QRCH)*zu(i,k)
  4142. if(pw(i,k).lt.0.)pw(i,k)=0.
  4143. endif
  4144. !
  4145. !----- set next level
  4146. !
  4147. QC(I,K)=QRC(I,K)+qrch
  4148. !
  4149. !--- integrated normalized ondensate
  4150. !
  4151. PWAV(I)=PWAV(I)+PW(I,K)
  4152. 100 CONTINUE
  4153. END SUBROUTINE cup_up_moisture
  4154. SUBROUTINE cup_up_nms(zu,z_cup,entr,cd,kbcon,ktop,ierr,k22, &
  4155. itf,jtf,ktf, &
  4156. its,ite, jts,jte, kts,kte )
  4157. IMPLICIT NONE
  4158. !
  4159. ! on input
  4160. !
  4161. ! only local wrf dimensions are need as of now in this routine
  4162. integer &
  4163. ,intent (in ) :: &
  4164. itf,jtf,ktf, &
  4165. its,ite, jts,jte, kts,kte
  4166. ! cd= detrainment function
  4167. real, dimension (its:ite,kts:kte) &
  4168. ,intent (in ) :: &
  4169. z_cup,cd
  4170. ! entr= entrainment rate
  4171. real &
  4172. ,intent (in ) :: &
  4173. entr
  4174. integer, dimension (its:ite) &
  4175. ,intent (in ) :: &
  4176. kbcon,ktop,k22
  4177. !
  4178. ! input and output
  4179. !
  4180. ! ierr error value, maybe modified in this routine
  4181. integer, dimension (its:ite) &
  4182. ,intent (inout) :: &
  4183. ierr
  4184. ! zu is the normalized mass flux
  4185. real, dimension (its:ite,kts:kte) &
  4186. ,intent (out ) :: &
  4187. zu
  4188. !
  4189. ! local variables in this routine
  4190. !
  4191. integer :: &
  4192. i,k
  4193. real :: &
  4194. dz
  4195. !
  4196. ! initialize for this go around
  4197. !
  4198. do k=kts,ktf
  4199. do i=its,itf
  4200. zu(i,k)=0.
  4201. enddo
  4202. enddo
  4203. !
  4204. ! do normalized mass budget
  4205. !
  4206. do i=its,itf
  4207. IF(ierr(I).eq.0)then
  4208. do k=k22(i),kbcon(i)
  4209. zu(i,k)=1.
  4210. enddo
  4211. DO K=KBcon(i)+1,KTOP(i)
  4212. DZ=Z_cup(i,K)-Z_cup(i,K-1)
  4213. ZU(i,K)=ZU(i,K-1)*(1.+(entr-cd(i,k))*DZ)
  4214. enddo
  4215. endif
  4216. enddo
  4217. END SUBROUTINE cup_up_nms
  4218. !====================================================================
  4219. SUBROUTINE g3init(RTHCUTEN,RQVCUTEN,RQCCUTEN,RQICUTEN, &
  4220. MASS_FLUX,cp,restart, &
  4221. P_QC,P_QI,P_FIRST_SCALAR, &
  4222. RTHFTEN, RQVFTEN, &
  4223. APR_GR,APR_W,APR_MC,APR_ST,APR_AS, &
  4224. APR_CAPMA,APR_CAPME,APR_CAPMI, &
  4225. cugd_tten,cugd_ttens,cugd_qvten, &
  4226. cugd_qvtens,cugd_qcten, &
  4227. allowed_to_read, &
  4228. ids, ide, jds, jde, kds, kde, &
  4229. ims, ime, jms, jme, kms, kme, &
  4230. its, ite, jts, jte, kts, kte )
  4231. !--------------------------------------------------------------------
  4232. IMPLICIT NONE
  4233. !--------------------------------------------------------------------
  4234. LOGICAL , INTENT(IN) :: restart,allowed_to_read
  4235. INTEGER , INTENT(IN) :: ids, ide, jds, jde, kds, kde, &
  4236. ims, ime, jms, jme, kms, kme, &
  4237. its, ite, jts, jte, kts, kte
  4238. INTEGER , INTENT(IN) :: P_FIRST_SCALAR, P_QI, P_QC
  4239. REAL, INTENT(IN) :: cp
  4240. REAL, DIMENSION( ims:ime , kms:kme , jms:jme ) , INTENT(OUT) :: &
  4241. CUGD_TTEN, &
  4242. CUGD_TTENS, &
  4243. CUGD_QVTEN, &
  4244. CUGD_QVTENS, &
  4245. CUGD_QCTEN
  4246. REAL, DIMENSION( ims:ime , kms:kme , jms:jme ) , INTENT(OUT) :: &
  4247. RTHCUTEN, &
  4248. RQVCUTEN, &
  4249. RQCCUTEN, &
  4250. RQICUTEN
  4251. REAL, DIMENSION( ims:ime , kms:kme , jms:jme ) , INTENT(OUT) :: &
  4252. RTHFTEN, &
  4253. RQVFTEN
  4254. REAL, DIMENSION( ims:ime , jms:jme ) , INTENT(OUT) :: &
  4255. APR_GR,APR_W,APR_MC,APR_ST,APR_AS, &
  4256. APR_CAPMA,APR_CAPME,APR_CAPMI, &
  4257. MASS_FLUX
  4258. INTEGER :: i, j, k, itf, jtf, ktf
  4259. jtf=min0(jte,jde-1)
  4260. ktf=min0(kte,kde-1)
  4261. itf=min0(ite,ide-1)
  4262. IF(.not.restart)THEN
  4263. DO j=jts,jte
  4264. DO k=kts,kte
  4265. DO i=its,ite
  4266. RTHCUTEN(i,k,j)=0.
  4267. RQVCUTEN(i,k,j)=0.
  4268. ENDDO
  4269. ENDDO
  4270. ENDDO
  4271. DO j=jts,jte
  4272. DO k=kts,kte
  4273. DO i=its,ite
  4274. cugd_tten(i,k,j)=0.
  4275. cugd_ttens(i,k,j)=0.
  4276. cugd_qvten(i,k,j)=0.
  4277. cugd_qvtens(i,k,j)=0.
  4278. ENDDO
  4279. ENDDO
  4280. ENDDO
  4281. DO j=jts,jtf
  4282. DO k=kts,ktf
  4283. DO i=its,itf
  4284. RTHFTEN(i,k,j)=0.
  4285. RQVFTEN(i,k,j)=0.
  4286. ENDDO
  4287. ENDDO
  4288. ENDDO
  4289. IF (P_QC .ge. P_FIRST_SCALAR) THEN
  4290. DO j=jts,jtf
  4291. DO k=kts,ktf
  4292. DO i=its,itf
  4293. RQCCUTEN(i,k,j)=0.
  4294. cugd_qcten(i,k,j)=0.
  4295. ENDDO
  4296. ENDDO
  4297. ENDDO
  4298. ENDIF
  4299. IF (P_QI .ge. P_FIRST_SCALAR) THEN
  4300. DO j=jts,jtf
  4301. DO k=kts,ktf
  4302. DO i=its,itf
  4303. RQICUTEN(i,k,j)=0.
  4304. ENDDO
  4305. ENDDO
  4306. ENDDO
  4307. ENDIF
  4308. DO j=jts,jtf
  4309. DO i=its,itf
  4310. mass_flux(i,j)=0.
  4311. ENDDO
  4312. ENDDO
  4313. DO j=jts,jtf
  4314. DO i=its,itf
  4315. APR_GR(i,j)=0.
  4316. APR_ST(i,j)=0.
  4317. APR_W(i,j)=0.
  4318. APR_MC(i,j)=0.
  4319. APR_AS(i,j)=0.
  4320. APR_CAPMA(i,j)=0.
  4321. APR_CAPME(i,j)=0.
  4322. APR_CAPMI(i,j)=0.
  4323. ENDDO
  4324. ENDDO
  4325. ENDIF
  4326. END SUBROUTINE g3init
  4327. SUBROUTINE massflx_stats(xf_ens,ensdim,maxens,maxens2,maxens3, &
  4328. xt_ave,xt_std,xt_cur,xt_ske,j,ierr,itest, &
  4329. APR_GR,APR_W,APR_MC,APR_ST,APR_AS, &
  4330. APR_CAPMA,APR_CAPME,APR_CAPMI, &
  4331. pr_gr,pr_w,pr_mc,pr_st,pr_as, &
  4332. pr_capma,pr_capme,pr_capmi, &
  4333. itf,jtf,ktf, &
  4334. its,ite, jts,jte, kts,kte)
  4335. IMPLICIT NONE
  4336. integer, intent (in ) :: &
  4337. j,ensdim,maxens3,maxens,maxens2,itest
  4338. INTEGER, INTENT(IN ) :: &
  4339. itf,jtf,ktf, &
  4340. its,ite, jts,jte, kts,kte
  4341. real, dimension (its:ite) &
  4342. , intent(inout) :: &
  4343. xt_ave,xt_cur,xt_std,xt_ske
  4344. integer, dimension (its:ite), intent (in) :: &
  4345. ierr
  4346. real, dimension (its:ite,jts:jte,1:ensdim) &
  4347. , intent(in ) :: &
  4348. xf_ens
  4349. real, dimension (its:ite,jts:jte) &
  4350. , intent(inout) :: &
  4351. APR_GR,APR_W,APR_MC,APR_ST,APR_AS, &
  4352. APR_CAPMA,APR_CAPME,APR_CAPMI
  4353. real, dimension (its:ite,jts:jte) &
  4354. , intent(inout) :: &
  4355. pr_gr,pr_w,pr_mc,pr_st,pr_as, &
  4356. pr_capma,pr_capme,pr_capmi
  4357. !
  4358. ! local stuff
  4359. !
  4360. real, dimension (its:ite , 1:maxens3 ) :: &
  4361. x_ave,x_cur,x_std,x_ske
  4362. real, dimension (its:ite , 1:maxens ) :: &
  4363. x_ave_cap
  4364. integer, dimension (1:maxens3) :: nc1
  4365. integer :: i,k
  4366. integer :: num,kk,num2,iedt
  4367. real :: a3,a4
  4368. num=ensdim/maxens3
  4369. num2=ensdim/maxens
  4370. if(itest.eq.1)then
  4371. do i=its,ite
  4372. pr_gr(i,j) = 0.
  4373. pr_w(i,j) = 0.
  4374. pr_mc(i,j) = 0.
  4375. pr_st(i,j) = 0.
  4376. pr_as(i,j) = 0.
  4377. pr_capma(i,j) = 0.
  4378. pr_capme(i,j) = 0.
  4379. pr_capmi(i,j) = 0.
  4380. enddo
  4381. endif
  4382. do k=1,maxens
  4383. do i=its,ite
  4384. x_ave_cap(i,k)=0.
  4385. enddo
  4386. enddo
  4387. do k=1,maxens3
  4388. do i=its,ite
  4389. x_ave(i,k)=0.
  4390. x_std(i,k)=0.
  4391. x_ske(i,k)=0.
  4392. x_cur(i,k)=0.
  4393. enddo
  4394. enddo
  4395. do i=its,ite
  4396. xt_ave(i)=0.
  4397. xt_std(i)=0.
  4398. xt_ske(i)=0.
  4399. xt_cur(i)=0.
  4400. enddo
  4401. do kk=1,num
  4402. do k=1,maxens3
  4403. do i=its,ite
  4404. if(ierr(i).eq.0)then
  4405. x_ave(i,k)=x_ave(i,k)+xf_ens(i,j,maxens3*(kk-1)+k)
  4406. endif
  4407. enddo
  4408. enddo
  4409. enddo
  4410. do iedt=1,maxens2
  4411. do k=1,maxens
  4412. do kk=1,maxens3
  4413. do i=its,ite
  4414. if(ierr(i).eq.0)then
  4415. x_ave_cap(i,k)=x_ave_cap(i,k) &
  4416. +xf_ens(i,j,maxens3*(k-1)+(iedt-1)*maxens*maxens3+kk)
  4417. endif
  4418. enddo
  4419. enddo
  4420. enddo
  4421. enddo
  4422. do k=1,maxens
  4423. do i=its,ite
  4424. if(ierr(i).eq.0)then
  4425. x_ave_cap(i,k)=x_ave_cap(i,k)/float(num2)
  4426. endif
  4427. enddo
  4428. enddo
  4429. do k=1,maxens3
  4430. do i=its,ite
  4431. if(ierr(i).eq.0)then
  4432. x_ave(i,k)=x_ave(i,k)/float(num)
  4433. endif
  4434. enddo
  4435. enddo
  4436. do k=1,maxens3
  4437. do i=its,ite
  4438. if(ierr(i).eq.0)then
  4439. xt_ave(i)=xt_ave(i)+x_ave(i,k)
  4440. endif
  4441. enddo
  4442. enddo
  4443. do i=its,ite
  4444. if(ierr(i).eq.0)then
  4445. xt_ave(i)=xt_ave(i)/float(maxens3)
  4446. endif
  4447. enddo
  4448. !
  4449. !--- now do std, skewness,curtosis
  4450. !
  4451. do kk=1,num
  4452. do k=1,maxens3
  4453. do i=its,ite
  4454. if(ierr(i).eq.0.and.x_ave(i,k).gt.0.)then
  4455. ! print *,i,j,k,kk,x_std(i,k),xf_ens(i,j,maxens3*(kk-1)+k),x_ave(i,k)
  4456. x_std(i,k)=x_std(i,k)+(xf_ens(i,j,maxens3*(kk-1)+k)-x_ave(i,k))**2
  4457. x_ske(i,k)=x_ske(i,k)+(xf_ens(i,j,maxens3*(kk-1)+k)-x_ave(i,k))**3
  4458. x_cur(i,k)=x_cur(i,k)+(xf_ens(i,j,maxens3*(kk-1)+k)-x_ave(i,k))**4
  4459. endif
  4460. enddo
  4461. enddo
  4462. enddo
  4463. do k=1,maxens3
  4464. do i=its,ite
  4465. if(ierr(i).eq.0.and.xt_ave(i).gt.0.)then
  4466. xt_std(i)=xt_std(i)+(x_ave(i,k)-xt_ave(i))**2
  4467. xt_ske(i)=xt_ske(i)+(x_ave(i,k)-xt_ave(i))**3
  4468. xt_cur(i)=xt_cur(i)+(x_ave(i,k)-xt_ave(i))**4
  4469. endif
  4470. enddo
  4471. enddo
  4472. do k=1,maxens3
  4473. do i=its,ite
  4474. if(ierr(i).eq.0.and.x_std(i,k).gt.0.)then
  4475. x_std(i,k)=x_std(i,k)/float(num)
  4476. a3=max(1.e-6,x_std(i,k))
  4477. x_std(i,k)=sqrt(a3)
  4478. a3=max(1.e-6,x_std(i,k)**3)
  4479. a4=max(1.e-6,x_std(i,k)**4)
  4480. x_ske(i,k)=x_ske(i,k)/float(num)/a3
  4481. x_cur(i,k)=x_cur(i,k)/float(num)/a4
  4482. endif
  4483. ! print*,' '
  4484. ! print*,'Some statistics at gridpoint i,j, ierr',i,j,ierr(i)
  4485. ! print*,'statistics for closure number ',k
  4486. ! print*,'Average= ',x_ave(i,k),' Std= ',x_std(i,k)
  4487. ! print*,'Skewness= ',x_ske(i,k),' Curtosis= ',x_cur(i,k)
  4488. ! print*,' '
  4489. enddo
  4490. enddo
  4491. do i=its,ite
  4492. if(ierr(i).eq.0.and.xt_std(i).gt.0.)then
  4493. xt_std(i)=xt_std(i)/float(maxens3)
  4494. a3=max(1.e-6,xt_std(i))
  4495. xt_std(i)=sqrt(a3)
  4496. a3=max(1.e-6,xt_std(i)**3)
  4497. a4=max(1.e-6,xt_std(i)**4)
  4498. xt_ske(i)=xt_ske(i)/float(maxens3)/a3
  4499. xt_cur(i)=xt_cur(i)/float(maxens3)/a4
  4500. ! print*,' '
  4501. ! print*,'Total ensemble independent statistics at i =',i
  4502. ! print*,'Average= ',xt_ave(i),' Std= ',xt_std(i)
  4503. ! print*,'Skewness= ',xt_ske(i),' Curtosis= ',xt_cur(i)
  4504. ! print*,' '
  4505. !
  4506. ! first go around: store massflx for different closures/caps
  4507. !
  4508. if(itest.eq.1)then
  4509. pr_gr(i,j) = .25*(x_ave(i,1)+x_ave(i,2)+x_ave(i,3)+x_ave(i,13))
  4510. pr_w(i,j) = .25*(x_ave(i,4)+x_ave(i,5)+x_ave(i,6)+x_ave(i,14))
  4511. pr_mc(i,j) = .25*(x_ave(i,7)+x_ave(i,8)+x_ave(i,9)+x_ave(i,15))
  4512. pr_st(i,j) = .333*(x_ave(i,10)+x_ave(i,11)+x_ave(i,12))
  4513. pr_as(i,j) = x_ave(i,16)
  4514. pr_capma(i,j) = x_ave_cap(i,1)
  4515. pr_capme(i,j) = x_ave_cap(i,2)
  4516. pr_capmi(i,j) = x_ave_cap(i,3)
  4517. !
  4518. ! second go around: store preciprates (mm/hour) for different closures/caps
  4519. !
  4520. else if (itest.eq.2)then
  4521. APR_GR(i,j)=.25*(x_ave(i,1)+x_ave(i,2)+x_ave(i,3)+x_ave(i,13))* &
  4522. 3600.*pr_gr(i,j) +APR_GR(i,j)
  4523. APR_W(i,j)=.25*(x_ave(i,4)+x_ave(i,5)+x_ave(i,6)+x_ave(i,14))* &
  4524. 3600.*pr_w(i,j) +APR_W(i,j)
  4525. APR_MC(i,j)=.25*(x_ave(i,7)+x_ave(i,8)+x_ave(i,9)+x_ave(i,15))* &
  4526. 3600.*pr_mc(i,j) +APR_MC(i,j)
  4527. APR_ST(i,j)=.333*(x_ave(i,10)+x_ave(i,11)+x_ave(i,12))* &
  4528. 3600.*pr_st(i,j) +APR_ST(i,j)
  4529. APR_AS(i,j)=x_ave(i,16)* &
  4530. 3600.*pr_as(i,j) +APR_AS(i,j)
  4531. APR_CAPMA(i,j) = x_ave_cap(i,1)* &
  4532. 3600.*pr_capma(i,j) +APR_CAPMA(i,j)
  4533. APR_CAPME(i,j) = x_ave_cap(i,2)* &
  4534. 3600.*pr_capme(i,j) +APR_CAPME(i,j)
  4535. APR_CAPMI(i,j) = x_ave_cap(i,3)* &
  4536. 3600.*pr_capmi(i,j) +APR_CAPMI(i,j)
  4537. endif
  4538. endif
  4539. enddo
  4540. END SUBROUTINE massflx_stats
  4541. SUBROUTINE cup_axx(tcrit,kbmax,z1,p,psur,xl,rv,cp,tx,qx,axx,ierr, &
  4542. cap_max,cap_max_increment,entr_rate,mentr_rate,&
  4543. j,itf,jtf,ktf, &
  4544. its,ite, jts,jte, kts,kte,ens4)
  4545. IMPLICIT NONE
  4546. INTEGER, INTENT(IN ) :: &
  4547. j,itf,jtf,ktf, &
  4548. its,ite, jts,jte, kts,kte,ens4
  4549. real, dimension (its:ite,kts:kte,1:ens4) &
  4550. , intent(inout) :: &
  4551. tx,qx
  4552. real, dimension (its:ite,kts:kte) &
  4553. , intent(in) :: &
  4554. p
  4555. real, dimension (its:ite) &
  4556. , intent(in) :: &
  4557. z1,psur,cap_max,cap_max_increment
  4558. real, intent(in) :: &
  4559. tcrit,xl,rv,cp,mentr_rate,entr_rate
  4560. real, dimension (its:ite,1:ens4) &
  4561. , intent(out) :: &
  4562. axx
  4563. integer, dimension (its:ite), intent (in) :: &
  4564. ierr,kbmax
  4565. integer, dimension (its:ite) :: &
  4566. ierrxx,k22xx,kbconxx,ktopxx,kstabm,kstabi
  4567. real, dimension (1:2) :: AE,BE,HT
  4568. real, dimension (its:ite,kts:kte) :: tv
  4569. real :: e,tvbar
  4570. integer n,i,k,iph
  4571. real, dimension (its:ite,kts:kte) :: &
  4572. he,hes,qes,z, &
  4573. qes_cup,q_cup,he_cup,hes_cup,z_cup,p_cup,gamma_cup,t_cup, &
  4574. tn_cup, &
  4575. dby,qc,qrcd,pwd,pw,hcd,qcd,dbyd,hc,qrc,zu,zd,cd
  4576. real, dimension (its:ite) :: &
  4577. AA0,HKB,QKB, &
  4578. PWAV,BU
  4579. do n=1,ens4
  4580. do i=its,ite
  4581. axx(i,n)=0.
  4582. enddo
  4583. enddo
  4584. HT(1)=XL/CP
  4585. HT(2)=2.834E6/CP
  4586. BE(1)=.622*HT(1)/.286
  4587. AE(1)=BE(1)/273.+ALOG(610.71)
  4588. BE(2)=.622*HT(2)/.286
  4589. AE(2)=BE(2)/273.+ALOG(610.71)
  4590. !
  4591. !
  4592. do 100 n=1,ens4
  4593. do k=kts,ktf
  4594. do i=its,itf
  4595. cd(i,k)=0.1*entr_rate
  4596. enddo
  4597. enddo
  4598. do i=its,itf
  4599. ierrxx(i)=ierr(i)
  4600. k22xx(i)=1
  4601. kbconxx(i)=1
  4602. ktopxx(i)=1
  4603. kstabm(i)=ktf-1
  4604. enddo
  4605. DO k=kts,ktf
  4606. do i=its,itf
  4607. if(ierrxx(i).eq.0)then
  4608. IPH=1
  4609. IF(Tx(I,K,n).LE.TCRIT)IPH=2
  4610. E=EXP(AE(IPH)-BE(IPH)/TX(I,K,N))
  4611. QES(I,K)=.622*E/(100.*P(I,K)-E)
  4612. IF(QES(I,K).LE.1.E-08)QES(I,K)=1.E-08
  4613. IF(Qx(I,K,N).GT.QES(I,K))Qx(I,K,N)=QES(I,K)
  4614. TV(I,K)=Tx(I,K,N)+.608*Qx(I,K,N)*Tx(I,K,N)
  4615. endif
  4616. enddo
  4617. enddo
  4618. !
  4619. do i=its,itf
  4620. if(ierrxx(i).eq.0)then
  4621. Z(I,KTS)=max(0.,Z1(I))-(ALOG(P(I,KTS))- &
  4622. ALOG(PSUR(I)))*287.*TV(I,KTS)/9.81
  4623. endif
  4624. enddo
  4625. ! --- calculate heights
  4626. DO K=kts+1,ktf
  4627. do i=its,itf
  4628. if(ierrxx(i).eq.0)then
  4629. TVBAR=.5*TV(I,K)+.5*TV(I,K-1)
  4630. Z(I,K)=Z(I,K-1)-(ALOG(P(I,K))- &
  4631. ALOG(P(I,K-1)))*287.*TVBAR/9.81
  4632. endif
  4633. enddo
  4634. enddo
  4635. !
  4636. !--- calculate moist static energy - HE
  4637. ! saturated moist static energy - HES
  4638. !
  4639. DO k=kts,ktf
  4640. do i=its,itf
  4641. if(ierrxx(i).eq.0)then
  4642. HE(I,K)=9.81*Z(I,K)+1004.*Tx(I,K,n)+2.5E06*Qx(I,K,n)
  4643. HES(I,K)=9.81*Z(I,K)+1004.*Tx(I,K,n)+2.5E06*QES(I,K)
  4644. IF(HE(I,K).GE.HES(I,K))HE(I,K)=HES(I,K)
  4645. endif
  4646. enddo
  4647. enddo
  4648. ! cup levels
  4649. !
  4650. do k=kts+1,ktf
  4651. do i=its,itf
  4652. if(ierrxx(i).eq.0)then
  4653. qes_cup(i,k)=.5*(qes(i,k-1)+qes(i,k))
  4654. q_cup(i,k)=.5*(qx(i,k-1,n)+qx(i,k,n))
  4655. hes_cup(i,k)=.5*(hes(i,k-1)+hes(i,k))
  4656. he_cup(i,k)=.5*(he(i,k-1)+he(i,k))
  4657. if(he_cup(i,k).gt.hes_cup(i,k))he_cup(i,k)=hes_cup(i,k)
  4658. z_cup(i,k)=.5*(z(i,k-1)+z(i,k))
  4659. p_cup(i,k)=.5*(p(i,k-1)+p(i,k))
  4660. t_cup(i,k)=.5*(tx(i,k-1,n)+tx(i,k,n))
  4661. gamma_cup(i,k)=(xl/cp)*(xl/(rv*t_cup(i,k) &
  4662. *t_cup(i,k)))*qes_cup(i,k)
  4663. endif
  4664. enddo
  4665. enddo
  4666. do i=its,itf
  4667. if(ierrxx(i).eq.0)then
  4668. qes_cup(i,1)=qes(i,1)
  4669. q_cup(i,1)=qx(i,1,n)
  4670. hes_cup(i,1)=hes(i,1)
  4671. he_cup(i,1)=he(i,1)
  4672. z_cup(i,1)=.5*(z(i,1)+z1(i))
  4673. p_cup(i,1)=.5*(p(i,1)+psur(i))
  4674. t_cup(i,1)=tx(i,1,n)
  4675. gamma_cup(i,1)=xl/cp*(xl/(rv*t_cup(i,1) &
  4676. *t_cup(i,1)))*qes_cup(i,1)
  4677. endif
  4678. enddo
  4679. !
  4680. !
  4681. !------- DETERMINE LEVEL WITH HIGHEST MOIST STATIC ENERGY CONTENT - K22
  4682. !
  4683. CALL cup_MAXIMI(HE_CUP,3,KBMAX,K22XX,ierrxx, &
  4684. itf,jtf,ktf, &
  4685. its,ite, jts,jte, kts,kte)
  4686. DO 36 i=its,itf
  4687. IF(ierrxx(I).eq.0.)THEN
  4688. IF(K22xx(I).GE.KBMAX(i))ierrxx(i)=2
  4689. endif
  4690. 36 CONTINUE
  4691. !
  4692. !--- DETERMINE THE LEVEL OF CONVECTIVE CLOUD BASE - KBCON
  4693. !
  4694. call cup_kbcon(cap_max_increment,1,k22xx,kbconxx,he_cup,hes_cup, &
  4695. ierrxx,kbmax,p_cup,cap_max, &
  4696. itf,jtf,ktf, &
  4697. its,ite, jts,jte, kts,kte)
  4698. !
  4699. !--- increase detrainment in stable layers
  4700. !
  4701. CALL cup_minimi(HEs_cup,Kbconxx,kstabm,kstabi,ierrxx, &
  4702. itf,jtf,ktf, &
  4703. its,ite, jts,jte, kts,kte)
  4704. do i=its,itf
  4705. IF(ierrxx(I).eq.0.)THEN
  4706. if(kstabm(i)-1.gt.kstabi(i))then
  4707. do k=kstabi(i),kstabm(i)-1
  4708. cd(i,k)=cd(i,k-1)+1.5*entr_rate
  4709. if(cd(i,k).gt.10.0*entr_rate)cd(i,k)=10.0*entr_rate
  4710. enddo
  4711. ENDIF
  4712. ENDIF
  4713. ENDDO
  4714. !
  4715. !--- calculate incloud moist static energy
  4716. !
  4717. call cup_up_he(k22xx,hkb,z_cup,cd,mentr_rate,he_cup,hc, &
  4718. kbconxx,ierrxx,dby,he,hes_cup,'deep', &
  4719. itf,jtf,ktf, &
  4720. its,ite, jts,jte, kts,kte)
  4721. !--- DETERMINE CLOUD TOP - KTOP
  4722. !
  4723. call cup_ktop(1,dby,kbconxx,ktopxx,ierrxx, &
  4724. itf,jtf,ktf, &
  4725. its,ite, jts,jte, kts,kte)
  4726. !
  4727. !c--- normalized updraft mass flux profile
  4728. !
  4729. call cup_up_nms(zu,z_cup,mentr_rate,cd,kbconxx,ktopxx,ierrxx,k22xx, &
  4730. itf,jtf,ktf, &
  4731. its,ite, jts,jte, kts,kte)
  4732. !
  4733. !--- calculate workfunctions for updrafts
  4734. !
  4735. call cup_up_aa0(aa0,z,zu,dby,GAMMA_CUP,t_cup, &
  4736. kbconxx,ktopxx,ierrxx, &
  4737. itf,jtf,ktf, &
  4738. its,ite, jts,jte, kts,kte)
  4739. do i=its,itf
  4740. if(ierrxx(i).eq.0)axx(i,n)=aa0(i)
  4741. enddo
  4742. 100 continue
  4743. END SUBROUTINE cup_axx
  4744. SUBROUTINE conv_grell_spread3d(rthcuten,rqvcuten,rqccuten,raincv, &
  4745. & cugd_avedx,cugd_tten,cugd_qvten,rqicuten,cugd_ttens, &
  4746. & cugd_qvtens,cugd_qcten,pi_phy,moist_qv,pratec,dt,num_tiles,&
  4747. & imomentum,F_QV ,F_QC ,F_QR ,F_QI ,F_QS, &
  4748. & ids, ide, jds, jde, kds, kde, &
  4749. & ips, ipe, jps, jpe, kps, kpe, &
  4750. & ims, ime, jms, jme, kms, kme, &
  4751. & its, ite, jts, jte, kts, kte )
  4752. !
  4753. INTEGER, INTENT(IN ) :: num_tiles,imomentum
  4754. INTEGER, INTENT(IN ) :: ids, ide, jds, jde, kds, kde,&
  4755. ims,ime, jms,jme, kms,kme, &
  4756. ips,ipe, jps,jpe, kps,kpe, &
  4757. its,ite, jts,jte, kts,kte, &
  4758. cugd_avedx
  4759. REAL, DIMENSION (ims:ime,kms:kme,jms:jme), optional,INTENT (INOUT) :: &
  4760. & rthcuten,rqvcuten,rqccuten,rqicuten
  4761. REAL, DIMENSION (ims:ime,kms:kme,jms:jme), optional,INTENT (IN ) :: &
  4762. & cugd_tten,cugd_qvten,cugd_ttens,cugd_qvtens,cugd_qcten
  4763. REAL, DIMENSION (ims:ime,kms:kme,jms:jme),INTENT (IN) :: &
  4764. moist_qv
  4765. REAL, DIMENSION (ims:ime,kms:kme,jms:jme), INTENT (IN) :: &
  4766. PI_PHY
  4767. REAL, DIMENSION (ims:ime,jms:jme), INTENT (INOUT) :: &
  4768. raincv,pratec
  4769. REAL, INTENT(IN) :: dt
  4770. INTEGER :: ikk1,ikk2,ikk11,i,j,k,kk,nn,smoothh,smoothv
  4771. INTEGER :: ifs,ife,jfs,jfe,ido,jdo,cugd_spread
  4772. LOGICAL :: new
  4773. !
  4774. ! Flags relating to the optional tendency arrays declared above
  4775. ! Models that carry the optional tendencies will provdide the
  4776. ! optional arguments at compile time; these flags all the model
  4777. ! to determine at run-time whether a particular tracer is in
  4778. ! use or not.
  4779. !
  4780. LOGICAL, OPTIONAL :: &
  4781. F_QV &
  4782. ,F_QC &
  4783. ,F_QR &
  4784. ,F_QI &
  4785. ,F_QS
  4786. REAL, DIMENSION (its-2:ite+2,kts:kte,jts-2:jte+2) :: &
  4787. RTHcutent,RQVcutent
  4788. real, dimension (its-2:ite+2,jts-2:jte+2) :: Qmem
  4789. real, dimension (its-1:ite+1,jts-1:jte+1) :: smTT,smTQ
  4790. real, dimension (kts:kte) :: conv_TRASHT,conv_TRASHQ
  4791. REAL :: Qmem1,Qmem2,Qmemf,Thresh
  4792. smoothh=1
  4793. smoothv=1
  4794. cugd_spread=cugd_avedx/2
  4795. ifs=max(its,ids)
  4796. jfs=max(jts,jds)
  4797. ife=min(ite,ide-1)
  4798. jfe=min(jte,jde-1)
  4799. do j=jfs-2,jfe+2
  4800. do i=ifs-2,ife+2
  4801. Qmem(i,j)=1.
  4802. enddo
  4803. enddo
  4804. do j=jfs-1,jfe+1
  4805. do i=ifs-1,ife+1
  4806. smTT(i,j)=0.
  4807. smTQ(i,j)=0.
  4808. enddo
  4809. enddo
  4810. do j=jfs,jfe
  4811. do k=kts,kte
  4812. do i=ifs,ife
  4813. rthcuten(i,k,j)=0.
  4814. rqvcuten(i,k,j)=0.
  4815. enddo
  4816. enddo
  4817. enddo
  4818. do j=jfs-2,jfe+2
  4819. do k=kts,kte
  4820. do i=ifs-2,ife+2
  4821. RTHcutent(i,k,j)=0.
  4822. RQVcutent(i,k,j)=0.
  4823. enddo
  4824. enddo
  4825. enddo
  4826. !
  4827. !
  4828. !
  4829. !
  4830. ! prelims finished, now go real for every grid point
  4831. !
  4832. if(cugd_spread.gt.0.or.smoothh.eq.1)then
  4833. !if(its.eq.ips)ifs=max(its-1,ids)
  4834. !if(ite.eq.ipe)ife=min(ite+1,ide-1)
  4835. !if(jts.eq.jps)jfs=max(jts-1,jds)
  4836. !if(jte.eq.jpe)jfe=min(jte+1,jde-1)
  4837. ifs=max(its-1,ids)
  4838. ife=min(ite+1,ide-1)
  4839. jfs=max(jts-1,jds)
  4840. jfe=min(jte+1,jde-1)
  4841. endif
  4842. ! *** jm note -- for smoothing this goes out one row/column beyond tile in i and j
  4843. do j=jfs,jfe
  4844. do i=ifs,ife
  4845. !
  4846. do k=kts,kte
  4847. RTHcutent(i,k,j)=cugd_tten(i,k,j)
  4848. RQVcutent(i,k,j)=cugd_qvten(i,k,j)
  4849. enddo
  4850. !
  4851. ! for high res run, spread the subsidence
  4852. ! this is tricky......only consider grid points where there was no rain,
  4853. ! so cugd_tten and such are zero!
  4854. !
  4855. if(cugd_spread.gt.0)then
  4856. do k=kts,kte
  4857. do nn=-1,1,1
  4858. jdo=max(j+nn,jds)
  4859. jdo=min(jdo,jde-1)
  4860. do kk=-1,1,1
  4861. ido=max(i+kk,ids)
  4862. ido=min(ido,ide-1)
  4863. RTHcutent(i,k,j)=RTHcutent(i,k,j) &
  4864. +Qmem(ido,jdo)*cugd_ttens(ido,k,jdo)
  4865. RQVcutent(i,k,j)=RQVcutent(i,k,j) &
  4866. +Qmem(ido,jdo)*cugd_qvtens(ido,k,jdo)
  4867. enddo
  4868. enddo
  4869. enddo
  4870. endif
  4871. !
  4872. ! end spreading
  4873. if(cugd_spread.eq.0)then
  4874. do k=kts,kte
  4875. RTHcutent(i,k,j)=RTHcutent(i,k,j)+cugd_ttens(i,k,j)
  4876. RQVcutent(i,k,j)=RQVcutent(i,k,j)+cugd_qvtens(i,k,j)
  4877. enddo
  4878. endif
  4879. enddo ! end j
  4880. enddo ! end i
  4881. ! smooth
  4882. do k=kts,kte
  4883. if(smoothh.eq.0)then
  4884. ifs=max(its,ids+4)
  4885. ife=min(ite,ide-5)
  4886. jfs=max(jts,jds+4)
  4887. jfe=min(jte,jde-5)
  4888. do i=ifs,ife
  4889. do j=jfs,jfe
  4890. rthcuten(i,k,j)=RTHcutent(i,k,j)
  4891. rqvcuten(i,k,j)=RQVcutent(i,k,j)
  4892. enddo ! end j
  4893. enddo ! end j
  4894. else if(smoothh.eq.1)then ! smooth
  4895. ifs=max(its,ids)
  4896. ife=min(ite,ide-1)
  4897. jfs=max(jts,jds)
  4898. jfe=min(jte,jde-1)
  4899. ! we need an extra row for j (halo comp)
  4900. !if(jts.eq.jps)jfs=max(jts-1,jds)
  4901. !if(jte.eq.jpe)jfe=min(jte+1,jde-1)
  4902. jfs=max(jts-1,jds)
  4903. jfe=min(jte+1,jde-1)
  4904. do i=ifs,ife
  4905. do j=jfs,jfe
  4906. smTT(i,j)=.25*(RTHcutent(i-1,k,j)+2.*RTHcutent(i,k,j)+RTHcutent(i+1,k,j))
  4907. smTQ(i,j)=.25*(RQVcutent(i-1,k,j)+2.*RQVcutent(i,k,j)+RQVcutent(i+1,k,j))
  4908. enddo ! end j
  4909. enddo ! end j
  4910. ifs=max(its,ids+4)
  4911. ife=min(ite,ide-5)
  4912. jfs=max(jts,jds+4)
  4913. jfe=min(jte,jde-5)
  4914. do i=ifs,ife
  4915. do j=jfs,jfe
  4916. rthcuten(i,k,j)=.25*(smTT(i,j-1)+2.*smTT(i,j)+smTT(i,j+1))
  4917. rqvcuten(i,k,j)=.25*(smTQ(i,j-1)+2.*smTQ(i,j)+smTQ(i,j+1))
  4918. enddo ! end j
  4919. enddo ! end i
  4920. endif ! smoothh
  4921. enddo ! end k
  4922. !
  4923. ! check moistening rates
  4924. !
  4925. ifs=max(its,ids+4)
  4926. ife=min(ite,ide-5)
  4927. jfs=max(jts,jds+4)
  4928. jfe=min(jte,jde-5)
  4929. do j=jfs,jfe
  4930. do i=ifs,ife
  4931. Qmemf=1.
  4932. Thresh=1.e-20
  4933. do k=kts,kte
  4934. if(rqvcuten(i,k,j).lt.0.)then
  4935. Qmem1=moist_qv(i,k,j)+rqvcuten(i,k,j)*dt
  4936. if(Qmem1.lt.Thresh)then
  4937. Qmem1=rqvcuten(i,k,j)
  4938. Qmem2=(Thresh-moist_qv(i,k,j))/dt
  4939. Qmemf=min(Qmemf,Qmem2/Qmem1)
  4940. Qmemf=max(0.,Qmemf)
  4941. Qmemf=min(1.,Qmemf)
  4942. endif
  4943. endif
  4944. enddo
  4945. do k=kts,kte
  4946. rqvcuten(i,k,j)=rqvcuten(i,k,j)*Qmemf
  4947. rthcuten(i,k,j)=rthcuten(i,k,j)*Qmemf
  4948. enddo
  4949. if(present(rqccuten))then
  4950. if(f_qc) then
  4951. do k=kts,kte
  4952. rqccuten(i,k,j)=rqccuten(i,k,j)*Qmemf
  4953. enddo
  4954. endif
  4955. endif
  4956. if(present(rqicuten))then
  4957. if(f_qi) then
  4958. do k=kts,kte
  4959. rqicuten(i,k,j)=rqicuten(i,k,j)*Qmemf
  4960. enddo
  4961. endif
  4962. endif
  4963. raincv(I,J)=raincv(I,J)*Qmemf
  4964. pratec(I,J)=pratec(I,J)*Qmemf
  4965. !
  4966. ! check heating rates
  4967. !
  4968. Thresh=200.
  4969. Qmemf=1.
  4970. Qmem1=0.
  4971. do k=kts,kte
  4972. Qmem1=abs(rthcuten(i,k,j))*86400.
  4973. if(Qmem1.gt.Thresh)then
  4974. Qmem2=Thresh/Qmem1
  4975. Qmemf=min(Qmemf,Qmem2)
  4976. Qmemf=max(0.,Qmemf)
  4977. endif
  4978. enddo
  4979. raincv(i,j)=raincv(i,j)*Qmemf
  4980. pratec(i,j)=pratec(i,j)*Qmemf
  4981. do k=kts,kte
  4982. rqvcuten(i,k,j)=rqvcuten(i,k,j)*Qmemf
  4983. rthcuten(i,k,j)=rthcuten(i,k,j)*Qmemf
  4984. enddo
  4985. if(present(rqccuten))then
  4986. if(f_qc) then
  4987. do k=kts,kte
  4988. rqccuten(i,k,j)=rqccuten(i,k,j)*Qmemf
  4989. enddo
  4990. endif
  4991. endif
  4992. if(present(rqicuten))then
  4993. if(f_qi) then
  4994. do k=kts,kte
  4995. rqicuten(i,k,j)=rqicuten(i,k,j)*Qmemf
  4996. enddo
  4997. endif
  4998. endif
  4999. if(smoothv.eq.1)then
  5000. !
  5001. ! smooth for now
  5002. !
  5003. do k=kts+2,kte-2
  5004. conv_TRASHT(k)= .25*(rthcuten(i,k-1,j)+2.*rthcuten(i,k,j)+rthcuten(i,k+1,j))
  5005. conv_TRASHQ(k)= .25*(rqvcuten(i,k-1,j)+2.*rqvcuten(i,k,j)+rqvcuten(i,k+1,j))
  5006. enddo
  5007. do k=kts+2,kte-2
  5008. rthcuten(i,k,j)=conv_TRASHT(k)
  5009. rqvcuten(i,k,j)=conv_TRASHQ(k)
  5010. enddo
  5011. endif
  5012. do k=kts,kte
  5013. rthcuten(i,k,j)=rthcuten(i,k,j)/pi_phy(i,k,j)
  5014. enddo
  5015. enddo ! end j
  5016. enddo ! end i
  5017. END SUBROUTINE CONV_GRELL_SPREAD3D
  5018. !-------------------------------------------------------
  5019. END MODULE module_cu_g3