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

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

source: trunk/NEMO/OPA_SRC/SBC/sbcblk_clio.F90 @ 1275

Last change on this file since 1275 was 1275, checked in by rblod, 15 years ago

First introduction off interpolation off the fly, see ticket #279

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