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_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/icethd_da.F90 @ 8506

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

changes in style - part2 -

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