1 | MODULE sbcblk_clio |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE sbcblk_clio *** |
---|
4 | !! Ocean forcing: bulk thermohaline forcing of the ocean (or ice) |
---|
5 | !!===================================================================== |
---|
6 | !! History : OPA ! 1997-06 (Louvain-La-Neuve) Original code |
---|
7 | !! ! 2001-04 (C. Ethe) add flx_blk_declin |
---|
8 | !! NEMO 2.0 ! 2002-08 (C. Ethe, G. Madec) F90: Free form and module |
---|
9 | !! 3.0 ! 2008-03 (C. Talandier, G. Madec) surface module + LIM3 |
---|
10 | !! 3.2 ! 2009-04 (B. Lemaire) Introduce iom_put |
---|
11 | !!---------------------------------------------------------------------- |
---|
12 | |
---|
13 | !!---------------------------------------------------------------------- |
---|
14 | !! sbc_blk_clio : CLIO bulk formulation: read and update required input fields |
---|
15 | !! blk_clio_oce : ocean CLIO bulk formulea: compute momentum, heat and freswater fluxes for the ocean |
---|
16 | !! blk_ice_clio : ice CLIO bulk formulea: compute momentum, heat and freswater fluxes for the sea-ice |
---|
17 | !! blk_clio_qsr_oce : shortwave radiation for ocean computed from the cloud cover |
---|
18 | !! blk_clio_qsr_ice : shortwave radiation for ice computed from the cloud cover |
---|
19 | !! flx_blk_declin : solar declinaison |
---|
20 | !!---------------------------------------------------------------------- |
---|
21 | USE oce ! ocean dynamics and tracers |
---|
22 | USE dom_oce ! ocean space and time domain |
---|
23 | USE phycst ! physical constants |
---|
24 | USE fldread ! read input fields |
---|
25 | USE sbc_oce ! Surface boundary condition: ocean fields |
---|
26 | USE iom ! I/O manager library |
---|
27 | USE in_out_manager ! I/O manager |
---|
28 | USE lib_mpp ! distribued memory computing library |
---|
29 | USE lbclnk ! ocean lateral boundary conditions (or mpp link) |
---|
30 | |
---|
31 | USE albedo |
---|
32 | USE prtctl ! Print control |
---|
33 | #if defined key_lim3 |
---|
34 | USE ice |
---|
35 | USE sbc_ice ! Surface boundary condition: ice fields |
---|
36 | #elif defined key_lim2 |
---|
37 | USE ice_2 |
---|
38 | #endif |
---|
39 | IMPLICIT NONE |
---|
40 | PRIVATE |
---|
41 | |
---|
42 | PUBLIC sbc_blk_clio ! routine called by sbcmod.F90 |
---|
43 | PUBLIC blk_ice_clio ! routine called by sbcice_lim.F90 |
---|
44 | |
---|
45 | INTEGER , PARAMETER :: jpfld = 7 ! maximum number of files to read |
---|
46 | INTEGER , PARAMETER :: jp_utau = 1 ! index of wind stress (i-component) (N/m2) at U-point |
---|
47 | INTEGER , PARAMETER :: jp_vtau = 2 ! index of wind stress (j-component) (N/m2) at V-point |
---|
48 | INTEGER , PARAMETER :: jp_wndm = 3 ! index of 10m wind module (m/s) at T-point |
---|
49 | INTEGER , PARAMETER :: jp_humi = 4 ! index of specific humidity ( - ) |
---|
50 | INTEGER , PARAMETER :: jp_ccov = 5 ! index of cloud cover ( - ) |
---|
51 | INTEGER , PARAMETER :: jp_tair = 6 ! index of 10m air temperature (Kelvin) |
---|
52 | INTEGER , PARAMETER :: jp_prec = 7 ! index of total precipitation (rain+snow) (Kg/m2/s) |
---|
53 | TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf ! structure of input fields (file informations, fields read) |
---|
54 | |
---|
55 | INTEGER, PARAMETER :: jpintsr = 24 ! number of time step between sunrise and sunset |
---|
56 | ! ! uses for heat flux computation |
---|
57 | LOGICAL :: lbulk_init = .TRUE. ! flag, bulk initialization done or not) |
---|
58 | |
---|
59 | #if ! defined key_lim3 |
---|
60 | ! in namicerun with LIM3 |
---|
61 | REAL(wp) :: cai = 1.40e-3 ! best estimate of atm drag in order to get correct FS export in ORCA2-LIM |
---|
62 | REAL(wp) :: cao = 1.00e-3 ! chosen by default ==> should depends on many things... !!gmto be updated |
---|
63 | #endif |
---|
64 | |
---|
65 | REAL(wp) :: rdtbs2 !: |
---|
66 | |
---|
67 | REAL(wp), DIMENSION(19) :: budyko ! BUDYKO's coefficient (cloudiness effect on LW radiation) |
---|
68 | DATA budyko / 1.00, 0.98, 0.95, 0.92, 0.89, 0.86, 0.83, 0.80, 0.78, 0.75, & |
---|
69 | & 0.72, 0.69, 0.67, 0.64, 0.61, 0.58, 0.56, 0.53, 0.50 / |
---|
70 | REAL(wp), DIMENSION(20) :: tauco ! cloud optical depth coefficient |
---|
71 | DATA tauco / 6.6, 6.6, 7.0, 7.2, 7.1, 6.8, 6.5, 6.6, 7.1, 7.6, & |
---|
72 | & 6.6, 6.1, 5.6, 5.5, 5.8, 5.8, 5.6, 5.6, 5.6, 5.6 / |
---|
73 | !! |
---|
74 | REAL(wp), DIMENSION(jpi,jpj) :: sbudyko ! cloudiness effect on LW radiation |
---|
75 | REAL(wp), DIMENSION(jpi,jpj) :: stauc ! cloud optical depth |
---|
76 | |
---|
77 | REAL(wp) :: zeps = 1.e-20 ! constant values |
---|
78 | REAL(wp) :: zeps0 = 1.e-13 |
---|
79 | |
---|
80 | !! * Substitutions |
---|
81 | # include "vectopt_loop_substitute.h90" |
---|
82 | !!---------------------------------------------------------------------- |
---|
83 | !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009) |
---|
84 | !! $Id$ |
---|
85 | !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) |
---|
86 | !!---------------------------------------------------------------------- |
---|
87 | |
---|
88 | CONTAINS |
---|
89 | |
---|
90 | SUBROUTINE sbc_blk_clio( kt ) |
---|
91 | !!--------------------------------------------------------------------- |
---|
92 | !! *** ROUTINE sbc_blk_clio *** |
---|
93 | !! |
---|
94 | !! ** Purpose : provide at each time step the surface ocean fluxes |
---|
95 | !! (momentum, heat, freshwater and runoff) |
---|
96 | !! |
---|
97 | !! ** Method : (1) READ each fluxes in NetCDF files: |
---|
98 | !! the i-component of the stress (N/m2) |
---|
99 | !! the j-component of the stress (N/m2) |
---|
100 | !! the 10m wind pseed module (m/s) |
---|
101 | !! the 10m air temperature (Kelvin) |
---|
102 | !! the 10m specific humidity (-) |
---|
103 | !! the cloud cover (-) |
---|
104 | !! the total precipitation (rain+snow) (Kg/m2/s) |
---|
105 | !! (2) CALL blk_oce_clio |
---|
106 | !! |
---|
107 | !! C A U T I O N : never mask the surface stress fields |
---|
108 | !! the stress is assumed to be in the mesh referential |
---|
109 | !! i.e. the (i,j) referential |
---|
110 | !! |
---|
111 | !! ** Action : defined at each time-step at the air-sea interface |
---|
112 | !! - utau, vtau i- and j-component of the wind stress |
---|
113 | !! - taum wind stress module at T-point |
---|
114 | !! - wndm 10m wind module at T-point |
---|
115 | !! - qns, qsr non-slor and solar heat flux |
---|
116 | !! - emp, emps evaporation minus precipitation |
---|
117 | !!---------------------------------------------------------------------- |
---|
118 | INTEGER, INTENT( in ) :: kt ! ocean time step |
---|
119 | !! |
---|
120 | INTEGER :: ifpr, jfpr ! dummy indices |
---|
121 | INTEGER :: ierror ! return error code |
---|
122 | !! |
---|
123 | CHARACTER(len=100) :: cn_dir ! Root directory for location of CLIO files |
---|
124 | TYPE(FLD_N), DIMENSION(jpfld) :: slf_i ! array of namelist informations on the fields to read |
---|
125 | TYPE(FLD_N) :: sn_utau, sn_vtau, sn_wndm, sn_tair ! informations about the fields to be read |
---|
126 | TYPE(FLD_N) :: sn_humi, sn_ccov, sn_prec ! " " |
---|
127 | !! |
---|
128 | NAMELIST/namsbc_clio/ cn_dir, sn_utau, sn_vtau, sn_wndm, sn_humi, & |
---|
129 | & sn_ccov, sn_tair, sn_prec |
---|
130 | !!--------------------------------------------------------------------- |
---|
131 | write(narea+200,*)'clio : '; call flush(narea+200) |
---|
132 | |
---|
133 | ! ! ====================== ! |
---|
134 | IF( kt == nit000 ) THEN ! First call kt=nit000 ! |
---|
135 | ! ! ====================== ! |
---|
136 | ! set file information (default values) |
---|
137 | cn_dir = './' ! directory in which the model is executed |
---|
138 | |
---|
139 | ! (NB: frequency positive => hours, negative => months) |
---|
140 | ! ! file ! frequency ! variable ! time intep ! clim ! 'yearly' or ! weights ! rotation ! |
---|
141 | ! ! name ! (hours) ! name ! (T/F) ! (T/F) ! 'monthly' ! filename ! pairs ! |
---|
142 | sn_utau = FLD_N( 'utau' , 24 , 'utau' , .true. , .false. , 'yearly' , '' , '' ) |
---|
143 | sn_vtau = FLD_N( 'vtau' , 24 , 'vtau' , .true. , .false. , 'yearly' , '' , '' ) |
---|
144 | sn_wndm = FLD_N( 'mwnd10m' , 24 , 'm_10' , .true. , .false. , 'yearly' , '' , '' ) |
---|
145 | sn_tair = FLD_N( 'tair10m' , 24 , 't_10' , .false. , .false. , 'yearly' , '' , '' ) |
---|
146 | sn_humi = FLD_N( 'humi10m' , 24 , 'q_10' , .false. , .false. , 'yearly' , '' , '' ) |
---|
147 | sn_ccov = FLD_N( 'ccover' , -1 , 'cloud' , .true. , .false. , 'yearly' , '' , '' ) |
---|
148 | sn_prec = FLD_N( 'precip' , -1 , 'precip' , .true. , .false. , 'yearly' , '' , '' ) |
---|
149 | |
---|
150 | REWIND( numnam ) ! ... read in namlist namsbc_clio |
---|
151 | READ ( numnam, namsbc_clio ) |
---|
152 | |
---|
153 | ! store namelist information in an array |
---|
154 | slf_i(jp_utau) = sn_utau ; slf_i(jp_vtau) = sn_vtau ; slf_i(jp_wndm) = sn_wndm |
---|
155 | slf_i(jp_tair) = sn_tair ; slf_i(jp_humi) = sn_humi |
---|
156 | slf_i(jp_ccov) = sn_ccov ; slf_i(jp_prec) = sn_prec |
---|
157 | |
---|
158 | ! set sf structure |
---|
159 | ALLOCATE( sf(jpfld), STAT=ierror ) |
---|
160 | IF( ierror > 0 ) THEN |
---|
161 | CALL ctl_stop( 'sbc_blk_clio: unable to allocate sf structure' ) ; RETURN |
---|
162 | ENDIF |
---|
163 | DO ifpr= 1, jpfld |
---|
164 | ALLOCATE( sf(ifpr)%fnow(jpi,jpj,1) ) |
---|
165 | IF( slf_i(ifpr)%ln_tint ) ALLOCATE( sf(ifpr)%fdta(jpi,jpj,1,2) ) |
---|
166 | END DO |
---|
167 | ! fill sf with slf_i and control print |
---|
168 | CALL fld_fill( sf, slf_i, cn_dir, 'sbc_blk_clio', 'flux formulation for ocean surface boundary condition', 'namsbc_clio' ) |
---|
169 | ! |
---|
170 | ENDIF |
---|
171 | ! ! ====================== ! |
---|
172 | ! ! At each time-step ! |
---|
173 | ! ! ====================== ! |
---|
174 | ! |
---|
175 | CALL fld_read( kt, nn_fsbc, sf ) ! input fields provided at the current time-step |
---|
176 | ! |
---|
177 | #if defined key_lim3 |
---|
178 | tatm_ice(:,:) = sf(jp_tair)%fnow(:,:,1) !RB ugly patch |
---|
179 | #endif |
---|
180 | ! |
---|
181 | IF(lwp .AND. nitend-nit000 <= 100 ) THEN |
---|
182 | IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN |
---|
183 | WRITE(numout,*) |
---|
184 | WRITE(numout,*) ' read monthly CLIO fluxes: ok, kt: ', kt |
---|
185 | WRITE(numout,*) |
---|
186 | ifpr = INT(jpi/8) ; jfpr = INT(jpj/10) |
---|
187 | WRITE(numout,*) TRIM(sf(jp_utau)%clvar),' day: ',ndastp |
---|
188 | CALL prihre( sf(jp_utau)%fnow,jpi,jpj,1,jpi,ifpr,1,jpj,jfpr,0.,numout ) |
---|
189 | WRITE(numout,*) |
---|
190 | WRITE(numout,*) TRIM(sf(jp_vtau)%clvar),' day: ',ndastp |
---|
191 | CALL prihre( sf(jp_vtau)%fnow,jpi,jpj,1,jpi,ifpr,1,jpj,jfpr,0.,numout ) |
---|
192 | WRITE(numout,*) |
---|
193 | WRITE(numout,*) TRIM(sf(jp_humi)%clvar),' day: ',ndastp |
---|
194 | CALL prihre( sf(jp_humi)%fnow,jpi,jpj,1,jpi,ifpr,1,jpj,jfpr,0.,numout ) |
---|
195 | WRITE(numout,*) |
---|
196 | WRITE(numout,*) TRIM(sf(jp_wndm)%clvar),' day: ',ndastp |
---|
197 | CALL prihre( sf(jp_wndm)%fnow,jpi,jpj,1,jpi,ifpr,1,jpj,jfpr,0.,numout ) |
---|
198 | WRITE(numout,*) |
---|
199 | WRITE(numout,*) TRIM(sf(jp_ccov)%clvar),' day: ',ndastp |
---|
200 | CALL prihre( sf(jp_ccov)%fnow,jpi,jpj,1,jpi,ifpr,1,jpj,jfpr,0.,numout ) |
---|
201 | WRITE(numout,*) |
---|
202 | WRITE(numout,*) TRIM(sf(jp_prec)%clvar),' day: ',ndastp |
---|
203 | CALL prihre( sf(jp_prec)%fnow,jpi,jpj,1,jpi,ifpr,1,jpj,jfpr,0.,numout ) |
---|
204 | WRITE(numout,*) |
---|
205 | WRITE(numout,*) TRIM(sf(jp_tair)%clvar),' day: ',ndastp |
---|
206 | CALL prihre( sf(jp_tair)%fnow,jpi,jpj,1,jpi,ifpr,1,jpj,jfpr,0.,numout ) |
---|
207 | WRITE(numout,*) |
---|
208 | ENDIF |
---|
209 | ENDIF |
---|
210 | |
---|
211 | IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN |
---|
212 | CALL blk_oce_clio( sf, sst_m ) ! compute the surface ocean fluxes using CLIO bulk formulea |
---|
213 | ENDIF ! |
---|
214 | ! |
---|
215 | END SUBROUTINE sbc_blk_clio |
---|
216 | |
---|
217 | |
---|
218 | SUBROUTINE blk_oce_clio( sf, pst ) |
---|
219 | !!--------------------------------------------------------------------------- |
---|
220 | !! *** ROUTINE blk_oce_clio *** |
---|
221 | !! |
---|
222 | !! ** Purpose : Compute momentum, heat and freshwater fluxes at ocean surface |
---|
223 | !! using CLIO bulk formulea |
---|
224 | !! |
---|
225 | !! ** Method : The flux of heat at the ocean surfaces are derived |
---|
226 | !! from semi-empirical ( or bulk ) formulae which relate the flux to |
---|
227 | !! the properties of the surface and of the lower atmosphere. Here, we |
---|
228 | !! follow the work of Oberhuber, 1988 |
---|
229 | !! - momentum flux (stresses) directly read in files at U- and V-points |
---|
230 | !! - compute ocean/ice albedos (call albedo_oce/albedo_ice) |
---|
231 | !! - compute shortwave radiation for ocean (call blk_clio_qsr_oce) |
---|
232 | !! - compute long-wave radiation for the ocean |
---|
233 | !! - compute the turbulent heat fluxes over the ocean |
---|
234 | !! - deduce the evaporation over the ocean |
---|
235 | !! ** Action : Fluxes over the ocean: |
---|
236 | !! - utau, vtau i- and j-component of the wind stress |
---|
237 | !! - taum wind stress module at T-point |
---|
238 | !! - wndm 10m wind module at T-point |
---|
239 | !! - qns, qsr non-slor and solar heat flux |
---|
240 | !! - emp, emps evaporation minus precipitation |
---|
241 | !! ** Nota : sf has to be a dummy argument for AGRIF on NEC |
---|
242 | !!---------------------------------------------------------------------- |
---|
243 | TYPE(fld), INTENT(in), DIMENSION(:) :: sf ! input data |
---|
244 | REAL(wp) , INTENT(in), DIMENSION(jpi,jpj) :: pst ! surface temperature [Celcius] |
---|
245 | !! |
---|
246 | INTEGER :: ji, jj ! dummy loop indices |
---|
247 | !! |
---|
248 | REAL(wp) :: zrhova, zcsho, zcleo, zcldeff ! temporary scalars |
---|
249 | REAL(wp) :: zqsato, zdteta, zdeltaq, ztvmoy, zobouks ! - - |
---|
250 | REAL(wp) :: zpsims, zpsihs, zpsils, zobouku, zxins, zpsimu ! - - |
---|
251 | REAL(wp) :: zpsihu, zpsilu, zstab,zpsim, zpsih, zpsil ! - - |
---|
252 | REAL(wp) :: zvatmg, zcmn, zchn, zcln, zcmcmn, zdenum ! - - |
---|
253 | REAL(wp) :: zdtetar, ztvmoyr, zlxins, zchcm, zclcm ! - - |
---|
254 | REAL(wp) :: zmt1, zmt2, zmt3, ztatm3, ztamr, ztaevbk ! - - |
---|
255 | REAL(wp) :: zsst, ztatm, zcco1, zpatm, zcmax, zrmax ! - - |
---|
256 | REAL(wp) :: zrhoa, zev, zes, zeso, zqatm, zevsqr ! - - |
---|
257 | REAL(wp) :: ztx2, zty2 ! - - |
---|
258 | !! |
---|
259 | REAL(wp), DIMENSION(jpi,jpj) :: zqlw ! long-wave heat flux over ocean |
---|
260 | REAL(wp), DIMENSION(jpi,jpj) :: zqla ! latent heat flux over ocean |
---|
261 | REAL(wp), DIMENSION(jpi,jpj) :: zqsb ! sensible heat flux over ocean |
---|
262 | !!--------------------------------------------------------------------- |
---|
263 | |
---|
264 | zpatm = 101000. ! atmospheric pressure (assumed constant here) |
---|
265 | |
---|
266 | !------------------------------------! |
---|
267 | ! momentum fluxes (utau, vtau ) ! |
---|
268 | !------------------------------------! |
---|
269 | !CDIR COLLAPSE |
---|
270 | DO jj = 1 , jpj |
---|
271 | DO ji = 1, jpi |
---|
272 | utau(ji,jj) = sf(jp_utau)%fnow(ji,jj,1) |
---|
273 | vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj,1) |
---|
274 | END DO |
---|
275 | END DO |
---|
276 | |
---|
277 | !------------------------------------! |
---|
278 | ! wind stress module (taum ) ! |
---|
279 | !------------------------------------! |
---|
280 | !CDIR NOVERRCHK |
---|
281 | DO jj = 2, jpjm1 |
---|
282 | !CDIR NOVERRCHK |
---|
283 | DO ji = fs_2, fs_jpim1 ! vector opt. |
---|
284 | ztx2 = utau(ji-1,jj ) + utau(ji,jj) |
---|
285 | zty2 = vtau(ji ,jj-1) + vtau(ji,jj) |
---|
286 | taum(ji,jj) = 0.5 * SQRT( ztx2 * ztx2 + zty2 * zty2 ) |
---|
287 | END DO |
---|
288 | END DO |
---|
289 | CALL lbc_lnk( taum, 'T', 1. ) |
---|
290 | |
---|
291 | !------------------------------------! |
---|
292 | ! store the wind speed (wndm ) ! |
---|
293 | !------------------------------------! |
---|
294 | !CDIR COLLAPSE |
---|
295 | DO jj = 1 , jpj |
---|
296 | DO ji = 1, jpi |
---|
297 | wndm(ji,jj) = sf(jp_wndm)%fnow(ji,jj,1) |
---|
298 | END DO |
---|
299 | END DO |
---|
300 | |
---|
301 | !------------------------------------------------! |
---|
302 | ! Shortwave radiation for ocean and snow/ice ! |
---|
303 | !------------------------------------------------! |
---|
304 | |
---|
305 | CALL blk_clio_qsr_oce( qsr ) |
---|
306 | |
---|
307 | !------------------------! |
---|
308 | ! Other ocean fluxes ! |
---|
309 | !------------------------! |
---|
310 | !CDIR NOVERRCHK |
---|
311 | !CDIR COLLAPSE |
---|
312 | DO jj = 1, jpj |
---|
313 | !CDIR NOVERRCHK |
---|
314 | DO ji = 1, jpi |
---|
315 | ! |
---|
316 | zsst = pst(ji,jj) + rt0 ! converte Celcius to Kelvin the SST |
---|
317 | ztatm = sf(jp_tair)%fnow(ji,jj,1) ! and set minimum value far above 0 K (=rt0 over land) |
---|
318 | zcco1 = 1.0 - sf(jp_ccov)%fnow(ji,jj,1) ! fraction of clear sky ( 1 - cloud cover) |
---|
319 | zrhoa = zpatm / ( 287.04 * ztatm ) ! air density (equation of state for dry air) |
---|
320 | ztamr = ztatm - rtt ! Saturation water vapour |
---|
321 | zmt1 = SIGN( 17.269, ztamr ) ! || |
---|
322 | zmt2 = SIGN( 21.875, ztamr ) ! \ / |
---|
323 | zmt3 = SIGN( 28.200, -ztamr ) ! \/ |
---|
324 | zes = 611.0 * EXP( ABS( ztamr ) * MIN ( zmt1, zmt2 ) / ( ztatm - 35.86 + MAX( 0.e0, zmt3 ) ) ) |
---|
325 | zev = sf(jp_humi)%fnow(ji,jj,1) * zes ! vapour pressure |
---|
326 | zevsqr = SQRT( zev * 0.01 ) ! square-root of vapour pressure |
---|
327 | zqatm = 0.622 * zev / ( zpatm - 0.378 * zev ) ! specific humidity |
---|
328 | |
---|
329 | !--------------------------------------! |
---|
330 | ! long-wave radiation over the ocean ! ( Berliand 1952 ; all latitudes ) |
---|
331 | !--------------------------------------! |
---|
332 | ztatm3 = ztatm * ztatm * ztatm |
---|
333 | zcldeff = 1.0 - sbudyko(ji,jj) * sf(jp_ccov)%fnow(ji,jj,1) * sf(jp_ccov)%fnow(ji,jj,1) |
---|
334 | ztaevbk = ztatm * ztatm3 * zcldeff * ( 0.39 - 0.05 * zevsqr ) |
---|
335 | ! |
---|
336 | zqlw(ji,jj) = - emic * stefan * ( ztaevbk + 4. * ztatm3 * ( zsst - ztatm ) ) |
---|
337 | |
---|
338 | !-------------------------------------------------- |
---|
339 | ! Latent and sensible heat fluxes over the ocean |
---|
340 | !-------------------------------------------------- |
---|
341 | ! ! vapour pressure at saturation of ocean |
---|
342 | zeso = 611.0 * EXP ( 17.2693884 * ( zsst - rtt ) * tmask(ji,jj,1) / ( zsst - 35.86 ) ) |
---|
343 | |
---|
344 | zqsato = ( 0.622 * zeso ) / ( zpatm - 0.378 * zeso ) ! humidity close to the ocean surface (at saturation) |
---|
345 | |
---|
346 | ! Drag coefficients from Large and Pond (1981,1982) |
---|
347 | ! ! Stability parameters |
---|
348 | zdteta = zsst - ztatm |
---|
349 | zdeltaq = zqatm - zqsato |
---|
350 | ztvmoy = ztatm * ( 1. + 2.2e-3 * ztatm * zqatm ) |
---|
351 | zdenum = MAX( sf(jp_wndm)%fnow(ji,jj,1) * sf(jp_wndm)%fnow(ji,jj,1) * ztvmoy, zeps ) |
---|
352 | zdtetar = zdteta / zdenum |
---|
353 | ztvmoyr = ztvmoy * ztvmoy * zdeltaq / zdenum |
---|
354 | ! ! case of stable atmospheric conditions |
---|
355 | zobouks = -70.0 * 10. * ( zdtetar + 3.2e-3 * ztvmoyr ) |
---|
356 | zobouks = MAX( 0.e0, zobouks ) |
---|
357 | zpsims = -7.0 * zobouks |
---|
358 | zpsihs = zpsims |
---|
359 | zpsils = zpsims |
---|
360 | ! ! case of unstable atmospheric conditions |
---|
361 | zobouku = MIN( 0.e0, -100.0 * 10.0 * ( zdtetar + 2.2e-3 * ztvmoyr ) ) |
---|
362 | zxins = ( 1. - 16. * zobouku )**0.25 |
---|
363 | zlxins = LOG( ( 1. + zxins * zxins ) / 2. ) |
---|
364 | zpsimu = 2. * LOG( ( 1 + zxins ) * 0.5 ) + zlxins - 2. * ATAN( zxins ) + rpi * 0.5 |
---|
365 | zpsihu = 2. * zlxins |
---|
366 | zpsilu = zpsihu |
---|
367 | ! ! intermediate values |
---|
368 | zstab = MAX( 0.e0, SIGN( 1.e0, zdteta ) ) |
---|
369 | zpsim = zstab * zpsimu + ( 1.0 - zstab ) * zpsims |
---|
370 | zpsih = zstab * zpsihu + ( 1.0 - zstab ) * zpsihs |
---|
371 | zpsil = zpsih |
---|
372 | |
---|
373 | zvatmg = MAX( 0.032 * 1.5e-3 * sf(jp_wndm)%fnow(ji,jj,1) * sf(jp_wndm)%fnow(ji,jj,1) / grav, zeps ) |
---|
374 | zcmn = vkarmn / LOG ( 10. / zvatmg ) |
---|
375 | zchn = 0.0327 * zcmn |
---|
376 | zcln = 0.0346 * zcmn |
---|
377 | zcmcmn = 1. / ( 1. - zcmn * zpsim / vkarmn ) |
---|
378 | ! sometimes the ratio zchn * zpsih / ( vkarmn * zcmn ) is too close to 1 and zchcm becomes very very big |
---|
379 | zcmax = 0.1 ! choice for maximum value of the heat transfer coefficient, guided by my intuition |
---|
380 | zrmax = 1 - 3.e-4 / zcmax ! maximum value of the ratio |
---|
381 | zchcm = zcmcmn / ( 1. - MIN ( zchn * zpsih / ( vkarmn * zcmn ) , zrmax ) ) |
---|
382 | zclcm = zchcm |
---|
383 | ! ! transfert coef. (Large and Pond 1981,1982) |
---|
384 | zcsho = zchn * zchcm |
---|
385 | zcleo = zcln * zclcm |
---|
386 | |
---|
387 | zrhova = zrhoa * sf(jp_wndm)%fnow(ji,jj,1) |
---|
388 | |
---|
389 | ! sensible heat flux |
---|
390 | zqsb(ji,jj) = zrhova * zcsho * 1004.0 * ( zsst - ztatm ) |
---|
391 | |
---|
392 | ! latent heat flux (bounded by zero) |
---|
393 | zqla(ji,jj) = MAX( 0.e0, zrhova * zcleo * 2.5e+06 * ( zqsato - zqatm ) ) |
---|
394 | ! |
---|
395 | END DO |
---|
396 | END DO |
---|
397 | |
---|
398 | ! ----------------------------------------------------------------------------- ! |
---|
399 | ! III Total FLUXES ! |
---|
400 | ! ----------------------------------------------------------------------------- ! |
---|
401 | |
---|
402 | !CDIR COLLAPSE |
---|
403 | !CDIR NOVERRCHK |
---|
404 | DO jj = 1, jpj |
---|
405 | !CDIR NOVERRCHK |
---|
406 | DO ji = 1, jpi |
---|
407 | qns (ji,jj) = zqlw(ji,jj) - zqsb(ji,jj) - zqla(ji,jj) ! Downward Non Solar flux |
---|
408 | emp (ji,jj) = zqla(ji,jj) / cevap - sf(jp_prec)%fnow(ji,jj,1) / rday * tmask(ji,jj,1) |
---|
409 | END DO |
---|
410 | END DO |
---|
411 | emps(:,:) = emp(:,:) |
---|
412 | ! |
---|
413 | CALL iom_put( "qlw_oce", zqlw ) ! output downward longwave heat over the ocean |
---|
414 | CALL iom_put( "qsb_oce", - zqsb ) ! output downward sensible heat over the ocean |
---|
415 | CALL iom_put( "qla_oce", - zqla ) ! output downward latent heat over the ocean |
---|
416 | CALL iom_put( "qns_oce", qns ) ! output downward non solar heat over the ocean |
---|
417 | |
---|
418 | IF(ln_ctl) THEN |
---|
419 | CALL prt_ctl(tab2d_1=zqsb , clinfo1=' blk_oce_clio: zqsb : ', tab2d_2=zqlw , clinfo2=' zqlw : ') |
---|
420 | CALL prt_ctl(tab2d_1=zqla , clinfo1=' blk_oce_clio: zqla : ', tab2d_2=qsr , clinfo2=' qsr : ') |
---|
421 | CALL prt_ctl(tab2d_1=pst , clinfo1=' blk_oce_clio: pst : ', tab2d_2=emp , clinfo2=' emp : ') |
---|
422 | CALL prt_ctl(tab2d_1=utau , clinfo1=' blk_oce_clio: utau : ', mask1=umask, & |
---|
423 | & tab2d_2=vtau , clinfo2=' vtau : ', mask2=vmask ) |
---|
424 | ENDIF |
---|
425 | |
---|
426 | END SUBROUTINE blk_oce_clio |
---|
427 | |
---|
428 | |
---|
429 | SUBROUTINE blk_ice_clio( pst , palb_cs, palb_os , & |
---|
430 | & p_taui, p_tauj, p_qns , p_qsr, & |
---|
431 | & p_qla , p_dqns, p_dqla, & |
---|
432 | & p_tpr , p_spr , & |
---|
433 | & p_fr1 , p_fr2 , cd_grid, pdim ) |
---|
434 | !!--------------------------------------------------------------------------- |
---|
435 | !! *** ROUTINE blk_ice_clio *** |
---|
436 | !! |
---|
437 | !! ** Purpose : Computation of the heat fluxes at ocean and snow/ice |
---|
438 | !! surface the solar heat at ocean and snow/ice surfaces and the |
---|
439 | !! sensitivity of total heat fluxes to the SST variations |
---|
440 | !! |
---|
441 | !! ** Method : The flux of heat at the ice and ocean surfaces are derived |
---|
442 | !! from semi-empirical ( or bulk ) formulae which relate the flux to |
---|
443 | !! the properties of the surface and of the lower atmosphere. Here, we |
---|
444 | !! follow the work of Oberhuber, 1988 |
---|
445 | !! |
---|
446 | !! ** Action : call albedo_oce/albedo_ice to compute ocean/ice albedo |
---|
447 | !! computation of snow precipitation |
---|
448 | !! computation of solar flux at the ocean and ice surfaces |
---|
449 | !! computation of the long-wave radiation for the ocean and sea/ice |
---|
450 | !! computation of turbulent heat fluxes over water and ice |
---|
451 | !! computation of evaporation over water |
---|
452 | !! computation of total heat fluxes sensitivity over ice (dQ/dT) |
---|
453 | !! computation of latent heat flux sensitivity over ice (dQla/dT) |
---|
454 | !! |
---|
455 | !!---------------------------------------------------------------------- |
---|
456 | REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: pst ! ice surface temperature [Kelvin] |
---|
457 | REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: palb_cs ! ice albedo (clear sky) (alb_ice_cs) [%] |
---|
458 | REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: palb_os ! ice albedo (overcast sky) (alb_ice_os) [%] |
---|
459 | REAL(wp), INTENT( out), DIMENSION(jpi,jpj) :: p_taui ! surface ice stress at I-point (i-component) [N/m2] |
---|
460 | REAL(wp), INTENT( out), DIMENSION(jpi,jpj) :: p_tauj ! surface ice stress at I-point (j-component) [N/m2] |
---|
461 | REAL(wp), INTENT( out), DIMENSION(:,:,:) :: p_qns ! non solar heat flux over ice (T-point) [W/m2] |
---|
462 | REAL(wp), INTENT( out), DIMENSION(:,:,:) :: p_qsr ! solar heat flux over ice (T-point) [W/m2] |
---|
463 | REAL(wp), INTENT( out), DIMENSION(:,:,:) :: p_qla ! latent heat flux over ice (T-point) [W/m2] |
---|
464 | REAL(wp), INTENT( out), DIMENSION(:,:,:) :: p_dqns ! non solar heat sensistivity (T-point) [W/m2] |
---|
465 | REAL(wp), INTENT( out), DIMENSION(:,:,:) :: p_dqla ! latent heat sensistivity (T-point) [W/m2] |
---|
466 | REAL(wp), INTENT( out), DIMENSION(jpi,jpj) :: p_tpr ! total precipitation (T-point) [Kg/m2/s] |
---|
467 | REAL(wp), INTENT( out), DIMENSION(jpi,jpj) :: p_spr ! solid precipitation (T-point) [Kg/m2/s] |
---|
468 | REAL(wp), INTENT( out), DIMENSION(jpi,jpj) :: p_fr1 ! 1sr fraction of qsr penetration in ice [%] |
---|
469 | REAL(wp), INTENT( out), DIMENSION(jpi,jpj) :: p_fr2 ! 2nd fraction of qsr penetration in ice [%] |
---|
470 | CHARACTER(len=1), INTENT(in ) :: cd_grid ! type of sea-ice grid ("C" or "B" grid) |
---|
471 | INTEGER, INTENT(in ) :: pdim ! number of ice categories |
---|
472 | !! |
---|
473 | INTEGER :: ji, jj, jl ! dummy loop indices |
---|
474 | INTEGER :: ijpl ! number of ice categories (size of 3rd dim of input arrays) |
---|
475 | !! |
---|
476 | REAL(wp) :: zcoef, zmt1, zmt2, zmt3, ztatm3 ! temporary scalars |
---|
477 | REAL(wp) :: ztaevbk, zind1, zind2, zind3, ztamr ! - - |
---|
478 | REAL(wp) :: zesi, zqsati, zdesidt ! - - |
---|
479 | REAL(wp) :: zdqla, zcldeff, zev, zes, zpatm, zrhova ! - - |
---|
480 | REAL(wp) :: zcshi, zclei, zrhovaclei, zrhovacshi ! - - |
---|
481 | REAL(wp) :: ztice3, zticemb, zticemb2, zdqlw, zdqsb ! - - |
---|
482 | !! |
---|
483 | REAL(wp), DIMENSION(jpi,jpj) :: ztatm ! Tair in Kelvin |
---|
484 | REAL(wp), DIMENSION(jpi,jpj) :: zqatm ! specific humidity |
---|
485 | REAL(wp), DIMENSION(jpi,jpj) :: zevsqr ! vapour pressure square-root |
---|
486 | REAL(wp), DIMENSION(jpi,jpj) :: zrhoa ! air density |
---|
487 | REAL(wp), DIMENSION(jpi,jpj,pdim) :: z_qlw, z_qsb |
---|
488 | !!--------------------------------------------------------------------- |
---|
489 | |
---|
490 | ijpl = pdim ! number of ice categories |
---|
491 | zpatm = 101000. ! atmospheric pressure (assumed constant here) |
---|
492 | |
---|
493 | !------------------------------------! |
---|
494 | ! momentum fluxes (utau, vtau ) ! |
---|
495 | !------------------------------------! |
---|
496 | |
---|
497 | SELECT CASE( cd_grid ) |
---|
498 | CASE( 'C' ) ! C-grid ice dynamics |
---|
499 | ! Change from wind speed to wind stress over OCEAN (cao is used) |
---|
500 | zcoef = cai / cao |
---|
501 | !CDIR COLLAPSE |
---|
502 | DO jj = 1 , jpj |
---|
503 | DO ji = 1, jpi |
---|
504 | p_taui(ji,jj) = zcoef * utau(ji,jj) |
---|
505 | p_tauj(ji,jj) = zcoef * vtau(ji,jj) |
---|
506 | END DO |
---|
507 | END DO |
---|
508 | CASE( 'B' ) ! B-grid ice dynamics |
---|
509 | ! stress from ocean U- and V-points to ice U,V point |
---|
510 | !CDIR COLLAPSE |
---|
511 | DO jj = 2, jpj |
---|
512 | DO ji = 2, jpi ! B grid : no vector opt. |
---|
513 | p_taui(ji,jj) = 0.5 * ( utau(ji-1,jj ) + utau(ji-1,jj-1) ) |
---|
514 | p_tauj(ji,jj) = 0.5 * ( vtau(ji ,jj-1) + vtau(ji-1,jj-1) ) |
---|
515 | END DO |
---|
516 | END DO |
---|
517 | CALL lbc_lnk( p_taui(:,:), 'I', -1. ) ! I-point (i.e. ice U-V point) |
---|
518 | CALL lbc_lnk( p_tauj(:,:), 'I', -1. ) ! I-point (i.e. ice U-V point) |
---|
519 | END SELECT |
---|
520 | |
---|
521 | |
---|
522 | ! Determine cloud optical depths as a function of latitude (Chou et al., 1981). |
---|
523 | ! and the correction factor for taking into account the effect of clouds |
---|
524 | !------------------------------------------------------ |
---|
525 | !CDIR NOVERRCHK |
---|
526 | !CDIR COLLAPSE |
---|
527 | DO jj = 1, jpj |
---|
528 | !CDIR NOVERRCHK |
---|
529 | DO ji = 1, jpi |
---|
530 | ztatm (ji,jj) = sf(jp_tair)%fnow(ji,jj,1) ! air temperature in Kelvins |
---|
531 | |
---|
532 | zrhoa(ji,jj) = zpatm / ( 287.04 * ztatm(ji,jj) ) ! air density (equation of state for dry air) |
---|
533 | |
---|
534 | ztamr = ztatm(ji,jj) - rtt ! Saturation water vapour |
---|
535 | zmt1 = SIGN( 17.269, ztamr ) |
---|
536 | zmt2 = SIGN( 21.875, ztamr ) |
---|
537 | zmt3 = SIGN( 28.200, -ztamr ) |
---|
538 | zes = 611.0 * EXP( ABS( ztamr ) * MIN ( zmt1, zmt2 ) & |
---|
539 | & / ( ztatm(ji,jj) - 35.86 + MAX( 0.e0, zmt3 ) ) ) |
---|
540 | |
---|
541 | zev = sf(jp_humi)%fnow(ji,jj,1) * zes ! vapour pressure |
---|
542 | zevsqr(ji,jj) = SQRT( zev * 0.01 ) ! square-root of vapour pressure |
---|
543 | zqatm(ji,jj) = 0.622 * zev / ( zpatm - 0.378 * zev ) ! specific humidity |
---|
544 | |
---|
545 | !---------------------------------------------------- |
---|
546 | ! Computation of snow precipitation (Ledley, 1985) | |
---|
547 | !---------------------------------------------------- |
---|
548 | zmt1 = 253.0 - ztatm(ji,jj) ; zind1 = MAX( 0.e0, SIGN( 1.e0, zmt1 ) ) |
---|
549 | zmt2 = ( 272.0 - ztatm(ji,jj) ) / 38.0 ; zind2 = MAX( 0.e0, SIGN( 1.e0, zmt2 ) ) |
---|
550 | zmt3 = ( 281.0 - ztatm(ji,jj) ) / 18.0 ; zind3 = MAX( 0.e0, SIGN( 1.e0, zmt3 ) ) |
---|
551 | p_spr(ji,jj) = sf(jp_prec)%fnow(ji,jj,1) / rday & ! rday = converte mm/day to kg/m2/s |
---|
552 | & * ( zind1 & ! solid (snow) precipitation [kg/m2/s] |
---|
553 | & + ( 1.0 - zind1 ) * ( zind2 * ( 0.5 + zmt2 ) & |
---|
554 | & + ( 1.0 - zind2 ) * zind3 * zmt3 ) ) |
---|
555 | |
---|
556 | !----------------------------------------------------! |
---|
557 | ! fraction of net penetrative shortwave radiation ! |
---|
558 | !----------------------------------------------------! |
---|
559 | ! fraction of qsr_ice which is NOT absorbed in the thin surface layer |
---|
560 | ! and thus which penetrates inside the ice cover ( Maykut and Untersteiner, 1971 ; Elbert anbd Curry, 1993 ) |
---|
561 | p_fr1(ji,jj) = 0.18 * ( 1.e0 - sf(jp_ccov)%fnow(ji,jj,1) ) + 0.35 * sf(jp_ccov)%fnow(ji,jj,1) |
---|
562 | p_fr2(ji,jj) = 0.82 * ( 1.e0 - sf(jp_ccov)%fnow(ji,jj,1) ) + 0.65 * sf(jp_ccov)%fnow(ji,jj,1) |
---|
563 | END DO |
---|
564 | END DO |
---|
565 | CALL iom_put( 'snowpre', p_spr ) ! Snow precipitation |
---|
566 | |
---|
567 | !-----------------------------------------------------------! |
---|
568 | ! snow/ice Shortwave radiation (abedo already computed) ! |
---|
569 | !-----------------------------------------------------------! |
---|
570 | CALL blk_clio_qsr_ice( palb_cs, palb_os, p_qsr ) |
---|
571 | |
---|
572 | ! ! ========================== ! |
---|
573 | DO jl = 1, ijpl ! Loop over ice categories ! |
---|
574 | ! ! ========================== ! |
---|
575 | !CDIR NOVERRCHK |
---|
576 | !CDIR COLLAPSE |
---|
577 | DO jj = 1 , jpj |
---|
578 | !CDIR NOVERRCHK |
---|
579 | DO ji = 1, jpi |
---|
580 | !-------------------------------------------! |
---|
581 | ! long-wave radiation over ice categories ! ( Berliand 1952 ; all latitudes ) |
---|
582 | !-------------------------------------------! |
---|
583 | ztatm3 = ztatm(ji,jj) * ztatm(ji,jj) * ztatm(ji,jj) |
---|
584 | zcldeff = 1.0 - sbudyko(ji,jj) * sf(jp_ccov)%fnow(ji,jj,1) * sf(jp_ccov)%fnow(ji,jj,1) |
---|
585 | ztaevbk = ztatm3 * ztatm(ji,jj) * zcldeff * ( 0.39 - 0.05 * zevsqr(ji,jj) ) |
---|
586 | ! |
---|
587 | z_qlw(ji,jj,jl) = - emic * stefan * ( ztaevbk + 4. * ztatm3 * ( pst(ji,jj,jl) - ztatm(ji,jj) ) ) |
---|
588 | |
---|
589 | !---------------------------------------- |
---|
590 | ! Turbulent heat fluxes over snow/ice ( Latent and sensible ) |
---|
591 | !---------------------------------------- |
---|
592 | |
---|
593 | ! vapour pressure at saturation of ice (tmask to avoid overflow in the exponential) |
---|
594 | zesi = 611.0 * EXP( 21.8745587 * tmask(ji,jj,1) * ( pst(ji,jj,jl) - rtt )/ ( pst(ji,jj,jl) - 7.66 ) ) |
---|
595 | ! humidity close to the ice surface (at saturation) |
---|
596 | zqsati = ( 0.622 * zesi ) / ( zpatm - 0.378 * zesi ) |
---|
597 | |
---|
598 | ! computation of intermediate values |
---|
599 | zticemb = pst(ji,jj,jl) - 7.66 |
---|
600 | zticemb2 = zticemb * zticemb |
---|
601 | ztice3 = pst(ji,jj,jl) * pst(ji,jj,jl) * pst(ji,jj,jl) |
---|
602 | zdesidt = zesi * ( 9.5 * LOG( 10.0 ) * ( rtt - 7.66 ) / zticemb2 ) |
---|
603 | |
---|
604 | ! Transfer cofficients assumed to be constant (Parkinson 1979 ; Maykut 1982) |
---|
605 | zcshi = 1.75e-03 |
---|
606 | zclei = zcshi |
---|
607 | |
---|
608 | ! sensible and latent fluxes over ice |
---|
609 | zrhova = zrhoa(ji,jj) * sf(jp_wndm)%fnow(ji,jj,1) ! computation of intermediate values |
---|
610 | zrhovaclei = zrhova * zcshi * 2.834e+06 |
---|
611 | zrhovacshi = zrhova * zclei * 1004.0 |
---|
612 | |
---|
613 | ! sensible heat flux |
---|
614 | z_qsb(ji,jj,jl) = zrhovacshi * ( pst(ji,jj,jl) - ztatm(ji,jj) ) |
---|
615 | |
---|
616 | ! latent heat flux |
---|
617 | p_qla(ji,jj,jl) = MAX( 0.e0, zrhovaclei * ( zqsati - zqatm(ji,jj) ) ) |
---|
618 | |
---|
619 | ! sensitivity of non solar fluxes (dQ/dT) (long-wave, sensible and latent fluxes) |
---|
620 | zdqlw = 4.0 * emic * stefan * ztice3 |
---|
621 | zdqsb = zrhovacshi |
---|
622 | zdqla = zrhovaclei * ( zdesidt * ( zqsati * zqsati / ( zesi * zesi ) ) * ( zpatm / 0.622 ) ) |
---|
623 | ! |
---|
624 | p_dqla(ji,jj,jl) = zdqla ! latent flux sensitivity |
---|
625 | p_dqns(ji,jj,jl) = -( zdqlw + zdqsb + zdqla ) ! total non solar sensitivity |
---|
626 | END DO |
---|
627 | ! |
---|
628 | END DO |
---|
629 | ! |
---|
630 | END DO |
---|
631 | ! |
---|
632 | ! ----------------------------------------------------------------------------- ! |
---|
633 | ! Total FLUXES ! |
---|
634 | ! ----------------------------------------------------------------------------- ! |
---|
635 | ! |
---|
636 | !CDIR COLLAPSE |
---|
637 | p_qns(:,:,:) = z_qlw (:,:,:) - z_qsb (:,:,:) - p_qla (:,:,:) ! Downward Non Solar flux |
---|
638 | !CDIR COLLAPSE |
---|
639 | p_tpr(:,:) = sf(jp_prec)%fnow(:,:,1) / rday ! total precipitation [kg/m2/s] |
---|
640 | ! |
---|
641 | !!gm : not necessary as all input data are lbc_lnk... |
---|
642 | CALL lbc_lnk( p_fr1 (:,:) , 'T', 1. ) |
---|
643 | CALL lbc_lnk( p_fr2 (:,:) , 'T', 1. ) |
---|
644 | DO jl = 1, ijpl |
---|
645 | CALL lbc_lnk( p_qns (:,:,jl) , 'T', 1. ) |
---|
646 | CALL lbc_lnk( p_dqns(:,:,jl) , 'T', 1. ) |
---|
647 | CALL lbc_lnk( p_qla (:,:,jl) , 'T', 1. ) |
---|
648 | CALL lbc_lnk( p_dqla(:,:,jl) , 'T', 1. ) |
---|
649 | END DO |
---|
650 | |
---|
651 | !!gm : mask is not required on forcing |
---|
652 | DO jl = 1, ijpl |
---|
653 | p_qns (:,:,jl) = p_qns (:,:,jl) * tmask(:,:,1) |
---|
654 | p_qla (:,:,jl) = p_qla (:,:,jl) * tmask(:,:,1) |
---|
655 | p_dqns(:,:,jl) = p_dqns(:,:,jl) * tmask(:,:,1) |
---|
656 | p_dqla(:,:,jl) = p_dqla(:,:,jl) * tmask(:,:,1) |
---|
657 | END DO |
---|
658 | |
---|
659 | IF(ln_ctl) THEN |
---|
660 | CALL prt_ctl(tab3d_1=z_qsb , clinfo1=' blk_ice_clio: z_qsb : ', tab3d_2=z_qlw , clinfo2=' z_qlw : ', kdim=ijpl) |
---|
661 | CALL prt_ctl(tab3d_1=p_qla , clinfo1=' blk_ice_clio: z_qla : ', tab3d_2=p_qsr , clinfo2=' p_qsr : ', kdim=ijpl) |
---|
662 | CALL prt_ctl(tab3d_1=p_dqns , clinfo1=' blk_ice_clio: p_dqns : ', tab3d_2=p_qns , clinfo2=' p_qns : ', kdim=ijpl) |
---|
663 | CALL prt_ctl(tab3d_1=p_dqla , clinfo1=' blk_ice_clio: p_dqla : ', tab3d_2=pst , clinfo2=' pst : ', kdim=ijpl) |
---|
664 | CALL prt_ctl(tab2d_1=p_tpr , clinfo1=' blk_ice_clio: p_tpr : ', tab2d_2=p_spr , clinfo2=' p_spr : ') |
---|
665 | CALL prt_ctl(tab2d_1=p_taui , clinfo1=' blk_ice_clio: p_taui : ', tab2d_2=p_tauj , clinfo2=' p_tauj : ') |
---|
666 | ENDIF |
---|
667 | |
---|
668 | |
---|
669 | END SUBROUTINE blk_ice_clio |
---|
670 | |
---|
671 | |
---|
672 | SUBROUTINE blk_clio_qsr_oce( pqsr_oce ) |
---|
673 | !!--------------------------------------------------------------------------- |
---|
674 | !! *** ROUTINE blk_clio_qsr_oce *** |
---|
675 | !! |
---|
676 | !! ** Purpose : Computation of the shortwave radiation at the ocean and the |
---|
677 | !! snow/ice surfaces. |
---|
678 | !! |
---|
679 | !! ** Method : - computed qsr from the cloud cover for both ice and ocean |
---|
680 | !! - also initialise sbudyko and stauc once for all |
---|
681 | !!---------------------------------------------------------------------- |
---|
682 | REAL(wp), INTENT( out), DIMENSION(jpi,jpj) :: pqsr_oce ! shortwave radiation over the ocean |
---|
683 | !! |
---|
684 | INTEGER, PARAMETER :: jp24 = 24 ! sampling of the daylight period (sunrise to sunset) into 24 equal parts |
---|
685 | !! |
---|
686 | INTEGER :: ji, jj, jt ! dummy loop indices |
---|
687 | INTEGER :: indaet ! = -1, 0, 1 for odd, normal and leap years resp. |
---|
688 | INTEGER :: iday ! integer part of day |
---|
689 | INTEGER :: indxb, indxc ! index for cloud depth coefficient |
---|
690 | |
---|
691 | REAL(wp) :: zalat , zclat, zcmue, zcmue2 ! local scalars |
---|
692 | REAL(wp) :: zmt1, zmt2, zmt3 ! |
---|
693 | REAL(wp) :: zdecl, zsdecl , zcdecl ! |
---|
694 | REAL(wp) :: za_oce, ztamr ! |
---|
695 | |
---|
696 | REAL(wp) :: zdl, zlha ! local scalars |
---|
697 | REAL(wp) :: zlmunoon, zcldcor, zdaycor ! |
---|
698 | REAL(wp) :: zxday, zdist, zcoef, zcoef1 ! |
---|
699 | REAL(wp) :: zes |
---|
700 | !! |
---|
701 | REAL(wp), DIMENSION(jpi,jpj) :: zev ! vapour pressure |
---|
702 | REAL(wp), DIMENSION(jpi,jpj) :: zdlha, zlsrise, zlsset ! 2D workspace |
---|
703 | |
---|
704 | REAL(wp), DIMENSION(jpi,jpj) :: zps, zpc ! sine (cosine) of latitude per sine (cosine) of solar declination |
---|
705 | !!--------------------------------------------------------------------- |
---|
706 | |
---|
707 | |
---|
708 | IF( lbulk_init ) THEN ! Initilization at first time step only |
---|
709 | rdtbs2 = nn_fsbc * rdt * 0.5 |
---|
710 | ! cloud optical depths as a function of latitude (Chou et al., 1981). |
---|
711 | ! and the correction factor for taking into account the effect of clouds |
---|
712 | DO jj = 1, jpj |
---|
713 | DO ji = 1 , jpi |
---|
714 | zalat = ( 90.e0 - ABS( gphit(ji,jj) ) ) / 5.e0 |
---|
715 | zclat = ( 95.e0 - gphit(ji,jj) ) / 10.e0 |
---|
716 | indxb = 1 + INT( zalat ) |
---|
717 | indxc = 1 + INT( zclat ) |
---|
718 | zdl = zclat - INT( zclat ) |
---|
719 | ! correction factor to account for the effect of clouds |
---|
720 | sbudyko(ji,jj) = budyko(indxb) |
---|
721 | stauc (ji,jj) = ( 1.e0 - zdl ) * tauco( indxc ) + zdl * tauco( indxc + 1 ) |
---|
722 | END DO |
---|
723 | END DO |
---|
724 | lbulk_init = .FALSE. |
---|
725 | ENDIF |
---|
726 | |
---|
727 | |
---|
728 | ! Saturated water vapour and vapour pressure |
---|
729 | ! ------------------------------------------ |
---|
730 | !CDIR NOVERRCHK |
---|
731 | !CDIR COLLAPSE |
---|
732 | DO jj = 1, jpj |
---|
733 | !CDIR NOVERRCHK |
---|
734 | DO ji = 1, jpi |
---|
735 | ztamr = sf(jp_tair)%fnow(ji,jj,1) - rtt |
---|
736 | zmt1 = SIGN( 17.269, ztamr ) |
---|
737 | zmt2 = SIGN( 21.875, ztamr ) |
---|
738 | zmt3 = SIGN( 28.200, -ztamr ) |
---|
739 | zes = 611.0 * EXP( ABS( ztamr ) * MIN ( zmt1, zmt2 ) & ! Saturation water vapour |
---|
740 | & / ( sf(jp_tair)%fnow(ji,jj,1) - 35.86 + MAX( 0.e0, zmt3 ) ) ) |
---|
741 | zev(ji,jj) = sf(jp_humi)%fnow(ji,jj,1) * zes * 1.0e-05 ! vapour pressure |
---|
742 | END DO |
---|
743 | END DO |
---|
744 | |
---|
745 | !-----------------------------------! |
---|
746 | ! Computation of solar irradiance ! |
---|
747 | !-----------------------------------! |
---|
748 | !!gm : hard coded leap year ??? |
---|
749 | indaet = 1 ! = -1, 0, 1 for odd, normal and leap years resp. |
---|
750 | zxday = nday_year + rdtbs2 / rday ! day of the year at which the fluxes are calculated |
---|
751 | iday = INT( zxday ) ! (centred at the middle of the ice time step) |
---|
752 | CALL flx_blk_declin( indaet, iday, zdecl ) ! solar declination of the current day |
---|
753 | zsdecl = SIN( zdecl * rad ) ! its sine |
---|
754 | zcdecl = COS( zdecl * rad ) ! its cosine |
---|
755 | |
---|
756 | |
---|
757 | ! correction factor added for computation of shortwave flux to take into account the variation of |
---|
758 | ! the distance between the sun and the earth during the year (Oberhuber 1988) |
---|
759 | zdist = zxday * 2. * rpi / REAL(nyear_len(1), wp) |
---|
760 | zdaycor = 1.0 + 0.0013 * SIN( zdist ) + 0.0342 * COS( zdist ) |
---|
761 | |
---|
762 | !CDIR NOVERRCHK |
---|
763 | DO jj = 1, jpj |
---|
764 | !CDIR NOVERRCHK |
---|
765 | DO ji = 1, jpi |
---|
766 | ! product of sine (cosine) of latitude and sine (cosine) of solar declination |
---|
767 | zps(ji,jj) = SIN( gphit(ji,jj) * rad ) * zsdecl |
---|
768 | zpc(ji,jj) = COS( gphit(ji,jj) * rad ) * zcdecl |
---|
769 | ! computation of the both local time of sunrise and sunset |
---|
770 | zlsrise(ji,jj) = ACOS( - SIGN( 1.e0, zps(ji,jj) ) & |
---|
771 | & * MIN( 1.e0, SIGN( 1.e0, zps(ji,jj) ) * ( zps(ji,jj) / zpc(ji,jj) ) ) ) |
---|
772 | zlsset (ji,jj) = - zlsrise(ji,jj) |
---|
773 | ! dividing the solar day into jp24 segments of length zdlha |
---|
774 | zdlha (ji,jj) = ( zlsrise(ji,jj) - zlsset(ji,jj) ) / REAL( jp24, wp ) |
---|
775 | END DO |
---|
776 | END DO |
---|
777 | |
---|
778 | |
---|
779 | !---------------------------------------------! |
---|
780 | ! shortwave radiation absorbed by the ocean ! |
---|
781 | !---------------------------------------------! |
---|
782 | pqsr_oce(:,:) = 0.e0 ! set ocean qsr to zero |
---|
783 | |
---|
784 | ! compute and sum ocean qsr over the daylight (i.e. between sunrise and sunset) |
---|
785 | !CDIR NOVERRCHK |
---|
786 | DO jt = 1, jp24 |
---|
787 | zcoef = FLOAT( jt ) - 0.5 |
---|
788 | !CDIR NOVERRCHK |
---|
789 | !CDIR COLLAPSE |
---|
790 | DO jj = 1, jpj |
---|
791 | !CDIR NOVERRCHK |
---|
792 | DO ji = 1, jpi |
---|
793 | zlha = COS( zlsrise(ji,jj) - zcoef * zdlha(ji,jj) ) ! local hour angle |
---|
794 | zcmue = MAX( 0.e0 , zps(ji,jj) + zpc(ji,jj) * zlha ) ! cos of local solar altitude |
---|
795 | zcmue2 = 1368.0 * zcmue * zcmue |
---|
796 | |
---|
797 | ! ocean albedo depending on the cloud cover (Payne, 1972) |
---|
798 | za_oce = ( 1.0 - sf(jp_ccov)%fnow(ji,jj,1) ) * 0.05 / ( 1.1 * zcmue**1.4 + 0.15 ) & ! clear sky |
---|
799 | & + sf(jp_ccov)%fnow(ji,jj,1) * 0.06 ! overcast |
---|
800 | |
---|
801 | ! solar heat flux absorbed by the ocean (Zillman, 1972) |
---|
802 | pqsr_oce(ji,jj) = pqsr_oce(ji,jj) & |
---|
803 | & + ( 1.0 - za_oce ) * zdlha(ji,jj) * zcmue2 & |
---|
804 | & / ( ( zcmue + 2.7 ) * zev(ji,jj) + 1.085 * zcmue + 0.10 ) |
---|
805 | END DO |
---|
806 | END DO |
---|
807 | END DO |
---|
808 | ! Taking into account the ellipsity of the earth orbit, the clouds AND masked if sea-ice cover > 0% |
---|
809 | zcoef1 = srgamma * zdaycor / ( 2. * rpi ) |
---|
810 | !CDIR COLLAPSE |
---|
811 | DO jj = 1, jpj |
---|
812 | DO ji = 1, jpi |
---|
813 | zlmunoon = ASIN( zps(ji,jj) + zpc(ji,jj) ) / rad ! local noon solar altitude |
---|
814 | zcldcor = MIN( 1.e0, ( 1.e0 - 0.62 * sf(jp_ccov)%fnow(ji,jj,1) & ! cloud correction (Reed 1977) |
---|
815 | & + 0.0019 * zlmunoon ) ) |
---|
816 | pqsr_oce(ji,jj) = zcoef1 * zcldcor * pqsr_oce(ji,jj) * tmask(ji,jj,1) ! and zcoef1: ellipsity |
---|
817 | END DO |
---|
818 | END DO |
---|
819 | |
---|
820 | END SUBROUTINE blk_clio_qsr_oce |
---|
821 | |
---|
822 | |
---|
823 | SUBROUTINE blk_clio_qsr_ice( pa_ice_cs, pa_ice_os, pqsr_ice ) |
---|
824 | !!--------------------------------------------------------------------------- |
---|
825 | !! *** ROUTINE blk_clio_qsr_ice *** |
---|
826 | !! |
---|
827 | !! ** Purpose : Computation of the shortwave radiation at the ocean and the |
---|
828 | !! snow/ice surfaces. |
---|
829 | !! |
---|
830 | !! ** Method : - computed qsr from the cloud cover for both ice and ocean |
---|
831 | !! - also initialise sbudyko and stauc once for all |
---|
832 | !!---------------------------------------------------------------------- |
---|
833 | REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: pa_ice_cs ! albedo of ice under clear sky |
---|
834 | REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: pa_ice_os ! albedo of ice under overcast sky |
---|
835 | REAL(wp), INTENT( out), DIMENSION(:,:,:) :: pqsr_ice ! shortwave radiation over the ice/snow |
---|
836 | !! |
---|
837 | INTEGER, PARAMETER :: jp24 = 24 ! sampling of the daylight period (sunrise to sunset) into 24 equal parts |
---|
838 | !! |
---|
839 | INTEGER :: ji, jj, jl, jt ! dummy loop indices |
---|
840 | INTEGER :: ijpl ! number of ice categories (3rd dim of pqsr_ice) |
---|
841 | INTEGER :: indaet ! = -1, 0, 1 for odd, normal and leap years resp. |
---|
842 | INTEGER :: iday ! integer part of day |
---|
843 | !! |
---|
844 | REAL(wp) :: zcmue, zcmue2, ztamr ! temporary scalars |
---|
845 | REAL(wp) :: zmt1, zmt2, zmt3 ! - - |
---|
846 | REAL(wp) :: zdecl, zsdecl, zcdecl ! - - |
---|
847 | REAL(wp) :: zlha, zdaycor, zes ! - - |
---|
848 | REAL(wp) :: zxday, zdist, zcoef, zcoef1 ! - - |
---|
849 | REAL(wp) :: zqsr_ice_cs, zqsr_ice_os ! - - |
---|
850 | !! |
---|
851 | REAL(wp), DIMENSION(jpi,jpj) :: zev ! vapour pressure |
---|
852 | REAL(wp), DIMENSION(jpi,jpj) :: zdlha, zlsrise, zlsset ! 2D workspace |
---|
853 | REAL(wp), DIMENSION(jpi,jpj) :: zps, zpc ! sine (cosine) of latitude per sine (cosine) of solar declination |
---|
854 | !!--------------------------------------------------------------------- |
---|
855 | |
---|
856 | ijpl = SIZE(pqsr_ice, 3 ) ! number of ice categories |
---|
857 | |
---|
858 | ! Saturated water vapour and vapour pressure |
---|
859 | ! ------------------------------------------ |
---|
860 | !CDIR NOVERRCHK |
---|
861 | !CDIR COLLAPSE |
---|
862 | DO jj = 1, jpj |
---|
863 | !CDIR NOVERRCHK |
---|
864 | DO ji = 1, jpi |
---|
865 | ztamr = sf(jp_tair)%fnow(ji,jj,1) - rtt |
---|
866 | zmt1 = SIGN( 17.269, ztamr ) |
---|
867 | zmt2 = SIGN( 21.875, ztamr ) |
---|
868 | zmt3 = SIGN( 28.200, -ztamr ) |
---|
869 | zes = 611.0 * EXP( ABS( ztamr ) * MIN ( zmt1, zmt2 ) & ! Saturation water vapour |
---|
870 | & / ( sf(jp_tair)%fnow(ji,jj,1) - 35.86 + MAX( 0.e0, zmt3 ) ) ) |
---|
871 | zev(ji,jj) = sf(jp_humi)%fnow(ji,jj,1) * zes * 1.0e-05 ! vapour pressure |
---|
872 | END DO |
---|
873 | END DO |
---|
874 | |
---|
875 | !-----------------------------------! |
---|
876 | ! Computation of solar irradiance ! |
---|
877 | !-----------------------------------! |
---|
878 | !!gm : hard coded leap year ??? |
---|
879 | indaet = 1 ! = -1, 0, 1 for odd, normal and leap years resp. |
---|
880 | zxday = nday_year + rdtbs2 / rday ! day of the year at which the fluxes are calculated |
---|
881 | iday = INT( zxday ) ! (centred at the middle of the ice time step) |
---|
882 | CALL flx_blk_declin( indaet, iday, zdecl ) ! solar declination of the current day |
---|
883 | zsdecl = SIN( zdecl * rad ) ! its sine |
---|
884 | zcdecl = COS( zdecl * rad ) ! its cosine |
---|
885 | |
---|
886 | |
---|
887 | ! correction factor added for computation of shortwave flux to take into account the variation of |
---|
888 | ! the distance between the sun and the earth during the year (Oberhuber 1988) |
---|
889 | zdist = zxday * 2. * rpi / REAL(nyear_len(1), wp) |
---|
890 | zdaycor = 1.0 + 0.0013 * SIN( zdist ) + 0.0342 * COS( zdist ) |
---|
891 | |
---|
892 | !CDIR NOVERRCHK |
---|
893 | DO jj = 1, jpj |
---|
894 | !CDIR NOVERRCHK |
---|
895 | DO ji = 1, jpi |
---|
896 | ! product of sine (cosine) of latitude and sine (cosine) of solar declination |
---|
897 | zps(ji,jj) = SIN( gphit(ji,jj) * rad ) * zsdecl |
---|
898 | zpc(ji,jj) = COS( gphit(ji,jj) * rad ) * zcdecl |
---|
899 | ! computation of the both local time of sunrise and sunset |
---|
900 | zlsrise(ji,jj) = ACOS( - SIGN( 1.e0, zps(ji,jj) ) & |
---|
901 | & * MIN( 1.e0, SIGN( 1.e0, zps(ji,jj) ) * ( zps(ji,jj) / zpc(ji,jj) ) ) ) |
---|
902 | zlsset (ji,jj) = - zlsrise(ji,jj) |
---|
903 | ! dividing the solar day into jp24 segments of length zdlha |
---|
904 | zdlha (ji,jj) = ( zlsrise(ji,jj) - zlsset(ji,jj) ) / REAL( jp24, wp ) |
---|
905 | END DO |
---|
906 | END DO |
---|
907 | |
---|
908 | |
---|
909 | !---------------------------------------------! |
---|
910 | ! shortwave radiation absorbed by the ice ! |
---|
911 | !---------------------------------------------! |
---|
912 | ! compute and sum ice qsr over the daylight for each ice categories |
---|
913 | pqsr_ice(:,:,:) = 0.e0 |
---|
914 | zcoef1 = zdaycor / ( 2. * rpi ) ! Correction for the ellipsity of the earth orbit |
---|
915 | |
---|
916 | ! !----------------------------! |
---|
917 | DO jl = 1, ijpl ! loop over ice categories ! |
---|
918 | ! !----------------------------! |
---|
919 | !CDIR NOVERRCHK |
---|
920 | DO jt = 1, jp24 |
---|
921 | zcoef = FLOAT( jt ) - 0.5 |
---|
922 | !CDIR NOVERRCHK |
---|
923 | !CDIR COLLAPSE |
---|
924 | DO jj = 1, jpj |
---|
925 | !CDIR NOVERRCHK |
---|
926 | DO ji = 1, jpi |
---|
927 | zlha = COS( zlsrise(ji,jj) - zcoef * zdlha(ji,jj) ) ! local hour angle |
---|
928 | zcmue = MAX( 0.e0 , zps(ji,jj) + zpc(ji,jj) * zlha ) ! cos of local solar altitude |
---|
929 | zcmue2 = 1368.0 * zcmue * zcmue |
---|
930 | |
---|
931 | ! solar heat flux absorbed by the ice/snow system (Shine and Crane 1984 adapted to high albedo) |
---|
932 | zqsr_ice_cs = ( 1.0 - pa_ice_cs(ji,jj,jl) ) * zdlha(ji,jj) * zcmue2 & ! clear sky |
---|
933 | & / ( ( 1.0 + zcmue ) * zev(ji,jj) + 1.2 * zcmue + 0.0455 ) |
---|
934 | zqsr_ice_os = zdlha(ji,jj) * SQRT( zcmue ) & ! overcast sky |
---|
935 | & * ( 53.5 + 1274.5 * zcmue ) * ( 1.0 - 0.996 * pa_ice_os(ji,jj,jl) ) & |
---|
936 | & / ( 1.0 + 0.139 * stauc(ji,jj) * ( 1.0 - 0.9435 * pa_ice_os(ji,jj,jl) ) ) |
---|
937 | |
---|
938 | pqsr_ice(ji,jj,jl) = pqsr_ice(ji,jj,jl) + ( ( 1.0 - sf(jp_ccov)%fnow(ji,jj,1) ) * zqsr_ice_cs & |
---|
939 | & + sf(jp_ccov)%fnow(ji,jj,1) * zqsr_ice_os ) |
---|
940 | END DO |
---|
941 | END DO |
---|
942 | END DO |
---|
943 | ! |
---|
944 | ! Correction : Taking into account the ellipsity of the earth orbit |
---|
945 | pqsr_ice(:,:,jl) = pqsr_ice(:,:,jl) * zcoef1 * tmask(:,:,1) |
---|
946 | ! |
---|
947 | ! !--------------------------------! |
---|
948 | END DO ! end loop over ice categories ! |
---|
949 | ! !--------------------------------! |
---|
950 | |
---|
951 | |
---|
952 | !!gm : this should be suppress as input data have been passed through lbc_lnk |
---|
953 | DO jl = 1, ijpl |
---|
954 | CALL lbc_lnk( pqsr_ice(:,:,jl) , 'T', 1. ) |
---|
955 | END DO |
---|
956 | ! |
---|
957 | END SUBROUTINE blk_clio_qsr_ice |
---|
958 | |
---|
959 | |
---|
960 | SUBROUTINE flx_blk_declin( ky, kday, pdecl ) |
---|
961 | !!--------------------------------------------------------------------------- |
---|
962 | !! *** ROUTINE flx_blk_declin *** |
---|
963 | !! |
---|
964 | !! ** Purpose : Computation of the solar declination for the day |
---|
965 | !! |
---|
966 | !! ** Method : ??? |
---|
967 | !!--------------------------------------------------------------------- |
---|
968 | INTEGER , INTENT(in ) :: ky ! = -1, 0, 1 for odd, normal and leap years resp. |
---|
969 | INTEGER , INTENT(in ) :: kday ! day of the year ( kday = 1 on january 1) |
---|
970 | REAL(wp), INTENT( out) :: pdecl ! solar declination |
---|
971 | !! |
---|
972 | REAL(wp) :: a0 = 0.39507671 ! coefficients for solar declinaison computation |
---|
973 | REAL(wp) :: a1 = 22.85684301 ! " "" " |
---|
974 | REAL(wp) :: a2 = -0.38637317 ! " "" " |
---|
975 | REAL(wp) :: a3 = 0.15096535 ! " "" " |
---|
976 | REAL(wp) :: a4 = -0.00961411 ! " "" " |
---|
977 | REAL(wp) :: b1 = -4.29692073 ! " "" " |
---|
978 | REAL(wp) :: b2 = 0.05702074 ! " "" " |
---|
979 | REAL(wp) :: b3 = -0.09028607 ! " "" " |
---|
980 | REAL(wp) :: b4 = 0.00592797 |
---|
981 | !! |
---|
982 | REAL(wp) :: zday ! corresponding day of type year (cf. ky) |
---|
983 | REAL(wp) :: zp ! temporary scalars |
---|
984 | !!--------------------------------------------------------------------- |
---|
985 | |
---|
986 | IF ( ky == 1 ) THEN ; zday = REAL( kday, wp ) - 0.5 |
---|
987 | ELSEIF( ky == 3 ) THEN ; zday = REAL( kday, wp ) - 1. |
---|
988 | ELSE ; zday = REAL( kday, wp ) |
---|
989 | ENDIF |
---|
990 | |
---|
991 | zp = rpi * ( 2.0 * zday - 367.0 ) / REAL(nyear_len(1), wp) |
---|
992 | |
---|
993 | pdecl = a0 & |
---|
994 | & + a1 * COS( zp ) + a2 * COS( 2. * zp ) + a3 * COS( 3. * zp ) + a4 * COS( 4. * zp ) & |
---|
995 | & + b1 * SIN( zp ) + b2 * SIN( 2. * zp ) + b3 * SIN( 3. * zp ) + b4 * SIN( 4. * zp ) |
---|
996 | ! |
---|
997 | END SUBROUTINE flx_blk_declin |
---|
998 | |
---|
999 | !!====================================================================== |
---|
1000 | END MODULE sbcblk_clio |
---|