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

Last change on this file since 3245 was 2475, checked in by gm, 14 years ago

v3.3beta: #633 LIM-3 correct the hard coded num_sal in limrst + symmetric changes in LIM-2

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