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/2014/dev_r4650_UKMO11_restart_functionality/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2014/dev_r4650_UKMO11_restart_functionality/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90 @ 4780

Last change on this file since 4780 was 4780, checked in by edblockley, 10 years ago

Second commit in UKMO11 development branch.

This change allows the user to replace the nn_stock frequency-based restart dump writing functionality with a list-based version (nn_stocklist).
This is conterolled using the logical ln_rst_list which defaults to false.
At present the list is hard-wired to have maximum 10 entries but this could be modified if required.

Ed

  • 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 par_ice        ! sea-ice parameters
21   USE dom_oce        ! ocean domain
22   USE sbc_oce        ! Surface boundary condition: ocean fields
23   USE sbc_ice        ! Surface boundary condition: ice fields
24   USE in_out_manager ! I/O manager
25   USE iom            ! I/O library
26   USE lib_mpp        ! MPP library
27   USE wrk_nemo       ! work arrays
28   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
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 iceini.F90
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=150)  ::   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   END SUBROUTINE lim_rst_opn
96
97
98   SUBROUTINE lim_rst_write( kt )
99      !!----------------------------------------------------------------------
100      !!                    ***  lim_rst_write  ***
101      !!
102      !! ** purpose  :   output of sea-ice variable in a netcdf file
103      !!----------------------------------------------------------------------
104      INTEGER, INTENT(in) ::   kt     ! number of iteration
105      !!
106      INTEGER ::   ji, jj, jk ,jl   ! dummy loop indices
107      INTEGER ::   iter
108      CHARACTER(len=15) ::   znam
109      CHARACTER(len=1)  ::   zchar, zchar1
110      REAL(wp), POINTER, DIMENSION(:,:) :: z2d
111      !!----------------------------------------------------------------------
112
113      CALL wrk_alloc( jpi, jpj, z2d )
114
115      iter = kt + nn_fsbc - 1   ! ice restarts are written at kt == nitrst - nn_fsbc + 1
116
117      IF( iter == nitrst ) THEN
118         IF(lwp) WRITE(numout,*)
119         IF(lwp) WRITE(numout,*) 'lim_rst_write : write ice restart file  kt =', kt
120         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~'         
121      ENDIF
122
123      ! Write in numriw (if iter == nitrst)
124      ! ------------------
125      !                                                                        ! calendar control
126      CALL iom_rstput( iter, nitrst, numriw, 'nn_fsbc', REAL( nn_fsbc, wp ) )      ! time-step
127      CALL iom_rstput( iter, nitrst, numriw, 'kt_ice' , REAL( iter   , wp ) )      ! date
128
129      ! Prognostic variables
130      DO jl = 1, jpl 
131         WRITE(zchar,'(I1)') jl
132         znam = 'v_i'//'_htc'//zchar
133         z2d(:,:) = v_i(:,:,jl)
134         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
135         znam = 'v_s'//'_htc'//zchar
136         z2d(:,:) = v_s(:,:,jl)
137         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
138         znam = 'smv_i'//'_htc'//zchar
139         z2d(:,:) = smv_i(:,:,jl)
140         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
141         znam = 'oa_i'//'_htc'//zchar
142         z2d(:,:) = oa_i(:,:,jl)
143         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
144         znam = 'a_i'//'_htc'//zchar
145         z2d(:,:) = a_i(:,:,jl)
146         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
147         znam = 't_su'//'_htc'//zchar
148         z2d(:,:) = t_su(:,:,jl)
149         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
150      END DO
151
152      DO jl = 1, jpl 
153         WRITE(zchar,'(I1)') jl
154         znam = 'tempt_sl1'//'_htc'//zchar
155         z2d(:,:) = e_s(:,:,1,jl)
156         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
157      END DO
158
159      DO jl = 1, jpl 
160         WRITE(zchar,'(I1)') jl
161         DO jk = 1, nlay_i 
162            WRITE(zchar1,'(I1)') jk
163            znam = 'tempt'//'_il'//zchar1//'_htc'//zchar
164            z2d(:,:) = e_i(:,:,jk,jl)
165            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
166         END DO
167      END DO
168
169      CALL iom_rstput( iter, nitrst, numriw, 'u_ice'        , u_ice      )
170      CALL iom_rstput( iter, nitrst, numriw, 'v_ice'        , v_ice      )
171      CALL iom_rstput( iter, nitrst, numriw, 'stress1_i'    , stress1_i  )
172      CALL iom_rstput( iter, nitrst, numriw, 'stress2_i'    , stress2_i  )
173      CALL iom_rstput( iter, nitrst, numriw, 'stress12_i'   , stress12_i )
174      CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass'  , snwice_mass )   !clem modif
175      CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass_b', snwice_mass_b ) !clem modif
176
177      DO jl = 1, jpl 
178         WRITE(zchar,'(I1)') jl
179         znam = 'sxice'//'_htc'//zchar
180         z2d(:,:) = sxice(:,:,jl)
181         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
182         znam = 'syice'//'_htc'//zchar
183         z2d(:,:) = syice(:,:,jl)
184         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
185         znam = 'sxxice'//'_htc'//zchar
186         z2d(:,:) = sxxice(:,:,jl)
187         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
188         znam = 'syyice'//'_htc'//zchar
189         z2d(:,:) = syyice(:,:,jl)
190         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
191         znam = 'sxyice'//'_htc'//zchar
192         z2d(:,:) = sxyice(:,:,jl)
193         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
194         znam = 'sxsn'//'_htc'//zchar
195         z2d(:,:) = sxsn(:,:,jl)
196         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
197         znam = 'sysn'//'_htc'//zchar
198         z2d(:,:) = sysn(:,:,jl)
199         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
200         znam = 'sxxsn'//'_htc'//zchar
201         z2d(:,:) = sxxsn(:,:,jl)
202         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
203         znam = 'syysn'//'_htc'//zchar
204         z2d(:,:) = syysn(:,:,jl)
205         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
206         znam = 'sxysn'//'_htc'//zchar
207         z2d(:,:) = sxysn(:,:,jl)
208         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
209         znam = 'sxa'//'_htc'//zchar
210         z2d(:,:) = sxa(:,:,jl)
211         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
212         znam = 'sya'//'_htc'//zchar
213         z2d(:,:) = sya(:,:,jl)
214         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
215         znam = 'sxxa'//'_htc'//zchar
216         z2d(:,:) = sxxa(:,:,jl)
217         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
218         znam = 'syya'//'_htc'//zchar
219         z2d(:,:) = syya(:,:,jl)
220         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
221         znam = 'sxya'//'_htc'//zchar
222         z2d(:,:) = sxya(:,:,jl)
223         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
224         znam = 'sxc0'//'_htc'//zchar
225         z2d(:,:) = sxc0(:,:,jl)
226         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
227         znam = 'syc0'//'_htc'//zchar
228         z2d(:,:) = syc0(:,:,jl)
229         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
230         znam = 'sxxc0'//'_htc'//zchar
231         z2d(:,:) = sxxc0(:,:,jl)
232         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
233         znam = 'syyc0'//'_htc'//zchar
234         z2d(:,:) = syyc0(:,:,jl)
235         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
236         znam = 'sxyc0'//'_htc'//zchar
237         z2d(:,:) = sxyc0(:,:,jl)
238         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
239         znam = 'sxsal'//'_htc'//zchar
240         z2d(:,:) = sxsal(:,:,jl)
241         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
242         znam = 'sysal'//'_htc'//zchar
243         z2d(:,:) = sysal(:,:,jl)
244         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
245         znam = 'sxxsal'//'_htc'//zchar
246         z2d(:,:) = sxxsal(:,:,jl)
247         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
248         znam = 'syysal'//'_htc'//zchar
249         z2d(:,:) = syysal(:,:,jl)
250         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
251         znam = 'sxysal'//'_htc'//zchar
252         z2d(:,:) = sxysal(:,:,jl)
253         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
254         znam = 'sxage'//'_htc'//zchar
255         z2d(:,:) = sxage(:,:,jl)
256         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
257         znam = 'syage'//'_htc'//zchar
258         z2d(:,:) = syage(:,:,jl)
259         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
260         znam = 'sxxage'//'_htc'//zchar
261         z2d(:,:) = sxxage(:,:,jl)
262         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
263         znam = 'syyage'//'_htc'//zchar
264         z2d(:,:) = syyage(:,:,jl)
265         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
266         znam = 'sxyage'//'_htc'//zchar
267         z2d(:,:) = sxyage(:,:,jl)
268         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
269      END DO
270
271      CALL iom_rstput( iter, nitrst, numriw, 'sxopw ' ,  sxopw  )
272      CALL iom_rstput( iter, nitrst, numriw, 'syopw ' ,  syopw  )
273      CALL iom_rstput( iter, nitrst, numriw, 'sxxopw' ,  sxxopw )
274      CALL iom_rstput( iter, nitrst, numriw, 'syyopw' ,  syyopw )
275      CALL iom_rstput( iter, nitrst, numriw, 'sxyopw' ,  sxyopw )
276
277      DO jl = 1, jpl 
278         WRITE(zchar,'(I1)') jl
279         DO jk = 1, nlay_i 
280            WRITE(zchar1,'(I1)') jk
281            znam = 'sxe'//'_il'//zchar1//'_htc'//zchar
282            z2d(:,:) = sxe(:,:,jk,jl)
283            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
284            znam = 'sye'//'_il'//zchar1//'_htc'//zchar
285            z2d(:,:) = sye(:,:,jk,jl)
286            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
287            znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar
288            z2d(:,:) = sxxe(:,:,jk,jl)
289            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
290            znam = 'syye'//'_il'//zchar1//'_htc'//zchar
291            z2d(:,:) = syye(:,:,jk,jl)
292            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
293            znam = 'sxye'//'_il'//zchar1//'_htc'//zchar
294            z2d(:,:) = sxye(:,:,jk,jl)
295            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
296         END DO
297      END DO
298
299      IF( iter == nitrst ) THEN
300         CALL iom_close( numriw )                         ! close the restart file
301         lrst_ice = .FALSE.
302      ENDIF
303      !
304      CALL wrk_dealloc( jpi, jpj, z2d )
305      !
306   END SUBROUTINE lim_rst_write
307
308
309   SUBROUTINE lim_rst_read
310      !!----------------------------------------------------------------------
311      !!                    ***  lim_rst_read  ***
312      !!
313      !! ** purpose  :   read of sea-ice variable restart in a netcdf file
314      !!----------------------------------------------------------------------
315      INTEGER :: ji, jj, jk, jl, indx
316      REAL(wp) ::   zfice, ziter
317      REAL(wp) ::   zs_inf, z_slope_s, zsmax, zsmin, zalpha, zindb   ! local scalars used for the salinity profile
318      REAL(wp), POINTER, DIMENSION(:)  ::   zs_zero 
319      REAL(wp), POINTER, DIMENSION(:,:) ::   z2d
320      CHARACTER(len=15) ::   znam
321      CHARACTER(len=1)  ::   zchar, zchar1
322      INTEGER           ::   jlibalt = jprstlib
323      LOGICAL           ::   llok
324      !!----------------------------------------------------------------------
325
326      CALL wrk_alloc( nlay_i, zs_zero )
327      CALL wrk_alloc( jpi, jpj, z2d )
328
329      IF(lwp) THEN
330         WRITE(numout,*)
331         WRITE(numout,*) 'lim_rst_read : read ice NetCDF restart file'
332         WRITE(numout,*) '~~~~~~~~~~~~~'
333      ENDIF
334
335      IF ( jprstlib == jprstdimg ) THEN
336        ! eventually read netcdf file (monobloc)  for restarting on different number of processors
337        ! if {cn_icerst_in}.nc exists, then set jlibalt to jpnf90
338        INQUIRE( FILE = TRIM(cn_icerst_indir)//'/'//TRIM(cn_icerst_in)//'.nc', EXIST = llok )
339        IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF
340      ENDIF
341
342      CALL iom_open ( TRIM(cn_icerst_indir)//'/'//cn_icerst_in, numrir, kiolib = jprstlib )
343
344      CALL iom_get( numrir, 'nn_fsbc', zfice )
345      CALL iom_get( numrir, 'kt_ice' , ziter )   
346      IF(lwp) WRITE(numout,*) '   read ice restart file at time step    : ', ziter
347      IF(lwp) WRITE(numout,*) '   in any case we force it to nit000 - 1 : ', nit000 - 1
348
349      !Control of date
350
351      IF( ( nit000 - NINT(ziter) ) /= 1 .AND. ABS( nrstdt ) == 1 )   &
352         &     CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nit000 in ice restart',  &
353         &                   '   verify the file or rerun with the value 0 for the',        &
354         &                   '   control of time parameter  nrstdt' )
355      IF( NINT(zfice) /= nn_fsbc          .AND. ABS( nrstdt ) == 1 )   &
356         &     CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nn_fsbc in ice restart',  &
357         &                   '   verify the file or rerun with the value 0 for the',         &
358         &                   '   control of time parameter  nrstdt' )
359
360      DO jl = 1, jpl 
361         WRITE(zchar,'(I1)') jl
362         znam = 'v_i'//'_htc'//zchar
363         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
364         v_i(:,:,jl) = z2d(:,:)
365         znam = 'v_s'//'_htc'//zchar
366         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
367         v_s(:,:,jl) = z2d(:,:) 
368         znam = 'smv_i'//'_htc'//zchar
369         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
370         smv_i(:,:,jl) = z2d(:,:)
371         znam = 'oa_i'//'_htc'//zchar
372         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
373         oa_i(:,:,jl) = z2d(:,:)
374         znam = 'a_i'//'_htc'//zchar
375         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
376         a_i(:,:,jl) = z2d(:,:)
377         znam = 't_su'//'_htc'//zchar
378         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
379         t_su(:,:,jl) = z2d(:,:)
380      END DO
381
382      DO jl = 1, jpl 
383         WRITE(zchar,'(I1)') jl
384         znam = 'tempt_sl1'//'_htc'//zchar
385         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
386         e_s(:,:,1,jl) = z2d(:,:)
387      END DO
388
389      DO jl = 1, jpl 
390         WRITE(zchar,'(I1)') jl
391         DO jk = 1, nlay_i 
392            WRITE(zchar1,'(I1)') jk
393            znam = 'tempt'//'_il'//zchar1//'_htc'//zchar
394            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
395            e_i(:,:,jk,jl) = z2d(:,:)
396         END DO
397      END DO
398
399      CALL iom_get( numrir, jpdom_autoglo, 'u_ice'     , u_ice      )
400      CALL iom_get( numrir, jpdom_autoglo, 'v_ice'     , v_ice      )
401      CALL iom_get( numrir, jpdom_autoglo, 'stress1_i' , stress1_i  )
402      CALL iom_get( numrir, jpdom_autoglo, 'stress2_i' , stress2_i  )
403      CALL iom_get( numrir, jpdom_autoglo, 'stress12_i', stress12_i )
404      CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass'  , snwice_mass )   !clem modif
405      CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass_b', snwice_mass_b ) !clem modif
406
407      DO jl = 1, jpl 
408         WRITE(zchar,'(I1)') jl
409         znam = 'sxice'//'_htc'//zchar
410         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
411         sxice(:,:,jl) = z2d(:,:)
412         znam = 'syice'//'_htc'//zchar
413         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
414         syice(:,:,jl) = z2d(:,:)
415         znam = 'sxxice'//'_htc'//zchar
416         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
417         sxxice(:,:,jl) = z2d(:,:)
418         znam = 'syyice'//'_htc'//zchar
419         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
420         syyice(:,:,jl) = z2d(:,:)
421         znam = 'sxyice'//'_htc'//zchar
422         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
423         sxyice(:,:,jl) = z2d(:,:)
424         znam = 'sxsn'//'_htc'//zchar
425         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
426         sxsn(:,:,jl) = z2d(:,:)
427         znam = 'sysn'//'_htc'//zchar
428         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
429         sysn(:,:,jl) = z2d(:,:)
430         znam = 'sxxsn'//'_htc'//zchar
431         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
432         sxxsn(:,:,jl) = z2d(:,:)
433         znam = 'syysn'//'_htc'//zchar
434         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
435         syysn(:,:,jl) = z2d(:,:)
436         znam = 'sxysn'//'_htc'//zchar
437         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
438         sxysn(:,:,jl) = z2d(:,:)
439         znam = 'sxa'//'_htc'//zchar
440         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
441         sxa(:,:,jl) = z2d(:,:)
442         znam = 'sya'//'_htc'//zchar
443         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
444         sya(:,:,jl) = z2d(:,:)
445         znam = 'sxxa'//'_htc'//zchar
446         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
447         sxxa(:,:,jl) = z2d(:,:)
448         znam = 'syya'//'_htc'//zchar
449         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
450         syya(:,:,jl) = z2d(:,:)
451         znam = 'sxya'//'_htc'//zchar
452         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
453         sxya(:,:,jl) = z2d(:,:)
454         znam = 'sxc0'//'_htc'//zchar
455         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
456         sxc0(:,:,jl) = z2d(:,:)
457         znam = 'syc0'//'_htc'//zchar
458         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
459         syc0(:,:,jl) = z2d(:,:)
460         znam = 'sxxc0'//'_htc'//zchar
461         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
462         sxxc0(:,:,jl) = z2d(:,:)
463         znam = 'syyc0'//'_htc'//zchar
464         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
465         syyc0(:,:,jl) = z2d(:,:)
466         znam = 'sxyc0'//'_htc'//zchar
467         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
468         sxyc0(:,:,jl) = z2d(:,:)
469         znam = 'sxsal'//'_htc'//zchar
470         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
471         sxsal(:,:,jl) = z2d(:,:)
472         znam = 'sysal'//'_htc'//zchar
473         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
474         sysal(:,:,jl) = z2d(:,:)
475         znam = 'sxxsal'//'_htc'//zchar
476         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
477         sxxsal(:,:,jl) = z2d(:,:)
478         znam = 'syysal'//'_htc'//zchar
479         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
480         syysal(:,:,jl) = z2d(:,:)
481         znam = 'sxysal'//'_htc'//zchar
482         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
483         sxysal(:,:,jl) = z2d(:,:)
484         znam = 'sxage'//'_htc'//zchar
485         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
486         sxage(:,:,jl) = z2d(:,:)
487         znam = 'syage'//'_htc'//zchar
488         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
489         syage(:,:,jl) = z2d(:,:)
490         znam = 'sxxage'//'_htc'//zchar
491         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
492         sxxage(:,:,jl) = z2d(:,:)
493         znam = 'syyage'//'_htc'//zchar
494         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
495         syyage(:,:,jl) = z2d(:,:)
496         znam = 'sxyage'//'_htc'//zchar
497         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
498         sxyage(:,:,jl)= z2d(:,:)
499      END DO
500
501      CALL iom_get( numrir, jpdom_autoglo, 'sxopw ' ,  sxopw  )
502      CALL iom_get( numrir, jpdom_autoglo, 'syopw ' ,  syopw  )
503      CALL iom_get( numrir, jpdom_autoglo, 'sxxopw' ,  sxxopw )
504      CALL iom_get( numrir, jpdom_autoglo, 'syyopw' ,  syyopw )
505      CALL iom_get( numrir, jpdom_autoglo, 'sxyopw' ,  sxyopw )
506
507      DO jl = 1, jpl 
508         WRITE(zchar,'(I1)') jl
509         DO jk = 1, nlay_i 
510            WRITE(zchar1,'(I1)') jk
511            znam = 'sxe'//'_il'//zchar1//'_htc'//zchar
512            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
513            sxe(:,:,jk,jl) = z2d(:,:)
514            znam = 'sye'//'_il'//zchar1//'_htc'//zchar
515            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
516            sye(:,:,jk,jl) = z2d(:,:)
517            znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar
518            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
519            sxxe(:,:,jk,jl) = z2d(:,:)
520            znam = 'syye'//'_il'//zchar1//'_htc'//zchar
521            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
522            syye(:,:,jk,jl) = z2d(:,:)
523            znam = 'sxye'//'_il'//zchar1//'_htc'//zchar
524            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
525            sxye(:,:,jk,jl) = z2d(:,:)
526         END DO
527      END DO
528      !
529      ! clem: I do not understand why the following IF is needed
530      !       I suspect something inconsistent in the main code with option num_sal=1
531      IF( num_sal == 1 ) THEN
532         DO jl = 1, jpl 
533            sm_i(:,:,jl) = bulk_sal
534            DO jk = 1, nlay_i 
535               s_i(:,:,jk,jl) = bulk_sal
536            END DO
537         END DO
538      ENDIF
539      !
540      !CALL iom_close( numrir ) !clem: closed in sbcice_lim.F90
541      !
542      CALL wrk_dealloc( nlay_i, zs_zero )
543      CALL wrk_dealloc( jpi, jpj, z2d )
544      !
545   END SUBROUTINE lim_rst_read
546
547#else
548   !!----------------------------------------------------------------------
549   !!   Default option :       Empty module            NO LIM sea-ice model
550   !!----------------------------------------------------------------------
551CONTAINS
552   SUBROUTINE lim_rst_read             ! Empty routine
553   END SUBROUTINE lim_rst_read
554   SUBROUTINE lim_rst_write            ! Empty routine
555   END SUBROUTINE lim_rst_write
556#endif
557
558   !!======================================================================
559END MODULE limrst
Note: See TracBrowser for help on using the repository browser.