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.
limrst.F90 in branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90 @ 7910

Last change on this file since 7910 was 7910, checked in by timgraham, 7 years ago

All wrk_alloc removed

  • Property svn:keywords set to Id
File size: 24.1 KB
Line 
1MODULE limrst
2   !!======================================================================
3   !!                     ***  MODULE  limrst  ***
4   !! Ice restart :  write the ice restart file
5   !!======================================================================
6   !! History:   -   ! 2005-04 (M. Vancoppenolle) Original code
7   !!           3.0  ! 2008-03 (C. Ethe) restart files in using IOM interface
8   !!           4.0  ! 2011-02 (G. Madec) dynamical allocation
9   !!----------------------------------------------------------------------
10#if defined key_lim3
11   !!----------------------------------------------------------------------
12   !!   'key_lim3' :                                   LIM sea-ice model
13   !!----------------------------------------------------------------------
14   !!   lim_rst_opn   : open ice restart file
15   !!   lim_rst_write : write of the restart file
16   !!   lim_rst_read  : read  the restart file
17   !!----------------------------------------------------------------------
18   USE ice            ! sea-ice variables
19   USE oce     , ONLY :  snwice_mass, snwice_mass_b
20   USE dom_oce        ! ocean domain
21   USE sbc_oce        ! Surface boundary condition: ocean fields
22   USE sbc_ice        ! Surface boundary condition: ice fields
23   USE in_out_manager ! I/O manager
24   USE iom            ! I/O library
25   USE lib_mpp        ! MPP library
26   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
27   USE limctl
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   lim_rst_opn    ! routine called by icestep.F90
33   PUBLIC   lim_rst_write  ! routine called by icestep.F90
34   PUBLIC   lim_rst_read   ! routine called by sbc_lim_init
35
36   LOGICAL, PUBLIC ::   lrst_ice         !: logical to control the ice restart write
37   INTEGER, PUBLIC ::   numrir, numriw   !: logical unit for ice restart (read and write)
38
39   !!----------------------------------------------------------------------
40   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
41   !! $Id$
42   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
43   !!----------------------------------------------------------------------
44CONTAINS
45
46   SUBROUTINE lim_rst_opn( kt )
47      !!----------------------------------------------------------------------
48      !!                    ***  lim_rst_opn  ***
49      !!
50      !! ** purpose  :   output of sea-ice variable in a netcdf file
51      !!----------------------------------------------------------------------
52      INTEGER, INTENT(in) ::   kt       ! number of iteration
53      !
54      CHARACTER(len=20)   ::   clkt     ! ocean time-step define as a character
55      CHARACTER(len=50)   ::   clname   ! ice output restart file name
56      CHARACTER(len=256)  ::   clpath   ! full path to ice output restart file
57      !!----------------------------------------------------------------------
58      !
59      IF( kt == nit000 )   lrst_ice = .FALSE.   ! default definition
60
61      ! in order to get better performances with NetCDF format, we open and define the ice restart file
62      ! one ice time step before writing the data (-> at nitrst - 2*nn_fsbc + 1), except if we write ice
63      ! restart files every ice time step or if an ice restart file was writen at nitend - 2*nn_fsbc + 1
64      IF( kt == nitrst - 2*nn_fsbc + 1 .OR. nstock == nn_fsbc    &
65         &                             .OR. ( kt == nitend - nn_fsbc + 1 .AND. .NOT. lrst_ice ) ) THEN
66         IF( nitrst <= nitend .AND. nitrst > 0 ) THEN
67            ! beware of the format used to write kt (default is i8.8, that should be large enough...)
68            IF( nitrst > 99999999 ) THEN   ;   WRITE(clkt, *       ) nitrst
69            ELSE                           ;   WRITE(clkt, '(i8.8)') nitrst
70            ENDIF
71            ! create the file
72            clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_icerst_out)
73            clpath = TRIM(cn_icerst_outdir) 
74            IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath)//'/'
75            IF(lwp) THEN
76               WRITE(numout,*)
77               SELECT CASE ( jprstlib )
78               CASE DEFAULT
79                  WRITE(numout,*) '             open ice restart NetCDF file: ',TRIM(clpath)//clname
80               END SELECT
81               IF( kt == nitrst - 2*nn_fsbc + 1 ) THEN   
82                  WRITE(numout,*)         '             kt = nitrst - 2*nn_fsbc + 1 = ', kt,' date= ', ndastp
83               ELSE   ;   WRITE(numout,*) '             kt = '                         , kt,' date= ', ndastp
84               ENDIF
85            ENDIF
86            !
87            CALL iom_open( TRIM(clpath)//TRIM(clname), numriw, ldwrt = .TRUE., kiolib = jprstlib )
88            lrst_ice = .TRUE.
89         ENDIF
90      ENDIF
91      !
92      IF( ln_limctl )   CALL lim_prt( kt, iiceprt, jiceprt, 1, ' - Beginning the time step - ' )   ! control print
93   END SUBROUTINE lim_rst_opn
94
95
96   SUBROUTINE lim_rst_write( kt )
97      !!----------------------------------------------------------------------
98      !!                    ***  lim_rst_write  ***
99      !!
100      !! ** purpose  :   output of sea-ice variable in a netcdf file
101      !!----------------------------------------------------------------------
102      INTEGER, INTENT(in) ::   kt     ! number of iteration
103      !!
104      INTEGER ::   ji, jj, jk ,jl   ! dummy loop indices
105      INTEGER ::   iter
106      CHARACTER(len=25) ::   znam
107      CHARACTER(len=2)  ::   zchar, zchar1
108      REAL(wp), DIMENSION(jpi,jpj) :: z2d
109      !!----------------------------------------------------------------------
110
111
112      iter = kt + nn_fsbc - 1   ! ice restarts are written at kt == nitrst - nn_fsbc + 1
113
114      IF( iter == nitrst ) THEN
115         IF(lwp) WRITE(numout,*)
116         IF(lwp) WRITE(numout,*) 'lim_rst_write : write ice restart file  kt =', kt
117         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~'         
118      ENDIF
119
120      ! Write in numriw (if iter == nitrst)
121      ! ------------------
122      !                                                                        ! calendar control
123      CALL iom_rstput( iter, nitrst, numriw, 'nn_fsbc', REAL( nn_fsbc, wp ) )      ! time-step
124      CALL iom_rstput( iter, nitrst, numriw, 'kt_ice' , REAL( iter   , wp ) )      ! date
125
126      ! Prognostic variables
127      DO jl = 1, jpl 
128         WRITE(zchar,'(I2.2)') jl
129         znam = 'v_i'//'_htc'//zchar
130         z2d(:,:) = v_i(:,:,jl)
131         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
132         znam = 'v_s'//'_htc'//zchar
133         z2d(:,:) = v_s(:,:,jl)
134         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
135         znam = 'smv_i'//'_htc'//zchar
136         z2d(:,:) = smv_i(:,:,jl)
137         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
138         znam = 'oa_i'//'_htc'//zchar
139         z2d(:,:) = oa_i(:,:,jl)
140         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
141         znam = 'a_i'//'_htc'//zchar
142         z2d(:,:) = a_i(:,:,jl)
143         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
144         znam = 't_su'//'_htc'//zchar
145         z2d(:,:) = t_su(:,:,jl)
146         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
147         znam = 'tempt_sl1'//'_htc'//zchar
148         z2d(:,:) = e_s(:,:,1,jl)
149         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
150         DO jk = 1, nlay_i 
151            WRITE(zchar1,'(I2.2)') jk
152            znam = 'tempt'//'_il'//zchar1//'_htc'//zchar
153            z2d(:,:) = e_i(:,:,jk,jl)
154            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
155         END DO
156      END DO
157
158      CALL iom_rstput( iter, nitrst, numriw, 'u_ice'        , u_ice      )
159      CALL iom_rstput( iter, nitrst, numriw, 'v_ice'        , v_ice      )
160      CALL iom_rstput( iter, nitrst, numriw, 'stress1_i'    , stress1_i  )
161      CALL iom_rstput( iter, nitrst, numriw, 'stress2_i'    , stress2_i  )
162      CALL iom_rstput( iter, nitrst, numriw, 'stress12_i'   , stress12_i )
163      CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass'  , snwice_mass )
164      CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass_b', snwice_mass_b )
165
166      ! In case Prather scheme is used for advection, write second order moments
167      ! ------------------------------------------------------------------------
168      IF( nn_limadv == -1 ) THEN
169         
170         DO jl = 1, jpl 
171            WRITE(zchar,'(I2.2)') jl
172            znam = 'sxice'//'_htc'//zchar
173            z2d(:,:) = sxice(:,:,jl)
174            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
175            znam = 'syice'//'_htc'//zchar
176            z2d(:,:) = syice(:,:,jl)
177            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
178            znam = 'sxxice'//'_htc'//zchar
179            z2d(:,:) = sxxice(:,:,jl)
180            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
181            znam = 'syyice'//'_htc'//zchar
182            z2d(:,:) = syyice(:,:,jl)
183            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
184            znam = 'sxyice'//'_htc'//zchar
185            z2d(:,:) = sxyice(:,:,jl)
186            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
187            znam = 'sxsn'//'_htc'//zchar
188            z2d(:,:) = sxsn(:,:,jl)
189            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
190            znam = 'sysn'//'_htc'//zchar
191            z2d(:,:) = sysn(:,:,jl)
192            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
193            znam = 'sxxsn'//'_htc'//zchar
194            z2d(:,:) = sxxsn(:,:,jl)
195            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
196            znam = 'syysn'//'_htc'//zchar
197            z2d(:,:) = syysn(:,:,jl)
198            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
199            znam = 'sxysn'//'_htc'//zchar
200            z2d(:,:) = sxysn(:,:,jl)
201            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
202            znam = 'sxa'//'_htc'//zchar
203            z2d(:,:) = sxa(:,:,jl)
204            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
205            znam = 'sya'//'_htc'//zchar
206            z2d(:,:) = sya(:,:,jl)
207            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
208            znam = 'sxxa'//'_htc'//zchar
209            z2d(:,:) = sxxa(:,:,jl)
210            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
211            znam = 'syya'//'_htc'//zchar
212            z2d(:,:) = syya(:,:,jl)
213            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
214            znam = 'sxya'//'_htc'//zchar
215            z2d(:,:) = sxya(:,:,jl)
216            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
217            znam = 'sxc0'//'_htc'//zchar
218            z2d(:,:) = sxc0(:,:,jl)
219            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
220            znam = 'syc0'//'_htc'//zchar
221            z2d(:,:) = syc0(:,:,jl)
222            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
223            znam = 'sxxc0'//'_htc'//zchar
224            z2d(:,:) = sxxc0(:,:,jl)
225            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
226            znam = 'syyc0'//'_htc'//zchar
227            z2d(:,:) = syyc0(:,:,jl)
228            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
229            znam = 'sxyc0'//'_htc'//zchar
230            z2d(:,:) = sxyc0(:,:,jl)
231            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
232            znam = 'sxsal'//'_htc'//zchar
233            z2d(:,:) = sxsal(:,:,jl)
234            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
235            znam = 'sysal'//'_htc'//zchar
236            z2d(:,:) = sysal(:,:,jl)
237            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
238            znam = 'sxxsal'//'_htc'//zchar
239            z2d(:,:) = sxxsal(:,:,jl)
240            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
241            znam = 'syysal'//'_htc'//zchar
242            z2d(:,:) = syysal(:,:,jl)
243            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
244            znam = 'sxysal'//'_htc'//zchar
245            z2d(:,:) = sxysal(:,:,jl)
246            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
247            znam = 'sxage'//'_htc'//zchar
248            z2d(:,:) = sxage(:,:,jl)
249            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
250            znam = 'syage'//'_htc'//zchar
251            z2d(:,:) = syage(:,:,jl)
252            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
253            znam = 'sxxage'//'_htc'//zchar
254            z2d(:,:) = sxxage(:,:,jl)
255            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
256            znam = 'syyage'//'_htc'//zchar
257            z2d(:,:) = syyage(:,:,jl)
258            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
259            znam = 'sxyage'//'_htc'//zchar
260            z2d(:,:) = sxyage(:,:,jl)
261            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
262         END DO
263
264         CALL iom_rstput( iter, nitrst, numriw, 'sxopw ' ,  sxopw  )
265         CALL iom_rstput( iter, nitrst, numriw, 'syopw ' ,  syopw  )
266         CALL iom_rstput( iter, nitrst, numriw, 'sxxopw' ,  sxxopw )
267         CALL iom_rstput( iter, nitrst, numriw, 'syyopw' ,  syyopw )
268         CALL iom_rstput( iter, nitrst, numriw, 'sxyopw' ,  sxyopw )
269         
270         DO jl = 1, jpl 
271            WRITE(zchar,'(I2.2)') jl
272            DO jk = 1, nlay_i 
273               WRITE(zchar1,'(I2.2)') jk
274               znam = 'sxe'//'_il'//zchar1//'_htc'//zchar
275               z2d(:,:) = sxe(:,:,jk,jl)
276               CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
277               znam = 'sye'//'_il'//zchar1//'_htc'//zchar
278               z2d(:,:) = sye(:,:,jk,jl)
279               CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
280               znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar
281               z2d(:,:) = sxxe(:,:,jk,jl)
282               CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
283               znam = 'syye'//'_il'//zchar1//'_htc'//zchar
284               z2d(:,:) = syye(:,:,jk,jl)
285               CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
286               znam = 'sxye'//'_il'//zchar1//'_htc'//zchar
287               z2d(:,:) = sxye(:,:,jk,jl)
288               CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
289            END DO
290         END DO
291
292      ENDIF
293     
294      ! close restart file
295      ! ------------------
296      IF( iter == nitrst ) THEN
297         CALL iom_close( numriw )
298         lrst_ice = .FALSE.
299      ENDIF
300      !
301      !
302   END SUBROUTINE lim_rst_write
303
304
305   SUBROUTINE lim_rst_read
306      !!----------------------------------------------------------------------
307      !!                    ***  lim_rst_read  ***
308      !!
309      !! ** purpose  :   read of sea-ice variable restart in a netcdf file
310      !!----------------------------------------------------------------------
311      INTEGER :: ji, jj, jk, jl
312      REAL(wp) ::   zfice, ziter
313      REAL(wp), DIMENSION(jpi,jpj) ::   z2d
314      CHARACTER(len=25) ::   znam
315      CHARACTER(len=2)  ::   zchar, zchar1
316      INTEGER           ::   jlibalt = jprstlib
317      LOGICAL           ::   llok
318      !!----------------------------------------------------------------------
319
320
321      IF(lwp) THEN
322         WRITE(numout,*)
323         WRITE(numout,*) 'lim_rst_read : read ice NetCDF restart file'
324         WRITE(numout,*) '~~~~~~~~~~~~~'
325      ENDIF
326
327      CALL iom_open ( TRIM(cn_icerst_indir)//'/'//cn_icerst_in, numrir, kiolib = jprstlib )
328
329      CALL iom_get( numrir, 'nn_fsbc', zfice )
330      CALL iom_get( numrir, 'kt_ice' , ziter )   
331      IF(lwp) WRITE(numout,*) '   read ice restart file at time step    : ', ziter
332      IF(lwp) WRITE(numout,*) '   in any case we force it to nit000 - 1 : ', nit000 - 1
333
334      !Control of date
335
336      IF( ( nit000 - NINT(ziter) ) /= 1 .AND. ABS( nrstdt ) == 1 )   &
337         &     CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nit000 in ice restart',  &
338         &                   '   verify the file or rerun with the value 0 for the',        &
339         &                   '   control of time parameter  nrstdt' )
340      IF( NINT(zfice) /= nn_fsbc          .AND. ABS( nrstdt ) == 1 )   &
341         &     CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nn_fsbc in ice restart',  &
342         &                   '   verify the file or rerun with the value 0 for the',         &
343         &                   '   control of time parameter  nrstdt' )
344
345      ! Prognostic variables
346      DO jl = 1, jpl 
347         WRITE(zchar,'(I2.2)') jl
348         znam = 'v_i'//'_htc'//zchar
349         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
350         v_i(:,:,jl) = z2d(:,:)
351         znam = 'v_s'//'_htc'//zchar
352         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
353         v_s(:,:,jl) = z2d(:,:) 
354         znam = 'smv_i'//'_htc'//zchar
355         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
356         smv_i(:,:,jl) = z2d(:,:)
357         znam = 'oa_i'//'_htc'//zchar
358         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
359         oa_i(:,:,jl) = z2d(:,:)
360         znam = 'a_i'//'_htc'//zchar
361         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
362         a_i(:,:,jl) = z2d(:,:)
363         znam = 't_su'//'_htc'//zchar
364         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
365         t_su(:,:,jl) = z2d(:,:)
366         znam = 'tempt_sl1'//'_htc'//zchar
367         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
368         e_s(:,:,1,jl) = z2d(:,:)
369         DO jk = 1, nlay_i 
370            WRITE(zchar1,'(I2.2)') jk
371            znam = 'tempt'//'_il'//zchar1//'_htc'//zchar
372            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
373            e_i(:,:,jk,jl) = z2d(:,:)
374         END DO
375      END DO
376
377      CALL iom_get( numrir, jpdom_autoglo, 'u_ice'     , u_ice      )
378      CALL iom_get( numrir, jpdom_autoglo, 'v_ice'     , v_ice      )
379      CALL iom_get( numrir, jpdom_autoglo, 'stress1_i' , stress1_i  )
380      CALL iom_get( numrir, jpdom_autoglo, 'stress2_i' , stress2_i  )
381      CALL iom_get( numrir, jpdom_autoglo, 'stress12_i', stress12_i )
382      CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass'  , snwice_mass )
383      CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass_b', snwice_mass_b )
384
385      ! In case Prather scheme is used for advection, read second order moments
386      ! ------------------------------------------------------------------------
387      IF( nn_limadv == -1 ) THEN
388
389         DO jl = 1, jpl 
390            WRITE(zchar,'(I2.2)') jl
391            znam = 'sxice'//'_htc'//zchar
392            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
393            sxice(:,:,jl) = z2d(:,:)
394            znam = 'syice'//'_htc'//zchar
395            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
396            syice(:,:,jl) = z2d(:,:)
397            znam = 'sxxice'//'_htc'//zchar
398            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
399            sxxice(:,:,jl) = z2d(:,:)
400            znam = 'syyice'//'_htc'//zchar
401            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
402            syyice(:,:,jl) = z2d(:,:)
403            znam = 'sxyice'//'_htc'//zchar
404            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
405            sxyice(:,:,jl) = z2d(:,:)
406            znam = 'sxsn'//'_htc'//zchar
407            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
408            sxsn(:,:,jl) = z2d(:,:)
409            znam = 'sysn'//'_htc'//zchar
410            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
411            sysn(:,:,jl) = z2d(:,:)
412            znam = 'sxxsn'//'_htc'//zchar
413            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
414            sxxsn(:,:,jl) = z2d(:,:)
415            znam = 'syysn'//'_htc'//zchar
416            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
417            syysn(:,:,jl) = z2d(:,:)
418            znam = 'sxysn'//'_htc'//zchar
419            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
420            sxysn(:,:,jl) = z2d(:,:)
421            znam = 'sxa'//'_htc'//zchar
422            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
423            sxa(:,:,jl) = z2d(:,:)
424            znam = 'sya'//'_htc'//zchar
425            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
426            sya(:,:,jl) = z2d(:,:)
427            znam = 'sxxa'//'_htc'//zchar
428            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
429            sxxa(:,:,jl) = z2d(:,:)
430            znam = 'syya'//'_htc'//zchar
431            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
432            syya(:,:,jl) = z2d(:,:)
433            znam = 'sxya'//'_htc'//zchar
434            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
435            sxya(:,:,jl) = z2d(:,:)
436            znam = 'sxc0'//'_htc'//zchar
437            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
438            sxc0(:,:,jl) = z2d(:,:)
439            znam = 'syc0'//'_htc'//zchar
440            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
441            syc0(:,:,jl) = z2d(:,:)
442            znam = 'sxxc0'//'_htc'//zchar
443            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
444            sxxc0(:,:,jl) = z2d(:,:)
445            znam = 'syyc0'//'_htc'//zchar
446            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
447            syyc0(:,:,jl) = z2d(:,:)
448            znam = 'sxyc0'//'_htc'//zchar
449            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
450            sxyc0(:,:,jl) = z2d(:,:)
451            znam = 'sxsal'//'_htc'//zchar
452            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
453            sxsal(:,:,jl) = z2d(:,:)
454            znam = 'sysal'//'_htc'//zchar
455            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
456            sysal(:,:,jl) = z2d(:,:)
457            znam = 'sxxsal'//'_htc'//zchar
458            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
459            sxxsal(:,:,jl) = z2d(:,:)
460            znam = 'syysal'//'_htc'//zchar
461            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
462            syysal(:,:,jl) = z2d(:,:)
463            znam = 'sxysal'//'_htc'//zchar
464            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
465            sxysal(:,:,jl) = z2d(:,:)
466            znam = 'sxage'//'_htc'//zchar
467            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
468            sxage(:,:,jl) = z2d(:,:)
469            znam = 'syage'//'_htc'//zchar
470            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
471            syage(:,:,jl) = z2d(:,:)
472            znam = 'sxxage'//'_htc'//zchar
473            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
474            sxxage(:,:,jl) = z2d(:,:)
475            znam = 'syyage'//'_htc'//zchar
476            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
477            syyage(:,:,jl) = z2d(:,:)
478            znam = 'sxyage'//'_htc'//zchar
479            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
480            sxyage(:,:,jl)= z2d(:,:)
481         END DO
482
483         CALL iom_get( numrir, jpdom_autoglo, 'sxopw ' ,  sxopw  )
484         CALL iom_get( numrir, jpdom_autoglo, 'syopw ' ,  syopw  )
485         CALL iom_get( numrir, jpdom_autoglo, 'sxxopw' ,  sxxopw )
486         CALL iom_get( numrir, jpdom_autoglo, 'syyopw' ,  syyopw )
487         CALL iom_get( numrir, jpdom_autoglo, 'sxyopw' ,  sxyopw )
488
489         DO jl = 1, jpl 
490            WRITE(zchar,'(I2.2)') jl
491            DO jk = 1, nlay_i 
492               WRITE(zchar1,'(I2.2)') jk
493               znam = 'sxe'//'_il'//zchar1//'_htc'//zchar
494               CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
495               sxe(:,:,jk,jl) = z2d(:,:)
496               znam = 'sye'//'_il'//zchar1//'_htc'//zchar
497               CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
498               sye(:,:,jk,jl) = z2d(:,:)
499               znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar
500               CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
501               sxxe(:,:,jk,jl) = z2d(:,:)
502               znam = 'syye'//'_il'//zchar1//'_htc'//zchar
503               CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
504               syye(:,:,jk,jl) = z2d(:,:)
505               znam = 'sxye'//'_il'//zchar1//'_htc'//zchar
506               CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
507               sxye(:,:,jk,jl) = z2d(:,:)
508            END DO
509         END DO
510         !
511      END IF
512     
513      ! clem: I do not understand why the following IF is needed
514      !       I suspect something inconsistent in the main code with option nn_icesal=1
515      IF( nn_icesal == 1 ) THEN
516         DO jl = 1, jpl 
517            sm_i(:,:,jl) = rn_icesal
518            DO jk = 1, nlay_i 
519               s_i(:,:,jk,jl) = rn_icesal
520            END DO
521         END DO
522      ENDIF
523      !
524      !CALL iom_close( numrir ) !clem: closed in sbcice_lim.F90
525      !
526      !
527   END SUBROUTINE lim_rst_read
528
529#else
530   !!----------------------------------------------------------------------
531   !!   Default option :       Empty module            NO LIM sea-ice model
532   !!----------------------------------------------------------------------
533CONTAINS
534   SUBROUTINE lim_rst_read             ! Empty routine
535   END SUBROUTINE lim_rst_read
536   SUBROUTINE lim_rst_write            ! Empty routine
537   END SUBROUTINE lim_rst_write
538#endif
539
540   !!======================================================================
541END MODULE limrst
Note: See TracBrowser for help on using the repository browser.