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 @ 834

Last change on this file since 834 was 834, checked in by ctlod, 16 years ago

Clean comments and useless lines, see ticket:#72

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