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

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

First round of chnages for restart functionality branch (UKMO11).

These changes add namelist variables to allow the user to specify the directory to read input restart files and write output restart files for NEMO & LIM2/3.

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