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.
icethd_pnd.F90 in NEMO/branches/2018/dev_r9838_ENHANCE04_MLF/src/ICE – NEMO

source: NEMO/branches/2018/dev_r9838_ENHANCE04_MLF/src/ICE/icethd_pnd.F90 @ 9937

Last change on this file since 9937 was 9937, checked in by gm, 6 years ago

#1911 (ENHANCE-04): step I.2 (end): clean sea ice related physical constant in dev_r9838_ENHANCE04_MLF

File size: 12.5 KB
Line 
1MODULE icethd_pnd 
2   !!======================================================================
3   !!                     ***  MODULE  icethd_pnd   ***
4   !!   sea-ice: Melt ponds on top of sea ice
5   !!======================================================================
6   !! history :       !  2012     (O. Lecomte)       Adaptation from Flocco and Turner
7   !!                 !  2017     (M. Vancoppenolle, O. Lecomte, C. Rousset) Implementation
8   !!            4.0  !  2018     (many people)      SI3 [aka Sea Ice cube]
9   !!----------------------------------------------------------------------
10#if defined key_si3
11   !!----------------------------------------------------------------------
12   !!   'key_si3' :                                     SI3 sea-ice model
13   !!----------------------------------------------------------------------
14   !!   ice_thd_pnd_init : some initialization and namelist read
15   !!   ice_thd_pnd      : main calling routine
16   !!----------------------------------------------------------------------
17   USE phycst         ! physical constants
18   USE dom_oce        ! ocean space and time domain
19   USE ice            ! sea-ice: variables
20   USE ice1D          ! sea-ice: thermodynamics variables
21   USE icetab         ! sea-ice: 1D <==> 2D transformation
22   !
23   USE in_out_manager ! I/O manager
24   USE lib_mpp        ! MPP library
25   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero)
26   USE timing         ! Timing
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   ice_thd_pnd_init    ! routine called by icestp.F90
32   PUBLIC   ice_thd_pnd         ! routine called by icestp.F90
33
34   INTEGER ::              nice_pnd    ! choice of the type of pond scheme
35   !                                   ! associated indices:
36   INTEGER, PARAMETER ::   np_pndNO  = 0   ! No pond scheme
37   INTEGER, PARAMETER ::   np_pndCST = 1   ! Constant pond scheme
38   INTEGER, PARAMETER ::   np_pndH12 = 2   ! Evolutive pond scheme (Holland et al. 2012)
39
40   !! * Substitutions
41#  include "vectopt_loop_substitute.h90"
42   !!----------------------------------------------------------------------
43   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
44   !! $Id: icethd_pnd.F90 8420 2017-10-05 13:07:10Z clem $
45   !! Software governed by the CeCILL licence     (./LICENSE)
46   !!----------------------------------------------------------------------
47CONTAINS
48
49   SUBROUTINE ice_thd_pnd
50      !!-------------------------------------------------------------------
51      !!               ***  ROUTINE ice_thd_pnd   ***
52      !!               
53      !! ** Purpose :   change melt pond fraction
54      !!               
55      !! ** Method  :   brut force
56      !!-------------------------------------------------------------------
57      !
58      SELECT CASE ( nice_pnd )
59      !
60      CASE (np_pndCST)   ;   CALL pnd_CST    !==  Constant melt ponds  ==!
61         !
62      CASE (np_pndH12)   ;   CALL pnd_H12    !==  Holland et al 2012 melt ponds  ==!
63         !
64      END SELECT
65      !
66   END SUBROUTINE ice_thd_pnd 
67
68
69   SUBROUTINE pnd_CST 
70      !!-------------------------------------------------------------------
71      !!                ***  ROUTINE pnd_CST  ***
72      !!
73      !! ** Purpose :   Compute melt pond evolution
74      !!
75      !! ** Method  :   Melt pond fraction and thickness are prescribed
76      !!                to non-zero values when t_su = 0C
77      !!
78      !! ** Tunable parameters : pond fraction (rn_apnd), pond depth (rn_hpnd)
79      !!               
80      !! ** Note   : Coupling with such melt ponds is only radiative
81      !!             Advection, ridging, rafting... are bypassed
82      !!
83      !! ** References : Bush, G.W., and Trump, D.J. (2017)
84      !!-------------------------------------------------------------------
85      INTEGER  ::   ji        ! loop indices
86      !!-------------------------------------------------------------------
87      DO ji = 1, npti
88         !
89         IF( a_i_1d(ji) > 0._wp .AND. t_su_1d(ji) >= rt0 ) THEN
90            a_ip_frac_1d(ji) = rn_apnd
91            h_ip_1d(ji)      = rn_hpnd   
92            a_ip_1d(ji)      = a_ip_frac_1d(ji) * a_i_1d(ji)
93         ELSE
94            a_ip_frac_1d(ji) = 0._wp
95            h_ip_1d(ji)      = 0._wp   
96            a_ip_1d(ji)      = 0._wp
97         ENDIF
98         !
99      END DO
100      !
101   END SUBROUTINE pnd_CST
102
103
104   SUBROUTINE pnd_H12
105      !!-------------------------------------------------------------------
106      !!                ***  ROUTINE pnd_H12  ***
107      !!
108      !! ** Purpose    : Compute melt pond evolution
109      !!
110      !! ** Method     : Empirical method. A fraction of meltwater is accumulated in ponds
111      !!                 and sent to ocean when surface is freezing
112      !!
113      !!                 pond growth:      Vp = Vp + dVmelt
114      !!                    with dVmelt = R/rhow * ( rhoi*dh_i + rhos*dh_s ) * a_i
115      !!                 pond contraction: Vp = Vp * exp(0.01*MAX(Tp-Tsu,0)/Tp)
116      !!                    with Tp = -2degC
117      !! 
118      !! ** Tunable parameters : (no real expertise yet, ideas?)
119      !!
120      !! ** Note       : Stolen from CICE for quick test of the melt pond
121      !!                 radiation and freshwater interfaces
122      !!                 Coupling can be radiative AND freshwater
123      !!                 Advection, ridging, rafting are called
124      !!
125      !! ** References : Holland, M. M. et al (J Clim 2012)
126      !!-------------------------------------------------------------------
127      REAL(wp), PARAMETER ::   zrmin       = 0.15_wp  ! minimum fraction of available meltwater retained for melt ponding
128      REAL(wp), PARAMETER ::   zrmax       = 0.70_wp  ! maximum     -           -         -         -            -
129      REAL(wp), PARAMETER ::   zpnd_aspect = 0.8_wp   ! pond aspect ratio
130      REAL(wp), PARAMETER ::   zTp         = -2._wp   ! reference temperature
131      !
132      REAL(wp) ::   zfr_mlt          ! fraction of available meltwater retained for melt ponding
133      REAL(wp) ::   zdv_mlt          ! available meltwater for melt ponding
134      REAL(wp) ::   z1_Tp            ! inverse reference temperature
135      REAL(wp) ::   z1_zpnd_aspect   ! inverse pond aspect ratio
136      REAL(wp) ::   zfac, zdum
137      !
138      INTEGER  ::   ji   ! loop indices
139      !!-------------------------------------------------------------------
140      z1_zpnd_aspect = 1._wp / zpnd_aspect
141      z1_Tp          = 1._wp / zTp 
142
143      DO ji = 1, npti
144         !                                                        !--------------------------------!
145         IF( h_i_1d(ji) < rn_himin) THEN                          ! Case ice thickness < rn_himin  !
146            !                                                     !--------------------------------!
147            !--- Remove ponds on thin ice
148            a_ip_1d(ji)      = 0._wp
149            a_ip_frac_1d(ji) = 0._wp
150            h_ip_1d(ji)      = 0._wp
151            !                                                     !--------------------------------!
152         ELSE                                                     ! Case ice thickness >= rn_himin !
153            !                                                     !--------------------------------!
154            v_ip_1d(ji) = h_ip_1d(ji) * a_ip_1d(ji)   ! record pond volume at previous time step
155            !
156            ! available meltwater for melt ponding [m, >0] and fraction
157            zdv_mlt = -( dh_i_sum(ji)*rhoi + dh_s_mlt(ji)*rhos ) * r1_rhow * a_i_1d(ji)
158            zfr_mlt = zrmin + ( zrmax - zrmin ) * a_i_1d(ji)  ! from CICE doc
159            !zfr_mlt = zrmin + zrmax * a_i_1d(ji)             ! from Holland paper
160            !
161            !--- Pond gowth ---!
162            ! v_ip should never be negative, otherwise code crashes
163            ! MV: as far as I saw, UM5 can create very small negative v_ip values (not Prather)
164            v_ip_1d(ji) = MAX( 0._wp, v_ip_1d(ji) + zfr_mlt * zdv_mlt )
165            !
166            ! melt pond mass flux (<0)
167            IF( ln_pnd_fwb .AND. zdv_mlt > 0._wp ) THEN
168               zfac = zfr_mlt * zdv_mlt * rhow * r1_Dt_ice
169               wfx_pnd_1d(ji) = wfx_pnd_1d(ji) - zfac
170               !
171               ! adjust ice/snow melting flux to balance melt pond flux (>0)
172               zdum = zfac / ( wfx_snw_sum_1d(ji) + wfx_sum_1d(ji) )
173               wfx_snw_sum_1d(ji) = wfx_snw_sum_1d(ji) * (1._wp + zdum)
174               wfx_sum_1d(ji)     = wfx_sum_1d(ji)     * (1._wp + zdum)
175            ENDIF
176            !
177            !--- Pond contraction (due to refreezing) ---!
178            v_ip_1d(ji) = v_ip_1d(ji) * EXP( 0.01_wp * MAX( zTp+rt0 - t_su_1d(ji), 0._wp ) * z1_Tp )
179            !
180            ! Set new pond area and depth assuming linear relation between h_ip and a_ip_frac
181            !    h_ip = zpnd_aspect * a_ip_frac = zpnd_aspect * a_ip/a_i
182            a_ip_1d(ji)      = SQRT( v_ip_1d(ji) * z1_zpnd_aspect * a_i_1d(ji) )
183            a_ip_frac_1d(ji) = a_ip_1d(ji) / a_i_1d(ji)
184            h_ip_1d(ji)      = zpnd_aspect * a_ip_frac_1d(ji)
185            !
186         ENDIF
187      END DO
188      !
189   END SUBROUTINE pnd_H12
190
191
192   SUBROUTINE ice_thd_pnd_init 
193      !!-------------------------------------------------------------------
194      !!                  ***  ROUTINE ice_thd_pnd_init   ***
195      !!
196      !! ** Purpose : Physical constants and parameters linked to melt ponds
197      !!              over sea ice
198      !!
199      !! ** Method  :  Read the namthd_pnd  namelist and check the melt pond 
200      !!               parameter values called at the first timestep (nit000)
201      !!
202      !! ** input   :   Namelist namthd_pnd 
203      !!-------------------------------------------------------------------
204      INTEGER  ::   ios, ioptio   ! Local integer
205      !!
206      NAMELIST/namthd_pnd/  ln_pnd_H12, ln_pnd_fwb, ln_pnd_CST, rn_apnd, rn_hpnd, ln_pnd_alb
207      !!-------------------------------------------------------------------
208      !
209      REWIND( numnam_ice_ref )              ! Namelist namthd_pnd  in reference namelist : Melt Ponds 
210      READ  ( numnam_ice_ref, namthd_pnd, IOSTAT = ios, ERR = 901)
211901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namthd_pnd  in reference namelist', lwp )
212      REWIND( numnam_ice_cfg )              ! Namelist namthd_pnd  in configuration namelist : Melt Ponds
213      READ  ( numnam_ice_cfg, namthd_pnd, IOSTAT = ios, ERR = 902 )
214902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namthd_pnd in configuration namelist', lwp )
215      IF(lwm) WRITE ( numoni, namthd_pnd )
216      !
217      IF(lwp) THEN                        ! control print
218         WRITE(numout,*)
219         WRITE(numout,*) 'ice_thd_pnd_init: ice parameters for melt ponds'
220         WRITE(numout,*) '~~~~~~~~~~~~~~~~'
221         WRITE(numout,*) '   Namelist namicethd_pnd:'
222         WRITE(numout,*) '      Evolutive melt pond fraction and depth (Holland et al 2012)  ln_pnd_H12 = ', ln_pnd_H12
223         WRITE(numout,*) '         Melt ponds store fresh water or not                       ln_pnd_fwb = ', ln_pnd_fwb
224         WRITE(numout,*) '      Prescribed melt pond fraction and depth                      ln_pnd_Cst = ', ln_pnd_CST
225         WRITE(numout,*) '         Prescribed pond fraction                                  rn_apnd    = ', rn_apnd
226         WRITE(numout,*) '         Prescribed pond depth                                     rn_hpnd    = ', rn_hpnd
227         WRITE(numout,*) '      Melt ponds affect albedo or not                              ln_pnd_alb = ', ln_pnd_alb
228      ENDIF
229      !
230      !                             !== set the choice of ice pond scheme ==!
231      ioptio = 0
232                                                            nice_pnd = np_pndNO
233      IF( ln_pnd_CST ) THEN   ;   ioptio = ioptio + 1   ;   nice_pnd = np_pndCST    ;   ENDIF
234      IF( ln_pnd_H12 ) THEN   ;   ioptio = ioptio + 1   ;   nice_pnd = np_pndH12    ;   ENDIF
235      IF( ioptio > 1 )   CALL ctl_stop( 'ice_thd_pnd_init: choose one and only one pond scheme (ln_pnd_H12 or ln_pnd_CST)' )
236      !
237      SELECT CASE( nice_pnd )
238      CASE( np_pndNO )         
239         IF(ln_pnd_fwb) THEN ; ln_pnd_fwb = .FALSE. ; CALL ctl_warn( 'ln_pnd_fwb=false when no ponds' ) ; ENDIF
240         IF(ln_pnd_alb) THEN ; ln_pnd_alb = .FALSE. ; CALL ctl_warn( 'ln_pnd_alb=false when no ponds' ) ; ENDIF
241      CASE( np_pndCST)
242         IF(ln_pnd_fwb) THEN ; ln_pnd_fwb = .FALSE. ; CALL ctl_warn( 'ln_pnd_fwb=false when ln_pnd_CST=true' ) ; ENDIF
243      END SELECT
244      !
245   END SUBROUTINE ice_thd_pnd_init
246   
247#else
248   !!----------------------------------------------------------------------
249   !!   Default option          Empty module          NO SI3 sea-ice model
250   !!----------------------------------------------------------------------
251#endif 
252
253   !!======================================================================
254END MODULE icethd_pnd 
Note: See TracBrowser for help on using the repository browser.