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_r7881_no_wrk_alloc/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/LIM_SRC_3/limthd_da.F90 @ 7910

Last change on this file since 7910 was 7910, checked in by timgraham, 7 years ago

All wrk_alloc removed

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