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 trunk/NEMO/LIM_SRC_3 – NEMO

source: trunk/NEMO/LIM_SRC_3/limistate.F90 @ 921

Last change on this file since 921 was 921, checked in by rblod, 16 years ago

Correct indentation and print for debug in LIM3, see ticket #134, step I

File size: 24.3 KB
Line 
1MODULE limistate
2   !!======================================================================
3   !!                     ***  MODULE  limistate  ***
4   !!              Initialisation of diagnostics ice variables
5   !!======================================================================
6#if defined key_lim3
7   !!----------------------------------------------------------------------
8   !!   'key_lim3' :                                    LIM3 sea-ice model
9   !!----------------------------------------------------------------------
10   !!   lim_istate      :  Initialisation of diagnostics ice variables
11   !!   lim_istate_init :  initialization of ice state and namelist read
12   !!----------------------------------------------------------------------
13   !! * Modules used
14   USE phycst
15   USE ocfzpt
16   USE oce             ! dynamics and tracers variables
17   USE dom_oce
18   USE sbc_oce         ! Surface boundary condition: ocean fields
19   USE par_ice         ! ice parameters
20   USE ice_oce         ! ice variables
21   USE in_out_manager
22   USE dom_ice
23   USE ice
24   USE lbclnk
25
26   IMPLICIT NONE
27   PRIVATE
28
29   !! * Accessibility
30   PUBLIC lim_istate      ! routine called by lim_init.F90
31
32   !! * Module variables
33   REAL(wp) ::             & !!! ** init namelist (namiceini) **
34      ttest    = 2.0  ,    &  ! threshold water temperature for initial sea ice
35      hninn    = 0.5  ,    &  ! initial snow thickness in the north
36      hginn_u  = 2.5  ,    &  ! initial ice thickness in the north
37      aginn_u  = 0.7  ,    &  ! initial leads area in the north
38      hginn_d  = 5.0  ,    &  ! initial ice thickness in the north
39      aginn_d  = 0.25 ,    &  ! initial leads area in the north
40      hnins    = 0.1  ,    &  ! initial snow thickness in the south
41      hgins_u  = 1.0  ,    &  ! initial ice thickness in the south
42      agins_u  = 0.7  ,    &  ! initial leads area in the south
43      hgins_d  = 2.0  ,    &  ! initial ice thickness in the south
44      agins_d  = 0.2  ,    &  ! initial leads area in the south
45      sinn     = 6.301 ,   &  ! initial salinity
46      sins     = 6.301
47
48   REAL(wp)  ::            &  ! constant values
49      zzero   = 0.0     ,  &
50      zone    = 1.0
51
52   !!----------------------------------------------------------------------
53   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)
54   !! $ Id: $
55   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
56   !!----------------------------------------------------------------------
57
58CONTAINS
59
60   SUBROUTINE lim_istate
61      !!-------------------------------------------------------------------
62      !!                    ***  ROUTINE lim_istate  ***
63      !!
64      !! ** Purpose :   defined the sea-ice initial state
65      !!
66      !! ** Method  :   restart from a state defined in a binary file
67      !!                or from arbitrary sea-ice conditions
68      !!
69      !! History :
70      !!   2.0  !  01-04  (C. Ethe, G. Madec)  Original code
71      !!--------------------------------------------------------------------
72
73      !! * Local variables
74      INTEGER  ::   ji, jj, jk, jl             ! dummy loop indices
75
76      REAL(wp) ::   zidto,    &  ! temporary scalar
77         zs0, ztf, zbin, &
78         zeps6, zeps, ztmelts, &
79         epsi06
80      REAL(wp), DIMENSION(jpm) ::   &
81         zgfactorn, zhin, &
82         zgfactors, zhis
83      REAL(wp), DIMENSION(jpi,jpj) ::   &
84         ztn 
85      REAL(wp) ::  &
86         zvol, zare, zh, zh1, zh2, zh3, zan, zbn, zas, zbs 
87      !--------------------------------------------------------------------
88
89      !--------------------------------------------------------------------
90      ! 1) Preliminary things
91      !--------------------------------------------------------------------
92      epsi06 = 1.0e-6
93
94      CALL lim_istate_init     !  reading the initials parameters of the ice
95
96      ! Initialisation at tn or -2 if ice
97      DO jj = 1, jpj
98         DO ji = 1, jpi
99            zbin = MAX( 0., SIGN( 1., fzptn(ji,jj) - tn(ji,jj,1) ) )
100            ztn(ji,jj) = ( (1.-zbin) * tn(ji,jj,1) - 2. * zbin + rt0 ) * tmask(ji,jj,1)
101         END DO
102      END DO
103
104      !--------------------------------------------------------------------
105      ! 2) Ice initialization (hi,hs,frld,t_su,sm_i,t_i,t_s)              |
106      !--------------------------------------------------------------------
107
108      WRITE(numout,*)
109      WRITE(numout,*) 'lim_istate : Ice initialization '
110      WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
111
112      ! reference salinity 34psu
113      zs0 = 34.e0
114      ztf = ABS ( rt0 - 0.0575       * zs0                               &
115         &                    + 1.710523e-03 * zs0 * SQRT( zs0 )   &
116         &                    - 2.154996e-04 * zs0 *zs0          )
117
118      ! constants for heat contents
119      zeps   = 1.0d-20
120      zeps6  = 1.0d-06
121
122      !  t_bo: Seawater freezing point
123      t_bo(:,:)  = ztf   
124
125      ! zgfactor for initial ice distribution
126      zgfactorn(:) = 0.0
127      zgfactors(:) = 0.0
128
129      ! first ice type
130      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2)
131         zhin (1)     = ( hi_max(jl-1) + hi_max(jl) ) / 2.0
132         zgfactorn(1) = zgfactorn(1) + exp(-(zhin(1)-hginn_u)*(zhin(1)-hginn_u)/2.0)
133         zhis (1)     = ( hi_max(jl-1) + hi_max(jl) ) / 2.0
134         zgfactors(1) = zgfactors(1) + exp(-(zhis(1)-hgins_u)*(zhis(1)-hgins_u)/2.0)
135      END DO ! jl
136      zgfactorn(1) = aginn_u / zgfactorn(1)
137      zgfactors(1) = agins_u / zgfactors(1)
138
139      ! -------------
140      ! new distribution, polynom of second order, conserving area and volume
141      zh1 = 0.0
142      zh2 = 0.0
143      zh3 = 0.0
144      DO jl = 1, jpl
145         zh = ( hi_max(jl-1) + hi_max(jl) ) / 2.0
146         zh1 = zh1 + zh
147         zh2 = zh2 + zh*zh
148         zh3 = zh3 + zh*zh*zh
149      END DO
150      WRITE(numout,*) ' zh1 : ', zh1
151      WRITE(numout,*) ' zh2 : ', zh2
152      WRITE(numout,*) ' zh3 : ', zh3
153
154      zvol = aginn_u*hginn_u
155      zare = aginn_u
156      IF ( jpl .GE. 2 ) THEN
157         zbn = ( zvol*zh2 - zare*zh3 ) / ( zh2*zh2 - zh1*zh3)
158         zan = ( zare - zbn*zh1 ) / zh2
159      ENDIF
160
161      WRITE(numout,*) ' zvol: ', zvol
162      WRITE(numout,*) ' zare: ', zare
163      WRITE(numout,*) ' zbn : ', zbn 
164      WRITE(numout,*) ' zan : ', zan 
165
166      zvol = agins_u*hgins_u
167      zare = agins_u
168      IF ( jpl .GE. 2 ) THEN
169         zbs = ( zvol*zh2 - zare*zh3 ) / ( zh2*zh2 - zh1*zh3)
170         zas = ( zare - zbs*zh1 ) / zh2
171      ENDIF
172
173      WRITE(numout,*) ' zvol: ', zvol
174      WRITE(numout,*) ' zare: ', zare
175      WRITE(numout,*) ' zbn : ', zbn 
176      WRITE(numout,*) ' zan : ', zan 
177
178      !end of new lines
179      ! -------------
180!!!
181      ! retour a LIMA_MEC
182      !     ! second ice type
183      !     zdummy  = hi_max(ice_cat_bounds(2,1)-1)
184      !     hi_max(ice_cat_bounds(2,1)-1) = 0.0
185
186      !     ! here to change !!!!
187      !     jm = 2
188      !     DO jl = ice_cat_bounds(jm,1), ice_cat_bounds(jm,2)
189      !        zhin (2)     = ( hi_max(jl-1) + hi_max(jl) ) / 2.0
190      !        zhin (2)     = ( hi_max_typ(jl-ice_cat_bounds(2,1),jm    ) + &
191      !                         hi_max_typ(jl-ice_cat_bounds(2,1) + 1,jm)   ) / 2.0
192      !        zgfactorn(2) = zgfactorn(2) + exp(-(zhin(2)-hginn_d)*(zhin(2)-hginn_d)/2.0)
193      !        zhis (2)     = ( hi_max(jl-1) + hi_max(jl) ) / 2.0
194      !        zhis (2)     = ( hi_max_typ(jl-ice_cat_bounds(2,1),jm    ) + &
195      !                         hi_max_typ(jl-ice_cat_bounds(2,1) + 1,jm)   ) / 2.0
196      !        zgfactors(2) = zgfactors(2) + exp(-(zhis(2)-hgins_d)*(zhis(2)-hgins_d)/2.0)
197      !     END DO ! jl
198      !     zgfactorn(2) = aginn_d / zgfactorn(2)
199      !     zgfactors(2) = agins_d / zgfactors(2)
200      !     hi_max(ice_cat_bounds(2,1)-1) = zdummy
201      ! END retour a LIMA_MEC
202!!!
203      DO jj = 1, jpj
204         DO ji = 1, jpi
205
206            !--- Criterion for presence (zidto=1) or absence (zidto=0) of ice
207            zidto  = tms(ji,jj) * ( 1.0 - MAX(zzero, SIGN( zone, ztn(ji,jj) - t_bo(ji,jj) - ttest) ) )
208
209            !--- Northern hemisphere
210            !----------------------------------------------------------------
211            IF( fcor(ji,jj) >= 0.e0 ) THEN   
212
213               !-----------------------
214               ! Ice area / thickness
215               !-----------------------
216
217               IF ( jpl .EQ. 1) THEN ! one category
218
219                  DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2) ! loop over ice thickness categories
220                     a_i(ji,jj,jl)    = zidto * aginn_u
221                     ht_i(ji,jj,jl)   = zidto * hginn_u
222                     v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl)
223                  END DO
224
225               ELSE ! several categories
226
227                  DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2) ! loop over ice thickness categories
228                     zhin(1)          = ( hi_max(jl-1) + hi_max(jl) ) / 2.0
229                     a_i(ji,jj,jl)    = zidto * MAX( zgfactorn(1) * exp(-(zhin(1)-hginn_u)* & 
230                        (zhin(1)-hginn_u)/2.0) , epsi06)
231                     ! new line
232                     a_i(ji,jj,jl)    = zidto * ( zan * zhin(1) * zhin(1) + zbn * zhin(1) )
233                     ht_i(ji,jj,jl)   = zidto * zhin(1) 
234                     v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl)
235                  END DO
236
237               ENDIF
238
239
240!!!
241               ! retour a LIMA_MEC
242               !              !ridged ice
243               !              zdummy  = hi_max(ice_cat_bounds(2,1)-1)
244               !              hi_max(ice_cat_bounds(2,1)-1) = 0.0
245               !              DO jl = ice_cat_bounds(2,1), ice_cat_bounds(2,2) ! loop over ice thickness categories
246               !                 zhin(2)          = ( hi_max(jl-1) + hi_max(jl) ) / 2.0
247               !                 a_i(ji,jj,jl)    = zidto * MAX( zgfactorn(2) * exp(-(zhin(2)-hginn_d)* &
248               !                                    (zhin(2)-hginn_d)/2.0) , epsi06)
249               !                 ht_i(ji,jj,jl)   = zidto * zhin(2)
250               !                 v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl)
251               !              END DO
252               !              hi_max(ice_cat_bounds(2,1)-1) = zdummy
253
254               !              !rafted ice
255               !              jl = 6
256               !              a_i(ji,jj,jl)       = 0.0
257               !              ht_i(ji,jj,jl)      = 0.0
258               !              v_i(ji,jj,jl)       = 0.0
259               ! END retour a LIMA_MEC
260!!!
261
262               DO jl = 1, jpl
263
264                  !-------------
265                  ! Snow depth
266                  !-------------
267                  ht_s(ji,jj,jl)   = zidto * hninn
268                  v_s(ji,jj,jl)    = ht_s(ji,jj,jl)*a_i(ji,jj,jl)
269
270                  !---------------
271                  ! Ice salinity
272                  !---------------
273                  sm_i(ji,jj,jl)   = zidto * sinn  + ( 1.0 - zidto ) * 0.1
274                  smv_i(ji,jj,jl)  = MIN( sm_i(ji,jj,jl) , sss_m(ji,jj) ) * v_i(ji,jj,jl)
275
276                  !----------
277                  ! Ice age
278                  !----------
279                  o_i(ji,jj,jl)    = zidto * 1.0   + ( 1.0 - zidto )
280                  oa_i(ji,jj,jl)   = o_i(ji,jj,jl) * a_i(ji,jj,jl)
281
282                  !------------------------------
283                  ! Sea ice surface temperature
284                  !------------------------------
285
286                  t_su(ji,jj,jl)   = zidto * 270.0 + ( 1.0 - zidto ) * t_bo(ji,jj)
287
288                  !------------------------------------
289                  ! Snow temperature and heat content
290                  !------------------------------------
291
292                  DO jk = 1, nlay_s
293                     t_s(ji,jj,jk,jl) = zidto * 270.00 + ( 1.0 - zidto ) * rtt
294                     ! Snow energy of melting
295                     e_s(ji,jk,jk,jl) = zidto * rhosn * ( cpic * ( rtt - t_s(ji,jj,jk,jl) ) + lfus )
296                     ! Change dimensions
297                     e_s(ji,jj,jk,jl) = e_s(ji,jj,jk,jl) / unit_fac
298                     ! Multiply by volume, so that heat content in 10^9 Joules
299                     e_s(ji,jj,jk,jl) = e_s(ji,jj,jk,jl) * area(ji,jj) * &
300                        v_s(ji,jj,jl)  / nlay_s
301                  END DO !jk
302
303                  !-----------------------------------------------
304                  ! Ice salinities, temperature and heat content
305                  !-----------------------------------------------
306
307                  DO jk = 1, nlay_i
308                     t_i(ji,jj,jk,jl) = zidto*270.00 + ( 1.0 - zidto ) * rtt 
309                     s_i(ji,jj,jk,jl) = zidto * sinn + ( 1.0 - zidto ) * 0.1
310                     ztmelts          = - tmut * s_i(ji,jj,jk,jl) + rtt !Melting temperature in K
311
312                     ! heat content per unit volume
313                     e_i(ji,jj,jk,jl) = zidto * rhoic * &
314                        (   cpic    * ( ztmelts - t_i(ji,jj,jk,jl) ) &
315                        +   lfus    * ( 1.0 - (ztmelts-rtt) / MIN((t_i(ji,jj,jk,jl)-rtt),-zeps) ) &
316                        - rcp      * ( ztmelts - rtt ) &
317                        )
318
319                     ! Correct dimensions to avoid big values
320                     e_i(ji,jj,jk,jl) = e_i(ji,jj,jk,jl) / unit_fac 
321
322                     ! Mutliply by ice volume, and divide by number of layers to get heat content in 10^9 J
323                     e_i(ji,jj,jk,jl) = e_i(ji,jj,jk,jl) * & 
324                        area(ji,jj) * a_i(ji,jj,jl) * ht_i(ji,jj,jl) / &
325                        nlay_i
326                  END DO ! jk
327
328               END DO ! jl
329
330            ELSE ! on fcor
331
332               !--- Southern hemisphere
333               !----------------------------------------------------------------
334
335               !-----------------------
336               ! Ice area / thickness
337               !-----------------------
338
339               IF ( jpl .EQ. 1) THEN ! one category
340
341                  DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2) ! loop over ice thickness categories
342                     a_i(ji,jj,jl)    = zidto * agins_u
343                     ht_i(ji,jj,jl)   = zidto * hgins_u
344                     v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl)
345                  END DO
346
347               ELSE ! several categories
348
349                  !level ice
350                  DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2) !over thickness categories
351
352                     zhis(1)       = ( hi_max(jl-1) + hi_max(jl) ) / 2.0
353                     a_i(ji,jj,jl) = zidto * MAX( zgfactors(1) * exp(-(zhis(1)-hgins_u) * & 
354                        (zhis(1)-hgins_u)/2.0) , epsi06 )
355                     ! new line square distribution volume conserving
356                     a_i(ji,jj,jl)    = zidto * ( zas * zhis(1) * zhis(1) + zbs * zhis(1) )
357                     ht_i(ji,jj,jl)   = zidto * zhis(1) 
358                     v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl)
359
360                  END DO ! jl
361
362               ENDIF
363
364!!!
365               ! retour a LIMA_MEC
366               !              !ridged ice
367               !              zdummy  = hi_max(ice_cat_bounds(2,1)-1)
368               !              hi_max(ice_cat_bounds(2,1)-1) = 0.0
369               !              DO jl = ice_cat_bounds(2,1), ice_cat_bounds(2,2) !over thickness categories
370               !                 zhis(2)       = ( hi_max(jl-1) + hi_max(jl) ) / 2.0
371               !                 a_i(ji,jj,jl) = zidto*MAX( zgfactors(2) * exp(-(zhis(2)-hgins_d)*(zhis(2)-hgins_d)/2.0), epsi06 )
372               !                 ht_i(ji,jj,jl)   = zidto * zhis(2)
373               !                 v_i(ji,jj,jl)    = ht_i(ji,jj,jl)*a_i(ji,jj,jl)
374               !              END DO
375               !              hi_max(ice_cat_bounds(2,1)-1) = zdummy
376
377               !              !rafted ice
378               !              jl = 6
379               !              a_i(ji,jj,jl)       = 0.0
380               !              ht_i(ji,jj,jl)      = 0.0
381               !              v_i(ji,jj,jl)       = 0.0
382               ! END retour a LIMA_MEC
383!!!
384
385               DO jl = 1, jpl !over thickness categories
386
387                  !---------------
388                  ! Snow depth
389                  !---------------
390
391                  ht_s(ji,jj,jl)   = zidto * hnins
392                  v_s(ji,jj,jl)    = ht_s(ji,jj,jl)*a_i(ji,jj,jl)
393
394                  !---------------
395                  ! Ice salinity
396                  !---------------
397
398                  sm_i(ji,jj,jl)   = zidto * sins  + ( 1.0 - zidto ) * 0.1
399                  smv_i(ji,jj,jl)  = MIN( sm_i(ji,jj,jl) , sss_m(ji,jj) ) * v_i(ji,jj,jl)
400
401                  !----------
402                  ! Ice age
403                  !----------
404
405                  o_i(ji,jj,jl)    = zidto * 1.0   + ( 1.0 - zidto )
406                  oa_i(ji,jj,jl)   = o_i(ji,jj,jl) * a_i(ji,jj,jl)
407
408                  !------------------------------
409                  ! Sea ice surface temperature
410                  !------------------------------
411
412                  t_su(ji,jj,jl)   = zidto * 270.0 + ( 1.0 - zidto ) * t_bo(ji,jj)
413
414                  !----------------------------------
415                  ! Snow temperature / heat content
416                  !----------------------------------
417
418                  DO jk = 1, nlay_s
419                     t_s(ji,jj,jk,jl) = zidto * 270.00 + ( 1.0 - zidto ) * rtt
420                     ! Snow energy of melting
421                     e_s(ji,jj,jk,jl) = zidto * rhosn * ( cpic * ( rtt - t_s(ji,jj,jk,jl) ) + lfus )
422                     ! Change dimensions
423                     e_s(ji,jj,jk,jl) = e_s(ji,jj,jk,jl) / unit_fac
424                     ! Multiply by volume, so that heat content in 10^9 Joules
425                     e_s(ji,jj,jk,jl) = e_s(ji,jj,jk,jl) * area(ji,jj) * &
426                        v_s(ji,jj,jl)  / nlay_s
427                  END DO
428
429                  !---------------------------------------------
430                  ! Ice temperature, salinity and heat content
431                  !---------------------------------------------
432
433                  DO jk = 1, nlay_i
434                     t_i(ji,jj,jk,jl) = zidto*270.00 + ( 1.0 - zidto ) * rtt 
435                     s_i(ji,jj,jk,jl) = zidto * sins + ( 1.0 - zidto ) * 0.1
436                     ztmelts          = - tmut * s_i(ji,jj,jk,jl) + rtt !Melting temperature in K
437
438                     ! heat content per unit volume
439                     e_i(ji,jj,jk,jl) = zidto * rhoic * &
440                        (   cpic    * ( ztmelts - t_i(ji,jj,jk,jl) ) &
441                        +   lfus  * ( 1.0 - (ztmelts-rtt) / MIN((t_i(ji,jj,jk,jl)-rtt),-zeps) ) &
442                        - rcp      * ( ztmelts - rtt ) &
443                        )
444
445                     ! Correct dimensions to avoid big values
446                     e_i(ji,jj,jk,jl) = e_i(ji,jj,jk,jl) / unit_fac 
447
448                     ! Mutliply by ice volume, and divide by number of layers to get heat content in 10^9 J
449                     e_i(ji,jj,jk,jl) = e_i(ji,jj,jk,jl) * & 
450                        area(ji,jj) * a_i(ji,jj,jl) * ht_i(ji,jj,jl) / &
451                        nlay_i
452                  END DO !jk
453
454               END DO ! jl
455
456            ENDIF ! on fcor
457
458         ENDDO
459      ENDDO
460
461      !--------------------------------------------------------------------
462      ! 3) Global ice variables for output diagnostics                    |
463      !--------------------------------------------------------------------
464
465      fsbbq (:,:)     = 0.e0
466      u_ice (:,:)     = 0.e0
467      v_ice (:,:)     = 0.e0
468      stress1_i(:,:)  = 0.0
469      stress2_i(:,:)  = 0.0
470      stress12_i(:,:) = 0.0
471
472# if defined key_coupled
473      albege(:,:)   = 0.8 * tms(:,:)
474# endif
475
476      !--------------------------------------------------------------------
477      ! 4) Moments for advection
478      !--------------------------------------------------------------------
479
480      sxice (:,:,:)  = 0.e0   ;   sxsn (:,:,:)  = 0.e0   ;   sxa  (:,:,:)  = 0.e0
481      syice (:,:,:)  = 0.e0   ;   sysn (:,:,:)  = 0.e0   ;   sya  (:,:,:)  = 0.e0
482      sxxice(:,:,:)  = 0.e0   ;   sxxsn(:,:,:)  = 0.e0   ;   sxxa (:,:,:)  = 0.e0
483      syyice(:,:,:)  = 0.e0   ;   syysn(:,:,:)  = 0.e0   ;   syya (:,:,:)  = 0.e0
484      sxyice(:,:,:)  = 0.e0   ;   sxysn(:,:,:)  = 0.e0   ;   sxya (:,:,:)  = 0.e0
485
486      sxc0  (:,:,:)  = 0.e0   ;   sxe  (:,:,:,:)= 0.e0   
487      syc0  (:,:,:)  = 0.e0   ;   sye  (:,:,:,:)= 0.e0   
488      sxxc0 (:,:,:)  = 0.e0   ;   sxxe (:,:,:,:)= 0.e0   
489      syyc0 (:,:,:)  = 0.e0   ;   syye (:,:,:,:)= 0.e0   
490      sxyc0 (:,:,:)  = 0.e0   ;   sxye (:,:,:,:)= 0.e0   
491
492      sxsal  (:,:,:)  = 0.e0
493      sysal  (:,:,:)  = 0.e0
494      sxxsal (:,:,:)  = 0.e0
495      syysal (:,:,:)  = 0.e0
496      sxysal (:,:,:)  = 0.e0
497
498      !--------------------------------------------------------------------
499      ! 5) Lateral boundary conditions                                    |
500      !--------------------------------------------------------------------
501
502      DO jl = 1, jpl
503
504         CALL lbc_lnk( a_i(:,:,jl)  , 'T', 1. )
505         CALL lbc_lnk( v_i(:,:,jl)  , 'T', 1. )
506         CALL lbc_lnk( v_s(:,:,jl)  , 'T', 1. )
507         CALL lbc_lnk( smv_i(:,:,jl), 'T', 1. )
508         CALL lbc_lnk( oa_i(:,:,jl) , 'T', 1. )
509
510         CALL lbc_lnk( ht_i(:,:,jl) , 'T', 1. )
511         CALL lbc_lnk( ht_s(:,:,jl) , 'T', 1. )
512         CALL lbc_lnk( sm_i(:,:,jl) , 'T', 1. )
513         CALL lbc_lnk( o_i(:,:,jl)  , 'T', 1. )
514         CALL lbc_lnk( t_su(:,:,jl) , 'T', 1. )
515         DO jk = 1, nlay_s
516            CALL lbc_lnk(t_s(:,:,jk,jl), 'T', 1. )
517            CALL lbc_lnk(e_s(:,:,jk,jl), 'T', 1. )
518         END DO
519         DO jk = 1, nlay_i
520            CALL lbc_lnk(t_i(:,:,jk,jl), 'T', 1. )
521            CALL lbc_lnk(e_i(:,:,jk,jl), 'T', 1. )
522         END DO
523
524         a_i (:,:,jl) = tms(:,:) * a_i(:,:,jl)
525
526      END DO
527
528      CALL lbc_lnk( at_i , 'T', 1. )
529      at_i(:,:) = tms(:,:) * at_i(:,:)                       ! put 0 over land
530
531      CALL lbc_lnk( fsbbq  , 'T', 1. )
532
533   END SUBROUTINE lim_istate
534
535   SUBROUTINE lim_istate_init
536      !!-------------------------------------------------------------------
537      !!                   ***  ROUTINE lim_istate_init  ***
538      !!       
539      !! ** Purpose : Definition of initial state of the ice
540      !!
541      !! ** Method : Read the namiceini namelist and check the parameter
542      !!       values called at the first timestep (nit000)
543      !!
544      !! ** input :
545      !!        Namelist namiceini
546      !!
547      !! history :
548      !!  8.5  ! 03-08 (C. Ethe) original code
549      !!-----------------------------------------------------------------------------
550      NAMELIST/namiceini/ ttest, hninn, hginn_u, aginn_u, hginn_d, aginn_d, hnins, &
551         hgins_u, agins_u, hgins_d, agins_d, sinn, sins
552      !!-----------------------------------------------------------------------------
553
554      ! Define the initial parameters
555      ! -------------------------
556
557      ! Read Namelist namiceini
558      REWIND ( numnam_ice )
559      READ   ( numnam_ice , namiceini )
560      IF(lwp) THEN
561         WRITE(numout,*)
562         WRITE(numout,*) 'lim_istate_init : ice parameters inititialisation '
563         WRITE(numout,*) '~~~~~~~~~~~~~~~'
564         WRITE(numout,*) '   threshold water temp. for initial sea-ice    ttest      = ', ttest
565         WRITE(numout,*) '   initial snow thickness in the north          hninn      = ', hninn
566         WRITE(numout,*) '   initial undef ice thickness in the north     hginn_u    = ', hginn_u
567         WRITE(numout,*) '   initial undef ice concentr. in the north     aginn_u    = ', aginn_u         
568         WRITE(numout,*) '   initial  def  ice thickness in the north     hginn_d    = ', hginn_d
569         WRITE(numout,*) '   initial  def  ice concentr. in the north     aginn_d    = ', aginn_d         
570         WRITE(numout,*) '   initial snow thickness in the south          hnins      = ', hnins 
571         WRITE(numout,*) '   initial undef ice thickness in the north     hgins_u    = ', hgins_u
572         WRITE(numout,*) '   initial undef ice concentr. in the north     agins_u    = ', agins_u         
573         WRITE(numout,*) '   initial  def  ice thickness in the north     hgins_d    = ', hgins_d
574         WRITE(numout,*) '   initial  def  ice concentr. in the north     agins_d    = ', agins_d         
575         WRITE(numout,*) '   initial  ice salinity       in the north     sinn       = ', sinn
576         WRITE(numout,*) '   initial  ice salinity       in the south     sins       = ', sins
577      ENDIF
578
579   END SUBROUTINE lim_istate_init
580
581#else
582   !!----------------------------------------------------------------------
583   !!   Default option :         Empty module          NO LIM sea-ice model
584   !!----------------------------------------------------------------------
585CONTAINS
586   SUBROUTINE lim_istate          ! Empty routine
587   END SUBROUTINE lim_istate
588#endif
589
590   !!======================================================================
591END MODULE limistate
Note: See TracBrowser for help on using the repository browser.