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

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

source: trunk/NEMO/OPA_SRC/SBC/sbcblk_clio.F90 @ 888

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

merge dev_001_SBC branche with the trunk to include the New Surface Module package, see ticket: #113

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