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 @ 1037

Last change on this file since 1037 was 1037, checked in by ctlod, 16 years ago

trunk: replace freeze(:,:) variable with fr_i(:,:), use the tfreez function defined in eosbn2.F90 and remove the useless ocfzpt.F90 module, see ticket: #177

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