source: LMDZ6/trunk/libf/phylmd/ecrad/ifs/liquid_effective_radius.F90 @ 4773

Last change on this file since 4773 was 4773, checked in by idelkadi, 7 months ago
  • Update of Ecrad in LMDZ The same organization of the Ecrad offline version is retained in order to facilitate the updating of Ecrad in LMDZ and the comparison between online and offline results. version 1.6.1 of Ecrad (https://github.com/lguez/ecrad.git)
  • Implementation of the double call of Ecrad in LMDZ


File size: 6.6 KB
Line 
1SUBROUTINE LIQUID_EFFECTIVE_RADIUS &
2     & (YDERAD,KIDIA, KFDIA, KLON, KLEV, &
3     &  PPRESSURE, PTEMPERATURE, PCLOUD_FRAC, PQ_LIQ, PQ_RAIN, &
4     &  PLAND_FRAC, PCCN_LAND, PCCN_SEA, &
5     &  PRE_UM) !, PPERT)
6
7! LIQUID_EFFECTIVE_RADIUS
8!
9! (C) Copyright 2015- ECMWF.
10!
11! This software is licensed under the terms of the Apache Licence Version 2.0
12! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
13!
14! In applying this licence, ECMWF does not waive the privileges and immunities
15! granted to it by virtue of its status as an intergovernmental organisation
16! nor does it submit to any jurisdiction.
17!
18! PURPOSE
19! -------
20!   Calculate effective radius of liquid clouds
21!
22! AUTHOR
23! ------
24!   Robin Hogan, ECMWF (using code extracted from radlswr.F90)
25!   Original: 2015-09-24
26!
27! MODIFICATIONS
28! -------------
29!
30!
31! -------------------------------------------------------------------
32
33USE PARKIND1 , ONLY : JPIM, JPRB
34USE YOMHOOK  , ONLY : LHOOK, DR_HOOK, JPHOOK
35USE YOERAD   , ONLY : TERAD
36USE YOERDU   , ONLY : REPLOG, REPSCW
37USE YOMLUN   , ONLY : NULERR
38USE YOMCST   , ONLY : RD, RPI
39
40! -------------------------------------------------------------------
41
42IMPLICIT NONE
43
44! INPUT ARGUMENTS
45
46! *** Array dimensions and ranges
47TYPE(TERAD)       ,INTENT(IN) :: YDERAD
48INTEGER(KIND=JPIM),INTENT(IN) :: KIDIA    ! Start column to process
49INTEGER(KIND=JPIM),INTENT(IN) :: KFDIA    ! End column to process
50INTEGER(KIND=JPIM),INTENT(IN) :: KLON     ! Number of columns
51INTEGER(KIND=JPIM),INTENT(IN) :: KLEV     ! Number of levels
52
53! *** Variables on model levels
54REAL(KIND=JPRB),   INTENT(IN) :: PPRESSURE(KLON,KLEV)    ! (Pa)
55REAL(KIND=JPRB),   INTENT(IN) :: PTEMPERATURE(KLON,KLEV) ! (K)
56REAL(KIND=JPRB),   INTENT(IN) :: PCLOUD_FRAC(KLON,KLEV)
57REAL(KIND=JPRB),   INTENT(IN) :: PQ_LIQ(KLON,KLEV)       ! (kg/kg)
58REAL(KIND=JPRB),   INTENT(IN) :: PQ_RAIN(KLON,KLEV)      ! (kg/kg)
59
60! *** Single-level variables
61REAL(KIND=JPRB),   INTENT(IN) :: PLAND_FRAC(KLON)        ! 1=land, 0=sea
62REAL(KIND=JPRB),   INTENT(IN) :: PCCN_LAND(KLON)
63REAL(KIND=JPRB),   INTENT(IN) :: PCCN_SEA(KLON)
64
65! OUTPUT ARGUMENT
66! Effective radius
67REAL(KIND=JPRB),  INTENT(OUT) :: PRE_UM(KLON,KLEV) ! (microns)
68
69! PARAMETERS
70
71! Minimum and maximum effective radius, in microns
72REAL(KIND=JPRB), PARAMETER :: PP_MIN_RE_UM =  4.0_JPRB
73REAL(KIND=JPRB), PARAMETER :: PP_MAX_RE_UM = 30.0_JPRB
74
75! LOCAL VARIABLES
76INTEGER(KIND=JPIM) :: IRADLP ! ID of effective radius scheme to use
77REAL(KIND=JPRB) :: ZCCN    ! CCN concentration (units?)
78
79REAL(KIND=JPRB) :: ZSPECTRAL_DISPERSION
80REAL(KIND=JPRB) :: ZNTOT_CM3 ! Number conc in cm-3
81REAL(KIND=JPRB) :: ZRE_CUBED
82REAL(KIND=JPRB) :: ZLWC_GM3, ZRWC_GM3 ! In-cloud liquid, rain content in g m-3
83REAL(KIND=JPRB) :: ZAIR_DENSITY_GM3   ! Air density in g m-3
84REAL(KIND=JPRB) :: ZRAIN_RATIO        ! Ratio of rain to liquid water content
85REAL(KIND=JPRB) :: ZWOOD_FACTOR, ZRATIO
86
87INTEGER(KIND=JPIM) :: JL, JK
88
89REAL(KIND=JPHOOK) :: ZHOOK_HANDLE
90
91! -------------------------------------------------------------------
92
93#include "abor1.intfb.h"
94
95! -------------------------------------------------------------------
96
97IF (LHOOK) CALL DR_HOOK('LIQUID_EFFECTIVE_RADIUS',0,ZHOOK_HANDLE)
98
99! -------------------------------------------------------------------
100
101IRADLP=YDERAD%NRADLP
102
103SELECT CASE(IRADLP)
104CASE(0)
105  ! Very old parameterization as a function of pressure, used in ERA-15
106  PRE_UM(KIDIA:KFDIA,:) = 10.0_JPRB&
107       &  + (100000.0_JPRB-PPRESSURE(KIDIA:KFDIA,:))*3.5_JPRB
108 
109CASE(1)
110  ! Simple distinction between land (10um) and ocean (13um) by Zhang
111  ! and Rossow
112  DO JL = KIDIA,KFDIA
113    IF (PLAND_FRAC(JL) < 0.5_JPRB) THEN
114      PRE_UM(JL,:) = 13.0_JPRB
115    ELSE
116      PRE_UM(JL,:) = 10.0_JPRB
117    ENDIF
118  ENDDO
119 
120CASE(2)
121  ! Martin et al. (JAS 1994)
122  DO JL = KIDIA,KFDIA
123    ! First compute the cloud droplet concentration
124    IF (PLAND_FRAC(JL) < 0.5_JPRB) THEN
125      ! Sea case
126      IF (YDERAD%LCCNO) THEN
127        ZCCN = PCCN_SEA(JL)
128      ELSE
129        ZCCN = YDERAD%RCCNSEA
130      ENDIF
131      ZSPECTRAL_DISPERSION = 0.77_JPRB
132      ! Cloud droplet concentration in cm-3 (activated CCN) over
133      ! ocean
134      ZNTOT_CM3 = -1.15E-03_JPRB*ZCCN*ZCCN + 0.963_JPRB*ZCCN + 5.30_JPRB
135    ELSE
136      ! Land case
137      IF (YDERAD%LCCNL) THEN
138        ZCCN=PCCN_LAND(JL)
139      ELSE 
140        ZCCN=YDERAD%RCCNLND
141      ENDIF
142      ZSPECTRAL_DISPERSION = 0.69_JPRB
143      ! Cloud droplet concentration in cm-3 (activated CCN) over
144      ! land
145      ZNTOT_CM3 = -2.10E-04_JPRB*ZCCN*ZCCN + 0.568_JPRB*ZCCN - 27.9_JPRB
146    ENDIF
147   
148    ZRATIO = (0.222_JPRB/ZSPECTRAL_DISPERSION)**0.333_JPRB
149   
150    DO JK = 1,KLEV
151
152      ! Only consider cloudy regions
153      IF (PCLOUD_FRAC(JL,JK) >= 0.001_JPRB&
154           &  .AND. (PQ_LIQ(JL,JK)+PQ_RAIN(JL,JK)) > 0.0_JPRB) THEN
155
156        ! Compute liquid and rain water contents
157        ZAIR_DENSITY_GM3 = 1000.0_JPRB * PPRESSURE(JL,JK)&
158             &           / (RD*PTEMPERATURE(JL,JK))
159        ! In-cloud mean water contents found by dividing by cloud
160        ! fraction
161        ZLWC_GM3 = ZAIR_DENSITY_GM3 * PQ_LIQ(JL,JK)  / PCLOUD_FRAC(JL,JK)
162        ZRWC_GM3 = ZAIR_DENSITY_GM3 * PQ_RAIN(JL,JK) / PCLOUD_FRAC(JL,JK)
163     
164        ! Wood's (2000, eq. 19) adjustment to Martin et al's
165        ! parameterization
166        IF (ZLWC_GM3 > REPSCW) THEN
167          ZRAIN_RATIO = ZRWC_GM3 / ZLWC_GM3
168          ZWOOD_FACTOR = ((1.0_JPRB + ZRAIN_RATIO)**0.666_JPRB)&
169               &     / (1.0_JPRB + 0.2_JPRB * ZRATIO*ZRAIN_RATIO)
170        ELSE
171          ZWOOD_FACTOR = 1.0_JPRB
172        ENDIF
173     
174        ! g m-3 and cm-3 units cancel out with density of water
175        ! 10^6/(1000*1000); need a factor of 10^6 to convert to
176        ! microns and cubed root is factor of 100 which appears in
177        ! equation below
178        ZRE_CUBED = (3.0_JPRB * (ZLWC_GM3 + ZRWC_GM3))&
179             &    / (4.0_JPRB*RPI*ZNTOT_CM3*ZSPECTRAL_DISPERSION)
180        IF (ZRE_CUBED > REPLOG) THEN
181          PRE_UM(JL,JK) = ZWOOD_FACTOR*100.0_JPRB*EXP(0.333_JPRB*LOG(ZRE_CUBED))
182          ! Make sure effective radius is bounded in range 4-30 microns
183          PRE_UM(JL,JK) = MAX(PP_MIN_RE_UM, MIN(PRE_UM(JL,JK), PP_MAX_RE_UM))
184        ELSE
185          PRE_UM(JL,JK) = PP_MIN_RE_UM
186        ENDIF
187
188      ELSE
189        ! Cloud fraction or liquid+rain water content too low to
190        ! consider this a cloud
191        PRE_UM(JL,JK) = PP_MIN_RE_UM
192
193      ENDIF
194
195    ENDDO
196   
197  ENDDO
198 
199CASE DEFAULT
200  WRITE(NULERR,'(A,I0,A)') 'LIQUID EFFECTIVE RADIUS OPTION IRADLP=',IRADLP,' NOT AVAILABLE'
201  CALL ABOR1('ERROR IN LIQUID_EFFECTIVE_RADIUS')
202END SELECT
203
204! -------------------------------------------------------------------
205
206IF (LHOOK) CALL DR_HOOK('LIQUID_EFFECTIVE_RADIUS',1,ZHOOK_HANDLE)
207 
208END SUBROUTINE LIQUID_EFFECTIVE_RADIUS
Note: See TracBrowser for help on using the repository browser.