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

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

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

Last change on this file since 2370 was 2370, checked in by gm, 13 years ago

v3.3beta: ice-ocean stress at kt with VP & EVP (LIM-2 and -3)

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