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

Last change on this file since 4773 was 4773, checked in by idelkadi, 6 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: 3.7 KB
Line 
1SUBROUTINE CLOUD_OVERLAP_DECORR_LEN &
2     & (KIDIA, KFDIA, KLON, PGEMU, KDECOLAT, &
3     &  PDECORR_LEN_EDGES_KM, PDECORR_LEN_WATER_KM, PDECORR_LEN_RATIO)
4
5! CLOUD_OVERLAP_DECORR_LEN
6!
7! (C) Copyright 2016- ECMWF.
8!
9! This software is licensed under the terms of the Apache Licence Version 2.0
10! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
11!
12! In applying this licence, ECMWF does not waive the privileges and immunities
13! granted to it by virtue of its status as an intergovernmental organisation
14! nor does it submit to any jurisdiction.
15!
16! PURPOSE
17! -------
18!   Calculate the cloud overlap decorrelation length as a function of
19!   latitude for use in the radiation scheme
20!
21! INTERFACE
22! ---------
23!   CLOUD_OVERLAP_DECORR_LEN is called from RADLSWR and RADIATION_SCHEME
24!
25! AUTHOR
26! ------
27!   Robin Hogan, ECMWF (using code extracted from radlswr.F90)
28!   Original: 2016-02-16
29!
30! MODIFICATIONS
31! -------------
32!
33! -------------------------------------------------------------------
34
35USE PARKIND1 , ONLY : JPIM, JPRB
36USE YOMHOOK  , ONLY : LHOOK, DR_HOOK, JPHOOK
37USE YOMCST   , ONLY : RPI
38USE YOECLD   , ONLY : RDECORR_CF, RDECORR_CW
39
40! -------------------------------------------------------------------
41
42IMPLICIT NONE
43
44! INPUT ARGUMENTS
45
46! *** Array dimensions and ranges
47INTEGER(KIND=JPIM),INTENT(IN) :: KIDIA    ! Start column to process
48INTEGER(KIND=JPIM),INTENT(IN) :: KFDIA    ! End column to process
49INTEGER(KIND=JPIM),INTENT(IN) :: KLON     ! Number of columns
50
51! *** Configuration variable controlling the overlap scheme
52INTEGER(KIND=JPIM),INTENT(IN) :: KDECOLAT
53
54! *** Single-level variables
55REAL(KIND=JPRB),   INTENT(IN) :: PGEMU(KLON) ! Sine of latitude
56
57! OUTPUT ARGUMENTS
58
59! *** Decorrelation lengths for cloud edges and cloud water content,
60! *** in km
61REAL(KIND=JPRB), INTENT(OUT)           :: PDECORR_LEN_EDGES_KM(KLON)
62REAL(KIND=JPRB), INTENT(OUT), OPTIONAL :: PDECORR_LEN_WATER_KM(KLON)
63 
64! Ratio of water-content to cloud-edge decorrelation lengths
65REAL(KIND=JPRB), INTENT(OUT), OPTIONAL :: PDECORR_LEN_RATIO
66
67! LOCAL VARIABLES
68
69REAL(KIND=JPRB) :: ZRADIANS_TO_DEGREES, ZABS_LAT_DEG, ZCOS_LAT
70
71INTEGER(KIND=JPIM) :: JL
72
73REAL(KIND=JPHOOK) :: ZHOOK_HANDLE
74
75! -------------------------------------------------------------------
76
77IF (LHOOK) CALL DR_HOOK('CLOUD_OVERLAP_DECORR_LEN',0,ZHOOK_HANDLE)
78 
79! -------------------------------------------------------------------
80
81IF (KDECOLAT == 0) THEN
82
83  ! Decorrelation lengths are constant values
84  PDECORR_LEN_EDGES_KM(KIDIA:KFDIA) = RDECORR_CF
85  IF (PRESENT(PDECORR_LEN_WATER_KM)) THEN
86    PDECORR_LEN_WATER_KM(KIDIA:KFDIA) = RDECORR_CW
87  ENDIF
88  IF (PRESENT(PDECORR_LEN_RATIO)) THEN
89    PDECORR_LEN_RATIO = RDECORR_CW / RDECORR_CF
90  ENDIF
91
92ELSE
93
94  ZRADIANS_TO_DEGREES = 180.0_JPRB / RPI
95
96  IF (KDECOLAT == 1) THEN
97    ! Shonk et al. (2010) Eq. 13 formula
98    DO JL = KIDIA,KFDIA
99      ZABS_LAT_DEG = ABS(ASIN(PGEMU(JL)) * ZRADIANS_TO_DEGREES)
100      PDECORR_LEN_EDGES_KM(JL) = 2.899_JPRB - 0.02759_JPRB * ZABS_LAT_DEG
101    ENDDO
102  ELSE ! KDECOLAT == 2
103    DO JL = KIDIA,KFDIA
104      ! Shonk et al. (2010) but smoothed over the equator
105      ZCOS_LAT = COS(ASIN(PGEMU(JL)))
106      PDECORR_LEN_EDGES_KM(JL) = 0.75_JPRB + 2.149_JPRB * ZCOS_LAT*ZCOS_LAT
107    ENDDO
108  ENDIF
109
110  ! Both KDECOLAT = 1 and 2 assume that the decorrelation length for
111  ! cloud water content is half that for cloud edges
112  IF (PRESENT(PDECORR_LEN_WATER_KM)) THEN
113    PDECORR_LEN_WATER_KM(KIDIA:KFDIA) = PDECORR_LEN_EDGES_KM(KIDIA:KFDIA) * 0.5_JPRB
114  ENDIF
115
116  IF (PRESENT(PDECORR_LEN_RATIO)) THEN
117    PDECORR_LEN_RATIO = 0.5_JPRB
118  ENDIF
119
120ENDIF
121
122! -------------------------------------------------------------------
123
124IF (LHOOK) CALL DR_HOOK('CLOUD_OVERLAP_DECORR_LEN',1,ZHOOK_HANDLE)
125
126END SUBROUTINE CLOUD_OVERLAP_DECORR_LEN
Note: See TracBrowser for help on using the repository browser.