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_r1837_mass_heat_salt_fluxes/NEMO/OPA_SRC/SBC – NEMO

source: branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/OPA_SRC/SBC/sbcblk_clio.F90 @ 1859

Last change on this file since 1859 was 1859, checked in by gm, 14 years ago

ticket:#665 step 2 & 3: heat content in qns & new forcing terms

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