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/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_clio.F90 @ 2528

Last change on this file since 2528 was 2528, checked in by rblod, 13 years ago

Update NEMOGCM from branch nemo_v3_3_beta

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