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 trunk/NEMO/LIM_SRC – NEMO

source: trunk/NEMO/LIM_SRC/limrst.F90 @ 3

Last change on this file since 3 was 3, checked in by opalod, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 11.4 KB
Line 
1MODULE limrst
2   !!======================================================================
3   !!                     ***  MODULE  limrst  ***
4   !! Ice restart :  write the ice restart file
5   !!======================================================================
6#if defined key_ice_lim
7   !!----------------------------------------------------------------------
8   !!   'key_ice_lim' :                                   LIM sea-ice model
9   !!----------------------------------------------------------------------
10   !!   lim_rst_write   : write of the restart file
11   !!   lim_rst_read    : read  the restart file
12   !!----------------------------------------------------------------------
13   !! * Modules used
14   USE in_out_manager
15   USE ice
16   USE ioipsl
17   USE dom_oce
18   USE ice_oce         ! ice variables
19   USE daymod
20
21   IMPLICIT NONE
22   PRIVATE
23
24   !! * Accessibility
25   PUBLIC lim_rst_write  ! routine called by lim_step.F90
26   PUBLIC lim_rst_read   ! routine called by lim_init.F90
27
28   !!----------------------------------------------------------------------
29   !!   LIM 2.0 , UCL-LODYC-IPSL  (2003)
30   !!----------------------------------------------------------------------
31
32CONTAINS
33
34# if defined key_fdir
35   !!----------------------------------------------------------------------
36   !!   'key_fdir' :                                     direct access file
37   !!----------------------------------------------------------------------
38#  include "limrst_fdir.h90"
39
40# else
41   !!----------------------------------------------------------------------
42   !!   Default option                                          NetCDF file
43   !!----------------------------------------------------------------------
44
45   SUBROUTINE lim_rst_write( niter )
46      !!----------------------------------------------------------------------
47      !!                    ***  lim_rst_write  ***
48      !!
49      !! ** purpose  :   output of sea-ice variable in a netcdf file
50      !!
51      !!----------------------------------------------------------------------
52      ! Arguments
53      INTEGER  ::    niter        ! number of iteration
54
55      !- dummy variables :
56      LOGICAL :: &
57         llbon
58      INTEGER :: &
59         ji, jj
60      INTEGER :: &
61         inumwrs, it0, itime
62      REAL(wp), DIMENSION(1) :: &
63         zdept
64      REAL(wp), DIMENSION(2) :: &
65         zinfo
66      REAL(wp),DIMENSION(jpi,jpj,35) :: &
67         zmoment
68      REAL(wp) :: &
69         zsec, zdate0, zdt
70
71      CHARACTER(len=45)  ::  &
72         ccfile = 'restart_ice_out.nc'
73
74      inumwrs  = 61
75      INQUIRE ( FILE = ccfile, EXIST = llbon )
76      IF( llbon ) THEN
77         OPEN ( UNIT = inumwrs , FILE = ccfile, STATUS = 'old' )
78         CLOSE( inumwrs , STATUS = 'delete' )
79      ENDIF
80
81
82      it0      = niter
83      zinfo(1) = FLOAT( nfice  )  ! coupling frequency OPA ICELLN  nfice
84      zinfo(2) = FLOAT( it0   )   ! iteration number
85
86      zsec     = 0.
87      itime    = 0
88      zdept(1) = 0.
89      zdt      = rdt_ice * nstock
90
91      ! Write in inumwrs
92
93      DO jj = 1, jpj              ! 3D array: 10 time faster than 35 restput
94         DO ji = 1, jpi
95            zmoment(ji,jj,1)  = sxice(ji,jj)
96            zmoment(ji,jj,2)  = syice(ji,jj)
97            zmoment(ji,jj,3)  = sxxice(ji,jj)
98            zmoment(ji,jj,4)  = syyice(ji,jj)
99            zmoment(ji,jj,5)  = sxyice(ji,jj)
100            zmoment(ji,jj,6)  = sxsn(ji,jj)
101            zmoment(ji,jj,7)  = sysn(ji,jj)
102            zmoment(ji,jj,8)  = sxxsn(ji,jj)
103            zmoment(ji,jj,9)  = syysn(ji,jj)
104            zmoment(ji,jj,10) = sxysn(ji,jj)
105            zmoment(ji,jj,11) = sxa(ji,jj)
106            zmoment(ji,jj,12) = sya(ji,jj)
107            zmoment(ji,jj,13) = sxxa(ji,jj)
108            zmoment(ji,jj,14) = syya(ji,jj)
109            zmoment(ji,jj,15) = sxya(ji,jj)
110            zmoment(ji,jj,16) = sxc0(ji,jj)
111            zmoment(ji,jj,17) = syc0(ji,jj)
112            zmoment(ji,jj,18) = sxxc0(ji,jj)
113            zmoment(ji,jj,19) = syyc0(ji,jj)
114            zmoment(ji,jj,20) = sxyc0(ji,jj)
115            zmoment(ji,jj,21) = sxc1(ji,jj)
116            zmoment(ji,jj,22) = syc1(ji,jj)
117            zmoment(ji,jj,23) = sxxc1(ji,jj)
118            zmoment(ji,jj,24) = syyc1(ji,jj)
119            zmoment(ji,jj,25) = sxyc1(ji,jj)
120            zmoment(ji,jj,26) = sxc2(ji,jj)
121            zmoment(ji,jj,27) = syc2(ji,jj)
122            zmoment(ji,jj,28) = sxxc2(ji,jj)
123            zmoment(ji,jj,29) = syyc2(ji,jj)
124            zmoment(ji,jj,30) = sxyc2(ji,jj)
125            zmoment(ji,jj,31) = sxst(ji,jj)
126            zmoment(ji,jj,32) = syst(ji,jj)
127            zmoment(ji,jj,33) = sxxst(ji,jj)
128            zmoment(ji,jj,34) = syyst(ji,jj)
129            zmoment(ji,jj,35) = sxyst(ji,jj)
130         END DO
131      END DO
132
133      CALL ymds2ju( nyear, nmonth, nday, zsec, zdate0 )
134      CALL restini( 'NONE', jpi, jpj, glamt, gphit, 1 , zdept, ccfile, itime, zdate0, zdt, inumwrs )
135     
136      CALL restput( inumwrs, 'info'   ,   1,   1, 2 , 0, zinfo   )  ! restart informations
137       
138      CALL restput( inumwrs, 'hicif'  , jpi, jpj, 1 , 0, hicif   )  ! prognostic variables
139      CALL restput( inumwrs, 'hsnif'  , jpi, jpj, 1 , 0, hsnif   )
140      CALL restput( inumwrs, 'frld'   , jpi, jpj, 1 , 0, frld    )
141      CALL restput( inumwrs, 'sist'   , jpi, jpj, 1 , 0, sist    )
142# if defined key_coupled
143      CALL restput( inumwrs, 'albege' , jpi, jpj, 1 , 0, albege  )
144# endif
145      CALL restput( inumwrs, 'tbif'   , jpi, jpj, 3 , 0, tbif    )
146      CALL restput( inumwrs, 'u_ice'  , jpi, jpj, 1 , 0, u_ice   )
147      CALL restput( inumwrs, 'v_ice'  , jpi, jpj, 1 , 0, v_ice   )
148      CALL restput( inumwrs, 'gtaux'  , jpi, jpj, 1 , 0, gtaux  )
149      CALL restput( inumwrs, 'gtauy'  , jpi, jpj, 1 , 0, gtauy  )
150      CALL restput( inumwrs, 'qstoif' , jpi, jpj, 1 , 0, qstoif  )
151      CALL restput( inumwrs, 'fsbbq'  , jpi, jpj, 1 , 0, fsbbq   )
152      CALL restput( inumwrs, 'moment' , jpi, jpj, 35, 0, zmoment )
153
154     
155      CALL restclo( inumwrs )
156
157   END SUBROUTINE lim_rst_write
158
159
160   SUBROUTINE lim_rst_read( niter )
161      !-----------------------------------------------------------------------
162      !  restart from a state defined in a binary file
163      !-----------------------------------------------------------------------
164      ! Arguments
165      INTEGER  ::   niter        ! number of iteration
166
167      !- dummy variables :
168      CHARACTER(len=45)  ::  &
169         ccfile = 'restart_ice_in.nc'
170      INTEGER :: &
171        ji, jj
172      INTEGER :: &
173         inumrst, it0, it1, itime, ibvar, ifice
174      LOGICAL :: &
175         llbon, llog
176      REAL(wp),DIMENSION(jpi,jpj) :: &
177         zlamt, zphit
178      REAL(wp),DIMENSION(jpi,jpj,35) :: &
179         zmoment
180      REAL(wp),DIMENSION(1) :: &
181         zdept
182      REAL(wp),DIMENSION(2) :: &
183         zinfo
184      REAL(wp) :: &
185         zdate0, zdt
186      CHARACTER ( len = 10 ) ::  &
187         clvnames(60)       
188
189      !Read inumrst
190      INQUIRE ( FILE = ccfile , EXIST = llbon)
191      IF( .NOT. llbon ) THEN
192         IF(lwp)WRITE(numout,cform_err)
193         IF(lwp)WRITE(numout,*) 'lim_rst_read : ===>>>> : Le fichier restart ',ccfile,' n''existe pas'
194         nstop = nstop + 1
195      ENDIF
196
197      !Initialisations
198      inumrst    = 71
199      it0        = nit000
200      itime      = 0
201      llog       = .FALSE.
202      zlamt(:,:) = 0.
203      zphit(:,:) = 0.
204      zdept(1)   = 0.
205
206      CALL restini(ccfile , jpi, jpj, zlamt, zphit, 1 , zdept, ccfile, itime, zdate0, zdt, inumrst )     
207      CALL ioget_vname( inumrst, ibvar, clvnames )
208
209      CALL restget    ( inumrst,'info', 1, 1 , 2, 0, llog, zinfo )
210 
211      ifice   = INT( zinfo(1) )
212      it1     = INT( zinfo(2) )
213
214      IF(lwp) THEN
215         WRITE(numout,*)
216         WRITE(numout,*) 'lim_rst_read : READ restart file name ', ccfile,' at time step : ', it1
217         WRITE(numout,*) '~~~~~~~~~~~~   number of variables   : ', ibvar
218         WRITE(numout,*) '               NetCDF variables      : ', clvnames(1:ibvar)
219      ENDIF
220
221     
222      !Control of date
223     
224      IF( ( it0 - it1 ) /= 1 .AND. ABS( nrstdt ) == 1 ) THEN
225         IF(lwp) THEN
226            WRITE(numout,cform_err)
227            WRITE(numout,*) 'lim_rst_read ===>>>> : problem with nit000 for the restart'
228            WRITE(numout,*) '   we stop. verify the file or rerun with the value  0 for the'
229            WRITE(numout,*) '   control of time parameter  nrstdt'
230            nstop = nstop + 1
231         ENDIF
232      ENDIF
233
234      CALL restget( inumrst, 'hicif'  , jpi, jpj, 1 , 0, llog, hicif   )
235      CALL restget( inumrst, 'hsnif'  , jpi, jpj, 1 , 0, llog, hsnif   )
236      CALL restget( inumrst, 'frld'   , jpi, jpj, 1 , 0, llog, frld    )
237      CALL restget( inumrst, 'sist'   , jpi, jpj, 1 , 0, llog, sist    )
238# if defined key_coupled 
239      CALL restget( inumrst, 'albege' , jpi, jpj, 1 , 0, llog, albege  )
240# endif
241      CALL restget( inumrst, 'tbif'   , jpi, jpj, 3 , 0, llog, tbif    )
242      CALL restget( inumrst, 'u_ice'  , jpi, jpj, 1 , 0, llog, u_ice   )
243      CALL restget( inumrst, 'v_ice'  , jpi, jpj, 1 , 0, llog, v_ice   )
244      CALL restget( inumrst, 'gtaux'  , jpi, jpj, 1 , 0, llog, gtaux  )
245      CALL restget( inumrst, 'gtauy'  , jpi, jpj, 1 , 0, llog, gtauy  )
246      CALL restget( inumrst, 'qstoif' , jpi, jpj, 1 , 0, llog, qstoif  )
247      CALL restget( inumrst, 'fsbbq'  , jpi, jpj, 1 , 0, llog, fsbbq   )
248      CALL restget( inumrst, 'moment' , jpi, jpj, 35, 0, llog, zmoment )
249
250      CALL restclo( inumrst )
251
252      niter = it1
253      DO jj = 1, jpj
254         DO ji = 1, jpi
255            sxice(ji,jj)  = zmoment(ji,jj,1)
256            syice(ji,jj)  = zmoment(ji,jj,2)
257            sxxice(ji,jj) = zmoment(ji,jj,3)
258            syyice(ji,jj) = zmoment(ji,jj,4)
259            sxyice(ji,jj) = zmoment(ji,jj,5)
260            sxsn(ji,jj)   = zmoment(ji,jj,6)
261            sysn(ji,jj)   = zmoment(ji,jj,7)
262            sxxsn(ji,jj)  = zmoment(ji,jj,8)
263            syysn(ji,jj)  = zmoment(ji,jj,9)
264            sxysn(ji,jj)  = zmoment(ji,jj,10)
265            sxa(ji,jj)    = zmoment(ji,jj,11)
266            sya(ji,jj)    = zmoment(ji,jj,12)
267            sxxa(ji,jj)   = zmoment(ji,jj,13)
268            syya(ji,jj)   = zmoment(ji,jj,14)
269            sxya(ji,jj)   = zmoment(ji,jj,15)
270            sxc0(ji,jj)   = zmoment(ji,jj,16)
271            syc0(ji,jj)   = zmoment(ji,jj,17)
272            sxxc0(ji,jj)  = zmoment(ji,jj,18)
273            syyc0(ji,jj)  = zmoment(ji,jj,19)
274            sxyc0(ji,jj)  = zmoment(ji,jj,20)
275            sxc1(ji,jj)   = zmoment(ji,jj,21)
276            syc1(ji,jj)   = zmoment(ji,jj,22)
277            sxxc1(ji,jj)  = zmoment(ji,jj,23)
278            syyc1(ji,jj)  = zmoment(ji,jj,24)
279            sxyc1(ji,jj)  = zmoment(ji,jj,25)
280            sxc2(ji,jj)   = zmoment(ji,jj,26)
281            syc2(ji,jj)   = zmoment(ji,jj,27)
282            sxxc2(ji,jj)  = zmoment(ji,jj,28)
283            syyc2(ji,jj)  = zmoment(ji,jj,29)
284            sxyc2(ji,jj)  = zmoment(ji,jj,30)
285            sxst(ji,jj)   = zmoment(ji,jj,31)
286            syst(ji,jj)   = zmoment(ji,jj,32)
287            sxxst(ji,jj)  = zmoment(ji,jj,33)
288            syyst(ji,jj)  = zmoment(ji,jj,34)
289            sxyst(ji,jj)  = zmoment(ji,jj,35)
290         END DO
291      END DO
292
293     
294   END SUBROUTINE lim_rst_read
295
296# endif
297
298#else
299   !!----------------------------------------------------------------------
300   !!   Default option :       Empty module            NO LIM sea-ice model
301   !!----------------------------------------------------------------------
302CONTAINS
303   SUBROUTINE lim_rst_read             ! Empty routine
304   END SUBROUTINE lim_rst_read
305   SUBROUTINE lim_rst_write            ! Empty routine
306   END SUBROUTINE lim_rst_write
307#endif
308
309   !!======================================================================
310END MODULE limrst
Note: See TracBrowser for help on using the repository browser.