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

Last change on this file since 1133 was 1133, checked in by smasson, 16 years ago

new sbc namelist format, see ticket:1

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