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/2012/dev_r3452_UKMO9_RESTART/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2012/dev_r3452_UKMO9_RESTART/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90 @ 3594

Last change on this file since 3594 was 3594, checked in by rfurner, 11 years ago

code not tested through SETTEE, builds and runs, but has not been thoroughly tested, so will not be included in 2012 merge, however submitted back to keep record of work done for 2013 developments

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