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

source: branches/2014/dev_CNRS_2014/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90 @ 4896

Last change on this file since 4896 was 4896, checked in by cetlod, 10 years ago

2014/dev_CNRS_2014 : merge the 1st branch onto dev_CNRS_2014, see ticket #1415

  • Property svn:keywords set to Id
File size: 24.4 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) 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 sbc_ice          ! Surface boundary condition: ice fields
22   USE eosbn2           ! equation of state
23   USE ice              ! sea-ice variables
24   USE par_ice          ! ice parameters
25   USE par_oce          ! ocean parameters
26   USE dom_ice          ! sea-ice domain
27   USE in_out_manager   ! I/O manager
28   USE lbclnk           ! lateral boundary condition - MPP exchanges
29   USE lib_mpp          ! MPP library
30   USE lib_fortran      ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
31   USE wrk_nemo         ! work arrays
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC   lim_istate      ! routine called by lim_init.F90
37
38   !                          !!** init namelist (namiceini) **
39   REAL(wp) ::   ttest   ! threshold water temperature for initial sea ice
40   REAL(wp) ::   hninn   ! initial snow thickness in the north
41   REAL(wp) ::   hnins   ! initial snow thickness in the south
42   REAL(wp) ::   hginn   ! initial ice thickness in the north
43   REAL(wp) ::   hgins   ! initial ice thickness in the south
44   REAL(wp) ::   aginn   ! initial leads area in the north
45   REAL(wp) ::   agins   ! initial leads area in the south
46   REAL(wp) ::   sinn    ! initial salinity
47   REAL(wp) ::   sins 
48
49   !!----------------------------------------------------------------------
50   !!   LIM 3.0,  UCL-LOCEAN-IPSL (2008)
51   !! $Id$
52   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
53   !!----------------------------------------------------------------------
54CONTAINS
55
56   SUBROUTINE lim_istate
57      !!-------------------------------------------------------------------
58      !!                    ***  ROUTINE lim_istate  ***
59      !!
60      !! ** Purpose :   defined the sea-ice initial state
61      !!
62      !! ** Method  :   
63      !!                This routine will put some ice where ocean
64      !!                is at the freezing point, then fill in ice
65      !!                state variables using prescribed initial
66      !!                values in the namelist           
67      !!
68      !! ** Steps   :   
69      !!                1) Read namelist
70      !!                2) Basal temperature; ice and hemisphere masks
71      !!                3) Fill in the ice thickness distribution using gaussian
72      !!                4) Fill in space-dependent arrays for state variables
73      !!                5) Diagnostic arrays
74      !!                6) Lateral boundary conditions
75      !!
76      !! ** Notes   : o_i, t_su, t_s, t_i, s_i must be filled everywhere, even
77      !!              where there is no ice (clem: I do not know why but it is mandatory)
78      !!
79      !! History :
80      !!   2.0  !  01-04  (C. Ethe, G. Madec)  Original code
81      !!   3.0  !  2007   (M. Vancoppenolle)   Rewrite for ice cats
82      !!   4.0  !  09-11  (M. Vancoppenolle)   Enhanced version for ice cats
83      !!--------------------------------------------------------------------
84
85      !! * Local variables
86      INTEGER    :: ji, jj, jk, jl             ! dummy loop indices
87      REAL(wp)   :: epsi20, ztmelts, zdh
88      INTEGER    :: i_hemis, i_fill, jl0 
89      REAL(wp)   :: ztest_1, ztest_2, ztest_3, ztest_4, ztests, zsigma, zarg, zA, zV, zA_cons, zV_cons, zconv
90      REAL(wp), POINTER, DIMENSION(:)     :: zhm_i_ini, zat_i_ini, zvt_i_ini, zhm_s_ini, zsm_i_ini
91      REAL(wp), POINTER, DIMENSION(:,:)   :: zht_i_ini, za_i_ini, zv_i_ini
92      REAL(wp), POINTER, DIMENSION(:,:)   :: zidto    ! ice indicator
93      INTEGER,  POINTER, DIMENSION(:,:)   :: zhemis   ! hemispheric index
94      !--------------------------------------------------------------------
95
96      CALL wrk_alloc( jpi, jpj, zidto )
97      CALL wrk_alloc( jpi, jpj, zhemis )
98      CALL wrk_alloc( jpl,   2, zht_i_ini,  za_i_ini,  zv_i_ini )
99      CALL wrk_alloc(   2,      zhm_i_ini, zat_i_ini, zvt_i_ini, zhm_s_ini, zsm_i_ini )
100
101      epsi20   = 1.0e-20
102      IF(lwp) WRITE(numout,*)
103      IF(lwp) WRITE(numout,*) 'lim_istate : Ice initialization '
104      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
105
106      !--------------------------------------------------------------------
107      ! 1) Read namelist
108      !--------------------------------------------------------------------
109
110      CALL lim_istate_init     !  reading the initials parameters of the ice
111
112!!gm  in lim2  the initialisation if only done if required in the namelist :
113!!gm      IF( .NOT. ln_limini ) THEN
114!!gm  this should be added in lim3 namelist...
115
116      !--------------------------------------------------------------------
117      ! 2) Basal temperature, ice mask and hemispheric index
118      !--------------------------------------------------------------------
119
120      ! Basal temperature is set to the freezing point of seawater in Celsius
121      t_bo(:,:) = eos_fzp( tsn(:,:,1,jp_sal) ) * tmask(:,:,1)       ! freezing/melting point of sea water [Celcius]
122
123      DO jj = 1, jpj                                       ! ice if sst <= t-freez + ttest
124         DO ji = 1, jpi
125            IF( tsn(ji,jj,1,jp_tem)  - t_bo(ji,jj) >= ttest ) THEN   ;   zidto(ji,jj) = 0._wp      ! no ice
126            ELSE                                                     ;   zidto(ji,jj) = 1._wp      !    ice
127            ENDIF
128         END DO
129      END DO
130
131      t_bo(:,:) = t_bo(:,:) + rt0                          ! conversion to Kelvin
132
133      ! Hemispheric index
134      ! MV 2011 new initialization
135      DO jj = 1, jpj
136         DO ji = 1, jpi
137            IF( fcor(ji,jj) >= 0._wp ) THEN   
138               zhemis(ji,jj) = 1 ! Northern hemisphere
139            ELSE
140               zhemis(ji,jj) = 2 ! Southern hemisphere
141            ENDIF
142         END DO
143      END DO
144      ! END MV 2011 new initialization
145
146      !--------------------------------------------------------------------
147      ! 3) Initialization of sea ice state variables
148      !--------------------------------------------------------------------
149
150      !-----------------------------
151      ! 3.1) Hemisphere-dependent arrays
152      !-----------------------------
153      ! assign initial thickness, concentration, snow depth and salinity to
154      ! an hemisphere-dependent array
155      zhm_i_ini(1) = hginn ; zhm_i_ini(2) = hgins  ! ice thickness
156      zat_i_ini(1) = aginn ; zat_i_ini(2) = agins  ! ice concentration
157      zvt_i_ini(:) = zhm_i_ini(:) * zat_i_ini(:)   ! ice volume
158      zhm_s_ini(1) = hninn ; zhm_s_ini(2) = hnins  ! snow depth
159      zsm_i_ini(1) = sinn  ; zsm_i_ini(2) = sins   ! bulk ice salinity
160
161      !---------------------------------------------------------------------
162      ! 3.2) Distribute ice concentration and thickness into the categories
163      !---------------------------------------------------------------------
164      ! a gaussian distribution for ice concentration is used
165      ! then we check whether the distribution fullfills
166      ! volume and area conservation, positivity and ice categories bounds
167      DO i_hemis = 1, 2
168
169      ztest_1 = 0 ; ztest_2 = 0 ; ztest_3 = 0 ; ztest_4 = 0
170
171      ! note for the great nemo engineers:
172      ! only very few of the WRITE statements are necessary for the reference version
173      ! they were one day useful, but now i personally doubt of their
174      ! potential for bringing anything useful
175
176      DO i_fill = jpl, 1, -1
177         IF ( ( ztest_1 + ztest_2 + ztest_3 + ztest_4 ) .NE. 4 ) THEN
178            !----------------------------
179            ! fill the i_fill categories
180            !----------------------------
181            ! *** 1 category to fill
182            IF ( i_fill .EQ. 1 ) THEN
183               zht_i_ini(1,i_hemis)       = zhm_i_ini(i_hemis)
184               za_i_ini(1,i_hemis)        = zat_i_ini(i_hemis)
185               zht_i_ini(2:jpl,i_hemis)   = 0._wp
186               za_i_ini(2:jpl,i_hemis)    = 0._wp
187            ELSE
188
189            ! *** >1 categores to fill
190            !--- Ice thicknesses in the i_fill - 1 first categories
191               DO jl = 1, i_fill - 1
192                  zht_i_ini(jl,i_hemis)    = 0.5 * ( hi_max(jl) + hi_max(jl-1) )
193               END DO
194
195            !--- jl0: most likely index where cc will be maximum
196               DO jl = 1, jpl
197                  IF ( ( zhm_i_ini(i_hemis) .GT. hi_max(jl-1) ) .AND. &
198                       ( zhm_i_ini(i_hemis) .LE. hi_max(jl)   ) ) THEN
199                     jl0 = jl
200                  ENDIF
201               END DO
202               jl0 = MIN(jl0, i_fill)
203
204            !--- Concentrations
205               za_i_ini(jl0,i_hemis)      = zat_i_ini(i_hemis) / SQRT(REAL(jpl))
206               DO jl = 1, i_fill - 1
207                  IF ( jl .NE. jl0 ) THEN
208                     zsigma               = 0.5 * zhm_i_ini(i_hemis)
209                     zarg                 = ( zht_i_ini(jl,i_hemis) - zhm_i_ini(i_hemis) ) / zsigma
210                     za_i_ini(jl,i_hemis) = za_i_ini(jl0,i_hemis) * EXP(-zarg**2)
211                  ENDIF
212               END DO
213
214               zA = 0. ! sum of the areas in the jpl categories
215               DO jl = 1, i_fill - 1
216                 zA = zA + za_i_ini(jl,i_hemis)
217               END DO
218               za_i_ini(i_fill,i_hemis)   = zat_i_ini(i_hemis) - zA ! ice conc in the last category
219               IF ( i_fill .LT. jpl ) za_i_ini(i_fill+1:jpl, i_hemis) = 0._wp
220         
221            !--- Ice thickness in the last category
222               zV = 0. ! sum of the volumes of the N-1 categories
223               DO jl = 1, i_fill - 1
224                  zV = zV + za_i_ini(jl,i_hemis)*zht_i_ini(jl,i_hemis)
225               END DO
226               zht_i_ini(i_fill,i_hemis) = ( zvt_i_ini(i_hemis) - zV ) / za_i_ini(i_fill,i_hemis) 
227               IF ( i_fill .LT. jpl ) zht_i_ini(i_fill+1:jpl, i_hemis) = 0._wp
228
229            !--- volumes
230               zv_i_ini(:,i_hemis) = za_i_ini(:,i_hemis) * zht_i_ini(:,i_hemis)
231               IF ( i_fill .LT. jpl ) zv_i_ini(i_fill+1:jpl, i_hemis) = 0._wp
232
233            ENDIF ! i_fill
234
235            !---------------------
236            ! Compatibility tests
237            !---------------------
238            ! Test 1: area conservation
239            zA_cons = SUM(za_i_ini(:,i_hemis)) ; zconv = ABS(zat_i_ini(i_hemis) - zA_cons )
240            IF ( zconv .LT. 1.0e-6 ) THEN
241               ztest_1 = 1
242            ELSE 
243              ! this write is useful
244              IF(lwp)  WRITE(numout,*) ' * TEST1 AREA NOT CONSERVED *** zA_cons = ', zA_cons,' zat_i_ini = ',zat_i_ini(i_hemis) 
245               ztest_1 = 0
246            ENDIF
247
248            ! Test 2: volume conservation
249            zV_cons = SUM(zv_i_ini(:,i_hemis))
250            zconv = ABS(zvt_i_ini(i_hemis) - zV_cons)
251
252            IF ( zconv .LT. 1.0e-6 ) THEN
253               ztest_2 = 1
254            ELSE
255              ! this write is useful
256              IF(lwp)  WRITE(numout,*) ' * TEST2 VOLUME NOT CONSERVED *** zV_cons = ', zV_cons, &
257                            ' zvt_i_ini = ', zvt_i_ini(i_hemis)
258               ztest_2 = 0
259            ENDIF
260
261            ! Test 3: thickness of the last category is in-bounds ?
262            IF ( zht_i_ini(i_fill, i_hemis) .GT. hi_max(i_fill-1) ) THEN
263               ztest_3 = 1
264            ELSE
265               ! this write is useful
266               IF(lwp) WRITE(numout,*) ' * TEST 3 THICKNESS OF THE LAST CATEGORY OUT OF BOUNDS *** zht_i_ini(i_fill,i_hemis) = ', &
267               zht_i_ini(i_fill,i_hemis), ' hi_max(jpl-1) = ', hi_max(i_fill-1)
268               ztest_3 = 0
269            ENDIF
270
271            ! Test 4: positivity of ice concentrations
272            ztest_4 = 1
273            DO jl = 1, jpl
274               IF ( za_i_ini(jl,i_hemis) .LT. 0._wp ) THEN 
275                  ! this write is useful
276                  IF(lwp) WRITE(numout,*) ' * TEST 4 POSITIVITY NOT OK FOR CAT ', jl, ' WITH A = ', za_i_ini(jl,i_hemis)
277                  ztest_4 = 0
278               ENDIF
279            END DO
280
281         ENDIF ! ztest_1 + ztest_2 + ztest_3 + ztest_4
282 
283         ztests = ztest_1 + ztest_2 + ztest_3 + ztest_4
284
285      END DO ! i_fill
286
287      IF(lwp) THEN
288         WRITE(numout,*), ' ztests : ', ztests
289         IF ( ztests .NE. 4 ) THEN
290            WRITE(numout,*)
291            WRITE(numout,*), ' !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! '
292            WRITE(numout,*), ' !!!! RED ALERT                  !!! '
293            WRITE(numout,*), ' !!!! BIIIIP BIIIP BIIIIP BIIIIP !!!'
294            WRITE(numout,*), ' !!!! Something is wrong in the LIM3 initialization procedure '
295            WRITE(numout,*), ' !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! '
296            WRITE(numout,*)
297            WRITE(numout,*), ' *** ztests is not equal to 4 '
298            WRITE(numout,*), ' *** ztest_i (i=1,4) = ', ztest_1, ztest_2, ztest_3, ztest_4
299            WRITE(numout,*), ' zat_i_ini : ', zat_i_ini(i_hemis)
300            WRITE(numout,*), ' zhm_i_ini : ', zhm_i_ini(i_hemis)
301         ENDIF ! ztests .NE. 4
302      ENDIF
303     
304      END DO ! i_hemis
305
306      !---------------------------------------------------------------------
307      ! 3.3) Space-dependent arrays for ice state variables
308      !---------------------------------------------------------------------
309
310      ! Ice concentration, thickness and volume, ice salinity, ice age, surface temperature
311      DO jl = 1, jpl ! loop over categories
312         DO jj = 1, jpj
313            DO ji = 1, jpi
314               a_i(ji,jj,jl)   = zidto(ji,jj) * za_i_ini (jl,zhemis(ji,jj))  ! concentration
315               ht_i(ji,jj,jl)  = zidto(ji,jj) * zht_i_ini(jl,zhemis(ji,jj))  ! ice thickness
316               ht_s(ji,jj,jl)  = ht_i(ji,jj,jl) * ( zhm_s_ini( zhemis(ji,jj) ) / zhm_i_ini( zhemis(ji,jj) ) )  ! snow depth
317               sm_i(ji,jj,jl)  = zidto(ji,jj) * zsm_i_ini(zhemis(ji,jj)) + ( 1._wp - zidto(ji,jj) ) * s_i_min ! salinity
318               o_i(ji,jj,jl)   = zidto(ji,jj) * 1._wp + ( 1._wp - zidto(ji,jj) ) ! age
319               t_su(ji,jj,jl)  = zidto(ji,jj) * 270.0 + ( 1._wp - zidto(ji,jj) ) * 270.0 ! surf temp
320
321               ! This case below should not be used if (ht_s/ht_i) is ok in namelist
322               ! In case snow load is in excess that would lead to transformation from snow to ice
323               ! Then, transfer the snow excess into the ice (different from limthd_dh)
324               zdh = MAX( 0._wp, ( rhosn * ht_s(ji,jj,jl) + ( rhoic - rau0 ) * ht_i(ji,jj,jl) ) * r1_rau0 ) 
325               ! recompute ht_i, ht_s avoiding out of bounds values
326               ht_i(ji,jj,jl) = MIN( hi_max(jl), ht_i(ji,jj,jl) + zdh )
327               ht_s(ji,jj,jl) = MAX( 0._wp, ht_s(ji,jj,jl) - zdh * rhoic / rhosn )
328
329               ! ice volume, salt content, age content
330               v_i(ji,jj,jl)   = ht_i(ji,jj,jl) * a_i(ji,jj,jl)              ! ice volume
331               v_s(ji,jj,jl)   = ht_s(ji,jj,jl) * a_i(ji,jj,jl)              ! snow volume
332               smv_i(ji,jj,jl) = MIN( sm_i(ji,jj,jl) , sss_m(ji,jj) ) * v_i(ji,jj,jl) ! salt content
333               oa_i(ji,jj,jl)  = o_i(ji,jj,jl) * a_i(ji,jj,jl)               ! age content
334            END DO ! ji
335         END DO ! jj
336      END DO ! jl
337
338      ! Snow temperature and heat content
339      DO jk = 1, nlay_s
340         DO jl = 1, jpl ! loop over categories
341            DO jj = 1, jpj
342               DO ji = 1, jpi
343                   t_s(ji,jj,jk,jl) = zidto(ji,jj) * 270.0 + ( 1._wp - zidto(ji,jj) ) * rtt
344                   ! Snow energy of melting
345                   e_s(ji,jj,jk,jl) = zidto(ji,jj) * rhosn * ( cpic * ( rtt - t_s(ji,jj,jk,jl) ) + lfus )
346                   ! Change dimensions
347                   e_s(ji,jj,jk,jl) = e_s(ji,jj,jk,jl) / unit_fac
348                   ! Multiply by volume, so that heat content in 10^9 Joules
349                   e_s(ji,jj,jk,jl) = e_s(ji,jj,jk,jl) * area(ji,jj) * v_s(ji,jj,jl) / nlay_s
350               END DO ! ji
351            END DO ! jj
352         END DO ! jl
353      END DO ! jk
354
355      ! Ice salinity, temperature and heat content
356      DO jk = 1, nlay_i
357         DO jl = 1, jpl ! loop over categories
358            DO jj = 1, jpj
359               DO ji = 1, jpi
360                   t_i(ji,jj,jk,jl) = zidto(ji,jj) * 270.00 + ( 1._wp - zidto(ji,jj) ) * rtt 
361                   s_i(ji,jj,jk,jl) = zidto(ji,jj) * zsm_i_ini(zhemis(ji,jj)) + ( 1._wp - zidto(ji,jj) ) * s_i_min
362                   ztmelts          = - tmut * s_i(ji,jj,jk,jl) + rtt !Melting temperature in K
363
364                   ! heat content per unit volume
365                   e_i(ji,jj,jk,jl) = zidto(ji,jj) * rhoic * (   cpic    * ( ztmelts - t_i(ji,jj,jk,jl) ) &
366                      +   lfus    * ( 1._wp - (ztmelts-rtt) / MIN((t_i(ji,jj,jk,jl)-rtt),-epsi20) ) &
367                      -   rcp     * ( ztmelts - rtt ) )
368
369                   ! Correct dimensions to avoid big values
370                   e_i(ji,jj,jk,jl) = e_i(ji,jj,jk,jl) / unit_fac 
371
372                   ! Mutliply by ice volume, and divide by number of layers
373                   ! to get heat content in 10^9 J
374                   e_i(ji,jj,jk,jl) = e_i(ji,jj,jk,jl) * area(ji,jj) * v_i(ji,jj,jl) / nlay_i
375               END DO ! ji
376            END DO ! jj
377         END DO ! jl
378      END DO ! jk
379
380      !--------------------------------------------------------------------
381      ! 4) Global ice variables for output diagnostics                    |
382      !--------------------------------------------------------------------
383      fsbbq (:,:)     = 0._wp
384      u_ice (:,:)     = 0._wp
385      v_ice (:,:)     = 0._wp
386      stress1_i(:,:)  = 0._wp
387      stress2_i(:,:)  = 0._wp
388      stress12_i(:,:) = 0._wp
389
390# if defined key_coupled
391      albege(:,:)   = 0.8 * tms(:,:)
392# endif
393
394      !--------------------------------------------------------------------
395      ! 5) Moments for advection
396      !--------------------------------------------------------------------
397
398      sxopw (:,:) = 0._wp 
399      syopw (:,:) = 0._wp 
400      sxxopw(:,:) = 0._wp 
401      syyopw(:,:) = 0._wp 
402      sxyopw(:,:) = 0._wp
403
404      sxice (:,:,:)  = 0._wp   ;   sxsn (:,:,:)  = 0._wp   ;   sxa  (:,:,:)  = 0._wp
405      syice (:,:,:)  = 0._wp   ;   sysn (:,:,:)  = 0._wp   ;   sya  (:,:,:)  = 0._wp
406      sxxice(:,:,:)  = 0._wp   ;   sxxsn(:,:,:)  = 0._wp   ;   sxxa (:,:,:)  = 0._wp
407      syyice(:,:,:)  = 0._wp   ;   syysn(:,:,:)  = 0._wp   ;   syya (:,:,:)  = 0._wp
408      sxyice(:,:,:)  = 0._wp   ;   sxysn(:,:,:)  = 0._wp   ;   sxya (:,:,:)  = 0._wp
409
410      sxc0  (:,:,:)  = 0._wp   ;   sxe  (:,:,:,:)= 0._wp   
411      syc0  (:,:,:)  = 0._wp   ;   sye  (:,:,:,:)= 0._wp   
412      sxxc0 (:,:,:)  = 0._wp   ;   sxxe (:,:,:,:)= 0._wp   
413      syyc0 (:,:,:)  = 0._wp   ;   syye (:,:,:,:)= 0._wp   
414      sxyc0 (:,:,:)  = 0._wp   ;   sxye (:,:,:,:)= 0._wp   
415
416      sxsal  (:,:,:)  = 0._wp
417      sysal  (:,:,:)  = 0._wp
418      sxxsal (:,:,:)  = 0._wp
419      syysal (:,:,:)  = 0._wp
420      sxysal (:,:,:)  = 0._wp
421
422      sxage  (:,:,:)  = 0._wp
423      syage  (:,:,:)  = 0._wp
424      sxxage (:,:,:)  = 0._wp
425      syyage (:,:,:)  = 0._wp
426      sxyage (:,:,:)  = 0._wp
427
428      !--------------------------------------------------------------------
429      ! 6) Lateral boundary conditions                                    |
430      !--------------------------------------------------------------------
431
432      DO jl = 1, jpl
433
434         CALL lbc_lnk( a_i(:,:,jl)  , 'T', 1. )
435         CALL lbc_lnk( v_i(:,:,jl)  , 'T', 1. )
436         CALL lbc_lnk( v_s(:,:,jl)  , 'T', 1. )
437         CALL lbc_lnk( smv_i(:,:,jl), 'T', 1. )
438         CALL lbc_lnk( oa_i(:,:,jl) , 'T', 1. )
439
440         CALL lbc_lnk( ht_i(:,:,jl) , 'T', 1. )
441         CALL lbc_lnk( ht_s(:,:,jl) , 'T', 1. )
442         CALL lbc_lnk( sm_i(:,:,jl) , 'T', 1. )
443         CALL lbc_lnk( o_i(:,:,jl)  , 'T', 1. )
444         CALL lbc_lnk( t_su(:,:,jl) , 'T', 1. )
445         DO jk = 1, nlay_s
446            CALL lbc_lnk(t_s(:,:,jk,jl), 'T', 1. )
447            CALL lbc_lnk(e_s(:,:,jk,jl), 'T', 1. )
448         END DO
449         DO jk = 1, nlay_i
450            CALL lbc_lnk(t_i(:,:,jk,jl), 'T', 1. )
451            CALL lbc_lnk(e_i(:,:,jk,jl), 'T', 1. )
452         END DO
453         !
454         a_i(:,:,jl) = tms(:,:) * a_i(:,:,jl)
455      END DO
456     
457      at_i (:,:) = 0.0_wp
458      DO jl = 1, jpl
459         at_i (:,:) = at_i (:,:) + a_i (:,:,jl)
460      END DO
461
462      CALL lbc_lnk( at_i , 'T', 1. )
463      at_i(:,:) = tms(:,:) * at_i(:,:)                       ! put 0 over land
464      !
465      CALL lbc_lnk( fsbbq  , 'T', 1. )
466      !
467      !--------------------------------------------------------------------
468      ! 6) ????                                                           |
469      !--------------------------------------------------------------------
470      tn_ice (:,:,:) = t_su (:,:,:)
471
472      CALL wrk_dealloc( jpi, jpj, zidto )
473      CALL wrk_dealloc( jpi, jpj, zhemis )
474      CALL wrk_dealloc( jpl,   2, zht_i_ini,  za_i_ini,  zv_i_ini )
475      CALL wrk_dealloc(   2,      zhm_i_ini, zat_i_ini, zvt_i_ini, zhm_s_ini, zsm_i_ini )
476
477   END SUBROUTINE lim_istate
478
479   SUBROUTINE lim_istate_init
480      !!-------------------------------------------------------------------
481      !!                   ***  ROUTINE lim_istate_init  ***
482      !!       
483      !! ** Purpose : Definition of initial state of the ice
484      !!
485      !! ** Method : Read the namiceini namelist and check the parameter
486      !!       values called at the first timestep (nit000)
487      !!
488      !! ** input :
489      !!        Namelist namiceini
490      !!
491      !! history :
492      !!  8.5  ! 03-08 (C. Ethe) original code
493      !!  8.5  ! 07-11 (M. Vancoppenolle) rewritten initialization
494      !!-----------------------------------------------------------------------------
495      NAMELIST/namiceini/ ttest, hninn, hnins, hginn, hgins, aginn, agins, sinn, sins
496      !
497      INTEGER :: ios                 ! Local integer output status for namelist read
498      !!-----------------------------------------------------------------------------
499      !
500      REWIND( numnam_ice_ref )              ! Namelist namiceini in reference namelist : Ice initial state
501      READ  ( numnam_ice_ref, namiceini, IOSTAT = ios, ERR = 901)
502901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namiceini in reference namelist', lwp )
503
504      REWIND( numnam_ice_cfg )              ! Namelist namiceini in configuration namelist : Ice initial state
505      READ  ( numnam_ice_cfg, namiceini, IOSTAT = ios, ERR = 902 )
506902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namiceini in configuration namelist', lwp )
507      WRITE ( numoni, namiceini )
508
509      ! Define the initial parameters
510      ! -------------------------
511
512      IF(lwp) THEN
513         WRITE(numout,*)
514         WRITE(numout,*) 'lim_istate_init : ice parameters inititialisation '
515         WRITE(numout,*) '~~~~~~~~~~~~~~~'
516         WRITE(numout,*) '   threshold water temp. for initial sea-ice    ttest      = ', ttest
517         WRITE(numout,*) '   initial snow thickness in the north          hninn      = ', hninn
518         WRITE(numout,*) '   initial snow thickness in the south          hnins      = ', hnins 
519         WRITE(numout,*) '   initial ice thickness  in the north          hginn      = ', hginn
520         WRITE(numout,*) '   initial ice thickness  in the south          hgins      = ', hgins
521         WRITE(numout,*) '   initial ice concentr.  in the north          aginn      = ', aginn
522         WRITE(numout,*) '   initial ice concentr.  in the north          agins      = ', agins
523         WRITE(numout,*) '   initial  ice salinity  in the north          sinn       = ', sinn
524         WRITE(numout,*) '   initial  ice salinity  in the south          sins       = ', sins
525      ENDIF
526
527   END SUBROUTINE lim_istate_init
528
529#else
530   !!----------------------------------------------------------------------
531   !!   Default option :         Empty module          NO LIM sea-ice model
532   !!----------------------------------------------------------------------
533CONTAINS
534   SUBROUTINE lim_istate          ! Empty routine
535   END SUBROUTINE lim_istate
536#endif
537
538   !!======================================================================
539END MODULE limistate
Note: See TracBrowser for help on using the repository browser.