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

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

Renamed wrk_use => wrk_in_use and wrk_release => wrk_not_released

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