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

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

dev_002_LIM : add the LIM 3.0 component, see ticketr: #71

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