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

Last change on this file since 1000 was 1000, checked in by cetlod, 16 years ago

computation of wind speed module, see ticket:164

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