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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90 @ 2287

Last change on this file since 2287 was 2287, checked in by smasson, 14 years ago

update licence of all NEMO files...

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