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

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

CT + CL : UPDATE105 : Add the subroutine albedo_init() in the albedo.F90 module to read the namelist namalb to set albedo parameters

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 12.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   INTEGER  ::             &  !: nameos : ocean physical parameters
29      albd_init = 0           !: control flag for initialization
30
31   REAL(wp)  ::            &  ! constant values
32      zzero   = 0.e0    ,  &
33      zone    = 1.0
34
35   !! * constants for albedo computation (flx_blk_albedo)
36   REAL(wp) ::   &
37      c1     = 0.05  ,     &   ! constants values
38      c2     = 0.10  ,     &
39      albice = 0.50  ,     &   !  albedo of melting ice in the arctic and antarctic (Shine & Hendersson-Sellers)
40      cgren  = 0.06  ,     &   !  correction of the snow or ice albedo to take into account
41                               !  effects of cloudiness (Grenfell & Perovich, 1984)
42      alphd  = 0.80  ,     &   !  coefficients for linear interpolation used to compute
43      alphdi = 0.72  ,     &   !  albedo between two extremes values (Pyane, 1972)
44      alphc  = 0.65  ,     &
45      zmue   = 0.40            !  cosine of local solar altitude
46
47   !!----------------------------------------------------------------------
48   !!   OPA 9.0 , LODYC-IPSL  (2004)
49   !!----------------------------------------------------------------------
50
51CONTAINS
52
53#if defined key_ice_lim
54   !!----------------------------------------------------------------------
55   !!   'key_ice_lim'                                         LIM ice model
56   !!----------------------------------------------------------------------
57
58   SUBROUTINE flx_blk_albedo( palb , palcn , palbp , palcnp )
59      !!----------------------------------------------------------------------
60      !!               ***  ROUTINE flx_blk_albedo  ***
61      !!         
62      !! ** Purpose :   Computation of the albedo of the snow/ice system
63      !!      as well as the ocean one
64      !!       
65      !! ** Method  : - Computation of the albedo of snow or ice (choose the
66      !!      rignt one by a large number of tests
67      !!              - Computation of the albedo of the ocean
68      !!
69      !! References :
70      !!      Shine and Hendersson-Sellers 1985, JGR, 90(D1), 2243-2250.
71      !!
72      !! History :
73      !!  8.0   !  01-04  (LIM 1.0)
74      !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine)
75      !!----------------------------------------------------------------------
76      !! * Modules used
77      USE ice                   ! ???
78
79      !! * Arguments
80      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  &
81         palb         ,     &    !  albedo of ice under overcast sky
82         palcn        ,     &    !  albedo of ocean under overcast sky
83         palbp        ,     &    !  albedo of ice under clear sky
84         palcnp                  !  albedo of ocean under clear sky
85
86      !! * Local variables
87      INTEGER ::    &
88         ji, jj                   ! dummy loop indices
89      REAL(wp) ::   & 
90         zmue14         ,     &   !  zmue**1.4
91         zalbpsnm       ,     &   !  albedo of ice under clear sky when snow is melting
92         zalbpsnf       ,     &   !  albedo of ice under clear sky when snow is freezing
93         zalbpsn        ,     &   !  albedo of snow/ice system when ice is coverd by snow
94         zalbpic        ,     &   !  albedo of snow/ice system when ice is free of snow
95         zithsn         ,     &   !  = 1 for hsn >= 0 ( ice is cov. by snow ) ; = 0 otherwise (ice is free of snow)
96         zitmlsn        ,     &   !  = 1 freezinz snow (sist >=rt0_snow) ; = 0 melting snow (sist<rt0_snow)
97         zihsc1         ,     &   !  = 1 hsn <= c1 ; = 0 hsn > c1
98         zihsc2                   !  = 1 hsn >= c2 ; = 0 hsn < c2
99      REAL(wp), DIMENSION(jpi,jpj) ::  &
100         zalbfz         ,     &   !  ( = alphdi for freezing ice ; = albice for melting ice )
101         zficeth                  !  function of ice thickness
102      LOGICAL , DIMENSION(jpi,jpj) ::  &
103         llmask
104      !!---------------------------------------------------------------------
105     
106      ! initialization
107      IF( albd_init == 0 )   CALL albedo_init
108
109      !-------------------------                                                             
110      !  Computation of  zficeth
111      !--------------------------
112     
113      llmask = (hsnif == 0.e0) .AND. ( sist >= rt0_ice )
114      WHERE ( llmask )   !  ice free of snow and melts
115         zalbfz = albice
116      ELSEWHERE                   
117         zalbfz = alphdi
118      END WHERE
119     
120      DO jj = 1, jpj
121         DO ji = 1, jpi
122            IF( hicif(ji,jj) > 1.5 ) THEN
123               zficeth(ji,jj) = zalbfz(ji,jj)
124            ELSEIF( hicif(ji,jj) > 1.0  .AND. hicif(ji,jj) <= 1.5 ) THEN
125               zficeth(ji,jj) = 0.472 + 2.0 * ( zalbfz(ji,jj) - 0.472 ) * ( hicif(ji,jj) - 1.0 )
126            ELSEIF( hicif(ji,jj) > 0.05 .AND. hicif(ji,jj) <= 1.0 ) THEN
127               zficeth(ji,jj) = 0.2467 + 0.7049 * hicif(ji,jj)                                &
128                  &                    - 0.8608 * hicif(ji,jj) * hicif(ji,jj)                 &
129                  &                    + 0.3812 * hicif(ji,jj) * hicif(ji,jj) * hicif (ji,jj)
130            ELSE
131               zficeth(ji,jj) = 0.1 + 3.6 * hicif(ji,jj) 
132            ENDIF
133         END DO
134      END DO
135     
136      !-----------------------------------------------
137      !    Computation of the snow/ice albedo system
138      !-------------------------- ---------------------
139     
140      !    Albedo of snow-ice for clear sky.
141      !-----------------------------------------------   
142      DO jj = 1, jpj
143         DO ji = 1, jpi
144            !  Case of ice covered by snow.             
145           
146            !  melting snow       
147            zihsc1       = 1.0 - MAX ( zzero , SIGN ( zone , - ( hsnif(ji,jj) - c1 ) ) )
148            zalbpsnm     = ( 1.0 - zihsc1 ) * ( zficeth(ji,jj) + hsnif(ji,jj) * ( alphd - zficeth(ji,jj) ) / c1 ) &
149               &                 + zihsc1   * alphd 
150            !  freezing snow               
151            zihsc2       = MAX ( zzero , SIGN ( zone , hsnif(ji,jj) - c2 ) )
152            zalbpsnf     = ( 1.0 - zihsc2 ) * ( albice + hsnif(ji,jj) * ( alphc - albice ) / c2 )                 &
153               &                 + zihsc2   * alphc 
154           
155            zitmlsn      =  MAX ( zzero , SIGN ( zone , sist(ji,jj) - rt0_snow ) )   
156            zalbpsn      =  zitmlsn * zalbpsnf + ( 1.0 - zitmlsn ) * zalbpsnm 
157           
158            !  Case of ice free of snow.
159            zalbpic      = zficeth(ji,jj) 
160           
161            ! albedo of the system   
162            zithsn       = 1.0 - MAX ( zzero , SIGN ( zone , - hsnif(ji,jj) ) )
163            palbp(ji,jj) =  zithsn * zalbpsn + ( 1.0 - zithsn ) *  zalbpic
164         END DO
165      END DO
166     
167      !    Albedo of snow-ice for overcast sky.
168      !---------------------------------------------- 
169      palb(:,:)   = palbp(:,:) + cgren                                           
170     
171      !--------------------------------------------
172      !    Computation of the albedo of the ocean
173      !-------------------------- -----------------                                                         
174     
175      !  Parameterization of Briegled and Ramanathan, 1982
176      zmue14      = zmue**1.4                                       
177      palcnp(:,:) = 0.05 / ( 1.1 * zmue14 + 0.15 )               
178     
179      !  Parameterization of Kondratyev, 1969 and Payne, 1972
180      palcn(:,:)  = 0.06                                                 
181     
182   END SUBROUTINE flx_blk_albedo
183
184# else
185   !!----------------------------------------------------------------------
186   !!   Default option :                                   NO sea-ice model
187   !!----------------------------------------------------------------------
188
189   SUBROUTINE flx_blk_albedo( palb , palcn , palbp , palcnp )
190      !!----------------------------------------------------------------------
191      !!               ***  ROUTINE flx_blk_albedo  ***
192      !!
193      !! ** Purpose :   Computation of the albedo of the snow/ice system
194      !!      as well as the ocean one
195      !!
196      !! ** Method  :   Computation of the albedo of snow or ice (choose the
197      !!      wright one by a large number of tests Computation of the albedo
198      !!      of the ocean
199      !!
200      !! History :
201      !!  8.0   !  01-04  (LIM 1.0)
202      !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine)
203      !!----------------------------------------------------------------------
204      !! * Arguments
205      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  &
206         palb         ,     &    !  albedo of ice under overcast sky
207         palcn        ,     &    !  albedo of ocean under overcast sky
208         palbp        ,     &    !  albedo of ice under clear sky
209         palcnp                  !  albedo of ocean under clear sky
210
211      REAL(wp) ::   &
212         zmue14                 !  zmue**1.4
213      !!----------------------------------------------------------------------
214
215      !--------------------------------------------
216      !    Computation of the albedo of the ocean
217      !-------------------------- -----------------
218
219      !  Parameterization of Briegled and Ramanathan, 1982
220      zmue14      = zmue**1.4
221      palcnp(:,:) = 0.05 / ( 1.1 * zmue14 + 0.15 )
222
223      !  Parameterization of Kondratyev, 1969 and Payne, 1972
224      palcn(:,:)  = 0.06
225
226      palb (:,:)  = palcn(:,:)
227      palbp(:,:)  = palcnp(:,:)
228
229   END SUBROUTINE flx_blk_albedo
230
231#endif
232
233   SUBROUTINE albedo_init
234      !!----------------------------------------------------------------------
235      !!                 ***  ROUTINE albedo_init  ***
236      !!
237      !! ** Purpose :   initializations for the albedo parameters
238      !!
239      !! ** Method  :   Read the namelist namalb
240      !!
241      !! ** Action  : 
242      !!
243      !!
244      !! History :
245      !!   9.0  !  04-11  (C. Talandier)  Original code
246      !!----------------------------------------------------------------------
247      NAMELIST/namalb/ cgren, albice, alphd, alphdi, alphc
248      !!----------------------------------------------------------------------
249      !!  OPA 9.0, LODYC-IPSL (2004)
250      !!----------------------------------------------------------------------
251
252      ! set the initialization flag to 1
253      albd_init = 1           ! indicate that the initialization has been done
254
255      ! Read Namelist namalb : albedo parameters
256      REWIND( numnam )
257      READ  ( numnam, namalb )
258
259      ! Control print
260      IF(lwp) THEN
261         WRITE(numout,*)
262         WRITE(numout,*) 'albedo_init : albedo '
263         WRITE(numout,*) '~~~~~~~~~~~'
264         WRITE(numout,*) '          Namelist namalb : set albedo parameters'
265         WRITE(numout,*)
266         WRITE(numout,*) '             correction of the snow or ice albedo to take into account cgren = ', cgren
267         WRITE(numout,*) '             albedo of melting ice in the arctic and antarctic        albice = ', albice
268         WRITE(numout,*) '             coefficients for linear                                   alphd = ', alphd
269         WRITE(numout,*) '             interpolation used to compute albedo                     alphdi = ', alphdi
270         WRITE(numout,*) '             between two extremes values (Pyane, 1972)                 alphc = ', alphc
271         WRITE(numout,*)
272      ENDIF
273
274   END SUBROUTINE albedo_init
275   !!======================================================================
276END MODULE albedo
Note: See TracBrowser for help on using the repository browser.