SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
mode_coare30_psi.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
6 !
7 !
8 USE yomhook ,ONLY : lhook, dr_hook
9 USE parkind1 ,ONLY : jprb
10 !
11  INTERFACE psifctu
12  MODULE PROCEDURE psifunctu
13  END INTERFACE
14  INTERFACE psifctt
15  MODULE PROCEDURE psifunctt
16  END INTERFACE
17 !
18  CONTAINS
19 !
20 !---------------------------------------------------------------------------------------
21 !
22 !#######################################################################################
23 FUNCTION psifunctu(PZL) RESULT(PSIFCTU)
24 !#######################################################################################
25 !
26 !**** *PSIFUNCTU*
27 !
28 ! PURPOSE
29 ! -------
30 ! To evaluate the stability function psi for wind speed (if KID=1) or
31 ! for temperature or humidity profiles (if KID.ne.1) from stability parameter
32 ! z/L.
33 !
34 ! EXTERNAL
35 ! --------
36 !
37 ! IMPLICIT ARGUMENTS
38 ! ------------------
39 !
40 ! REFERENCE
41 ! ---------
42 ! Lik79 : Liu, W. T., K. B. Katsaros, and J. A. Businger, 1979:
43 ! Bulk parameterization of air-sea exchanges of heat and water vapor including
44 ! the molecular constraints at the interface. J. Atm. Sci., 36, 1722--1735.
45 ! DyH70 : Dyer, A. J., and B. B. Hicks, 1970: Flux-gradient relationship
46 ! in the constant flux layer. Quart. J. Roy. Meteor. Soc., 96, 715--721.
47 !
48 ! AUTHOR
49 ! ------
50 !
51 ! MODIFICATIONS
52 ! -------------
53 !-------------------------------------------------------------------------------
54 IMPLICIT NONE
55 !
56 ! 0. Declaration
57 !
58 ! 0.1 declaration of arguments
59 !
60 REAL, DIMENSION(:), INTENT(IN) :: pzl !Obukhovs stability parameter
61 REAL, DIMENSION(SIZE(PZL)) :: psifctu !function psi value
62 ! 0.2 declaration of local variables
63 REAL, DIMENSION(SIZE(PZL)) :: zy,zx,zc,zpsic,zpsik,zf
64 INTEGER :: jj
65 REAL(KIND=JPRB) :: zhook_handle
66 !
67 IF (lhook) CALL dr_hook('MODE_COARE30_PSI:PSIFUNCTU',0,zhook_handle)
68 DO jj=1,SIZE(pzl)
69  IF(pzl(jj)<0.) THEN
70  zx(jj) = (1.0 - 15. * pzl(jj))**0.25 ! Kansas unstable
71  zpsik(jj)= 2.0 * log((1.0+zx(jj) )/2.0) &
72  + log((1.0+zx(jj)*zx(jj))/2.0) &
73  - 2.0 * atan(zx(jj)) &
74  + 2.0 * atan(1.0)
75  !
76  zy(jj) = (1.0 - 10.15 * pzl(jj))**0.3333 ! Convective
77  zpsic(jj)= 1.5 * log((zy(jj)*zy(jj)+zy(jj)+1.)/3.) &
78  - (3.0**0.5) * atan((2.0*zy(jj)+1.0)/(3.0**0.5)) &
79  + 4.0 * atan(1.0)/(3.0**0.5)
80  !
81  zf(jj) =pzl(jj) * pzl(jj) / (1.0+pzl(jj)*pzl(jj))
82  !
83  psifctu(jj)=(1.-zf(jj)) * zpsik(jj) + zf(jj) * zpsic(jj)
84  ELSE
85  zc(jj)=min(50.,0.35*pzl(jj)) ! Stable
86  psifctu(jj)=-((1.+1.*pzl(jj))**1. + 0.6667*(pzl(jj)-14.28)/exp(zc(jj)) + 8.525)
87  ENDIF
88 ENDDO
89 IF (lhook) CALL dr_hook('MODE_COARE30_PSI:PSIFUNCTU',1,zhook_handle)
90 
91 END FUNCTION psifunctu
92 !---------------------------------------------------------------------------------------
93 !
94 !#######################################################################################
95 FUNCTION psifunctt(PZL) RESULT(PSIFCTT)
96 !#######################################################################################
97 !
98 !**** *PSIFUNCTU*
99 !
100 ! PURPOSE
101 ! -------
102 ! To evaluate the stability function psi for wind speed (if KID=1) or
103 ! for temperature or humidity profiles (if KID.ne.1) from stability parameter
104 ! z/L.
105 !
106 ! EXTERNAL
107 ! --------
108 !
109 ! IMPLICIT ARGUMENTS
110 ! ------------------
111 !
112 ! REFERENCE
113 ! ---------
114 ! Lik79 : Liu, W. T., K. B. Katsaros, and J. A. Businger, 1979:
115 ! Bulk parameterization of air-sea exchanges of heat and water vapor including
116 ! the molecular constraints at the interface. J. Atm. Sci., 36, 1722--1735.
117 ! DyH70 : Dyer, A. J., and B. B. Hicks, 1970: Flux-gradient relationship
118 ! in the constant flux layer. Quart. J. Roy. Meteor. Soc., 96, 715--721.
119 !
120 ! AUTHOR
121 ! ------
122 !
123 ! MODIFICATIONS
124 ! -------------
125 !-------------------------------------------------------------------------------
126 IMPLICIT NONE
127 !
128 ! 0. Declaration
129 !
130 ! 0.1 declaration of arguments
131 !
132 REAL, DIMENSION(:), INTENT(IN) :: pzl !Obukhovs stability parameter
133 REAL, DIMENSION(SIZE(PZL)) :: psifctt !function psi value
134 ! 0.2 declaration of local variables
135 REAL, DIMENSION(SIZE(PZL)) :: zx,zy,zc,zpsic,zpsik,zf
136 INTEGER :: jj
137 REAL(KIND=JPRB) :: zhook_handle
138 !
139 IF (lhook) CALL dr_hook('MODE_COARE30_PSI:PSIFUNCTT',0,zhook_handle)
140 DO jj=1,SIZE(pzl)
141  IF(pzl(jj)<0.) THEN
142  zx(jj) = (1. - 15. * pzl(jj))**.5 ! Kansas unstable
143  zpsik(jj)= 2.0 * log((1.0+zx(jj) )/2.0)
144  !
145  zy(jj) = (1.0 - 34.15 * pzl(jj))**0.3333 ! Convective
146  zpsic(jj)= 1.5 * log((zy(jj)*zy(jj)+zy(jj)+1.0)/3.) &
147  - (3.0**0.5) * atan((2.0*zy(jj)+1.0)/(3.0**0.5)) &
148  + 4.0 * atan(1.0)/(3.0**0.5)
149  !
150  zf(jj) = pzl(jj) * pzl(jj) / (1.0+pzl(jj)*pzl(jj))
151  !
152  psifctt(jj)= (1.-zf(jj)) * zpsik(jj) + zf(jj) * zpsic(jj)
153  ELSE
154  zc(jj)=min(50.,0.35*pzl(jj)) ! Stable
155  psifctt(jj)=-((1.+2.*pzl(jj)/3.)**1.5 + 0.6667*(pzl(jj)-14.28)/exp(zc(jj)) + 8.525)
156  ENDIF
157 ENDDO
158 IF (lhook) CALL dr_hook('MODE_COARE30_PSI:PSIFUNCTT',1,zhook_handle)
159 
160 END FUNCTION psifunctt
161 !
162 END MODULE mode_coare30_psi
real function, dimension(size(pzl)) psifunctu(PZL)
real function, dimension(size(pzl)) psifunctt(PZL)