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.
icealb.F90 in NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/ICE – NEMO

source: NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/ICE/icealb.F90 @ 13662

Last change on this file since 13662 was 13662, checked in by clem, 3 years ago

update to almost r4.0.4

  • Property svn:keywords set to Id
File size: 12.9 KB
Line 
1MODULE icealb
2   !!======================================================================
3   !!                       ***  MODULE  icealb  ***
4   !! Atmospheric forcing:  Albedo over sea ice
5   !!=====================================================================
6   !! History :  4.0  !  2017-07  (C. Rousset)       Split ice and ocean albedos
7   !!            4.0  !  2018     (many people)      SI3 [aka Sea Ice cube]
8   !!----------------------------------------------------------------------
9#if defined key_si3
10   !!----------------------------------------------------------------------
11   !!   'key_si3'                                       SI3 sea-ice model
12   !!----------------------------------------------------------------------
13   !!   ice_alb        : albedo for ice (clear and overcast skies)
14   !!   ice_alb_init   : initialisation of albedo computation
15   !!----------------------------------------------------------------------
16   USE phycst         ! physical constants
17   USE dom_oce        ! domain: ocean
18   USE ice, ONLY: jpl ! sea-ice: number of categories
19   USE icevar         ! sea-ice: operations
20   !
21   USE in_out_manager ! I/O manager
22   USE lib_mpp        ! MPP library
23   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
24   USE timing         ! Timing
25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   ice_alb_init   ! called in icestp
30   PUBLIC   ice_alb        ! called in icesbc.F90 and iceupdate.F90
31
32   REAL(wp), PUBLIC, PARAMETER ::   rn_alb_oce = 0.066   !: ocean or lead albedo (Pegau and Paulson, Ann. Glac. 2001)
33   !
34   !                             !!* albedo namelist (namalb)
35   REAL(wp) ::   rn_alb_sdry      ! dry snow albedo
36   REAL(wp) ::   rn_alb_smlt      ! melting snow albedo
37   REAL(wp) ::   rn_alb_idry      ! dry ice albedo
38   REAL(wp) ::   rn_alb_imlt      ! bare puddled ice albedo
39   REAL(wp) ::   rn_alb_dpnd      ! ponded ice albedo
40
41   !!----------------------------------------------------------------------
42   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
43   !! $Id$
44   !! Software governed by the CeCILL license (see ./LICENSE)
45   !!----------------------------------------------------------------------
46CONTAINS
47
48   SUBROUTINE ice_alb( pt_su, ph_ice, ph_snw, ld_pnd_alb, pafrac_pnd, ph_pnd, pcloud_fra, palb_ice )
49      !!----------------------------------------------------------------------
50      !!               ***  ROUTINE ice_alb  ***
51      !!         
52      !! ** Purpose :   Computation of the albedo of the snow/ice system
53      !!       
54      !! ** Method  :   The scheme is "home made" (for cloudy skies) and based on Brandt et al. (J. Climate 2005)
55      !!                                                                      and Grenfell & Perovich (JGR 2004)
56      !!                  1) Albedo dependency on ice thickness follows the findings from Brandt et al (2005)
57      !!                     which are an update of Allison et al. (JGR 1993) ; Brandt et al. 1999
58      !!                     0-5cm  : linear function of ice thickness
59      !!                     5-150cm: log    function of ice thickness
60      !!                     > 150cm: constant
61      !!                  2) Albedo dependency on snow thickness follows the findings from Grenfell & Perovich (2004)
62      !!                     i.e. it increases as -EXP(-snw_thick/0.02) during freezing and -EXP(-snw_thick/0.03) during melting
63      !!                  3) Albedo dependency on clouds is speculated from measurements of Grenfell and Perovich (2004)
64      !!                     i.e. cloudy-clear albedo depend on cloudy albedo following a 2d order polynomial law
65      !!                  4) The needed 4 parameters are: dry and melting snow, freezing ice and bare puddled ice
66      !!
67      !!                     compilation of values from literature (reference overcast sky values)
68      !!                        rn_alb_sdry = 0.85      ! dry snow
69      !!                        rn_alb_smlt = 0.75      ! melting snow
70      !!                        rn_alb_idry = 0.60      ! bare frozen ice
71      !!                        rn_alb_imlt = 0.50      ! bare puddled ice albedo
72      !!                        rn_alb_dpnd = 0.36      ! ponded-ice overcast albedo (Lecomte et al, 2015)
73      !!                                                ! early melt pnds 0.27, late melt ponds 0.14 Grenfell & Perovich
74      !!                     Perovich et al 2002 (Sheba) => the only dataset for which all types of ice/snow were retrieved
75      !!                        rn_alb_sdry = 0.85      ! dry snow
76      !!                        rn_alb_smlt = 0.72      ! melting snow
77      !!                        rn_alb_idry = 0.65      ! bare frozen ice
78      !!                     Brandt et al 2005 (East Antarctica)
79      !!                        rn_alb_sdry = 0.87      ! dry snow
80      !!                        rn_alb_smlt = 0.82      ! melting snow
81      !!                        rn_alb_idry = 0.54      ! bare frozen ice
82      !!
83      !! ** Note    :   The old parameterization from Shine & Henderson-Sellers (not here anymore) presented several misconstructions
84      !!                  1) ice albedo when ice thick. tends to 0 is different than ocean albedo
85      !!                  2) for small ice thick. covered with some snow (<3cm?), albedo is larger
86      !!                     under melting conditions than under freezing conditions
87      !!                  3) the evolution of ice albedo as a function of ice thickness shows 
88      !!                     3 sharp inflexion points (at 5cm, 100cm and 150cm) that look highly unrealistic
89      !!
90      !! References :   Shine & Henderson-Sellers 1985, JGR, 90(D1), 2243-2250.
91      !!                Brandt et al. 2005, J. Climate, vol 18
92      !!                Grenfell & Perovich 2004, JGR, vol 109
93      !!----------------------------------------------------------------------
94      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   pt_su        !  ice surface temperature (Kelvin)
95      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   ph_ice       !  sea-ice thickness
96      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   ph_snw       !  snow depth
97      LOGICAL , INTENT(in   )                   ::   ld_pnd_alb   !  effect of melt ponds on albedo
98      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   pafrac_pnd   !  melt pond relative fraction (per unit ice area)
99      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   ph_pnd       !  melt pond depth
100      REAL(wp), INTENT(in   ), DIMENSION(:,:)   ::   pcloud_fra   !  cloud fraction
101      REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   palb_ice     !  albedo of ice
102      !
103      REAL(wp), DIMENSION(jpi,jpj,jpl) :: za_s_fra   ! ice fraction covered by snow
104      INTEGER  ::   ji, jj, jl                ! dummy loop indices
105      REAL(wp) ::   z1_c1, z1_c2,z1_c3, z1_c4 ! local scalar
106      REAL(wp) ::   z1_href_pnd               ! inverse of the characteristic length scale (Lecomte et al. 2015)
107      REAL(wp) ::   zalb_pnd, zafrac_pnd      ! ponded sea ice albedo & relative pound fraction
108      REAL(wp) ::   zalb_ice, zafrac_ice      ! bare sea ice albedo & relative ice fraction
109      REAL(wp) ::   zalb_snw, zafrac_snw      ! snow-covered sea ice albedo & relative snow fraction
110      REAL(wp) ::   zalb_cs, zalb_os          ! albedo of ice under clear/overcast sky
111      !!---------------------------------------------------------------------
112      !
113      IF( ln_timing )   CALL timing_start('icealb')
114      !
115      z1_href_pnd = 1. / 0.05
116      z1_c1 = 1. / ( LOG(1.5) - LOG(0.05) ) 
117      z1_c2 = 1. / 0.05
118      z1_c3 = 1. / 0.02
119      z1_c4 = 1. / 0.03
120      !
121      CALL ice_var_snwfra( ph_snw, za_s_fra )   ! calculate ice fraction covered by snow
122      !
123      DO jl = 1, jpl
124         DO jj = 1, jpj
125            DO ji = 1, jpi
126               !
127               !---------------------------------------------!
128               !--- Specific snow, ice and pond fractions ---!
129               !---------------------------------------------!               
130               zafrac_snw = za_s_fra(ji,jj,jl)
131               IF( ld_pnd_alb ) THEN
132                  zafrac_pnd = MIN( pafrac_pnd(ji,jj,jl), 1._wp - zafrac_snw ) ! make sure (a_ip_eff + a_s_fra) <= 1
133               ELSE
134                  zafrac_pnd = 0._wp
135               ENDIF
136               zafrac_ice = MAX( 0._wp, 1._wp - zafrac_pnd - zafrac_snw ) ! max for roundoff errors
137               !
138               !---------------!
139               !--- Albedos ---!
140               !---------------!               
141               !                       !--- Bare ice albedo (for hi > 150cm)
142               IF( ld_pnd_alb ) THEN
143                  zalb_ice = rn_alb_idry
144               ELSE
145                  IF( ph_snw(ji,jj,jl) == 0._wp .AND. pt_su(ji,jj,jl) >= rt0 ) THEN   ;   zalb_ice = rn_alb_imlt
146                  ELSE                                                                ;   zalb_ice = rn_alb_idry   ;   ENDIF
147               ENDIF
148               !                       !--- Bare ice albedo (for hi < 150cm)
149               IF( 0.05 < ph_ice(ji,jj,jl) .AND. ph_ice(ji,jj,jl) <= 1.5 ) THEN      ! 5cm < hi < 150cm
150                  zalb_ice = zalb_ice    + ( 0.18 - zalb_ice   ) * z1_c1 * ( LOG(1.5) - LOG(ph_ice(ji,jj,jl)) )
151               ELSEIF( ph_ice(ji,jj,jl) <= 0.05 ) THEN                               ! 0cm < hi < 5cm
152                  zalb_ice = rn_alb_oce  + ( 0.18 - rn_alb_oce ) * z1_c2 * ph_ice(ji,jj,jl)
153               ENDIF
154               !
155               !                       !--- Snow-covered ice albedo (freezing, melting cases)
156               IF( pt_su(ji,jj,jl) < rt0 ) THEN
157                  zalb_snw = rn_alb_sdry - ( rn_alb_sdry - zalb_ice ) * EXP( - ph_snw(ji,jj,jl) * z1_c3 )
158               ELSE
159                  zalb_snw = rn_alb_smlt - ( rn_alb_smlt - zalb_ice ) * EXP( - ph_snw(ji,jj,jl) * z1_c4 )
160               ENDIF
161               !                       !--- Ponded ice albedo
162               zalb_pnd = rn_alb_dpnd - ( rn_alb_dpnd - zalb_ice ) * EXP( - ph_pnd(ji,jj,jl) * z1_href_pnd ) 
163               !
164               !                       !--- Surface albedo is weighted mean of snow, ponds and bare ice contributions
165               zalb_os = ( zafrac_snw * zalb_snw + zafrac_pnd * zalb_pnd + zafrac_ice * zalb_ice ) * tmask(ji,jj,1)
166               !
167               zalb_cs = zalb_os - ( - 0.1010 * zalb_os * zalb_os  &
168                  &                  + 0.1933 * zalb_os - 0.0148 ) * tmask(ji,jj,1)
169               !
170               ! albedo depends on cloud fraction because of non-linear spectral effects
171               palb_ice(ji,jj,jl) = ( 1._wp - pcloud_fra(ji,jj) ) * zalb_cs + pcloud_fra(ji,jj) * zalb_os
172
173            END DO
174         END DO
175      END DO
176      !
177      !
178      IF( ln_timing )   CALL timing_stop('icealb')
179      !
180   END SUBROUTINE ice_alb
181
182
183   SUBROUTINE ice_alb_init
184      !!----------------------------------------------------------------------
185      !!                 ***  ROUTINE alb_init  ***
186      !!
187      !! ** Purpose :   initializations for the albedo parameters
188      !!
189      !! ** Method  :   Read the namelist namalb
190      !!----------------------------------------------------------------------
191      INTEGER ::   ios   ! Local integer output status for namelist read
192      !!
193      NAMELIST/namalb/ rn_alb_sdry, rn_alb_smlt, rn_alb_idry, rn_alb_imlt, rn_alb_dpnd
194      !!----------------------------------------------------------------------
195      !
196      REWIND( numnam_ice_ref )              ! Namelist namalb in reference namelist : Albedo parameters
197      READ  ( numnam_ice_ref, namalb, IOSTAT = ios, ERR = 901)
198901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namalb in reference namelist' )
199      REWIND( numnam_ice_cfg )              ! Namelist namalb in configuration namelist : Albedo parameters
200      READ  ( numnam_ice_cfg, namalb, IOSTAT = ios, ERR = 902 )
201902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namalb in configuration namelist' )
202      IF(lwm) WRITE( numoni, namalb )
203      !
204      IF(lwp) THEN                      ! Control print
205         WRITE(numout,*)
206         WRITE(numout,*) 'ice_alb_init: set albedo parameters'
207         WRITE(numout,*) '~~~~~~~~~~~~'
208         WRITE(numout,*) '   Namelist namalb:'
209         WRITE(numout,*) '      albedo of dry snow                   rn_alb_sdry = ', rn_alb_sdry
210         WRITE(numout,*) '      albedo of melting snow               rn_alb_smlt = ', rn_alb_smlt
211         WRITE(numout,*) '      albedo of dry ice                    rn_alb_idry = ', rn_alb_idry
212         WRITE(numout,*) '      albedo of bare puddled ice           rn_alb_imlt = ', rn_alb_imlt
213         WRITE(numout,*) '      albedo of ponded ice                 rn_alb_dpnd = ', rn_alb_dpnd
214      ENDIF
215      !
216   END SUBROUTINE ice_alb_init
217
218#else
219   !!----------------------------------------------------------------------
220   !!   Default option           Dummy module         NO SI3 sea-ice model
221   !!----------------------------------------------------------------------
222#endif
223
224   !!======================================================================
225END MODULE icealb
Note: See TracBrowser for help on using the repository browser.