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

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

dev_001_SBC: modification to allow same results as the reference flxblk.F90, see ticket:#96

  • Property svn:executable set to *
File size: 52.2 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) ::   zcoef, 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
286      ! Change from wind speed to wind stress over OCEAN (cao is used)
287      ! note: 1.3 = air density)
288!!gm  the module is wrong as U and V points are not the same
289!!gm  the surface currents are not taken into account...
290!CDIR COLLAPSE
291      DO jj = 1 , jpj
292         DO ji = 1, jpi
293            utau(ji,jj) = sf(jp_wndi)%fnow(ji,jj)
294            vtau(ji,jj) = sf(jp_wndj)%fnow(ji,jj)
295         END DO
296      END DO
297!!gm  better coding:  use the wind module and averaging to U and V points
298!     zcoef = 1.3 * cao * 0.5
299!     DO jj = 1 , jpjm1
300!        DO ji = 1, fs_jpim1
301!           utau(ji,jj) = zcoef * ( sf(jp_wndm)%fnow(ji+1,jj) + sf(jp_wndm)%fnow(ji,jj) ) * sf(jp_wndi)%fnow(ji,jj)
302!           vtau(ji,jj) = zcoef * ( sf(jp_wndm)%fnow(ji,jj+1) + sf(jp_wndm)%fnow(ji,jj) ) * sf(jp_wndj)%fnow(ji,jj)
303!          END DO
304!       END DO
305!      CALL lbc_lnk( utau(:,:), 'U', -1. )
306!      CALL lbc_lnk( vtau(:,:), 'V', -1. )
307!!gm end coding
308
309     
310      !------------------------------------------------!
311      !   Shortwave radiation for ocean and snow/ice   !
312      !------------------------------------------------!
313     
314      CALL blk_clio_qsr_oce( qsr )
315
316
317      !------------------------!
318      !   Other ocean fluxes   !
319      !------------------------!
320!CDIR NOVERRCHK
321!CDIR COLLAPSE
322      DO jj = 1, jpj
323!CDIR NOVERRCHK
324         DO ji = 1, jpi
325            !
326            zsst  = pst(ji,jj)              + rt0           ! converte Celcius to Kelvin the SST and Tair
327            ztatm = sf(jp_tair)%fnow(ji,jj) + rt0           ! and set minimum value far above 0 K (=rt0 over land)
328            zcco1 = 1.0 - sf(jp_ccov)%fnow(ji,jj)           ! fraction of clear sky ( 1 - cloud cover)
329            zrhoa = zpatm / ( 287.04 * ztatm )              ! air density (equation of state for dry air)
330            ztamr = ztatm - rtt                             ! Saturation water vapour
331            zmt1  = SIGN( 17.269,  ztamr )                  !           ||
332            zmt2  = SIGN( 21.875,  ztamr )                  !          \  /
333            zmt3  = SIGN( 28.200, -ztamr )                  !           \/
334            zes   = 611.0 * EXP(  ABS( ztamr ) * MIN ( zmt1, zmt2 ) / ( ztatm - 35.86  + MAX( 0.e0, zmt3 ) )  )
335            zev    = sf(jp_humi)%fnow(ji,jj) * zes          ! vapour pressure 
336            zevsqr = SQRT( zev * 0.01 )                     ! square-root of vapour pressure
337            zqatm = 0.622 * zev / ( zpatm - 0.378 * zev )   ! specific humidity
338
339            !--------------------------------------!
340            !  long-wave radiation over the ocean  !  ( Berliand 1952 ; all latitudes )
341            !--------------------------------------!
342            ztatm3  = ztatm * ztatm * ztatm
343            zcldeff = 1.0 - sbudyko(ji,jj) * sf(jp_ccov)%fnow(ji,jj) * sf(jp_ccov)%fnow(ji,jj)   
344            ztaevbk = ztatm * ztatm3 * zcldeff * ( 0.39 - 0.05 * zevsqr ) 
345            !
346            zqlw(ji,jj) = - emic * stefan * ( ztaevbk + 4. * ztatm3 * ( zsst - ztatm ) ) 
347
348            !--------------------------------------------------
349            !  Latent and sensible heat fluxes over the ocean
350            !--------------------------------------------------
351            !                                                          ! vapour pressure at saturation of ocean
352            zeso =  611.0 * EXP ( 17.2693884 * ( zsst - rtt ) * tmask(ji,jj,1) / ( zsst - 35.86 ) )
353
354            zqsato = ( 0.622 * zeso ) / ( zpatm - 0.378 * zeso )       ! humidity close to the ocean surface (at saturation)
355
356            ! Drag coefficients from Large and Pond (1981,1982)
357            !                                                          ! Stability parameters
358            zdteta  = zsst - ztatm
359            zdeltaq = zqatm - zqsato
360            ztvmoy  = ztatm * ( 1. + 2.2e-3 * ztatm * zqatm )
361            zdenum  = MAX( sf(jp_wndm)%fnow(ji,jj) * sf(jp_wndm)%fnow(ji,jj) * ztvmoy, zeps )
362            zdtetar = zdteta / zdenum
363            ztvmoyr = ztvmoy * ztvmoy * zdeltaq / zdenum
364            !                                                          ! case of stable atmospheric conditions
365            zobouks = -70.0 * 10. * ( zdtetar + 3.2e-3 * ztvmoyr )
366            zobouks = MAX( 0.e0, zobouks )
367            zpsims = -7.0 * zobouks
368            zpsihs =  zpsims
369            zpsils =  zpsims
370            !                                                          ! case of unstable atmospheric conditions
371            zobouku = MIN(  0.e0, -100.0 * 10.0 * ( zdtetar + 2.2e-3 * ztvmoyr )  )
372            zxins   = ( 1. - 16. * zobouku )**0.25
373            zlxins  = LOG( ( 1. + zxins * zxins ) / 2. )
374            zpsimu  = 2. * LOG( ( 1 + zxins ) * 0.5 )  + zlxins - 2. * ATAN( zxins ) + rpi * 0.5
375            zpsihu  = 2. * zlxins
376            zpsilu  = zpsihu
377            !                                                          ! intermediate values
378            zstab   = MAX( 0.e0, SIGN( 1.e0, zdteta ) )
379            zpsim   = zstab * zpsimu + ( 1.0 - zstab ) * zpsims
380            zpsih   = zstab * zpsihu + ( 1.0 - zstab ) * zpsihs
381            zpsil   = zpsih
382           
383            zvatmg         = MAX( 0.032 * 1.5e-3 * sf(jp_wndm)%fnow(ji,jj) * sf(jp_wndm)%fnow(ji,jj) / grav, zeps )
384            zcmn           = vkarmn / LOG ( 10. / zvatmg )
385            zchn           = 0.0327 * zcmn
386            zcln           = 0.0346 * zcmn
387            zcmcmn         = 1. / ( 1. - zcmn * zpsim / vkarmn )
388            zchcm          = zcmcmn / ( 1. - zchn * zpsih / ( vkarmn * zcmn ) )
389            zclcm          = zchcm
390            !                                                          ! transfert coef. (Large and Pond 1981,1982)
391            zcsho          = zchn * zchcm                               
392            zcleo          = zcln * zclcm 
393
394            zrhova         = zrhoa * sf(jp_wndm)%fnow(ji,jj)
395
396            ! sensible heat flux
397            zqsb(ji,jj) = zrhova * zcsho * 1004.0  * ( zsst - ztatm ) 
398         
399            ! latent heat flux (bounded by zero)
400            zqla(ji,jj) = MAX(  0.e0, zrhova * zcleo * 2.5e+06 * ( zqsato - zqatm )  )
401            !               
402         END DO
403      END DO
404     
405      ! ----------------------------------------------------------------------------- !
406      !     III    Total FLUXES                                                       !
407      ! ----------------------------------------------------------------------------- !
408!CDIR COLLAPSE
409      qns (:,:) = zqlw(:,:) - zqsb(:,:) - zqla(:,:)      ! Downward Non Solar flux
410!CDIR COLLAPSE
411      emp (:,:) = zqla(:,:) / cevap - sf(jp_prec)%fnow(:,:) / rday * tmask(:,:,1)
412!CDIR COLLAPSE
413      emps(:,:) = emp(:,:)
414      !
415   END SUBROUTINE blk_oce_clio
416
417
418   SUBROUTINE blk_ice_clio(  pst   , pui   , pvi   , palb_cs, palb_os ,   &
419      &                      p_taui, p_tauj, p_qns , p_qsr,   &
420      &                      p_qla , p_dqns, p_dqla,          &
421      &                      p_tpr , p_spr ,                  &
422      &                      p_fr1 , p_fr2 , cd_grid  )
423      !!---------------------------------------------------------------------------
424      !!                     ***  ROUTINE blk_ice_clio  ***
425      !!                 
426      !!  ** Purpose :   Computation of the heat fluxes at ocean and snow/ice
427      !!       surface the solar heat at ocean and snow/ice surfaces and the
428      !!       sensitivity of total heat fluxes to the SST variations
429      !!         
430      !!  ** Method  :   The flux of heat at the ice and ocean surfaces are derived
431      !!       from semi-empirical ( or bulk ) formulae which relate the flux to
432      !!       the properties of the surface and of the lower atmosphere. Here, we
433      !!       follow the work of Oberhuber, 1988   
434      !!
435      !!  ** Action  :   call flx_blk_albedo to compute ocean and ice albedo
436      !!          computation of snow precipitation
437      !!          computation of solar flux at the ocean and ice surfaces
438      !!          computation of the long-wave radiation for the ocean and sea/ice
439      !!          computation of turbulent heat fluxes over water and ice
440      !!          computation of evaporation over water
441      !!          computation of total heat fluxes sensitivity over ice (dQ/dT)
442      !!          computation of latent heat flux sensitivity over ice (dQla/dT)
443      !!
444      !!----------------------------------------------------------------------
445      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj,jpl) ::   pst      ! ice surface temperature                   [Kelvin]
446      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj)     ::   pui      ! ice surface velocity (i-component, I-point)  [m/s]
447      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj)     ::   pvi      ! ice surface velocity (j-component, I-point)  [m/s]
448      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj,jpl) ::   palb_cs  ! ice albedo (clear sky) (alb_ice_cs)            [%]
449      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj,jpl) ::   palb_os  ! ice albedo (overcast sky) (alb_ice_cs)         [%]
450      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj)     ::   p_taui   ! surface ice stress at I-point (i-component) [N/m2]
451      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj)     ::   p_tauj   ! surface ice stress at I-point (j-component) [N/m2]
452      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj,jpl) ::   p_qns    ! non solar heat flux over ice (T-point)      [W/m2]
453      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj,jpl) ::   p_qsr    !     solar heat flux over ice (T-point)      [W/m2]
454      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj,jpl) ::   p_qla    ! latent    heat flux over ice (T-point)      [W/m2]
455      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj,jpl) ::   p_dqns   ! non solar heat sensistivity  (T-point)      [W/m2]
456      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj,jpl) ::   p_dqla   ! latent    heat sensistivity  (T-point)      [W/m2]
457      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj)     ::   p_tpr    ! total precipitation          (T-point)       [Kg/m2/s]
458      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj)     ::   p_spr    ! solid precipitation          (T-point)       [Kg/m2/s]
459      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj)     ::   p_fr1    ! 1sr fraction of qsr penetration in ice             [%]
460      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj)     ::   p_fr2    ! 2nd fraction of qsr penetration in ice             [%]
461      CHARACTER(len=1), INTENT(in   )                 ::   cd_grid  ! type of sea-ice grid ("C" or "B" grid)
462      !!
463      INTEGER  ::   ji, jj, jl    ! dummy loop indices
464      !!
465      REAL(wp) ::   zcoef, zmt1, zmt2, zmt3, ztatm3             ! temporary scalars
466      REAL(wp) ::   ztaevbk, zind1, zind2, zind3, ztamr         !    -         -
467      REAL(wp) ::   zesi, zqsati, zdesidt                       !    -         -
468      REAL(wp) ::   zdqla, zcldeff, zev, zes, zpatm, zrhova     !    -         -
469      REAL(wp) ::   zcshi, zclei, zrhovaclei, zrhovacshi        !    -         -
470      REAL(wp) ::   ztice3, zticemb, zticemb2, zdqlw, zdqsb     !    -         -
471      !!
472      REAL(wp), DIMENSION(jpi,jpj) ::   ztatm   ! Tair in Kelvin
473      REAL(wp), DIMENSION(jpi,jpj) ::   zqatm   ! specific humidity
474      REAL(wp), DIMENSION(jpi,jpj) ::   zevsqr  ! vapour pressure square-root
475      REAL(wp), DIMENSION(jpi,jpj) ::   zrhoa   ! air density
476      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z_qlw, z_qsb
477      !!---------------------------------------------------------------------
478
479      zpatm = 101000.                        ! atmospheric pressure  (assumed constant  here)
480
481      !------------------------------------!
482      !   momentum fluxes  (utau, vtau )   !
483      !------------------------------------!
484
485      SELECT CASE( cd_grid )
486      CASE( 'C' )                          ! C-grid ice dynamics
487         ! Change from wind speed to wind stress over OCEAN (cao is used)
488         zcoef = cai / cao 
489!CDIR COLLAPSE
490         DO jj = 1 , jpj
491            DO ji = 1, jpi
492               p_taui(ji,jj) = zcoef * utau(ji,jj)
493               p_tauj(ji,jj) = zcoef * vtau(ji,jj)
494            END DO
495         END DO
496      CASE( 'B' )                          ! B-grid ice dynamics
497         ! stress from ocean U- and V-points to ice U,V point
498         zcoef = cai / cao * 0.5
499!CDIR COLLAPSE
500         DO jj = 2, jpj
501            DO ji = fs_2, jpi   ! vector opt.
502               p_taui(ji,jj) = 0.5 * ( utau(ji-1,jj  ) + utau(ji-1,jj-1) )
503               p_tauj(ji,jj) = 0.5 * ( vtau(ji  ,jj-1) + vtau(ji-1,jj-1) )
504            END DO
505         END DO
506         CALL lbc_lnk( p_taui(:,:), 'I', -1. )   ! I-point (i.e. ice U-V point)
507         CALL lbc_lnk( p_tauj(:,:), 'I', -1. )   ! I-point (i.e. ice U-V point)
508      END SELECT
509
510
511      !  Determine cloud optical depths as a function of latitude (Chou et al., 1981).
512      !  and the correction factor for taking into account  the effect of clouds
513      !------------------------------------------------------
514!CDIR NOVERRCHK
515!CDIR COLLAPSE
516      DO jj = 1, jpj
517!CDIR NOVERRCHK
518         DO ji = 1, jpi
519            ztatm (ji,jj) = sf(jp_tair)%fnow(ji,jj) + rt0            ! air temperature in Kelvins
520     
521            zrhoa(ji,jj) = zpatm / ( 287.04 * ztatm(ji,jj) )         ! air density (equation of state for dry air)
522     
523            ztamr = ztatm(ji,jj) - rtt                               ! Saturation water vapour
524            zmt1  = SIGN( 17.269,  ztamr )
525            zmt2  = SIGN( 21.875,  ztamr )
526            zmt3  = SIGN( 28.200, -ztamr )
527            zes   = 611.0 * EXP(  ABS( ztamr ) * MIN ( zmt1, zmt2 )   &
528               &                / ( ztatm(ji,jj) - 35.86  + MAX( 0.e0, zmt3 ) )  )
529
530            zev = sf(jp_humi)%fnow(ji,jj) * zes                      ! vapour pressure 
531            zevsqr(ji,jj) = SQRT( zev * 0.01 )                       ! square-root of vapour pressure
532            zqatm(ji,jj) = 0.622 * zev / ( zpatm - 0.378 * zev )     ! specific humidity
533
534            !----------------------------------------------------
535            !   Computation of snow precipitation (Ledley, 1985) |
536            !----------------------------------------------------
537            zmt1  =   253.0 - ztatm(ji,jj)            ;   zind1 = MAX( 0.e0, SIGN( 1.e0, zmt1 ) )
538            zmt2  = ( 272.0 - ztatm(ji,jj) ) / 38.0   ;   zind2 = MAX( 0.e0, SIGN( 1.e0, zmt2 ) )
539            zmt3  = ( 281.0 - ztatm(ji,jj) ) / 18.0   ;   zind3 = MAX( 0.e0, SIGN( 1.e0, zmt3 ) )
540            p_spr(ji,jj) = sf(jp_prec)%fnow(ji,jj) / rday   &        ! rday = converte mm/day to kg/m2/s
541               &         * (          zind1      &                   ! solid  (snow) precipitation [kg/m2/s]
542               &            + ( 1.0 - zind1 ) * (          zind2   * ( 0.5 + zmt2 )   &
543               &                                 + ( 1.0 - zind2 ) *  zind3 * zmt3  )   ) 
544
545            !----------------------------------------------------!
546            !  fraction of net penetrative shortwave radiation   !
547            !----------------------------------------------------!
548            ! fraction of qsr_ice which is NOT absorbed in the thin surface layer
549            ! and thus which penetrates inside the ice cover ( Maykut and Untersteiner, 1971 ; Elbert anbd Curry, 1993 )
550            p_fr1(ji,jj) = 0.18  * ( 1.e0 - sf(jp_ccov)%fnow(ji,jj) ) + 0.35 * sf(jp_ccov)%fnow(ji,jj) 
551            p_fr2(ji,jj) = 0.82  * ( 1.e0 - sf(jp_ccov)%fnow(ji,jj) ) + 0.65 * sf(jp_ccov)%fnow(ji,jj)
552         END DO
553      END DO
554     
555      !-----------------------------------------------------------!
556      !  snow/ice Shortwave radiation   (abedo already computed)  !
557      !-----------------------------------------------------------!
558      CALL blk_clio_qsr_ice( palb_cs, palb_os, p_qsr )
559
560      !                                     ! ========================== !
561      DO jl = 1, jpl                        !  Loop over ice categories  !
562         !                                  ! ========================== !
563!CDIR NOVERRCHK
564!CDIR COLLAPSE
565         DO jj = 1 , jpj
566!CDIR NOVERRCHK
567            DO ji = 1, jpi
568               !-------------------------------------------!
569               !  long-wave radiation over ice categories  !  ( Berliand 1952 ; all latitudes )
570               !-------------------------------------------!
571               ztatm3  = ztatm(ji,jj) * ztatm(ji,jj) * ztatm(ji,jj)
572               zcldeff = 1.0 - sbudyko(ji,jj) * sf(jp_ccov)%fnow(ji,jj) * sf(jp_ccov)%fnow(ji,jj)   
573               ztaevbk = ztatm3 * ztatm(ji,jj) * zcldeff * ( 0.39 - 0.05 * zevsqr(ji,jj) ) 
574               !
575               z_qlw(ji,jj,jl) = - emic * stefan * ( ztaevbk + 4. * ztatm3 * ( pst(ji,jj,jl) - ztatm(ji,jj) ) ) 
576
577               !----------------------------------------
578               !  Turbulent heat fluxes over snow/ice     ( Latent and sensible )
579               !----------------------------------------       
580
581               ! vapour pressure at saturation of ice (tmask to avoid overflow in the exponential)
582               zesi =  611.0 * EXP( 21.8745587 * tmask(ji,jj,1) * ( pst(ji,jj,jl) - rtt )/ ( pst(ji,jj,jl) - 7.66 ) )
583               ! humidity close to the ice surface (at saturation)
584               zqsati   = ( 0.622 * zesi ) / ( zpatm - 0.378 * zesi )
585               
586               !  computation of intermediate values
587               zticemb  = pst(ji,jj,jl) - 7.66
588               zticemb2 = zticemb * zticemb 
589               ztice3   = pst(ji,jj,jl) * pst(ji,jj,jl) * pst(ji,jj,jl)
590               zdesidt  = zesi * ( 9.5 * LOG( 10.0 ) * ( rtt - 7.66 )  / zticemb2 )
591               
592               !  Transfer cofficients assumed to be constant (Parkinson 1979 ; Maykut 1982)
593               zcshi    = 1.75e-03
594               zclei    = zcshi
595               
596               !  sensible and latent fluxes over ice
597               zrhova     = zrhoa(ji,jj) * sf(jp_wndm)%fnow(ji,jj)      ! computation of intermediate values
598               zrhovaclei = zrhova * zcshi * 2.834e+06
599               zrhovacshi = zrhova * zclei * 1004.0
600           
601               !  sensible heat flux
602               z_qsb(ji,jj,jl) = zrhovacshi * ( pst(ji,jj,jl) - ztatm(ji,jj) )
603           
604               !  latent heat flux
605               p_qla(ji,jj,jl) = MAX(  0.e0, zrhovaclei * ( zqsati - zqatm(ji,jj) )  )
606             
607               !  sensitivity of non solar fluxes (dQ/dT) (long-wave, sensible and latent fluxes)
608               zdqlw = 4.0 * emic * stefan * ztice3
609               zdqsb = zrhovacshi
610               zdqla = zrhovaclei * ( zdesidt * ( zqsati * zqsati / ( zesi * zesi ) ) * ( zpatm / 0.622 ) )   
611               !
612               p_dqla(ji,jj,jl) = zdqla                           ! latent flux sensitivity
613               p_dqns(ji,jj,jl) = -( zdqlw + zdqsb + zdqla )      !  total non solar sensitivity
614            END DO
615         END DO
616      END DO
617
618      !
619      ! ----------------------------------------------------------------------------- !
620      !     III    Total FLUXES                                                       !
621      ! ----------------------------------------------------------------------------- !
622      !
623!CDIR COLLAPSE
624      p_qns(:,:,:) =     z_qlw (:,:,:) - z_qsb (:,:,:) - p_qla (:,:,:)      ! Downward Non Solar flux
625!CDIR COLLAPSE
626      p_tpr(:,:) = sf(jp_prec)%fnow(:,:) / rday     ! total precipitation [kg/m2/s]
627      !
628!!gm : not necessary as all input data are lbc_lnk...
629      CALL lbc_lnk( p_fr1  (:,:) , 'T', 1. )
630      CALL lbc_lnk( p_fr2  (:,:) , 'T', 1. )
631      DO jl = 1, jpl
632         CALL lbc_lnk( p_qns (:,:,jl) , 'T', 1. )
633         CALL lbc_lnk( p_dqns(:,:,jl) , 'T', 1. )
634         CALL lbc_lnk( p_qla (:,:,jl) , 'T', 1. )
635         CALL lbc_lnk( p_dqla(:,:,jl) , 'T', 1. )
636      END DO
637
638!!gm : mask is not required on forcing
639      DO jl = 1, jpl
640         p_qns (:,:,jl) = p_qns (:,:,jl) * tmask(:,:,1)
641         p_qla (:,:,jl) = p_qla (:,:,jl) * tmask(:,:,1)
642         p_dqns(:,:,jl) = p_dqns(:,:,jl) * tmask(:,:,1)
643         p_dqla(:,:,jl) = p_dqla(:,:,jl) * tmask(:,:,1)
644      END DO
645
646   END SUBROUTINE blk_ice_clio
647
648
649   SUBROUTINE blk_clio_qsr_oce( pqsr_oce )
650      !!---------------------------------------------------------------------------
651      !!                     ***  ROUTINE blk_clio_qsr_oce  ***
652      !!                 
653      !!  ** Purpose :   Computation of the shortwave radiation at the ocean and the
654      !!               snow/ice surfaces.
655      !!         
656      !!  ** Method  : - computed qsr from the cloud cover for both ice and ocean
657      !!               - also initialise sbudyko and stauc once for all
658      !!----------------------------------------------------------------------
659      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj)     ::   pqsr_oce    ! shortwave radiation  over the ocean
660      !!
661      INTEGER, PARAMETER  ::   jp24 = 24   ! sampling of the daylight period (sunrise to sunset) into 24 equal parts
662      !!     
663      INTEGER  ::   ji, jj, jt    ! dummy loop indices
664      INTEGER  ::   indaet            !  = -1, 0, 1 for odd, normal and leap years resp.
665      INTEGER  ::   iday              ! integer part of day
666      INTEGER  ::   indxb, indxc      ! index for cloud depth coefficient
667
668      REAL(wp)  ::   zalat , zclat, zcmue, zcmue2    ! local scalars
669      REAL(wp)  ::   zmt1, zmt2, zmt3                !
670      REAL(wp)  ::   zdecl, zsdecl , zcdecl          !
671      REAL(wp)  ::   za_oce, ztamr, zinda             !
672
673      REAL(wp) ::   zdl, zlha     ! local scalars
674      REAL(wp) ::   zlmunoon, zcldcor, zdaycor            !   
675      REAL(wp) ::   zxday, zdist, zcoef, zcoef1           !
676      REAL(wp) ::   zes
677      !!
678      REAL(wp), DIMENSION(jpi,jpj) ::   zev         ! vapour pressure
679      REAL(wp), DIMENSION(jpi,jpj) ::   zdlha, zlsrise, zlsset     ! 2D workspace
680
681      REAL(wp), DIMENSION(jpi,jpj) ::   zps, zpc   ! sine (cosine) of latitude per sine (cosine) of solar declination
682      !!---------------------------------------------------------------------
683
684
685      IF( lbulk_init ) THEN             !   Initilization at first time step only
686         rdtbs2 = nn_fsbc * rdt * 0.5
687         ! cloud optical depths as a function of latitude (Chou et al., 1981).
688         ! and the correction factor for taking into account  the effect of clouds
689         DO jj = 1, jpj
690            DO ji = 1 , jpi
691               zalat          = ( 90.e0 - ABS( gphit(ji,jj) ) ) /  5.e0
692               zclat          = ( 95.e0 -      gphit(ji,jj)   ) / 10.e0
693               indxb          = 1 + INT( zalat )
694               indxc          = 1 + INT( zclat )
695               zdl            = zclat - INT( zclat )
696               !  correction factor to account for the effect of clouds
697               sbudyko(ji,jj) = budyko(indxb)
698               stauc  (ji,jj) = ( 1.e0 - zdl ) * tauco( indxc ) + zdl * tauco( indxc + 1 )
699            END DO
700         END DO
701         IF    ( nleapy == 1 ) THEN   ;   yearday = 366.e0
702         ELSEIF( nleapy == 0 ) THEN   ;   yearday = 365.e0
703         ELSEIF( nleapy == 30) THEN   ;   yearday = 360.e0
704         ENDIF
705         lbulk_init = .FALSE.
706      ENDIF
707
708
709      ! Saturated water vapour and vapour pressure
710      ! ------------------------------------------
711!CDIR NOVERRCHK
712!CDIR COLLAPSE
713      DO jj = 1, jpj
714!CDIR NOVERRCHK
715         DO ji = 1, jpi
716            ztamr = sf(jp_tair)%fnow(ji,jj) + rt0 - rtt
717            zmt1  = SIGN( 17.269,  ztamr )
718            zmt2  = SIGN( 21.875,  ztamr )
719            zmt3  = SIGN( 28.200, -ztamr )
720            zes = 611.0 * EXP(  ABS( ztamr ) * MIN ( zmt1, zmt2 )   &              ! Saturation water vapour
721               &                     / ( sf(jp_tair)%fnow(ji,jj) + rt0 - 35.86  + MAX( 0.e0, zmt3 ) )  )
722            zev(ji,jj) = sf(jp_humi)%fnow(ji,jj) * zes * 1.0e-05                   ! vapour pressure 
723         END DO
724      END DO
725
726      !-----------------------------------!
727      !  Computation of solar irradiance  !
728      !-----------------------------------!
729!!gm : hard coded  leap year ???
730      indaet   = 1                                    ! = -1, 0, 1 for odd, normal and leap years resp.
731      zxday = nday_year + rdtbs2 / rday               ! day of the year at which the fluxes are calculated
732      iday  = INT( zxday )                            ! (centred at the middle of the ice time step)
733      CALL flx_blk_declin( indaet, iday, zdecl )      ! solar declination of the current day
734      zsdecl = SIN( zdecl * rad )                     ! its sine
735      zcdecl = COS( zdecl * rad )                     ! its cosine
736
737
738      !  correction factor added for computation of shortwave flux to take into account the variation of
739      !  the distance between the sun and the earth during the year (Oberhuber 1988)
740      zdist    = zxday * 2. * rpi / yearday
741      zdaycor  = 1.0 + 0.0013 * SIN( zdist ) + 0.0342 * COS( zdist )
742
743!CDIR NOVERRCHK
744      DO jj = 1, jpj
745!CDIR NOVERRCHK
746         DO ji = 1, jpi
747            !  product of sine (cosine) of latitude and sine (cosine) of solar declination
748            zps(ji,jj) = SIN( gphit(ji,jj) * rad ) * zsdecl
749            zpc(ji,jj) = COS( gphit(ji,jj) * rad ) * zcdecl
750            !  computation of the both local time of sunrise and sunset
751            zlsrise(ji,jj) = ACOS( - SIGN( 1.e0, zps(ji,jj) )    &
752               &                   * MIN(  1.e0, SIGN( 1.e0, zps(ji,jj) ) * ( zps(ji,jj) / zpc(ji,jj) )  )   )
753            zlsset (ji,jj) = - zlsrise(ji,jj)
754            !  dividing the solar day into jp24 segments of length zdlha
755            zdlha  (ji,jj) = ( zlsrise(ji,jj) - zlsset(ji,jj) ) / REAL( jp24 )
756         END DO
757      END DO
758
759
760      !---------------------------------------------!
761      !  shortwave radiation absorbed by the ocean  !
762      !---------------------------------------------!
763      pqsr_oce(:,:)   = 0.e0      ! set ocean qsr to zero     
764
765      ! compute and sum ocean qsr over the daylight (i.e. between sunrise and sunset)
766!CDIR NOVERRCHK   
767      DO jt = 1, jp24
768         zcoef = FLOAT( jt ) - 0.5
769!CDIR NOVERRCHK     
770!CDIR COLLAPSE
771         DO jj = 1, jpj
772!CDIR NOVERRCHK
773            DO ji = 1, jpi
774               zlha = COS(  zlsrise(ji,jj) - zcoef * zdlha(ji,jj)  )                  ! local hour angle
775               zcmue              = MAX( 0.e0 ,   zps(ji,jj) + zpc(ji,jj) * zlha  )   ! cos of local solar altitude
776               zcmue2             = 1368.0 * zcmue * zcmue
777
778               ! ocean albedo depending on the cloud cover (Payne, 1972)
779               za_oce     = ( 1.0 - sf(jp_ccov)%fnow(ji,jj) ) * 0.05 / ( 1.1 * zcmue**1.4 + 0.15 )   &   ! clear sky
780                  &       +         sf(jp_ccov)%fnow(ji,jj)   * 0.06                                     ! overcast
781
782                  ! solar heat flux absorbed by the ocean (Zillman, 1972)
783               pqsr_oce(ji,jj) = pqsr_oce(ji,jj)                                         &
784                  &            + ( 1.0 - za_oce ) * zdlha(ji,jj) * zcmue2                &
785                  &            / ( ( zcmue + 2.7 ) * zev(ji,jj) + 1.085 * zcmue +  0.10 )
786            END DO
787         END DO
788      END DO
789      ! Taking into account the ellipsity of the earth orbit, the clouds AND masked if sea-ice cover > 0%
790!!gm : bug zinda is always 0 si ice....
791      zcoef1 = srgamma * zdaycor / ( 2. * rpi )
792!CDIR COLLAPSE
793      DO jj = 1, jpj
794         DO ji = 1, jpi
795            zlmunoon = ASIN( zps(ji,jj) + zpc(ji,jj) ) / rad                         ! local noon solar altitude
796            zcldcor  = MIN(  1.e0, ( 1.e0 - 0.62 * sf(jp_ccov)%fnow(ji,jj)   &       ! cloud correction (Reed 1977)
797               &                          + 0.0019 * zlmunoon )                 )
798            zinda    = MAX(  0.e0, SIGN(  1.e0, -( -1.5 + freeze(ji,jj) )  )   )            ! 0 if more than 0% of ice
799            pqsr_oce(ji,jj) = zcoef1 * zcldcor * zinda * pqsr_oce(ji,jj) * tmask(ji,jj,1)   ! and zcoef1: ellipsity
800         END DO
801      END DO
802
803   END SUBROUTINE blk_clio_qsr_oce
804
805
806   SUBROUTINE blk_clio_qsr_ice( pa_ice_cs, pa_ice_os, pqsr_ice )
807      !!---------------------------------------------------------------------------
808      !!                     ***  ROUTINE blk_clio_qsr_ice  ***
809      !!                 
810      !!  ** Purpose :   Computation of the shortwave radiation at the ocean and the
811      !!               snow/ice surfaces.
812      !!         
813      !!  ** Method  : - computed qsr from the cloud cover for both ice and ocean
814      !!               - also initialise sbudyko and stauc once for all
815      !!----------------------------------------------------------------------
816      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj,jpl) ::   pa_ice_cs   ! albedo of ice under clear sky
817      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj,jpl) ::   pa_ice_os   ! albedo of ice under overcast sky
818      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj,jpl) ::   pqsr_ice    ! shortwave radiation over the ice/snow
819      !!
820      INTEGER, PARAMETER  ::   jp24 = 24   ! sampling of the daylight period (sunrise to sunset) into 24 equal parts
821      !!
822      INTEGER  ::   ji, jj, jl, jt    ! dummy loop indices
823      INTEGER  ::   indaet            !  = -1, 0, 1 for odd, normal and leap years resp.
824      INTEGER  ::   iday              ! integer part of day
825
826      REAL(wp)  ::   zcmue, zcmue2    ! local scalars
827      REAL(wp)  ::   zmt1, zmt2, zmt3                !
828      REAL(wp)  ::   zdecl, zsdecl , zcdecl          !
829      REAL(wp)  ::   ztamr             !
830
831      REAL(wp) ::   zlha     ! local scalars
832      REAL(wp) ::   zdaycor            !
833      REAL(wp) ::   zxday, zdist, zcoef, zcoef1           !
834      REAL(wp) ::   zes
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       
840      REAL(wp), DIMENSION(jpi,jpj) ::   zps, zpc   ! sine (cosine) of latitude per sine (cosine) of solar declination
841      !!---------------------------------------------------------------------
842     
843      ! Saturated water vapour and vapour pressure
844      ! ------------------------------------------
845!CDIR NOVERRCHK
846!CDIR COLLAPSE
847      DO jj = 1, jpj
848!CDIR NOVERRCHK
849         DO ji = 1, jpi           
850            ztamr = sf(jp_tair)%fnow(ji,jj) + rt0 - rtt           
851            zmt1  = SIGN( 17.269,  ztamr )
852            zmt2  = SIGN( 21.875,  ztamr )
853            zmt3  = SIGN( 28.200, -ztamr )
854            zes = 611.0 * EXP(  ABS( ztamr ) * MIN ( zmt1, zmt2 )   &              ! Saturation water vapour
855               &                     / ( sf(jp_tair)%fnow(ji,jj) + rt0 - 35.86  + MAX( 0.e0, zmt3 ) )  )
856            zev(ji,jj) = sf(jp_humi)%fnow(ji,jj) * zes * 1.0e-05                   ! vapour pressure 
857         END DO
858      END DO
859
860      !-----------------------------------!
861      !  Computation of solar irradiance  !
862      !-----------------------------------!
863!!gm : hard coded  leap year ???
864      indaet   = 1                                    ! = -1, 0, 1 for odd, normal and leap years resp.
865      zxday = nday_year + rdtbs2 / rday               ! day of the year at which the fluxes are calculated
866      iday  = INT( zxday )                            ! (centred at the middle of the ice time step)
867      CALL flx_blk_declin( indaet, iday, zdecl )      ! solar declination of the current day
868      zsdecl = SIN( zdecl * rad )                     ! its sine
869      zcdecl = COS( zdecl * rad )                     ! its cosine
870
871     
872      !  correction factor added for computation of shortwave flux to take into account the variation of
873      !  the distance between the sun and the earth during the year (Oberhuber 1988)
874      zdist    = zxday * 2. * rpi / yearday
875      zdaycor  = 1.0 + 0.0013 * SIN( zdist ) + 0.0342 * COS( zdist )
876
877!CDIR NOVERRCHK
878      DO jj = 1, jpj
879!CDIR NOVERRCHK
880         DO ji = 1, jpi
881            !  product of sine (cosine) of latitude and sine (cosine) of solar declination
882            zps(ji,jj) = SIN( gphit(ji,jj) * rad ) * zsdecl
883            zpc(ji,jj) = COS( gphit(ji,jj) * rad ) * zcdecl
884            !  computation of the both local time of sunrise and sunset
885            zlsrise(ji,jj) = ACOS( - SIGN( 1.e0, zps(ji,jj) )    &
886               &                   * MIN(  1.e0, SIGN( 1.e0, zps(ji,jj) ) * ( zps(ji,jj) / zpc(ji,jj) )  )   ) 
887            zlsset (ji,jj) = - zlsrise(ji,jj)
888            !  dividing the solar day into jp24 segments of length zdlha
889            zdlha  (ji,jj) = ( zlsrise(ji,jj) - zlsset(ji,jj) ) / REAL( jp24 )
890         END DO
891      END DO
892
893
894      !---------------------------------------------!
895      !  shortwave radiation absorbed by the ice    !
896      !---------------------------------------------!
897      ! compute and sum ice qsr over the daylight for each ice categories
898      pqsr_ice(:,:,:) = 0.e0
899      zcoef1 = zdaycor / ( 2. * rpi )
900     
901      !                    !----------------------------!
902      DO jl = 1, jpl       !  loop over ice categories  !
903         !                 !----------------------------!
904!CDIR NOVERRCHK   
905         DO jt = 1, jp24   
906            zcoef = FLOAT( jt ) - 0.5
907!CDIR NOVERRCHK     
908!CDIR COLLAPSE
909            DO jj = 1, jpj
910!CDIR NOVERRCHK
911               DO ji = 1, jpi
912                  zlha = COS(  zlsrise(ji,jj) - zcoef * zdlha(ji,jj)  )                  ! local hour angle
913                  zcmue              = MAX( 0.e0 ,   zps(ji,jj) + zpc(ji,jj) * zlha  )   ! cos of local solar altitude
914                  zcmue2             = 1368.0 * zcmue * zcmue
915                 
916                  !  solar heat flux absorbed by the ice/snow system (Shine and Crane 1984 adapted to high albedo)
917                  zqsr_ice_cs =  ( 1.0 - pa_ice_cs(ji,jj,jl) ) * zdlha(ji,jj) * zcmue2        &   ! clear sky
918                     &        / ( ( 1.0 + zcmue ) * zev(ji,jj) + 1.2 * zcmue + 0.0455 )
919                  zqsr_ice_os = zdlha(ji,jj) * SQRT( zcmue )                                  &   ! overcast sky
920                     &        * ( 53.5 + 1274.5 * zcmue )      * ( 1.0 - 0.996  * pa_ice_os(ji,jj,jl) )    &
921                     &        / (  1.0 + 0.139  * stauc(ji,jj) * ( 1.0 - 0.9435 * pa_ice_os(ji,jj,jl) ) )       
922             
923                  pqsr_ice(ji,jj,jl) = pqsr_ice(ji,jj,jl) + (  ( 1.0 - sf(jp_ccov)%fnow(ji,jj) ) * zqsr_ice_cs    &
924                     &                                       +         sf(jp_ccov)%fnow(ji,jj)   * zqsr_ice_os  )
925               END DO
926            END DO
927         END DO
928         !
929         ! Correction : Taking into account the ellipsity of the earth orbit
930         pqsr_ice(:,:,jl) = pqsr_ice(:,:,jl) * zcoef1 * tmask(:,:,1)
931         !
932         !                 !--------------------------------!
933      END DO               !  end loop over ice categories  !
934         !                 !--------------------------------!
935
936
937!!gm  : this should be suppress as input data have been passed through lbc_lnk
938      DO jl = 1, jpl
939         CALL lbc_lnk( pqsr_ice(:,:,jl) , 'T', 1. )
940      END DO
941      !
942   END SUBROUTINE blk_clio_qsr_ice
943
944
945   SUBROUTINE flx_blk_declin( ky, kday, pdecl )
946      !!---------------------------------------------------------------------------
947      !!               ***  ROUTINE flx_blk_declin  ***
948      !!         
949      !! ** Purpose :   Computation of the solar declination for the day
950      !!       
951      !! ** Method  :   ???
952      !!---------------------------------------------------------------------
953      INTEGER , INTENT(in   ) ::   ky      ! = -1, 0, 1 for odd, normal and leap years resp.
954      INTEGER , INTENT(in   ) ::   kday    ! day of the year ( kday = 1 on january 1)
955      REAL(wp), INTENT(  out) ::   pdecl   ! solar declination
956      !!
957      REAL(wp) ::   a0  =  0.39507671      ! coefficients for solar declinaison computation
958      REAL(wp) ::   a1  = 22.85684301      !     "              ""                 "
959      REAL(wp) ::   a2  = -0.38637317      !     "              ""                 "
960      REAL(wp) ::   a3  =  0.15096535      !     "              ""                 "
961      REAL(wp) ::   a4  = -0.00961411      !     "              ""                 "
962      REAL(wp) ::   b1  = -4.29692073      !     "              ""                 "
963      REAL(wp) ::   b2  =  0.05702074      !     "              ""                 "
964      REAL(wp) ::   b3  = -0.09028607      !     "              ""                 "
965      REAL(wp) ::   b4  =  0.00592797
966      !!
967      REAL(wp) ::   zday   ! corresponding day of type year (cf. ky)
968      REAL(wp) ::   zp     ! temporary scalars
969      !!---------------------------------------------------------------------
970           
971      IF    ( ky == 1 )  THEN   ;   zday = REAL( kday ) - 0.5
972      ELSEIF( ky == 3 )  THEN   ;   zday = REAL( kday ) - 1.
973      ELSE                      ;   zday = REAL( kday )
974      ENDIF
975     
976      zp = rpi * ( 2.0 * zday - 367.0 ) / yearday
977     
978      pdecl  = a0                                                                      &
979         &   + a1 * COS( zp ) + a2 * COS( 2. * zp ) + a3 * COS( 3. * zp ) + a4 * COS( 4. * zp )   &
980         &   + b1 * SIN( zp ) + b2 * SIN( 2. * zp ) + b3 * SIN( 3. * zp ) + b4 * SIN( 4. * zp )
981      !
982   END SUBROUTINE flx_blk_declin
983
984   !!======================================================================
985END MODULE sbcblk_clio
Note: See TracBrowser for help on using the repository browser.