1 | MODULE sbcblk_phy |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE sbcblk_phy *** |
---|
4 | !! A set of functions to compute air themodynamics parameters |
---|
5 | !! needed by Aerodynamic Bulk Formulas |
---|
6 | !!===================================================================== |
---|
7 | !! 4.0 ! 2019 L. Brodeau from AeroBulk package (https://github.com/brodeau/aerobulk/) |
---|
8 | !!---------------------------------------------------------------------- |
---|
9 | |
---|
10 | !! rho_air : density of (moist) air (depends on T_air, q_air and SLP |
---|
11 | !! cp_air : specific heat of (moist) air (depends spec. hum. q_air) |
---|
12 | !! q_sat : saturation humidity as a function of SLP and temperature |
---|
13 | !! gamma_moist : |
---|
14 | !! L_vap : latent heat of vaporization of water as a function of temperature |
---|
15 | !! visc_air : kinematic viscosity (aka Nu_air) of air from temperature |
---|
16 | |
---|
17 | USE dom_oce ! ocean space and time domain |
---|
18 | USE phycst ! physical constants |
---|
19 | |
---|
20 | IMPLICIT NONE |
---|
21 | PRIVATE |
---|
22 | |
---|
23 | PUBLIC rho_air |
---|
24 | PUBLIC cp_air |
---|
25 | PUBLIC q_sat |
---|
26 | PUBLIC gamma_moist |
---|
27 | PUBLIC L_vap |
---|
28 | PUBLIC visc_air |
---|
29 | |
---|
30 | !!---------------------------------------------------------------------- |
---|
31 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
32 | !! $Id: sbcblk.F90 10535 2019-01-16 17:36:47Z clem $ |
---|
33 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
34 | !!---------------------------------------------------------------------- |
---|
35 | CONTAINS |
---|
36 | |
---|
37 | FUNCTION rho_air( ptak, pqa, pslp ) |
---|
38 | !!------------------------------------------------------------------------------- |
---|
39 | !! *** FUNCTION rho_air *** |
---|
40 | !! |
---|
41 | !! ** Purpose : compute density of (moist) air using the eq. of state of the atmosphere |
---|
42 | !! |
---|
43 | !! ** Author: L. Brodeau, june 2016 / AeroBulk (https://github.com/brodeau/aerobulk/) |
---|
44 | !!------------------------------------------------------------------------------- |
---|
45 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: ptak ! air temperature [K] |
---|
46 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pqa ! air specific humidity [kg/kg] |
---|
47 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pslp ! pressure in [Pa] |
---|
48 | REAL(wp), DIMENSION(jpi,jpj) :: rho_air ! density of moist air [kg/m^3] |
---|
49 | !!------------------------------------------------------------------------------- |
---|
50 | ! |
---|
51 | rho_air = pslp / ( R_dry*ptak * ( 1._wp + rctv0*pqa ) ) |
---|
52 | ! |
---|
53 | END FUNCTION rho_air |
---|
54 | |
---|
55 | |
---|
56 | FUNCTION cp_air( pqa ) |
---|
57 | !!------------------------------------------------------------------------------- |
---|
58 | !! *** FUNCTION cp_air *** |
---|
59 | !! |
---|
60 | !! ** Purpose : Compute specific heat (Cp) of moist air |
---|
61 | !! |
---|
62 | !! ** Author: L. Brodeau, june 2016 / AeroBulk (https://github.com/brodeau/aerobulk/) |
---|
63 | !!------------------------------------------------------------------------------- |
---|
64 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pqa ! air specific humidity [kg/kg] |
---|
65 | REAL(wp), DIMENSION(jpi,jpj) :: cp_air ! specific heat of moist air [J/K/kg] |
---|
66 | !!------------------------------------------------------------------------------- |
---|
67 | ! |
---|
68 | cp_air = rCp_dry + rCp_vap * pqa |
---|
69 | ! |
---|
70 | END FUNCTION cp_air |
---|
71 | |
---|
72 | |
---|
73 | FUNCTION q_sat( ptak, pslp ) |
---|
74 | !!---------------------------------------------------------------------------------- |
---|
75 | !! *** FUNCTION q_sat *** |
---|
76 | !! |
---|
77 | !! ** Purpose : Specific humidity at saturation in [kg/kg] |
---|
78 | !! Based on accurate estimate of "e_sat" |
---|
79 | !! aka saturation water vapor (Goff, 1957) |
---|
80 | !! |
---|
81 | !! ** Author: L. Brodeau, june 2016 / AeroBulk (https://github.com/brodeau/aerobulk/) |
---|
82 | !!---------------------------------------------------------------------------------- |
---|
83 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: ptak ! air temperature [K] |
---|
84 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pslp ! sea level atmospheric pressure [Pa] |
---|
85 | REAL(wp), DIMENSION(jpi,jpj) :: q_sat ! Specific humidity at saturation [kg/kg] |
---|
86 | ! |
---|
87 | INTEGER :: ji, jj ! dummy loop indices |
---|
88 | REAL(wp) :: zta, ze_sat, ztmp ! local scalar |
---|
89 | !!---------------------------------------------------------------------------------- |
---|
90 | ! |
---|
91 | DO jj = 1, jpj |
---|
92 | DO ji = 1, jpi |
---|
93 | ! |
---|
94 | zta = MAX( ptak(ji,jj) , 180._wp ) ! air temp., prevents fpe0 errors dute to unrealistically low values over masked regions... |
---|
95 | ztmp = rt0 / zta |
---|
96 | ! |
---|
97 | ! Vapour pressure at saturation [hPa] : WMO, (Goff, 1957) |
---|
98 | ze_sat = 10.**( 10.79574*(1. - ztmp) - 5.028*LOG10(zta/rt0) & |
---|
99 | & + 1.50475*10.**(-4)*(1. - 10.**(-8.2969*(zta/rt0 - 1.)) ) & |
---|
100 | & + 0.42873*10.**(-3)*(10.**(4.76955*(1. - ztmp)) - 1.) + 0.78614 ) |
---|
101 | ! |
---|
102 | q_sat(ji,jj) = reps0 * ze_sat/( 0.01_wp*pslp(ji,jj) - (1._wp - reps0)*ze_sat ) ! 0.01 because SLP is in [Pa] |
---|
103 | ! |
---|
104 | END DO |
---|
105 | END DO |
---|
106 | ! |
---|
107 | END FUNCTION q_sat |
---|
108 | |
---|
109 | |
---|
110 | FUNCTION gamma_moist( ptak, pqa ) |
---|
111 | !!---------------------------------------------------------------------------------- |
---|
112 | !! *** FUNCTION gamma_moist *** |
---|
113 | !! |
---|
114 | !! ** Purpose : Compute the moist adiabatic lapse-rate. |
---|
115 | !! => http://glossary.ametsoc.org/wiki/Moist-adiabatic_lapse_rate |
---|
116 | !! => http://www.geog.ucsb.edu/~joel/g266_s10/lecture_notes/chapt03/oh10_3_01/oh10_3_01.html |
---|
117 | !! |
---|
118 | !! ** Author: L. Brodeau, june 2016 / AeroBulk (https://github.com/brodeau/aerobulk/) |
---|
119 | !!---------------------------------------------------------------------------------- |
---|
120 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: ptak ! air temperature [K] |
---|
121 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pqa ! specific humidity [kg/kg] |
---|
122 | REAL(wp), DIMENSION(jpi,jpj) :: gamma_moist ! moist adiabatic lapse-rate |
---|
123 | ! |
---|
124 | INTEGER :: ji, jj ! dummy loop indices |
---|
125 | REAL(wp) :: zrv, ziRT ! local scalar |
---|
126 | !!---------------------------------------------------------------------------------- |
---|
127 | ! |
---|
128 | DO jj = 1, jpj |
---|
129 | DO ji = 1, jpi |
---|
130 | zrv = pqa(ji,jj) / (1. - pqa(ji,jj)) |
---|
131 | ziRT = 1. / (R_dry*ptak(ji,jj)) ! 1/RT |
---|
132 | gamma_moist(ji,jj) = grav * ( 1. + rLevap*zrv*ziRT ) / ( rCp_dry + rLevap*rLevap*zrv*reps0*ziRT/ptak(ji,jj) ) |
---|
133 | END DO |
---|
134 | END DO |
---|
135 | ! |
---|
136 | END FUNCTION gamma_moist |
---|
137 | |
---|
138 | |
---|
139 | FUNCTION L_vap( psst ) |
---|
140 | !!--------------------------------------------------------------------------------- |
---|
141 | !! *** FUNCTION L_vap *** |
---|
142 | !! |
---|
143 | !! ** Purpose : Compute the latent heat of vaporization of water from temperature |
---|
144 | !! |
---|
145 | !! ** Author: L. Brodeau, june 2016 / AeroBulk (https://github.com/brodeau/aerobulk/) |
---|
146 | !!---------------------------------------------------------------------------------- |
---|
147 | REAL(wp), DIMENSION(jpi,jpj) :: L_vap ! latent heat of vaporization [J/kg] |
---|
148 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: psst ! water temperature [K] |
---|
149 | !!---------------------------------------------------------------------------------- |
---|
150 | ! |
---|
151 | L_vap = ( 2.501 - 0.00237 * ( psst(:,:) - rt0) ) * 1.e6 |
---|
152 | ! |
---|
153 | END FUNCTION L_vap |
---|
154 | |
---|
155 | |
---|
156 | |
---|
157 | FUNCTION visc_air(ptak) |
---|
158 | !!---------------------------------------------------------------------------------- |
---|
159 | !! Air kinetic viscosity (m^2/s) given from temperature in degrees... |
---|
160 | !! |
---|
161 | !! ** Author: L. Brodeau, june 2016 / AeroBulk (https://github.com/brodeau/aerobulk/) |
---|
162 | !!---------------------------------------------------------------------------------- |
---|
163 | REAL(wp), DIMENSION(jpi,jpj) :: visc_air ! |
---|
164 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: ptak ! air temperature in (K) |
---|
165 | ! |
---|
166 | INTEGER :: ji, jj ! dummy loop indices |
---|
167 | REAL(wp) :: ztc, ztc2 ! local scalar |
---|
168 | !!---------------------------------------------------------------------------------- |
---|
169 | ! |
---|
170 | DO jj = 1, jpj |
---|
171 | DO ji = 1, jpi |
---|
172 | ztc = ptak(ji,jj) - rt0 ! air temp, in deg. C |
---|
173 | ztc2 = ztc*ztc |
---|
174 | visc_air(ji,jj) = 1.326e-5*(1. + 6.542E-3*ztc + 8.301e-6*ztc2 - 4.84e-9*ztc2*ztc) |
---|
175 | END DO |
---|
176 | END DO |
---|
177 | ! |
---|
178 | END FUNCTION visc_air |
---|
179 | |
---|
180 | |
---|
181 | !!====================================================================== |
---|
182 | END MODULE sbcblk_phy |
---|