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

Last change on this file since 464 was 464, checked in by opalod, 18 years ago

nemo_v1_update_055:RB: just change key_autotasking to key_mpp_omp

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