source: LMDZ4/trunk/libf/phylmd/ocean_forced_mod.F90 @ 996

Last change on this file since 996 was 996, checked in by lsce, 16 years ago
  • Modifications liées au calcul des nouveau sous-fractions
  • Nettoyage de ocean slab : il reste uniquement la version avec glace de mer forcé
  • Nouveaux variables pour distiguer la version et type d'ocean : type_ocean=force/slab/couple, version_ocean=opa8/nemo pour couplé ou version_ocean=sicOBS pour slab

JG

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 9.4 KB
Line 
1!
2! $Header$
3!
4MODULE ocean_forced_mod
5!
6! This module is used for both the sub-surfaces ocean and sea-ice for the case of a
7! forced ocean,  "ocean=force".
8!
9  USE surface_data,     ONLY : calice, calsno, tau_gl
10  USE fonte_neige_mod,  ONLY : fonte_neige
11  USE calcul_fluxs_mod, ONLY : calcul_fluxs
12  USE dimphy
13
14  IMPLICIT NONE
15
16CONTAINS
17!
18!****************************************************************************************
19!
20  SUBROUTINE ocean_forced_noice(itime, dtime, jour, knon, knindex, &
21       debut, &
22       p1lay, tq_cdrag, precip_rain, precip_snow, &
23       temp_air, spechum, &
24       petAcoef, peqAcoef, petBcoef, peqBcoef, &
25       ps, u1_lay, v1_lay, &
26       radsol, snow, agesno, &
27       qsurf, evap, fluxsens, fluxlat, &
28       tsurf_new, dflux_s, dflux_l)
29!
30! This subroutine treats the "open ocean", all grid points that are not entierly covered
31! by ice.
32! The routine receives data from climatologie file limit.nc and does some calculations at the
33! surface.
34!
35    USE limit_read_mod
36    INCLUDE "indicesol.h"
37    INCLUDE "YOMCST.h"
38
39! Input arguments
40!****************************************************************************************
41    INTEGER, INTENT(IN)                      :: itime, jour, knon
42    INTEGER, DIMENSION(klon), INTENT(IN)     :: knindex
43    LOGICAL, INTENT(IN)                      :: debut
44    REAL, INTENT(IN)                         :: dtime
45    REAL, DIMENSION(klon), INTENT(IN)        :: p1lay
46    REAL, DIMENSION(klon), INTENT(IN)        :: tq_cdrag
47    REAL, DIMENSION(klon), INTENT(IN)        :: precip_rain, precip_snow
48    REAL, DIMENSION(klon), INTENT(IN)        :: temp_air, spechum
49    REAL, DIMENSION(klon), INTENT(IN)        :: petAcoef, peqAcoef
50    REAL, DIMENSION(klon), INTENT(IN)        :: petBcoef, peqBcoef
51    REAL, DIMENSION(klon), INTENT(IN)        :: ps
52    REAL, DIMENSION(klon), INTENT(IN)        :: u1_lay, v1_lay
53
54! In/Output arguments
55!****************************************************************************************
56    REAL, DIMENSION(klon), INTENT(INOUT)     :: radsol
57    REAL, DIMENSION(klon), INTENT(INOUT)     :: snow
58    REAL, DIMENSION(klon), INTENT(INOUT)     :: agesno !? put to 0 in ocean
59 
60! Output arguments
61!****************************************************************************************
62    REAL, DIMENSION(klon), INTENT(OUT)       :: qsurf
63    REAL, DIMENSION(klon), INTENT(OUT)       :: evap, fluxsens, fluxlat
64    REAL, DIMENSION(klon), INTENT(OUT)       :: tsurf_new
65    REAL, DIMENSION(klon), INTENT(OUT)       :: dflux_s, dflux_l
66
67! Local variables
68!****************************************************************************************
69    INTEGER                     :: i
70    REAL, DIMENSION(klon)       :: cal, beta, dif_grnd
71    REAL, DIMENSION(klon)       :: alb_neig, tsurf_lim, zx_sl
72    LOGICAL                     :: check=.FALSE.
73
74!****************************************************************************************
75! Start calculation
76!****************************************************************************************
77    IF (check) WRITE(*,*)' Entering ocean_forced_noice'
78
79!****************************************************************************************
80! 1)   
81! Read sea-surface temperature from file limit.nc
82!
83!****************************************************************************************
84    CALL limit_read_sst(knon,knindex,tsurf_lim)
85
86!****************************************************************************************
87! 2)
88! Flux calculation
89!
90!****************************************************************************************
91! Set some variables for calcul_fluxs
92    cal = 0.
93    beta = 1.
94    dif_grnd = 0.
95    alb_neig(:) = 0.
96    agesno(:) = 0.
97 
98! Calcul de tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l and qsurf
99    CALL calcul_fluxs(knon, is_oce, dtime, &
100         tsurf_lim, p1lay, cal, beta, tq_cdrag, ps, &
101         precip_rain, precip_snow, snow, qsurf,  &
102         radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
103         petAcoef, peqAcoef, petBcoef, peqBcoef, &
104         tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
105
106
107  END SUBROUTINE ocean_forced_noice
108!
109!****************************************************************************************
110!
111  SUBROUTINE ocean_forced_ice(itime, dtime, jour, knon, knindex, &
112       debut, &
113       tsurf_in, p1lay, tq_cdrag, precip_rain, precip_snow, temp_air, spechum, &
114       petAcoef, peqAcoef, petBcoef, peqBcoef, &
115       ps, u1_lay, v1_lay, &
116       radsol, snow, qsol, agesno, tsoil, &
117       qsurf, alb1_new, alb2_new, evap, fluxsens, fluxlat, &
118       tsurf_new, dflux_s, dflux_l)
119!
120! This subroutine treats the ocean where there is ice.
121! The routine reads data from climatologie file and does flux calculations at the
122! surface.
123!
124    USE limit_read_mod
125
126    INCLUDE "indicesol.h"
127    INCLUDE "dimsoil.h"
128    INCLUDE "YOMCST.h"
129    INCLUDE "clesphys.h"
130
131! Input arguments
132!****************************************************************************************
133    INTEGER, INTENT(IN)                  :: itime, jour, knon
134    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
135    LOGICAL, INTENT(IN)                  :: debut
136    REAL, INTENT(IN)                     :: dtime
137    REAL, DIMENSION(klon), INTENT(IN)    :: tsurf_in
138    REAL, DIMENSION(klon), INTENT(IN)    :: p1lay
139    REAL, DIMENSION(klon), INTENT(IN)    :: tq_cdrag
140    REAL, DIMENSION(klon), INTENT(IN)    :: precip_rain, precip_snow
141    REAL, DIMENSION(klon), INTENT(IN)    :: temp_air, spechum
142    REAL, DIMENSION(klon), INTENT(IN)    :: petAcoef, peqAcoef
143    REAL, DIMENSION(klon), INTENT(IN)    :: petBcoef, peqBcoef
144    REAL, DIMENSION(klon), INTENT(IN)    :: ps
145    REAL, DIMENSION(klon), INTENT(IN)    :: u1_lay, v1_lay
146
147! In/Output arguments
148!****************************************************************************************
149    REAL, DIMENSION(klon), INTENT(INOUT)          :: radsol
150    REAL, DIMENSION(klon), INTENT(INOUT)          :: snow, qsol
151    REAL, DIMENSION(klon), INTENT(INOUT)          :: agesno
152    REAL, DIMENSION(klon, nsoilmx), INTENT(INOUT) :: tsoil
153
154! Output arguments
155!****************************************************************************************
156    REAL, DIMENSION(klon), INTENT(OUT)            :: qsurf
157    REAL, DIMENSION(klon), INTENT(OUT)            :: alb1_new  ! new albedo in visible SW interval
158    REAL, DIMENSION(klon), INTENT(OUT)            :: alb2_new  ! new albedo in near IR interval
159    REAL, DIMENSION(klon), INTENT(OUT)            :: evap, fluxsens, fluxlat
160    REAL, DIMENSION(klon), INTENT(OUT)            :: tsurf_new
161    REAL, DIMENSION(klon), INTENT(OUT)            :: dflux_s, dflux_l     
162
163! Local variables
164!****************************************************************************************
165    LOGICAL                     :: check=.FALSE.
166    INTEGER                     :: i
167    REAL                        :: zfra
168    REAL, PARAMETER             :: t_grnd=271.35
169    REAL, DIMENSION(klon)       :: cal, beta, dif_grnd, capsol
170    REAL, DIMENSION(klon)       :: alb_neig, tsurf_tmp
171    REAL, DIMENSION(klon)       :: soilcap, soilflux
172
173!****************************************************************************************
174! Start calculation
175!****************************************************************************************
176    IF (check) WRITE(*,*)'Entering surface_seaice, knon=',knon
177
178!****************************************************************************************
179! 1)
180! Flux calculation : tsurf_new, evap, fluxlat, fluxsens,
181!                    dflux_s, dflux_l and qsurf
182!****************************************************************************************
183    tsurf_tmp(:) = tsurf_in(:)
184
185! calculate the parameters cal, beta, capsol and dif_grnd
186    CALL calbeta(dtime, is_sic, knon, snow, qsol, beta, capsol, dif_grnd)
187
188   
189    IF (soil_model) THEN
190! update tsoil and calculate soilcap and soilflux
191       CALL soil(dtime, is_sic, knon, snow, tsurf_tmp, tsoil,soilcap, soilflux)
192       cal(1:knon) = RCPD / soilcap(1:knon)
193       radsol(1:knon) = radsol(1:knon)  + soilflux(1:knon)
194       dif_grnd = 1.0 / tau_gl
195    ELSE
196       dif_grnd = 1.0 / tau_gl
197       cal = RCPD * calice
198       WHERE (snow > 0.0) cal = RCPD * calsno
199    ENDIF
200
201    beta = 1.0
202    CALL calcul_fluxs(knon, is_sic, dtime, &
203         tsurf_tmp, p1lay, cal, beta, tq_cdrag, ps, &
204         precip_rain, precip_snow, snow, qsurf,  &
205         radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
206         petAcoef, peqAcoef, petBcoef, peqBcoef, &
207         tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
208
209!****************************************************************************************
210! 2)
211! Calculations due to snow and runoff
212!
213!****************************************************************************************
214    CALL fonte_neige( knon, is_sic, knindex, dtime, &
215         tsurf_tmp, precip_rain, precip_snow, &
216         snow, qsol, tsurf_new, evap)
217   
218! Calculation of albedo at snow (alb_neig) and update the age of snow (agesno)
219!
220    CALL albsno(klon, knon, dtime, agesno(:), alb_neig(:), precip_snow(:)) 
221
222    WHERE (snow(1:knon) .LT. 0.0001) agesno(1:knon) = 0.
223
224    alb1_new(:) = 0.0
225    DO i=1, knon
226       zfra = MAX(0.0,MIN(1.0,snow(i)/(snow(i)+10.0)))
227       alb1_new(i) = alb_neig(i) * zfra +  0.6 * (1.0-zfra)
228    ENDDO
229
230    alb2_new(:) = alb1_new(:)
231
232  END SUBROUTINE ocean_forced_ice
233!
234!****************************************************************************************
235!
236END MODULE ocean_forced_mod
237
238
239
240
241
242
Note: See TracBrowser for help on using the repository browser.