1 ! Generated by TAPENADE (INRIA, Tropics team)
2 ! Tapenade 3.7 (r4786) - 21 Feb 2013 15:53
4 ! Differentiation of cumulus_driver in forward (tangent) mode (with options r8):
5 ! variations of useful results: raincv rthcuten pratec rqvcuten
6 ! with respect to varying inputs: th raincv p t rthcuten z pratec
7 ! qv_curr rqvcuten rho dz8w
8 ! RW status of diff variables: th:in raincv:in-out p:in t:in
9 ! rthcuten:in-out z:in pratec:in-out qv_curr:in
10 ! rqvcuten:in-out rho:in dz8w:in
11 !WRF:MEDIATION_LAYER:PHYSICS
13 MODULE g_module_cumulus_driver
15 ! Order dependent args for domain, mem, and tile dims
16 ! Order independent args (use VAR= in call)
19 !Balwinder.Singh@pnnl.gov: Used for CAM's wet scavenging
20 ! Package selection variables
21 ! Optional moisture tracers
22 ! Optional arguments for GD scheme
23 ! Optional output arguments for CAMZM scheme
24 ! Optional arguments for SAS scheme
25 !Kwon for SAS2010 shallow convection
26 ! Optional arguments for NSAS scheme
27 ! Optional moisture and other tendencies
28 ! Optional variables for tiedtke scheme - add by ZCX&YQW
29 ! Optional moisture tracer flags
30 ! Optional trigger function activation variable
31 SUBROUTINE G_CUMULUS_DRIVER(grid, ids, ide, jds, jde, kds, kde, ims, ime&
32 & , jms, jme, kms, kme, ips, ipe, jps, jpe, kps, kpe, i_start, i_end, &
33 & j_start, j_end, kts, kte, num_tiles, u, v, th, thd, t, td, w, p, pd, &
34 & pi, rho, rhod, itimestep, dt, dx, cudt, curr_secs, adapt_step_flag, &
35 & cudtacttime, rainc, raincv, raincvd, pratec, pratecd, nca, z, zd, &
36 & z_at_w, dz8w, dz8wd, mavail, pblh, p8w, psfc, tsk, tke_pbl, ust, &
37 & forcet, forceq, w0avg, stepcu, gsw, cldefi, lowlyr, xland, cu_act_flag&
38 & , warm_rain, hfx, qfx, cldfra, cldfra_mp_all, tpert2d, htop, hbot, &
39 & kpbl, ht, ensdim, maxiens, maxens, maxens2, maxens3, periodic_x, &
40 & periodic_y, evapcdp3d, icwmrdp3d, rprddp3d, &
41 & cu_physics, bl_pbl_physics, sf_sfclay_physics, qv_curr, qv_currd, &
42 & qc_curr, qr_curr, qi_curr, qs_curr, qg_curr, qv_prev, qc_prev, qr_prev&
43 & , qi_prev, qs_prev, qg_prev, apr_gr, apr_w, apr_mc, apr_st, apr_as, &
44 & apr_capma, apr_capme, apr_capmi, edt_out, clos_choice, mass_flux, &
45 & xf_ens, pr_ens, cugd_avedx, imomentum, ishallow, cugd_tten, cugd_qvten&
46 & , cugd_qcten, cugd_ttens, cugd_qvtens, gd_cloud, gd_cloud2, cape, zmmu&
47 & , zmmd, zmdt, zmdq, dlf, rliq, pconvb, pconvt, evaptzm, fzsntzm, &
48 & evsntzm, evapqzm, zmflxprc, zmflxsnw, zmntprpd, zmntsnpd, zmeiheat, &
49 & cmfmc, cmfmcdzm, preccdzm, precz, zmmtu, zmmtv, zmupgu, zmupgd, zmvpgu&
50 & , zmvpgd, zmicuu, zmicud, zmicvu, zmicvd, zmdice, zmdliq, dp3d, du3d, &
51 & ed3d, eu3d, md3d, mu3d, dsubcld2d, ideep2d, jt2d, maxg2d, lengath2d, &
52 & k22_shallow, kbcon_shallow, ktop_shallow, xmb_shallow, ktop_deep, &
53 & pgcon, sas_mass_flux, shalconv, shal_pgcon, hpbl2d, evap2d, heat2d, &
54 & mp_physics, rqvcuten, rqvcutend, rqccuten, rqrcuten, rqicuten, &
55 & rqscuten, rqgcuten, rqcncuten, rqincuten, rqvblten, rqvften, rucuten, &
56 & rvcuten, rthcuten, rthcutend, rthraten, rthblten, rthften, mommix, &
57 & store_rand, znu, f_qv, f_qc, f_qr, f_qi, f_qs, f_qg, cfu1, cfd1, dfu1&
58 & , efu1, dfd1, efd1, f_flux, kfeta_trigger)
60 USE module_model_constants
61 USE module_state_description, ONLY: KFSCHEME,BMJSCHEME &
62 ,KFETASCHEME,GDSCHEME &
64 ,P_QC,P_QI,Param_FIRST_SCALAR &
65 ,CAMZMSCHEME, SASSCHEME &
67 ,NSASSCHEME, DUCUSCHEME &
71 ! *** add new modules of schemes here
74 USE module_dm , ONLY : ntasks_x,ntasks_y,local_communicator,mytask,ntasks
76 USE module_domain , ONLY: domain
77 USE g_module_cu_du , ONLY : DUCU_D
78 USE module_wrf_error , ONLY : wrf_err_message
81 !======================================================================
82 ! Grid structure in physics part of WRF
83 !----------------------------------------------------------------------
84 ! The horizontal velocities used in the physics are unstaggered
85 ! relative to temperature/moisture variables. All predicted
86 ! variables are carried at half levels except w, which is at full
87 ! levels. Some arrays with names (*8w) are at w (full) levels.
89 !----------------------------------------------------------------------
90 ! In WRF, kms (smallest number) is the bottom level and kme (largest
91 ! number) is the top level. In your scheme, if 1 is at the top level,
92 ! then you have to reverse the order in the k direction.
94 ! kme - half level (no data at this level)
95 ! kme ----- full level
97 ! kme-1 ----- full level
102 ! kms+2 ----- full level
104 ! kms+1 ----- full level
106 ! kms ----- full level
108 !======================================================================
111 ! Rho_d dry density (kg/m^3)
112 ! Theta_m moist potential temperature (K)
113 ! Qv water vapor mixing ratio (kg/kg)
114 ! Qc cloud water mixing ratio (kg/kg)
115 ! Qr rain water mixing ratio (kg/kg)
116 ! Qi cloud ice mixing ratio (kg/kg)
117 ! Qs snow mixing ratio (kg/kg)
118 !-----------------------------------------------------------------
119 !-- DT time step (second)
120 !-- CUDT cumulus time step (minute)
121 !-- curr_secs current forecast time (seconds)
122 !-- itimestep number of time step (integer)
123 !-- DX horizontal space interval (m)
124 !-- rr dry air density (kg/m^3)
126 !-- RUCUTEN Zonal wind tendency due to
127 ! cumulus scheme precipitation (m/s/s)
128 !-- RVCUTEN Meridional wind tendency due to
129 ! cumulus scheme precipitation (m/s/s)
130 !-- RTHCUTEN Theta tendency due to
131 ! cumulus scheme precipitation (K/s)
132 !-- RQVCUTEN Qv tendency due to
133 ! cumulus scheme precipitation (kg/kg/s)
134 !-- RQRCUTEN Qr tendency due to
135 ! cumulus scheme precipitation (kg/kg/s)
136 !-- RQCCUTEN Qc tendency due to
137 ! cumulus scheme precipitation (kg/kg/s)
138 !-- RQSCUTEN Qs tendency due to
139 ! cumulus scheme precipitation (kg/kg/s)
140 !-- RQICUTEN Qi tendency due to
141 ! cumulus scheme precipitation (kg/kg/s)
143 !-- RAINC accumulated total cumulus scheme precipitation (mm)
144 !-- RAINCV time-step cumulus scheme precipitation (mm)
145 !-- PRATEC precipitiation rate from cumulus scheme (mm/s)
146 !-- NCA counter of the cloud relaxation
147 ! time in KF cumulus scheme (integer)
148 !-- u_phy u-velocity interpolated to theta points (m/s)
149 !-- v_phy v-velocity interpolated to theta points (m/s)
150 !-- th_phy potential temperature (K)
151 !-- t_phy temperature (K)
152 !-- tsk skin temperature (K)
153 !-- tke_pbl turbulent kinetic energy from PBL scheme (m2/s2)
154 !-- ust u* in similarity theory (m/s)
155 !-- w vertical velocity (m/s)
156 !-- moist moisture array (4D - last index is species) (kg/kg)
157 !-- z height above sea level at middle of layers (m)
158 !-- z_at_w height above sea level at layer interfaces (m)
159 !-- dz8w dz between full levels (m)
160 !-- pblh planetary boundary layer height (m)
161 !-- mavail soil moisture availability
162 !-- p8w pressure at full levels (Pa)
163 !-- psfc surface pressure (Pa)
164 !-- p_phy pressure (Pa)
165 !-- pi_phy exner function (dimensionless)
166 ! points (dimensionless)
167 !-- hfx upward heat flux at surface (W/m2)
168 !-- qfx upward moisture flux at surface (kg/m2/s)
169 !-- RTHRATEN radiative temp forcing for Grell-Devenyi scheme
170 !-- RTHBLTEN PBL temp forcing for Grell-Devenyi scheme
171 !-- RQVBLTEN PBL moisture forcing for Grell-Devenyi scheme
178 !-- cldfra cloud fraction
179 !-- cldfra_mp_all cloud fraction
181 !-- W0AVG average vertical velocity, (for KF scheme) (m/s)
182 !-- kfeta_trigger namelist for KF trigger (=1, default; =2, moisture-advection-dependent trigger)
183 !-- rho density (kg/m^3)
184 !-- CLDEFI precipitation efficiency (for BMJ scheme) (dimensionless)
185 !-- STEPCU # of fundamental timesteps between convection calls
186 !-- XLAND land-sea mask (1.0 for land; 2.0 for water)
187 !-- LOWLYR index of lowest model layer above the ground
188 !-- XLV0 latent heat of vaporization constant
189 ! used in temperature dependent formula (J/kg)
190 !-- XLV1 latent heat of vaporization constant
191 ! used in temperature dependent formula (J/kg/K)
192 !-- XLS0 latent heat of sublimation constant
193 ! used in temperature dependent formula (J/kg)
194 !-- XLS1 latent heat of sublimation constant
195 ! used in temperature dependent formula (J/kg/K)
196 !-- R_d gas constant for dry air ( 287. J/kg/K)
197 !-- R_v gas constant for water vapor (461 J/k/kg)
198 !-- Cp specific heat at constant pressure (1004 J/k/kg)
199 !-- rvovrd R_v divided by R_d (dimensionless)
200 !-- G acceleration due to gravity (m/s^2)
201 !-- EP_1 constant for virtual temperature
202 ! (R_v/R_d - 1) (dimensionless)
203 !-- pi_phy the exner function, (p/p0)**(R/Cp) (none unit)
204 !-- evapcdp3d Evaporation of deep convective precipitation (kg/kg/s)
205 !-- icwmrdp3d Deep Convection in-cloud water mixing ratio (kg/m2)
206 !-- rprddp3d dq/dt due to deep convective rainout (kg/kg/s)
207 !-- ids start index for i in domain
208 !-- ide end index for i in domain
209 !-- jds start index for j in domain
210 !-- jde end index for j in domain
211 !-- kds start index for k in domain
212 !-- kde end index for k in domain
213 !-- ims start index for i in memory
214 !-- ime end index for i in memory
215 !-- jms start index for j in memory
216 !-- jme end index for j in memory
217 !-- kms start index for k in memory
218 !-- kme end index for k in memory
219 !-- i_start start indices for i in tile
220 !-- i_end end indices for i in tile
221 !-- j_start start indices for j in tile
222 !-- j_end end indices for j in tile
223 !-- kts start index for k in tile
224 !-- kte end index for k in tile
225 !-- num_tiles number of tiles
226 !-- HBOT index of lowest model layer with convection
227 !-- HTOP index of highest model layer with convection
228 !-- LBOT index of lowest model layer with convection
229 !-- LTOP index of highest model layer with convection
230 !-- KPBL layer index of the PBL
231 !-- periodic_x T/F this is using periodic lateral boundaries in the X direction
232 !-- periodic_y T/F this is using periodic lateral boundaries in the Y-direction
234 !======================================================================
235 INTEGER, INTENT(IN) :: ids, ide, jds, jde, kds, kde, ims, ime, jms, &
236 & jme, kms, kme, kts, kte, itimestep, num_tiles
237 LOGICAL :: periodic_x, periodic_y
238 TYPE(DOMAIN), INTENT(INOUT) :: grid
239 INTEGER, DIMENSION(num_tiles), INTENT(IN) :: i_start, i_end, j_start, &
241 INTEGER, INTENT(IN) :: ensdim, maxiens, maxens, maxens2, maxens3
242 INTEGER, OPTIONAL, INTENT(IN) :: cugd_avedx, clos_choice, &
243 & bl_pbl_physics, sf_sfclay_physics
244 INTEGER, INTENT(IN) :: cu_physics
245 INTEGER, INTENT(IN) :: stepcu
246 LOGICAL, INTENT(IN) :: warm_rain
247 !BSINGH:01/31/2013: Added for CAMZM
248 REAL, INTENT(IN), OPTIONAL :: pgcon, shal_pgcon, sas_mass_flux
249 INTEGER, INTENT(IN), OPTIONAL :: shalconv
250 INTEGER, DIMENSION(ims:ime, jms:jme), INTENT(IN) :: lowlyr
251 REAL, DIMENSION(ims:ime, kms:kme, jms:jme), INTENT(IN) :: z, dz8w, p8w&
252 & , p, pi, u, v, th, t, rho, w
253 REAL, DIMENSION(ims:ime, kms:kme, jms:jme), INTENT(IN) :: zd, dz8wd, &
255 REAL, DIMENSION(ims:ime, kms:kme, jms:jme), INTENT(OUT), OPTIONAL :: &
256 & evapcdp3d, icwmrdp3d, rprddp3d
257 REAL, DIMENSION(ims:ime, kms:kme, jms:jme), INTENT(IN), OPTIONAL :: &
258 & z_at_w, cldfra, cldfra_mp_all, tke_pbl
259 REAL, DIMENSION(ims:ime, kms:kme, jms:jme), INTENT(INOUT) :: w0avg
260 REAL, DIMENSION(ims:ime, jms:jme), INTENT(IN) :: gsw, ht, xland
261 REAL, DIMENSION(ims:ime, jms:jme), INTENT(INOUT) :: rainc, raincv, nca&
262 & , htop, hbot, cldefi
263 REAL, DIMENSION(ims:ime, jms:jme), INTENT(INOUT) :: raincvd
264 REAL, DIMENSION(kms:kme), OPTIONAL, INTENT(IN) :: znu
265 REAL, DIMENSION(ims:ime, jms:jme), INTENT(INOUT), OPTIONAL :: pratec, &
266 & mavail, pblh, psfc, tsk, tpert2d, ust, hfx, qfx
267 REAL, DIMENSION(ims:ime, jms:jme), INTENT(INOUT), OPTIONAL :: pratecd
268 REAL, DIMENSION(ims:ime, jms:jme) :: tmppratec
269 REAL, DIMENSION(ims:ime, jms:jme) :: tmppratecd
270 INTEGER, DIMENSION(ims:ime, jms:jme), INTENT(IN) :: kpbl
271 LOGICAL, DIMENSION(ims:ime, jms:jme), INTENT(INOUT) :: cu_act_flag
272 INTEGER, INTENT(IN), OPTIONAL :: kfeta_trigger
273 REAL, INTENT(IN) :: dt, dx
274 INTEGER, INTENT(IN), OPTIONAL :: ips, ipe, jps, jpe, kps, kpe, &
275 & imomentum, ishallow
276 REAL, INTENT(IN), OPTIONAL :: cudt
277 REAL, INTENT(IN), OPTIONAL :: curr_secs
278 LOGICAL, INTENT(IN), OPTIONAL :: adapt_step_flag
279 REAL, INTENT(INOUT), OPTIONAL :: cudtacttime
280 REAL :: cudt_pass, curr_secs_pass, cudtacttime_pass
281 LOGICAL :: adapt_step_flag_pass
282 INTEGER, INTENT(IN), OPTIONAL :: mp_physics
283 REAL, DIMENSION(ims:ime, jms:jme), OPTIONAL, INTENT(IN) :: store_rand
285 REAL, OPTIONAL, INTENT(INOUT) :: mommix
286 !Kwon for sas2010 shallow convection
287 REAL, DIMENSION(ims:ime, jms:jme), OPTIONAL, INTENT(INOUT) :: hpbl2d, &
290 REAL, DIMENSION(ims:ime, kms:kme, jms:jme), INTENT(INOUT) :: rucuten, &
295 INTEGER, DIMENSION(ims:ime, jms:jme), OPTIONAL, INTENT(INOUT) :: &
296 & k22_shallow, kbcon_shallow, ktop_shallow, ideep2d, jt2d, maxg2d, &
298 INTEGER, DIMENSION(ims:ime, jms:jme), OPTIONAL, INTENT(OUT) :: &
300 ! optional moisture tracers
301 ! 2 time levels; if only one then use CURR
302 ! optional moisture and other tendencies
303 REAL, DIMENSION(ims:ime, kms:kme, jms:jme), OPTIONAL, INTENT(INOUT) ::&
304 & qv_curr, qc_curr, qr_curr, qi_curr, qs_curr, qg_curr, qv_prev, qc_prev&
305 & , qr_prev, qi_prev, qs_prev, qg_prev, rqvcuten, rqccuten, rqrcuten, &
306 & rqicuten, rqscuten, rqgcuten, rqcncuten, rqincuten, rqvblten, rqvften&
307 & , rthraten, rthblten, cugd_tten, cugd_qvten, cugd_qcten, cugd_ttens, &
308 & cugd_qvtens, forcet, forceq, rthften, rthcuten
309 REAL, DIMENSION(ims:ime, kms:kme, jms:jme), OPTIONAL, INTENT(INOUT) ::&
310 & qv_currd, rqvcutend, rthcutend
311 REAL, DIMENSION(ims:ime, jms:jme), OPTIONAL, INTENT(INOUT) :: apr_gr, &
312 & apr_w, apr_mc, apr_st, apr_as, apr_capma, apr_capme, apr_capmi, &
313 & edt_out, xmb_shallow, mass_flux, cape, pconvb, pconvt, preccdzm, precz&
315 REAL, DIMENSION(ims:ime, kms:kme, jms:jme), OPTIONAL, INTENT(INOUT) ::&
316 & gd_cloud, gd_cloud2, zmmd, zmmu, zmdt, zmdq, dlf, evaptzm, fzsntzm, &
317 & evsntzm, evapqzm, zmflxprc, zmflxsnw, zmntprpd, zmntsnpd, zmeiheat, &
318 & cmfmc, cmfmcdzm, zmmtu, zmmtv, zmupgu, zmupgd, zmvpgu, zmvpgd, zmicuu&
319 & , zmicud, zmicvu, zmicvd, zmdice, zmdliq, dp3d, du3d, ed3d, eu3d, md3d&
321 REAL, DIMENSION(ims:ime, jms:jme, ensdim), OPTIONAL, INTENT(INOUT) :: &
323 REAL, DIMENSION(ims:ime, kms:kme, jms:jme), OPTIONAL, INTENT(INOUT) ::&
324 & cfu1, cfd1, dfu1, efu1, dfd1, efd1
326 ! Flags relating to the optional tendency arrays declared above
327 ! Models that carry the optional tendencies will provdide the
328 ! optional arguments at compile time; these flags all the model
329 ! to determine at run-time whether a particular tracer is in
332 LOGICAL, INTENT(IN), OPTIONAL :: f_qv, f_qc, f_qr, f_qi, f_qs, f_qg
333 LOGICAL, INTENT(IN), OPTIONAL :: f_flux
335 INTEGER :: i, j, k, its, ite, jts, jte, ij, trigger_kf
337 LOGICAL :: decided, run_param, doing_adapt_dt
338 !-----------------------------------------------------------------
340 IF (PRESENT(f_flux)) l_flux = f_flux
341 IF (.NOT.PRESENT(curr_secs)) THEN
344 curr_secs_pass = curr_secs
346 IF (.NOT.PRESENT(cudt)) THEN
348 cudtacttime_pass = -1
351 cudtacttime_pass = cudtacttime
353 IF (.NOT.PRESENT(adapt_step_flag)) THEN
354 adapt_step_flag_pass = .false.
356 adapt_step_flag_pass = adapt_step_flag
358 ! Initialize tmppratec to pratec
359 IF (PRESENT(pratec)) THEN
360 tmppratecd(:, :) = pratecd(:, :)
361 tmppratec(:, :) = pratec(:, :)
366 IF (.NOT.PRESENT(kfeta_trigger)) THEN
369 trigger_kf = kfeta_trigger
371 IF (cu_physics .EQ. 0) THEN
374 ! Initialization for adaptive time step.
375 IF (adapt_step_flag_pass) THEN
376 doing_adapt_dt = .true.
377 IF (cudtacttime_pass .EQ. 0.) cudtacttime_pass = curr_secs_pass + &
380 doing_adapt_dt = .false.
382 ! Do we run through this scheme or not?
383 ! Test 1: If this is the initial model time, then yes.
385 ! Test 2: If the user asked for the cumulus to be run every time step, then yes.
387 ! Test 3: If not adaptive dt, and this is on the requested cumulus frequency, then yes.
388 ! MOD(ITIMESTEP,STEPCU)=0
389 ! Test 4: If using adaptive dt and the current time is past the last requested activate cumulus time, then yes.
390 ! CURR_SECS >= CUDTACTTIME
391 ! If we do run through the scheme, we set the flag run_param to TRUE and we set the decided flag
392 ! to TRUE. The decided flag says that one of these tests was able to say "yes", run the scheme.
393 ! We only proceed to other tests if the previous tests all have left decided as FALSE.
394 ! If we set run_param to TRUE and this is adaptive time stepping, we set the time to the next
398 IF (.NOT.decided .AND. itimestep .EQ. 1) THEN
402 IF (.NOT.decided .AND. (cudt_pass .EQ. 0. .OR. stepcu .EQ. 1)) THEN
406 IF (.NOT.decided .AND. (.NOT.doing_adapt_dt) .AND. MOD(itimestep, &
407 & stepcu) .EQ. 0) THEN
411 IF (.NOT.decided .AND. doing_adapt_dt .AND. curr_secs_pass .GE. &
412 & cudtacttime_pass) THEN
415 cudtacttime_pass = curr_secs_pass + cudt_pass*60
418 ! DON'T JUDGE TIME STEP HERE, SINCE KF NEEDS ACCUMULATED W FIELD.
419 ! DO IT INSIDE THE INDIVIDUAL CUMULUS SCHEME
420 ! SET START AND END POINTS FOR TILES
422 !$OMP PRIVATE ( ij ,its,ite,jts,jte, i,j,k)
428 SELECT CASE (cu_physics)
430 CALL WRF_DEBUG(100, 'in ducu')
431 ! order independent arguments
451 CALL DUCU_D(ids=ids, ide=ide, jds=jds, jde=jde, kds=kds, kde=&
452 & kde, ims=ims, ime=ime, jms=jms, jme=jme, kms=kms, kme=&
453 & kme, its=its, ite=ite, jts=jts, jte=jte, kts=kts, kte=&
454 & kte, dt=dt, ktau=itimestep, dx=dx, rho=rho, rhod=rhod, &
455 & raincv=raincv, raincvd=raincvd, nca=nca, pratec=&
456 & tmppratec, pratecd=tmppratecd, u=u, v=v, th=th, thd=thd&
457 & , t=t, td=td, w=w, dz8w=dz8w, dz8wd=dz8wd, z=z, zd=zd, &
458 & pcps=p, pcpsd=pd, pi=pi, w0avg=w0avg, cp=cp, rd=r_d, rv=&
459 & r_v, g=g, xlv=xlv0, ep2=ep_2, svp1=svp1, svp2=svp2, svp3&
460 & =svp3, svpt0=svpt0, stepcu=stepcu, cu_act_flag=&
461 & cu_act_flag, warm_rain=warm_rain, cutop=htop, cubot=hbot&
462 & , qv=qv_curr, qvd=qv_currd, rthcuten=rthcuten, rthcutend&
463 & =rthcutend, rqvcuten=rqvcuten, rqvcutend=rqvcutend)
466 WRITE(wrf_err_message, *) &
467 & 'The cumulus option does not exist: cu_physics = ', cu_physics
468 CALL WRF_ERROR_FATAL(wrf_err_message)
471 !$OMP END PARALLEL DO
472 ! Copy pratec back to output array, if necessary.
473 IF (PRESENT(pratec)) THEN
474 pratecd(:, :) = tmppratecd(:, :)
475 pratec(:, :) = tmppratec(:, :)
477 ! Copy cudtacttime back if necessary
478 IF (PRESENT(cudtacttime)) cudtacttime = cudtacttime_pass
479 CALL WRF_DEBUG(200, 'returning from cumulus_driver')
481 !print *,'calling CU scheme'
482 !print *,'NOT calling CU scheme'
486 END SUBROUTINE G_CUMULUS_DRIVER
487 END MODULE g_module_cumulus_driver