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.
flxblk.F90 in trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/flxblk.F90 @ 247

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 33.2 KB
Line 
1MODULE flxblk
2   !!======================================================================
3   !!                       ***  MODULE  flxblk  ***
4   !! Ocean forcing:  bulk thermohaline forcing of the ocean (or ice)
5   !!=====================================================================
6#if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
7   !!----------------------------------------------------------------------
8   !!   'key_flx_bulk_monthly'   or                            MONTHLY bulk
9   !!   'key_flx_bulk_daily'                                     DAILY bulk
10   !!----------------------------------------------------------------------
11   !!   flx_blk        : thermohaline fluxes from bulk
12   !!   flx_blk_declin : solar declinaison
13   !!----------------------------------------------------------------------
14   !! * Modules used
15   USE oce             ! ocean dynamics and tracers
16   USE dom_oce         ! ocean space and time domain
17   USE cpl_oce         ! ???
18   USE phycst          ! physical constants
19   USE daymod
20   USE blk_oce         ! bulk variables
21   USE flx_oce         ! forcings variables
22   USE ocfzpt          ! ???
23   USE in_out_manager
24   USE lbclnk
25   USE albedo
26
27   IMPLICIT NONE
28   PRIVATE
29
30   !! * Accessibility
31   PUBLIC flx_blk        ! routine called by flx.F90
32
33   !! * Module variables
34   INTEGER, PARAMETER  ::   &
35      jpintsr = 24          ! number of time step between sunrise and sunset
36      !                     ! uses for heat flux computation
37   LOGICAL ::   &
38      lbulk_init = .TRUE.   ! flag, bulk initialization done or not)
39
40   REAL(wp), DIMENSION(jpi,jpj) ::   &
41      stauc            ,  &   ! cloud optical depth
42      sbudyko   
43
44   !! * constants for bulk computation (flx_blk)
45   REAL(wp), DIMENSION(19)  ::  &
46      budyko                  ! BUDYKO's coefficient
47   ! BUDYKO's coefficient (cloudiness effect on LW radiation):
48   DATA budyko / 1.00, 0.98, 0.95, 0.92, 0.89, 0.86, 0.83, 0.80, 0.78, 0.75,  &
49      &          0.72, 0.69, 0.67, 0.64, 0.61, 0.58, 0.56, 0.53, 0.50 /
50   REAL(wp), DIMENSION(20)  :: &
51      tauco                  ! cloud optical depth coefficient
52   ! Cloud optical depth coefficient
53   DATA tauco / 6.6, 6.6, 7.0, 7.2, 7.1, 6.8, 6.5, 6.6, 7.1, 7.6,   &
54      &         6.6, 6.1, 5.6, 5.5, 5.8, 5.8, 5.6, 5.6, 5.6, 5.6 /
55   REAL(wp)  ::            &  ! constant values
56      zeps    = 1.e-20  ,  &
57      zeps0   = 1.e-13  ,  &
58      zeps1   = 1.e-06  ,  &
59      zzero   = 0.e0    ,  &
60      zone    = 1.0
61
62   !! * constants for solar declinaison computation (flx_blk_declin)
63   REAL(wp) ::                &
64      a0  =  0.39507671   ,   &  ! coefficients
65      a1  = 22.85684301   ,   &
66      a2  = -0.38637317   ,   &
67      a3  =  0.15096535   ,   &
68      a4  = -0.00961411   ,   &
69      b1  = -4.29692073   ,   &
70      b2  =  0.05702074   ,   &
71      b3  = -0.09028607   ,   &
72      b4  =  0.00592797
73   !!----------------------------------------------------------------------
74   !!   OPA 9.0 , LOCEAN-IPSL (2005)
75   !! $Header$
76   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
77   !!----------------------------------------------------------------------
78
79CONTAINS
80
81   SUBROUTINE flx_blk( psst )
82      !!---------------------------------------------------------------------------
83      !!                     ***  ROUTINE flx_blk  ***
84      !!                 
85      !!  ** Purpose :   Computation of the heat fluxes at ocean and snow/ice
86      !!       surface the solar heat at ocean and snow/ice surfaces and the
87      !!       sensitivity of total heat fluxes to the SST variations
88      !!         
89      !!  ** Method  :   The flux of heat at the ice and ocean surfaces are derived
90      !!       from semi-empirical ( or bulk ) formulae which relate the flux to
91      !!       the properties of the surface and of the lower atmosphere. Here, we
92      !!       follow the work of Oberhuber, 1988   
93      !!
94      !!  ** Action  :   call flx_blk_albedo to compute ocean and ice albedo
95      !!          computation of snow precipitation
96      !!          computation of solar flux at the ocean and ice surfaces
97      !!          computation of the long-wave radiation for the ocean and sea/ice
98      !!          computation of turbulent heat fluxes over water and ice
99      !!          computation of evaporation over water
100      !!          computation of total heat fluxes sensitivity over ice (dQ/dT)
101      !!          computation of latent heat flux sensitivity over ice (dQla/dT)
102      !!
103      !! History :
104      !!   8.0  !  97-06  (Louvain-La-Neuve)  Original code
105      !!   8.5  !  02-09  (C. Ethe , G. Madec )  F90: Free form and module
106      !!----------------------------------------------------------------------
107      !! * Arguments
108      REAL(wp), INTENT( in ), DIMENSION(jpi,jpj) ::   &
109         &                          psst      ! Sea Surface Temperature
110
111      !! * Local variables
112      INTEGER  ::             &
113         ji, jj, jt        ,  &  ! dummy loop indices
114         indaet            ,  &  !  = -1, 0, 1 for odd, normal and leap years resp.
115         iday              ,  &  ! integer part of day
116         indxb             ,  &  ! index for budyko coefficient
117         indxc                   ! index for cloud depth coefficient
118
119      REAL(wp)  ::            & 
120         zalat , zclat     ,  &  ! latitude in degrees
121         zmt1, zmt2, zmt3  ,  &  ! tempory air temperatures variables
122         ztatm3, ztatm4    ,  &  ! power 3 and 4 of air temperature
123         z4tatm3           ,  &  ! 4 * ztatm3
124         zcmue             ,  &  ! cosine of local solar altitude
125         zcmue2            ,  &  ! root of zcmue1
126         zscmue            ,  &  ! square-root of zcmue1
127         zpcmue            ,  &  ! zcmue1**1.4
128         zdecl             ,  &  ! solar declination
129         zsdecl , zcdecl   ,  &  ! sine and cosine of solar declination
130         zalbo             ,  &  ! albedo of sea-water
131         zalbi             ,  &  ! albedo of ice
132         ztamr             ,  &  ! air temperature minus triple point of water (rtt)
133         ztaevbk           ,  &  ! part of net longwave radiation
134         zevi , zevo       ,  &  ! vapour pressure of ice and ocean
135         zind1,zind2,zind3 ,  &  ! switch for testing the values of air temperature
136         zinda             ,  &  ! switch for testing the values of sea ice cover
137         zpis2             ,  &  ! pi / 2
138         z2pi                    ! 2 * pi
139
140      REAL(wp)  ::            & 
141         zxday             ,  &  ! day of year
142         zdist             ,  &  ! distance between the sun and the earth during the year
143         zdaycor           ,  &  ! corr. factor to take into account the variation of
144         !                       ! zday when calc. the solar rad.   
145         zesi, zeso        ,  &  ! vapour pressure of ice and ocean at saturation
146         zesi2             ,  &  ! root of zesi
147         zqsato            ,  &  ! humidity close to the ocean surface (at saturation)   
148         zqsati            ,  &  ! humidity close to the ice surface (at saturation)
149         zqsati2           ,  &  ! root of  zqsati
150         zdesidt           ,  &  ! derivative of zesi, function of ice temperature
151         zdteta            ,  &  ! diff. betw. sst and air temperature
152         zdeltaq           ,  &  ! diff. betw. spec. hum. and hum. close to the surface
153         ztvmoy, zobouks   ,  &  ! tempory scalars
154         zpsims, zpsihs, zpsils, zobouku, zxins, zpsimu ,  & 
155         zpsihu, zpsilu, zstab,zpsim, zpsih, zpsil      ,  & 
156         zvatmg, zcmn, zchn, zcln, zcmcmn, zdenum       ,  & 
157         zdtetar, ztvmoyr, zlxins, zcmn2, zchcm, zclcm , zcoef
158
159      REAL(wp)  ::            & 
160         zrhova            ,  &  ! air density per wind speed
161         zcsho , zcleo     ,  &  ! transfer coefficient over ocean
162         zcshi , zclei     ,  &  ! transfer coefficient over ice-free
163         zrhovacleo        ,  &  ! air density per wind speed per transfer coef.
164         zrhovacsho, zrhovaclei, zrhovacshi, & 
165         ztice3            ,  &  ! power 3 of ice temperature
166         zticemb, zticemb2 ,  &  ! tempory air temperatures variables
167         zdqlw_ice         ,  &  ! sensitivity of long-wave flux over ice
168         zdqsb_ice         ,  &  ! sensitivity of sensible heat flux over ice
169         zdqla_ice         ,  &  ! sensitivity of latent heat flux over ice
170         zdl, zdr                ! fractionnal part of latitude
171      REAL(wp), DIMENSION(jpi,jpj) :: & 
172         zpatm            ,  &   ! atmospheric pressure
173         zqatm            ,  &   ! specific humidity
174         zes              ,  &   ! vapour pressure at saturation
175         zev, zevsqr      ,  &   ! vapour pressure and his square-root
176         zrhoa            ,  &   ! air density
177         ztatm            ,  &   ! air temperature in Kelvins
178         zfrld            ,  &   ! fraction of sea ice cover
179         zcatm1           ,  &   ! fraction of cloud
180         zcldeff                 ! correction factor to account cloud effect
181      REAL(wp), DIMENSION(jpi,jpj) ::   & 
182         zalbocsd         ,  &   ! albedo of ocean
183         zalboos          ,  &   ! albedo of ocean under overcast sky
184         zalbics          ,  &   ! albedo of ice under clear sky
185         zalbios          ,  &   ! albedo of ice under overcast sky
186         zalbomu          ,  &   ! albedo of ocean when zcmue is 0.4
187         zqsro            ,  &   ! solar radiation over ocean
188         zqsrics          ,  &   ! solar radiation over ice under clear sky
189         zqsrios          ,  &   ! solar radiation over ice under overcast sky
190         zcldcor          ,  &   ! cloud correction
191         zlsrise, zlsset  ,  &   ! sunrise and sunset
192         zlmunoon         ,  &   ! local noon solar altitude
193         zdlha            ,  &   ! length of the ninstr segments of the solar day
194         zps              ,  &   ! sine of latitude per sine of solar decli.
195         zpc                     ! cosine of latitude per cosine of solar decli.
196
197      REAL(wp), DIMENSION(jpi,jpj) ::   & 
198         zqlw_oce         ,  &   ! long-wave heat flux over ocean
199         zqlw_ice         ,  &   ! long-wave heat flux over ice
200         zqla_oce         ,  &   ! latent heat flux over ocean
201         zqla_ice         ,  &   ! latent heat flux over ice
202         zqsb_oce         ,  &   ! sensible heat flux over ocean
203         zqsb_ice                ! sensible heat flux over ice
204 
205      REAL(wp), DIMENSION(jpi,jpj,jpintsr) ::    &
206         zlha             ,  &   ! local hour angle
207         zalbocs          ,  &   ! tempory var. of ocean albedo under clear sky
208         zsqsro           ,  &   ! tempory var. of solar rad. over ocean
209         zsqsrics         ,  &   ! temp. var. of solar rad. over ice under clear sky
210         zsqsrios                ! temp. var. of solar rad. over ice under overcast sky
211      !!---------------------------------------------------------------------
212
213      !---------------------
214      !   Initilization    !
215      !---------------------
216#if ! defined key_ice_lim
217      tn_ice(:,:) = psst(:,:)
218#endif
219
220      !  Determine cloud optical depths as a function of latitude (Chou et al., 1981).
221      !  and the correction factor for taking into account  the effect of clouds
222      !------------------------------------------------------
223      IF( lbulk_init ) THEN
224         DO jj = 1, jpj 
225            DO ji = 1 , jpi
226               zalat          = ( 90.e0 - ABS( gphit(ji,jj) ) ) /  5.e0
227               zclat          = ( 95.e0 -      gphit(ji,jj)   ) / 10.e0
228               indxb          = 1 + INT( zalat ) 
229               !  correction factor to account for the effect of clouds
230               sbudyko(ji,jj) = budyko(indxb) 
231               indxc          = 1 + INT( zclat ) 
232               zdl            = zclat - INT( zclat ) 
233               zdr            = 1.0 - zdl
234               stauc(ji,jj)   = zdr * tauco( indxc ) + zdl * tauco( indxc + 1 ) 
235            END DO
236         END DO
237         IF( nleapy == 1 ) THEN
238            yearday = 366.e0
239         ELSE IF( nleapy == 0 ) THEN
240            yearday = 365.e0
241         ELSEIF( nleapy == 30) THEN
242            yearday = 360.e0
243         ENDIF
244         lbulk_init = .FALSE.
245      ENDIF
246
247      zqlw_oce(:,:) = 0.e0
248      zqla_oce(:,:) = 0.e0
249      zqsb_oce(:,:) = 0.e0
250      zqlw_ice(:,:) = 0.e0
251      zqla_ice(:,:) = 0.e0
252      zqsb_ice(:,:) = 0.e0
253
254      zpis2       = rpi / 2.
255      z2pi        = 2. * rpi
256
257 !CDIR NOVERRCHK
258      DO jj = 1, jpj
259 !CDIR NOVERRCHK
260         DO ji = 1, jpi
261
262            ztatm (ji,jj) = 273.15 + tatm  (ji,jj)  !  air temperature in Kelvins
263            zcatm1(ji,jj) = 1.0    - catm  (ji,jj)  !  fractional cloud cover
264            zfrld (ji,jj) = 1.0    - freeze(ji,jj)  !  fractional sea ice cover
265            zpatm(ji,jj)  = 101000.               !  pressure
266     
267            !  Computation of air density, obtained from the equation of state for dry air.
268            zrhoa(ji,jj) = zpatm(ji,jj) / ( 287.04 * ztatm(ji,jj) )
269     
270            !  zes : Saturation water vapour
271            ztamr = ztatm(ji,jj) - rtt
272            zmt1  = SIGN( 17.269, ztamr )
273            zmt2  = SIGN( 21.875, ztamr )
274            zmt3  = SIGN( 28.200, -ztamr )
275            zes(ji,jj) = 611.0 * EXP (  ABS( ztamr ) * MIN ( zmt1, zmt2 )   &
276               &                      / ( ztatm(ji,jj) - 35.86  + MAX( zzero, zmt3 ) ) )
277
278            !  zev : vapour pressure  (hatm is relative humidity) 
279            zev(ji,jj)   = hatm(ji,jj) * zes(ji,jj) 
280            !  square-root of vapour pressure
281!CDIR NOVERRCHK
282            zevsqr(ji,jj) = SQRT( zev(ji,jj) * 0.01 )
283            !  zqapb  : specific humidity
284            zqatm(ji,jj) = 0.622 * zev(ji,jj) / ( zpatm(ji,jj) - 0.378 * zev(ji,jj) )
285
286
287            !----------------------------------------------------
288            !   Computation of snow precipitation (Ledley, 1985) |
289            !----------------------------------------------------
290
291            zmt1  =   253.0 - ztatm(ji,jj)
292            zmt2  = ( 272.0 - ztatm(ji,jj) ) / 38.0 
293            zmt3  = ( 281.0 - ztatm(ji,jj) ) / 18.0
294            zind1 = MAX( zzero, SIGN( zone, zmt1 ) )
295            zind2 = MAX( zzero, SIGN( zone, zmt2 ) )
296            zind3 = MAX( zzero, SIGN( zone, zmt3 ) )
297            ! total precipitation
298            tprecip(ji,jj) = watm(ji,jj)
299            ! solid  (snow) precipitation
300            sprecip(ji,jj) = tprecip(ji,jj) *       &
301               &             (           zind1      &
302               &               + ( 1.0 - zind1 ) * ( zind2 * ( 0.5 + zmt2 ) + ( 1.0 - zind2 ) *  zind3 * zmt3 ) ) 
303         END DO
304      END DO
305
306      !----------------------------------------------------------
307      !   Computation of albedo (need to calculates heat fluxes)|
308      !-----------------------------------------------------------
309     
310      CALL flx_blk_albedo( zalbios, zalboos, zalbics, zalbomu )
311
312      !-------------------------------------
313      !   Computation of solar irradiance. |
314      !----------------------------------------
315      indaet   = 1 
316      !  compution of the day of the year at which the fluxes have to be calculate
317      !--The date corresponds to the middle of the time step.
318      zxday=nday_year + rdtbs2/rday
319
320      iday   = INT( zxday )
321      IF(l_ctl)   WRITE(numout,*) ' declin : iday ', iday, ' nfbulk= ', nfbulk
322      !   computation of the solar declination, his sine and his cosine
323      CALL flx_blk_declin( indaet, iday, zdecl )
324     
325      zdecl    = zdecl * rad
326      zsdecl   = SIN( zdecl )
327      zcdecl   = COS( zdecl )
328     
329      !  correction factor added for computation of shortwave flux to take into account the variation of
330      !  the distance between the sun and the earth during the year (Oberhuber 1988)
331      zdist    = zxday * z2pi / yearday
332      zdaycor  = 1.0 + 0.0013 * SIN( zdist ) + 0.0342 * COS( zdist )
333
334!CDIR NOVERRCHK
335      DO jj = 1, jpj
336!CDIR NOVERRCHK
337         DO ji = 1, jpi
338            !  product of sine of latitude and sine of solar declination
339            zps     (ji,jj) = SIN( gphit(ji,jj) * rad ) * zsdecl
340            !  product of cosine of latitude and cosine of solar declination
341            zpc     (ji,jj) = COS( gphit(ji,jj) * rad ) * zcdecl
342            !  computation of the both local time of sunrise and sunset
343            zlsrise (ji,jj) = ACOS( - SIGN( zone, zps(ji,jj) ) * MIN( zone, SIGN( zone, zps(ji,jj) )  &
344               &                     * ( zps(ji,jj) / zpc(ji,jj) ) ) ) 
345            zlsset  (ji,jj) = - zlsrise(ji,jj)
346            !  dividing the solar day into jpintsr segments of length zdlha
347            zdlha   (ji,jj) = ( zlsrise(ji,jj) - zlsset(ji,jj) ) / REAL( jpintsr )
348            !  computation of the local noon solar altitude
349            zlmunoon(ji,jj) = ASIN ( ( zps(ji,jj) + zpc(ji,jj) ) ) / rad
350           
351            !  cloud correction taken from Reed (1977) (imposed lower than 1)
352            zcldcor (ji,jj) = MIN( zone, ( 1.e0 - 0.62 * catm(ji,jj) + 0.0019 * zlmunoon(ji,jj) ) )
353         END DO
354      END DO
355
356         !  Computation of solar heat flux at each time of the day between sunrise and sunset.
357         !  We do this to a better optimisation of the code
358         !------------------------------------------------------       
359
360!CDIR NOVERRCHK   
361      DO jt = 1, jpintsr   
362         zcoef = FLOAT( jt ) - 0.5
363!CDIR NOVERRCHK     
364         DO jj = 1, jpj
365!CDIR NOVERRCHK
366            DO ji = 1, jpi
367               !  local hour angle
368               zlha (ji,jj,jt) = COS ( zlsrise(ji,jj) - zcoef * zdlha(ji,jj) )
369
370               ! cosine of local solar altitude
371               zcmue              = MAX ( zzero ,   zps(ji,jj) + zpc(ji,jj) * zlha (ji,jj,jt)  )
372               zcmue2             = 1368.0 * zcmue * zcmue
373               zscmue             = SQRT ( zcmue )
374               zpcmue             = zcmue**1.4
375               ! computation of sea-water albedo (Payne, 1972)
376               zalbocs(ji,jj,jt)  = 0.05 / ( 1.1 * zpcmue + 0.15 )
377               zalbo              = zcatm1(ji,jj) * zalbocs(ji,jj,jt) + catm(ji,jj) * zalboos(ji,jj)
378               ! solar heat flux absorbed at ocean surfaces (Zillman, 1972)
379               zevo               = zev(ji,jj) * 1.0e-05
380               zsqsro(ji,jj,jt)   =  ( 1.0 - zalbo ) * zdlha(ji,jj) * zcmue2                &
381                                   / ( ( zcmue + 2.7 ) * zevo + 1.085 * zcmue +  0.10 )
382               !  solar heat flux absorbed at sea/ice surfaces
383               !  Formulation of Shine and Crane, 1984 adapted for high albedo surfaces
384
385               !  For clear sky       
386               zevi               = zevo
387               zalbi              = zalbics(ji,jj)
388               zsqsrics(ji,jj,jt) =  ( 1.0 - zalbi ) * zdlha(ji,jj) * zcmue2                &
389                  &                / ( ( 1.0 + zcmue ) * zevi + 1.2 * zcmue + 0.0455 )
390
391               ! For overcast sky
392               zalbi              = zalbios(ji,jj)
393               zsqsrios(ji,jj,jt) = zdlha(ji,jj) *                                                           &
394                  &                 ( ( 53.5 + 1274.5 * zcmue      ) *  zscmue * ( 1.0 - 0.996  * zalbi ) )  &
395                  &                 / (  1.0 + 0.139  * stauc(ji,jj) *           ( 1.0 - 0.9435 * zalbi ) )
396            END DO
397         END DO
398      END DO
399
400
401      !  Computation of daily (between sunrise and sunset) solar heat flux absorbed
402      !  at the ocean and snow/ice surfaces.
403      !--------------------------------------------------------------------
404
405      zalbocsd(:,:) = 0.e0
406      zqsro   (:,:) = 0.e0
407      zqsrics (:,:) = 0.e0
408      zqsrios (:,:) = 0.e0
409
410      DO jt = 1, jpintsr 
411#   if defined key_vectopt_loop && ! defined key_autotasking
412         DO ji = 1, jpij 
413            zalbocsd(ji,1) = zalbocsd(ji,1) + zdlha   (ji,1) * zalbocs(ji,1,jt)   &
414               &                                             / MAX( 2.0 * zlsrise(ji,1) , zeps0 )
415            zqsro   (ji,1) = zqsro   (ji,1) + zsqsro  (ji,1,jt)
416            zqsrics (ji,1) = zqsrics (ji,1) + zsqsrics(ji,1,jt)
417            zqsrios (ji,1) = zqsrios (ji,1) + zsqsrios(ji,1,jt)
418         END DO
419#  else
420         DO jj = 1, jpj
421            DO ji = 1, jpi 
422               zalbocsd(ji,jj) = zalbocsd(ji,jj) + zdlha(ji,jj) * zalbocs(ji,jj,jt)   &
423                  &                                              / MAX( 2.0 * zlsrise(ji,jj) , zeps0 )
424               zqsro  (ji,jj)  = zqsro   (ji,jj) + zsqsro  (ji,jj,jt)
425               zqsrics(ji,jj)  = zqsrics (ji,jj) + zsqsrics(ji,jj,jt)
426               zqsrios(ji,jj)  = zqsrios (ji,jj) + zsqsrios(ji,jj,jt)
427            END DO
428         END DO
429#  endif
430      END DO
431
432      DO jj = 1, jpj
433         DO ji = 1, jpi 
434
435            !-------------------------------------------
436            !  Computation of shortwave radiation.
437            !-------------------------------------------
438
439            ! the solar heat flux absorbed at ocean and snow/ice surfaces
440            !------------------------------------------------------------
441
442            ! For ocean
443            qsr_oce(ji,jj) = srgamma * zcldcor(ji,jj) * zqsro(ji,jj) / z2pi
444            zinda          = SIGN( zone , -( -0.5 - zfrld(ji,jj) ) )
445            zinda          = 1.0 - MAX( zzero , zinda )
446            qsr_oce(ji,jj) = ( 1.- zinda ) * qsr_oce(ji,jj)
447
448            ! For snow/ice
449            qsr_ice(ji,jj) = ( zcatm1(ji,jj) * zqsrics(ji,jj) + catm(ji,jj) * zqsrios(ji,jj) ) / z2pi
450
451
452            ! Taking into account the ellipsity of the earth orbit
453            !-----------------------------------------------------
454
455            qsr_ice(ji,jj) = qsr_ice(ji,jj) * zdaycor
456            qsr_oce(ji,jj) = qsr_oce(ji,jj) * zdaycor
457
458            !  fraction of net shortwave radiation which is not absorbed in the
459            !  thin surface layer and penetrates inside the ice cover
460            !  ( Maykut and Untersteiner, 1971 ; Elbert anbd Curry, 1993 )
461            !------------------------------------------------------------------
462
463            fr1_i0(ji,jj) = 0.18  * zcatm1(ji,jj) + 0.35 * catm(ji,jj) 
464            fr2_i0(ji,jj) = 0.82  * zcatm1(ji,jj) + 0.65 * catm(ji,jj)
465
466            !---------------------------------------------------------------------------
467            !   Computation of long-wave radiation  ( Berliand 1952 ; all latitudes )
468            !---------------------------------------------------------------------------
469
470            ! tempory variables
471            ztatm3         = ztatm(ji,jj) * ztatm(ji,jj) * ztatm(ji,jj)
472            ztatm4         = ztatm3 * ztatm(ji,jj)
473            z4tatm3        = 4. * ztatm3
474            zcldeff(ji,jj) = 1.0 - sbudyko(ji,jj) * catm(ji,jj) * catm(ji,jj)   
475            ztaevbk        = ztatm4 * zcldeff(ji,jj) * ( 0.39 - 0.05 * zevsqr(ji,jj) ) 
476
477            !  Long-Wave for Ice
478            !----------------------
479            zqlw_ice(ji,jj) = - emic * stefan * ( ztaevbk + z4tatm3 * ( tn_ice(ji,jj) - ztatm(ji,jj) ) ) 
480
481            !  Long-Wave for Ocean
482            !-----------------------
483            zqlw_oce(ji,jj) = - emic * stefan * ( ztaevbk + z4tatm3 * ( psst  (ji,jj) - ztatm(ji,jj) ) ) 
484
485         END DO
486      END DO
487
488      !----------------------------------------
489      !  Computation of turbulent heat fluxes  ( Latent and sensible )
490      !----------------------------------------       
491      !CDIR NOVERRCHK
492      DO jj = 2 , jpjm1
493!ib   DO jj = 1 , jpj
494         !CDIR NOVERRCHK
495         DO  ji = 1, jpi
496
497            !  Turbulent heat fluxes over water
498            !----------------------------------
499
500            ! zeso     : vapour pressure at saturation of ocean
501            ! zqsato   : humidity close to the ocean surface (at saturation)
502            zeso          =  611.0 * EXP ( 17.2693884 * ( psst(ji,jj) - rtt ) * tmask(ji,jj,1) / ( psst(ji,jj) - 35.86 ) )
503            zqsato        = ( 0.622 * zeso ) / ( zpatm(ji,jj) - 0.378 * zeso )
504
505            !  Drag coefficients from Large and Pond (1981,1982)
506            !---------------------------------------------------
507   
508            !  Stability parameters
509            zdteta         = psst(ji,jj) - ztatm(ji,jj)
510            zdeltaq        = zqatm(ji,jj) - zqsato
511            ztvmoy         = ztatm(ji,jj) * ( 1. + 2.2e-3 * ztatm(ji,jj) * zqatm(ji,jj) )
512            zdenum         = MAX( vatm(ji,jj) * vatm(ji,jj) * ztvmoy, zeps )
513!i
514!i          if( zdenum == 0.e0 ) then
515!i               write(numout,*) 'flxblk  zdenum=0 ', ji,jj
516!i               zdenum = zeps
517!i          endif
518!i
519            zdtetar        = zdteta / zdenum
520            ztvmoyr        = ztvmoy * ztvmoy * zdeltaq / zdenum
521           
522            ! For stable atmospheric conditions
523            zobouks        = -70.0 * 10. * ( zdtetar + 3.2e-3 * ztvmoyr )
524            zobouks        = MAX( zzero , zobouks )
525            zpsims         = -7.0 * zobouks
526            zpsihs         =  zpsims
527            zpsils         =  zpsims
528
529            !  For unstable atmospheric conditions
530            zobouku        = -100.0 * 10.0 * ( zdtetar + 2.2e-3 * ztvmoyr )
531            zobouku        = MIN( zzero , zobouku )
532            zxins          = ( 1. - 16. * zobouku )**0.25
533            zlxins         = LOG( ( 1. + zxins * zxins ) / 2. )
534            zpsimu         = 2. * LOG( ( 1 + zxins ) / 2. )  + zlxins - 2. * ATAN( zxins ) + zpis2
535            zpsihu         = 2. * zlxins
536            zpsilu         = zpsihu
537
538            ! computation of intermediate values
539            zstab          = MAX( zzero , SIGN( zone , zdteta ) )
540            zpsim          = zstab * zpsimu + (1.0 - zstab ) * zpsims
541            zpsih          = zstab * zpsihu + (1.0 - zstab ) * zpsihs
542            zpsil          = zpsih
543           
544            zvatmg         = MAX( 0.032 * 1.5e-3 * vatm(ji,jj) * vatm(ji,jj) / grav, zeps )
545!i
546!!          if( zvatmg == 0.e0 ) then
547!!               write(numout,*) 'flxblk  zvatmg=0 ', ji,jj
548!!               zvatmg = zeps
549!!          endif
550!i
551
552            zcmn           = vkarmn / LOG ( 10. / zvatmg )
553            zcmn2          = zcmn * zcmn
554            zchn           = 0.0327 * zcmn
555            zcln           = 0.0346 * zcmn
556            zcmcmn         = 1 / ( 1 - zcmn * zpsim / vkarmn )
557            zchcm          = zcmcmn / ( 1 - zchn * zpsih / ( vkarmn * zcmn ) )
558            zclcm          = zchcm
559
560
561            !  Transfer cofficient zcsho and zcleo over ocean according to Large and Pond (1981,1982)
562            !--------------------------------------------------------------
563            zcsho          = zchn * zchcm
564            zcleo          = zcln * zclcm 
565
566
567            !   Computation of sensible and latent fluxes over Ocean
568            !----------------------------------------------------------------
569
570            !  computation of intermediate values
571            zrhova         = zrhoa(ji,jj) * vatm(ji,jj)
572            zrhovacsho     = zrhova * zcsho
573            zrhovacleo     = zrhova * zcleo
574
575            ! sensible heat flux
576            zqsb_oce(ji,jj) = zrhovacsho * 1004.0  * ( psst(ji,jj) - ztatm(ji,jj) ) 
577         
578            !  latent heat flux
579            zqla_oce(ji,jj) = MAX(0.e0, zrhovacleo * 2.5e+06 * ( zqsato      - zqatm(ji,jj) ) )
580               
581            !  Calculate evaporation over water. (kg/m2/s)
582            !-------------------------------------------------
583            evap(ji,jj)    = zqla_oce(ji,jj) / cevap
584               
585               
586            !  Turbulent heat fluxes over snow/ice.
587            !--------------------------------------------------
588           
589            !  zesi     : vapour pressure at saturation of ice
590            !  zqsati   : humidity close to the ice surface (at saturation)
591            zesi           =  611.0 * EXP ( 21.8745587 * tmask(ji,jj,1)   &   ! tmask needed to avoid overflow in the exponential
592               &                                       * ( tn_ice(ji,jj) - rtt ) / ( tn_ice(ji,jj) - 7.66 ) )
593            zqsati         = ( 0.622 * zesi ) / ( zpatm(ji,jj) - 0.378 * zesi )
594               
595            !  computation of intermediate values
596            zticemb        = ( tn_ice(ji,jj) - 7.66 )
597            zticemb2       = zticemb * zticemb 
598            ztice3         = tn_ice(ji,jj) * tn_ice(ji,jj) * tn_ice(ji,jj)
599            zqsati2        = zqsati * zqsati
600            zesi2          = zesi * zesi
601            zdesidt        = zesi * ( 9.5 * LOG( 10.0 ) * ( rtt - 7.66 )  / zticemb2 )
602               
603            !  Transfer cofficient zcshi and zclei over ice. Assumed to be constant Parkinson 1979 ; Maykut 1982
604            !--------------------------------------------------------------------
605            zcshi          = 1.75e-03
606            zclei          = zcshi
607               
608            !  Computation of sensible and latent fluxes over ice
609            !----------------------------------------------------------------
610               
611            !  computation of intermediate values
612            zrhova          = zrhoa(ji,jj) * vatm(ji,jj)
613            zrhovacshi      = zrhova * zcshi * 2.834e+06
614            zrhovaclei      = zrhova * zclei * 1004.0
615           
616            !  sensible heat flux
617            zqsb_ice(ji,jj) = zrhovaclei * ( tn_ice(ji,jj) - ztatm(ji,jj) )
618           
619            !  latent heat flux
620            zqla_ice(ji,jj) = zrhovacshi * ( zqsati        - zqatm(ji,jj) )
621            qla_ice (ji,jj) = MAX(0.e0, zqla_ice(ji,jj) )
622             
623            !  Computation of sensitivity of non solar fluxes (dQ/dT)
624            !---------------------------------------------------------------
625               
626            !  computation of long-wave, sensible and latent flux sensitivity
627            zdqlw_ice       = 4.0 * emic * stefan * ztice3
628            zdqsb_ice       = zrhovaclei
629            zdqla_ice       = zrhovacshi * ( zdesidt * ( zqsati2 / zesi2 ) * ( zpatm(ji,jj) / 0.622 ) )         
630           
631            !  total non solar sensitivity
632            dqns_ice(ji,jj) = -( zdqlw_ice + zdqsb_ice + zdqla_ice ) 
633           
634            ! latent flux sensitivity
635            dqla_ice(ji,jj) = zdqla_ice
636           
637         END DO
638      END DO
639
640      ! total non solar heat flux over ice
641      qnsr_ice(:,:) = zqlw_ice(:,:) - zqsb_ice(:,:) - zqla_ice(:,:)
642      ! total non solar heat flux over water
643      qnsr_oce(:,:) = zqlw_oce(:,:) - zqsb_oce(:,:) - zqla_oce(:,:)
644
645      ! solid precipitations ( kg/m2/day -> kg/m2/s)
646      tprecip(:,:) = tprecip  (:,:) / rday 
647      ! snow  precipitations ( kg/m2/day -> kg/m2/s)
648      sprecip(:,:) = sprecip  (:,:) / rday 
649!i
650      CALL lbc_lnk( qsr_oce (:,:) , 'T', 1. )
651      CALL lbc_lnk( qnsr_oce(:,:) , 'T', 1. )
652      CALL lbc_lnk( qsr_ice (:,:) , 'T', 1. )
653      CALL lbc_lnk( qnsr_ice(:,:) , 'T', 1. )
654      CALL lbc_lnk( qla_ice (:,:) , 'T', 1. )
655      CALL lbc_lnk( dqns_ice(:,:) , 'T', 1. )
656      CALL lbc_lnk( dqla_ice(:,:) , 'T', 1. )
657      CALL lbc_lnk( fr1_i0  (:,:) , 'T', 1. )
658      CALL lbc_lnk( fr2_i0  (:,:) , 'T', 1. )
659      CALL lbc_lnk( tprecip (:,:) , 'T', 1. )
660      CALL lbc_lnk( sprecip (:,:) , 'T', 1. )
661      CALL lbc_lnk( evap    (:,:) , 'T', 1. )
662!i
663!i
664      qsr_oce (:,:) = qsr_oce (:,:)*tmask(:,:,1)
665      qnsr_oce(:,:) = qnsr_oce(:,:)*tmask(:,:,1)
666      qsr_ice (:,:) = qsr_ice (:,:)*tmask(:,:,1)
667      qnsr_ice(:,:) = qnsr_ice(:,:)*tmask(:,:,1)
668      qla_ice (:,:) = qla_ice (:,:)*tmask(:,:,1)
669      dqns_ice(:,:) = dqns_ice(:,:)*tmask(:,:,1)
670      dqla_ice(:,:) = dqla_ice(:,:)*tmask(:,:,1)
671      fr1_i0  (:,:) = fr1_i0  (:,:)*tmask(:,:,1)
672      fr2_i0  (:,:) = fr2_i0  (:,:)*tmask(:,:,1)
673      tprecip (:,:) = tprecip (:,:)*tmask(:,:,1)
674      sprecip (:,:) = sprecip (:,:)*tmask(:,:,1)
675      evap    (:,:) = evap    (:,:)*tmask(:,:,1)
676!i
677
678   END SUBROUTINE flx_blk
679
680
681   SUBROUTINE flx_blk_declin( ky, kday, pdecl )
682      !!---------------------------------------------------------------------------
683      !!               ***  ROUTINE flx_blk_declin  ***
684      !!         
685      !! ** Purpose :   Computation of the solar declination for the day
686      !!         kday ( in decimal degrees ).
687      !!       
688      !! ** Method  :
689      !!
690      !! History :
691      !!         original    : 01-04 (LIM)
692      !!         addition    : 02-08 (C. Ethe, G. Madec)
693      !!---------------------------------------------------------------------
694      !! * Arguments
695      INTEGER, INTENT( in ) ::   &
696         ky  ,        &  ! = -1, 0, 1 for odd, normal and leap years resp.
697         kday            ! day of the year ( kday = 1 on january 1)
698      REAL(wp), INTENT(out) ::  &
699         pdecl            ! solar declination
700
701      !! * Local variables
702      REAL(wp) ::                & 
703         zday                ,   &  ! corresponding day of type year (cf. ky)
704         zp1, zp2, zp3, zp4         ! temporary scalars
705      !!---------------------------------------------------------------------
706     
707      zday = FLOAT( kday ) 
708     
709      IF( ky == 1 )  THEN
710         zday = zday - 0.5
711      ELSEIF( ky == 3 )  THEN
712         zday = zday - 1.
713      ELSE
714         zday = REAL( kday )
715      ENDIF
716     
717      zp1 = rpi * ( 2.0 * zday - 367.0 ) / yearday
718      zp2 = 2. * zp1
719      zp3 = 3. * zp1
720      zp4 = 4. * zp1
721     
722      pdecl  = a0                                                                      &
723         &   + a1 * COS( zp1 ) + a2 * COS( zp2 ) + a3 * COS( zp3 ) + a4 * COS( zp4 )   &
724         &   + b1 * SIN( zp1 ) + b2 * SIN( zp2 ) + b3 * SIN( zp3 ) + b4 * SIN( zp4 )
725     
726   END SUBROUTINE flx_blk_declin
727
728#else
729   !!----------------------------------------------------------------------
730   !!   Default option :           Empty module                     NO bulk
731   !!----------------------------------------------------------------------
732CONTAINS
733   SUBROUTINE flx_blk            ! Empty routine
734   END SUBROUTINE flx_blk
735#endif
736
737   !!======================================================================
738END MODULE flxblk
Note: See TracBrowser for help on using the repository browser.