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

Last change on this file since 959 was 921, checked in by rblod, 16 years ago

Correct indentation and print for debug in LIM3, see ticket #134, step I

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