New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
sbcblk_clio.F90 in trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/sbcblk_clio.F90 @ 1730

Last change on this file since 1730 was 1730, checked in by smasson, 14 years ago

use integer in calendar, see ticket:601

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