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

Last change on this file since 9885 was 9604, checked in by clem, 6 years ago

change history of the ice routines

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