source: lmdz_wrf/WRFV3/phys/module_shallowcu_driver.F @ 1

Last change on this file since 1 was 1, checked in by lfita, 10 years ago
  • -- --- Opening of the WRF+LMDZ coupling repository --- -- -

WRF: version v3.3
LMDZ: version v1818

More details in:

File size: 17.9 KB
Line 
1!WRF:MEDIATION_LAYER:PHYSICS
2!
3
4MODULE module_shallowcu_driver
5CONTAINS
6   SUBROUTINE shallowcu_driver(                                       &
7                 ! Order dependent args for domain, mem, and tile dims
8                      ids,ide, jds,jde, kds,kde                       &
9                     ,ims,ime, jms,jme, kms,kme                       &
10                     ,ips,ipe, jps,jpe, kps,kpe                       &
11                     ,i_start,i_end,j_start,j_end,kts,kte,num_tiles   &
12                 ! Order independent args (use VAR= in call)
13                 ! --Prognostic
14                     ,u,v,th,t                                        &
15                     ,p,pi,rho,moist                                  &
16                 ! --Other arguments
17                     ,num_moist                                       &
18                     ,itimestep,dt,dx,cudt,curr_secs,adapt_step_flag  &
19                     ,rainsh,pratesh,nca,rainshv                      &
20                     ,z,z_at_w,dz8w,mavail,pblh,p8w                   &
21                     ,tke_pbl                                         &
22                     ,cldfra,cldfra_old,cldfrash                      &
23                     ,htop,hbot     &
24                 ! Package selection variables
25                     ,shcu_physics                                    &
26                 ! Optional moisture tracers
27                     ,qv_curr, qc_curr, qr_curr                       &
28                     ,qi_curr, qs_curr, qg_curr                       &
29                 ! Optional output arguments for CAMZM scheme
30                     ,dlf, rliq, rliq2  &
31                     ,cmfmc, cmfmc2       &
32                 ! Optional output arguments for CAMUW scheme
33                     ,cush, snowsh, icwmrsh, rprdsh, cbmf, cmfsl      &
34                     ,cmflq, evapcsh                                  &
35                 ! Optional moisture and other tendencies
36                     ,rqvshten,rqcshten,rqrshten                      &
37                     ,rqishten,rqsshten,rqgshten                      &
38                     ,rqvblten,rqvften                                &
39                     ,rushten,rvshten                                 &
40                     ,rthshten,rthraten,rthblten,rthften              &
41                 ! Optional moisture tracer flags
42                     ,f_qv,f_qc,f_qr                                  &
43                     ,f_qi,f_qs,f_qg                                  &
44                     ,ht                                              &
45                                                                      )
46!----------------------------------------------------------------------
47   USE module_model_constants
48   USE module_state_description, ONLY: CAMUWSHCUSCHEME, G3SHCUSCHEME
49
50! *** add new modules of schemes here
51
52   USE module_cu_camuwshcu_driver, ONLY : camuwshcu_driver
53   USE module_dm
54   USE module_domain, ONLY: domain
55
56   !  This driver calls subroutines for the shallow cumulus
57   !  parameterizations.
58   !
59   !  1. G3 shallow cumulus
60   !  2. UW shallow cumulus from CAM
61   !
62!----------------------------------------------------------------------
63   IMPLICIT NONE
64!======================================================================
65! Grid structure in physics part of WRF
66!----------------------------------------------------------------------
67! The horizontal velocities used in the physics are unstaggered
68! relative to temperature/moisture variables. All predicted
69! variables are carried at half levels except w, which is at full
70! levels. Some arrays with names (*8w) are at w (full) levels.
71!
72!----------------------------------------------------------------------
73! In WRF, kms (smallest number) is the bottom level and kme (largest
74! number) is the top level.  In your scheme, if 1 is at the top level,
75! then you have to reverse the order in the k direction.
76!
77!         kme      -   half level (no data at this level)
78!         kme    ----- full level
79!         kme-1    -   half level
80!         kme-1  ----- full level
81!         .
82!         .
83!         .
84!         kms+2    -   half level
85!         kms+2  ----- full level
86!         kms+1    -   half level
87!         kms+1  ----- full level
88!         kms      -   half level
89!         kms    ----- full level
90!
91!======================================================================
92! Definitions
93!-----------
94! Rho_d      dry density (kg/m^3)
95! Theta_m    moist potential temperature (K)
96! Qv         water vapor mixing ratio (kg/kg)
97! Qc         cloud water mixing ratio (kg/kg)
98! Qr         rain water mixing ratio (kg/kg)
99! Qi         cloud ice mixing ratio (kg/kg)
100! Qs         snow mixing ratio (kg/kg)
101!-----------------------------------------------------------------
102!-- DT            time step (second)
103!-- CUDT          cumulus time step (minute)
104!-- curr_secs     current forecast time (seconds)
105!-- itimestep     number of time step (integer)   
106!-- DX            horizontal space interval (m)
107!-- rr            dry air density (kg/m^3)
108!
109!-- RUSHTEN       Zonal wind tendency due to shallow
110!                 cumulus scheme precipitation (m/s/s)
111!-- RVSHTEN       Meridional wind tendency due to
112!                 cumulus scheme precipitation (m/s/s)
113!-- RTHSHTEN      Theta tendency due to shallow
114!                 cumulus scheme precipitation (K/s)
115!-- RQVSHTEN      Qv tendency due to shallow
116!                 cumulus scheme precipitation (kg/kg/s)
117!-- RQRSHTEN      Qr tendency due to shallow
118!                 cumulus scheme precipitation (kg/kg/s)
119!-- RQCSHTEN      Qc tendency due to shallow
120!                 cumulus scheme precipitation (kg/kg/s)
121!-- RQSSHTEN      Qs tendency due to shallow
122!                 cumulus scheme precipitation (kg/kg/s)
123!-- RQISHTEN      Qi tendency due to shallow
124!                 cumulus scheme precipitation (kg/kg/s)
125!-- RQGSHTEN      Qg tendency due to shallow
126!                 cumulus scheme precipitation (kg/kg/s)
127!
128!-- RAINSH        accumulated total shallow cumulus scheme precipitation (mm)
129!-- RAINSHV       time-step shallow cumulus scheme precipitation (mm)
130!-- PRATESH       precipitiation rate from shallow cumulus scheme (mm/s)
131!-- NCA           counter of the cloud relaxation
132!                 time in KF cumulus scheme (integer)
133!-- u_phy         u-velocity interpolated to theta points (m/s)
134!-- v_phy         v-velocity interpolated to theta points (m/s)
135!-- th_phy        potential temperature (K)
136!-- t_phy         temperature (K)
137!-- tke_pbl       turbulent kinetic energy from PBL scheme (m2/s2)
138!-- w             vertical velocity (m/s)
139!-- moist         moisture array (4D - last index is species) (kg/kg)
140!-- z             height above sea level at middle of layers (m)
141!-- z_at_w        height above sea level at layer interfaces (m)
142!-- dz8w          dz between full levels (m)
143!-- pblh          planetary boundary layer height (m)
144!-- mavail        soil moisture availability
145!-- p8w           pressure at full levels (Pa)
146!-- p_phy         pressure (Pa)
147!-- pi_phy        the exner function, (p/p0)**(R/Cp) (dimensionless)
148!                 points (dimensionless)
149!-- hfx           upward heat flux at surface (W/m2)
150!-- RTHRATEN      radiative temp forcing for Grell-Devenyi scheme
151!-- RTHBLTEN      PBL temp forcing for Grell-Devenyi scheme
152!-- RQVBLTEN      PBL moisture forcing for Grell-Devenyi scheme
153!-- RTHFTEN
154!-- RQVFTEN
155!-- cldfra        cloud fraction
156!-- cldfra_old    cloud fraction from previous time step
157!-- cldfrash      cloud fraction from shallow Cu
158!-- rho           density (kg/m^3)
159!-- XLV0          latent heat of vaporization constant
160!                 used in temperature dependent formula (J/kg)
161!-- XLV1          latent heat of vaporization constant
162!                 used in temperature dependent formula (J/kg/K)
163!-- XLS0          latent heat of sublimation constant
164!                 used in temperature dependent formula (J/kg)
165!-- XLS1          latent heat of sublimation constant
166!                 used in temperature dependent formula (J/kg/K)
167!-- R_d           gas constant for dry air ( 287. J/kg/K)
168!-- R_v           gas constant for water vapor (461 J/k/kg)
169!-- Cp            specific heat at constant pressure (1004 J/k/kg)
170!-- rvovrd        R_v divided by R_d (dimensionless)
171!-- G             acceleration due to gravity (m/s^2)
172!-- EP_1          constant for virtual temperature
173!                 (R_v/R_d - 1) (dimensionless)
174!-- ids           start index for i in domain
175!-- ide           end index for i in domain
176!-- jds           start index for j in domain
177!-- jde           end index for j in domain
178!-- kds           start index for k in domain
179!-- kde           end index for k in domain
180!-- ims           start index for i in memory
181!-- ime           end index for i in memory
182!-- jms           start index for j in memory
183!-- jme           end index for j in memory
184!-- kms           start index for k in memory
185!-- kme           end index for k in memory
186!-- i_start       start indices for i in tile
187!-- i_end         end indices for i in tile
188!-- j_start       start indices for j in tile
189!-- j_end         end indices for j in tile
190!-- kts           start index for k in tile
191!-- kte           end index for k in tile
192!-- num_tiles     number of tiles
193!-- HBOT          index of lowest model layer with convection
194!-- HTOP          index of highest model layer with convection
195!-- LBOT          index of lowest model layer with convection
196!-- LTOP          index of highest model layer with convection
197!-- periodic_x    T/F this is using periodic lateral boundaries in the X direction
198!-- periodic_y    T/F this is using periodic lateral boundaries in the Y-direction
199!
200!======================================================================
201
202   INTEGER,      INTENT(IN   )    ::                             &
203                                      ids,ide, jds,jde, kds,kde, &
204                                      ims,ime, jms,jme, kms,kme, &
205                                                        kts,kte, &
206                                      itimestep, num_tiles
207
208   INTEGER, DIMENSION(num_tiles), INTENT(IN) ::                       &
209     &           i_start,i_end,j_start,j_end
210
211   INTEGER,      INTENT(IN   )    ::                             &
212                  num_moist
213
214   INTEGER,      INTENT(IN   )    ::               shcu_physics
215
216   REAL, DIMENSION( ims:ime, kms:kme, jms:jme, num_moist ),      &
217         INTENT(INOUT)  ::                                       &
218                                                          moist
219
220   REAL, DIMENSION( ims:ime, kms:kme, jms:jme ),                 &
221         INTENT(IN ) ::                                          &
222                                                         cldfra  &
223                                                    ,cldfra_old  &
224                                                      ,       z  &
225                                                      ,  z_at_w  &
226                                                      ,    dz8w  &
227                                                      ,     p8w  &
228                                                      ,       p  &
229                                                      ,      pi  &
230                                                      ,       u  &
231                                                      ,       v  &
232                                                      ,      th  &
233                                                      ,       t  &
234                                                      , tke_pbl  &
235                                                      ,     rho
236
237
238   REAL, DIMENSION( ims:ime , jms:jme ), INTENT(IN) ::           &
239                  MAVAIL,PBLH,ht
240
241   REAL, DIMENSION( ims:ime , jms:jme ),                         &
242          INTENT(INOUT) ::                               RAINSH  &
243                                                    ,       NCA  &
244                                                    ,      HTOP  &
245                                                    ,      HBOT
246 
247
248   REAL, DIMENSION( ims:ime , jms:jme ),INTENT(INOUT),OPTIONAL :: &
249        PRATESH, RAINSHV
250   REAL, DIMENSION( ims:ime , jms:jme ) :: tmppratesh
251                                                   
252   REAL,  INTENT(IN   ) :: DT, DX
253   INTEGER,      INTENT(IN   ),OPTIONAL    ::                             &
254                                      ips,ipe, jps,jpe, kps,kpe
255   REAL,  INTENT(IN   ),OPTIONAL :: CUDT
256   REAL,  INTENT(IN   ),OPTIONAL :: CURR_SECS
257   LOGICAL,INTENT(IN   ),OPTIONAL    ::     adapt_step_flag
258   REAL   :: cudt_pass, curr_secs_pass
259   LOGICAL :: adapt_step_flag_pass
260
261!
262! optional arguments
263!
264   REAL, DIMENSION( ims:ime, kms:kme, jms:jme ),                 &
265         OPTIONAL, INTENT(INOUT) ::                              &
266                      ! optional moisture tracers
267                      qv_curr, qc_curr, qr_curr                  &
268                     ,qi_curr, qs_curr, qg_curr                  &
269                      ! optional moisture and other tendencies
270                     ,rqvshten,rqcshten,rqrshten                 &
271                     ,rqishten,rqsshten,rqgshten                 &
272                     ,rqvblten,rqvften                           &
273                     ,rthraten,rthblten                          &
274                     ,rthften,rushten,rvshten,rthshten
275
276   REAL, DIMENSION( ims:ime , jms:jme ),                         &
277                    OPTIONAL, INTENT(INOUT) ::                   &
278                rliq, rliq2 &
279               ,cbmf, cush, snowsh
280   REAL, DIMENSION( ims:ime, kms:kme, jms:jme ),                 &
281         OPTIONAL, INTENT(INOUT) ::                              &
282                  cldfrash, cmfsl, cmflq, icwmrsh,               &
283                  dlf, evapcsh,                                  &
284                  cmfmc, cmfmc2, rprdsh
285!
286! Flags relating to the optional tendency arrays declared above
287! Models that carry the optional tendencies will provdide the
288! optional arguments at compile time; these flags all the model
289! to determine at run-time whether a particular tracer is in
290! use or not.
291!
292   LOGICAL, INTENT(IN), OPTIONAL ::                             &
293                                                      f_qv      &
294                                                     ,f_qc      &
295                                                     ,f_qr      &
296                                                     ,f_qi      &
297                                                     ,f_qs      &
298                                                     ,f_qg
299
300
301! LOCAL  VAR
302
303   INTEGER :: i,j,k,its,ite,jts,jte,ij
304   CHARACTER(len=200) :: message
305
306!-----------------------------------------------------------------
307
308   if (.not. PRESENT(CURR_SECS)) then
309      curr_secs_pass = -1
310   else
311      curr_secs_pass = curr_secs
312   endif
313
314   if (.not. PRESENT(CUDT)) then
315      cudt_pass = -1
316   else
317      cudt_pass = cudt
318   endif
319
320   if (.not. PRESENT(adapt_step_flag)) then
321      adapt_step_flag_pass = .false.
322   else
323      adapt_step_flag_pass = adapt_step_flag
324   endif
325
326   ! Initialize tmppratesh to pratesh
327
328   if ( PRESENT ( pratesh ) ) then
329      tmppratesh(:,:) = pratesh(:,:)
330   else
331      tmppratesh(:,:) = 0.
332   end if
333
334
335   IF (shcu_physics .eq. 0) return
336
337! DON'T JUDGE TIME STEP HERE, SINCE KF NEEDS ACCUMULATED W FIELD.
338! DO IT INSIDE THE INDIVIDUAL CUMULUS SCHEME
339
340! SET START AND END POINTS FOR TILES
341!$OMP PARALLEL DO   &
342!$OMP PRIVATE ( ij ,its,ite,jts,jte, i,j,k)
343   DO ij = 1 , num_tiles
344      its = i_start(ij)
345      ite = i_end(ij)
346      jts = j_start(ij)
347      jte = j_end(ij)
348
349
350   scps_select: SELECT CASE(shcu_physics)
351
352   CASE (G3SHCUSCHEME)
353      ! This setting takes the place of ishallow in v3.1.1+
354
355   CASE (CAMUWSHCUSCHEME)
356      CALL wrf_debug(100,'in camuw_scps')
357      IF(.not.f_qi)THEN
358         WRITE( message , * ) 'This shallow cumulus option requires ice microphysics option: f_qi = ', f_qi
359         CALL wrf_error_fatal ( message )
360      ENDIF
361      CALL camuwshcu_driver(                                             &
362            IDS=ids,IDE=ide,JDS=jds,JDE=jde,KDS=kds,KDE=kde              &
363           ,IMS=ims,IME=ime,JMS=jms,JME=jme,KMS=kms,KME=kme              &
364           ,ITS=its,ITE=ite,JTS=jts,JTE=jte,KTS=kts,KTE=kte              &
365           ,NUM_MOIST=num_moist, DT=dt                                   &
366           ,P=p, P8W=p8w, PI_PHY=pi                                      &
367           ,Z=z, Z_AT_W=z_at_w, DZ8W=dz8w                                &
368           ,T_PHY=t, U_PHY=u, V_PHY=v                                    &
369           ,MOIST=moist, QV=qv_curr, QC=qc_curr, QI=qi_curr              &
370           ,PBLH_IN=pblh, TKE_PBL=tke_pbl                                &
371           ,CLDFRA=cldfra, CLDFRA_OLD=cldfra_old, CLDFRASH=cldfrash      &
372           ,CUSH_INOUT=cush, RAINSH=rainsh, PRATESH=tmppratesh           &
373           ,SNOWSH=snowsh                                                &
374           ,ICWMRSH=icwmrsh, CMFMC=cmfmc, CMFMC2_INOUT=cmfmc2            &
375           ,RPRDSH_INOUT=rprdsh, CBMF_INOUT=cbmf                         &
376           ,CMFSL=cmfsl, CMFLQ=cmflq, DLF=dlf, EVAPCSH_INOUT=evapcsh     &
377           ,RLIQ=rliq, RLIQ2_INOUT=rliq2, CUBOT=hbot, CUTOP=htop         &
378           ,RUSHTEN=rushten, RVSHTEN=rvshten, RTHSHTEN=rthshten          &
379           ,RQVSHTEN=rqvshten, RQCSHTEN=rqcshten, RQRSHTEN=rqrshten      &
380           ,RQISHTEN=rqishten, RQSSHTEN=rqsshten, RQGSHTEN=rqgshten      &
381           ,HT=ht                                                        &                                                 
382                                                                         )
383
384   CASE DEFAULT
385      WRITE( message , * ) 'The shallow cumulus option does not exist: shcu_physics = ', shcu_physics
386      CALL wrf_error_fatal ( message )
387
388   END SELECT scps_select
389
390   ENDDO
391   !$OMP END PARALLEL DO
392
393   !
394   ! Copy pratesh back to output array, if necessary.
395   !
396   if (PRESENT(PRATESH)) then
397      pratesh(:,:) = tmppratesh(:,:)
398      if (PRESENT(RAINSHV)) then
399         rainshv(:,:) = pratesh(:,:)*dt
400      endif
401   endif
402
403   END SUBROUTINE shallowcu_driver
404
405END MODULE module_shallowcu_driver
Note: See TracBrowser for help on using the repository browser.