source: branches/2017/dev_v3.20_2017_transport_max/SOURCES/source_3.20/ice_phy_remap.f @ 39

Last change on this file since 39 was 39, checked in by vancop, 7 years ago

add tank mass and salt balance

File size: 22.4 KB
Line 
1      SUBROUTINE ice_phy_remap(nlay_s,nlay_i,kideb,kiut)
2
3!!-----------------------------------------------------------------------------
4!! ** Purpose :
5!!              This routine redistributes heat content and salt mass
6!!              on the new grid
7!!
8!!
9!! ** Method  : Linear redistribution
10!!           
11!! ** Steps   : switches, snow, ice heat content, ice salt content
12!!
13!! ** Arguments
14!!
15!! ** Inputs / Outputs
16!!
17!! ** External
18!!
19!! ** References
20!!
21!! ** History  : (05-2003) Martin Vancoppenolle, LIM1D
22!!               (05-2008) Martin Vancoppenolle, LLN, revision BIOLIM
23!!               (09-2009) Martin Vancoppenolle, LLN, restructuration BIOLIM
24!!-----------------------------------------------------------------------------
25
26      USE lib_fortran
27
28      INCLUDE 'type.com'
29      INCLUDE 'para.com'
30      INCLUDE 'const.com'
31      INCLUDE 'ice.com'
32      INCLUDE 'thermo.com'
33      INCLUDE 'bio.com'
34      INCLUDE 'tank.com'
35
36      ! Local Variables
37      REAL(8), DIMENSION (maxnlay) :: 
38     &   zsh_i0              ,   !: old ice salt content (ppt.m-2)
39     &   zsh_i1                  !: new ice salt content (ppt.m-2)
40
41      REAL(8), DIMENSION (maxnlay) :: 
42     &   zqh_i0              ,   !: old ice heat content (J.m-2)
43     &   zqh_i1                  !: new ice heat content (J.m-2)
44
45      REAL(8), DIMENSION (maxnlay) :: 
46     &   zqh_s0              ,   !: old snow heat content (J.m-2)
47     &   zqh_s1                  !: new snow heat content (J.m-2)
48
49      REAL(8), DIMENSION( maxnlay ) ::
50     &  zthick1                  !: thickness of physical layers
51
52      REAL(8), DIMENSION (maxnlay+2) ::
53     &   zthick0                 !: thickness of old layers
54      LOGICAL ::
55     &   ln_write, ln_con
56
57      ! Local Constants
58      zeps   = 1.0e-20
59
60      ln_write = .TRUE.
61      ln_con   = .TRUE.
62
63      s_i_b(1,:) = sn_i_b(:) ! update salinity
64
65      IF ( ln_write ) THEN
66         WRITE(numout,*) ' ** ice_phy_remap : '
67         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~ '
68         WRITE(numout,*) 
69      ENDIF
70!
71!------------------------------------------------------------------------------|
72!  CONSERVATION CHECKS                                                         |
73!------------------------------------------------------------------------------|
74!
75
76      ji = 1
77      IF ( ln_con ) THEN
78         CALL ice_sal_column(kideb,kiut,z_ms_i_ini,s_i_b(1,1:nlay_i),
79     &                       deltaz_i_phy, nlay_i, .FALSE. )
80         ! salt content loss due to ice melt
81         zfmelt = ( s_i_b(ji,1) * dh_i_surf(ji) + s_i_b(ji,nlay_i) * 
82     &              MIN(dh_i_bott(ji),0.0) ) / ddtb
83      ENDIF
84
85      zqt_s_ini = 0.0 ! total heat content in snow (initial value)
86      zqt_i_ini = 0.0 ! total heat content in ice  (initial value)
87      zqt_s_fin = 0.0 ! total heat content in snow (final value)
88      zqt_i_fin = 0.0 ! total heat content in ice  (final value)
89      zqt_ini   = 0.0 ! total heat content snow + ice (initial value)
90      zqt_fin   = 0.0 ! total heat content snow + ice (final value)
91
92      DO 10 ji = kideb, kiut
93!
94!------------------------------------------------------------------------------|
95!  SWITCHES                                                                    |
96!------------------------------------------------------------------------------|
97!
98      ! snow surface behaviour : calcul de snind-snswi
99      ! snind : index tel que sa valeur est 0 si la neige s'accrète
100      !                1 si la 1ere couche est entamée par la fonte
101      !                2 si la 2eme ....
102      !                                  etc ...
103      snind    =  0 
104      deltah   =  0.0
105      DO layer = 1, nlay_s
106         IF ( - dh_s_tot(ji) .GT. deltah ) THEN
107            snind  =  layer 
108         ENDIF
109         deltah = deltah + deltaz_s_phy(layer)
110      END DO
111
112      ! snswi : switch which value equals 1 if snow melts
113      !                                 0 if not
114      snswi    =  MAX(0,INT(-dh_s_tot(ji)/MAX(zeps,ABS(dh_s_tot(ji)))))
115
116      ! ice surface behaviour : computation of icsuind-icsuswi
117      ! icsuind : index which values equals 0 if there is nothing
118      !                                 1 if first layer has started to melt
119      !                                 2 if first and second layer have started ...
120      !                                 etc ...
121      icsuind    =  0 
122      deltah   =  0.0
123      DO layer = 1, nlay_i
124         IF  ( -dh_i_surf(ji).GT.deltah) THEN
125            icsuind  =  layer 
126         ENDIF
127         deltah = deltah + deltaz_i_phy(layer)
128      END DO
129
130      ! icsuswi : switch which value equals 1 if ice melts at the surface
131      !                                   0 if not
132      icsuswi    =  max(0,int(-dh_i_surf(ji)
133     &              /max(zeps,abs(dh_i_surf(ji)))))
134
135      ! ice bottom behaviour : computation of icboind-icboswi
136      ! icboind : index which values equals 0 if accretion is on the way
137      !                                     1 if last layer has started to melt
138      !                               2 if penultiem layer has started ...
139      !                               etc ...
140      icboind    =  0 
141      deltah   =  0.0
142      DO layer = nlay_i, 1, -1
143         IF (-dh_i_bott(ji) .GT. deltah) THEN
144            icboind  =  nlay_i+1-layer 
145         ENDIF
146         deltah = deltah + deltaz_i_phy(layer)
147      END DO
148
149      ! icboswi : switch which value equals 1 if accretion of ice is on the way
150      !                                         0 if ablation is on the way
151      icboswi    =  max(0,int(dh_i_bott(ji)
152     &              /max(zeps,abs(dh_i_bott(ji)))))
153
154      ! snow-ice formation : calcul de snicind-snicswi
155      ! snicind : index which values equals 0 if no snow-ice forms
156      !                1 if last layer of snow has started to melt
157      !                          2 if penultiem layer ...
158      snicind    =  0
159      deltah   =  0.0
160      DO layer = nlay_s, 1, -1
161         IF ( dh_snowice(ji) .GT. deltah ) THEN
162            snicind  =  nlay_s+1-layer
163         ENDIF
164         deltah = deltah + deltaz_s_phy(layer)
165      END DO
166
167      ! snicswi : switch which value equals 1 if snow-ice forms
168      !                                     0 if not
169      snicswi    =  max(0,int(dh_snowice(ji)/
170     &              max(zeps,abs(dh_snowice(ji)))))
171
172      IF ( ln_write ) THEN
173         WRITE(numout,*) ' - Switches ... '
174         WRITE(numout,*) '  snind   : ', snind
175         WRITE(numout,*) '  snswi   : ', snswi
176         WRITE(numout,*) '  icsuind : ', icsuind
177         WRITE(numout,*) '  icsuswi : ', icsuswi
178         WRITE(numout,*) '  icboind : ', icboind
179         WRITE(numout,*) '  icboswi : ', icboswi
180         WRITE(numout,*) '  snicind : ', snicind
181         WRITE(numout,*) '  snicswi : ', snicswi
182         WRITE(numout,*) 
183      ENDIF
184
185!------------------------------------------------------------------------------!
186
187      !------------------------------!
188      !                              !
189      !     SNOW redistribution      !
190      !                              !
191      !------------------------------!
192
193!
194!------------------------------------------------------------------------------|
195!      S-1) 'Old' snow cotes
196!------------------------------------------------------------------------------|
197!
198      !
199      ! by 'old', I mean that layers coming from accretion are included, and
200      ! that surface layers which were partly melted are reduced ...
201
202      ! indexes of the vectors
203      ntop0    =  1
204      nbot0    =  nlay_s+1-snind+(1-snicind)*snicswi
205
206      ! cotes of the top of the layers
207      zm0(0)   =  0.0
208      DO layer = 1, nbot0-1
209         limsum    =  snswi*(layer+snind-1) + (1-snswi)*(layer-1)
210         limsum    =  MIN( limsum , nlay_s )
211         zm0(layer) =  dh_s_tot(ji)
212         DO layer_a = 1, limsum
213            zm0(layer) = zm0(layer) + deltaz_s_phy(layer_a)
214         END DO
215      END DO
216
217      zm0(nbot0) =  dh_s_tot(ji) - snicswi*dh_snowice(ji)
218      DO layer = 1, nlay_s
219        zm0(nbot0) = zm0(nbot0) + deltaz_s_phy(layer)
220      END DO
221      zm0(1)     =  dh_s_tot(ji)*(1-snswi) + snswi*zm0(1)
222
223      ! thicknesses
224      DO layer = ntop0, nbot0
225         zthick0(layer)  =  zm0(layer) - zm0(layer-1)
226      END DO
227!
228!------------------------------------------------------------------------------|
229!      S-2) 'Old' enthalpies
230!------------------------------------------------------------------------------|
231!
232      ! enthalpies
233      zqh_s0(1) =  rhon * ( cpg * ( tpw - (1 - snswi) * tabqb(ji) - ! fallen snow
234     &             snswi * t_s_b(ji,1) ) + lfus )* zthick0(1) 
235      zqt_s_ini = zqt_s_ini + zqh_s0(1)
236
237      DO layer = 2, nbot0 ! remaining snow
238         limsum = (1-snswi)*(layer-1) + snswi*(layer+snind-1)
239         limsum = MIN( limsum, nlay_s )
240         zqh_s0(layer) = rhon*( cpg*(tpw - t_s_b(ji,limsum)) + lfus) 
241     &            *zthick0(layer)
242         zswitch   = 1.0 - MAX (0.0, SIGN ( 1.0d0, zeps - ht_s_b(ji) ) )
243         zqt_s_ini = zqt_s_ini + ( 1 - snswi ) * zqh_s0(layer) * zswitch
244         WRITE(numout,*) 'limsum : ', limsum
245      END DO
246      zqt_ini = zqt_s_ini
247
248      IF ( ln_write ) THEN
249         WRITE(numout,*) ' - Snow redistribution ... '
250         WRITE(numout,*) ' ntop0 : ', ntop0
251         WRITE(numout,*) ' nbot0 : ', nbot0
252         WRITE(numout,*) ' zm0   : ', ( zm0(layer), layer = 0, nbot0)
253         WRITE(numout,*) ' zqh_s0: ', ( zqh_s0(layer), layer = 1, nbot0)
254         WRITE(numout,*) ' q_s_b1: ', q_s_b(ji,1)
255         WRITE(numout,*)
256      ENDIF
257
258      !-----------------------------------------
259      ! snow enthalpy lost in sea ice formation
260      !-----------------------------------------
261      zqsnow     =  0.0
262      zdeltah    =  0.0
263
264      DO layer =  nlay_s, 1, -1
265         zhsnow    =  MAX(0.0,dh_snowice(ji)-zdeltah)
266         zqsnow    =  zqsnow + q_s_b(ji,layer) * zhsnow
267      END DO
268
269!
270!------------------------------------------------------------------------------|
271!      S-3) New snow grid
272!------------------------------------------------------------------------------|
273!
274      ! indexes of the vectors
275      ntop1    =  1
276      nbot1    =  nlay_s
277
278      ! cotes and thicknesses
279      CALL ice_phy_grid( kideb , kiut , nlay_s , ht_s_b(ji), .FALSE., 
280     &                   "sno" )
281!
282!------------------------------------------------------------------------------|
283!      S-4) New snow enthalpy
284!------------------------------------------------------------------------------|
285!
286      CALL ice_phy_relay( nbot0 , nbot1 , ntop0 , ntop1 , 
287     &                    zthick0, deltaz_s_phy, zqh_s0 , zqh_s1 )
288
289      zqt_s_fin = 0.0 ! total heat content
290!
291!------------------------------------------------------------------------------|
292!      S-5) Recover snow temperature
293!------------------------------------------------------------------------------|
294!
295      WRITE(numout,*) ' Recover snow temperature '
296      WRITE(numout,*) ' nlay_s  : ', nlay_s
297      WRITE(numout,*) ' ji      : ', ji
298      WRITE(numout,*) ' ht_s_b  : ', ht_s_b(ji)
299      WRITE(numout,*) ' tpw     : ', tpw
300      WRITE(numout,*) ' rhon    : ', rhon
301      DO layer = 1, nlay_s
302         isnow   = INT( 1.0 - MAX( 0.0 , SIGN( 1.0d0, - ht_s_b(ji) ) ))
303         WRITE(numout,*) ' isnow : ', isnow
304         t_s_b(ji,layer)  =  isnow * ( tpw - ( zqh_s1(layer) / rhon / 
305     &                       MAX( deltaz_s_phy(layer) , zeps ) - lfus )
306     &                       / cpg ) +
307     &                       ( 1.0 - isnow ) * tpw
308         WRITE(numout,*) ' zqh_s1: ', zqh_s1(layer)
309         WRITE(numout,*) ' deltaz_s_phy : ', deltaz_s_phy(layer)
310         WRITE(numout,*) ' zeps         : ', zeps
311         WRITE(numout,*) ' lfus         : ', lfus
312         WRITE(numout,*) ' cpg          : ', cpg 
313         WRITE(numout,*) ' t_s_b        : ', t_s_b(ji,layer)
314         zqt_s_fin = zqt_s_fin + zqh_s1(layer)
315         q_s_b(ji,layer) = isnow * zqh_s1(layer) / 
316     &                     MAX( deltaz_s_phy(layer) , zeps )
317      END DO
318      WRITE(numout,*) ' t_s_b        : ', t_s_b(ji,1)
319      zqt_fin = zqt_s_fin
320
321      IF ( ln_write ) THEN
322         WRITE(numout,*) ' - Heat conservation, ice_th_remap , snow '
323         WRITE(numout,*) ' zqt_s_fin : ', zqt_s_fin
324         WRITE(numout,*) ' zqt_s_ini : ', zqt_s_ini
325         WRITE(numout,*) ' TS1. zqt_s_fin - zqt_s_ini : ', 
326     &                   zqt_s_fin - zqt_s_ini
327         WRITE(numout,*)
328      ENDIF
329
330!------------------------------------------------------------------------------!
331 
332      !------------------------------!
333      !                              !
334      !     ICE redistribution       !
335      !                              !
336      !------------------------------!
337
338!------------------------------------------------------------------------------!
339
340!
341!------------------------------------------------------------------------------!
342!  I-1) Old ice grid                                                           !
343!------------------------------------------------------------------------------!
344!
345      ! indexes of the vectors
346      ntop0    =  1
347      nbot0    =  MAX(1, MIN( nlay_i + 1 - icboind + (1-icsuind)*icsuswi
348     &                      + snicswi, nlay_i + 2 ) )
349
350      ! cotes of the top of the layers
351      zm0(0)   =  0.0
352      DO layer = 1, nbot0-1
353         limsum    =  ((icsuswi*(icsuind+layer-1) + (1-icsuswi)*layer))*
354     &               (1-snicswi) + (layer-1)*snicswi
355         zm0(layer)=  icsuswi*dh_i_surf(ji) + snicswi*dh_snowice(ji)
356         DO layer_a = 1, limsum
357            zm0(layer) = zm0(layer) + deltaz_i_phy(layer_a)
358         END DO
359      END DO
360
361      zm0(nbot0) =  icsuswi*dh_i_surf(ji) + snicswi*dh_snowice(ji) + 
362     &              dh_i_bott(ji)
363      DO layer = 1, nlay_i
364         zm0(nbot0) = zm0(nbot0) + deltaz_i_phy(layer)
365      END DO
366      zm0(1)     =  snicswi*dh_snowice(ji) + (1-snicswi)*zm0(1)
367
368      ! thicknesses
369      DO layer = ntop0, nbot0
370         zthick0(layer)  =  zm0(layer) - zm0(layer-1)
371      END DO
372
373      IF ( ln_write ) THEN
374         WRITE(numout,*) ' - Ice redistribution ... '
375         WRITE(numout,*) ' ntop0 : ', ntop0
376         WRITE(numout,*) ' nbot0 : ', nbot0
377         WRITE(numout,*) ' zm0   : ', ( zm0(layer), layer = 0, nbot0)
378         WRITE(numout,*) ' zthick0: ', ( zthick0(layer), layer = ntop0, 
379     &                                  nbot0)
380      ENDIF
381!
382!------------------------------------------------------------------------------|
383!  I-2) Old ice heat content                                                   |
384!------------------------------------------------------------------------------|
385!
386      !-------------------------
387      ! sources of heat content
388      !-------------------------
389      !- new ice
390      tmelts = - tmut * s_i_new + tpw
391      zqh_i_new =  rhog * ( cpg * ( tmelts - t_bo_b(ji) ) 
392     &             + lfus * ( 1.0 - ( tmelts - tpw ) /
393     &             ( t_bo_b(ji) - tpw ) ) - cpw * ( tmelts - tpw ) )
394     &             * zthick0(nbot0)
395
396      !- snow ice
397      zqh_i_sni =  rho0 * cpw * ( tpw - t_bo_b(ji) ) * dh_snowice(ji) * 
398     &            ( rhog - rhon ) / rhog * snicswi  ! generally positive
399      fsnic  =  - zqh_i_sni / ddtb
400      zqh_i_sni =  zqsnow + zqh_i_sni
401
402      !----------------------
403      ! sea ice heat content
404      !----------------------
405      zqh_i0(:) = 0.0
406      !- internal ice layers
407      DO layer = ntop0, nbot0
408          limsum = MAX( 1 , MIN( snicswi*(layer-1) 
409     &           + icsuswi * ( layer - 1 +  icsuind )
410     &           + ( 1 - icsuswi ) * ( 1 - snicswi ) * layer, nlay_i ) )
411          zqh_i0(layer) = q_i_b(ji,limsum) * zthick0(layer)
412          WRITE(numout,*) ' limsum : ', limsum, ' layer : ', layer
413      END DO
414       
415      !- boundary values
416      zqh_i0(1)     =  snicswi * zqh_i_sni + ( 1 - snicswi ) * zqh_i0(1)
417      zqh_i0(nbot0) =  ( 1 - icboswi ) * zqh_i0(nbot0) + 
418     &                 icboswi * zqh_i_new
419
420      IF ( ln_write ) THEN
421         WRITE(numout,*) ' zqh_i_new: ', zqh_i_new
422         WRITE(numout,*) ' zqh_i_sni: ', zqh_i_sni
423         WRITE(numout,*) ' zqh_i0: ', ( zqh_i0(layer), layer = ntop0, 
424     &                                  nbot0)
425      ENDIF
426
427      DO layer = ntop0, nbot0
428         zqt_i_ini = zqt_i_ini + zqh_i0(layer) 
429      END DO
430
431      zqt_ini = zqt_ini + zqt_i_ini ! includes zqsnic and zqsnow
432
433!
434!------------------------------------------------------------------------------|
435!  I-3) Old ice salt content                                                   |
436!------------------------------------------------------------------------------|
437!
438      ! basal new ice salt content
439      zsh_i_new = rn_e_newice * s_w * MAX ( dh_i_bott(ji), 0.0 )
440      ! snow ice salt content
441      s_i_snic  =  ( rhog - rhon ) / rhog * s_w *
442     &              frtr_si_phy ! snow ice salinity
443      zsh_i_sni = s_i_snic * dh_snowice(ji)
444
445      IF ( ln_write ) THEN
446         WRITE(numout,*) ' Salt sources : '
447         WRITE(numout,*) ' ~~~~~~~~~~~~~~ '
448         WRITE(numout,*) ' zsh_i_new : ', zsh_i_new
449         WRITE(numout,*) ' zsh_i_sni : ', zsh_i_sni
450      ENDIF
451
452      zsh_i0(:) = 0.0
453
454      DO layer = ntop0, nbot0
455          limsum =  snicswi*(layer-1) + icsuswi*(layer-1+icsuind)
456     &            + (1-icsuswi)*(1-snicswi)*layer
457          limsum =  MAX(1,MIN(snicswi*(layer-1) + icsuswi*(layer-1
458     &           +  icsuind)
459     &           + (1-icsuswi)*(1-snicswi)*layer, nlay_i))
460          zsh_i0(layer) = s_i_b(ji,limsum)*zthick0(layer)
461      END DO
462
463      zsh_i0(nbot0) =  (1-icboswi)* zsh_i0(nbot0) + icboswi * zsh_i_new
464      zsh_i0(1)     =  snicswi * zsh_i_sni + ( 1 - snicswi ) * zsh_i0(1)
465     
466!     z_ms_i_ini = 0.0
467!     DO layer = ntop0, nbot0
468!        z_ms_i_ini = z_ms_i_ini + zsh_i0(layer)
469!     END DO
470
471      IF ( ln_write ) THEN
472         WRITE(numout,*) ' frtr_si_phy:', frtr_si_phy
473         WRITE(numout,*) ' s_w      : ', s_w
474         WRITE(numout,*) ' s_i_snic : ', s_i_snic
475         WRITE(numout,*) ' zsh_i0   : ', zsh_i0(ntop0:nbot0)
476         WRITE(numout,*)
477      ENDIF
478!
479!------------------------------------------------------------------------------|
480!  I-4) New ice profile                                                        |
481!------------------------------------------------------------------------------|
482!
483      ! indexes of the vectors
484      ntop1    =  1 
485      nbot1    =  nlay_i
486
487      ! cotes and thicknesses
488      CALL ice_phy_grid( kideb , kiut , nlay_i , ht_i_b(ji), .FALSE., 
489     &                   "ice" )
490
491      IF ( ln_write ) THEN
492         WRITE(numout,*) ' z_i_phy : ', ( z_i_phy(layer), 
493     &                   layer = ntop1, nbot1 )
494         WRITE(numout,*) ' deltaz_i_phy : ', ( deltaz_i_phy(layer), 
495     &                   layer = ntop1, nbot1 )
496      ENDIF
497!
498!------------------------------------------------------------------------------|
499!  I-5) Redistribute ice heat content                                          |
500!------------------------------------------------------------------------------|
501!
502      ! Remapping ice enthalpy
503      CALL ice_phy_relay( nbot0 , nbot1 , ntop0 , ntop1 , 
504     &                    zthick0, deltaz_i_phy, zqh_i0 , zqh_i1 )
505
506      IF ( ln_write ) THEN
507         WRITE(numout,*) ' zqh_i1 : ',( zqh_i1(layer), layer = ntop1,
508     &                                  nbot1)
509         WRITE(numout,*)
510      ENDIF
511
512      DO layer = ntop1, nbot1
513         zqt_i_fin = zqt_i_fin + zqh_i1(layer) 
514      END DO
515
516      zqt_fin = zqt_fin + zqt_i_fin ! includes zqsnic and zqsnow
517!
518!------------------------------------------------------------------------------|
519!  I-6) Redistribute ice salt content                                          |
520!------------------------------------------------------------------------------|
521!
522      CALL ice_phy_relay( nbot0 , nbot1 , ntop0 , ntop1 , 
523     &                    zthick0, deltaz_i_phy, zsh_i0 , zsh_i1 )
524      IF ( ln_write ) THEN
525         WRITE(numout,*) ' zsh_i1   : ', zsh_i1(ntop0:nbot0)
526         WRITE(numout,*)
527      ENDIF
528
529!
530!------------------------------------------------------------------------------|
531!  I-7) Heat conservation test                                                 |
532!------------------------------------------------------------------------------|
533!
534      IF ( ln_write ) THEN
535         WRITE(numout,*) ' - Heat conservation, ice_th_remap ,
536     &   sea ice... '
537         WRITE(numout,*) ' zqt_i_fin : ', zqt_i_fin
538         WRITE(numout,*) ' zqt_i_ini : ', zqt_i_ini
539         WRITE(numout,*) ' TI1. zqt_i_fin - zqt_i_ini : ', 
540     &                   zqt_i_fin - zqt_i_ini
541         WRITE(numout,*)
542         WRITE(numout,*) ' - Heat conservation, total ... '
543         WRITE(numout,*) ' zqt_ini         : ', zqt_ini
544         WRITE(numout,*) ' zqt_fin         : ', zqt_fin
545         WRITE(numout,*) ' zqt_fin-zqt_ini : ', zqt_fin-zqt_ini
546      ENDIF
547!
548!------------------------------------------------------------------------------|
549!  I-8) Recover energy of melting, salinity and temperature                    |
550!------------------------------------------------------------------------------|
551!
552      DO layer = 1, nlay_i
553         q_i_b(ji,layer) = zqh_i1(layer) / 
554     &                     MAX( deltaz_i_phy(layer) , zeps )
555      END DO
556
557      DO layer = 1, nlay_i
558         s_i_b(ji,layer) = zsh_i1(layer) / MAX( deltaz_i_phy(layer) , 
559     &                     zeps )
560      END DO
561
562      DO layer = 1, nlay_i
563         tmelts = -tmut*s_i_b(ji,layer) + tpw
564         aaa = cpg
565         bbb = (cpw-cpg)*(tmelts-tpw) + q_i_b(ji,layer)/ rhog
566     &       - lfus 
567         ccc = lfus * (tmelts-tpw)
568         discrim = SQRT( bbb*bbb - 4.0*aaa*ccc )
569         t_i_b(ji,layer) = tpw + (- bbb - discrim) / ( 2.0*aaa )
570      END DO
571!
572!------------------------------------------------------------------------------|
573!  I-9) Salt conservation test                                                 |
574!------------------------------------------------------------------------------|
575!
576      CALL ice_sal_column(kideb,kiut,z_ms_i_fin,s_i_b(ji,1:nlay_i),
577     &                    deltaz_i_phy, nlay_i, .FALSE.)
578      IF ( ln_write ) WRITE(numout,*) ' z_ms_i_fin : ',
579     &                z_ms_i_fin
580
581      dms_i = z_ms_i_fin / 1000. - dms_i         ! 2nd step of computation of the change in mass of salt in sea ice
582
583      ! Flux due to bottom and snow ice formation
584      zfgrml = zsh_i_new / ddtb
585      zfsigr = zsh_i_sni / ddtb
586
587      zfgrml = zfgrml + zfmelt
588      IF ( ln_write ) THEN
589         WRITE(numout,*) ' zfgrml : ', zfgrml
590         WRITE(numout,*) ' zfsigr : ', zfsigr
591      ENDIF
592
593      zerror = 1.0e-9
594      CALL ice_sal_conserv(kideb,kiut,'ice_phy_remap: ',zerror,
595     &                           z_ms_i_ini,z_ms_i_fin,
596     &                           zfgrml, zfsigr, ddtb)
597
598 10   CONTINUE
599
600      RETURN
601
602!-------------------------------------------------------------------------------
603! Fin de la routine ice_th_remap
604      END
Note: See TracBrowser for help on using the repository browser.