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/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90 @ 6989

Last change on this file since 6989 was 6989, checked in by clem, 8 years ago

use a namelist parameter to choose between the different advection schemes

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