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/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE – NEMO

source: NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/icealb.F90 @ 12658

Last change on this file since 12658 was 12439, checked in by dancopsey, 4 years ago
  • Provide maximum limits to how big ponds can get. If they exceep this they leak water into the ocean.
  • Water going into melt ponds does not affect ice thickness until it leaks inot the ocean.
  • Deep snow on sea ice can cover up the ponds by forming a lid.
File size: 13.3 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   USE dom_oce        ! domain: ocean
19   USE icethd_pnd, only: pnd_lid_max, pnd_lid_min
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, plh_pnd, palb_cs, palb_os )
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(:,:,:) ::   plh_pnd      !  melt pond lid thickness
101      REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   palb_cs      !  albedo of ice under clear    sky
102      REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   palb_os      !  albedo of ice under overcast sky
103      !
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) ::   lfrac_pnd                 ! The fraction of the meltpond exposed (not inder a frozen lid)
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      DO jl = 1, jpl
122         DO jj = 1, jpj
123            DO ji = 1, jpi
124               !                       !--- Specific snow, ice and pond fractions (for now, we prevent melt ponds and snow at the same time)
125               IF( ph_snw(ji,jj,jl) == 0._wp ) THEN
126                  zafrac_snw = 0._wp
127                  IF( ld_pnd_alb ) THEN
128                     IF ( plh_pnd(ji,jj,jl) > pnd_lid_max ) THEN
129                        lfrac_pnd = 0._wp
130                     ELSE
131                        IF ( plh_pnd(ji,jj,jl) < pnd_lid_min ) THEN
132                           lfrac_pnd = 1._wp
133                        ELSE
134                           lfrac_pnd = ( plh_pnd(ji,jj,jl) - pnd_lid_min ) / (pnd_lid_max - pnd_lid_min)
135                        END IF
136                     END IF
137                     zafrac_pnd = pafrac_pnd(ji,jj,jl) * lfrac_pnd
138                  ELSE
139                     zafrac_pnd = 0._wp
140                  ENDIF
141                  zafrac_ice = 1._wp - zafrac_pnd
142               ELSE
143                  zafrac_snw = 1._wp      ! Snow fully "shades" melt ponds and ice
144                  zafrac_pnd = 0._wp
145                  zafrac_ice = 0._wp
146               ENDIF
147               !
148               !                       !--- Bare ice albedo (for hi > 150cm)
149               IF( ld_pnd_alb ) THEN
150                  zalb_ice = rn_alb_idry
151               ELSE
152                  IF( ph_snw(ji,jj,jl) == 0._wp .AND. pt_su(ji,jj,jl) >= rt0 ) THEN  ;   zalb_ice = rn_alb_imlt
153                  ELSE                                                               ;   zalb_ice = rn_alb_idry   ;   ENDIF
154               ENDIF
155               !                       !--- Bare ice albedo (for hi < 150cm)
156               IF( 0.05 < ph_ice(ji,jj,jl) .AND. ph_ice(ji,jj,jl) <= 1.5 ) THEN      ! 5cm < hi < 150cm
157                  zalb_ice = zalb_ice    + ( 0.18 - zalb_ice   ) * z1_c1 * ( LOG(1.5) - LOG(ph_ice(ji,jj,jl)) )
158               ELSEIF( ph_ice(ji,jj,jl) <= 0.05 ) THEN                               ! 0cm < hi < 5cm
159                  zalb_ice = rn_alb_oce  + ( 0.18 - rn_alb_oce ) * z1_c2 * ph_ice(ji,jj,jl)
160               ENDIF
161               !
162               !                       !--- Snow-covered ice albedo (freezing, melting cases)
163               IF( pt_su(ji,jj,jl) < rt0 ) THEN
164                  zalb_snw = rn_alb_sdry - ( rn_alb_sdry - zalb_ice ) * EXP( - ph_snw(ji,jj,jl) * z1_c3 )
165               ELSE
166                  zalb_snw = rn_alb_smlt - ( rn_alb_smlt - zalb_ice ) * EXP( - ph_snw(ji,jj,jl) * z1_c4 )
167               ENDIF
168               !                       !--- Ponded ice albedo
169               IF( ld_pnd_alb ) THEN
170                  zalb_pnd = rn_alb_dpnd - ( rn_alb_dpnd - zalb_ice ) * EXP( - ph_pnd(ji,jj,jl) * z1_href_pnd ) 
171               ELSE
172                  zalb_pnd = rn_alb_dpnd
173               ENDIF
174               !                       !--- Surface albedo is weighted mean of snow, ponds and bare ice contributions
175               palb_os(ji,jj,jl) = ( zafrac_snw * zalb_snw + zafrac_pnd * zalb_pnd + zafrac_ice * zalb_ice ) * tmask(ji,jj,1)
176               !
177               palb_cs(ji,jj,jl) = palb_os(ji,jj,jl)  &
178                  &                - ( - 0.1010 * palb_os(ji,jj,jl) * palb_os(ji,jj,jl)  &
179                  &                    + 0.1933 * palb_os(ji,jj,jl) - 0.0148 ) * tmask(ji,jj,1)
180               !
181            END DO
182         END DO
183      END DO
184      !
185      !
186      IF( ln_timing )   CALL timing_stop('icealb')
187      !
188   END SUBROUTINE ice_alb
189
190
191   SUBROUTINE ice_alb_init
192      !!----------------------------------------------------------------------
193      !!                 ***  ROUTINE alb_init  ***
194      !!
195      !! ** Purpose :   initializations for the albedo parameters
196      !!
197      !! ** Method  :   Read the namelist namalb
198      !!----------------------------------------------------------------------
199      INTEGER ::   ios   ! Local integer output status for namelist read
200      !!
201      NAMELIST/namalb/ rn_alb_sdry, rn_alb_smlt, rn_alb_idry, rn_alb_imlt, rn_alb_dpnd
202      !!----------------------------------------------------------------------
203      !
204      REWIND( numnam_ice_ref )              ! Namelist namalb in reference namelist : Albedo parameters
205      READ  ( numnam_ice_ref, namalb, IOSTAT = ios, ERR = 901)
206901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namalb in reference namelist', lwp )
207      REWIND( numnam_ice_cfg )              ! Namelist namalb in configuration namelist : Albedo parameters
208      READ  ( numnam_ice_cfg, namalb, IOSTAT = ios, ERR = 902 )
209902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namalb in configuration namelist', lwp )
210      IF(lwm) WRITE( numoni, namalb )
211      !
212      IF(lwp) THEN                      ! Control print
213         WRITE(numout,*)
214         WRITE(numout,*) 'ice_alb_init: set albedo parameters'
215         WRITE(numout,*) '~~~~~~~~~~~~'
216         WRITE(numout,*) '   Namelist namalb:'
217         WRITE(numout,*) '      albedo of dry snow                   rn_alb_sdry = ', rn_alb_sdry
218         WRITE(numout,*) '      albedo of melting snow               rn_alb_smlt = ', rn_alb_smlt
219         WRITE(numout,*) '      albedo of dry ice                    rn_alb_idry = ', rn_alb_idry
220         WRITE(numout,*) '      albedo of bare puddled ice           rn_alb_imlt = ', rn_alb_imlt
221         WRITE(numout,*) '      albedo of ponded ice                 rn_alb_dpnd = ', rn_alb_dpnd
222      ENDIF
223      !
224   END SUBROUTINE ice_alb_init
225
226#else
227   !!----------------------------------------------------------------------
228   !!   Default option           Dummy module         NO SI3 sea-ice model
229   !!----------------------------------------------------------------------
230#endif
231
232   !!======================================================================
233END MODULE icealb
Note: See TracBrowser for help on using the repository browser.