LMDZ
ocean_forced_mod.F90
Go to the documentation of this file.
1 !
3 !
4 ! This module is used for both the sub-surfaces ocean and sea-ice for the case of a
5 ! forced ocean, "ocean=force".
6 !
7  IMPLICIT NONE
8 
9 CONTAINS
10 !
11 !****************************************************************************************
12 !
13  SUBROUTINE ocean_forced_noice( &
14  itime, dtime, jour, knon, knindex, &
15  p1lay, cdragh, cdragq, cdragm, precip_rain, precip_snow, &
16  temp_air, spechum, &
17  acoefh, acoefq, bcoefh, bcoefq, &
18  acoefu, acoefv, bcoefu, bcoefv, &
19  ps, u1, v1, gustiness, &
20  radsol, snow, agesno, &
21  qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
22  tsurf_new, dflux_s, dflux_l)
23 !
24 ! This subroutine treats the "open ocean", all grid points that are not entierly covered
25 ! by ice.
26 ! The routine receives data from climatologie file limit.nc and does some calculations at the
27 ! surface.
28 !
29  USE dimphy
31  USE limit_read_mod
33  USE indice_sol_mod
34  include "YOMCST.h"
35  include "clesphys.h"
36 
37 
38 ! Input arguments
39 !****************************************************************************************
40  INTEGER, INTENT(IN) :: itime, jour, knon
41  INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
42  REAL, INTENT(IN) :: dtime
43  REAL, DIMENSION(klon), INTENT(IN) :: p1lay
44  REAL, DIMENSION(klon), INTENT(IN) :: cdragh, cdragq, cdragm
45  REAL, DIMENSION(klon), INTENT(IN) :: precip_rain, precip_snow
46  REAL, DIMENSION(klon), INTENT(IN) :: temp_air, spechum
47  REAL, DIMENSION(klon), INTENT(IN) :: AcoefH, AcoefQ, BcoefH, BcoefQ
48  REAL, DIMENSION(klon), INTENT(IN) :: AcoefU, AcoefV, BcoefU, BcoefV
49  REAL, DIMENSION(klon), INTENT(IN) :: ps
50  REAL, DIMENSION(klon), INTENT(IN) :: u1, v1, gustiness
51 
52 ! In/Output arguments
53 !****************************************************************************************
54  REAL, DIMENSION(klon), INTENT(INOUT) :: radsol
55  REAL, DIMENSION(klon), INTENT(INOUT) :: snow
56  REAL, DIMENSION(klon), INTENT(INOUT) :: agesno !? put to 0 in ocean
57 
58 ! Output arguments
59 !****************************************************************************************
60  REAL, DIMENSION(klon), INTENT(OUT) :: qsurf
61  REAL, DIMENSION(klon), INTENT(OUT) :: evap, fluxsens, fluxlat
62  REAL, DIMENSION(klon), INTENT(OUT) :: flux_u1, flux_v1
63  REAL, DIMENSION(klon), INTENT(OUT) :: tsurf_new
64  REAL, DIMENSION(klon), INTENT(OUT) :: dflux_s, dflux_l
65 
66 ! Local variables
67 !****************************************************************************************
68  INTEGER :: i
69  REAL, DIMENSION(klon) :: cal, beta, dif_grnd
70  REAL, DIMENSION(klon) :: alb_neig, tsurf_lim, zx_sl
71  REAL, DIMENSION(klon) :: u0, v0
72  REAL, DIMENSION(klon) :: u1_lay, v1_lay
73  LOGICAL :: check=.false.
74 
75 !****************************************************************************************
76 ! Start calculation
77 !****************************************************************************************
78  IF (check) WRITE(*,*)' Entering ocean_forced_noice'
79 
80 !****************************************************************************************
81 ! 1)
82 ! Read sea-surface temperature from file limit.nc
83 !
84 !****************************************************************************************
85 !--sb:
86 !!jyg if (knon.eq.1) then ! single-column model
87  if (klon_glo.eq.1) then ! single-column model
88  CALL read_tsurf1d(knon,tsurf_lim) ! new
89  else ! GCM
90  CALL limit_read_sst(knon,knindex,tsurf_lim)
91  endif ! knon
92 !sb--
93 
94 !****************************************************************************************
95 ! 2)
96 ! Flux calculation
97 !
98 !****************************************************************************************
99 ! Set some variables for calcul_fluxs
100  cal = 0.
101  beta = 1.
102  dif_grnd = 0.
103  alb_neig(:) = 0.
104  agesno(:) = 0.
105 ! Suppose zero surface speed
106  u0(:)=0.0
107  v0(:)=0.0
108  u1_lay(:) = u1(:) - u0(:)
109  v1_lay(:) = v1(:) - v0(:)
110 
111 ! Calcul de tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l and qsurf
112  CALL calcul_fluxs(knon, is_oce, dtime, &
113  tsurf_lim, p1lay, cal, beta, cdragh, cdragq, ps, &
114  precip_rain, precip_snow, snow, qsurf, &
115  radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, gustiness, &
116  f_qsat_oce,acoefh, acoefq, bcoefh, bcoefq, &
117  tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
118 
119 ! - Flux calculation at first modele level for U and V
120  CALL calcul_flux_wind(knon, dtime, &
121  u0, v0, u1, v1, gustiness, cdragm, &
122  acoefu, acoefv, bcoefu, bcoefv, &
123  p1lay, temp_air, &
124  flux_u1, flux_v1)
125 
126  END SUBROUTINE ocean_forced_noice
127 !
128 !***************************************************************************************
129 !
130  SUBROUTINE ocean_forced_ice( &
131  itime, dtime, jour, knon, knindex, &
132  tsurf_in, p1lay, cdragh, cdragm, precip_rain, precip_snow, temp_air, spechum, &
133  acoefh, acoefq, bcoefh, bcoefq, &
134  acoefu, acoefv, bcoefu, bcoefv, &
135  ps, u1, v1, gustiness, &
136  radsol, snow, qsol, agesno, tsoil, &
137  qsurf, alb1_new, alb2_new, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
138  tsurf_new, dflux_s, dflux_l)
139 !
140 ! This subroutine treats the ocean where there is ice.
141 ! The routine reads data from climatologie file and does flux calculations at the
142 ! surface.
143 !
144  USE dimphy
145  USE calcul_fluxs_mod
146  USE surface_data, ONLY : calice, calsno, tau_gl
147  USE limit_read_mod
148  USE fonte_neige_mod, ONLY : fonte_neige
149  USE indice_sol_mod
150 
151 ! INCLUDE "indicesol.h"
152  include "dimsoil.h"
153  include "YOMCST.h"
154  include "clesphys.h"
155 
156 ! Input arguments
157 !****************************************************************************************
158  INTEGER, INTENT(IN) :: itime, jour, knon
159  INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
160  REAL, INTENT(IN) :: dtime
161  REAL, DIMENSION(klon), INTENT(IN) :: tsurf_in
162  REAL, DIMENSION(klon), INTENT(IN) :: p1lay
163  REAL, DIMENSION(klon), INTENT(IN) :: cdragh, cdragm
164  REAL, DIMENSION(klon), INTENT(IN) :: precip_rain, precip_snow
165  REAL, DIMENSION(klon), INTENT(IN) :: temp_air, spechum
166  REAL, DIMENSION(klon), INTENT(IN) :: AcoefH, AcoefQ, BcoefH, BcoefQ
167  REAL, DIMENSION(klon), INTENT(IN) :: AcoefU, AcoefV, BcoefU, BcoefV
168  REAL, DIMENSION(klon), INTENT(IN) :: ps
169  REAL, DIMENSION(klon), INTENT(IN) :: u1, v1, gustiness
170 
171 ! In/Output arguments
172 !****************************************************************************************
173  REAL, DIMENSION(klon), INTENT(INOUT) :: radsol
174  REAL, DIMENSION(klon), INTENT(INOUT) :: snow, qsol
175  REAL, DIMENSION(klon), INTENT(INOUT) :: agesno
176  REAL, DIMENSION(klon, nsoilmx), INTENT(INOUT) :: tsoil
177 
178 ! Output arguments
179 !****************************************************************************************
180  REAL, DIMENSION(klon), INTENT(OUT) :: qsurf
181  REAL, DIMENSION(klon), INTENT(OUT) :: alb1_new ! new albedo in visible SW interval
182  REAL, DIMENSION(klon), INTENT(OUT) :: alb2_new ! new albedo in near IR interval
183  REAL, DIMENSION(klon), INTENT(OUT) :: evap, fluxsens, fluxlat
184  REAL, DIMENSION(klon), INTENT(OUT) :: flux_u1, flux_v1
185  REAL, DIMENSION(klon), INTENT(OUT) :: tsurf_new
186  REAL, DIMENSION(klon), INTENT(OUT) :: dflux_s, dflux_l
187 
188 ! Local variables
189 !****************************************************************************************
190  LOGICAL :: check=.false.
191  INTEGER :: i
192  REAL :: zfra
193  REAL, PARAMETER :: t_grnd=271.35
194  REAL, DIMENSION(klon) :: cal, beta, dif_grnd, capsol
195  REAL, DIMENSION(klon) :: alb_neig, tsurf_tmp
196  REAL, DIMENSION(klon) :: soilcap, soilflux
197  REAL, DIMENSION(klon) :: u0, v0
198  REAL, DIMENSION(klon) :: u1_lay, v1_lay
199 
200 !****************************************************************************************
201 ! Start calculation
202 !****************************************************************************************
203  IF (check) WRITE(*,*)'Entering surface_seaice, knon=',knon
204 
205 !****************************************************************************************
206 ! 1)
207 ! Flux calculation : tsurf_new, evap, fluxlat, fluxsens, flux_u1, flux_v1
208 ! dflux_s, dflux_l and qsurf
209 !****************************************************************************************
210  tsurf_tmp(:) = tsurf_in(:)
211 
212 ! calculate the parameters cal, beta, capsol and dif_grnd
213  CALL calbeta(dtime, is_sic, knon, snow, qsol, beta, capsol, dif_grnd)
214 
215 
216  IF (soil_model) THEN
217 ! update tsoil and calculate soilcap and soilflux
218  CALL soil(dtime, is_sic, knon, snow, tsurf_tmp, tsoil,soilcap, soilflux)
219  cal(1:knon) = rcpd / soilcap(1:knon)
220  radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
221  dif_grnd = 1.0 / tau_gl
222  ELSE
223  dif_grnd = 1.0 / tau_gl
224  cal = rcpd * calice
225  WHERE (snow > 0.0) cal = rcpd * calsno
226  ENDIF
227 
228  beta = 1.0
229 ! Suppose zero surface speed
230  u0(:)=0.0
231  v0(:)=0.0
232  u1_lay(:) = u1(:) - u0(:)
233  v1_lay(:) = v1(:) - v0(:)
234  CALL calcul_fluxs(knon, is_sic, dtime, &
235  tsurf_tmp, p1lay, cal, beta, cdragh, cdragh, ps, &
236  precip_rain, precip_snow, snow, qsurf, &
237  radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, gustiness, &
238  f_qsat_oce,acoefh, acoefq, bcoefh, bcoefq, &
239  tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
240 
241 ! - Flux calculation at first modele level for U and V
242  CALL calcul_flux_wind(knon, dtime, &
243  u0, v0, u1, v1, gustiness, cdragm, &
244  acoefu, acoefv, bcoefu, bcoefv, &
245  p1lay, temp_air, &
246  flux_u1, flux_v1)
247 
248 !****************************************************************************************
249 ! 2)
250 ! Calculations due to snow and runoff
251 !
252 !****************************************************************************************
253  CALL fonte_neige( knon, is_sic, knindex, dtime, &
254  tsurf_tmp, precip_rain, precip_snow, &
255  snow, qsol, tsurf_new, evap)
256 
257 ! Calculation of albedo at snow (alb_neig) and update the age of snow (agesno)
258 !
259  CALL albsno(klon, knon, dtime, agesno(:), alb_neig(:), precip_snow(:))
260 
261  WHERE (snow(1:knon) .LT. 0.0001) agesno(1:knon) = 0.
262 
263  alb1_new(:) = 0.0
264  DO i=1, knon
265  zfra = max(0.0,min(1.0,snow(i)/(snow(i)+10.0)))
266  alb1_new(i) = alb_neig(i) * zfra + 0.6 * (1.0-zfra)
267  ENDDO
268 
269  alb2_new(:) = alb1_new(:)
270 
271  END SUBROUTINE ocean_forced_ice
272 
273 !************************************************************************
274 ! 1D case
275 !************************************************************************
276  SUBROUTINE read_tsurf1d(knon,sst_out)
278 ! This subroutine specifies the surface temperature to be used in 1D simulations
279 
280  USE dimphy, ONLY : klon
281 
282  INTEGER, INTENT(IN) :: knon ! nomber of points on compressed grid
283  REAL, DIMENSION(klon), INTENT(OUT) :: sst_out ! tsurf used to force the single-column model
284 
285  INTEGER :: i
286 ! COMMON defined in lmdz1d.F:
287  real ts_cur
288  common /sst_forcing/ts_cur
289 
290  DO i = 1, knon
291  sst_out(i) = ts_cur
292  ENDDO
293 
294  END SUBROUTINE read_tsurf1d
295 
296 !
297 !************************************************************************
298 !
299 END MODULE ocean_forced_mod
300 
301 
302 
303 
304 
305 
subroutine albsno(klon, knon, dtime, agesno, alb_neig_grid, precip_snow)
Definition: albsno.F90:5
!$Header!c include clesph0 h c COMMON clesph0 soil_model
Definition: clesph0.h:6
subroutine read_tsurf1d(knon, sst_out)
subroutine fonte_neige(knon, nisurf, knindex, dtime, tsurf, precip_rain, precip_snow, snow, qsol, tsurf_new, evap)
real, parameter calsno
Definition: surface_data.F90:8
subroutine calcul_flux_wind(knon, dtime, u0, v0, u1, v1, gustiness, cdrag_m, AcoefU, AcoefV, BcoefU, BcoefV, p1lay, t1lay, flux_u1, flux_v1)
!$Header!integer nvarmx dtime
Definition: gradsdef.h:20
integer, save klon
Definition: dimphy.F90:3
subroutine ocean_forced_noice(itime, dtime, jour, knon, knindex, p1lay, cdragh, cdragq, cdragm, precip_rain, precip_snow, temp_air, spechum, AcoefH, AcoefQ, BcoefH, BcoefQ, AcoefU, AcoefV, BcoefU, BcoefV, ps, u1, v1, gustiness, radsol, snow, agesno, qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, tsurf_new, dflux_s, dflux_l)
integer, save klon_glo
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_ener_conserv REAL solaire RCFC12 RCFC12_act CFC12_ppt!IM ajout CFMIP2 CMIP5 LOGICAL ok_4xCO2atm RCFC12_per CFC12_ppt_per!OM correction du bilan d eau global!OM Correction sur precip KE REAL cvl_corr!OM Fonte calotte dans bilan eau LOGICAL ok_lic_melt!IM simulateur ISCCP INTEGER overlap!IM seuils cdrh REAL cdhmax!IM param stabilite s terres et en dehors REAL f_ri_cd_min!IM MAFo pmagic evap0!Frottement au f_cdrag_oce REAL f_qsat_oce
Definition: clesphys.h:46
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
subroutine limit_read_sst(knon, knindex, sst_out)
real, parameter tau_gl
Definition: surface_data.F90:7
!$Header!integer nvarmx s s itime
Definition: gradsdef.h:20
integer, parameter is_sic
real, parameter calice
Definition: surface_data.F90:6
subroutine calcul_fluxs(knon, nisurf, dtime, tsurf, p1lay, cal, beta, cdragh, cdragq, ps, precip_rain, precip_snow, snow, qsurf, radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, gustiness, fqsat, petAcoef, peqAcoef, petBcoef, peqBcoef, tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
Definition: dimphy.F90:1
subroutine calbeta(dtime, indice, knon, snow, qsol, vbeta, vcal, vdif)
Definition: calbeta.F90:6
integer, parameter is_oce
subroutine ocean_forced_ice(itime, dtime, jour, knon, knindex, tsurf_in, p1lay, cdragh, cdragm, precip_rain, precip_snow, temp_air, spechum, AcoefH, AcoefQ, BcoefH, BcoefQ, AcoefU, AcoefV, BcoefU, BcoefV, ps, u1, v1, gustiness, radsol, snow, qsol, agesno, tsoil, qsurf, alb1_new, alb2_new, evap, fluxsens, fluxlat, flux_u1, flux_v1, tsurf_new, dflux_s, dflux_l)
subroutine soil(ptimestep, indice, knon, snow, ptsrf, ptsoil, pcapcal, pfluxgrd)
Definition: soil.F90:6