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

source: trunk/NEMO/OPA_SRC/SBC/albedo.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: 10.1 KB
Line 
1MODULE albedo
2   !!======================================================================
3   !!                       ***  MODULE  albedo  ***
4   !! Ocean forcing:  bulk thermohaline forcing of the ocean (or ice)
5   !!=====================================================================
6   !!----------------------------------------------------------------------
7   !!   flx_blk_albedo : albedo for ocean and ice (clear and overcast skies)
8   !!----------------------------------------------------------------------
9   !! * Modules used
10   USE oce             ! ocean dynamics and tracers
11   USE dom_oce         ! ocean space and time domain
12   USE cpl_oce         ! ???
13   USE phycst          ! physical constants
14   USE daymod
15   USE blk_oce         ! bulk variables
16   USE flx_oce         ! forcings variables
17   USE ocfzpt          ! ???
18   USE in_out_manager
19   USE lbclnk
20
21   IMPLICIT NONE
22   PRIVATE
23
24   !! * Accessibility
25   PUBLIC flx_blk_albedo ! routine called by limflx.F90 in coupled
26                         ! and in flxblk.F90 in forced
27   !! * Module variables
28   REAL(wp)  ::            &  ! constant values
29      zzero   = 0.e0    ,  &
30      zone    = 1.0
31
32   !! * constants for albedo computation (flx_blk_albedo)
33   REAL(wp) ::   &
34      c1     = 0.05  ,     &   ! constants values
35      c2     = 0.10  ,     &
36      albice = 0.50  ,     &   !  albedo of melting ice in the arctic and antarctic (Shine & Hendersson-Sellers)
37      cgren  = 0.06  ,     &   !  correction of the snow or ice albedo to take into account
38                               !  effects of cloudiness (Grenfell & Perovich, 1984)
39      alphd  = 0.80  ,     &   !  coefficients for linear interpolation used to compute
40      alphdi = 0.72  ,     &   !  albedo between two extremes values (Pyane, 1972)
41      alphc  = 0.65  ,     &
42      zmue   = 0.40            !  cosine of local solar altitude
43
44   !!----------------------------------------------------------------------
45   !!   OPA 9.0 , LODYC-IPSL  (2004)
46   !!----------------------------------------------------------------------
47
48CONTAINS
49
50#if defined key_ice_lim
51   !!----------------------------------------------------------------------
52   !!   'key_ice_lim'                                         LIM ice model
53   !!----------------------------------------------------------------------
54
55   SUBROUTINE flx_blk_albedo( palb , palcn , palbp , palcnp )
56      !!----------------------------------------------------------------------
57      !!               ***  ROUTINE flx_blk_albedo  ***
58      !!         
59      !! ** Purpose :   Computation of the albedo of the snow/ice system
60      !!      as well as the ocean one
61      !!       
62      !! ** Method  : - Computation of the albedo of snow or ice (choose the
63      !!      rignt one by a large number of tests
64      !!              - Computation of the albedo of the ocean
65      !!
66      !! References :
67      !!      Shine and Hendersson-Sellers 1985, JGR, 90(D1), 2243-2250.
68      !!
69      !! History :
70      !!  8.0   !  01-04  (LIM 1.0)
71      !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine)
72      !!----------------------------------------------------------------------
73      !! * Modules used
74      USE ice                   ! ???
75
76      !! * Arguments
77      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  &
78         palb         ,     &    !  albedo of ice under overcast sky
79         palcn        ,     &    !  albedo of ocean under overcast sky
80         palbp        ,     &    !  albedo of ice under clear sky
81         palcnp                  !  albedo of ocean under clear sky
82
83      !! * Local variables
84      INTEGER ::    &
85         ji, jj                   ! dummy loop indices
86      REAL(wp) ::   & 
87         zmue14         ,     &   !  zmue**1.4
88         zalbpsnm       ,     &   !  albedo of ice under clear sky when snow is melting
89         zalbpsnf       ,     &   !  albedo of ice under clear sky when snow is freezing
90         zalbpsn        ,     &   !  albedo of snow/ice system when ice is coverd by snow
91         zalbpic        ,     &   !  albedo of snow/ice system when ice is free of snow
92         zithsn         ,     &   !  = 1 for hsn >= 0 ( ice is cov. by snow ) ; = 0 otherwise (ice is free of snow)
93         zitmlsn        ,     &   !  = 1 freezinz snow (sist >=rt0_snow) ; = 0 melting snow (sist<rt0_snow)
94         zihsc1         ,     &   !  = 1 hsn <= c1 ; = 0 hsn > c1
95         zihsc2                   !  = 1 hsn >= c2 ; = 0 hsn < c2
96      REAL(wp), DIMENSION(jpi,jpj) ::  &
97         zalbfz         ,     &   !  ( = alphdi for freezing ice ; = albice for melting ice )
98         zficeth                  !  function of ice thickness
99      LOGICAL , DIMENSION(jpi,jpj) ::  &
100         llmask
101      !!---------------------------------------------------------------------
102     
103      !-------------------------                                                             
104      !  Computation of  zficeth
105      !--------------------------
106     
107      llmask = (hsnif == 0.e0) .AND. ( sist >= rt0_ice )
108      WHERE ( llmask )   !  ice free of snow and melts
109         zalbfz = albice
110      ELSEWHERE                   
111         zalbfz = alphdi
112      END WHERE
113     
114      DO jj = 1, jpj
115         DO ji = 1, jpi
116            IF( hicif(ji,jj) > 1.5 ) THEN
117               zficeth(ji,jj) = zalbfz(ji,jj)
118            ELSEIF( hicif(ji,jj) > 1.0  .AND. hicif(ji,jj) <= 1.5 ) THEN
119               zficeth(ji,jj) = 0.472 + 2.0 * ( zalbfz(ji,jj) - 0.472 ) * ( hicif(ji,jj) - 1.0 )
120            ELSEIF( hicif(ji,jj) > 0.05 .AND. hicif(ji,jj) <= 1.0 ) THEN
121               zficeth(ji,jj) = 0.2467 + 0.7049 * hicif(ji,jj)                                &
122                  &                    - 0.8608 * hicif(ji,jj) * hicif(ji,jj)                 &
123                  &                    + 0.3812 * hicif(ji,jj) * hicif(ji,jj) * hicif (ji,jj)
124            ELSE
125               zficeth(ji,jj) = 0.1 + 3.6 * hicif(ji,jj) 
126            ENDIF
127         END DO
128      END DO
129     
130      !-----------------------------------------------
131      !    Computation of the snow/ice albedo system
132      !-------------------------- ---------------------
133     
134      !    Albedo of snow-ice for clear sky.
135      !-----------------------------------------------   
136      DO jj = 1, jpj
137         DO ji = 1, jpi
138            !  Case of ice covered by snow.             
139           
140            !  melting snow       
141            zihsc1       = 1.0 - MAX ( zzero , SIGN ( zone , - ( hsnif(ji,jj) - c1 ) ) )
142            zalbpsnm     = ( 1.0 - zihsc1 ) * ( zficeth(ji,jj) + hsnif(ji,jj) * ( alphd - zficeth(ji,jj) ) / c1 ) &
143               &                 + zihsc1   * alphd 
144            !  freezing snow               
145            zihsc2       = MAX ( zzero , SIGN ( zone , hsnif(ji,jj) - c2 ) )
146            zalbpsnf     = ( 1.0 - zihsc2 ) * ( albice + hsnif(ji,jj) * ( alphc - albice ) / c2 )                 &
147               &                 + zihsc2   * alphc 
148           
149            zitmlsn      =  MAX ( zzero , SIGN ( zone , sist(ji,jj) - rt0_snow ) )   
150            zalbpsn      =  zitmlsn * zalbpsnf + ( 1.0 - zitmlsn ) * zalbpsnm 
151           
152            !  Case of ice free of snow.
153            zalbpic      = zficeth(ji,jj) 
154           
155            ! albedo of the system   
156            zithsn       = 1.0 - MAX ( zzero , SIGN ( zone , - hsnif(ji,jj) ) )
157            palbp(ji,jj) =  zithsn * zalbpsn + ( 1.0 - zithsn ) *  zalbpic
158         END DO
159      END DO
160     
161      !    Albedo of snow-ice for overcast sky.
162      !---------------------------------------------- 
163      palb(:,:)   = palbp(:,:) + cgren                                           
164     
165      !--------------------------------------------
166      !    Computation of the albedo of the ocean
167      !-------------------------- -----------------                                                         
168     
169      !  Parameterization of Briegled and Ramanathan, 1982
170      zmue14      = zmue**1.4                                       
171      palcnp(:,:) = 0.05 / ( 1.1 * zmue14 + 0.15 )               
172     
173      !  Parameterization of Kondratyev, 1969 and Payne, 1972
174      palcn(:,:)  = 0.06                                                 
175     
176   END SUBROUTINE flx_blk_albedo
177
178# else
179   !!----------------------------------------------------------------------
180   !!   Default option :                                   NO sea-ice model
181   !!----------------------------------------------------------------------
182
183   SUBROUTINE flx_blk_albedo( palb , palcn , palbp , palcnp )
184      !!----------------------------------------------------------------------
185      !!               ***  ROUTINE flx_blk_albedo  ***
186      !!
187      !! ** Purpose :   Computation of the albedo of the snow/ice system
188      !!      as well as the ocean one
189      !!
190      !! ** Method  :   Computation of the albedo of snow or ice (choose the
191      !!      wright one by a large number of tests Computation of the albedo
192      !!      of the ocean
193      !!
194      !! History :
195      !!  8.0   !  01-04  (LIM 1.0)
196      !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine)
197      !!----------------------------------------------------------------------
198      !! * Arguments
199      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  &
200         palb         ,     &    !  albedo of ice under overcast sky
201         palcn        ,     &    !  albedo of ocean under overcast sky
202         palbp        ,     &    !  albedo of ice under clear sky
203         palcnp                  !  albedo of ocean under clear sky
204
205      REAL(wp) ::   &
206         zmue14                 !  zmue**1.4
207      !!----------------------------------------------------------------------
208
209      !--------------------------------------------
210      !    Computation of the albedo of the ocean
211      !-------------------------- -----------------
212
213      !  Parameterization of Briegled and Ramanathan, 1982
214      zmue14      = zmue**1.4
215      palcnp(:,:) = 0.05 / ( 1.1 * zmue14 + 0.15 )
216
217      !  Parameterization of Kondratyev, 1969 and Payne, 1972
218      palcn(:,:)  = 0.06
219
220      palb (:,:)  = palcn(:,:)
221      palbp(:,:)  = palcnp(:,:)
222
223   END SUBROUTINE flx_blk_albedo
224
225#endif
226   !!======================================================================
227END MODULE albedo
Note: See TracBrowser for help on using the repository browser.