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

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

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 42.0 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_albedo : albedo for ocean and ice (clear and overcast skies)
13   !!   flx_blk_declin : solar declinaison
14   !!----------------------------------------------------------------------
15   !! * Modules used
16   USE oce             ! ocean dynamics and tracers
17   USE dom_oce         ! ocean space and time domain
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
26   IMPLICIT NONE
27   PRIVATE
28
29   !! * Accessibility
30   PUBLIC flx_blk        ! routine called by flx.F90
31   PUBLIC flx_blk_albedo ! routine called by limflx.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    = 1e-20   ,  &
57         zeps0   = 1e-13   ,  &
58         zeps1   = 1e-06   ,  &
59         zzero   = 0.0     ,  &
60         zone    = 1.0
61
62      !! * constants for albedo computation (flx_blk_albedo)
63      REAL(wp) ::   &
64         c1     = 0.05  ,     &   ! constants values
65         c2     = 0.1   ,     &
66         albice = 0.50  ,     &   !  albedo of melting ice in the arctic and antarctic (Shine & Hendersson-Sellers)
67         cgren  = 0.06  ,     &   !  correction of the snow or ice albedo to take into account
68                                  !  effects of cloudiness (Grenfell & Perovich, 1984)
69         alphd  = 0.80  ,     &   !  coefficients for linear interpolation used to compute
70         alphdi = 0.72  ,     &   !  albedo between two extremes values (Pyane, 1972)
71         alphc  = 0.65  ,     &
72         zmue   = 0.4             !  cosine of local solar altitude
73
74      !! * constants for solar declinaison computation (flx_blk_declin)
75      REAL(wp) ::                &
76         a0  =  0.39507671   ,   &  ! coefficients
77         a1  = 22.85684301   ,   &
78         a2  = -0.38637317   ,   &
79         a3  =  0.15096535   ,   &
80         a4  = -0.00961411   ,   &
81         b1  = -4.29692073   ,   &
82         b2  =  0.05702074   ,   &
83         b3  = -0.09028607   ,   &
84         b4  =  0.00592797
85   !!----------------------------------------------------------------------
86   !!   OPA 9.0 , LODYC-IPSL  (2003)
87   !!----------------------------------------------------------------------
88
89CONTAINS
90
91   SUBROUTINE flx_blk( kt, psst )
92      !!---------------------------------------------------------------------------
93      !!                     ***  ROUTINE flx_blk  ***
94      !!                 
95      !!  ** Purpose :   Computation of the heat fluxes at ocean and snow/ice
96      !!       surface the solar heat at ocean and snow/ice surfaces and the
97      !!       sensitivity of total heat fluxes to the SST variations
98      !!         
99      !!  ** Method  :   The flux of heat at the ice and ocean surfaces are derived
100      !!       from semi-empirical ( or bulk ) formulae which relate the flux to
101      !!       the properties of the surface and of the lower atmosphere. Here, we
102      !!       follow the work of Oberhuber, 1988   
103      !!
104      !!  ** Action  :   call flx_blk_albedo to compute ocean and ice albedo
105      !!          computation of snow precipitation
106      !!          computation of solar flux at the ocean and ice surfaces
107      !!          computation of the long-wave radiation for the ocean and sea/ice
108      !!          computation of turbulent heat fluxes over water and ice
109      !!          computation of evaporation over water
110      !!          computation of total heat fluxes sensitivity over ice (dQ/dT)
111      !!          computation of latent heat flux sensitivity over ice (dQla/dT)
112      !!
113      !! History :
114      !!   8.0  !  97-06  (Louvain-La-Neuve)  Original code
115      !!   8.5  !  02-09  (C. Ethe , G. Madec )  F90: Free form and module
116      !!----------------------------------------------------------------------
117      !! * Arguments
118      INTEGER , INTENT( in  )  ::   kt        ! time step
119      REAL(wp), INTENT( in ), DIMENSION(jpi,jpj) ::   &
120         &                          psst      ! Sea Surface Temperature
121
122      !! * Local variables
123      INTEGER  ::             &
124         ji, jj, jt        ,  &  ! dummy loop indices
125         indaet            ,  &  !  = -1, 0, 1 for odd, normal and leap years resp.
126         iday              ,  &  ! integer part of day
127         indxb             ,  &  ! index for budyko coefficient
128         indxc                   ! index for cloud depth coefficient
129
130      REAL(wp)  ::            & 
131         zalat , zclat     ,  &  ! latitude in degrees
132         zmt1, zmt2, zmt3  ,  &  ! tempory air temperatures variables
133         ztatm3, ztatm4    ,  &  ! power 3 and 4 of air temperature
134         z4tatm3           ,  &  ! 4 * ztatm3
135         zcmue             ,  &  ! cosine of local solar altitude
136         zcmue2            ,  &  ! root of zcmue1
137         zscmue            ,  &  ! square-root of zcmue1
138         zpcmue            ,  &  ! zcmue1**1.4
139         zdecl             ,  &  ! solar declination
140         zsdecl , zcdecl   ,  &  ! sine and cosine of solar declination
141         zalbo             ,  &  ! albedo of sea-water
142         zalbi             ,  &  ! albedo of ice
143         ztamr             ,  &  ! air temperature minus triple point of water (rtt)
144         ztaevbk           ,  &  ! part of net longwave radiation
145         zevi , zevo       ,  &  ! vapour pressure of ice and ocean
146         zind1,zind2,zind3 ,  &  ! switch for testing the values of air temperature
147         zinda             ,  &  ! switch for testing the values of sea ice cover
148         zpis2             ,  &  ! pi / 2
149         z2pi                    ! 2 * pi
150
151      REAL(wp)  ::            & 
152         zxday             ,  &  ! day of year
153         ztsec             ,  &  ! time in seconds
154         zdist             ,  &  ! distance between the sun and the earth during the year
155         zdaycor           ,  &  ! corr. factor to take into account the variation of
156         !                       ! zday when calc. the solar rad.   
157         zesi, zeso        ,  &  ! vapour pressure of ice and ocean at saturation
158         zesi2             ,  &  ! root of zesi
159         zqsato            ,  &  ! humidity close to the ocean surface (at saturation)   
160         zqsati            ,  &  ! humidity close to the ice surface (at saturation)
161         zqsati2           ,  &  ! root of  zqsati
162         zdesidt           ,  &  ! derivative of zesi, function of ice temperature
163         zdteta            ,  &  ! diff. betw. sst and air temperature
164         zdeltaq           ,  &  ! diff. betw. spec. hum. and hum. close to the surface
165         ztvmoy, zobouks   ,  &  ! tempory scalars
166         zpsims, zpsihs, zpsils, zobouku, zxins, zpsimu ,  & 
167         zpsihu, zpsilu, zstab,zpsim, zpsih, zpsil      ,  & 
168         zvatmg, zcmn, zchn, zcln, zcmcmn, zdenum       ,  & 
169         zdtetar, ztvmoyr, zlxins, zcmn2, zchcm, zclcm , zcoef
170
171      REAL(wp)  ::            & 
172         zrhova            ,  &  ! air density per wind speed
173         zcsho , zcleo     ,  &  ! transfer coefficient over ocean
174         zcshi , zclei     ,  &  ! transfer coefficient over ice-free
175         zrhovacleo        ,  &  ! air density per wind speed per transfer coef.
176         zrhovacsho, zrhovaclei, zrhovacshi, & 
177         ztice3            ,  &  ! power 3 of ice temperature
178         zticemb, zticemb2 ,  &  ! tempory air temperatures variables
179         zdqlw_ice         ,  &  ! sensitivity of long-wave flux over ice
180         zdqsb_ice         ,  &  ! sensitivity of sensible heat flux over ice
181         zdqla_ice         ,  &  ! sensitivity of latent heat flux over ice
182         zdl, zdr                ! fractionnal part of latitude
183      REAL(wp), DIMENSION(jpi,jpj) :: & 
184         zpatm            ,  &   ! atmospheric pressure
185         zqatm            ,  &   ! specific humidity
186         zes              ,  &   ! vapour pressure at saturation
187         zev, zevsqr      ,  &   ! vapour pressure and his square-root
188         zrhoa            ,  &   ! air density
189         ztatm            ,  &   ! air temperature in Kelvins
190         zfrld            ,  &   ! fraction of sea ice cover
191         zcatm1           ,  &   ! fraction of cloud
192         zcldeff                 ! correction factor to account cloud effect
193      REAL(wp), DIMENSION(jpi,jpj) ::   & 
194         zalbocsd         ,  &   ! albedo of ocean
195         zalboos          ,  &   ! albedo of ocean under overcast sky
196         zalbics          ,  &   ! albedo of ice under clear sky
197         zalbios          ,  &   ! albedo of ice under overcast sky
198         zalbomu          ,  &   ! albedo of ocean when zcmue is 0.4
199         zqsro            ,  &   ! solar radiation over ocean
200         zqsrics          ,  &   ! solar radiation over ice under clear sky
201         zqsrios          ,  &   ! solar radiation over ice under overcast sky
202         zcldcor          ,  &   ! cloud correction
203         zlsrise, zlsset  ,  &   ! sunrise and sunset
204         zlmunoon         ,  &   ! local noon solar altitude
205         zdlha            ,  &   ! length of the ninstr segments of the solar day
206         zps              ,  &   ! sine of latitude per sine of solar decli.
207         zpc                     ! cosine of latitude per cosine of solar decli.
208
209      REAL(wp), DIMENSION(jpi,jpj) ::   & 
210         zqlw_oce         ,  &   ! long-wave heat flux over ocean
211         zqlw_ice         ,  &   ! long-wave heat flux over ice
212         zqla_oce         ,  &   ! latent heat flux over ocean
213         zqla_ice         ,  &   ! latent heat flux over ice
214         zqsb_oce         ,  &   ! sensible heat flux over ocean
215         zqsb_ice                ! sensible heat flux over ice
216 
217      REAL(wp), DIMENSION(jpi,jpj,jpintsr) ::    &
218         zlha             ,  &   ! local hour angle
219         zalbocs          ,  &   ! tempory var. of ocean albedo under clear sky
220         zsqsro           ,  &   ! tempory var. of solar rad. over ocean
221         zsqsrics         ,  &   ! temp. var. of solar rad. over ice under clear sky
222         zsqsrios                ! temp. var. of solar rad. over ice under overcast sky
223      !!---------------------------------------------------------------------
224
225      !---------------------
226      !   Initilization    !
227      !---------------------
228#if ! defined key_ice_lim
229      tn_ice(:,:) = psst(:,:)
230#endif
231
232      !  Determine cloud optical depths as a function of latitude (Chou et al., 1981).
233      !  and the correction factor for taking into account  the effect of clouds
234      !------------------------------------------------------
235      IF( lbulk_init ) THEN
236         DO jj = 1, jpj 
237            DO ji = 1 , jpi
238            zalat          = ( 90.0 - ABS( gphit(ji,jj) ) ) / 5.0
239            zclat          = ( 95.0 -      gphit(ji,jj)   ) / 10.0
240            indxb          = 1 + INT( zalat ) 
241            !  correction factor to account for the effect of clouds
242            sbudyko(ji,jj) = budyko(indxb) 
243            indxc          = 1 + INT( zclat ) 
244            zdl            = zclat - INT( zclat ) 
245            zdr            = 1.0 - zdl
246            stauc(ji,jj)   = zdr * tauco( indxc ) + zdl * tauco( indxc + 1 ) 
247            END DO
248         END DO
249         IF( nleapy == 1 ) THEN
250            yearday = 366.0
251         ELSE IF( nleapy == 0 ) THEN
252            yearday = 365.0
253         ELSEIF( nleapy == 30) THEN
254            yearday = 360.0
255         ENDIF
256         lbulk_init = .FALSE.
257      ENDIF
258
259      zqlw_oce(:,:) = 0.e0
260      zqla_oce(:,:) = 0.e0
261      zqsb_oce(:,:) = 0.e0
262      zqlw_ice(:,:) = 0.e0
263      zqla_ice(:,:) = 0.e0
264      zqsb_ice(:,:) = 0.e0
265
266      zpis2       = rpi / 2.              ! pi / 2
267      z2pi        = 2. * rpi              ! 2 * pi
268
269 !CDIR NOVERRCHK
270     DO jj = 1, jpj
271 !CDIR NOVERRCHK
272        DO ji = 1, jpi
273
274      ztatm (ji,jj) = 273.15 + tatm  (ji,jj)  !  air temperature in Kelvins
275      zcatm1(ji,jj) = 1.0    - catm  (ji,jj)  !  fractional cloud cover
276      zfrld (ji,jj) = 1.0    - freeze(ji,jj)  !  fractional sea ice cover
277      zpatm(ji,jj)  = 101000.               !  pressure
278     
279      !  Computation of air density, obtained from the equation of state for dry air.
280      zrhoa(ji,jj) = zpatm(ji,jj) / ( 287.04 * ztatm(ji,jj) )
281     
282      !  zes : Saturation water vapour
283            ztamr = ztatm(ji,jj) - rtt
284            zmt1  = SIGN( 17.269, ztamr )
285            zmt2  = SIGN( 21.875, ztamr )
286            zmt3  = SIGN( 28.200, -ztamr )
287            zes(ji,jj) = 611.0 * EXP (  ABS( ztamr ) * MIN ( zmt1, zmt2 )   &
288               &                      / ( ztatm(ji,jj) - 35.86  + MAX( zzero, zmt3 ) ) )
289
290      !  zev : vapour pressure  (hatm is relative humidity) 
291      zev(ji,jj)   = hatm(ji,jj) * zes(ji,jj) 
292      !  square-root of vapour pressure
293!CDIR NOVERRCHK
294      zevsqr(ji,jj) = SQRT( zev(ji,jj) * 0.01 )
295      !  zqapb  : specific humidity
296      zqatm(ji,jj) = 0.622 * zev(ji,jj) / ( zpatm(ji,jj) - 0.378 * zev(ji,jj) )
297
298
299      !----------------------------------------------------
300      !   Computation of snow precipitation (Ledley, 1985) |
301      !----------------------------------------------------
302
303            zmt1  =   253.0 - ztatm(ji,jj)
304            zmt2  = ( 272.0 - ztatm(ji,jj) ) / 38.0 
305            zmt3  = ( 281.0 - ztatm(ji,jj) ) / 18.0
306            zind1 = MAX( zzero, SIGN( zone, zmt1 ) )
307            zind2 = MAX( zzero, SIGN( zone, zmt2 ) )
308            zind3 = MAX( zzero, SIGN( zone, zmt3 ) )
309            ! total precipitation
310            tprecip(ji,jj) = watm(ji,jj)
311            ! solid  (snow) precipitation
312            sprecip(ji,jj) = tprecip(ji,jj) *       &
313               &             (           zind1      &
314               &               + ( 1.0 - zind1 ) * ( zind2 * ( 0.5 + zmt2 ) + ( 1.0 - zind2 ) *  zind3 * zmt3 ) ) 
315         END DO
316      END DO
317
318      !----------------------------------------------------------
319      !   Computation of albedo (need to calculates heat fluxes)|
320      !-----------------------------------------------------------
321     
322      CALL flx_blk_albedo( zalbios, zalboos, zalbics, zalbomu )
323
324      !-------------------------------------
325      !   Computation of solar irradiance. |
326      !----------------------------------------
327      indaet   = 1 
328      !  compution of the day of the year at which the fluxes have to be calculate
329      !--The date corresponds to the middle of the time step.
330      ztsec = ( 2 * INT ( ( kt - 1 ) / nfbulk ) + 1 ) * rdtbs2
331      zxday = MOD( ztsec , raass ) / rday + 1.0 
332
333      iday   = INT( zxday )
334      IF( l_ctl .AND. lwp ) WRITE(numout,*) ' declin : iday ', iday, ' nfbulk= ', nfbulk
335      !   computation of the solar declination, his sine and his cosine
336      CALL flx_blk_declin( indaet, iday, zdecl )
337     
338      zdecl    = zdecl * rad
339      zsdecl   = SIN( zdecl )
340      zcdecl   = COS( zdecl )
341     
342      !  correction factor added for computation of shortwave flux to take into account the variation of
343      !  the distance between the sun and the earth during the year (Oberhuber 1988)
344      zdist    = zxday * z2pi / yearday
345      zdaycor  = 1.0 + 0.0013 * SIN( zdist ) + 0.0342 * COS( zdist )
346
347!CDIR NOVERRCHK
348      DO jj = 1, jpj
349!CDIR NOVERRCHK
350         DO ji = 1, jpi
351            !  product of sine of latitude and sine of solar declination
352            zps(ji,jj)     = SIN( gphit(ji,jj) * rad ) * zsdecl
353            !  product of cosine of latitude and cosine of solar declination
354            zpc(ji,jj)     = COS( gphit(ji,jj) * rad ) * zcdecl
355            !  computation of the both local time of sunrise and sunset
356            zlsrise(ji,jj) =  ACOS( - SIGN( zone, zps(ji,jj) ) * MIN( zone, SIGN( zone, zps(ji,jj) )  &
357               &                     * ( zps(ji,jj) / zpc(ji,jj) ) ) ) 
358            zlsset(ji,jj)  = - zlsrise(ji,jj)
359            !  dividing the solar day into jpintsr segments of length zdlha
360            zdlha(ji,jj)   =  ( zlsrise(ji,jj) - zlsset(ji,jj) ) / REAL( jpintsr )
361            !  computation of the local noon solar altitude
362            zlmunoon(ji,jj)=  ASIN ( ( zps(ji,jj) + zpc(ji,jj) ) ) / rad
363           
364            !  cloud correction taken from Reed (1977) (imposed lower than 1)
365            zcldcor(ji,jj) = MIN( zone, ( 1 - 0.62 * catm(ji,jj) + 0.0019 * zlmunoon(ji,jj) ) )
366         END DO
367      END DO
368
369         !  Computation of solar heat flux at each time of the day between sunrise and sunset.
370         !  We do this to a better optimisation of the code
371         !------------------------------------------------------       
372
373!CDIR NOVERRCHK   
374      DO jt = 1, jpintsr   
375         zcoef = FLOAT( jt ) - 0.5
376!CDIR NOVERRCHK     
377         DO jj = 1, jpj
378!CDIR NOVERRCHK
379            DO ji = 1, jpi
380               !  local hour angle
381               zlha (ji,jj,jt)= COS ( zlsrise(ji,jj) - zcoef * zdlha(ji,jj) )
382
383               ! cosine of local solar altitude
384               zcmue              = MAX ( zzero ,   zps(ji,jj) + zpc(ji,jj) * zlha (ji,jj,jt)  )
385               zcmue2             = 1368.0 * zcmue * zcmue
386               zscmue             = SQRT ( zcmue )
387               zpcmue             = zcmue**1.4
388               ! computation of sea-water albedo (Payne, 1972)
389               zalbocs(ji,jj,jt)  = 0.05 / ( 1.1 * zpcmue + 0.15 )
390               zalbo              = zcatm1(ji,jj) * zalbocs(ji,jj,jt) + catm(ji,jj) * zalboos(ji,jj)
391               ! solar heat flux absorbed at ocean surfaces (Zillman, 1972)
392               zevo               = zev(ji,jj) * 1.0e-05
393               zsqsro(ji,jj,jt)   =  ( 1.0 - zalbo ) * zdlha(ji,jj) * zcmue2                &
394                                   / ( ( zcmue + 2.7 ) * zevo + 1.085 * zcmue +  0.10 )
395               !  solar heat flux absorbed at sea/ice surfaces
396               !  Formulation of Shine and Crane, 1984 adapted for high albedo surfaces
397
398               !  For clear sky       
399               zevi               = zevo
400               zalbi              = zalbics(ji,jj)
401               zsqsrics(ji,jj,jt) =  ( 1.0 - zalbi ) * zdlha(ji,jj) * zcmue2                &
402                  &                / ( ( 1.0 + zcmue ) * zevi + 1.2 * zcmue + 0.0455 )
403
404               ! For overcast sky
405               zalbi              = zalbios(ji,jj)
406               zsqsrios(ji,jj,jt) = zdlha(ji,jj) *                                                           &
407                  &                 ( ( 53.5 + 1274.5 * zcmue      ) *  zscmue * ( 1.0 - 0.996  * zalbi ) )  &
408                  &                 / (  1.0 + 0.139  * stauc(ji,jj) *           ( 1.0 - 0.9435 * zalbi ) )
409            END DO
410         END DO
411      END DO
412
413
414      !  Computation of daily (between sunrise and sunset) solar heat flux absorbed
415      !  at the ocean and snow/ice surfaces.
416      !--------------------------------------------------------------------
417
418      zalbocsd(:,:) = 0. 
419      zqsro   (:,:) = 0.
420      zqsrics (:,:) = 0.
421      zqsrios (:,:) = 0.
422
423      DO jt = 1, jpintsr 
424#   if defined key_vectopt_loop && ! defined key_autotasking
425         DO ji = 1, jpij 
426            zalbocsd(ji,1)  = zalbocsd(ji,1) + zdlha(ji,1) * zalbocs(ji,1,jt)   &
427               &             / MAX( 2.0 * zlsrise(ji,1) , zeps0 )
428            zqsro   (ji,1)  =   zqsro(ji,1) + zsqsro  (ji,1,jt)
429            zqsrics (ji,1)  = zqsrics(ji,1) + zsqsrics(ji,1,jt)
430            zqsrios (ji,1)  = zqsrios(ji,1) + zsqsrios(ji,1,jt)
431         END DO
432#  else
433         DO jj = 1, jpj
434            DO ji = 1, jpi 
435               zalbocsd(ji,jj)  = zalbocsd(ji,jj) + zdlha(ji,jj) * zalbocs(ji,jj,jt)   &
436                  &             / MAX( 2.0 * zlsrise(ji,jj) , zeps0 )
437               zqsro  (ji,jj)   =   zqsro(ji,jj) + zsqsro  (ji,jj,jt)
438               zqsrics(ji,jj)   = zqsrics(ji,jj) + zsqsrics(ji,jj,jt)
439               zqsrios(ji,jj)   = zqsrios(ji,jj) + zsqsrios(ji,jj,jt)
440            END DO
441         END DO
442#  endif
443      END DO
444
445      DO jj = 1, jpj
446         DO ji = 1, jpi 
447
448      !-------------------------------------------
449      !  Computation of shortwave radiation.
450      !-------------------------------------------
451
452            ! the solar heat flux absorbed at ocean and snow/ice surfaces
453            !------------------------------------------------------------
454
455            ! For ocean
456            qsr_oce(ji,jj) = srgamma * zcldcor(ji,jj) * zqsro(ji,jj) / z2pi
457            zinda          = SIGN( zone , -( -0.5 - zfrld(ji,jj) ) )
458            zinda          = 1.0 - MAX( zzero , zinda )
459            qsr_oce(ji,jj) = ( 1.- zinda ) * qsr_oce(ji,jj)
460
461            ! For snow/ice
462            qsr_ice(ji,jj) = ( zcatm1(ji,jj) * zqsrics(ji,jj) + catm(ji,jj) * zqsrios(ji,jj) ) / z2pi
463
464
465            ! Taking into account the ellipsity of the earth orbit
466            !-----------------------------------------------------
467
468            qsr_ice(ji,jj) = qsr_ice(ji,jj) * zdaycor
469            qsr_oce(ji,jj) = qsr_oce(ji,jj) * zdaycor
470
471            !  fraction of net shortwave radiation which is not absorbed in the
472            !  thin surface layer and penetrates inside the ice cover
473            !  ( Maykut and Untersteiner, 1971 ; Elbert anbd Curry, 1993 )
474            !------------------------------------------------------------------
475
476            fr1_i0(ji,jj) = 0.18  * zcatm1(ji,jj) + 0.35 * catm(ji,jj) 
477            fr2_i0(ji,jj) = 0.82  * zcatm1(ji,jj) + 0.65 * catm(ji,jj)
478
479      !---------------------------------------------------------------------------
480      !   Computation of long-wave radiation  ( Berliand 1952 ; all latitudes )
481      !---------------------------------------------------------------------------
482
483            ! tempory variables
484            ztatm3         = ztatm(ji,jj) * ztatm(ji,jj) * ztatm(ji,jj)
485            ztatm4         = ztatm3 * ztatm(ji,jj)
486            z4tatm3        = 4. * ztatm3
487            zcldeff(ji,jj) = 1.0 - sbudyko(ji,jj) * catm(ji,jj) * catm(ji,jj)   
488            ztaevbk        = ztatm4 * zcldeff(ji,jj) * ( 0.39 - 0.05 * zevsqr(ji,jj) ) 
489
490            !  Long-Wave for Ice
491            !----------------------
492            zqlw_ice(ji,jj) = - emic * stefan * ( ztaevbk + z4tatm3 * ( tn_ice(ji,jj) - ztatm(ji,jj) ) ) 
493
494            !  Long-Wave for Ocean
495            !-----------------------
496            zqlw_oce(ji,jj) = - emic * stefan * ( ztaevbk + z4tatm3 * ( psst  (ji,jj) - ztatm(ji,jj) ) ) 
497
498         END DO
499      END DO
500
501      !----------------------------------------
502      !  Computation of turbulent heat fluxes  ( Latent and sensible )
503      !----------------------------------------       
504      !CDIR NOVERRCHK
505      DO jj = 2 , jpjm1
506!ib   DO jj = 1 , jpj
507         !CDIR NOVERRCHK
508         DO  ji = 1, jpi
509
510            !  Turbulent heat fluxes over water
511            !----------------------------------
512
513            ! zeso     : vapour pressure at saturation of ocean
514            ! zqsato   : humidity close to the ocean surface (at saturation)
515            zeso          =  611.0 * EXP ( 17.2693884 * ( psst(ji,jj) - rtt ) * tmask(ji,jj,1) / ( psst(ji,jj) - 35.86 ) )
516            zqsato        = ( 0.622 * zeso ) / ( zpatm(ji,jj) - 0.378 * zeso )
517
518            !  Drag coefficients from Large and Pond (1981,1982)
519            !---------------------------------------------------
520   
521            !  Stability parameters
522            zdteta         = psst(ji,jj) - ztatm(ji,jj)
523            zdeltaq        = zqatm(ji,jj) - zqsato
524            ztvmoy         = ztatm(ji,jj) * ( 1. + 2.2e-3 * ztatm(ji,jj) * zqatm(ji,jj) )
525            zdenum         = MAX( vatm(ji,jj) * vatm(ji,jj) * ztvmoy, zeps )
526!i
527!i          if( zdenum == 0.e0 ) then
528!i               write(numout,*) 'flxblk  zdenum=0 ', ji,jj
529!i               zdenum = zeps
530!i          endif
531!i
532            zdtetar        = zdteta / zdenum
533            ztvmoyr        = ztvmoy * ztvmoy * zdeltaq / zdenum
534           
535            ! For stable atmospheric conditions
536            zobouks        = -70.0 * 10. * ( zdtetar + 3.2e-3 * ztvmoyr )
537            zobouks        = MAX( zzero , zobouks )
538            zpsims         = -7.0 * zobouks
539            zpsihs         =  zpsims
540            zpsils         =  zpsims
541
542            !  For unstable atmospheric conditions
543            zobouku        = -100.0 * 10.0 * ( zdtetar + 2.2e-3 * ztvmoyr )
544            zobouku        = MIN( zzero , zobouku )
545            zxins          = ( 1. - 16. * zobouku )**0.25
546            zlxins         = LOG( ( 1. + zxins * zxins ) / 2. )
547            zpsimu         = 2. * LOG( ( 1 + zxins ) / 2. )  + zlxins - 2. * ATAN( zxins ) + zpis2
548            zpsihu         = 2. * zlxins
549            zpsilu         = zpsihu
550
551            ! computation of intermediate values
552            zstab          = MAX( zzero , SIGN( zone , zdteta ) )
553            zpsim          = zstab * zpsimu + (1.0 - zstab ) * zpsims
554            zpsih          = zstab * zpsihu + (1.0 - zstab ) * zpsihs
555            zpsil          = zpsih
556           
557            zvatmg         = MAX( 0.032 * 1.5e-3 * vatm(ji,jj) * vatm(ji,jj) / g, zeps )
558!i
559!!          if( zvatmg == 0.e0 ) then
560!!               write(numout,*) 'flxblk  zvatmg=0 ', ji,jj
561!!               zvatmg = zeps
562!!          endif
563!i
564
565            zcmn           = vkarmn / LOG ( 10. / zvatmg )
566            zcmn2          = zcmn * zcmn
567            zchn           = 0.0327 * zcmn
568            zcln           = 0.0346 * zcmn
569            zcmcmn         = 1 / ( 1 - zcmn * zpsim / vkarmn )
570            zchcm          = zcmcmn / ( 1 - zchn * zpsih / ( vkarmn * zcmn ) )
571            zclcm          = zchcm
572
573
574            !  Transfer cofficient zcsho and zcleo over ocean according to Large and Pond (1981,1982)
575            !--------------------------------------------------------------
576            zcsho          = zchn * zchcm
577            zcleo          = zcln * zclcm 
578
579
580            !   Computation of sensible and latent fluxes over Ocean
581            !----------------------------------------------------------------
582
583            !  computation of intermediate values
584            zrhova         = zrhoa(ji,jj) * vatm(ji,jj)
585            zrhovacsho     = zrhova * zcsho
586            zrhovacleo     = zrhova * zcleo
587
588            ! sensible heat flux
589            zqsb_oce(ji,jj) = zrhovacsho * 1004.0  * ( psst(ji,jj) - ztatm(ji,jj) ) 
590         
591            !  latent heat flux
592            zqla_oce(ji,jj) = zrhovacleo * 2.5e+06 * ( zqsato      - zqatm(ji,jj) )
593               
594            !  Calculate evaporation over water. (kg/m2/s)
595            !-------------------------------------------------
596            evap(ji,jj)    = zqla_oce(ji,jj) / cevap
597               
598               
599            !  Turbulent heat fluxes over snow/ice.
600            !--------------------------------------------------
601           
602            !  zesi     : vapour pressure at saturation of ice
603            !  zqsati   : humidity close to the ice surface (at saturation)
604            zesi           =  611.0 * EXP ( 21.8745587 * tmask(ji,jj,1)   &   ! tmask needed to avoid overflow in the exponential
605               &                                       * ( tn_ice(ji,jj) - rtt ) / ( tn_ice(ji,jj) - 7.66 ) )
606            zqsati         = ( 0.622 * zesi ) / ( zpatm(ji,jj) - 0.378 * zesi )
607               
608            !  computation of intermediate values
609            zticemb        = ( tn_ice(ji,jj) - 7.66 )
610            zticemb2       = zticemb * zticemb 
611            ztice3         = tn_ice(ji,jj) * tn_ice(ji,jj) * tn_ice(ji,jj)
612            zqsati2        = zqsati * zqsati
613            zesi2          = zesi * zesi
614            zdesidt        = zesi * ( 9.5 * LOG( 10.0 ) * ( rtt - 7.66 )  / zticemb2 )
615               
616            !  Transfer cofficient zcshi and zclei over ice. Assumed to be constant Parkinson 1979 ; Maykut 1982
617            !--------------------------------------------------------------------
618            zcshi          = 1.75e-03
619            zclei          = zcshi
620               
621            !  Computation of sensible and latent fluxes over ice
622            !----------------------------------------------------------------
623               
624            !  computation of intermediate values
625            zrhova          = zrhoa(ji,jj) * vatm(ji,jj)
626            zrhovacshi      = zrhova * zcshi * 2.834e+06
627            zrhovaclei      = zrhova * zclei * 1004.0
628           
629            !  sensible heat flux
630            zqsb_ice(ji,jj) = zrhovaclei * ( tn_ice(ji,jj) - ztatm(ji,jj) )
631           
632            !  latent heat flux
633            zqla_ice(ji,jj) = zrhovacshi * ( zqsati        - zqatm(ji,jj) )
634             qla_ice(ji,jj) = zqla_ice(ji,jj)
635             
636            !  Computation of sensitivity of non solar fluxes (dQ/dT)
637            !---------------------------------------------------------------
638               
639            !  computation of long-wave, sensible and latent flux sensitivity
640            zdqlw_ice       = 4.0 * emic * stefan * ztice3
641            zdqsb_ice       = zrhovaclei
642            zdqla_ice       = zrhovacshi * ( zdesidt * ( zqsati2 / zesi2 ) * ( zpatm(ji,jj) / 0.622 ) )         
643           
644            !  total non solar sensitivity
645            dqns_ice(ji,jj) = -( zdqlw_ice + zdqsb_ice + zdqla_ice ) 
646           
647            ! latent flux sensitivity
648            dqla_ice(ji,jj) = zdqla_ice
649           
650         END DO
651      END DO
652
653      ! total non solar heat flux over ice
654      qnsr_ice(:,:) = zqlw_ice(:,:) - zqsb_ice(:,:) - zqla_ice(:,:)
655      ! total non solar heat flux over water
656      qnsr_oce(:,:) = zqlw_oce(:,:) - zqsb_oce(:,:) - zqla_oce(:,:)
657
658      ! solid precipitations ( kg/m2/day -> kg/m2/s)
659      tprecip(:,:) = tprecip  (:,:) / rday 
660      ! snow  precipitations ( kg/m2/day -> kg/m2/s)
661      sprecip(:,:) = sprecip  (:,:) / rday 
662!i
663      CALL lbc_lnk( qsr_oce (:,:) , 'T', 1. )
664      CALL lbc_lnk( qnsr_oce(:,:) , 'T', 1. )
665      CALL lbc_lnk( qsr_ice (:,:) , 'T', 1. )
666      CALL lbc_lnk( qnsr_ice(:,:) , 'T', 1. )
667      CALL lbc_lnk( qla_ice (:,:) , 'T', 1. )
668      CALL lbc_lnk( dqns_ice(:,:) , 'T', 1. )
669      CALL lbc_lnk( dqla_ice(:,:) , 'T', 1. )
670      CALL lbc_lnk( fr1_i0  (:,:) , 'T', 1. )
671      CALL lbc_lnk( fr2_i0  (:,:) , 'T', 1. )
672      CALL lbc_lnk( tprecip (:,:) , 'T', 1. )
673      CALL lbc_lnk( sprecip (:,:) , 'T', 1. )
674      CALL lbc_lnk( evap    (:,:) , 'T', 1. )
675!i
676!i
677      qsr_oce (:,:) = qsr_oce (:,:)*tmask(:,:,1)
678      qnsr_oce(:,:) = qnsr_oce(:,:)*tmask(:,:,1)
679      qsr_ice (:,:) = qsr_ice (:,:)*tmask(:,:,1)
680      qnsr_ice(:,:) = qnsr_ice(:,:)*tmask(:,:,1)
681      qla_ice (:,:) = qla_ice (:,:)*tmask(:,:,1)
682      dqns_ice(:,:) = dqns_ice(:,:)*tmask(:,:,1)
683      dqla_ice(:,:) = dqla_ice(:,:)*tmask(:,:,1)
684      fr1_i0  (:,:) = fr1_i0  (:,:)*tmask(:,:,1)
685      fr2_i0  (:,:) = fr2_i0  (:,:)*tmask(:,:,1)
686      tprecip (:,:) = tprecip (:,:)*tmask(:,:,1)
687      sprecip (:,:) = sprecip (:,:)*tmask(:,:,1)
688      evap    (:,:) = evap    (:,:)*tmask(:,:,1)
689!i
690
691   END SUBROUTINE flx_blk
692
693
694#if defined key_ice_lim
695   !!----------------------------------------------------------------------
696   !!   'key_ice_lim'                                         LIM ice model
697   !!----------------------------------------------------------------------
698
699   SUBROUTINE flx_blk_albedo( palb , palcn , palbp , palcnp )
700      !!----------------------------------------------------------------------
701      !!               ***  ROUTINE flx_blk_albedo  ***
702      !!         
703      !! ** Purpose :   Computation of the albedo of the snow/ice system
704      !!      as well as the ocean one
705      !!       
706      !! ** Method  : - Computation of the albedo of snow or ice (choose the
707      !!      rignt one by a large number of tests
708      !!              - Computation of the albedo of the ocean
709      !!
710      !! References :
711      !!      Shine and Hendersson-Sellers 1985, JGR, 90(D1), 2243-2250.
712      !!
713      !! History :
714      !!  8.0   !  01-04  (LIM 1.0)
715      !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine)
716      !!----------------------------------------------------------------------
717      !! * Modules used
718      USE ice                   ! ???
719
720      !! * Arguments
721      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  &
722         palb         ,     &    !  albedo of ice under overcast sky
723         palcn        ,     &    !  albedo of ocean under overcast sky
724         palbp        ,     &    !  albedo of ice under clear sky
725         palcnp                  !  albedo of ocean under clear sky
726
727      !! * Local variables
728      INTEGER ::    &
729         ji, jj                   ! dummy loop indices
730      REAL(wp) ::   & 
731         zmue14         ,     &   !  zmue**1.4
732         zalbpsnm       ,     &   !  albedo of ice under clear sky when snow is melting
733         zalbpsnf       ,     &   !  albedo of ice under clear sky when snow is freezing
734         zalbpsn        ,     &   !  albedo of snow/ice system when ice is coverd by snow
735         zalbpic        ,     &   !  albedo of snow/ice system when ice is free of snow
736         zithsn         ,     &   !  = 1 for hsn >= 0 ( ice is cov. by snow ) ; = 0 otherwise (ice is free of snow)
737         zitmlsn        ,     &   !  = 1 freezinz snow (sist >=rt0_snow) ; = 0 melting snow (sist<rt0_snow)
738         zihsc1         ,     &   !  = 1 hsn <= c1 ; = 0 hsn > c1
739         zihsc2                   !  = 1 hsn >= c2 ; = 0 hsn < c2
740      REAL(wp), DIMENSION(jpi,jpj) ::  &
741         zalbfz         ,     &   !  ( = alphdi for freezing ice ; = albice for melting ice )
742         zficeth                  !  function of ice thickness
743      LOGICAL , DIMENSION(jpi,jpj) ::  &
744         llmask
745      !!---------------------------------------------------------------------
746     
747      !-------------------------                                                             
748      !  Computation of  zficeth
749      !--------------------------
750     
751      llmask = (hsnif == 0.0) .AND. ( sist >= rt0_ice )
752      WHERE ( llmask )   !  ice free of snow and melts
753         zalbfz = albice
754      ELSEWHERE                   
755         zalbfz = alphdi
756      END WHERE
757     
758      DO jj = 1, jpj
759         DO ji = 1, jpi
760            IF( hicif(ji,jj) > 1.5 ) THEN
761               zficeth(ji,jj) = zalbfz(ji,jj)
762            ELSEIF( hicif(ji,jj) > 1.0  .AND. hicif(ji,jj) <= 1.5 ) THEN
763               zficeth(ji,jj) = 0.472 + 2.0 * ( zalbfz(ji,jj) - 0.472 ) * ( hicif(ji,jj) - 1.0 )
764            ELSEIF( hicif(ji,jj) > 0.05 .AND. hicif(ji,jj) <= 1.0 ) THEN
765               zficeth(ji,jj) = 0.2467 + 0.7049 * hicif(ji,jj)                                &
766                  &                    - 0.8608 * hicif(ji,jj) * hicif(ji,jj)                 &
767                  &                    + 0.3812 * hicif(ji,jj) * hicif(ji,jj) * hicif (ji,jj)
768            ELSE
769               zficeth(ji,jj) = 0.1 + 3.6 * hicif(ji,jj) 
770            ENDIF
771         END DO
772      END DO
773     
774      !-----------------------------------------------
775      !    Computation of the snow/ice albedo system
776      !-------------------------- ---------------------
777     
778      !    Albedo of snow-ice for clear sky.
779      !-----------------------------------------------   
780      DO jj = 1, jpj
781         DO ji = 1, jpi
782            !  Case of ice covered by snow.             
783           
784            !  melting snow       
785            zihsc1       = 1.0 - MAX ( zzero , SIGN ( zone , - ( hsnif(ji,jj) - c1 ) ) )
786            zalbpsnm     = ( 1.0 - zihsc1 ) * ( zficeth(ji,jj) + hsnif(ji,jj) * ( alphd - zficeth(ji,jj) ) / c1 ) &
787               &                 + zihsc1   * alphd 
788            !  freezing snow               
789            zihsc2       = MAX ( zzero , SIGN ( zone , hsnif(ji,jj) - c2 ) )
790            zalbpsnf     = ( 1.0 - zihsc2 ) * ( albice + hsnif(ji,jj) * ( alphc - albice ) / c2 )                 &
791               &                 + zihsc2   * alphc 
792           
793            zitmlsn      =  MAX ( zzero , SIGN ( zone , sist(ji,jj) - rt0_snow ) )   
794            zalbpsn      =  zitmlsn * zalbpsnf + ( 1.0 - zitmlsn ) * zalbpsnm 
795           
796            !  Case of ice free of snow.
797            zalbpic      = zficeth(ji,jj) 
798           
799            ! albedo of the system   
800            zithsn       = 1.0 - MAX ( zzero , SIGN ( zone , - hsnif(ji,jj) ) )
801            palbp(ji,jj) =  zithsn * zalbpsn + ( 1.0 - zithsn ) *  zalbpic
802         END DO
803      END DO
804     
805      !    Albedo of snow-ice for overcast sky.
806      !---------------------------------------------- 
807      palb(:,:)   = palbp(:,:) + cgren                                           
808     
809      !--------------------------------------------
810      !    Computation of the albedo of the ocean
811      !-------------------------- -----------------                                                         
812     
813      !  Parameterization of Briegled and Ramanathan, 1982
814      zmue14      = zmue**1.4                                       
815      palcnp(:,:) = 0.05 / ( 1.1 * zmue14 + 0.15 )               
816     
817      !  Parameterization of Kondratyev, 1969 and Payne, 1972
818      palcn(:,:)  = 0.06                                                 
819     
820   END SUBROUTINE flx_blk_albedo
821
822# else
823   !!----------------------------------------------------------------------
824   !!   Default option :                                   NO sea-ice model
825   !!----------------------------------------------------------------------
826
827   SUBROUTINE flx_blk_albedo( palb , palcn , palbp , palcnp )
828      !!----------------------------------------------------------------------
829      !!               ***  ROUTINE flx_blk_albedo  ***
830      !!
831      !! ** Purpose :   Computation of the albedo of the snow/ice system
832      !!      as well as the ocean one
833      !!
834      !! ** Method  :   Computation of the albedo of snow or ice (choose the
835      !!      wright one by a large number of tests Computation of the albedo
836      !!      of the ocean
837      !!
838      !! History :
839      !!  8.0   !  01-04  (LIM 1.0)
840      !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine)
841      !!----------------------------------------------------------------------
842      !! * Arguments
843      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  &
844         palb         ,     &    !  albedo of ice under overcast sky
845         palcn        ,     &    !  albedo of ocean under overcast sky
846         palbp        ,     &    !  albedo of ice under clear sky
847         palcnp                  !  albedo of ocean under clear sky
848
849      REAL(wp) ::   &
850         zmue14                 !  zmue**1.4
851      !!----------------------------------------------------------------------
852
853      !--------------------------------------------
854      !    Computation of the albedo of the ocean
855      !-------------------------- -----------------
856
857      !  Parameterization of Briegled and Ramanathan, 1982
858      zmue14      = zmue**1.4
859      palcnp(:,:) = 0.05 / ( 1.1 * zmue14 + 0.15 )
860
861      !  Parameterization of Kondratyev, 1969 and Payne, 1972
862      palcn(:,:)  = 0.06
863
864      palb (:,:)  = palcn(:,:)
865      palbp(:,:)  = palcnp(:,:)
866
867   END SUBROUTINE flx_blk_albedo
868
869#endif
870
871   SUBROUTINE flx_blk_declin( ky, kday, pdecl )
872      !!---------------------------------------------------------------------------
873      !!               ***  ROUTINE flx_blk_declin  ***
874      !!         
875      !! ** Purpose :   Computation of the solar declination for the day
876      !!         kday ( in decimal degrees ).
877      !!       
878      !! ** Method  :
879      !!
880      !! History :
881      !!         original    : 01-04 (LIM)
882      !!         addition    : 02-08 (C. Ethe, G. Madec)
883      !!---------------------------------------------------------------------
884      !! * Arguments
885      INTEGER, INTENT( in ) ::   &
886         ky  ,        &  ! = -1, 0, 1 for odd, normal and leap years resp.
887         kday            ! day of the year ( kday = 1 on january 1)
888      REAL(wp), INTENT(out) ::  &
889         pdecl            ! solar declination
890
891      !! * Local variables
892      REAL(wp) ::                & 
893         zday                ,   &  ! corresponding day of type year (cf. ky)
894         zp1, zp2, zp3, zp4         ! temporary scalars
895      !!---------------------------------------------------------------------
896     
897      zday = FLOAT( kday ) 
898     
899      IF( ky == 1 )  THEN
900         zday = zday - 0.5
901      ELSEIF( ky == 3 )  THEN
902         zday = zday - 1.
903      ELSE
904         zday = REAL( kday )
905      ENDIF
906     
907      zp1 = rpi * ( 2.0 * zday - 367.0 ) / yearday
908      zp2 = 2. * zp1
909      zp3 = 3. * zp1
910      zp4 = 4. * zp1
911     
912      pdecl  = a0                                                                      &
913         &   + a1 * COS( zp1 ) + a2 * COS( zp2 ) + a3 * COS( zp3 ) + a4 * COS( zp4 )   &
914         &   + b1 * SIN( zp1 ) + b2 * SIN( zp2 ) + b3 * SIN( zp3 ) + b4 * SIN( zp4 )
915     
916   END SUBROUTINE flx_blk_declin
917
918#else
919   !!----------------------------------------------------------------------
920   !!   Default option :           Empty module                     NO bulk
921   !!----------------------------------------------------------------------
922CONTAINS
923   SUBROUTINE flx_blk            ! Empty routine
924   END SUBROUTINE flx_blk
925#endif
926
927   !!======================================================================
928END MODULE flxblk
Note: See TracBrowser for help on using the repository browser.