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

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

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

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

wind stress module directly at T-point, see ticket:577

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