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

Last change on this file since 156 was 152, checked in by opalod, 20 years ago

CL + CT: UPDATE097: Move the computation step of the albedo in a module albedo.F90 and add the corresponding "USE albedo" module in both flxblk.F90 and limflx.F90 modules

  • 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
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( kt, 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      INTEGER , INTENT( in  )  ::   kt        ! time step
107      REAL(wp), INTENT( in ), DIMENSION(jpi,jpj) ::   &
108         &                          psst      ! Sea Surface Temperature
109
110      !! * Local variables
111      INTEGER  ::             &
112         ji, jj, jt        ,  &  ! dummy loop indices
113         indaet            ,  &  !  = -1, 0, 1 for odd, normal and leap years resp.
114         iday              ,  &  ! integer part of day
115         indxb             ,  &  ! index for budyko coefficient
116         indxc                   ! index for cloud depth coefficient
117
118      REAL(wp)  ::            & 
119         zalat , zclat     ,  &  ! latitude in degrees
120         zmt1, zmt2, zmt3  ,  &  ! tempory air temperatures variables
121         ztatm3, ztatm4    ,  &  ! power 3 and 4 of air temperature
122         z4tatm3           ,  &  ! 4 * ztatm3
123         zcmue             ,  &  ! cosine of local solar altitude
124         zcmue2            ,  &  ! root of zcmue1
125         zscmue            ,  &  ! square-root of zcmue1
126         zpcmue            ,  &  ! zcmue1**1.4
127         zdecl             ,  &  ! solar declination
128         zsdecl , zcdecl   ,  &  ! sine and cosine of solar declination
129         zalbo             ,  &  ! albedo of sea-water
130         zalbi             ,  &  ! albedo of ice
131         ztamr             ,  &  ! air temperature minus triple point of water (rtt)
132         ztaevbk           ,  &  ! part of net longwave radiation
133         zevi , zevo       ,  &  ! vapour pressure of ice and ocean
134         zind1,zind2,zind3 ,  &  ! switch for testing the values of air temperature
135         zinda             ,  &  ! switch for testing the values of sea ice cover
136         zpis2             ,  &  ! pi / 2
137         z2pi                    ! 2 * pi
138
139      REAL(wp)  ::            & 
140         zxday             ,  &  ! day of year
141         ztsec             ,  &  ! time in seconds
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      ztsec = ( 2 * INT ( ( kt - 1 ) / nfbulk ) + 1 ) * rdtbs2
319      zxday = MOD( ztsec , raass ) / rday + 1.0 
320
321      iday   = INT( zxday )
322      IF(l_ctl)   WRITE(numout,*) ' declin : iday ', iday, ' nfbulk= ', nfbulk
323      !   computation of the solar declination, his sine and his cosine
324      CALL flx_blk_declin( indaet, iday, zdecl )
325     
326      zdecl    = zdecl * rad
327      zsdecl   = SIN( zdecl )
328      zcdecl   = COS( zdecl )
329     
330      !  correction factor added for computation of shortwave flux to take into account the variation of
331      !  the distance between the sun and the earth during the year (Oberhuber 1988)
332      zdist    = zxday * z2pi / yearday
333      zdaycor  = 1.0 + 0.0013 * SIN( zdist ) + 0.0342 * COS( zdist )
334
335!CDIR NOVERRCHK
336      DO jj = 1, jpj
337!CDIR NOVERRCHK
338         DO ji = 1, jpi
339            !  product of sine of latitude and sine of solar declination
340            zps     (ji,jj) = SIN( gphit(ji,jj) * rad ) * zsdecl
341            !  product of cosine of latitude and cosine of solar declination
342            zpc     (ji,jj) = COS( gphit(ji,jj) * rad ) * zcdecl
343            !  computation of the both local time of sunrise and sunset
344            zlsrise (ji,jj) = ACOS( - SIGN( zone, zps(ji,jj) ) * MIN( zone, SIGN( zone, zps(ji,jj) )  &
345               &                     * ( zps(ji,jj) / zpc(ji,jj) ) ) ) 
346            zlsset  (ji,jj) = - zlsrise(ji,jj)
347            !  dividing the solar day into jpintsr segments of length zdlha
348            zdlha   (ji,jj) = ( zlsrise(ji,jj) - zlsset(ji,jj) ) / REAL( jpintsr )
349            !  computation of the local noon solar altitude
350            zlmunoon(ji,jj) = ASIN ( ( zps(ji,jj) + zpc(ji,jj) ) ) / rad
351           
352            !  cloud correction taken from Reed (1977) (imposed lower than 1)
353            zcldcor (ji,jj) = MIN( zone, ( 1.e0 - 0.62 * catm(ji,jj) + 0.0019 * zlmunoon(ji,jj) ) )
354         END DO
355      END DO
356
357         !  Computation of solar heat flux at each time of the day between sunrise and sunset.
358         !  We do this to a better optimisation of the code
359         !------------------------------------------------------       
360
361!CDIR NOVERRCHK   
362      DO jt = 1, jpintsr   
363         zcoef = FLOAT( jt ) - 0.5
364!CDIR NOVERRCHK     
365         DO jj = 1, jpj
366!CDIR NOVERRCHK
367            DO ji = 1, jpi
368               !  local hour angle
369               zlha (ji,jj,jt) = COS ( zlsrise(ji,jj) - zcoef * zdlha(ji,jj) )
370
371               ! cosine of local solar altitude
372               zcmue              = MAX ( zzero ,   zps(ji,jj) + zpc(ji,jj) * zlha (ji,jj,jt)  )
373               zcmue2             = 1368.0 * zcmue * zcmue
374               zscmue             = SQRT ( zcmue )
375               zpcmue             = zcmue**1.4
376               ! computation of sea-water albedo (Payne, 1972)
377               zalbocs(ji,jj,jt)  = 0.05 / ( 1.1 * zpcmue + 0.15 )
378               zalbo              = zcatm1(ji,jj) * zalbocs(ji,jj,jt) + catm(ji,jj) * zalboos(ji,jj)
379               ! solar heat flux absorbed at ocean surfaces (Zillman, 1972)
380               zevo               = zev(ji,jj) * 1.0e-05
381               zsqsro(ji,jj,jt)   =  ( 1.0 - zalbo ) * zdlha(ji,jj) * zcmue2                &
382                                   / ( ( zcmue + 2.7 ) * zevo + 1.085 * zcmue +  0.10 )
383               !  solar heat flux absorbed at sea/ice surfaces
384               !  Formulation of Shine and Crane, 1984 adapted for high albedo surfaces
385
386               !  For clear sky       
387               zevi               = zevo
388               zalbi              = zalbics(ji,jj)
389               zsqsrics(ji,jj,jt) =  ( 1.0 - zalbi ) * zdlha(ji,jj) * zcmue2                &
390                  &                / ( ( 1.0 + zcmue ) * zevi + 1.2 * zcmue + 0.0455 )
391
392               ! For overcast sky
393               zalbi              = zalbios(ji,jj)
394               zsqsrios(ji,jj,jt) = zdlha(ji,jj) *                                                           &
395                  &                 ( ( 53.5 + 1274.5 * zcmue      ) *  zscmue * ( 1.0 - 0.996  * zalbi ) )  &
396                  &                 / (  1.0 + 0.139  * stauc(ji,jj) *           ( 1.0 - 0.9435 * zalbi ) )
397            END DO
398         END DO
399      END DO
400
401
402      !  Computation of daily (between sunrise and sunset) solar heat flux absorbed
403      !  at the ocean and snow/ice surfaces.
404      !--------------------------------------------------------------------
405
406      zalbocsd(:,:) = 0.e0
407      zqsro   (:,:) = 0.e0
408      zqsrics (:,:) = 0.e0
409      zqsrios (:,:) = 0.e0
410
411      DO jt = 1, jpintsr 
412#   if defined key_vectopt_loop && ! defined key_autotasking
413         DO ji = 1, jpij 
414            zalbocsd(ji,1) = zalbocsd(ji,1) + zdlha   (ji,1) * zalbocs(ji,1,jt)   &
415               &                                             / MAX( 2.0 * zlsrise(ji,1) , zeps0 )
416            zqsro   (ji,1) = zqsro   (ji,1) + zsqsro  (ji,1,jt)
417            zqsrics (ji,1) = zqsrics (ji,1) + zsqsrics(ji,1,jt)
418            zqsrios (ji,1) = zqsrios (ji,1) + zsqsrios(ji,1,jt)
419         END DO
420#  else
421         DO jj = 1, jpj
422            DO ji = 1, jpi 
423               zalbocsd(ji,jj) = zalbocsd(ji,jj) + zdlha(ji,jj) * zalbocs(ji,jj,jt)   &
424                  &                                              / MAX( 2.0 * zlsrise(ji,jj) , zeps0 )
425               zqsro  (ji,jj)  = zqsro   (ji,jj) + zsqsro  (ji,jj,jt)
426               zqsrics(ji,jj)  = zqsrics (ji,jj) + zsqsrics(ji,jj,jt)
427               zqsrios(ji,jj)  = zqsrios (ji,jj) + zsqsrios(ji,jj,jt)
428            END DO
429         END DO
430#  endif
431      END DO
432
433      DO jj = 1, jpj
434         DO ji = 1, jpi 
435
436            !-------------------------------------------
437            !  Computation of shortwave radiation.
438            !-------------------------------------------
439
440            ! the solar heat flux absorbed at ocean and snow/ice surfaces
441            !------------------------------------------------------------
442
443            ! For ocean
444            qsr_oce(ji,jj) = srgamma * zcldcor(ji,jj) * zqsro(ji,jj) / z2pi
445            zinda          = SIGN( zone , -( -0.5 - zfrld(ji,jj) ) )
446            zinda          = 1.0 - MAX( zzero , zinda )
447            qsr_oce(ji,jj) = ( 1.- zinda ) * qsr_oce(ji,jj)
448
449            ! For snow/ice
450            qsr_ice(ji,jj) = ( zcatm1(ji,jj) * zqsrics(ji,jj) + catm(ji,jj) * zqsrios(ji,jj) ) / z2pi
451
452
453            ! Taking into account the ellipsity of the earth orbit
454            !-----------------------------------------------------
455
456            qsr_ice(ji,jj) = qsr_ice(ji,jj) * zdaycor
457            qsr_oce(ji,jj) = qsr_oce(ji,jj) * zdaycor
458
459            !  fraction of net shortwave radiation which is not absorbed in the
460            !  thin surface layer and penetrates inside the ice cover
461            !  ( Maykut and Untersteiner, 1971 ; Elbert anbd Curry, 1993 )
462            !------------------------------------------------------------------
463
464            fr1_i0(ji,jj) = 0.18  * zcatm1(ji,jj) + 0.35 * catm(ji,jj) 
465            fr2_i0(ji,jj) = 0.82  * zcatm1(ji,jj) + 0.65 * catm(ji,jj)
466
467            !---------------------------------------------------------------------------
468            !   Computation of long-wave radiation  ( Berliand 1952 ; all latitudes )
469            !---------------------------------------------------------------------------
470
471            ! tempory variables
472            ztatm3         = ztatm(ji,jj) * ztatm(ji,jj) * ztatm(ji,jj)
473            ztatm4         = ztatm3 * ztatm(ji,jj)
474            z4tatm3        = 4. * ztatm3
475            zcldeff(ji,jj) = 1.0 - sbudyko(ji,jj) * catm(ji,jj) * catm(ji,jj)   
476            ztaevbk        = ztatm4 * zcldeff(ji,jj) * ( 0.39 - 0.05 * zevsqr(ji,jj) ) 
477
478            !  Long-Wave for Ice
479            !----------------------
480            zqlw_ice(ji,jj) = - emic * stefan * ( ztaevbk + z4tatm3 * ( tn_ice(ji,jj) - ztatm(ji,jj) ) ) 
481
482            !  Long-Wave for Ocean
483            !-----------------------
484            zqlw_oce(ji,jj) = - emic * stefan * ( ztaevbk + z4tatm3 * ( psst  (ji,jj) - ztatm(ji,jj) ) ) 
485
486         END DO
487      END DO
488
489      !----------------------------------------
490      !  Computation of turbulent heat fluxes  ( Latent and sensible )
491      !----------------------------------------       
492      !CDIR NOVERRCHK
493      DO jj = 2 , jpjm1
494!ib   DO jj = 1 , jpj
495         !CDIR NOVERRCHK
496         DO  ji = 1, jpi
497
498            !  Turbulent heat fluxes over water
499            !----------------------------------
500
501            ! zeso     : vapour pressure at saturation of ocean
502            ! zqsato   : humidity close to the ocean surface (at saturation)
503            zeso          =  611.0 * EXP ( 17.2693884 * ( psst(ji,jj) - rtt ) * tmask(ji,jj,1) / ( psst(ji,jj) - 35.86 ) )
504            zqsato        = ( 0.622 * zeso ) / ( zpatm(ji,jj) - 0.378 * zeso )
505
506            !  Drag coefficients from Large and Pond (1981,1982)
507            !---------------------------------------------------
508   
509            !  Stability parameters
510            zdteta         = psst(ji,jj) - ztatm(ji,jj)
511            zdeltaq        = zqatm(ji,jj) - zqsato
512            ztvmoy         = ztatm(ji,jj) * ( 1. + 2.2e-3 * ztatm(ji,jj) * zqatm(ji,jj) )
513            zdenum         = MAX( vatm(ji,jj) * vatm(ji,jj) * ztvmoy, zeps )
514!i
515!i          if( zdenum == 0.e0 ) then
516!i               write(numout,*) 'flxblk  zdenum=0 ', ji,jj
517!i               zdenum = zeps
518!i          endif
519!i
520            zdtetar        = zdteta / zdenum
521            ztvmoyr        = ztvmoy * ztvmoy * zdeltaq / zdenum
522           
523            ! For stable atmospheric conditions
524            zobouks        = -70.0 * 10. * ( zdtetar + 3.2e-3 * ztvmoyr )
525            zobouks        = MAX( zzero , zobouks )
526            zpsims         = -7.0 * zobouks
527            zpsihs         =  zpsims
528            zpsils         =  zpsims
529
530            !  For unstable atmospheric conditions
531            zobouku        = -100.0 * 10.0 * ( zdtetar + 2.2e-3 * ztvmoyr )
532            zobouku        = MIN( zzero , zobouku )
533            zxins          = ( 1. - 16. * zobouku )**0.25
534            zlxins         = LOG( ( 1. + zxins * zxins ) / 2. )
535            zpsimu         = 2. * LOG( ( 1 + zxins ) / 2. )  + zlxins - 2. * ATAN( zxins ) + zpis2
536            zpsihu         = 2. * zlxins
537            zpsilu         = zpsihu
538
539            ! computation of intermediate values
540            zstab          = MAX( zzero , SIGN( zone , zdteta ) )
541            zpsim          = zstab * zpsimu + (1.0 - zstab ) * zpsims
542            zpsih          = zstab * zpsihu + (1.0 - zstab ) * zpsihs
543            zpsil          = zpsih
544           
545            zvatmg         = MAX( 0.032 * 1.5e-3 * vatm(ji,jj) * vatm(ji,jj) / grav, zeps )
546!i
547!!          if( zvatmg == 0.e0 ) then
548!!               write(numout,*) 'flxblk  zvatmg=0 ', ji,jj
549!!               zvatmg = zeps
550!!          endif
551!i
552
553            zcmn           = vkarmn / LOG ( 10. / zvatmg )
554            zcmn2          = zcmn * zcmn
555            zchn           = 0.0327 * zcmn
556            zcln           = 0.0346 * zcmn
557            zcmcmn         = 1 / ( 1 - zcmn * zpsim / vkarmn )
558            zchcm          = zcmcmn / ( 1 - zchn * zpsih / ( vkarmn * zcmn ) )
559            zclcm          = zchcm
560
561
562            !  Transfer cofficient zcsho and zcleo over ocean according to Large and Pond (1981,1982)
563            !--------------------------------------------------------------
564            zcsho          = zchn * zchcm
565            zcleo          = zcln * zclcm 
566
567
568            !   Computation of sensible and latent fluxes over Ocean
569            !----------------------------------------------------------------
570
571            !  computation of intermediate values
572            zrhova         = zrhoa(ji,jj) * vatm(ji,jj)
573            zrhovacsho     = zrhova * zcsho
574            zrhovacleo     = zrhova * zcleo
575
576            ! sensible heat flux
577            zqsb_oce(ji,jj) = zrhovacsho * 1004.0  * ( psst(ji,jj) - ztatm(ji,jj) ) 
578         
579            !  latent heat flux
580            zqla_oce(ji,jj) = zrhovacleo * 2.5e+06 * ( zqsato      - zqatm(ji,jj) )
581               
582            !  Calculate evaporation over water. (kg/m2/s)
583            !-------------------------------------------------
584            evap(ji,jj)    = zqla_oce(ji,jj) / cevap
585               
586               
587            !  Turbulent heat fluxes over snow/ice.
588            !--------------------------------------------------
589           
590            !  zesi     : vapour pressure at saturation of ice
591            !  zqsati   : humidity close to the ice surface (at saturation)
592            zesi           =  611.0 * EXP ( 21.8745587 * tmask(ji,jj,1)   &   ! tmask needed to avoid overflow in the exponential
593               &                                       * ( tn_ice(ji,jj) - rtt ) / ( tn_ice(ji,jj) - 7.66 ) )
594            zqsati         = ( 0.622 * zesi ) / ( zpatm(ji,jj) - 0.378 * zesi )
595               
596            !  computation of intermediate values
597            zticemb        = ( tn_ice(ji,jj) - 7.66 )
598            zticemb2       = zticemb * zticemb 
599            ztice3         = tn_ice(ji,jj) * tn_ice(ji,jj) * tn_ice(ji,jj)
600            zqsati2        = zqsati * zqsati
601            zesi2          = zesi * zesi
602            zdesidt        = zesi * ( 9.5 * LOG( 10.0 ) * ( rtt - 7.66 )  / zticemb2 )
603               
604            !  Transfer cofficient zcshi and zclei over ice. Assumed to be constant Parkinson 1979 ; Maykut 1982
605            !--------------------------------------------------------------------
606            zcshi          = 1.75e-03
607            zclei          = zcshi
608               
609            !  Computation of sensible and latent fluxes over ice
610            !----------------------------------------------------------------
611               
612            !  computation of intermediate values
613            zrhova          = zrhoa(ji,jj) * vatm(ji,jj)
614            zrhovacshi      = zrhova * zcshi * 2.834e+06
615            zrhovaclei      = zrhova * zclei * 1004.0
616           
617            !  sensible heat flux
618            zqsb_ice(ji,jj) = zrhovaclei * ( tn_ice(ji,jj) - ztatm(ji,jj) )
619           
620            !  latent heat flux
621            zqla_ice(ji,jj) = zrhovacshi * ( zqsati        - zqatm(ji,jj) )
622            qla_ice (ji,jj) = zqla_ice(ji,jj)
623             
624            !  Computation of sensitivity of non solar fluxes (dQ/dT)
625            !---------------------------------------------------------------
626               
627            !  computation of long-wave, sensible and latent flux sensitivity
628            zdqlw_ice       = 4.0 * emic * stefan * ztice3
629            zdqsb_ice       = zrhovaclei
630            zdqla_ice       = zrhovacshi * ( zdesidt * ( zqsati2 / zesi2 ) * ( zpatm(ji,jj) / 0.622 ) )         
631           
632            !  total non solar sensitivity
633            dqns_ice(ji,jj) = -( zdqlw_ice + zdqsb_ice + zdqla_ice ) 
634           
635            ! latent flux sensitivity
636            dqla_ice(ji,jj) = zdqla_ice
637           
638         END DO
639      END DO
640
641      ! total non solar heat flux over ice
642      qnsr_ice(:,:) = zqlw_ice(:,:) - zqsb_ice(:,:) - zqla_ice(:,:)
643      ! total non solar heat flux over water
644      qnsr_oce(:,:) = zqlw_oce(:,:) - zqsb_oce(:,:) - zqla_oce(:,:)
645
646      ! solid precipitations ( kg/m2/day -> kg/m2/s)
647      tprecip(:,:) = tprecip  (:,:) / rday 
648      ! snow  precipitations ( kg/m2/day -> kg/m2/s)
649      sprecip(:,:) = sprecip  (:,:) / rday 
650!i
651      CALL lbc_lnk( qsr_oce (:,:) , 'T', 1. )
652      CALL lbc_lnk( qnsr_oce(:,:) , 'T', 1. )
653      CALL lbc_lnk( qsr_ice (:,:) , 'T', 1. )
654      CALL lbc_lnk( qnsr_ice(:,:) , 'T', 1. )
655      CALL lbc_lnk( qla_ice (:,:) , 'T', 1. )
656      CALL lbc_lnk( dqns_ice(:,:) , 'T', 1. )
657      CALL lbc_lnk( dqla_ice(:,:) , 'T', 1. )
658      CALL lbc_lnk( fr1_i0  (:,:) , 'T', 1. )
659      CALL lbc_lnk( fr2_i0  (:,:) , 'T', 1. )
660      CALL lbc_lnk( tprecip (:,:) , 'T', 1. )
661      CALL lbc_lnk( sprecip (:,:) , 'T', 1. )
662      CALL lbc_lnk( evap    (:,:) , 'T', 1. )
663!i
664!i
665      qsr_oce (:,:) = qsr_oce (:,:)*tmask(:,:,1)
666      qnsr_oce(:,:) = qnsr_oce(:,:)*tmask(:,:,1)
667      qsr_ice (:,:) = qsr_ice (:,:)*tmask(:,:,1)
668      qnsr_ice(:,:) = qnsr_ice(:,:)*tmask(:,:,1)
669      qla_ice (:,:) = qla_ice (:,:)*tmask(:,:,1)
670      dqns_ice(:,:) = dqns_ice(:,:)*tmask(:,:,1)
671      dqla_ice(:,:) = dqla_ice(:,:)*tmask(:,:,1)
672      fr1_i0  (:,:) = fr1_i0  (:,:)*tmask(:,:,1)
673      fr2_i0  (:,:) = fr2_i0  (:,:)*tmask(:,:,1)
674      tprecip (:,:) = tprecip (:,:)*tmask(:,:,1)
675      sprecip (:,:) = sprecip (:,:)*tmask(:,:,1)
676      evap    (:,:) = evap    (:,:)*tmask(:,:,1)
677!i
678
679   END SUBROUTINE flx_blk
680
681
682   SUBROUTINE flx_blk_declin( ky, kday, pdecl )
683      !!---------------------------------------------------------------------------
684      !!               ***  ROUTINE flx_blk_declin  ***
685      !!         
686      !! ** Purpose :   Computation of the solar declination for the day
687      !!         kday ( in decimal degrees ).
688      !!       
689      !! ** Method  :
690      !!
691      !! History :
692      !!         original    : 01-04 (LIM)
693      !!         addition    : 02-08 (C. Ethe, G. Madec)
694      !!---------------------------------------------------------------------
695      !! * Arguments
696      INTEGER, INTENT( in ) ::   &
697         ky  ,        &  ! = -1, 0, 1 for odd, normal and leap years resp.
698         kday            ! day of the year ( kday = 1 on january 1)
699      REAL(wp), INTENT(out) ::  &
700         pdecl            ! solar declination
701
702      !! * Local variables
703      REAL(wp) ::                & 
704         zday                ,   &  ! corresponding day of type year (cf. ky)
705         zp1, zp2, zp3, zp4         ! temporary scalars
706      !!---------------------------------------------------------------------
707     
708      zday = FLOAT( kday ) 
709     
710      IF( ky == 1 )  THEN
711         zday = zday - 0.5
712      ELSEIF( ky == 3 )  THEN
713         zday = zday - 1.
714      ELSE
715         zday = REAL( kday )
716      ENDIF
717     
718      zp1 = rpi * ( 2.0 * zday - 367.0 ) / yearday
719      zp2 = 2. * zp1
720      zp3 = 3. * zp1
721      zp4 = 4. * zp1
722     
723      pdecl  = a0                                                                      &
724         &   + a1 * COS( zp1 ) + a2 * COS( zp2 ) + a3 * COS( zp3 ) + a4 * COS( zp4 )   &
725         &   + b1 * SIN( zp1 ) + b2 * SIN( zp2 ) + b3 * SIN( zp3 ) + b4 * SIN( zp4 )
726     
727   END SUBROUTINE flx_blk_declin
728
729#else
730   !!----------------------------------------------------------------------
731   !!   Default option :           Empty module                     NO bulk
732   !!----------------------------------------------------------------------
733CONTAINS
734   SUBROUTINE flx_blk            ! Empty routine
735   END SUBROUTINE flx_blk
736#endif
737
738   !!======================================================================
739END MODULE flxblk
Note: See TracBrowser for help on using the repository browser.