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

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

source: branches/dev_001_SBC/NEMO/OPA_SRC/SBC/sbcblk_clio.F90 @ 879

Last change on this file since 879 was 879, checked in by ctlod, 16 years ago

dev_001_SBC: clean & add control prints, see ticket:#104

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