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

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90 @ 8373

Last change on this file since 8373 was 8373, checked in by clem, 7 years ago

remove most of wrk_alloc

  • Property svn:keywords set to Id
File size: 27.8 KB
Line 
1MODULE limistate
2   !!======================================================================
3   !!                     ***  MODULE  limistate  ***
4   !!              Initialisation of diagnostics ice variables
5   !!======================================================================
6   !! History :  2.0  ! 2004-01 (C. Ethe, G. Madec)  Original code
7   !!            3.0  ! 2011-02 (G. Madec) dynamical allocation
8   !!             -   ! 2014    (C. Rousset) add N/S initializations
9   !!----------------------------------------------------------------------
10#if defined key_lim3
11   !!----------------------------------------------------------------------
12   !!   'key_lim3' :                                    LIM3 sea-ice model
13   !!----------------------------------------------------------------------
14   !!   lim_istate      :  Initialisation of diagnostics ice variables
15   !!   lim_istate_init :  initialization of ice state and namelist read
16   !!----------------------------------------------------------------------
17   USE phycst         ! physical constant
18   USE oce            ! dynamics and tracers variables
19   USE dom_oce        ! ocean domain
20   USE sbc_oce , ONLY : sst_m, sss_m 
21   USE sbc_ice , ONLY : tn_ice
22   USE eosbn2         ! equation of state
23   USE ice            ! sea-ice variables
24   USE par_oce        ! ocean parameters
25   USE limvar         ! lim_var_salprof
26   !
27   USE in_out_manager ! I/O manager
28   USE lib_mpp        ! MPP library
29   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
30   USE wrk_nemo       ! work arrays
31   USE fldread        ! read input fields
32   USE iom
33
34   IMPLICIT NONE
35   PRIVATE
36
37   PUBLIC   lim_istate      ! routine called by lim_init.F90
38
39   INTEGER , PARAMETER ::   jpfldi = 6           ! maximum number of files to read
40   INTEGER , PARAMETER ::   jp_hti = 1           ! index of ice thickness (m)    at T-point
41   INTEGER , PARAMETER ::   jp_hts = 2           ! index of snow thicknes (m)    at T-point
42   INTEGER , PARAMETER ::   jp_ati = 3           ! index of ice fraction (%) at T-point
43   INTEGER , PARAMETER ::   jp_tsu = 4           ! index of ice surface temp (K)    at T-point
44   INTEGER , PARAMETER ::   jp_tmi = 5           ! index of ice temp at T-point
45   INTEGER , PARAMETER ::   jp_smi = 6           ! index of ice sali at T-point
46   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   si  ! structure of input fields (file informations, fields read)
47   !!----------------------------------------------------------------------
48   !!   LIM 3.0,  UCL-LOCEAN-IPSL (2008)
49   !! $Id$
50   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
51   !!----------------------------------------------------------------------
52CONTAINS
53
54   SUBROUTINE lim_istate
55      !!-------------------------------------------------------------------
56      !!                    ***  ROUTINE lim_istate  ***
57      !!
58      !! ** Purpose :   defined the sea-ice initial state
59      !!
60      !! ** Method  :   This routine will put some ice where ocean
61      !!                is at the freezing point, then fill in ice
62      !!                state variables using prescribed initial
63      !!                values in the namelist           
64      !!
65      !! ** Steps   :   1) Read namelist
66      !!                2) Basal temperature; ice and hemisphere masks
67      !!                3) Fill in the ice thickness distribution using gaussian
68      !!                4) Fill in space-dependent arrays for state variables
69      !!                5) Diagnostic arrays
70      !!                6) Lateral boundary conditions
71      !!
72      !! ** Notes   : o_i, t_su, t_s, t_i, s_i must be filled everywhere, even
73      !!              where there is no ice (clem: I do not know why, is it mandatory?)
74      !!
75      !! History :
76      !!   2.0  !  01-04  (C. Ethe, G. Madec)  Original code
77      !!   3.0  !  2007   (M. Vancoppenolle)   Rewrite for ice cats
78      !!   4.0  !  09-11  (M. Vancoppenolle)   Enhanced version for ice cats
79      !!--------------------------------------------------------------------
80      !! * Local variables
81      INTEGER    :: ji, jj, jk, jl             ! dummy loop indices
82      REAL(wp)   :: ztmelts, zdh
83      INTEGER    :: i_hemis, i_fill, jl0
84      REAL(wp)   :: zarg, zV, zconv, zdv
85      REAL(wp), DIMENSION(jpi,jpj)     :: zswitch    ! ice indicator
86      REAL(wp), DIMENSION(jpi,jpj)     :: zht_i_ini, zat_i_ini, zvt_i_ini            !data from namelist or nc file
87      REAL(wp), DIMENSION(jpi,jpj)     :: zts_u_ini, zht_s_ini, zsm_i_ini, ztm_i_ini !data from namelist or nc file
88      REAL(wp), DIMENSION(jpi,jpj,jpl) :: zh_i_ini, za_i_ini                         !data by cattegories to fill
89      INTEGER , DIMENSION(4)           :: itest
90      !--------------------------------------------------------------------
91
92      IF(lwp) WRITE(numout,*)
93      IF(lwp) WRITE(numout,*) 'lim_istate : sea-ice initialization '
94      IF(lwp) WRITE(numout,*) '~~~~~~~~~~ '
95
96      !--------------------------------------------------------------------
97      ! 1) Read namelist
98      !--------------------------------------------------------------------
99      !
100      CALL lim_istate_init
101
102      ! init surface temperature
103      DO jl = 1, jpl
104         t_su  (:,:,jl) = rt0 * tmask(:,:,1)
105         tn_ice(:,:,jl) = rt0 * tmask(:,:,1)
106      END DO
107
108      ! init basal temperature (considered at freezing point)
109      CALL eos_fzp( sss_m(:,:), t_bo(:,:) )
110      t_bo(:,:) = ( t_bo(:,:) + rt0 ) * tmask(:,:,1) 
111
112
113      !--------------------------------------------------------------------
114      ! 2) Initialization of sea ice state variables
115      !--------------------------------------------------------------------
116      IF( ln_limini ) THEN
117         !
118         IF( ln_limini_file )THEN
119         !
120            zht_i_ini(:,:)  = si(jp_hti)%fnow(:,:,1)
121            zht_s_ini(:,:)  = si(jp_hts)%fnow(:,:,1)
122            zat_i_ini(:,:)  = si(jp_ati)%fnow(:,:,1)
123            zts_u_ini(:,:)  = si(jp_tsu)%fnow(:,:,1)
124            ztm_i_ini(:,:)  = si(jp_tmi)%fnow(:,:,1)
125            zsm_i_ini(:,:)  = si(jp_smi)%fnow(:,:,1)
126            !
127            WHERE( zat_i_ini(:,:) > 0._wp ) ; zswitch(:,:) = tmask(:,:,1) 
128            ELSEWHERE                       ; zswitch(:,:) = 0._wp
129            END WHERE
130            !
131         ELSE ! ln_limini_file = F
132
133            !--------------------------------------------------------------------
134            ! 3) Basal temperature, ice mask
135            !--------------------------------------------------------------------
136            ! no ice if sst <= t-freez + ttest
137            WHERE( ( sst_m(:,:) - (t_bo(:,:) - rt0) ) * tmask(:,:,1) >= rn_thres_sst ) ; zswitch(:,:) = 0._wp 
138            ELSEWHERE                                                                  ; zswitch(:,:) = tmask(:,:,1)
139            END WHERE
140
141            !-----------------------------
142            ! 3.1) Hemisphere-dependent arrays
143            !-----------------------------
144            ! assign initial thickness, concentration, snow depth and salinity to an hemisphere-dependent array
145            DO jj = 1, jpj
146               DO ji = 1, jpi
147                  IF( ff_t(ji,jj) >= 0._wp ) THEN
148                     zht_i_ini(ji,jj) = rn_hti_ini_n * zswitch(ji,jj)
149                     zht_s_ini(ji,jj) = rn_hts_ini_n * zswitch(ji,jj)
150                     zat_i_ini(ji,jj) = rn_ati_ini_n * zswitch(ji,jj)
151                     zts_u_ini(ji,jj) = rn_tmi_ini_n * zswitch(ji,jj)
152                     zsm_i_ini(ji,jj) = rn_smi_ini_n * zswitch(ji,jj)
153                     ztm_i_ini(ji,jj) = rn_tmi_ini_n * zswitch(ji,jj)
154                  ELSE
155                     zht_i_ini(ji,jj) = rn_hti_ini_s * zswitch(ji,jj)
156                     zht_s_ini(ji,jj) = rn_hts_ini_s * zswitch(ji,jj)
157                     zat_i_ini(ji,jj) = rn_ati_ini_s * zswitch(ji,jj)
158                     zts_u_ini(ji,jj) = rn_tmi_ini_s * zswitch(ji,jj)
159                     zsm_i_ini(ji,jj) = rn_smi_ini_s * zswitch(ji,jj)
160                     ztm_i_ini(ji,jj) = rn_tmi_ini_s * zswitch(ji,jj)
161                  ENDIF
162               END DO
163            END DO
164            !
165         ENDIF ! ln_limini_file
166         
167         zvt_i_ini(:,:) = zht_i_ini(:,:) * zat_i_ini(:,:)   ! ice volume
168         !---------------------------------------------------------------------
169         ! 3.2) Distribute ice concentration and thickness into the categories
170         !---------------------------------------------------------------------
171         ! a gaussian distribution for ice concentration is used
172         ! then we check whether the distribution fullfills
173         ! volume and area conservation, positivity and ice categories bounds
174         zh_i_ini(:,:,:) = 0._wp 
175         za_i_ini(:,:,:) = 0._wp
176         !
177         DO jj = 1, jpj
178            DO ji = 1, jpi
179               !
180               IF( zat_i_ini(ji,jj) > 0._wp .AND. zht_i_ini(ji,jj) > 0._wp )THEN
181
182                  !--- jl0: most likely index where cc will be maximum
183                  jl0 = jpl
184                  DO jl = 1, jpl
185                     IF ( ( zht_i_ini(ji,jj) >  hi_max(jl-1) ) .AND. ( zht_i_ini(ji,jj) <= hi_max(jl) ) ) THEN
186                        jl0 = jl
187                        CYCLE
188                     ENDIF
189                  END DO
190                  !
191                  ! initialisation of tests
192                  itest(:)  = 0
193                 
194                  i_fill = jpl + 1                                             !====================================
195                  DO WHILE ( ( SUM( itest(:) ) /= 4 ) .AND. ( i_fill >= 2 ) )  ! iterative loop on i_fill categories
196                     ! iteration                                               !====================================
197                     i_fill = i_fill - 1
198
199                     ! initialisation of ice variables for each try
200                     zh_i_ini(ji,jj,:) = 0._wp 
201                     za_i_ini(ji,jj,:) = 0._wp
202                     itest(:) = 0
203                     !
204                     ! *** case very thin ice: fill only category 1
205                     IF ( i_fill == 1 ) THEN
206                        zh_i_ini(ji,jj,1) = zht_i_ini(ji,jj)
207                        za_i_ini(ji,jj,1) = zat_i_ini(ji,jj)
208
209                     ! *** case ice is thicker: fill categories >1
210                     ELSE
211
212                        ! Fill ice thicknesses in the (i_fill-1) cat by hmean
213                        DO jl = 1, i_fill-1
214                           zh_i_ini(ji,jj,jl) = hi_mean(jl)
215                        END DO
216                        !
217                        !--- Concentrations
218                        za_i_ini(ji,jj,jl0) = zat_i_ini(ji,jj) / SQRT(REAL(jpl))
219                        DO jl = 1, i_fill - 1
220                           IF( jl /= jl0 )THEN
221                              zarg               = ( zh_i_ini(ji,jj,jl) - zht_i_ini(ji,jj) ) / ( 0.5_wp * zht_i_ini(ji,jj) )
222                              za_i_ini(ji,jj,jl) = za_i_ini(ji,jj,jl0) * EXP(-zarg**2)
223                           ENDIF
224                        END DO
225                        !
226                        ! Concentration in the last (i_fill) category
227                        za_i_ini(ji,jj,i_fill) = zat_i_ini(ji,jj) - SUM( za_i_ini(ji,jj,1:i_fill-1) )
228
229                        ! Ice thickness in the last (i_fill) category
230                        zV = SUM( za_i_ini(ji,jj,1:i_fill-1) * zh_i_ini(ji,jj,1:i_fill-1) )
231                        zh_i_ini(ji,jj,i_fill) = ( zvt_i_ini(ji,jj) - zV ) / MAX( za_i_ini(ji,jj,i_fill), epsi10 ) 
232
233                        ! clem: correction if concentration of upper cat is greater than lower cat
234                        !       (it should be a gaussian around jl0 but sometimes it is not)
235                        IF ( jl0 /= jpl ) THEN
236                           DO jl = jpl, jl0+1, -1
237                              IF ( za_i_ini(ji,jj,jl) > za_i_ini(ji,jj,jl-1) ) THEN
238                                 zdv = zh_i_ini(ji,jj,jl) * za_i_ini(ji,jj,jl)
239                                 zh_i_ini(ji,jj,jl    ) = 0._wp
240                                 za_i_ini(ji,jj,jl    ) = 0._wp
241                                 za_i_ini(ji,jj,1:jl-1) = za_i_ini(ji,jj,1:jl-1)  &
242                                    &                     + zdv / MAX( REAL(jl-1) * zht_i_ini(ji,jj), epsi10 )
243                              END IF
244                           ENDDO
245                        ENDIF
246                        !
247                     ENDIF ! case ice is thick or thin
248
249                     !---------------------
250                     ! Compatibility tests
251                     !---------------------
252                     ! Test 1: area conservation
253                     zconv = ABS( zat_i_ini(ji,jj) - SUM( za_i_ini(ji,jj,1:jpl) ) )
254                     IF ( zconv < epsi06 ) itest(1) = 1
255                     
256                     ! Test 2: volume conservation
257                     zconv = ABS(       zat_i_ini(ji,jj)       * zht_i_ini(ji,jj)   &
258                        &        - SUM( za_i_ini (ji,jj,1:jpl) * zh_i_ini (ji,jj,1:jpl) ) )
259                     IF ( zconv < epsi06 ) itest(2) = 1
260                     
261                     ! Test 3: thickness of the last category is in-bounds ?
262                     IF ( zh_i_ini(ji,jj,i_fill) >= hi_max(i_fill-1) ) itest(3) = 1
263                     
264                     ! Test 4: positivity of ice concentrations
265                     itest(4) = 1
266                     DO jl = 1, i_fill
267                        IF ( za_i_ini(ji,jj,jl) < 0._wp ) itest(4) = 0
268                     END DO
269                     !                                      !============================
270                  END DO                                    ! end iteration on categories
271                  !                                         !============================
272                  !
273                  IF( lwp .AND. SUM(itest) /= 4 ) THEN
274                     WRITE(numout,*)
275                     WRITE(numout,*) ' !!!! ALERT itest is not equal to 4      !!! '
276                     WRITE(numout,*) ' !!!! Something is wrong in the LIM3 initialization procedure '
277                     WRITE(numout,*)
278                     WRITE(numout,*) ' *** itest_i (i=1,4) = ', itest(:)
279                     WRITE(numout,*) ' zat_i_ini : ', zat_i_ini(ji,jj)
280                     WRITE(numout,*) ' zht_i_ini : ', zht_i_ini(ji,jj)
281                  ENDIF
282               
283               ENDIF !  zat_i_ini(ji,jj) > 0._wp .AND. zht_i_ini(ji,jj) > 0._wp
284               !
285            END DO   
286         END DO   
287
288         !---------------------------------------------------------------------
289         ! 3.3) Space-dependent arrays for ice state variables
290         !---------------------------------------------------------------------
291
292         ! Ice concentration, thickness and volume, ice salinity, ice age, surface temperature
293         DO jl = 1, jpl ! loop over categories
294            DO jj = 1, jpj
295               DO ji = 1, jpi
296                  a_i(ji,jj,jl)   = zswitch(ji,jj) * za_i_ini(ji,jj,jl)                       ! concentration
297                  ht_i(ji,jj,jl)  = zswitch(ji,jj) * zh_i_ini(ji,jj,jl)                       ! ice thickness
298                  sm_i(ji,jj,jl)  = zswitch(ji,jj) * zsm_i_ini(ji,jj)                         ! salinity
299                  o_i(ji,jj,jl)   = 0._wp                                                     ! age (0 day)
300                  t_su(ji,jj,jl)  = zswitch(ji,jj) * zts_u_ini(ji,jj) + ( 1._wp - zswitch(ji,jj) ) * rt0 ! surf temp
301
302                  IF( zht_i_ini(ji,jj) > 0._wp )THEN
303                    ht_s(ji,jj,jl)= ht_i(ji,jj,jl) * ( zht_s_ini(ji,jj) / zht_i_ini(ji,jj) )  ! snow depth
304                  ELSE
305                    ht_s(ji,jj,jl)= 0._wp
306                  ENDIF
307
308                  ! This case below should not be used if (ht_s/ht_i) is ok in namelist
309                  ! In case snow load is in excess that would lead to transformation from snow to ice
310                  ! Then, transfer the snow excess into the ice (different from limthd_dh)
311                  zdh = MAX( 0._wp, ( rhosn * ht_s(ji,jj,jl) + ( rhoic - rau0 ) * ht_i(ji,jj,jl) ) * r1_rau0 ) 
312                  ! recompute ht_i, ht_s avoiding out of bounds values
313                  ht_i(ji,jj,jl) = MIN( hi_max(jl), ht_i(ji,jj,jl) + zdh )
314                  ht_s(ji,jj,jl) = MAX( 0._wp, ht_s(ji,jj,jl) - zdh * rhoic * r1_rhosn )
315
316                  ! ice volume, salt content, age content
317                  v_i(ji,jj,jl)   = ht_i(ji,jj,jl) * a_i(ji,jj,jl)              ! ice volume
318                  v_s(ji,jj,jl)   = ht_s(ji,jj,jl) * a_i(ji,jj,jl)              ! snow volume
319                  smv_i(ji,jj,jl) = MIN( sm_i(ji,jj,jl) , sss_m(ji,jj) ) * v_i(ji,jj,jl) ! salt content
320                  oa_i(ji,jj,jl)  = o_i(ji,jj,jl) * a_i(ji,jj,jl)               ! age content
321               END DO
322            END DO
323         END DO
324
325         ! for constant salinity in time
326         IF( nn_icesal == 1 .OR. nn_icesal == 3 )  THEN
327            CALL lim_var_salprof
328            smv_i = sm_i * v_i
329         ENDIF
330           
331         ! Snow temperature and heat content
332         DO jk = 1, nlay_s
333            DO jl = 1, jpl ! loop over categories
334               DO jj = 1, jpj
335                  DO ji = 1, jpi
336                     t_s(ji,jj,jk,jl) = zswitch(ji,jj) * ztm_i_ini(ji,jj) + ( 1._wp - zswitch(ji,jj) ) * rt0
337                     ! Snow energy of melting
338                     e_s(ji,jj,jk,jl) = zswitch(ji,jj) * rhosn * ( cpic * ( rt0 - t_s(ji,jj,jk,jl) ) + lfus )
339
340                     ! Mutliply by volume, and divide by number of layers to get heat content in J/m2
341                     e_s(ji,jj,jk,jl) = e_s(ji,jj,jk,jl) * v_s(ji,jj,jl) * r1_nlay_s
342                  END DO
343               END DO
344            END DO
345         END DO
346
347         ! Ice salinity, temperature and heat content
348         DO jk = 1, nlay_i
349            DO jl = 1, jpl ! loop over categories
350               DO jj = 1, jpj
351                  DO ji = 1, jpi
352                     t_i(ji,jj,jk,jl) = zswitch(ji,jj) * ztm_i_ini(ji,jj) + ( 1._wp - zswitch(ji,jj) ) * rt0 
353                     s_i(ji,jj,jk,jl) = zswitch(ji,jj) * zsm_i_ini(ji,jj) + ( 1._wp - zswitch(ji,jj) ) * rn_simin
354                     ztmelts          = - tmut * s_i(ji,jj,jk,jl) + rt0 !Melting temperature in K
355
356                     ! heat content per unit volume
357                     e_i(ji,jj,jk,jl) = zswitch(ji,jj) * rhoic * (   cpic    * ( ztmelts - t_i(ji,jj,jk,jl) ) &
358                        +   lfus    * ( 1._wp - (ztmelts-rt0) / MIN((t_i(ji,jj,jk,jl)-rt0),-epsi20) ) &
359                        -   rcp     * ( ztmelts - rt0 ) )
360
361                     ! Mutliply by ice volume, and divide by number of layers to get heat content in J/m2
362                     e_i(ji,jj,jk,jl) = e_i(ji,jj,jk,jl) * v_i(ji,jj,jl) * r1_nlay_i
363                  END DO
364               END DO
365            END DO
366         END DO
367
368         tn_ice (:,:,:) = t_su (:,:,:)
369
370         ! MV MP 2016
371         ! Melt pond volume and fraction
372         IF ( ln_pnd ) THEN
373
374            DO jl = 1, jpl
375
376               a_ip_frac(:,:,jl) = 0.2 *  zswitch(:,:)
377               h_ip     (:,:,jl) = 0.05 * zswitch(:,:)
378               a_ip(:,:,jl)      = a_ip_frac(:,:,jl) * a_i (:,:,jl) 
379               v_ip(:,:,jl)      = h_ip     (:,:,jl) * a_ip(:,:,jl)
380
381            END DO
382
383         ELSE
384
385            a_ip(:,:,:)      = 0._wp
386            v_ip(:,:,:)      = 0._wp
387            a_ip_frac(:,:,:) = 0._wp
388            h_ip     (:,:,:) = 0._wp
389
390         ENDIF
391         ! END MV MP 2016
392
393      ELSE ! if ln_limini=false
394         a_i  (:,:,:) = 0._wp
395         v_i  (:,:,:) = 0._wp
396         v_s  (:,:,:) = 0._wp
397         smv_i(:,:,:) = 0._wp
398         oa_i (:,:,:) = 0._wp
399         ht_i (:,:,:) = 0._wp
400         ht_s (:,:,:) = 0._wp
401         sm_i (:,:,:) = 0._wp
402         o_i  (:,:,:) = 0._wp
403
404         e_i(:,:,:,:) = 0._wp
405         e_s(:,:,:,:) = 0._wp
406
407         DO jl = 1, jpl
408            DO jk = 1, nlay_i
409               t_i(:,:,jk,jl) = rt0 * tmask(:,:,1)
410            END DO
411            DO jk = 1, nlay_s
412               t_s(:,:,jk,jl) = rt0 * tmask(:,:,1)
413            END DO
414         END DO
415
416         a_ip(:,:,:)      = 0._wp
417         v_ip(:,:,:)      = 0._wp
418         a_ip_frac(:,:,:) = 0._wp
419         h_ip     (:,:,:) = 0._wp
420
421      ENDIF ! ln_limini
422     
423      at_i (:,:) = 0.0_wp
424      DO jl = 1, jpl
425         at_i (:,:) = at_i (:,:) + a_i (:,:,jl)
426      END DO
427
428      !--------------------------------------------------------------------
429      ! 4) Global ice variables for output diagnostics                    |
430      !--------------------------------------------------------------------
431      u_ice (:,:)     = 0._wp
432      v_ice (:,:)     = 0._wp
433      stress1_i(:,:)  = 0._wp
434      stress2_i(:,:)  = 0._wp
435      stress12_i(:,:) = 0._wp
436
437      !--------------------------------------------------------------------
438      ! 5) Moments for advection
439      !--------------------------------------------------------------------
440
441      sxopw (:,:) = 0._wp 
442      syopw (:,:) = 0._wp 
443      sxxopw(:,:) = 0._wp 
444      syyopw(:,:) = 0._wp 
445      sxyopw(:,:) = 0._wp
446
447      sxice (:,:,:)  = 0._wp   ;   sxsn (:,:,:)  = 0._wp   ;   sxa  (:,:,:)  = 0._wp
448      syice (:,:,:)  = 0._wp   ;   sysn (:,:,:)  = 0._wp   ;   sya  (:,:,:)  = 0._wp
449      sxxice(:,:,:)  = 0._wp   ;   sxxsn(:,:,:)  = 0._wp   ;   sxxa (:,:,:)  = 0._wp
450      syyice(:,:,:)  = 0._wp   ;   syysn(:,:,:)  = 0._wp   ;   syya (:,:,:)  = 0._wp
451      sxyice(:,:,:)  = 0._wp   ;   sxysn(:,:,:)  = 0._wp   ;   sxya (:,:,:)  = 0._wp
452
453      sxc0  (:,:,:)  = 0._wp   ;   sxe  (:,:,:,:)= 0._wp   
454      syc0  (:,:,:)  = 0._wp   ;   sye  (:,:,:,:)= 0._wp   
455      sxxc0 (:,:,:)  = 0._wp   ;   sxxe (:,:,:,:)= 0._wp   
456      syyc0 (:,:,:)  = 0._wp   ;   syye (:,:,:,:)= 0._wp   
457      sxyc0 (:,:,:)  = 0._wp   ;   sxye (:,:,:,:)= 0._wp   
458
459      sxsal  (:,:,:)  = 0._wp
460      sysal  (:,:,:)  = 0._wp
461      sxxsal (:,:,:)  = 0._wp
462      syysal (:,:,:)  = 0._wp
463      sxysal (:,:,:)  = 0._wp
464
465      sxage  (:,:,:)  = 0._wp
466      syage  (:,:,:)  = 0._wp
467      sxxage (:,:,:)  = 0._wp
468      syyage (:,:,:)  = 0._wp
469      sxyage (:,:,:)  = 0._wp
470
471      !------------------------------------
472      ! 6) store fields at before time-step
473      !------------------------------------
474      ! it is only necessary for the 1st interpolation by Agrif
475      a_i_b  (:,:,:)   = a_i  (:,:,:)
476      e_i_b  (:,:,:,:) = e_i  (:,:,:,:)
477      v_i_b  (:,:,:)   = v_i  (:,:,:)
478      v_s_b  (:,:,:)   = v_s  (:,:,:)
479      e_s_b  (:,:,:,:) = e_s  (:,:,:,:)
480      smv_i_b(:,:,:)   = smv_i(:,:,:)
481      oa_i_b (:,:,:)   = oa_i (:,:,:)
482      u_ice_b(:,:)     = u_ice(:,:)
483      v_ice_b(:,:)     = v_ice(:,:)
484
485      ! MV MP 2016
486      IF ( nn_pnd_scheme > 0 ) THEN
487         sxap  (:,:,:) = 0._wp    ; sxvp  (:,:,:) = 0._wp 
488         syap  (:,:,:) = 0._wp    ; syvp  (:,:,:) = 0._wp 
489         sxxap (:,:,:) = 0._wp    ; sxxvp (:,:,:) = 0._wp 
490         syyap (:,:,:) = 0._wp    ; syyvp (:,:,:) = 0._wp 
491         sxyap (:,:,:) = 0._wp    ; sxyvp (:,:,:) = 0._wp
492      ENDIF
493      ! END MV MP 2016
494
495!!!clem
496!!      ! Output the initial state and forcings
497!!      CALL dia_wri_state( 'output.init', nit000 )
498!!!     
499
500   END SUBROUTINE lim_istate
501
502   SUBROUTINE lim_istate_init
503      !!-------------------------------------------------------------------
504      !!                   ***  ROUTINE lim_istate_init  ***
505      !!       
506      !! ** Purpose : Definition of initial state of the ice
507      !!
508      !! ** Method : Read the namiceini namelist and check the parameter
509      !!       values called at the first timestep (nit000)
510      !!
511      !! ** input :
512      !!        Namelist namiceini
513      !!
514      !! history :
515      !!  8.5  ! 03-08 (C. Ethe) original code
516      !!  8.5  ! 07-11 (M. Vancoppenolle) rewritten initialization
517      !!-----------------------------------------------------------------------------
518      !
519      INTEGER :: ios,ierr,inum_ice                 ! Local integer output status for namelist read
520      INTEGER :: ji,jj
521      INTEGER :: ifpr, ierror
522      !
523      CHARACTER(len=256) ::  cn_dir          ! Root directory for location of ice files
524      TYPE(FLD_N)                    ::   sn_hti, sn_hts, sn_ati, sn_tsu, sn_tmi, sn_smi
525      TYPE(FLD_N), DIMENSION(jpfldi) ::   slf_i                 ! array of namelist informations on the fields to read
526      !
527      NAMELIST/namiceini/ ln_limini, ln_limini_file, rn_thres_sst, rn_hts_ini_n, rn_hts_ini_s,  &
528         &                rn_hti_ini_n, rn_hti_ini_s, rn_ati_ini_n, rn_ati_ini_s, rn_smi_ini_n, &
529         &                rn_smi_ini_s, rn_tmi_ini_n, rn_tmi_ini_s,                             &
530         &                sn_hti, sn_hts, sn_ati, sn_tsu, sn_tmi, sn_smi, cn_dir
531      !!-----------------------------------------------------------------------------
532      !
533      REWIND( numnam_ice_ref )              ! Namelist namiceini in reference namelist : Ice initial state
534      READ  ( numnam_ice_ref, namiceini, IOSTAT = ios, ERR = 901)
535901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namiceini in reference namelist', lwp )
536
537      REWIND( numnam_ice_cfg )              ! Namelist namiceini in configuration namelist : Ice initial state
538      READ  ( numnam_ice_cfg, namiceini, IOSTAT = ios, ERR = 902 )
539902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namiceini in configuration namelist', lwp )
540      IF(lwm) WRITE ( numoni, namiceini )
541
542      slf_i(jp_hti) = sn_hti  ;  slf_i(jp_hts) = sn_hts
543      slf_i(jp_ati) = sn_ati  ;  slf_i(jp_tsu) = sn_tsu
544      slf_i(jp_tmi) = sn_tmi  ;  slf_i(jp_smi) = sn_smi
545
546      ! Define the initial parameters
547      ! -------------------------
548
549      IF(lwp) THEN
550         WRITE(numout,*)
551         WRITE(numout,*) 'lim_istate_init : ice parameters inititialisation '
552         WRITE(numout,*) '~~~~~~~~~~~~~~~'
553         WRITE(numout,*) '   initialization with ice (T) or not (F)       ln_limini     = ', ln_limini
554         WRITE(numout,*) '   ice initialization from a netcdf file      ln_limini_file  = ', ln_limini_file
555         WRITE(numout,*) '   threshold water temp. for initial sea-ice    rn_thres_sst  = ', rn_thres_sst
556         WRITE(numout,*) '   initial snow thickness in the north          rn_hts_ini_n  = ', rn_hts_ini_n
557         WRITE(numout,*) '   initial snow thickness in the south          rn_hts_ini_s  = ', rn_hts_ini_s 
558         WRITE(numout,*) '   initial ice thickness  in the north          rn_hti_ini_n  = ', rn_hti_ini_n
559         WRITE(numout,*) '   initial ice thickness  in the south          rn_hti_ini_s  = ', rn_hti_ini_s
560         WRITE(numout,*) '   initial ice concentr.  in the north          rn_ati_ini_n  = ', rn_ati_ini_n
561         WRITE(numout,*) '   initial ice concentr.  in the north          rn_ati_ini_s  = ', rn_ati_ini_s
562         WRITE(numout,*) '   initial  ice salinity  in the north          rn_smi_ini_n  = ', rn_smi_ini_n
563         WRITE(numout,*) '   initial  ice salinity  in the south          rn_smi_ini_s  = ', rn_smi_ini_s
564         WRITE(numout,*) '   initial  ice/snw temp  in the north          rn_tmi_ini_n  = ', rn_tmi_ini_n
565         WRITE(numout,*) '   initial  ice/snw temp  in the south          rn_tmi_ini_s  = ', rn_tmi_ini_s
566      ENDIF
567
568      IF( ln_limini_file ) THEN                      ! Ice initialization using input file
569         !
570         ! set si structure
571         ALLOCATE( si(jpfldi), STAT=ierror )
572         IF( ierror > 0 ) THEN
573            CALL ctl_stop( 'Ice_ini in limistate: unable to allocate si structure' )   ;   RETURN
574         ENDIF
575
576         DO ifpr = 1, jpfldi
577            ALLOCATE( si(ifpr)%fnow(jpi,jpj,1) )
578            ALLOCATE( si(ifpr)%fdta(jpi,jpj,1,2) )
579         END DO
580
581         ! fill si with slf_i and control print
582         CALL fld_fill( si, slf_i, cn_dir, 'lim_istate', 'lim istate ini', 'numnam_ice' )
583
584         CALL fld_read( nit000, 1, si )                ! input fields provided at the current time-step
585
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.