1 | MODULE limrhg |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE limrhg *** |
---|
4 | !! Ice rheology : sea ice rheology |
---|
5 | !!====================================================================== |
---|
6 | #if defined key_lim3 |
---|
7 | !!---------------------------------------------------------------------- |
---|
8 | !! 'key_lim3' LIM3 sea-ice model |
---|
9 | !!---------------------------------------------------------------------- |
---|
10 | !! lim_rhg : computes ice velocities |
---|
11 | !!---------------------------------------------------------------------- |
---|
12 | !! * Modules used |
---|
13 | USE phycst |
---|
14 | USE par_oce |
---|
15 | USE ice_oce ! ice variables |
---|
16 | USE dom_oce |
---|
17 | USE dom_ice |
---|
18 | USE sbc_ice ! Surface boundary condition: ice fields |
---|
19 | USE ice |
---|
20 | USE iceini |
---|
21 | USE lbclnk |
---|
22 | USE lib_mpp |
---|
23 | USE in_out_manager ! I/O manager |
---|
24 | USE limitd_me |
---|
25 | USE prtctl ! Print control |
---|
26 | |
---|
27 | |
---|
28 | IMPLICIT NONE |
---|
29 | PRIVATE |
---|
30 | |
---|
31 | !! * Routine accessibility |
---|
32 | PUBLIC lim_rhg ! routine called by lim_dyn |
---|
33 | |
---|
34 | !! * Substitutions |
---|
35 | # include "vectopt_loop_substitute.h90" |
---|
36 | |
---|
37 | !! * Module variables |
---|
38 | REAL(wp) :: & ! constant values |
---|
39 | rzero = 0.e0 , & |
---|
40 | rone = 1.e0 |
---|
41 | !!---------------------------------------------------------------------- |
---|
42 | !! LIM 3.0, UCL-LOCEAN-IPSL (2008) |
---|
43 | !! $Id$ |
---|
44 | !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) |
---|
45 | !!---------------------------------------------------------------------- |
---|
46 | |
---|
47 | CONTAINS |
---|
48 | |
---|
49 | SUBROUTINE lim_rhg( k_j1, k_jpj ) |
---|
50 | |
---|
51 | !!------------------------------------------------------------------- |
---|
52 | !! *** SUBROUTINE lim_rhg *** |
---|
53 | !! EVP-C-grid |
---|
54 | !! |
---|
55 | !! ** purpose : determines sea ice drift from wind stress, ice-ocean |
---|
56 | !! stress and sea-surface slope. Ice-ice interaction is described by |
---|
57 | !! a non-linear elasto-viscous-plastic (EVP) law including shear |
---|
58 | !! strength and a bulk rheology (Hunke and Dukowicz, 2002). |
---|
59 | !! |
---|
60 | !! The points in the C-grid look like this, dear reader |
---|
61 | !! |
---|
62 | !! (ji,jj) |
---|
63 | !! | |
---|
64 | !! | |
---|
65 | !! (ji-1,jj) | (ji,jj) |
---|
66 | !! --------- |
---|
67 | !! | | |
---|
68 | !! | (ji,jj) |------(ji,jj) |
---|
69 | !! | | |
---|
70 | !! --------- |
---|
71 | !! (ji-1,jj-1) (ji,jj-1) |
---|
72 | !! |
---|
73 | !! ** Inputs : - wind forcing (stress), oceanic currents |
---|
74 | !! ice total volume (vt_i) per unit area |
---|
75 | !! snow total volume (vt_s) per unit area |
---|
76 | !! |
---|
77 | !! ** Action : - compute u_ice, v_ice : the components of the |
---|
78 | !! sea-ice velocity vector |
---|
79 | !! - compute delta_i, shear_i, divu_i, which are inputs |
---|
80 | !! of the ice thickness distribution |
---|
81 | !! |
---|
82 | !! ** Steps : 1) Compute ice snow mass, ice strength |
---|
83 | !! 2) Compute wind, oceanic stresses, mass terms and |
---|
84 | !! coriolis terms of the momentum equation |
---|
85 | !! 3) Solve the momentum equation (iterative procedure) |
---|
86 | !! 4) Prevent high velocities if the ice is thin |
---|
87 | !! 5) Recompute invariants of the strain rate tensor |
---|
88 | !! which are inputs of the ITD, store stress |
---|
89 | !! for the next time step |
---|
90 | !! 6) Control prints of residual (convergence) |
---|
91 | !! and charge ellipse. |
---|
92 | !! The user should make sure that the parameters |
---|
93 | !! nevp, telast and creepl maintain stress state |
---|
94 | !! on the charge ellipse for plastic flow |
---|
95 | !! e.g. in the Canadian Archipelago |
---|
96 | !! |
---|
97 | !! ** References : Hunke and Dukowicz, JPO97 |
---|
98 | !! Bouillon et al., 08, in prep (update this when |
---|
99 | !! published) |
---|
100 | !! Vancoppenolle et al., OM08 |
---|
101 | !! |
---|
102 | !! History : |
---|
103 | !! 1.0 ! 07-03 (M.A. Morales Maqueda, S. Bouillon) |
---|
104 | !! 2.0 ! 08-03 M. Vancoppenolle : LIM3 |
---|
105 | !! |
---|
106 | !!------------------------------------------------------------------- |
---|
107 | ! * Arguments |
---|
108 | ! |
---|
109 | INTEGER, INTENT(in) :: & |
---|
110 | k_j1 , & !: southern j-index for ice computation |
---|
111 | k_jpj !: northern j-index for ice computation |
---|
112 | |
---|
113 | ! * Local variables |
---|
114 | INTEGER :: ji, jj !: dummy loop indices |
---|
115 | |
---|
116 | INTEGER :: & |
---|
117 | jter !: temporary integers |
---|
118 | |
---|
119 | CHARACTER (len=50) :: charout |
---|
120 | |
---|
121 | REAL(wp) :: & |
---|
122 | zt11, zt12, zt21, zt22, & !: temporary scalars |
---|
123 | ztagnx, ztagny, & !: wind stress on U/V points |
---|
124 | delta ! |
---|
125 | |
---|
126 | REAL(wp) :: & |
---|
127 | za, & !: |
---|
128 | zstms, & !: temporary scalar for ice strength |
---|
129 | zsang, & !: temporary scalar for coriolis term |
---|
130 | zmask !: mask for the computation of ice mass |
---|
131 | |
---|
132 | REAL(wp),DIMENSION(jpi,jpj) :: & |
---|
133 | zpresh , & !: temporary array for ice strength |
---|
134 | zpreshc , & !: Ice strength on grid cell corners (zpreshc) |
---|
135 | zfrld1, zfrld2, & !: lead fraction on U/V points |
---|
136 | zmass1, zmass2, & !: ice/snow mass on U/V points |
---|
137 | zcorl1, zcorl2, & !: coriolis parameter on U/V points |
---|
138 | za1ct, za2ct , & !: temporary arrays |
---|
139 | zc1 , & !: ice mass |
---|
140 | zusw , & !: temporary weight for the computation |
---|
141 | !: of ice strength |
---|
142 | u_oce1, v_oce1, & !: ocean u/v component on U points |
---|
143 | u_oce2, v_oce2, & !: ocean u/v component on V points |
---|
144 | u_ice2, & !: ice u component on V point |
---|
145 | v_ice1 !: ice v component on U point |
---|
146 | |
---|
147 | REAL(wp) :: & |
---|
148 | dtevp, & !: time step for subcycling |
---|
149 | dtotel, & !: |
---|
150 | ecc2, & !: square of yield ellipse eccenticity |
---|
151 | z0, & !: temporary scalar |
---|
152 | zr, & !: temporary scalar |
---|
153 | zcca, zccb, & !: temporary scalars |
---|
154 | zu_ice2, & !: |
---|
155 | zv_ice1, & !: |
---|
156 | zddc, zdtc, & !: temporary array for delta on corners |
---|
157 | zdst, & !: temporary array for delta on centre |
---|
158 | zdsshx, zdsshy, & !: term for the gradient of ocean surface |
---|
159 | sigma1, sigma2 !: internal ice stress |
---|
160 | |
---|
161 | REAL(wp),DIMENSION(jpi,jpj) :: & |
---|
162 | zf1, zf2 !: arrays for internal stresses |
---|
163 | |
---|
164 | REAL(wp),DIMENSION(jpi,jpj) :: & |
---|
165 | zdd, zdt, & !: Divergence and tension at centre of grid cells |
---|
166 | zds, & !: Shear on northeast corner of grid cells |
---|
167 | deltat, & !: Delta at centre of grid cells |
---|
168 | deltac, & !: Delta on corners |
---|
169 | zs1, zs2, & !: Diagonal stress tensor components zs1 and zs2 |
---|
170 | zs12 !: Non-diagonal stress tensor component zs12 |
---|
171 | |
---|
172 | REAL(wp) :: & |
---|
173 | zresm , & !: Maximal error on ice velocity |
---|
174 | zindb , & !: ice (1) or not (0) |
---|
175 | zdummy !: dummy argument |
---|
176 | |
---|
177 | REAL(wp),DIMENSION(jpi,jpj) :: & |
---|
178 | zu_ice , & !: Ice velocity on previous time step |
---|
179 | zv_ice , & |
---|
180 | zresr !: Local error on velocity |
---|
181 | |
---|
182 | ! |
---|
183 | !------------------------------------------------------------------------------! |
---|
184 | ! 1) Ice-Snow mass (zc1), ice strength (zpresh) ! |
---|
185 | !------------------------------------------------------------------------------! |
---|
186 | ! |
---|
187 | ! Put every vector to 0 |
---|
188 | zpresh(:,:) = 0.0 ; zc1(:,:) = 0.0 |
---|
189 | zpreshc(:,:) = 0.0 |
---|
190 | u_ice2(:,:) = 0.0 ; v_ice1(:,:) = 0.0 |
---|
191 | zdd(:,:) = 0.0 ; zdt(:,:) = 0.0 ; zds(:,:) = 0.0 |
---|
192 | |
---|
193 | ! Ice strength on T-points |
---|
194 | CALL lim_itd_me_icestrength(ridge_scheme_swi) |
---|
195 | |
---|
196 | ! Ice mass and temp variables |
---|
197 | !CDIR NOVERRCHK |
---|
198 | DO jj = k_j1 , k_jpj |
---|
199 | !CDIR NOVERRCHK |
---|
200 | DO ji = 1 , jpi |
---|
201 | zc1(ji,jj) = tms(ji,jj) * ( rhosn * vt_s(ji,jj) + rhoic * vt_i(ji,jj) ) |
---|
202 | zpresh(ji,jj) = tms(ji,jj) * strength(ji,jj) / 2. |
---|
203 | ! tmi = 1 where there is ice or on land |
---|
204 | tmi(ji,jj) = 1.0 - ( 1.0 - MAX( 0.0 , SIGN ( 1.0 , vt_i(ji,jj) - & |
---|
205 | epsd ) ) ) * tms(ji,jj) |
---|
206 | END DO |
---|
207 | END DO |
---|
208 | |
---|
209 | ! Ice strength on grid cell corners (zpreshc) |
---|
210 | ! needed for calculation of shear stress |
---|
211 | !CDIR NOVERRCHK |
---|
212 | DO jj = k_j1+1, k_jpj-1 |
---|
213 | !CDIR NOVERRCHK |
---|
214 | DO ji = 2, jpim1 !RB caution no fs_ (ji+1,jj+1) |
---|
215 | zstms = tms(ji+1,jj+1) * wght(ji+1,jj+1,2,2) + & |
---|
216 | & tms(ji,jj+1) * wght(ji+1,jj+1,1,2) + & |
---|
217 | & tms(ji+1,jj) * wght(ji+1,jj+1,2,1) + & |
---|
218 | & tms(ji,jj) * wght(ji+1,jj+1,1,1) |
---|
219 | zusw(ji,jj) = 1.0 / MAX( zstms, epsd ) |
---|
220 | zpreshc(ji,jj) = ( zpresh(ji+1,jj+1) * wght(ji+1,jj+1,2,2) + & |
---|
221 | & zpresh(ji,jj+1) * wght(ji+1,jj+1,1,2) + & |
---|
222 | & zpresh(ji+1,jj) * wght(ji+1,jj+1,2,1) + & |
---|
223 | & zpresh(ji,jj) * wght(ji+1,jj+1,1,1) & |
---|
224 | & ) * zusw(ji,jj) |
---|
225 | END DO |
---|
226 | END DO |
---|
227 | |
---|
228 | CALL lbc_lnk( zpreshc(:,:), 'F', 1. ) |
---|
229 | ! |
---|
230 | !------------------------------------------------------------------------------! |
---|
231 | ! 2) Wind / ocean stress, mass terms, coriolis terms |
---|
232 | !------------------------------------------------------------------------------! |
---|
233 | ! |
---|
234 | ! Wind stress, coriolis and mass terms on the sides of the squares |
---|
235 | ! zfrld1: lead fraction on U-points |
---|
236 | ! zfrld2: lead fraction on V-points |
---|
237 | ! zmass1: ice/snow mass on U-points |
---|
238 | ! zmass2: ice/snow mass on V-points |
---|
239 | ! zcorl1: Coriolis parameter on U-points |
---|
240 | ! zcorl2: Coriolis parameter on V-points |
---|
241 | ! (ztagnx,ztagny): wind stress on U/V points |
---|
242 | ! u_oce1: ocean u component on u points |
---|
243 | ! v_oce1: ocean v component on u points |
---|
244 | ! u_oce2: ocean u component on v points |
---|
245 | ! v_oce2: ocean v component on v points |
---|
246 | |
---|
247 | DO jj = k_j1+1, k_jpj-1 |
---|
248 | DO ji = fs_2, fs_jpim1 |
---|
249 | |
---|
250 | zt11 = tms(ji,jj)*e1t(ji,jj) |
---|
251 | zt12 = tms(ji+1,jj)*e1t(ji+1,jj) |
---|
252 | zt21 = tms(ji,jj)*e2t(ji,jj) |
---|
253 | zt22 = tms(ji,jj+1)*e2t(ji,jj+1) |
---|
254 | |
---|
255 | ! Leads area. |
---|
256 | zfrld1(ji,jj) = ( zt12 * ( 1.0 - at_i(ji,jj) ) + & |
---|
257 | & zt11 * ( 1.0 - at_i(ji+1,jj) ) ) / ( zt11 + zt12 + epsd ) |
---|
258 | zfrld2(ji,jj) = ( zt22 * ( 1.0 - at_i(ji,jj) ) + & |
---|
259 | & zt21 * ( 1.0 - at_i(ji,jj+1) ) ) / ( zt21 + zt22 + epsd ) |
---|
260 | |
---|
261 | ! Mass, coriolis coeff. and currents |
---|
262 | zmass1(ji,jj) = ( zt12*zc1(ji,jj) + zt11*zc1(ji+1,jj) ) / (zt11+zt12+epsd) |
---|
263 | zmass2(ji,jj) = ( zt22*zc1(ji,jj) + zt21*zc1(ji,jj+1) ) / (zt21+zt22+epsd) |
---|
264 | zcorl1(ji,jj) = zmass1(ji,jj) * ( e1t(ji+1,jj)*fcor(ji,jj) + & |
---|
265 | e1t(ji,jj)*fcor(ji+1,jj) ) & |
---|
266 | / (e1t(ji,jj) + e1t(ji+1,jj) + epsd ) |
---|
267 | zcorl2(ji,jj) = zmass2(ji,jj) * ( e2t(ji,jj+1)*fcor(ji,jj) + & |
---|
268 | e2t(ji,jj)*fcor(ji,jj+1) ) & |
---|
269 | / ( e2t(ji,jj+1) + e2t(ji,jj) + epsd ) |
---|
270 | ! |
---|
271 | u_oce1(ji,jj) = u_oce(ji,jj) |
---|
272 | v_oce2(ji,jj) = v_oce(ji,jj) |
---|
273 | |
---|
274 | ! Ocean has no slip boundary condition |
---|
275 | v_oce1(ji,jj) = 0.5*( (v_oce(ji,jj)+v_oce(ji,jj-1))*e1t(ji,jj) & |
---|
276 | & +(v_oce(ji+1,jj)+v_oce(ji+1,jj-1))*e1t(ji+1,jj)) & |
---|
277 | & /(e1t(ji+1,jj)+e1t(ji,jj)) * tmu(ji,jj) |
---|
278 | |
---|
279 | u_oce2(ji,jj) = 0.5*((u_oce(ji,jj)+u_oce(ji-1,jj))*e2t(ji,jj) & |
---|
280 | & +(u_oce(ji,jj+1)+u_oce(ji-1,jj+1))*e2t(ji,jj+1)) & |
---|
281 | & / (e2t(ji,jj+1)+e2t(ji,jj)) * tmv(ji,jj) |
---|
282 | |
---|
283 | ! Wind stress. |
---|
284 | ztagnx = ( 1. - zfrld1(ji,jj) ) * utaui_ice(ji,jj) |
---|
285 | ztagny = ( 1. - zfrld2(ji,jj) ) * vtaui_ice(ji,jj) |
---|
286 | |
---|
287 | ! Computation of the velocity field taking into account the ice internal interaction. |
---|
288 | ! Terms that are independent of the velocity field. |
---|
289 | |
---|
290 | ! SB On utilise maintenant le gradient de la pente de l'ocean |
---|
291 | ! include it later |
---|
292 | ! zdsshx = (ssh_io(ji+1,jj) - ssh_io(ji,jj))/e1u(ji,jj) |
---|
293 | ! zdsshy = (ssh_io(ji,jj+1) - ssh_io(ji,jj))/e2v(ji,jj) |
---|
294 | |
---|
295 | zdsshx = 0.0 |
---|
296 | zdsshy = 0.0 |
---|
297 | |
---|
298 | za1ct(ji,jj) = ztagnx - zmass1(ji,jj) * grav * zdsshx |
---|
299 | za2ct(ji,jj) = ztagny - zmass2(ji,jj) * grav * zdsshy |
---|
300 | |
---|
301 | END DO |
---|
302 | END DO |
---|
303 | |
---|
304 | ! |
---|
305 | !------------------------------------------------------------------------------! |
---|
306 | ! 3) Solution of the momentum equation, iterative procedure |
---|
307 | !------------------------------------------------------------------------------! |
---|
308 | ! |
---|
309 | ! Time step for subcycling |
---|
310 | dtevp = rdt_ice / nevp |
---|
311 | dtotel = dtevp / ( 2.0 * telast ) |
---|
312 | |
---|
313 | !-ecc2: square of yield ellipse eccenticrity (reminder: must become a namelist parameter) |
---|
314 | ecc2 = ecc*ecc |
---|
315 | |
---|
316 | !-Initialise stress tensor |
---|
317 | zs1(:,:) = stress1_i(:,:) |
---|
318 | zs2(:,:) = stress2_i(:,:) |
---|
319 | zs12(:,:) = stress12_i(:,:) |
---|
320 | |
---|
321 | !----------------------! |
---|
322 | DO jter = 1 , nevp ! loop over jter ! |
---|
323 | !----------------------! |
---|
324 | DO jj = k_j1, k_jpj-1 |
---|
325 | zu_ice(:,jj) = u_ice(:,jj) ! velocity at previous time step |
---|
326 | zv_ice(:,jj) = v_ice(:,jj) |
---|
327 | END DO |
---|
328 | |
---|
329 | DO jj = k_j1+1, k_jpj-1 |
---|
330 | DO ji = fs_2, jpim1 !RB bug no vect opt due to tmi |
---|
331 | |
---|
332 | ! |
---|
333 | !- Divergence, tension and shear (Section a. Appendix B of Hunke & Dukowicz, 2002) |
---|
334 | !- zdd(:,:), zdt(:,:): divergence and tension at centre of grid cells |
---|
335 | !- zds(:,:): shear on northeast corner of grid cells |
---|
336 | ! |
---|
337 | !- IMPORTANT REMINDER: Dear Gurvan, note that, the way these terms are coded, |
---|
338 | ! there are many repeated calculations. |
---|
339 | ! Speed could be improved by regrouping terms. For |
---|
340 | ! the moment, however, the stress is on clarity of coding to avoid |
---|
341 | ! bugs (Martin, for Miguel). |
---|
342 | ! |
---|
343 | !- ALSO: arrays zdd, zdt, zds and delta could |
---|
344 | ! be removed in the future to minimise memory demand. |
---|
345 | ! |
---|
346 | !- MORE NOTES: Note that we are calculating deformation rates and stresses on the corners of |
---|
347 | ! grid cells, exactly as in the B grid case. For simplicity, the indexation on |
---|
348 | ! the corners is the same as in the B grid. |
---|
349 | ! |
---|
350 | ! |
---|
351 | zdd(ji,jj) = ( e2u(ji,jj)*u_ice(ji,jj) & |
---|
352 | & -e2u(ji-1,jj)*u_ice(ji-1,jj) & |
---|
353 | & +e1v(ji,jj)*v_ice(ji,jj) & |
---|
354 | & -e1v(ji,jj-1)*v_ice(ji,jj-1) & |
---|
355 | & ) & |
---|
356 | & / area(ji,jj) |
---|
357 | |
---|
358 | zdt(ji,jj) = ( ( u_ice(ji,jj)/e2u(ji,jj) & |
---|
359 | & -u_ice(ji-1,jj)/e2u(ji-1,jj) & |
---|
360 | & )*e2t(ji,jj)*e2t(ji,jj) & |
---|
361 | & -( v_ice(ji,jj)/e1v(ji,jj) & |
---|
362 | & -v_ice(ji,jj-1)/e1v(ji,jj-1) & |
---|
363 | & )*e1t(ji,jj)*e1t(ji,jj) & |
---|
364 | & ) & |
---|
365 | & / area(ji,jj) |
---|
366 | |
---|
367 | ! |
---|
368 | zds(ji,jj) = ( ( u_ice(ji,jj+1)/e1u(ji,jj+1) & |
---|
369 | & -u_ice(ji,jj)/e1u(ji,jj) & |
---|
370 | & )*e1f(ji,jj)*e1f(ji,jj) & |
---|
371 | & +( v_ice(ji+1,jj)/e2v(ji+1,jj) & |
---|
372 | & -v_ice(ji,jj)/e2v(ji,jj) & |
---|
373 | & )*e2f(ji,jj)*e2f(ji,jj) & |
---|
374 | & ) & |
---|
375 | & / ( e1f(ji,jj) * e2f(ji,jj) ) * ( 2.0 - tmf(ji,jj) ) & |
---|
376 | & * tmi(ji,jj) * tmi(ji,jj+1) & |
---|
377 | & * tmi(ji+1,jj) * tmi(ji+1,jj+1) |
---|
378 | |
---|
379 | |
---|
380 | v_ice1(ji,jj) = 0.5*( (v_ice(ji,jj)+v_ice(ji,jj-1))*e1t(ji+1,jj) & |
---|
381 | & +(v_ice(ji+1,jj)+v_ice(ji+1,jj-1))*e1t(ji,jj)) & |
---|
382 | & /(e1t(ji+1,jj)+e1t(ji,jj)) * tmu(ji,jj) |
---|
383 | |
---|
384 | u_ice2(ji,jj) = 0.5*( (u_ice(ji,jj)+u_ice(ji-1,jj))*e2t(ji,jj+1) & |
---|
385 | & +(u_ice(ji,jj+1)+u_ice(ji-1,jj+1))*e2t(ji,jj)) & |
---|
386 | & /(e2t(ji,jj+1)+e2t(ji,jj)) * tmv(ji,jj) |
---|
387 | |
---|
388 | END DO |
---|
389 | END DO |
---|
390 | CALL lbc_lnk( v_ice1(:,:), 'U', -1. ) |
---|
391 | CALL lbc_lnk( u_ice2(:,:), 'V', -1. ) |
---|
392 | |
---|
393 | !CDIR NOVERRCHK |
---|
394 | DO jj = k_j1+1, k_jpj-1 |
---|
395 | !CDIR NOVERRCHK |
---|
396 | DO ji = fs_2, fs_jpim1 |
---|
397 | |
---|
398 | !- Calculate Delta at centre of grid cells |
---|
399 | zdst = ( e2u( ji , jj ) * v_ice1(ji,jj) & |
---|
400 | & - e2u( ji-1, jj ) * v_ice1(ji-1,jj) & |
---|
401 | & + e1v( ji , jj ) * u_ice2(ji,jj) & |
---|
402 | & - e1v( ji , jj-1 ) * u_ice2(ji,jj-1) & |
---|
403 | & ) & |
---|
404 | & / area(ji,jj) |
---|
405 | |
---|
406 | delta = SQRT( zdd(ji,jj)*zdd(ji,jj) + & |
---|
407 | & ( zdt(ji,jj)*zdt(ji,jj) + zdst*zdst ) * usecc2 ) |
---|
408 | deltat(ji,jj) = MAX( SQRT(zdd(ji,jj)**2 + & |
---|
409 | (zdt(ji,jj)**2 + zdst**2)*usecc2), creepl ) |
---|
410 | |
---|
411 | !-Calculate stress tensor components zs1 and zs2 |
---|
412 | !-at centre of grid cells (see section 3.5 of CICE user's guide). |
---|
413 | zs1(ji,jj) = ( zs1(ji,jj) & |
---|
414 | & - dtotel*( ( 1.0 - alphaevp) * zs1(ji,jj) + & |
---|
415 | & ( delta / deltat(ji,jj) - zdd(ji,jj) / deltat(ji,jj) ) & |
---|
416 | * zpresh(ji,jj) ) ) & |
---|
417 | & / ( 1.0 + alphaevp * dtotel ) |
---|
418 | |
---|
419 | zs2(ji,jj) = ( zs2(ji,jj) & |
---|
420 | & - dtotel*((1.0-alphaevp)*ecc2*zs2(ji,jj) - & |
---|
421 | zdt(ji,jj)/deltat(ji,jj)*zpresh(ji,jj)) ) & |
---|
422 | & / ( 1.0 + alphaevp*ecc2*dtotel ) |
---|
423 | |
---|
424 | END DO |
---|
425 | END DO |
---|
426 | |
---|
427 | CALL lbc_lnk( zs1(:,:), 'T', 1. ) |
---|
428 | CALL lbc_lnk( zs2(:,:), 'T', 1. ) |
---|
429 | |
---|
430 | !CDIR NOVERRCHK |
---|
431 | DO jj = k_j1+1, k_jpj-1 |
---|
432 | !CDIR NOVERRCHK |
---|
433 | DO ji = fs_2, fs_jpim1 |
---|
434 | !- Calculate Delta on corners |
---|
435 | zddc = ( ( v_ice1(ji,jj+1)/e1u(ji,jj+1) & |
---|
436 | & -v_ice1(ji,jj)/e1u(ji,jj) & |
---|
437 | & )*e1f(ji,jj)*e1f(ji,jj) & |
---|
438 | & +( u_ice2(ji+1,jj)/e2v(ji+1,jj) & |
---|
439 | & -u_ice2(ji,jj)/e2v(ji,jj) & |
---|
440 | & )*e2f(ji,jj)*e2f(ji,jj) & |
---|
441 | & ) & |
---|
442 | & / ( e1f(ji,jj) * e2f(ji,jj) ) |
---|
443 | |
---|
444 | zdtc = (-( v_ice1(ji,jj+1)/e1u(ji,jj+1) & |
---|
445 | & -v_ice1(ji,jj)/e1u(ji,jj) & |
---|
446 | & )*e1f(ji,jj)*e1f(ji,jj) & |
---|
447 | & +( u_ice2(ji+1,jj)/e2v(ji+1,jj) & |
---|
448 | & -u_ice2(ji,jj)/e2v(ji,jj) & |
---|
449 | & )*e2f(ji,jj)*e2f(ji,jj) & |
---|
450 | & ) & |
---|
451 | & / ( e1f(ji,jj) * e2f(ji,jj) ) |
---|
452 | |
---|
453 | deltac(ji,jj) = SQRT(zddc**2+(zdtc**2+zds(ji,jj)**2)*usecc2) + creepl |
---|
454 | |
---|
455 | !-Calculate stress tensor component zs12 at corners (see section 3.5 of CICE user's guide). |
---|
456 | zs12(ji,jj) = ( zs12(ji,jj) & |
---|
457 | & - dtotel*( (1.0-alphaevp)*ecc2*zs12(ji,jj) - zds(ji,jj) / & |
---|
458 | & ( 2.0*deltac(ji,jj) ) * zpreshc(ji,jj))) & |
---|
459 | & / ( 1.0 + alphaevp*ecc2*dtotel ) |
---|
460 | |
---|
461 | END DO ! ji |
---|
462 | END DO ! jj |
---|
463 | |
---|
464 | CALL lbc_lnk( zs12(:,:), 'F', 1. ) |
---|
465 | |
---|
466 | ! Ice internal stresses (Appendix C of Hunke and Dukowicz, 2002) |
---|
467 | DO jj = k_j1+1, k_jpj-1 |
---|
468 | DO ji = fs_2, fs_jpim1 |
---|
469 | !- contribution of zs1, zs2 and zs12 to zf1 |
---|
470 | zf1(ji,jj) = 0.5*( (zs1(ji+1,jj)-zs1(ji,jj))*e2u(ji,jj) & |
---|
471 | & +(zs2(ji+1,jj)*e2t(ji+1,jj)**2-zs2(ji,jj)*e2t(ji,jj)**2)/e2u(ji,jj) & |
---|
472 | & +2.0*(zs12(ji,jj)*e1f(ji,jj)**2-zs12(ji,jj-1)*e1f(ji,jj-1)**2)/e1u(ji,jj) & |
---|
473 | & ) / ( e1u(ji,jj)*e2u(ji,jj) ) |
---|
474 | ! contribution of zs1, zs2 and zs12 to zf2 |
---|
475 | zf2(ji,jj) = 0.5*( (zs1(ji,jj+1)-zs1(ji,jj))*e1v(ji,jj) & |
---|
476 | & -(zs2(ji,jj+1)*e1t(ji,jj+1)**2 - zs2(ji,jj)*e1t(ji,jj)**2)/e1v(ji,jj) & |
---|
477 | & + 2.0*(zs12(ji,jj)*e2f(ji,jj)**2 - & |
---|
478 | zs12(ji-1,jj)*e2f(ji-1,jj)**2)/e2v(ji,jj) & |
---|
479 | & ) / ( e1v(ji,jj)*e2v(ji,jj) ) |
---|
480 | END DO |
---|
481 | END DO |
---|
482 | ! |
---|
483 | ! Computation of ice velocity |
---|
484 | ! |
---|
485 | ! Both the Coriolis term and the ice-ocean drag are solved semi-implicitly. |
---|
486 | ! |
---|
487 | IF (MOD(jter,2).eq.0) THEN |
---|
488 | |
---|
489 | !CDIR NOVERRCHK |
---|
490 | DO jj = k_j1+1, k_jpj-1 |
---|
491 | !CDIR NOVERRCHK |
---|
492 | DO ji = fs_2, fs_jpim1 |
---|
493 | zmask = (1.0-MAX(rzero,SIGN(rone,-zmass1(ji,jj))))*tmu(ji,jj) |
---|
494 | zsang = SIGN ( 1.0 , fcor(ji,jj) ) * sangvg |
---|
495 | z0 = zmass1(ji,jj)/dtevp |
---|
496 | |
---|
497 | ! SB modif because ocean has no slip boundary condition |
---|
498 | zv_ice1 = 0.5*( (v_ice(ji,jj)+v_ice(ji,jj-1))*e1t(ji,jj) & |
---|
499 | & +(v_ice(ji+1,jj)+v_ice(ji+1,jj-1))*e1t(ji+1,jj)) & |
---|
500 | & /(e1t(ji+1,jj)+e1t(ji,jj)) * tmu(ji,jj) |
---|
501 | za = rhoco*SQRT((u_ice(ji,jj)-u_oce1(ji,jj))**2 + & |
---|
502 | (zv_ice1-v_oce1(ji,jj))**2) * (1.0-zfrld1(ji,jj)) |
---|
503 | zr = z0*u_ice(ji,jj) + zf1(ji,jj) + za1ct(ji,jj) + & |
---|
504 | za*(cangvg*u_oce1(ji,jj)-zsang*v_oce1(ji,jj)) |
---|
505 | zcca = z0+za*cangvg |
---|
506 | zccb = zcorl1(ji,jj)+za*zsang |
---|
507 | u_ice(ji,jj) = (zr+zccb*zv_ice1)/(zcca+epsd)*zmask |
---|
508 | |
---|
509 | END DO |
---|
510 | END DO |
---|
511 | |
---|
512 | CALL lbc_lnk( u_ice(:,:), 'U', -1. ) |
---|
513 | |
---|
514 | !CDIR NOVERRCHK |
---|
515 | DO jj = k_j1+1, k_jpj-1 |
---|
516 | !CDIR NOVERRCHK |
---|
517 | DO ji = fs_2, fs_jpim1 |
---|
518 | |
---|
519 | zmask = (1.0-MAX(rzero,SIGN(rone,-zmass2(ji,jj))))*tmv(ji,jj) |
---|
520 | zsang = SIGN(1.0,fcor(ji,jj))*sangvg |
---|
521 | z0 = zmass2(ji,jj)/dtevp |
---|
522 | ! SB modif because ocean has no slip boundary condition |
---|
523 | zu_ice2 = 0.5*( (u_ice(ji,jj)+u_ice(ji-1,jj))*e2t(ji,jj) & |
---|
524 | & + (u_ice(ji,jj+1)+u_ice(ji-1,jj+1))*e2t(ji,jj+1)) & |
---|
525 | & /(e2t(ji,jj+1)+e2t(ji,jj)) * tmv(ji,jj) |
---|
526 | za = rhoco*SQRT((zu_ice2-u_oce2(ji,jj))**2 + & |
---|
527 | (v_ice(ji,jj)-v_oce2(ji,jj))**2)*(1.0-zfrld2(ji,jj)) |
---|
528 | zr = z0*v_ice(ji,jj) + zf2(ji,jj) + & |
---|
529 | za2ct(ji,jj) + za*(cangvg*v_oce2(ji,jj)+zsang*u_oce2(ji,jj)) |
---|
530 | zcca = z0+za*cangvg |
---|
531 | zccb = zcorl2(ji,jj)+za*zsang |
---|
532 | v_ice(ji,jj) = (zr-zccb*zu_ice2)/(zcca+epsd)*zmask |
---|
533 | |
---|
534 | END DO |
---|
535 | END DO |
---|
536 | |
---|
537 | CALL lbc_lnk( v_ice(:,:), 'V', -1. ) |
---|
538 | |
---|
539 | ELSE |
---|
540 | !CDIR NOVERRCHK |
---|
541 | DO jj = k_j1+1, k_jpj-1 |
---|
542 | !CDIR NOVERRCHK |
---|
543 | DO ji = fs_2, fs_jpim1 |
---|
544 | zmask = (1.0-MAX(rzero,SIGN(rone,-zmass2(ji,jj))))*tmv(ji,jj) |
---|
545 | zsang = SIGN(1.0,fcor(ji,jj))*sangvg |
---|
546 | z0 = zmass2(ji,jj)/dtevp |
---|
547 | ! SB modif because ocean has no slip boundary condition |
---|
548 | zu_ice2 = 0.5*( (u_ice(ji,jj)+u_ice(ji-1,jj))*e2t(ji,jj) & |
---|
549 | & +(u_ice(ji,jj+1)+u_ice(ji-1,jj+1))*e2t(ji,jj+1)) & |
---|
550 | & /(e2t(ji,jj+1)+e2t(ji,jj)) * tmv(ji,jj) |
---|
551 | |
---|
552 | za = rhoco*SQRT((zu_ice2-u_oce2(ji,jj))**2 + & |
---|
553 | (v_ice(ji,jj)-v_oce2(ji,jj))**2)*(1.0-zfrld2(ji,jj)) |
---|
554 | zr = z0*v_ice(ji,jj) + zf2(ji,jj) + & |
---|
555 | za2ct(ji,jj) + za*(cangvg*v_oce2(ji,jj)+zsang*u_oce2(ji,jj)) |
---|
556 | zcca = z0+za*cangvg |
---|
557 | zccb = zcorl2(ji,jj)+za*zsang |
---|
558 | v_ice(ji,jj) = (zr-zccb*zu_ice2)/(zcca+epsd)*zmask |
---|
559 | |
---|
560 | END DO |
---|
561 | END DO |
---|
562 | |
---|
563 | CALL lbc_lnk( v_ice(:,:), 'V', -1. ) |
---|
564 | |
---|
565 | !CDIR NOVERRCHK |
---|
566 | DO jj = k_j1+1, k_jpj-1 |
---|
567 | !CDIR NOVERRCHK |
---|
568 | DO ji = fs_2, fs_jpim1 |
---|
569 | zmask = (1.0-MAX(rzero,SIGN(rone,-zmass1(ji,jj))))*tmu(ji,jj) |
---|
570 | zsang = SIGN(1.0,fcor(ji,jj))*sangvg |
---|
571 | z0 = zmass1(ji,jj)/dtevp |
---|
572 | ! SB modif because ocean has no slip boundary condition |
---|
573 | ! GG Bug |
---|
574 | ! zv_ice1 = 0.5*( (v_ice(ji,jj)+v_ice(ji,jj-1))*e1t(ji+1,jj) & |
---|
575 | ! & +(v_ice(ji+1,jj)+v_ice(ji+1,jj-1))*e1t(ji,jj)) & |
---|
576 | ! & /(e1t(ji+1,jj)+e1t(ji,jj)) * tmu(ji,jj) |
---|
577 | zv_ice1 = 0.5*( (v_ice(ji,jj)+v_ice(ji,jj-1))*e1t(ji,jj) & |
---|
578 | & +(v_ice(ji+1,jj)+v_ice(ji+1,jj-1))*e1t(ji+1,jj)) & |
---|
579 | & /(e1t(ji+1,jj)+e1t(ji,jj)) * tmu(ji,jj) |
---|
580 | |
---|
581 | za = rhoco*SQRT((u_ice(ji,jj)-u_oce1(ji,jj))**2 + & |
---|
582 | (zv_ice1-v_oce1(ji,jj))**2)*(1.0-zfrld1(ji,jj)) |
---|
583 | zr = z0*u_ice(ji,jj) + zf1(ji,jj) + za1ct(ji,jj) + & |
---|
584 | za*(cangvg*u_oce1(ji,jj)-zsang*v_oce1(ji,jj)) |
---|
585 | zcca = z0+za*cangvg |
---|
586 | zccb = zcorl1(ji,jj)+za*zsang |
---|
587 | u_ice(ji,jj) = (zr+zccb*zv_ice1)/(zcca+epsd)*zmask |
---|
588 | END DO ! ji |
---|
589 | END DO ! jj |
---|
590 | |
---|
591 | CALL lbc_lnk( u_ice(:,:), 'U', -1. ) |
---|
592 | |
---|
593 | ENDIF |
---|
594 | |
---|
595 | IF(ln_ctl) THEN |
---|
596 | !--- Convergence test. |
---|
597 | DO jj = k_j1+1 , k_jpj-1 |
---|
598 | zresr(:,jj) = MAX( ABS( u_ice(:,jj) - zu_ice(:,jj) ) , & |
---|
599 | ABS( v_ice(:,jj) - zv_ice(:,jj) ) ) |
---|
600 | END DO |
---|
601 | zresm = MAXVAL( zresr( 1:jpi , k_j1+1:k_jpj-1 ) ) |
---|
602 | IF( lk_mpp ) CALL mpp_max( zresm ) ! max over the global domain |
---|
603 | ENDIF |
---|
604 | |
---|
605 | ! ! ==================== ! |
---|
606 | END DO ! end loop over jter ! |
---|
607 | ! ! ==================== ! |
---|
608 | |
---|
609 | ! |
---|
610 | !------------------------------------------------------------------------------! |
---|
611 | ! 4) Prevent ice velocities when the ice is thin |
---|
612 | !------------------------------------------------------------------------------! |
---|
613 | ! |
---|
614 | ! If the ice thickness is below 1cm then ice velocity should equal the |
---|
615 | ! ocean velocity, |
---|
616 | ! This prevents high velocity when ice is thin |
---|
617 | !CDIR NOVERRCHK |
---|
618 | DO jj = k_j1+1, k_jpj-1 |
---|
619 | !CDIR NOVERRCHK |
---|
620 | DO ji = fs_2, fs_jpim1 |
---|
621 | zindb = MAX( 0.0, SIGN( 1.0, at_i(ji,jj) - 1.0e-6 ) ) |
---|
622 | zdummy = zindb * vt_i(ji,jj) / MAX(at_i(ji,jj) , 1.0e-06 ) |
---|
623 | IF ( zdummy .LE. 5.0e-2 ) THEN |
---|
624 | u_ice(ji,jj) = u_oce(ji,jj) |
---|
625 | v_ice(ji,jj) = v_oce(ji,jj) |
---|
626 | ENDIF ! zdummy |
---|
627 | END DO |
---|
628 | END DO |
---|
629 | |
---|
630 | CALL lbc_lnk( u_ice(:,:), 'U', -1. ) |
---|
631 | CALL lbc_lnk( v_ice(:,:), 'V', -1. ) |
---|
632 | |
---|
633 | DO jj = k_j1+1, k_jpj-1 |
---|
634 | DO ji = fs_2, fs_jpim1 |
---|
635 | zindb = MAX( 0.0, SIGN( 1.0, at_i(ji,jj) - 1.0e-6 ) ) |
---|
636 | zdummy = zindb * vt_i(ji,jj) / MAX(at_i(ji,jj) , 1.0e-06 ) |
---|
637 | IF ( zdummy .LE. 5.0e-2 ) THEN |
---|
638 | v_ice1(ji,jj) = 0.5*( (v_ice(ji,jj)+v_ice(ji,jj-1))*e1t(ji+1,jj) & |
---|
639 | & +(v_ice(ji+1,jj)+v_ice(ji+1,jj-1))*e1t(ji,jj)) & |
---|
640 | & /(e1t(ji+1,jj)+e1t(ji,jj)) * tmu(ji,jj) |
---|
641 | |
---|
642 | u_ice2(ji,jj) = 0.5*( (u_ice(ji,jj)+u_ice(ji-1,jj))*e2t(ji,jj+1) & |
---|
643 | & +(u_ice(ji,jj+1)+u_ice(ji-1,jj+1))*e2t(ji,jj)) & |
---|
644 | & /(e2t(ji,jj+1)+e2t(ji,jj)) * tmv(ji,jj) |
---|
645 | ENDIF ! zdummy |
---|
646 | END DO |
---|
647 | END DO |
---|
648 | |
---|
649 | CALL lbc_lnk( u_ice2(:,:), 'V', -1. ) |
---|
650 | CALL lbc_lnk( v_ice1(:,:), 'U', -1. ) |
---|
651 | |
---|
652 | ! Recompute delta, shear and div, inputs for mechanical redistribution |
---|
653 | !CDIR NOVERRCHK |
---|
654 | DO jj = k_j1+1, k_jpj-1 |
---|
655 | !CDIR NOVERRCHK |
---|
656 | DO ji = fs_2, jpim1 !RB bug no vect opt due to tmi |
---|
657 | !- zdd(:,:), zdt(:,:): divergence and tension at centre |
---|
658 | !- zds(:,:): shear on northeast corner of grid cells |
---|
659 | zindb = MAX( 0.0, SIGN( 1.0, at_i(ji,jj) - 1.0e-6 ) ) |
---|
660 | zdummy = zindb * vt_i(ji,jj) / MAX(at_i(ji,jj) , 1.0e-06 ) |
---|
661 | |
---|
662 | IF ( zdummy .LE. 5.0e-2 ) THEN |
---|
663 | |
---|
664 | zdd(ji,jj) = ( e2u(ji,jj)*u_ice(ji,jj) & |
---|
665 | & -e2u(ji-1,jj)*u_ice(ji-1,jj) & |
---|
666 | & +e1v(ji,jj)*v_ice(ji,jj) & |
---|
667 | & -e1v(ji,jj-1)*v_ice(ji,jj-1) & |
---|
668 | & ) & |
---|
669 | & / area(ji,jj) |
---|
670 | |
---|
671 | zdt(ji,jj) = ( ( u_ice(ji,jj)/e2u(ji,jj) & |
---|
672 | & -u_ice(ji-1,jj)/e2u(ji-1,jj) & |
---|
673 | & )*e2t(ji,jj)*e2t(ji,jj) & |
---|
674 | & -( v_ice(ji,jj)/e1v(ji,jj) & |
---|
675 | & -v_ice(ji,jj-1)/e1v(ji,jj-1) & |
---|
676 | & )*e1t(ji,jj)*e1t(ji,jj) & |
---|
677 | & ) & |
---|
678 | & / area(ji,jj) |
---|
679 | ! |
---|
680 | ! SB modif because ocean has no slip boundary condition |
---|
681 | zds(ji,jj) = ( ( u_ice(ji,jj+1) / e1u(ji,jj+1) & |
---|
682 | & - u_ice(ji,jj) / e1u(ji,jj) ) & |
---|
683 | & * e1f(ji,jj) * e1f(ji,jj) & |
---|
684 | & + ( v_ice(ji+1,jj) / e2v(ji+1,jj) & |
---|
685 | & - v_ice(ji,jj) / e2v(ji,jj) ) & |
---|
686 | & * e2f(ji,jj) * e2f(ji,jj) ) & |
---|
687 | & / ( e1f(ji,jj) * e2f(ji,jj) ) * ( 2.0 - tmf(ji,jj) ) & |
---|
688 | & * tmi(ji,jj) * tmi(ji,jj+1) & |
---|
689 | & * tmi(ji+1,jj) * tmi(ji+1,jj+1) |
---|
690 | |
---|
691 | zdst = ( e2u( ji , jj ) * v_ice1(ji,jj) & |
---|
692 | & - e2u( ji-1, jj ) * v_ice1(ji-1,jj) & |
---|
693 | & + e1v( ji , jj ) * u_ice2(ji,jj) & |
---|
694 | & - e1v( ji , jj-1 ) * u_ice2(ji,jj-1) & |
---|
695 | & ) & |
---|
696 | & / area(ji,jj) |
---|
697 | |
---|
698 | deltat(ji,jj) = SQRT( zdd(ji,jj)*zdd(ji,jj) + & |
---|
699 | & ( zdt(ji,jj)*zdt(ji,jj) + zdst*zdst ) * usecc2 & |
---|
700 | & ) + creepl |
---|
701 | |
---|
702 | ENDIF ! zdummy |
---|
703 | |
---|
704 | END DO !jj |
---|
705 | END DO !ji |
---|
706 | ! |
---|
707 | !------------------------------------------------------------------------------! |
---|
708 | ! 5) Store stress tensor and its invariants |
---|
709 | !------------------------------------------------------------------------------! |
---|
710 | ! |
---|
711 | ! * Invariants of the stress tensor are required for limitd_me |
---|
712 | ! accelerates convergence and improves stability |
---|
713 | DO jj = k_j1+1, k_jpj-1 |
---|
714 | DO ji = fs_2, fs_jpim1 |
---|
715 | divu_i (ji,jj) = zdd (ji,jj) |
---|
716 | delta_i(ji,jj) = deltat(ji,jj) |
---|
717 | shear_i(ji,jj) = zds (ji,jj) |
---|
718 | END DO |
---|
719 | END DO |
---|
720 | |
---|
721 | ! Lateral boundary condition |
---|
722 | CALL lbc_lnk( divu_i (:,:), 'T', 1. ) |
---|
723 | CALL lbc_lnk( delta_i(:,:), 'T', 1. ) |
---|
724 | CALL lbc_lnk( shear_i(:,:), 'F', 1. ) |
---|
725 | |
---|
726 | ! * Store the stress tensor for the next time step |
---|
727 | stress1_i (:,:) = zs1 (:,:) |
---|
728 | stress2_i (:,:) = zs2 (:,:) |
---|
729 | stress12_i(:,:) = zs12(:,:) |
---|
730 | |
---|
731 | ! |
---|
732 | !------------------------------------------------------------------------------! |
---|
733 | ! 6) Control prints of residual and charge ellipse |
---|
734 | !------------------------------------------------------------------------------! |
---|
735 | ! |
---|
736 | ! print the residual for convergence |
---|
737 | IF(ln_ctl) THEN |
---|
738 | WRITE(charout,FMT="('lim_rhg : res =',D23.16, ' iter =',I4)") zresm, jter |
---|
739 | CALL prt_ctl_info(charout) |
---|
740 | CALL prt_ctl(tab2d_1=u_ice, clinfo1=' lim_rhg : u_ice :', tab2d_2=v_ice, clinfo2=' v_ice :') |
---|
741 | ENDIF |
---|
742 | |
---|
743 | ! print charge ellipse |
---|
744 | ! This can be desactivated once the user is sure that the stress state |
---|
745 | ! lie on the charge ellipse. See Bouillon et al. 08 for more details |
---|
746 | IF(ln_ctl) THEN |
---|
747 | CALL prt_ctl_info('lim_rhg : numit :',ivar1=numit) |
---|
748 | CALL prt_ctl_info('lim_rhg : nwrite :',ivar1=nwrite) |
---|
749 | CALL prt_ctl_info('lim_rhg : MOD :',ivar1=MOD(numit,nwrite)) |
---|
750 | IF( MOD(numit,nwrite) .EQ. 0 ) THEN |
---|
751 | WRITE(charout,FMT="('lim_rhg :', I4, I6, I1, I1, A10)") 1000, numit, 0, 0, ' ch. ell. ' |
---|
752 | CALL prt_ctl_info(charout) |
---|
753 | DO jj = k_j1+1, k_jpj-1 |
---|
754 | DO ji = 2, jpim1 |
---|
755 | IF (zpresh(ji,jj) .GT. 1.0) THEN |
---|
756 | sigma1 = ( zs1(ji,jj) + (zs2(ji,jj)**2 + 4*zs12(ji,jj)**2 )**0.5 ) / ( 2*zpresh(ji,jj) ) |
---|
757 | sigma2 = ( zs1(ji,jj) - (zs2(ji,jj)**2 + 4*zs12(ji,jj)**2 )**0.5 ) / ( 2*zpresh(ji,jj) ) |
---|
758 | WRITE(charout,FMT="('lim_rhg :', I4, I4, D23.16, D23.16, D23.16, D23.16, A10)") |
---|
759 | CALL prt_ctl_info(charout) |
---|
760 | ENDIF |
---|
761 | END DO |
---|
762 | END DO |
---|
763 | WRITE(charout,FMT="('lim_rhg :', I4, I6, I1, I1, A10)") 2000, numit, 0, 0, ' ch. ell. ' |
---|
764 | CALL prt_ctl_info(charout) |
---|
765 | ENDIF |
---|
766 | ENDIF |
---|
767 | |
---|
768 | END SUBROUTINE lim_rhg |
---|
769 | |
---|
770 | #else |
---|
771 | !!---------------------------------------------------------------------- |
---|
772 | !! Default option Dummy module NO LIM sea-ice model |
---|
773 | !!---------------------------------------------------------------------- |
---|
774 | CONTAINS |
---|
775 | SUBROUTINE lim_rhg( k1 , k2 ) ! Dummy routine |
---|
776 | WRITE(*,*) 'lim_rhg: You should not have seen this print! error?', k1, k2 |
---|
777 | END SUBROUTINE lim_rhg |
---|
778 | #endif |
---|
779 | |
---|
780 | !!============================================================================== |
---|
781 | END MODULE limrhg |
---|