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/trunk/src/ICE – NEMO

source: NEMO/trunk/src/ICE/icealb.F90 @ 15368

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

Some harmless reorganization of SI3: 1) extract the parts where mpi com were needed from inside thermo. 2) code an optional upstream scheme inside rheology to calculate P as the sub time step level. 3) prepare the albedo to scheme to recieve an aditional namelist parameter (pivotal ice thickness)

  • Property svn:keywords set to Id
File size: 12.8 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_wp   !: 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   !! * Substitutions
42#  include "do_loop_substitute.h90"
43   !!----------------------------------------------------------------------
44   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
45   !! $Id$
46   !! Software governed by the CeCILL license (see ./LICENSE)
47   !!----------------------------------------------------------------------
48CONTAINS
49
50   SUBROUTINE ice_alb( pt_su, ph_ice, ph_snw, ld_pnd_alb, pafrac_pnd, ph_pnd, pcloud_fra, palb_ice )
51      !!----------------------------------------------------------------------
52      !!               ***  ROUTINE ice_alb  ***
53      !!         
54      !! ** Purpose :   Computation of the albedo of the snow/ice system
55      !!       
56      !! ** Method  :   The scheme is "home made" (for cloudy skies) and based on Brandt et al. (J. Climate 2005)
57      !!                                                                      and Grenfell & Perovich (JGR 2004)
58      !!                  1) Albedo dependency on ice thickness follows the findings from Brandt et al (2005)
59      !!                     which are an update of Allison et al. (JGR 1993) ; Brandt et al. 1999
60      !!                     0-5cm  : linear function of ice thickness
61      !!                     5-150cm: log    function of ice thickness
62      !!                     > 150cm: constant
63      !!                  2) Albedo dependency on snow thickness follows the findings from Grenfell & Perovich (2004)
64      !!                     i.e. it increases as -EXP(-snw_thick/0.02) during freezing and -EXP(-snw_thick/0.03) during melting
65      !!                  3) Albedo dependency on clouds is speculated from measurements of Grenfell and Perovich (2004)
66      !!                     i.e. cloudy-clear albedo depend on cloudy albedo following a 2d order polynomial law
67      !!                  4) The needed 4 parameters are: dry and melting snow, freezing ice and bare puddled ice
68      !!
69      !!                     compilation of values from literature (reference overcast sky values)
70      !!                        rn_alb_sdry = 0.85      ! dry snow
71      !!                        rn_alb_smlt = 0.75      ! melting snow
72      !!                        rn_alb_idry = 0.60      ! bare frozen ice
73      !!                        rn_alb_imlt = 0.50      ! bare puddled ice albedo
74      !!                        rn_alb_dpnd = 0.36      ! ponded-ice overcast albedo (Lecomte et al, 2015)
75      !!                                                ! early melt pnds 0.27, late melt ponds 0.14 Grenfell & Perovich
76      !!                     Perovich et al 2002 (Sheba) => the only dataset for which all types of ice/snow were retrieved
77      !!                        rn_alb_sdry = 0.85      ! dry snow
78      !!                        rn_alb_smlt = 0.72      ! melting snow
79      !!                        rn_alb_idry = 0.65      ! bare frozen ice
80      !!                     Brandt et al 2005 (East Antarctica)
81      !!                        rn_alb_sdry = 0.87      ! dry snow
82      !!                        rn_alb_smlt = 0.82      ! melting snow
83      !!                        rn_alb_idry = 0.54      ! bare frozen ice
84      !!
85      !! ** Note    :   The old parameterization from Shine & Henderson-Sellers (not here anymore) presented several misconstructions
86      !!                  1) ice albedo when ice thick. tends to 0 is different than ocean albedo
87      !!                  2) for small ice thick. covered with some snow (<3cm?), albedo is larger
88      !!                     under melting conditions than under freezing conditions
89      !!                  3) the evolution of ice albedo as a function of ice thickness shows 
90      !!                     3 sharp inflexion points (at 5cm, 100cm and 150cm) that look highly unrealistic
91      !!
92      !! References :   Shine & Henderson-Sellers 1985, JGR, 90(D1), 2243-2250.
93      !!                Brandt et al. 2005, J. Climate, vol 18
94      !!                Grenfell & Perovich 2004, JGR, vol 109
95      !!----------------------------------------------------------------------
96      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   pt_su        !  ice surface temperature (Kelvin)
97      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   ph_ice       !  sea-ice thickness
98      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   ph_snw       !  snow depth
99      LOGICAL , INTENT(in   )                   ::   ld_pnd_alb   !  effect of melt ponds on albedo
100      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   pafrac_pnd   !  melt pond relative fraction (per unit ice area)
101      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   ph_pnd       !  melt pond depth
102      REAL(wp), INTENT(in   ), DIMENSION(:,:)   ::   pcloud_fra   !  cloud fraction
103      REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   palb_ice     !  albedo of ice
104      !
105      REAL(wp), DIMENSION(jpi,jpj,jpl) :: za_s_fra   ! ice fraction covered by snow
106      INTEGER  ::   ji, jj, jl                ! dummy loop indices
107      REAL(wp) ::   z1_c1, z1_c2,z1_c3, z1_c4 ! local scalar
108      REAL(wp) ::   z1_href_pnd               ! inverse of the characteristic length scale (Lecomte et al. 2015)
109      REAL(wp) ::   zalb_pnd, zafrac_pnd      ! ponded sea ice albedo & relative pound fraction
110      REAL(wp) ::   zalb_ice, zafrac_ice      ! bare sea ice albedo & relative ice fraction
111      REAL(wp) ::   zalb_snw, zafrac_snw      ! snow-covered sea ice albedo & relative snow fraction
112      REAL(wp) ::   zalb_cs, zalb_os          ! albedo of ice under clear/overcast sky
113      !! clem
114      REAL(wp), PARAMETER ::   zhi_albcst = 1.5_wp ! pivotal thickness (should be in the namelist)
115      !!---------------------------------------------------------------------
116      !
117      IF( ln_timing )   CALL timing_start('icealb')
118      !
119      z1_href_pnd = 1._wp / 0.05_wp
120      z1_c1 = 1._wp / ( LOG(zhi_albcst) - LOG(0.05_wp) ) 
121      z1_c2 = 1._wp / 0.05_wp
122      z1_c3 = 1._wp / 0.02_wp
123      z1_c4 = 1._wp / 0.03_wp
124      !
125      CALL ice_var_snwfra( ph_snw, za_s_fra )   ! calculate ice fraction covered by snow
126      !
127      DO jl = 1, jpl
128         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )   ! palb_ice used over the full domain in icesbc
129            !
130            !---------------------------------------------!
131            !--- Specific snow, ice and pond fractions ---!
132            !---------------------------------------------!               
133            zafrac_snw = za_s_fra(ji,jj,jl)
134            IF( ld_pnd_alb ) THEN
135               zafrac_pnd = MIN( pafrac_pnd(ji,jj,jl), 1._wp - zafrac_snw ) ! make sure (a_ip_eff + a_s_fra) <= 1
136            ELSE
137               zafrac_pnd = 0._wp
138            ENDIF
139            zafrac_ice = MAX( 0._wp, 1._wp - zafrac_pnd - zafrac_snw ) ! max for roundoff errors
140            !
141            !---------------!
142            !--- Albedos ---!
143            !---------------!               
144            !                       !--- Bare ice albedo (for hi > 150cm)
145            IF( ld_pnd_alb ) THEN
146               zalb_ice = rn_alb_idry
147            ELSE
148               IF( ph_snw(ji,jj,jl) == 0._wp .AND. pt_su(ji,jj,jl) >= rt0 ) THEN   ;   zalb_ice = rn_alb_imlt
149               ELSE                                                                ;   zalb_ice = rn_alb_idry   ;   ENDIF
150            ENDIF
151            !                       !--- Bare ice albedo (for hi < 150cm)
152            IF( 0.05 < ph_ice(ji,jj,jl) .AND. ph_ice(ji,jj,jl) <= zhi_albcst ) THEN      ! 5cm < hi < 150cm
153               zalb_ice = zalb_ice    + ( 0.18_wp - zalb_ice   ) * z1_c1 * ( LOG(zhi_albcst) - LOG(ph_ice(ji,jj,jl)) )
154            ELSEIF( ph_ice(ji,jj,jl) <= 0.05_wp ) THEN                               ! 0cm < hi < 5cm
155               zalb_ice = rn_alb_oce  + ( 0.18_wp - rn_alb_oce ) * z1_c2 * ph_ice(ji,jj,jl)
156            ENDIF
157            !
158            !                       !--- Snow-covered ice albedo (freezing, melting cases)
159            IF( pt_su(ji,jj,jl) < rt0 ) THEN
160               zalb_snw = rn_alb_sdry - ( rn_alb_sdry - zalb_ice ) * EXP( - ph_snw(ji,jj,jl) * z1_c3 )
161            ELSE
162               zalb_snw = rn_alb_smlt - ( rn_alb_smlt - zalb_ice ) * EXP( - ph_snw(ji,jj,jl) * z1_c4 )
163            ENDIF
164            !                       !--- Ponded ice albedo
165            zalb_pnd = rn_alb_dpnd - ( rn_alb_dpnd - zalb_ice ) * EXP( - ph_pnd(ji,jj,jl) * z1_href_pnd ) 
166            !
167            !                       !--- Surface albedo is weighted mean of snow, ponds and bare ice contributions
168            zalb_os = ( zafrac_snw * zalb_snw + zafrac_pnd * zalb_pnd + zafrac_ice * zalb_ice ) * tmask(ji,jj,1)
169            !
170            zalb_cs = zalb_os - ( - 0.1010_wp * zalb_os * zalb_os  &
171               &                  + 0.1933_wp * zalb_os - 0.0148_wp ) * tmask(ji,jj,1)
172            !
173            ! albedo depends on cloud fraction because of non-linear spectral effects
174            palb_ice(ji,jj,jl) = ( 1._wp - pcloud_fra(ji,jj) ) * zalb_cs + pcloud_fra(ji,jj) * zalb_os
175
176         END_2D
177      END DO
178      !
179      !
180      IF( ln_timing )   CALL timing_stop('icealb')
181      !
182   END SUBROUTINE ice_alb
183
184
185   SUBROUTINE ice_alb_init
186      !!----------------------------------------------------------------------
187      !!                 ***  ROUTINE alb_init  ***
188      !!
189      !! ** Purpose :   initializations for the albedo parameters
190      !!
191      !! ** Method  :   Read the namelist namalb
192      !!----------------------------------------------------------------------
193      INTEGER ::   ios   ! Local integer output status for namelist read
194      !!
195      NAMELIST/namalb/ rn_alb_sdry, rn_alb_smlt, rn_alb_idry, rn_alb_imlt, rn_alb_dpnd
196      !!----------------------------------------------------------------------
197      !
198      READ  ( numnam_ice_ref, namalb, IOSTAT = ios, ERR = 901)
199901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namalb in reference namelist' )
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.