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

Last change on this file since 1207 was 1207, checked in by rblod, 16 years ago

Suppress a vectorization optimisation leading to inexact results with vopt

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