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

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

CT : BUGFIX135 : correction of the zxday calculation using nday_year the number of days since the beginning of the run

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