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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_clio.F90 @ 2409

Last change on this file since 2409 was 2409, checked in by cetlod, 14 years ago

Finalize the new organisation of 1D vertical configuration, see ticket #760

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