Merge remote-tracking branch 'origin/release-v4.6.1'
[WRF.git] / phys / module_ltng_cpmpr92z.F
blob4b1117f48c6b25d33793c17809fb1fbe552a94c3
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, 2013: Evaluating a lightning parameterization 
10 !   based on cloud-top height for mesoscale numerical model simulations, 
11 !   Geosci. Model Dev., 6, 429–443, https://doi.org/10.5194/gmd-6-429-2013.
13 !**********************************************************************
15  MODULE module_ltng_cpmpr92z
16  CONTAINS
18  SUBROUTINE ltng_cpmpr92z ( &
19                           ! Frequently used prognostics
20                             dx, dy, xland, ht, z, t,              &
21                           ! Scheme specific prognostics
22                             kLNB,                                 &
23                           ! Scheme specific namelist inputs
24                             cldtop_adjustment,                    &
25                           ! Order dependent args for domain, mem, and tile dims
26                             ids, ide, jds, jde, kds, kde,         &
27                             ims, ime, jms, jme, kms, kme,         &
28                             ips, ipe, jps, jpe, kps, kpe,         &
29                           ! Mandatory output for all quantitative schemes
30                             total_flashrate                       &
31                           )
32 !-----------------------------------------------------------------
33 ! Framework
34  USE module_state_description
36 ! Model layer
37  USE module_model_constants
38  USE module_wrf_error
40  IMPLICIT NONE
41 !-----------------------------------------------------------------
43 ! Frequently used prognostics
44  REAL,    INTENT(IN   )    ::       dx, dy
46  REAL,    DIMENSION( ims:ime,          jms:jme ), INTENT(IN   ) :: xland, ht
47  REAL,    DIMENSION( ims:ime, kms:kme, jms:jme ), INTENT(IN   ) :: z, t
49 ! Scheme specific prognostics
50  INTEGER, DIMENSION( ims:ime,          jms:jme ), INTENT(IN   ) :: kLNB     ! model LNB from cu_physics
52 ! Scheme specific namelist inputs
53  REAL,    INTENT(IN   )    ::       cldtop_adjustment
55 ! Order dependent args for domain, mem, and tile dims
56  INTEGER, INTENT(IN   )    ::       ids,ide, jds,jde, kds,kde
57  INTEGER, INTENT(IN   )    ::       ims,ime, jms,jme, kms,kme
58  INTEGER, INTENT(IN   )    ::       ips,ipe, jps,jpe, kps,kpe
60 ! Mandatory outputs for all quantitative schemes
61  REAL,    DIMENSION( ims:ime,          jms:jme ), INTENT(  OUT) :: total_flashrate
63 ! Local variables
64  REAL :: dA              ! grid area dx*dy in km2
65  REAL :: zkm             ! AGL z in km
67  REAL, PARAMETER:: baseArea=1296. ! base-case area, dx = 36 km
69  INTEGER :: i,k,j
71  CHARACTER (LEN=250) :: message
73 !-----------------------------------------------------------------
75  dA = dx*dy/1E6
77  total_flashrate( ips:ipe,jps:jpe ) = 0.
79 ! Compute AGL heights in km
80  jloop: DO j=jps,jpe
81     iloop: DO i=ips,ipe
82         IF ( t(i,kLNB(i,j),j) .lt. 273.15 .and. &
83             kLNB(i,j) .ge. kps .and. kLNB(i,j) .le. kpe ) THEN              ! Cloud top must freeze
84             zkm = ( z(i,kLNB(i,j),j) - ht(i,j) )/1E3 + cldtop_adjustment    ! Compute AGL height in km
85             IF ( zkm .gt. 0. ) THEN                                         ! Must be above ground
86               IF ( xland(i,j) .lt. 1.5 ) THEN
87                 total_flashrate(i,j) = 3.44E-5 * (zkm**4.9) /60.            ! Continental equation
88               ELSE
89                 total_flashrate(i,j) = 6.57E-6 * (zkm**4.9) /60.            ! Marine equation (Michalon 99)
90               ENDIF
91             ENDIF
92         ENDIF
93     ENDDO iloop
94  ENDDO jloop
96 ! Scale by areal ratio
97  total_flashrate(ips:ipe,jps:jpe) = total_flashrate(ips:ipe,jps:jpe) * dA/baseArea
99  END SUBROUTINE ltng_cpmpr92z
101  END MODULE module_ltng_cpmpr92z