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.
limthd_da.F90 in branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limthd_da.F90 @ 8371

Last change on this file since 8371 was 8371, checked in by clem, 7 years ago

minor updates

File size: 9.4 KB
Line 
1MODULE limthd_da
2   !!======================================================================
3   !!                       ***  MODULE limthd_da ***
4   !! LIM-3 sea-ice :  computation of lateral melting in the ice
5   !!======================================================================
6   !! History :   4.0   ! 2016-03 (C. Rousset) original code
7   !!---------------------------------------------------------------------
8#if defined key_lim3
9   !!----------------------------------------------------------------------
10   !!   'key_lim3'                                      LIM-3 sea-ice model
11   !!----------------------------------------------------------------------
12   !!   lim_thd_da   : sea ice lateral melting
13   !!----------------------------------------------------------------------
14   USE par_oce        ! ocean parameters
15   USE phycst         ! physical constants (ocean directory)
16   USE ice            ! LIM variables
17   USE thd_ice        ! thermodynamic sea-ice variables
18   !
19   USE lib_mpp        ! MPP library
20   USE wrk_nemo       ! work arrays
21   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   lim_thd_da        ! called by limthd module
27
28   !!----------------------------------------------------------------------
29   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
30   !! $Id: limthd_da.F90 5123 2015-03-04 16:06:03Z clem $
31   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33CONTAINS
34
35   SUBROUTINE lim_thd_da
36      !!-------------------------------------------------------------------
37      !!                ***  ROUTINE lim_thd_da  ***   
38      !!   
39      !! ** Purpose :   computes sea ice lateral melting
40      !!
41      !! ** Method  :   dA/dt = - P * W   [s-1]
42      !!                   W = melting velocity [m.s-1]
43      !!                   P = perimeter of ice-ocean lateral interface normalized by grid cell area [m.m-2]
44      !!
45      !!                   W = m1 * (Tw -Tf)**m2                    --- originally from Josberger 1979 ---
46      !!                      (Tw - Tf) = elevation of water temp above freezing
47      !!                      m1 and m2 = (1.6e-6 , 1.36) best fit from field experiment near the coast of Prince Patrick Island (Perovich 1983) => static ice
48      !!                      m1 and m2 = (3.0e-6 , 1.36) best fit from MIZEX 84 experiment (Maykut and Perovich 1987) => moving ice
49      !!
50      !!                   P = N * pi * D                           --- from Rothrock and Thorndike 1984 ---
51      !!                      D = mean floe caliper diameter
52      !!                      N = number of floes = ice area / floe area(average) = A / (Cs * D**2)
53      !!                         A = ice concentration
54      !!                         Cs = deviation from a square (square:Cs=1 ; circle:Cs=pi/4 ; floe:Cs=0.66)
55      !!
56      !!                   D = Dmin * ( Astar / (Astar-A) )**beta   --- from Lupkes et al., 2012 (eq. 26-27) ---
57      !!                                                             
58      !!                      Astar = 1 / ( 1 - (Dmin/Dmax)**(1/beta) )
59      !!                      Dmin = minimum floe diameter (recommended to be 8m +- 20%)
60      !!                      Dmax = maximum floe diameter (recommended to be 300m, but it does not impact melting much except for Dmax<100m)
61      !!                      beta = 1.0 +-20% (recommended value)
62      !!                           = 0.3 best fit for western Fram Strait and Antarctica
63      !!                           = 1.4 best fit for eastern Fram Strait
64      !!
65      !! ** Tunable parameters  :   We propose to tune the lateral melting via 2 parameters
66      !!                               Dmin [6-10m]   => 6  vs 8m = +40% melting at the peak (A~0.5)
67      !!                                                 10 vs 8m = -20% melting
68      !!                               beta [0.8-1.2] => decrease = more melt and melt peaks toward higher concentration
69      !!                                                                  (A~0.5 for beta=1 ; A~0.8 for beta=0.2)
70      !!                                                 0.3 = best fit for western Fram Strait and Antarctica
71      !!                                                 1.4 = best fit for eastern Fram Strait
72      !!
73      !! ** Note   :   Former and more simple formulations for floe diameters can be found in Mai (1995),
74      !!               Birnbaum and Lupkes (2002), Lupkes and Birnbaum (2005). They are reviewed in Lupkes et al 2012
75      !!               A simpler implementation for CICE can be found in Bitz et al (2001) and Tsamados et al (2015)
76      !!
77      !! ** References
78      !!    Bitz, C. M., Holland, M. M., Weaver, A. J., & Eby, M. (2001).
79      !!              Simulating the ice‐thickness distribution in a coupled climate model.
80      !!              Journal of Geophysical Research: Oceans, 106(C2), 2441-2463.
81      !!    Josberger, E. G. (1979).
82      !!              Laminar and turbulent boundary layers adjacent to melting vertical ice walls in salt water
83      !!              (No. SCIENTIFIC-16). WASHINGTON UNIV SEATTLE DEPT OF ATMOSPHERIC SCIENCES.
84      !!    Lüpkes, C., Gryanik, V. M., Hartmann, J., & Andreas, E. L. (2012).
85      !!              A parametrization, based on sea ice morphology, of the neutral atmospheric drag coefficients
86      !!              for weather prediction and climate models.
87      !!              Journal of Geophysical Research: Atmospheres, 117(D13).
88      !!    Maykut, G. A., & Perovich, D. K. (1987).
89      !!              The role of shortwave radiation in the summer decay of a sea ice cover.
90      !!              Journal of Geophysical Research: Oceans, 92(C7), 7032-7044.
91      !!    Perovich, D. K. (1983).
92      !!              On the summer decay of a sea ice cover. (Doctoral dissertation, University of Washington).
93      !!    Rothrock, D. A., & Thorndike, A. S. (1984).
94      !!              Measuring the sea ice floe size distribution.
95      !!              Journal of Geophysical Research: Oceans, 89(C4), 6477-6486.
96      !!    Tsamados, M., Feltham, D., Petty, A., Schroeder, D., & Flocco, D. (2015).
97      !!              Processes controlling surface, bottom and lateral melt of Arctic sea ice in a state of the art sea ice model.
98      !!              Phil. Trans. R. Soc. A, 373(2052), 20140167.
99      !!---------------------------------------------------------------------
100      INTEGER  ::   ji     ! dummy loop indices
101      REAL(wp)            ::   zastar, zdfloe, zperi, zwlat, zda
102      REAL(wp), PARAMETER ::   zdmax = 300._wp
103      REAL(wp), PARAMETER ::   zcs   = 0.66_wp
104      REAL(wp), PARAMETER ::   zm1   = 3.e-6_wp
105      REAL(wp), PARAMETER ::   zm2   = 1.36_wp
106      !
107      REAL(wp), DIMENSION(jpij) ::   zda_tot
108      !!---------------------------------------------------------------------
109
110      !------------------------------------------------------------!
111      !------------------------------------------------------------!
112      zastar = 1._wp / ( 1._wp - (rn_dmin / zdmax)**(1._wp/rn_beta) )
113      DO ji = 1, nidx   
114         ! --- Calculate reduction of total sea ice concentration --- !
115         zdfloe = rn_dmin * ( zastar / ( zastar - at_i_1d(ji) ) )**rn_beta         ! Mean floe caliper diameter [m]
116         zperi  = at_i_1d(ji) * rpi / ( zcs * zdfloe )                             ! Mean perimeter of the floe = N*pi*D = (A/cs*D^2)*pi*D [m.m-2]
117         zwlat  = zm1 * ( MAX( 0._wp, sst_1d(ji) - ( t_bo_1d(ji) - rt0 ) ) )**zm2  ! Melt speed rate [m/s]
118         
119         zda_tot(ji) = MIN( zwlat * zperi * rdt_ice, at_i_1d(ji) )                 ! sea ice concentration decrease (>0)
120     
121         ! --- Distribute reduction among ice categories and calculate associated ice-ocean fluxes --- !
122         IF( a_i_1d(ji) > 0._wp ) THEN
123            ! decrease of concentration for the category jl
124            !    each category contributes to melting in proportion to its concentration
125            zda = MIN( a_i_1d(ji), zda_tot(ji) * a_i_1d(ji) / at_i_1d(ji) )
126           
127            ! Contribution to salt flux
128            sfx_lam_1d(ji) = sfx_lam_1d(ji) + rhoic *  ht_i_1d(ji) * zda * sm_i_1d(ji) * r1_rdtice
129           
130            ! Contribution to heat flux into the ocean [W.m-2], (<0) 
131            hfx_thd_1d(ji) = hfx_thd_1d(ji) - zda * r1_rdtice * ( ht_i_1d(ji) * r1_nlay_i * SUM( e_i_1d(ji,1:nlay_i) )  &
132                                                                + ht_s_1d(ji) * r1_nlay_s * SUM( e_s_1d(ji,1:nlay_s) ) ) 
133           
134            ! Contribution to mass flux
135            wfx_lam_1d(ji) =  wfx_lam_1d(ji) + zda * r1_rdtice * ( rhoic * ht_i_1d(ji) + rhosn * ht_s_1d(ji) )
136           
137            ! new concentration
138            a_i_1d(ji) = a_i_1d(ji) - zda
139           
140            ! ensure that ht_i = 0 where a_i = 0
141            IF( a_i_1d(ji) == 0._wp ) THEN
142               ht_i_1d(ji) = 0._wp
143               ht_s_1d(ji) = 0._wp
144            ENDIF
145         ENDIF
146      END DO
147      !
148   END SUBROUTINE lim_thd_da
149   
150#else
151   !!----------------------------------------------------------------------
152   !!   Default option         Dummy Module          No LIM-3 sea-ice model
153   !!----------------------------------------------------------------------
154CONTAINS
155   SUBROUTINE lim_thd_da          ! Empty routine
156   END SUBROUTINE lim_thd_da
157#endif
158   !!======================================================================
159END MODULE limthd_da
Note: See TracBrowser for help on using the repository browser.