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

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

Add svn Id (first try), see ticket #210

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