updated top-level README and version_decl for V4.5 (#1847)
[WRF.git] / phys / module_ltng_cpmpr92z.F
blobf93f55c37daccf1eeb1d87112fc96206efa6e8bd
1 ! WRF:MODEL_LAYER:PHYSICS
3 ! Lightning flash rate prediction based on cloud-top height. Implemented
4 ! for models using convective parameterization. Assume use of sub-grid LNB.
6 ! Price, C., and D. Rind (1992), A Simple Lightning Parameterization for Calculating
7 !   Global Lightning Distributions, J. Geophys. Res., 97(D9), 9919-9933, doi:10.1029/92JD00719.
9 ! Wong, J., M. Barth, and D. Noone (2012), Evaluating a Lightning Parameterization
10 !   at Resolutions with Partially-Resolved Convection, GMDD, in preparation.
12 ! Contact: J. Wong <johnwong@ucar.edu>
14 !**********************************************************************
16  MODULE module_ltng_cpmpr92z
17  CONTAINS
19  SUBROUTINE ltng_cpmpr92z ( &
20                           ! Frequently used prognostics
21                             dx, dy, xland, ht, z, t,              &
22                           ! Scheme specific prognostics
23                             kLNB,                                 &
24                           ! Scheme specific namelist inputs
25                             cldtop_adjustment,                    &
26                           ! Order dependent args for domain, mem, and tile dims
27                             ids, ide, jds, jde, kds, kde,         &
28                             ims, ime, jms, jme, kms, kme,         &
29                             ips, ipe, jps, jpe, kps, kpe,         &
30                           ! Mandatory output for all quantitative schemes
31                             total_flashrate                       &
32                           )
33 !-----------------------------------------------------------------
34 ! Framework
35  USE module_state_description
37 ! Model layer
38  USE module_model_constants
39  USE module_wrf_error
41  IMPLICIT NONE
42 !-----------------------------------------------------------------
44 ! Frequently used prognostics
45  REAL,    INTENT(IN   )    ::       dx, dy
47  REAL,    DIMENSION( ims:ime,          jms:jme ), INTENT(IN   ) :: xland, ht
48  REAL,    DIMENSION( ims:ime, kms:kme, jms:jme ), INTENT(IN   ) :: z, t
50 ! Scheme specific prognostics
51  INTEGER, DIMENSION( ims:ime,          jms:jme ), INTENT(IN   ) :: kLNB     ! model LNB from cu_physics
53 ! Scheme specific namelist inputs
54  REAL,    INTENT(IN   )    ::       cldtop_adjustment
56 ! Order dependent args for domain, mem, and tile dims
57  INTEGER, INTENT(IN   )    ::       ids,ide, jds,jde, kds,kde
58  INTEGER, INTENT(IN   )    ::       ims,ime, jms,jme, kms,kme
59  INTEGER, INTENT(IN   )    ::       ips,ipe, jps,jpe, kps,kpe
61 ! Mandatory outputs for all quantitative schemes
62  REAL,    DIMENSION( ims:ime,          jms:jme ), INTENT(  OUT) :: total_flashrate
64 ! Local variables
65  REAL :: dA              ! grid area dx*dy in km2
66  REAL :: zkm             ! AGL z in km
68  REAL, PARAMETER:: baseArea=1296. ! base-case area, dx = 36 km
70  INTEGER :: i,k,j
72  CHARACTER (LEN=250) :: message
74 !-----------------------------------------------------------------
76  dA = dx*dy/1E6
78  total_flashrate( ips:ipe,jps:jpe ) = 0.
80 ! Compute AGL heights in km
81  jloop: DO j=jps,jpe
82     iloop: DO i=ips,ipe
83         IF ( t(i,kLNB(i,j),j) .lt. 273.15 .and. &
84             kLNB(i,j) .ge. kps .and. kLNB(i,j) .le. kpe ) THEN              ! Cloud top must freeze
85             zkm = ( z(i,kLNB(i,j),j) - ht(i,j) )/1E3 + cldtop_adjustment    ! Compute AGL height in km
86             IF ( zkm .gt. 0. ) THEN                                         ! Must be above ground
87               IF ( xland(i,j) .lt. 1.5 ) THEN
88                 total_flashrate(i,j) = 3.44E-5 * (zkm**4.9) /60.            ! Continental equation
89               ELSE
90                 total_flashrate(i,j) = 6.57E-6 * (zkm**4.9) /60.            ! Marine equation (Michalon 99)
91               ENDIF
92             ENDIF
93         ENDIF
94     ENDDO iloop
95  ENDDO jloop
97 ! Scale by areal ratio
98  total_flashrate(ips:ipe,jps:jpe) = total_flashrate(ips:ipe,jps:jpe) * dA/baseArea
100  END SUBROUTINE ltng_cpmpr92z
102  END MODULE module_ltng_cpmpr92z