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 tags/nemo_v3_2_2/NEMO/LIM_SRC_3 – NEMO

source: tags/nemo_v3_2_2/NEMO/LIM_SRC_3/limrst.F90 @ 3532

Last change on this file since 3532 was 2477, checked in by cetlod, 13 years ago

v3.2:remove hardcoded value of num_sal in limrst.F90, see ticket #633

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