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/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_clio.F90 @ 2590

Last change on this file since 2590 was 2590, checked in by trackstand2, 13 years ago

Merge branch 'dynamic_memory' into master-svn-dyn

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