1 | ! |
---|
2 | ! $Id: surf_ocean_mod.F90 3851 2021-02-22 11:44:07Z acozic $ |
---|
3 | ! |
---|
4 | MODULE surf_ocean_mod |
---|
5 | |
---|
6 | IMPLICIT NONE |
---|
7 | |
---|
8 | CONTAINS |
---|
9 | ! |
---|
10 | !****************************************************************************** |
---|
11 | ! |
---|
12 | SUBROUTINE surf_ocean(rlon, rlat, swnet, lwnet, alb1, & |
---|
13 | windsp, rmu0, fder, tsurf_in, & |
---|
14 | itime, dtime, jour, knon, knindex, & |
---|
15 | p1lay, z1lay, cdragh, cdragm, precip_rain, precip_snow, temp_air, spechum, & |
---|
16 | AcoefH, AcoefQ, BcoefH, BcoefQ, & |
---|
17 | AcoefU, AcoefV, BcoefU, BcoefV, & |
---|
18 | ps, u1, v1, gustiness, rugoro, pctsrf, & |
---|
19 | snow, qsurf, agesno, & |
---|
20 | z0m, z0h, SFRWL, alb_dir_new, alb_dif_new, evap, fluxsens, fluxlat, & |
---|
21 | tsurf_new, dflux_s, dflux_l, lmt_bils, & |
---|
22 | flux_u1, flux_v1, delta_sst, delta_sal, ds_ns, dt_ns, dter, dser, tkt, tks, & |
---|
23 | taur, sss) |
---|
24 | |
---|
25 | use albedo, only: alboc, alboc_cd |
---|
26 | use bulk_flux_m, only: bulk_flux |
---|
27 | USE dimphy, ONLY: klon, zmasq |
---|
28 | USE surface_data, ONLY : type_ocean |
---|
29 | USE ocean_forced_mod, ONLY : ocean_forced_noice |
---|
30 | USE ocean_slab_mod, ONLY : ocean_slab_noice |
---|
31 | USE ocean_cpl_mod, ONLY : ocean_cpl_noice |
---|
32 | USE indice_sol_mod, ONLY : nbsrf, is_oce |
---|
33 | USE limit_read_mod |
---|
34 | use config_ocean_skin_m, only: activate_ocean_skin |
---|
35 | ! |
---|
36 | ! This subroutine will make a call to ocean_XXX_noice according to the ocean mode (force, |
---|
37 | ! slab or couple). The calculations of albedo and rugosity for the ocean surface are |
---|
38 | ! done in here because they are identical for the different modes of ocean. |
---|
39 | |
---|
40 | |
---|
41 | INCLUDE "YOMCST.h" |
---|
42 | |
---|
43 | include "clesphys.h" |
---|
44 | ! for cycle_diurne and for iflag_z0_oce==-1 (prescribed z0) |
---|
45 | |
---|
46 | ! Input variables |
---|
47 | !****************************************************************************** |
---|
48 | INTEGER, INTENT(IN) :: itime, jour, knon |
---|
49 | INTEGER, DIMENSION(klon), INTENT(IN) :: knindex |
---|
50 | REAL, INTENT(IN) :: dtime |
---|
51 | REAL, DIMENSION(klon), INTENT(IN) :: rlon, rlat |
---|
52 | REAL, DIMENSION(klon), INTENT(IN) :: swnet ! net shortwave radiation at surface |
---|
53 | REAL, DIMENSION(klon), INTENT(IN) :: lwnet ! net longwave radiation at surface |
---|
54 | REAL, DIMENSION(klon), INTENT(IN) :: alb1 ! albedo in visible SW interval |
---|
55 | REAL, DIMENSION(klon), INTENT(IN) :: windsp ! wind at 10 m, in m s-1 |
---|
56 | REAL, DIMENSION(klon), INTENT(IN) :: rmu0 |
---|
57 | REAL, DIMENSION(klon), INTENT(IN) :: fder |
---|
58 | REAL, INTENT(IN):: tsurf_in(klon) ! defined only for subscripts 1:knon |
---|
59 | REAL, DIMENSION(klon), INTENT(IN) :: p1lay,z1lay ! pression (Pa) et altitude (m) du premier niveau |
---|
60 | REAL, DIMENSION(klon), INTENT(IN) :: cdragh |
---|
61 | REAL, DIMENSION(klon), INTENT(IN) :: cdragm |
---|
62 | REAL, DIMENSION(klon), INTENT(IN) :: precip_rain, precip_snow |
---|
63 | REAL, DIMENSION(klon), INTENT(IN) :: temp_air, spechum |
---|
64 | REAL, DIMENSION(klon), INTENT(IN) :: AcoefH, AcoefQ, BcoefH, BcoefQ |
---|
65 | REAL, DIMENSION(klon), INTENT(IN) :: AcoefU, AcoefV, BcoefU, BcoefV |
---|
66 | REAL, DIMENSION(klon), INTENT(IN) :: ps |
---|
67 | REAL, DIMENSION(klon), INTENT(IN) :: u1, v1, gustiness |
---|
68 | REAL, DIMENSION(klon), INTENT(IN) :: rugoro |
---|
69 | REAL, DIMENSION(klon,nbsrf), INTENT(IN) :: pctsrf |
---|
70 | |
---|
71 | ! In/Output variables |
---|
72 | !****************************************************************************** |
---|
73 | REAL, DIMENSION(klon), INTENT(INOUT) :: snow |
---|
74 | REAL, DIMENSION(klon), INTENT(INOUT) :: qsurf |
---|
75 | REAL, DIMENSION(klon), INTENT(INOUT) :: agesno |
---|
76 | REAL, DIMENSION(klon), INTENT(inOUT):: z0h |
---|
77 | |
---|
78 | REAL, intent(inout):: delta_sst(:) ! (knon) |
---|
79 | ! Ocean-air interface temperature minus bulk SST, in K. Defined |
---|
80 | ! only if activate_ocean_skin >= 1. |
---|
81 | |
---|
82 | real, intent(inout):: delta_sal(:) ! (knon) |
---|
83 | ! Ocean-air interface salinity minus bulk salinity, in ppt. Defined |
---|
84 | ! only if activate_ocean_skin >= 1. |
---|
85 | |
---|
86 | REAL, intent(inout):: ds_ns(:) ! (knon) |
---|
87 | ! "delta salinity near surface". Salinity variation in the |
---|
88 | ! near-surface turbulent layer. That is subskin salinity minus |
---|
89 | ! foundation salinity. In ppt. |
---|
90 | |
---|
91 | REAL, intent(inout):: dt_ns(:) ! (knon) |
---|
92 | ! "delta temperature near surface". Temperature variation in the |
---|
93 | ! near-surface turbulent layer. That is subskin temperature |
---|
94 | ! minus foundation temperature. (Can be negative.) In K. |
---|
95 | |
---|
96 | ! Output variables |
---|
97 | !************************************************************************** |
---|
98 | REAL, DIMENSION(klon), INTENT(OUT) :: z0m |
---|
99 | !albedo SB >>> |
---|
100 | ! REAL, DIMENSION(klon), INTENT(OUT) :: alb1_new ! new albedo in visible SW interval |
---|
101 | ! REAL, DIMENSION(klon), INTENT(OUT) :: alb2_new ! new albedo in near IR interval |
---|
102 | REAL, DIMENSION(6), INTENT(IN) :: SFRWL |
---|
103 | REAL, DIMENSION(klon,nsw), INTENT(OUT) :: alb_dir_new,alb_dif_new |
---|
104 | !albedo SB <<< |
---|
105 | REAL, DIMENSION(klon), INTENT(OUT) :: evap, fluxsens, fluxlat |
---|
106 | REAL, INTENT(OUT):: tsurf_new(klon) ! sea surface temperature, in K |
---|
107 | REAL, DIMENSION(klon), INTENT(OUT) :: dflux_s, dflux_l |
---|
108 | REAL, DIMENSION(klon), INTENT(OUT) :: lmt_bils |
---|
109 | REAL, DIMENSION(klon), INTENT(OUT) :: flux_u1, flux_v1 |
---|
110 | |
---|
111 | REAL, intent(out):: dter(:) ! (knon) |
---|
112 | ! Temperature variation in the diffusive microlayer, that is |
---|
113 | ! ocean-air interface temperature minus subskin temperature. In |
---|
114 | ! K. |
---|
115 | |
---|
116 | REAL, intent(out):: dser(:) ! (knon) |
---|
117 | ! Salinity variation in the diffusive microlayer, that is |
---|
118 | ! ocean-air interface salinity minus subskin salinity. In ppt. |
---|
119 | |
---|
120 | REAL, intent(out):: tkt(:) ! (knon) |
---|
121 | ! épaisseur (m) de la couche de diffusion thermique (microlayer) |
---|
122 | ! cool skin thickness |
---|
123 | |
---|
124 | REAL, intent(out):: tks(:) ! (knon) |
---|
125 | ! épaisseur (m) de la couche de diffusion de masse (microlayer) |
---|
126 | |
---|
127 | REAL, intent(out):: taur(:) ! (knon) |
---|
128 | ! momentum flux due to rain, in Pa |
---|
129 | |
---|
130 | real, intent(out):: sss(:) ! (klon) |
---|
131 | ! Bulk salinity of the surface layer of the ocean, in ppt. (Only |
---|
132 | ! defined for subscripts 1:knon, but we have to declare it with |
---|
133 | ! size klon because of the coupling machinery.) |
---|
134 | |
---|
135 | ! Local variables |
---|
136 | !************************************************************************* |
---|
137 | INTEGER :: i, k |
---|
138 | REAL :: tmp |
---|
139 | REAL, PARAMETER :: cepdu2=(0.1)**2 |
---|
140 | REAL, DIMENSION(klon) :: alb_eau, z0_lim |
---|
141 | REAL, DIMENSION(klon) :: radsol |
---|
142 | REAL, DIMENSION(klon) :: cdragq ! Cdrag pour l'evaporation |
---|
143 | CHARACTER(len=20),PARAMETER :: modname="surf_ocean" |
---|
144 | real rhoa(knon) ! density of moist air (kg / m3) |
---|
145 | REAL sens_prec_liq(knon) |
---|
146 | |
---|
147 | REAL t_int(knon) ! ocean-air interface temperature, in K |
---|
148 | real s_int(knon) ! ocean-air interface salinity, in ppt |
---|
149 | |
---|
150 | !************************************************************************** |
---|
151 | |
---|
152 | |
---|
153 | !****************************************************************************** |
---|
154 | ! Calculate total net radiance at surface |
---|
155 | ! |
---|
156 | !****************************************************************************** |
---|
157 | radsol(1:klon) = 0.0 ! initialisation a priori inutile |
---|
158 | radsol(1:knon) = swnet(1:knon) + lwnet(1:knon) |
---|
159 | |
---|
160 | !****************************************************************************** |
---|
161 | ! Cdragq computed from cdrag |
---|
162 | ! The difference comes only from a factor (f_z0qh_oce) on z0, so that |
---|
163 | ! it can be computed inside surf_ocean |
---|
164 | ! More complicated appraches may require the propagation through |
---|
165 | ! pbl_surface of an independant cdragq variable. |
---|
166 | !****************************************************************************** |
---|
167 | |
---|
168 | IF ( f_z0qh_oce .ne. 1.) THEN |
---|
169 | ! Si on suit les formulations par exemple de Tessel, on |
---|
170 | ! a z0h=0.4*nu/u*, z0q=0.62*nu/u*, d'ou f_z0qh_oce=0.62/0.4=1.55 |
---|
171 | cdragq(1:knon)=cdragh(1:knon)* & |
---|
172 | log(z1lay(1:knon)/z0h(1:knon))/log(z1lay(1:knon)/(f_z0qh_oce*z0h(1:knon))) |
---|
173 | ELSE |
---|
174 | cdragq(1:knon)=cdragh(1:knon) |
---|
175 | ENDIF |
---|
176 | |
---|
177 | rhoa = PS(:KNON) / (Rd * temp_air(:knon) * (1. + retv * spechum(:knon))) |
---|
178 | !****************************************************************************** |
---|
179 | ! Switch according to type of ocean (couple, slab or forced) |
---|
180 | !****************************************************************************** |
---|
181 | SELECT CASE(type_ocean) |
---|
182 | CASE('couple') |
---|
183 | CALL ocean_cpl_noice( & |
---|
184 | swnet, lwnet, alb1, & |
---|
185 | windsp, fder, & |
---|
186 | itime, dtime, knon, knindex, & |
---|
187 | p1lay, cdragh, cdragq, cdragm, precip_rain, precip_snow,temp_air,spechum,& |
---|
188 | AcoefH, AcoefQ, BcoefH, BcoefQ, & |
---|
189 | AcoefU, AcoefV, BcoefU, BcoefV, & |
---|
190 | ps, u1, v1, gustiness, tsurf_in, & |
---|
191 | radsol, snow, agesno, & |
---|
192 | qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, & |
---|
193 | tsurf_new, dflux_s, dflux_l, sens_prec_liq, sss, delta_sal, rhoa, & |
---|
194 | delta_sst) |
---|
195 | |
---|
196 | CASE('slab') |
---|
197 | CALL ocean_slab_noice( & |
---|
198 | itime, dtime, jour, knon, knindex, & |
---|
199 | p1lay, cdragh, cdragq, cdragm, precip_rain, precip_snow, temp_air, spechum,& |
---|
200 | AcoefH, AcoefQ, BcoefH, BcoefQ, & |
---|
201 | AcoefU, AcoefV, BcoefU, BcoefV, & |
---|
202 | ps, u1, v1, gustiness, tsurf_in, & |
---|
203 | radsol, snow, & |
---|
204 | qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, & |
---|
205 | tsurf_new, dflux_s, dflux_l, lmt_bils) |
---|
206 | |
---|
207 | CASE('force') |
---|
208 | CALL ocean_forced_noice( & |
---|
209 | itime, dtime, jour, knon, knindex, & |
---|
210 | p1lay, cdragh, cdragq, cdragm, precip_rain, precip_snow, & |
---|
211 | temp_air, spechum, & |
---|
212 | AcoefH, AcoefQ, BcoefH, BcoefQ, & |
---|
213 | AcoefU, AcoefV, BcoefU, BcoefV, & |
---|
214 | ps, u1, v1, gustiness, tsurf_in, & |
---|
215 | radsol, snow, agesno, & |
---|
216 | qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, & |
---|
217 | tsurf_new, dflux_s, dflux_l, sens_prec_liq, rhoa) |
---|
218 | END SELECT |
---|
219 | |
---|
220 | !****************************************************************************** |
---|
221 | ! fcodron: compute lmt_bils forced case (same as wfbils_oce / 1.-contfracatm) |
---|
222 | !****************************************************************************** |
---|
223 | IF (type_ocean.NE.'slab') THEN |
---|
224 | lmt_bils(1:klon)=0. |
---|
225 | DO i=1,knon |
---|
226 | lmt_bils(knindex(i))=(swnet(i)+lwnet(i)+fluxsens(i)+fluxlat(i)) & |
---|
227 | *pctsrf(knindex(i),is_oce)/(1.-zmasq(knindex(i))) |
---|
228 | END DO |
---|
229 | END IF |
---|
230 | |
---|
231 | !****************************************************************************** |
---|
232 | ! Calculate ocean surface albedo |
---|
233 | !****************************************************************************** |
---|
234 | !albedo SB >>> |
---|
235 | IF (iflag_albedo==0) THEN |
---|
236 | !--old parametrizations of ocean surface albedo |
---|
237 | ! |
---|
238 | IF (iflag_cycle_diurne.GE.1) THEN |
---|
239 | ! |
---|
240 | CALL alboc_cd(rmu0,alb_eau) |
---|
241 | ! |
---|
242 | !--ad-hoc correction for model radiative balance tuning |
---|
243 | !--now outside alboc_cd routine |
---|
244 | alb_eau(1:klon) = fmagic*alb_eau(1:klon) + pmagic |
---|
245 | alb_eau(1:klon)=MIN(MAX(alb_eau(1:klon),0.0),1.0) |
---|
246 | ! |
---|
247 | ELSE |
---|
248 | ! |
---|
249 | CALL alboc(REAL(jour),rlat,alb_eau) |
---|
250 | !--ad-hoc correction for model radiative balance tuning |
---|
251 | !--now outside alboc routine |
---|
252 | alb_eau(1:klon) = fmagic*alb_eau(1:klon) + pmagic |
---|
253 | alb_eau(1:klon)=MIN(MAX(alb_eau(1:klon),0.04),0.60) |
---|
254 | ! |
---|
255 | ENDIF |
---|
256 | ! |
---|
257 | DO i =1, knon |
---|
258 | DO k=1,nsw |
---|
259 | alb_dir_new(i,k) = alb_eau(knindex(i)) |
---|
260 | ENDDO |
---|
261 | ENDDO |
---|
262 | !IM 09122015 next line corresponds to the old way of doing in LMDZ5A/IPSLCM5A versions |
---|
263 | !albedo for diffuse radiation is taken the same as for direct radiation |
---|
264 | alb_dif_new(1:knon,:)=alb_dir_new(1:knon,:) |
---|
265 | !IM 09122015 end |
---|
266 | ! |
---|
267 | ELSE IF (iflag_albedo==1) THEN |
---|
268 | !--new parametrization of ocean surface albedo by Sunghye Baek |
---|
269 | !--albedo for direct and diffuse radiation are different |
---|
270 | ! |
---|
271 | CALL ocean_albedo(knon,rmu0,knindex,windsp,SFRWL,alb_dir_new,alb_dif_new) |
---|
272 | ! |
---|
273 | !--ad-hoc correction for model radiative balance tuning |
---|
274 | alb_dir_new(1:knon,:) = fmagic*alb_dir_new(1:knon,:) + pmagic |
---|
275 | alb_dif_new(1:knon,:) = fmagic*alb_dif_new(1:knon,:) + pmagic |
---|
276 | alb_dir_new(1:knon,:)=MIN(MAX(alb_dir_new(1:knon,:),0.0),1.0) |
---|
277 | alb_dif_new(1:knon,:)=MIN(MAX(alb_dif_new(1:knon,:),0.0),1.0) |
---|
278 | ! |
---|
279 | ELSE IF (iflag_albedo==2) THEN |
---|
280 | ! F. Codron albedo read from limit.nc |
---|
281 | CALL limit_read_rug_alb(itime, dtime, jour,& |
---|
282 | knon, knindex, z0_lim, alb_eau) |
---|
283 | DO i =1, knon |
---|
284 | DO k=1,nsw |
---|
285 | alb_dir_new(i,k) = alb_eau(i) |
---|
286 | ENDDO |
---|
287 | ENDDO |
---|
288 | alb_dif_new=alb_dir_new |
---|
289 | ENDIF |
---|
290 | !albedo SB <<< |
---|
291 | |
---|
292 | !****************************************************************************** |
---|
293 | ! Calculate the rugosity |
---|
294 | !****************************************************************************** |
---|
295 | IF (iflag_z0_oce==0) THEN |
---|
296 | DO i = 1, knon |
---|
297 | tmp = MAX(cepdu2,gustiness(i)+u1(i)**2+v1(i)**2) |
---|
298 | z0m(i) = 0.018*cdragm(i) * (gustiness(i)+u1(i)**2+v1(i)**2)/RG & |
---|
299 | + 0.11*14e-6 / SQRT(cdragm(i) * tmp) |
---|
300 | z0m(i) = MAX(1.5e-05,z0m(i)) |
---|
301 | ENDDO |
---|
302 | z0h(1:knon)=z0m(1:knon) ! En attendant mieux |
---|
303 | |
---|
304 | ELSE IF (iflag_z0_oce==1) THEN |
---|
305 | DO i = 1, knon |
---|
306 | tmp = MAX(cepdu2,gustiness(i)+u1(i)**2+v1(i)**2) |
---|
307 | z0m(i) = 0.018*cdragm(i) * (gustiness(i)+u1(i)**2+v1(i)**2)/RG & |
---|
308 | + 0.11*14e-6 / SQRT(cdragm(i) * tmp) |
---|
309 | z0m(i) = MAX(1.5e-05,z0m(i)) |
---|
310 | z0h(i)=0.4*14e-6 / SQRT(cdragm(i) * tmp) |
---|
311 | ENDDO |
---|
312 | ELSE IF (iflag_z0_oce==-1) THEN |
---|
313 | DO i = 1, knon |
---|
314 | z0m(i) = z0min |
---|
315 | z0h(i) = z0min |
---|
316 | ENDDO |
---|
317 | ELSE |
---|
318 | CALL abort_physic(modname,'version non prevue',1) |
---|
319 | ENDIF |
---|
320 | |
---|
321 | if (activate_ocean_skin >= 1) then |
---|
322 | if (type_ocean /= 'couple') sss(:knon) = 35. |
---|
323 | call bulk_flux(tkt, tks, taur, dter, dser, t_int, s_int, ds_ns, dt_ns, & |
---|
324 | u = windsp(:knon), t_ocean_1 = tsurf_new(:knon), s1 = sss(:knon), & |
---|
325 | rain = precip_rain(:knon) + precip_snow(:knon), & |
---|
326 | hf = - fluxsens(:knon), hlb = - fluxlat(:knon), & |
---|
327 | rnl = - lwnet(:knon), & |
---|
328 | tau = sqrt(flux_u1(:knon)**2 + flux_v1(:knon)**2), rhoa = rhoa, & |
---|
329 | xlv = [(rlvtt, i = 1, knon)], rf = - sens_prec_liq, dtime = dtime, & |
---|
330 | rns = swnet(:knon)) |
---|
331 | delta_sst = t_int - tsurf_new(:knon) |
---|
332 | delta_sal = s_int - sss(:knon) |
---|
333 | if (activate_ocean_skin >= 2) tsurf_new(:knon) = t_int |
---|
334 | end if |
---|
335 | |
---|
336 | END SUBROUTINE surf_ocean |
---|
337 | !**************************************************************************** |
---|
338 | ! |
---|
339 | END MODULE surf_ocean_mod |
---|