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.
limistate.F90 in branches/2013/dev_r3406_CNRS_LIM3/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2013/dev_r3406_CNRS_LIM3/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90 @ 3977

Last change on this file since 3977 was 3938, checked in by flavoni, 11 years ago

dev_r3406_CNRS_LIM3: update LIM3, see ticket #1116

  • Property svn:keywords set to Id
File size: 23.5 KB
Line 
1MODULE limistate
2   !!======================================================================
3   !!                     ***  MODULE  limistate  ***
4   !!              Initialisation of diagnostics ice variables
5   !!======================================================================
6   !! History :  2.0  ! 2004-01 (C. Ethe, G. Madec)  Original code
7   !!            4.0  ! 2011-02 (G. Madec) dynamical allocation
8   !!             -   ! 2012    (C. Rousset) clean + add par_oce (for jp_sal)...bug?
9   !!----------------------------------------------------------------------
10#if defined key_lim3
11   !!----------------------------------------------------------------------
12   !!   'key_lim3' :                                    LIM3 sea-ice model
13   !!----------------------------------------------------------------------
14   !!   lim_istate      :  Initialisation of diagnostics ice variables
15   !!   lim_istate_init :  initialization of ice state and namelist read
16   !!----------------------------------------------------------------------
17   USE phycst           ! physical constant
18   USE oce              ! dynamics and tracers variables
19   USE dom_oce          ! ocean domain
20   USE sbc_oce          ! Surface boundary condition: ocean fields
21   USE eosbn2           ! equation of state
22   USE ice              ! sea-ice variables
23   USE par_ice          ! ice parameters
24   USE par_oce          ! ocean parameters
25   USE dom_ice          ! sea-ice domain
26   USE in_out_manager   ! I/O manager
27   USE lbclnk           ! lateral boundary condition - MPP exchanges
28   USE lib_mpp          ! MPP library
29   USE wrk_nemo         ! work arrays
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   lim_istate      ! routine called by lim_init.F90
35
36   !                                  !!** init namelist (namiceini) **
37   REAL(wp) ::   ttest    = 2.0_wp     ! threshold water temperature for initial sea ice
38   REAL(wp) ::   hninn    = 0.5_wp     ! initial snow thickness in the north
39   REAL(wp) ::   hginn_u  = 2.5_wp     ! initial ice thickness in the north
40   REAL(wp) ::   aginn_u  = 0.7_wp     ! initial leads area in the north
41   REAL(wp) ::   hginn_d  = 5.0_wp     ! initial ice thickness in the north
42   REAL(wp) ::   aginn_d  = 0.25_wp    ! initial leads area in the north
43   REAL(wp) ::   hnins    = 0.1_wp     ! initial snow thickness in the south
44   REAL(wp) ::   hgins_u  = 1.0_wp     ! initial ice thickness in the south
45   REAL(wp) ::   agins_u  = 0.7_wp     ! initial leads area in the south
46   REAL(wp) ::   hgins_d  = 2.0_wp     ! initial ice thickness in the south
47   REAL(wp) ::   agins_d  = 0.2_wp     ! initial leads area in the south
48   REAL(wp) ::   sinn     = 6.301_wp   ! initial salinity
49   REAL(wp) ::   sins     = 6.301_wp   !
50
51   !!----------------------------------------------------------------------
52   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
53   !! $Id$
54   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
55   !!----------------------------------------------------------------------
56CONTAINS
57
58   SUBROUTINE lim_istate
59      !!-------------------------------------------------------------------
60      !!                    ***  ROUTINE lim_istate  ***
61      !!
62      !! ** Purpose :   defined the sea-ice initial state
63      !!
64      !! ** Method  :   restart from a state defined in a binary file
65      !!                or from arbitrary sea-ice conditions
66      !!-------------------------------------------------------------------
67      INTEGER  ::   ji, jj, jk, jl            ! dummy loop indices
68      INTEGER  ::   i_fill, jl0, ztest_1, ztest_2, ztest_3, ztest_4, ztests 
69      REAL(wp) ::   zarg, zV, zconv
70      REAL(wp) ::   zeps06, zeps, ztmelts   ! local scalars
71      REAL(wp),          DIMENSION(jpl) ::   zain, zhtin, zhtsn, zais, zhtis, zhtss 
72      REAL(wp),          DIMENSION(jpl) ::   zai, zhti, zhts 
73      REAL(wp), POINTER, DIMENSION(:,:) ::   zidto      ! ice indicator
74      !--------------------------------------------------------------------
75
76      CALL wrk_alloc( jpi, jpj, zidto )
77
78      !--------------------------------------------------------------------
79      ! 1) Preliminary things
80      !--------------------------------------------------------------------
81
82      CALL lim_istate_init     !  reading the initials parameters of the ice
83
84!!gm  in lim2  the initialisation if only done if required in the namelist :
85!!gm      IF( .NOT. ln_limini ) THEN
86!!gm  this should be added in lim3 namelist...
87
88      !--------------------------------------------------------------------
89      ! 2) Ice initialization (hi,hs,frld,t_su,sm_i,t_i,t_s)              |
90      !--------------------------------------------------------------------
91
92      IF(lwp) WRITE(numout,*)
93      IF(lwp) WRITE(numout,*) 'lim_istate : Ice initialization '
94      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
95
96      t_bo(:,:) = tfreez( tsn(:,:,1,jp_sal) ) * tmask(:,:,1)       ! freezing/melting point of sea water [Celcius]
97
98      DO jj = 1, jpj                                       ! ice if sst <= t-freez + ttest
99         DO ji = 1, jpi
100            IF( tsn(ji,jj,1,jp_tem)  - t_bo(ji,jj) >= ttest ) THEN   ;   zidto(ji,jj) = 0.e0      ! no ice
101            ELSE                                                     ;   zidto(ji,jj) = 1.e0      !    ice
102            ENDIF
103         END DO
104      END DO
105
106      t_bo(:,:) = t_bo(:,:) + rt0                          ! t_bo converted from Celsius to Kelvin (rt0 over land)
107
108      ! constants for heat contents
109      zeps    = 1.e-20_wp
110      zeps06  = 1.e-06_wp
111
112      !-------------------------------------------------------------------
113      ! 3) Distribute ice concentration and thickness into the categories
114      !-------------------------------------------------------------------
115      ! snow distribution
116      zhtsn(1:jpl) = 0.d0
117      zhtss(1:jpl) = 0.d0
118      DO jl = 1, jpl
119         zhtsn(jl) = hninn
120         zhtss(jl) = hnins
121      END DO
122
123      ! -------------------
124      ! Northern Hemisphere
125      ! -------------------
126      ! initialisation of tests
127      ztest_1 = 0
128      ztest_2 = 0
129      ztest_3 = 0
130      ztest_4 = 0
131      ztests  = 0
132         
133      i_fill = jpl + 1                                    !====================================
134      DO WHILE ( ( ztests /= 4 ) .AND. ( i_fill >= 2 ) )  ! iterative loop on i_fill categories 
135         ! iteration                                      !====================================
136         i_fill = i_fill - 1
137 
138         ! initialisation of ice variables for each try
139         zhtin(1:jpl) = 0.d0
140         zain (1:jpl) = 0.d0
141         
142         ! *** case very thin ice: fill only category 1
143         IF ( i_fill == 1 ) THEN
144            zhtin(1) = hginn_u
145            zain (1) = aginn_u
146           
147            ! *** case ice is thicker: fill categories >1
148         ELSE
149           
150            ! Fill ice thicknesses except the last one (i_fill) by (hmax-hmin)/2
151            DO jl = 1, i_fill - 1
152               zhtin(jl) = ( hi_max(jl) + hi_max(jl-1) ) / 2.
153            END DO
154           
155            ! find which category (jl0) the input ice thickness falls into
156            jl0 = i_fill
157            DO jl = 1, i_fill
158               IF ( ( hginn_u >= hi_max(jl-1) ) .AND. ( hginn_u < hi_max(jl) ) ) THEN
159                  jl0 = jl
160                  CYCLE
161               ENDIF
162            END DO
163           
164            ! Concentrations in the (i_fill-1) categories
165            zain(jl0) = aginn_u / SQRT(REAL(jpl))
166            DO jl = 1, i_fill - 1
167               IF ( jl == jl0 ) CYCLE
168               zarg           = ( zhtin(jl) - hginn_u ) / ( hginn_u / 2. )
169               zain(jl) =   zain (jl0) * EXP(-zarg**2)
170            END DO
171           
172            ! Concentration in the last (i_fill) category
173            zain(i_fill) = aginn_u - SUM( zain(1:i_fill-1) )
174           
175            ! Ice thickness in the last (i_fill) category
176            zV = SUM( zain(1:i_fill-1) * zhtin(1:i_fill-1) )
177            zhtin(i_fill) = ( hginn_u*aginn_u -  zV ) / zain(i_fill) 
178           
179         ENDIF ! case ice is thick or thin
180         
181         !---------------------
182         ! Compatibility tests
183         !---------------------
184         ! Test 1: area conservation
185         zconv = ABS( aginn_u - SUM( zain(1:jpl) ) )
186         IF ( zconv < zeps06 ) ztest_1 = 1
187         
188         ! Test 2: volume conservation
189         zconv = ABS( hginn_u*aginn_u - SUM( zain(1:jpl)*zhtin(1:jpl) ) )
190         IF ( zconv < zeps06 ) ztest_2 = 1
191         
192         ! Test 3: thickness of the last category is in-bounds ?
193         IF ( zhtin(i_fill) >= hi_max(i_fill-1) ) ztest_3 = 1
194         
195         ! Test 4: positivity of ice concentrations
196         ztest_4 = 1
197         DO jl = 1, i_fill
198            IF ( zain(jl) < 0.0d0 ) ztest_4 = 0
199         END DO
200         
201         ztests = ztest_1 + ztest_2 + ztest_3 + ztest_4
202                                                        !============================
203      END DO                                            ! end iteration on categories
204                                                        !============================
205      ! Check if tests have passed (i.e. volume conservation...)
206      IF ( ztests .NE. 4 ) THEN
207         WRITE(numout,*) ' !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! '
208         WRITE(numout,*) ' !! ALERT categories distribution !!'
209         WRITE(numout,*) ' !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! '
210         WRITE(numout,*) ' *** ztests is not equal to 4 '
211         WRITE(numout,*) ' *** ztest (1:4) = ', ztest_1, ztest_2, ztest_3, ztest_4
212      ENDIF
213
214      ! -------------------
215      ! Southern Hemisphere
216      ! -------------------
217      ! initialisation of tests
218      ztest_1 = 0
219      ztest_2 = 0
220      ztest_3 = 0
221      ztest_4 = 0
222      ztests  = 0
223         
224      i_fill = jpl + 1                                    !====================================
225      DO WHILE ( ( ztests /= 4 ) .AND. ( i_fill >= 2 ) )  ! iterative loop on i_fill categories 
226         ! iteration                                      !====================================
227         i_fill = i_fill - 1
228 
229         ! initialisation of ice variables for each try
230         zhtis(1:jpl) = 0.d0
231         zais (1:jpl) = 0.d0
232         
233         ! *** case very thin ice: fill only category 1
234         IF ( i_fill == 1 ) THEN
235            zhtis(1) = hgins_u
236            zais (1) = agins_u
237           
238            ! *** case ice is thicker: fill categories >1
239         ELSE
240           
241            ! Fill ice thicknesses except the last one (i_fill) by (hmax-hmin)/2
242            DO jl = 1, i_fill - 1
243               zhtis(jl) = ( hi_max(jl) + hi_max(jl-1) ) / 2.
244            END DO
245           
246            ! find which category (jl0) the input ice thickness falls into
247            jl0 = i_fill
248            DO jl = 1, i_fill
249               IF ( ( hgins_u >= hi_max(jl-1) ) .AND. ( hgins_u < hi_max(jl) ) ) THEN
250                  jl0 = jl
251                  CYCLE
252               ENDIF
253            END DO
254           
255            ! Concentrations in the (i_fill-1) categories
256            zais(jl0) = agins_u / SQRT(REAL(jpl))
257            DO jl = 1, i_fill - 1
258               IF ( jl == jl0 ) CYCLE
259               zarg           = ( zhtis(jl) - hgins_u ) / ( hgins_u / 2. )
260               zais(jl) =   zais (jl0) * EXP(-zarg**2)
261            END DO
262           
263            ! Concentration in the last (i_fill) category
264            zais(i_fill) = agins_u - SUM( zais(1:i_fill-1) )
265           
266            ! Ice thickness in the last (i_fill) category
267            zV = SUM( zais(1:i_fill-1) * zhtis(1:i_fill-1) )
268            zhtis(i_fill) = ( hgins_u*agins_u -  zV ) / zais(i_fill) 
269           
270         ENDIF ! case ice is thick or thin
271         
272         !---------------------
273         ! Compatibility tests
274         !---------------------
275         ! Test 1: area conservation
276         zconv = ABS( agins_u - SUM( zais(1:jpl) ) )
277         IF ( zconv < zeps06 ) ztest_1 = 1
278         
279         ! Test 2: volume conservation
280         zconv = ABS( hgins_u*agins_u - SUM( zais(1:jpl)*zhtis(1:jpl) ) )
281         IF ( zconv < zeps06 ) ztest_2 = 1
282         
283         ! Test 3: thickness of the last category is in-bounds ?
284         IF ( zhtis(i_fill) >= hi_max(i_fill-1) ) ztest_3 = 1
285         
286         ! Test 4: positivity of ice concentrations
287         ztest_4 = 1
288         DO jl = 1, i_fill
289            IF ( zais(jl) < 0.0d0 ) ztest_4 = 0
290         END DO
291         
292         ztests = ztest_1 + ztest_2 + ztest_3 + ztest_4
293                                                        !============================
294      END DO                                            ! end iteration on categories
295                                                        !============================
296      ! Check if tests have passed (i.e. volume conservation...)
297      IF ( ztests .NE. 4 ) THEN
298         WRITE(numout,*) ' !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! '
299         WRITE(numout,*) ' !! ALERT categories distribution !!'
300         WRITE(numout,*) ' !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! '
301         WRITE(numout,*) ' *** ztests is not equal to 4 '
302         WRITE(numout,*) ' *** ztest (1:4) = ', ztest_1, ztest_2, ztest_3, ztest_4
303      ENDIF
304!!
305!!
306!!
307      ! ---------------------
308      ! 4) fill ice variables
309      ! ---------------------
310      zai(:) = 0.0
311      zhti(:)= 0.0
312      zhts(:)= 0.0
313      DO jj = 1, jpj
314         DO ji = 1, jpi
315
316            !--- Northern hemisphere
317            !----------------------------------------------------------------
318            IF( fcor(ji,jj) >= 0._wp ) THEN
319               zai(:) = zain(:) ; zhti(:) = zhtin(:) ; zhts(:) = zhtsn(:)     
320            ELSE
321               zai(:) = zais(:) ; zhti(:) = zhtis(:) ; zhts(:) = zhtss(:)     
322            ENDIF
323           
324            DO jl = 1, jpl
325               !-----------------------
326               ! Ice area / thickness
327               !-----------------------
328               a_i(ji,jj,jl)    = zidto(ji,jj) * zai(jl)
329               ht_i(ji,jj,jl)   = zidto(ji,jj) * zhti(jl)
330               v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl)
331               
332               !-------------
333               ! Snow depth
334               !-------------
335               ht_s(ji,jj,jl)   = zidto(ji,jj) * zhts(jl)
336               v_s(ji,jj,jl)    = ht_s(ji,jj,jl)*a_i(ji,jj,jl)
337               
338               !---------------
339               ! Ice salinity
340               !---------------
341               sm_i(ji,jj,jl)   = zidto(ji,jj) * sinn  + ( 1.0 - zidto(ji,jj) ) * 0.1
342               smv_i(ji,jj,jl)  = MIN( sm_i(ji,jj,jl) , sss_m(ji,jj) ) * v_i(ji,jj,jl)
343               
344               !----------
345               ! Ice age
346               !----------
347               o_i(ji,jj,jl)    = zidto(ji,jj) * 1.0   + ( 1.0 - zidto(ji,jj) )
348               oa_i(ji,jj,jl)   = o_i(ji,jj,jl) * a_i(ji,jj,jl)
349               
350               !------------------------------
351               ! Sea ice surface temperature
352               !------------------------------
353               t_su(ji,jj,jl)   = zidto(ji,jj) * 270.0 + ( 1.0 - zidto(ji,jj) ) * t_bo(ji,jj)
354               
355               !------------------------------------
356               ! Snow temperature and heat content
357               !------------------------------------
358               DO jk = 1, nlay_s
359                  t_s(ji,jj,jk,jl) = zidto(ji,jj) * 270.00 + ( 1.0 - zidto(ji,jj) ) * rtt
360                  ! Snow energy of melting
361                  e_s(ji,jj,jk,jl) = zidto(ji,jj) * rhosn * ( cpic * ( rtt - t_s(ji,jj,jk,jl) ) + lfus )
362                  ! Change dimensions
363                  e_s(ji,jj,jk,jl) = e_s(ji,jj,jk,jl) / unit_fac
364                  ! Multiply by volume, so that heat content in 10^9 Joules
365                  e_s(ji,jj,jk,jl) = e_s(ji,jj,jk,jl) * area(ji,jj) * &
366                       v_s(ji,jj,jl)  / REAL( nlay_s )
367               END DO !jk
368               
369               !-----------------------------------------------
370               ! Ice salinities, temperature and heat content
371               !-----------------------------------------------
372               DO jk = 1, nlay_i
373                  t_i(ji,jj,jk,jl) = zidto(ji,jj)*270.00 + ( 1.0 - zidto(ji,jj) ) * rtt 
374                  s_i(ji,jj,jk,jl) = zidto(ji,jj) * sinn + ( 1.0 - zidto(ji,jj) ) * 0.1
375                  ztmelts          = - tmut * s_i(ji,jj,jk,jl) + rtt !Melting temperature in K
376                 
377                  ! heat content per unit volume
378                  e_i(ji,jj,jk,jl) = zidto(ji,jj) * rhoic * &
379                       (   cpic    * ( ztmelts - t_i(ji,jj,jk,jl) ) &
380                       +   lfus    * ( 1.0 - (ztmelts-rtt) / MIN((t_i(ji,jj,jk,jl)-rtt),-zeps) ) &
381                       - rcp      * ( ztmelts - rtt ) &
382                       )
383                 
384                  ! Correct dimensions to avoid big values
385                  e_i(ji,jj,jk,jl) = e_i(ji,jj,jk,jl) / unit_fac 
386                 
387                  ! Mutliply by ice volume, and divide by number of layers to get heat content in 10^9 J
388                  e_i(ji,jj,jk,jl) = e_i(ji,jj,jk,jl) * & 
389                       area(ji,jj) * a_i(ji,jj,jl) * ht_i(ji,jj,jl) / &
390                       REAL( nlay_i )
391               END DO ! jk
392               
393            END DO ! jl
394           
395         END DO
396      END DO
397 
398      IF(lwp) THEN                        ! control print
399         WRITE(numout,*) '~~~~~~~~~~~~~~~'
400         WRITE(numout,*) '   max ice  thickness   = ', (MAXVAL(ht_i(:,:,jl)),jl=1,jpl)
401         WRITE(numout,*) '   max snow thickness   = ', (MAXVAL(ht_s(:,:,jl)),jl=1,jpl)
402         WRITE(numout,*) '   max ice  area        = ', (MAXVAL(a_i(:,:,jl)),jl=1,jpl)
403         WRITE(numout,*) '   max ice  salinity    = ', (MAXVAL(sm_i(:,:,jl)),jl=1,jpl)
404         WRITE(numout,*) '   min ice  salinity    = ', (MINVAL(sm_i(:,:,jl)),jl=1,jpl)
405         WRITE(numout,*) '   max ice  surf temper = ', (MAXVAL(t_su(:,:,jl)-rtt),jl=1,jpl)
406         WRITE(numout,*) '   min ice  surf temper = ', (MINVAL(t_su(:,:,jl)-rtt),jl=1,jpl)
407      ENDIF
408
409      !--------------------------------------------------------------------
410      ! 5) Global ice variables for output diagnostics                    |
411      !--------------------------------------------------------------------
412
413      fsbbq (:,:)     = 0.e0
414      u_ice (:,:)     = 0.e0
415      v_ice (:,:)     = 0.e0
416      stress1_i(:,:)  = 0.0
417      stress2_i(:,:)  = 0.0
418      stress12_i(:,:) = 0.0
419
420      !--------------------------------------------------------------------
421      ! 6) Moments for advection
422      !--------------------------------------------------------------------
423
424      sxopw (:,:) = 0.e0 
425      syopw (:,:) = 0.e0 
426      sxxopw(:,:) = 0.e0 
427      syyopw(:,:) = 0.e0 
428      sxyopw(:,:) = 0.e0
429
430      sxice (:,:,:)  = 0.e0   ;   sxsn (:,:,:)  = 0.e0   ;   sxa  (:,:,:)  = 0.e0
431      syice (:,:,:)  = 0.e0   ;   sysn (:,:,:)  = 0.e0   ;   sya  (:,:,:)  = 0.e0
432      sxxice(:,:,:)  = 0.e0   ;   sxxsn(:,:,:)  = 0.e0   ;   sxxa (:,:,:)  = 0.e0
433      syyice(:,:,:)  = 0.e0   ;   syysn(:,:,:)  = 0.e0   ;   syya (:,:,:)  = 0.e0
434      sxyice(:,:,:)  = 0.e0   ;   sxysn(:,:,:)  = 0.e0   ;   sxya (:,:,:)  = 0.e0
435
436      sxc0  (:,:,:)  = 0.e0   ;   sxe  (:,:,:,:)= 0.e0   
437      syc0  (:,:,:)  = 0.e0   ;   sye  (:,:,:,:)= 0.e0   
438      sxxc0 (:,:,:)  = 0.e0   ;   sxxe (:,:,:,:)= 0.e0   
439      syyc0 (:,:,:)  = 0.e0   ;   syye (:,:,:,:)= 0.e0   
440      sxyc0 (:,:,:)  = 0.e0   ;   sxye (:,:,:,:)= 0.e0   
441
442      sxsal  (:,:,:)  = 0.e0
443      sysal  (:,:,:)  = 0.e0
444      sxxsal (:,:,:)  = 0.e0
445      syysal (:,:,:)  = 0.e0
446      sxysal (:,:,:)  = 0.e0
447
448      sxopw(:,:) = 0.e0 ; syopw(:,:) = 0.e0; sxxopw(:,:) = 0.e0; syyopw(:,:) = 0.e0; sxyopw(:,:) = 0.e0
449
450      !--------------------------------------------------------------------
451      ! 7) Lateral boundary conditions                                    |
452      !--------------------------------------------------------------------
453
454      DO jl = 1, jpl
455         CALL lbc_lnk( a_i(:,:,jl)  , 'T', 1. )
456         CALL lbc_lnk( v_i(:,:,jl)  , 'T', 1. )
457         CALL lbc_lnk( v_s(:,:,jl)  , 'T', 1. )
458         CALL lbc_lnk( smv_i(:,:,jl), 'T', 1. )
459         CALL lbc_lnk( oa_i(:,:,jl) , 'T', 1. )
460         !
461         CALL lbc_lnk( ht_i(:,:,jl) , 'T', 1. )
462         CALL lbc_lnk( ht_s(:,:,jl) , 'T', 1. )
463         CALL lbc_lnk( sm_i(:,:,jl) , 'T', 1. )
464         CALL lbc_lnk( o_i(:,:,jl)  , 'T', 1. )
465         CALL lbc_lnk( t_su(:,:,jl) , 'T', 1. )
466         DO jk = 1, nlay_s
467            CALL lbc_lnk(t_s(:,:,jk,jl), 'T', 1. )
468            CALL lbc_lnk(e_s(:,:,jk,jl), 'T', 1. )
469         END DO
470         DO jk = 1, nlay_i
471            CALL lbc_lnk(t_i(:,:,jk,jl), 'T', 1. )
472            CALL lbc_lnk(e_i(:,:,jk,jl), 'T', 1. )
473         END DO
474         !
475         a_i(:,:,jl) = tms(:,:) * a_i(:,:,jl)
476      END DO
477
478      CALL lbc_lnk( at_i , 'T', 1. )
479      at_i(:,:) = tms(:,:) * at_i(:,:)                       ! put 0 over land
480      !
481      CALL lbc_lnk( fsbbq  , 'T', 1. )
482      !
483      CALL wrk_dealloc( jpi, jpj, zidto )
484      !
485   END SUBROUTINE lim_istate
486
487
488   SUBROUTINE lim_istate_init
489      !!-------------------------------------------------------------------
490      !!                   ***  ROUTINE lim_istate_init  ***
491      !!       
492      !! ** Purpose : Definition of initial state of the ice
493      !!
494      !! ** Method :   Read the namiceini namelist and check the parameter
495      !!             values called at the first timestep (nit000)
496      !!
497      !! ** input  :   namelist namiceini
498      !!-----------------------------------------------------------------------------
499      NAMELIST/namiceini/ ttest, hninn, hginn_u, aginn_u, hginn_d, aginn_d, hnins,   &
500         &                hgins_u, agins_u, hgins_d, agins_d, sinn, sins
501      !!-----------------------------------------------------------------------------
502      !
503      REWIND ( numnam_ice )               ! Read Namelist namiceini
504      READ   ( numnam_ice , namiceini )
505      !
506      IF(lwp) THEN                        ! control print
507         WRITE(numout,*)
508         WRITE(numout,*) 'lim_istate_init : ice parameters inititialisation '
509         WRITE(numout,*) '~~~~~~~~~~~~~~~'
510         WRITE(numout,*) '   threshold water temp. for initial sea-ice    ttest      = ', ttest
511         WRITE(numout,*) '   initial snow thickness in the north          hninn      = ', hninn
512         WRITE(numout,*) '   initial undef ice thickness in the north     hginn_u    = ', hginn_u
513         WRITE(numout,*) '   initial undef ice concentr. in the north     aginn_u    = ', aginn_u         
514         WRITE(numout,*) '   initial  def  ice thickness in the north     hginn_d    = ', hginn_d
515         WRITE(numout,*) '   initial  def  ice concentr. in the north     aginn_d    = ', aginn_d         
516         WRITE(numout,*) '   initial snow thickness in the south          hnins      = ', hnins 
517         WRITE(numout,*) '   initial undef ice thickness in the north     hgins_u    = ', hgins_u
518         WRITE(numout,*) '   initial undef ice concentr. in the north     agins_u    = ', agins_u         
519         WRITE(numout,*) '   initial  def  ice thickness in the north     hgins_d    = ', hgins_d
520         WRITE(numout,*) '   initial  def  ice concentr. in the north     agins_d    = ', agins_d         
521         WRITE(numout,*) '   initial  ice salinity       in the north     sinn       = ', sinn
522         WRITE(numout,*) '   initial  ice salinity       in the south     sins       = ', sins
523      ENDIF
524      !
525   END SUBROUTINE lim_istate_init
526
527#else
528   !!----------------------------------------------------------------------
529   !!   Default option :         Empty module          NO LIM sea-ice model
530   !!----------------------------------------------------------------------
531CONTAINS
532   SUBROUTINE lim_istate          ! Empty routine
533   END SUBROUTINE lim_istate
534#endif
535
536   !!======================================================================
537END MODULE limistate
Note: See TracBrowser for help on using the repository browser.