SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modi_glt_lmltsi_r.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 !GLT_LIC The GELATO model is a seaice model used in stand-alone or embedded mode.
6 !GLT_LIC It has been developed by Meteo-France. The holder of GELATO is Meteo-France.
7 !GLT_LIC
8 !GLT_LIC This software is governed by the CeCILL-C license under French law and biding
9 !GLT_LIC by the rules of distribution of free software. See the CeCILL-C_V1-en.txt
10 !GLT_LIC (English) and CeCILL-C_V1-fr.txt (French) for details. The CeCILL is a free
11 !GLT_LIC software license, explicitly compatible with the GNU GPL
12 !GLT_LIC (see http://www.gnu.org/licenses/license-list.en.html#CeCILL)
13 !GLT_LIC
14 !GLT_LIC The CeCILL-C licence agreement grants users the right to modify and re-use the
15 !GLT_LIC software governed by this free software license. The exercising of this right
16 !GLT_LIC is conditional upon the obligation to make available to the community the
17 !GLT_LIC modifications made to the source code of the software so as to contribute to
18 !GLT_LIC its evolution.
19 !GLT_LIC
20 !GLT_LIC In consideration of access to the source code and the rights to copy, modify
21 !GLT_LIC and redistribute granted by the license, users are provided only with a limited
22 !GLT_LIC warranty and the software's author, the holder of the economic rights, and the
23 !GLT_LIC successive licensors only have limited liability. In this respect, the risks
24 !GLT_LIC associated with loading, using, modifying and/or developing or reproducing the
25 !GLT_LIC software by the user are brought to the user's attention, given its Free
26 !GLT_LIC Software status, which may make it complicated to use, with the result that its
27 !GLT_LIC use is reserved for developers and experienced professionals having in-depth
28 !GLT_LIC computer knowledge. Users are therefore encouraged to load and test the
29 !GLT_LIC suitability of the software as regards their requirements in conditions enabling
30 !GLT_LIC the security of their systems and/or data to be ensured and, more generally, to
31 !GLT_LIC use and operate it in the same conditions of security.
32 !GLT_LIC
33 !GLT_LIC The GELATO sofware is cureently distibuted with the SURFEX software, available at
34 !GLT_LIC http://www.cnrm.meteo.fr/surfex. The fact that you download the software deemed that
35 !GLT_LIC you had knowledge of the CeCILL-C license and that you accept its terms.
36 !GLT_LIC Attempts to use this software in a way not complying with CeCILL-C license
37 !GLT_LIC may lead to prosecution.
38 !GLT_LIC
39 ! =======================================================================
40 ! ======================== MODULE modi_glt_lmltsi_r =========================
41 ! =======================================================================
42 !
43 ! Goal:
44 ! -----
45 ! Here the lateral sea ice ablation rate is assessed by means of a
46 ! Hakkinen & Mellor (1992) parameterization.
47 !
48 ! Method:
49 ! -------
50 ! Let a sea ice floe of thickness hsi[k] and concentration
51 ! fsi[k] (total concentration is fsit, undergoing bottom ablation
52 ! ( dhsi[k]<0 during time step dt ). The lateral ablation is supposed to
53 ! be :
54 ! dfsi[k] = 0.7 * fsi[k]/fsit * ( 1.-fsit ) * dhsi[k]/hsi[k]
55 !
56 ! The energy used for this process is taken from the ocean and
57 ! computed:
58 ! dE[k] = cpice0 * dfsi[k] * hsi[k]
59 !
60 ! Created : 2001/07 (D. Salas y Melia)
61 ! Taken out from thermo_ice routine.
62 ! Modified: 2009/06 (D. Salas y Melia)
63 ! Reduced grid
64 ! Modified: 2011/12 (A. Voldoire)
65 ! new ice/water fluxes interface CALL
66 !
67 ! ---------------------- BEGIN MODULE modi_glt_lmltsi_r ---------------------
68 !
69 !THXS_SFX!MODULE modi_glt_lmltsi_r
70 !THXS_SFX!INTERFACE
71 !THXS_SFX!!
72 !THXS_SFX!SUBROUTINE glt_lmltsi_r( tpmxl,tpsil,tpsit,tpdia,tptfl )
73 !THXS_SFX!!
74 !THXS_SFX! USE modd_types_glt
75 !THXS_SFX! USE modd_glt_param
76 !THXS_SFX! TYPE(t_mxl), DIMENSION(np), INTENT(in) :: &
77 !THXS_SFX! tpmxl
78 !THXS_SFX! TYPE(t_vtp), DIMENSION(nl,nt,np), INTENT(in) :: &
79 !THXS_SFX! tpsil
80 !THXS_SFX! TYPE(t_sit), DIMENSION(nt,np), INTENT(inout) :: &
81 !THXS_SFX! tpsit
82 !THXS_SFX! TYPE(t_dia), DIMENSION(np), INTENT(inout) :: &
83 !THXS_SFX! tpdia
84 !THXS_SFX! TYPE(t_tfl), DIMENSION(np), INTENT(inout) :: &
85 !THXS_SFX! tptfl
86 !THXS_SFX!END SUBROUTINE glt_lmltsi_r
87 !THXS_SFX!!
88 !THXS_SFX!END INTERFACE
89 !THXS_SFX!END MODULE modi_glt_lmltsi_r
90 !
91 ! ---------------------- END MODULE modi_glt_lmltsi_r -----------------------
92 !
93 !
94 !
95 ! -----------------------------------------------------------------------
96 ! ------------------------- SUBROUTINE glt_lmltsi_r -------------------------
97 !
98 SUBROUTINE glt_lmltsi_r &
99  ( tpmxl,tpsil,tpsit,tpdia,tptfl )
101  USE modd_types_glt
102  USE modd_glt_param
103  USE modi_glt_updtfl_r
104 !
105  IMPLICIT NONE
106 !
107 !* Arguments
108 !
109  TYPE(t_mxl), DIMENSION(np), INTENT(in) :: &
110  tpmxl
111  TYPE(t_vtp), DIMENSION(nl,nt,np), INTENT(in) :: &
112  tpsil
113  TYPE(t_sit), DIMENSION(nt,np), INTENT(inout) :: &
114  tpsit
115  TYPE(t_dia), DIMENSION(np), INTENT(inout) :: &
116  tpdia
117  TYPE(t_tfl), DIMENSION(np), INTENT(inout) :: &
118  tptfl
119 !
120 !* Local variables
121 !
122  INTEGER :: &
123  jl
124  REAL, DIMENSION(np) :: &
125  zdtml
126  REAL, DIMENSION(nt,np) :: &
127  zfsia,zdmsi,zdmsn,zmrate3,zent
128 !
129 !
130 !
131 ! 1. Initializations
132 ! ===================
133 !
134 ! .. Sea ice concentration field "after" lateral ablation
135 !
136  zfsia(:,:) = tpsit(:,:)%fsi
137 !
138 ! .. Total sea ice concentration field (3D expanded) --> for Hakkinen
139 !
140 ! zfsit(:) = SUM( tpsit(:,:)%fsi,DIM=1 )
141 ! zfsit3(:,:) = SPREAD( zfsit(:),1,nt )
142 !
143 ! .. Total ocean heat flux (3D expanded) --> for Hakkinen
144 !
145 ! zqoct3(:,:) = SPREAD( tpmxl(:)%qoc+tpmxl(:)%qml,1,nt )
146 !
147 !
148 !
149 ! 2. Compute sea ice concentration field after lateral melting
150 ! ============================================================
151 !
152 ! .. Hakkinen method : quite OK in the Arctic, too rough in the
153 ! Antarctic
154 !
155 ! WHERE ( tpsit(:,:)%hsi>=xhsimin .AND. zfsit3(:,:)>=epsil1 )
156 ! zdhsi(:,:) = -dtt*hofusni0*zqoct3(:,:)
157 ! zfsia(:,:) = zfsia(:,:) + &
158 ! 0.7*tpsit(:,:)%fsi/zfsit3(:,:)*( 1.-zfsit3(:,:) )* &
159 ! AMIN1( zdhsi(:,:),0. ) / tpsit(:,:)%hsi
160 ! zfsia(:,:) = AMAX1( zfsia(:,:),0. )
161 ! ENDWHERE
162 !
163 ! .. Steele et al. (1992), Maykut & Perovich (1987), summed up by
164 ! Schmidt et al. (2003) : certainly closer to the real world, but
165 ! requires glt_info on the geometry and size of floes ( xlmelt parameter ).
166 !
167  zdtml(:) = tpmxl(:)%tml - tpmxl(:)%mlf
168  zdtml(:) = amax1( zdtml(:), 0. )
169  zmrate3(:,:) = spread( xm1 * zdtml(:)**xm2,1,nt )
170 !
171 ! .. We suppose ice floes are squares:
172 ! xlmelt = P / A (P: perimeter of a floe, A its surface)
173 ! Let a be the characteristic size of a floe ; P=4*a, A=a*a
174 ! hence:
175 ! xlmelt = 4/a
176 ! The total ice fraction change should be:
177 ! dfsitot = -fsitot*[ 4/a*MR*dt ] = -fsitot*[ xlmelt*MR*dt ]
178 ! where MR is the lateral melting rate in m.s-1
179 ! But this is also true for every ice category (the intensity of the
180 ! lateral melting does not depend on the number of ice categories).
181 !
182  zfsia(:,:) = zfsia(:,:) * &
183  ( 1. - xlmelt*dtt*zmrate3(:,:) )
184  zfsia(:,:) = amax1( zfsia(:,:),0. )
185 !
186 ! .. Compute diagnostic
187 !
188  tpdia(:)%mrl = &
189  sum( ( zfsia(:,:)-tpsit(:,:)%fsi )* &
190  tpsit(:,:)%hsi, dim=1 ) * rhoice / dtt
191 !
192 !
193 !
194 ! 3. Energy conservation
195 ! ======================
196 !
197 ! It is assumed that the amount of energy needed to melt sea ice
198 ! laterally comes from the ocean.
199 !
200 !
201 ! 3.1. Compute involved masses of ice and snow
202 ! --------------------------------------------
203 !
204 ! .. Variation of sea ice mass due to lateral melting
205 !
206  zdmsi(:,:) = rhoice * &
207  ( zfsia(:,:)-tpsit(:,:)%fsi ) * tpsit(:,:)%hsi
208 !
209 ! .. Variation of snow mass due to lateral melting
210 !
211  zdmsn(:,:) = tpsit(:,:)%rsn * &
212  ( zfsia(:,:)-tpsit(:,:)%fsi ) * tpsit(:,:)%hsn
213 !
214 !
215 ! 3.2. Massic gltools_enthalpy and salinity of removed ice
216 ! -------------------------------------------------
217 !
218 ! .. Massic gltools_enthalpy
219 !
220  zent(:,:) = 0.
221  DO jl=1,nilay
222  zent(:,:) = zent(:,:) + &
223  sf3t(nilay+1-jl)*tpsil(jl,:,:)%ent
224  END DO
225 !
226 !
227 ! 3.3. Update water, heat and salt fluxes affecting the ocean
228 ! ------------------------------------------------------------
229 !
230 ! .. This is the contribution of sea ice melting
231 !
232  CALL glt_updtfl_r( 'I2O',tpmxl,tptfl,zdmsi,pent=zent,psalt=tpsit%ssi )
233 !
234 !
235 ! 3.4. Massic gltools_enthalpy of removed snow
236 ! -------------------------------------
237 !
238  zent(:,:) = sum( tpsil(nilay+1:nl,:,:)%ent, dim=1 )/float(nslay)
239 !
240 !
241 ! 3.5. Update water, heat and salt fluxes affecting the ocean
242 ! ------------------------------------------------------------
243 !
244  CALL glt_updtfl_r( 'FW2O',tpmxl,tptfl,zdmsn,pent=zent )
245  tpdia(:)%snml = sum( zdmsn(:,:), dim=1 ) / dtt
246 !
247 !
248 !
249 ! 4. Update ice state
250 ! =====================================
251 !
252 ! .. Concentration field
253 !
254  tpsit(:,:)%fsi = zfsia(:,:)
255 !
256 ! .. If necessary, re-initialize sea ice with nil concentration
257 !
258  WHERE ( tpsit(:,:)%fsi<epsil1 .AND. tpsit(:,:)%hsi>epsil1 )
259  tpsit(:,:)%esi = .false.
260  tpsit(:,:)%fsi = 0.
261  tpsit(:,:)%hsi = 0.
262  tpsit(:,:)%asn = albw
263  tpsit(:,:)%hsn = 0.
264  tpsit(:,:)%rsn = rhosnwmin
265  ENDWHERE
266 !
267  IF ( niceage==1 ) THEN
268  WHERE ( tpsit(:,:)%fsi<epsil1 .AND. tpsit(:,:)%hsi>=epsil1 )
269  tpsit(:,:)%age = 0.
270  ENDWHERE
271  ENDIF
272 !
273  IF ( nicesal==1 ) THEN
274  WHERE ( tpsit(:,:)%fsi<epsil1 .AND. tpsit(:,:)%hsi>=epsil1 )
275  tpsit(:,:)%ssi = 0.
276  ENDWHERE
277  ENDIF
278 !
279  IF ( nmponds==1 ) THEN
280  WHERE ( tpsit(:,:)%fsi<epsil1 .AND. tpsit(:,:)%hsi>=epsil1 )
281  tpsit(:,:)%vmp = 0.
282  ENDWHERE
283  ENDIF
284 !
285 END SUBROUTINE glt_lmltsi_r
286 
287 ! ----------------------- END SUBROUTINE glt_lmltsi_r -----------------------
288 ! -----------------------------------------------------------------------
subroutine glt_updtfl_r(hflag, tpmxl, tptfl, pdmass, pent, psalt)
subroutine glt_lmltsi_r(tpmxl, tpsil, tpsit, tpdia, tptfl)