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

Last change on this file since 1482 was 1482, checked in by smasson, 15 years ago

distribution of iom_put + cleaning of LIM2 outputs, see ticket:437

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