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.
restart.F90 in trunk/NEMO/OPA_SRC – NEMO

source: trunk/NEMO/OPA_SRC/restart.F90 @ 359

Last change on this file since 359 was 359, checked in by opalod, 18 years ago

nemo_v1_update_033 : RB + CT : Add new surface pressure gradient algorithms

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 20.0 KB
Line 
1MODULE restart
2   !!======================================================================
3   !!                     ***  MODULE  restart  ***
4   !! Ocean restart :  write the ocean restart file
5   !!=====================================================================
6
7   !!----------------------------------------------------------------------
8   !!   rst_write  : write of the restart file
9   !!   rst_read   : read the restart file
10   !!----------------------------------------------------------------------
11   !! * Modules used
12   USE dom_oce         ! ocean space and time domain
13   USE oce             ! ocean dynamics and tracers
14   USE phycst          ! physical constants
15   USE in_out_manager  ! I/O manager
16   USE daymod          ! calendar
17   USE sol_oce         ! ocean elliptic solver
18   USE zdf_oce         ! ???
19   USE zdftke          ! turbulent kinetic energy scheme
20   USE ice_oce         ! ice variables
21   USE blk_oce         ! bulk variables
22   USE flx_oce         ! sea-ice/ocean forcings variables
23   USE dynspg          ! choice/control of key cpp for surface pressure gradient
24   USE dynspg_ts       ! free surface time splitting scheme variables
25   USE cpl_oce,         ONLY : lk_cpl              !
26
27   IMPLICIT NONE
28   PRIVATE
29
30   !! * Routine accessibility
31   PUBLIC rst_write  ! routine called by step.F90
32   PUBLIC rst_read   ! routine called by inidtr.F90
33
34   !! * Module variables
35   CHARACTER (len=48) ::   &
36      crestart = 'initial.nc'   ! restart file name
37   !!----------------------------------------------------------------------
38   !!  OPA 9.0 , LOCEAN-IPSL (2005)
39   !! $Header$
40   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
41   !!----------------------------------------------------------------------
42
43
44CONTAINS
45
46#if  ( defined key_mpp_mpi   ||   defined key_mpp_shmem ) && defined key_dimgout
47   !!----------------------------------------------------------------------
48   !!   'key_mpp_mpi'     OR      MPI massively parallel processing library
49   !!   'key_mpp_shmem'         SHMEM massively parallel processing library
50   !!                     AND
51   !!   'key_dimgout'         
52   !!----------------------------------------------------------------------
53   !!                 direct acces file one per processor
54   !!          (merging/splitting is done off-line, eventually)
55   !!-----------------------------------------------------------------------
56#  include "restart_dimg.h90"
57
58#else
59   !!----------------------------------------------------------------------
60   !!   Default option                                          NetCDF file
61   !!----------------------------------------------------------------------
62
63   SUBROUTINE rst_write( kt )
64      !!---------------------------------------------------------------------
65      !!                   ***  ROUTINE rstwrite  ***
66      !!                     
67      !! ** Purpose :   Write restart fields in NetCDF format
68      !!
69      !! ** Method  :   Write in numwrs file each nstock time step in NetCDF
70      !!      file, save fields which are necessary for restart
71      !!
72      !! History :
73      !!        !  99-11  (M. Imbard)  Original code
74      !!   8.5  !  02-08  (G. Madec)  F90: Free form
75      !!   9.0  !  05-11  (V. Garnier) Surface pressure gradient organization
76      !!----------------------------------------------------------------------
77      !! * Modules used
78      USE ioipsl
79
80      !! * Arguments
81      INTEGER, INTENT( in ) ::   kt         ! ocean time-step
82
83      !! * Local declarations
84      LOGICAL ::   llbon
85      CHARACTER (len=50) ::   clname, cln
86      INTEGER ::   ic, jc, itime
87      REAL(wp) ::   zdate0
88      REAL(wp), DIMENSION( 1) ::   zfice, zfblk   ! used only in case of ice & bulk
89      REAL(wp), DIMENSION(10) ::   zinfo(10)
90      REAL(wp), DIMENSION(jpi,jpj) :: ztab 
91      !!----------------------------------------------------------------------
92
93      IF( kt == nit000 ) THEN
94         IF(lwp) WRITE(numout,*)
95         IF(lwp) WRITE(numout,*) 'rst_wri : write restart.output NetCDF file'
96         IF(lwp) WRITE(numout,*) '~~~~~~~'
97         zfice(1) = 1.e0   ;   zfblk(1) = 1.e0
98      ENDIF
99
100
101      IF( MOD( kt, nstock ) == 0 .OR. kt == nitend ) THEN
102         
103         ! 0. Initializations
104         ! ------------------
105
106         IF(lwp) WRITE(numout,*) ' '
107         IF(lwp) WRITE(numout,*) 'rst_write : write the restart file in NetCDF format ',   &
108                                              'at it= ',kt,' date= ',ndastp
109         IF(lwp) WRITE(numout,*) '~~~~~~~~~'
110
111         ! Job informations
112         zinfo(1) = FLOAT( no        )   ! job number
113         zinfo(2) = FLOAT( kt        )   ! time-step
114         zinfo(3) = FLOAT( 2 - nsolv )   ! pcg solver
115         zinfo(4) = FLOAT( nsolv - 1 )   ! sor solver
116         IF( lk_zdftke ) THEN
117            zinfo(5) = 1.e0              ! TKE
118         ELSE
119            zinfo(5) = 0.e0              ! no TKE
120         ENDIF
121         zinfo(6) = FLOAT( ndastp )      ! date
122         zinfo(7) = adatrj               ! ???
123
124         ! delete the restart file if it exists
125         INQUIRE( FILE=crestart, EXIST=llbon )
126         IF(llbon) THEN
127            OPEN( UNIT=numwrs, FILE=crestart, STATUS='old' )
128            CLOSE( numwrs, STATUS='delete' )
129         ENDIF
130
131         ! Name of the new restart file
132         ic     = 1
133         DO jc = 1, 16
134            IF( cexper(jc:jc) /= ' ' )   ic = jc
135         END DO
136         WRITE(cln,'("_",i4.4,i2.2,i2.2,"_restart")') nyear, nmonth, nday
137         clname = cexper(1:ic)//cln
138         ic = 1
139         DO jc = 1, 48
140            IF( clname(jc:jc) /= ' ' ) ic = jc
141         END DO
142         crestart = clname(1:ic)//".nc"
143         itime = 0
144         CALL ymds2ju( nyear, nmonth, nday, 0.e0, zdate0 )
145         CALL restini( 'NONE', jpi, jpj, glamt, gphit, jpk, gdept, clname,   &
146                        itime, zdate0, rdt*nstock ,numwrs, domain_id=nidom )
147
148         CALL restput( numwrs, 'info'   , 1  , 1  , 10 , 0, zinfo   )   ! restart informations
149         
150         CALL restput( numwrs, 'ub'     , jpi, jpj, jpk, 0, ub      )   ! prognostic variables
151         CALL restput( numwrs, 'vb'     , jpi, jpj, jpk, 0, vb      )
152         CALL restput( numwrs, 'tb'     , jpi, jpj, jpk, 0, tb      )
153         CALL restput( numwrs, 'sb'     , jpi, jpj, jpk, 0, sb      )
154         CALL restput( numwrs, 'rotb'   , jpi, jpj, jpk, 0, rotb    )
155         CALL restput( numwrs, 'hdivb'  , jpi, jpj, jpk, 0, hdivb   )
156         CALL restput( numwrs, 'un'     , jpi, jpj, jpk, 0, un      )
157         CALL restput( numwrs, 'vn'     , jpi, jpj, jpk, 0, vn      )
158         CALL restput( numwrs, 'tn'     , jpi, jpj, jpk, 0, tn      )
159         CALL restput( numwrs, 'sn'     , jpi, jpj, jpk, 0, sn      )
160         CALL restput( numwrs, 'rotn'   , jpi, jpj, jpk, 0, rotn    )
161         CALL restput( numwrs, 'hdivn'  , jpi, jpj, jpk, 0, hdivn   )
162
163         ztab(:,:) = gcx(1:jpi,1:jpj)
164         CALL restput( numwrs, 'gcx'    , jpi, jpj, 1  , 0, ztab    )   ! Read elliptic solver arrays
165         ztab(:,:) = gcxb(1:jpi,1:jpj)
166         CALL restput( numwrs, 'gcxb'   , jpi, jpj, 1  , 0, ztab    )
167# if defined key_dynspg_rl
168         CALL restput( numwrs, 'bsfb'   , jpi, jpj, 1  , 0, bsfb    )   ! Rigid-lid formulation (bsf)
169         CALL restput( numwrs, 'bsfn'   , jpi, jpj, 1  , 0, bsfn    )
170         CALL restput( numwrs, 'bsfd'   , jpi, jpj, 1  , 0, bsfd    )
171# else
172         CALL restput( numwrs, 'sshb'   , jpi, jpj, 1  , 0, sshb    )   ! free surface formulation (ssh)
173         CALL restput( numwrs, 'sshn'   , jpi, jpj, 1  , 0, sshn    )
174#  if defined key_dynspg_ts
175         CALL restput( numwrs, 'sshb_b' , jpi, jpj, 1  , 0, sshb_b  )   ! free surface formulation (ssh)
176         CALL restput( numwrs, 'sshn_b' , jpi, jpj, 1  , 0, sshn_b  )   ! issued from barotropic loop
177         CALL restput( numwrs, 'un_b'   , jpi, jpj, 1  , 0, un_b    )   ! horizontal transports
178         CALL restput( numwrs, 'vn_b'   , jpi, jpj, 1  , 0, vn_b    )   ! issued from barotropic loop
179#  endif
180# endif
181# if defined key_zdftke   ||   defined key_esopa
182         IF( lk_zdftke ) THEN
183            CALL restput( numwrs, 'en'     , jpi, jpj, jpk, 0, en      )   ! TKE arrays
184         ENDIF
185# endif
186# if defined key_ice_lim
187         zfice(1) = FLOAT( nfice )                                      ! Louvain La Neuve Sea Ice Model
188         CALL restput( numwrs, 'nfice'  ,   1,   1, 1  , 0, zfice   )
189         CALL restput( numwrs, 'sst_io' , jpi, jpj, 1  , 0, sst_io  )
190         CALL restput( numwrs, 'sss_io' , jpi, jpj, 1  , 0, sss_io  )
191         CALL restput( numwrs, 'u_io'   , jpi, jpj, 1  , 0, u_io    )
192         CALL restput( numwrs, 'v_io'   , jpi, jpj, 1  , 0, v_io    )
193# if defined key_coupled
194         CALL restput( numwrs, 'alb_ice', jpi, jpj, 1  , 0, alb_ice )
195# endif
196# endif
197# if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
198         zfblk(1) = FLOAT( nfbulk )                                 ! Bulk
199         CALL restput( numwrs, 'nfbulk' ,   1,   1, 1  , 0, zfblk   )
200         CALL restput( numwrs, 'gsst'   , jpi, jpj, 1  , 0, gsst    )
201# endif
202
203         CALL restclo( numwrs )                                         ! close the restart file
204         
205      ENDIF
206
207   END SUBROUTINE rst_write
208
209
210   SUBROUTINE rst_read
211      !!----------------------------------------------------------------------
212      !!                   ***  ROUTINE rst_read  ***
213      !!
214      !! ** Purpose :   Read files for restart
215      !!
216      !! ** Method  :   Read the previous fields on the NetCDF file
217      !!      the first record indicates previous characterics
218      !!      after control with the present run, we read :
219      !!      - prognostic variables on the second record
220      !!      - elliptic solver arrays
221      !!      - barotropic stream function arrays ("key_dynspg_rl" defined)
222      !!        or free surface arrays
223      !!      - tke arrays (lk_zdftke=T)
224      !!      for this last three records,  the previous characteristics
225      !!      could be different with those used in the present run.
226      !!
227      !!   According to namelist parameter nrstdt,
228      !!       nrstdt = 0  no control on the date (nit000 is  arbitrary).
229      !!       nrstdt = 1  we verify that nit000 is equal to the last
230      !!                   time step of previous run + 1.
231      !!       In both those options, the  exact duration of the experiment
232      !!       since the beginning (cumulated duration of all previous restart runs)
233      !!       is not stored in the restart and is assumed to be (nit000-1)*rdt.
234      !!       This is valid is the time step has remained constant.
235      !!
236      !!       nrstdt = 2  the duration of the experiment in days (adatrj)
237      !!                    has been stored in the restart file.
238      !!
239      !! History :
240      !!        !  99-05  (M. Imbard)  Original code
241      !!   8.5  !  02-09  (G. Madec)  F90: Free form
242      !!   9.0  !  05-11  (V. Garnier) Surface pressure gradient organization
243      !!----------------------------------------------------------------------
244      !! * Modules used
245      USE ioipsl
246
247      !! * Local declarations
248      LOGICAL ::   llog
249      CHARACTER (len=8 ) ::   clvnames(50)
250      CHARACTER (len=32) ::   clname = 'restart'
251      INTEGER  ::   &
252         itime, ibvar,     &  !
253         inum                 ! temporary logical unit
254      REAL(wp) ::   zdate0, zdt, zinfo(10)
255      REAL(wp) ::   zdept(jpk), zlamt(jpi,jpj), zphit(jpi,jpj)
256      REAL(wp), DIMENSION(jpi,jpj) :: ztab 
257#   if defined key_ice_lim
258      INTEGER  ::   ios1, ji, jj, jn
259      REAL(wp) ::   zfice(1)
260#   endif
261# if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
262      INTEGER  ::   ios2, jk
263      REAL(wp) ::   zfblk(1)
264#   endif
265      !!----------------------------------------------------------------------
266      !!  OPA 8.5, LODYC-IPSL (2002)
267      !!----------------------------------------------------------------------
268
269      IF(lwp) WRITE(numout,*)
270      IF(lwp) WRITE(numout,*) 'rst_read : read the NetCDF restart file'
271      IF(lwp) WRITE(numout,*) '~~~~~~~~'
272
273      IF(lwp) WRITE(numout,*) ' Info on the present job : '
274      IF(lwp) WRITE(numout,*) '   job number          : ', no
275      IF(lwp) WRITE(numout,*) '   time-step           : ', nit000
276      IF(lwp) WRITE(numout,*) '   solver type         : ', nsolv
277      IF( lk_zdftke ) THEN
278         IF(lwp) WRITE(numout,*) '   tke option          : 1 '
279      ELSE
280         IF(lwp) WRITE(numout,*) '   tke option          : 0 '
281      ENDIF
282      IF(lwp) WRITE(numout,*) '   date ndastp         : ', ndastp
283      IF(lwp) WRITE(numout,*)
284
285      ! Time domain : restart
286      ! -------------------------
287
288      IF(lwp) WRITE(numout,*)
289      IF(lwp) WRITE(numout,*)
290      IF(lwp) WRITE(numout,*) ' *** restart option'
291      SELECT CASE ( nrstdt )
292      CASE ( 0 ) 
293         IF(lwp) WRITE(numout,*) ' nrstdt = 0 no control of nit000'
294      CASE ( 1 ) 
295         IF(lwp) WRITE(numout,*) ' nrstdt = 1 we control the date of nit000'
296      CASE ( 2 )
297         IF(lwp) WRITE(numout,*) ' nrstdt = 2 the date adatrj is read in restart file'
298      CASE DEFAULT
299         IF(lwp) WRITE(numout,*) '  ===>>>> nrstdt not equal 0, 1 or 2 : no control of the date'
300         IF(lwp) WRITE(numout,*) ' =======                   ========='
301      END SELECT
302
303      itime = 0
304      llog  = .FALSE.
305      zlamt(:,:) = 0.e0
306      zphit(:,:) = 0.e0
307      zdept(:)   = 0.e0
308      CALL restini( clname, jpi, jpj, zlamt, zphit, jpk, zdept, 'NONE',   &
309         &          itime, zdate0, zdt, inum, domain_id=nidom )
310
311      CALL ioget_vname( inum, ibvar, clvnames)
312      CALL restget( inum, 'info', 1, 1, 10, 0, llog, zinfo )
313
314      IF(lwp) WRITE(numout,*)
315      IF(lwp) WRITE(numout,*) ' Info on the restart file read : '
316      IF(lwp) WRITE(numout,*) '   FILE name           : ', clname
317      IF(lwp) WRITE(numout,*) '   job number          : ', NINT( zinfo(1) )
318      IF(lwp) WRITE(numout,*) '   time-step           : ', NINT( zinfo(2) )
319      IF(lwp) WRITE(numout,*) '   solver type         : ', NINT( zinfo(4) ) + 1
320      IF(lwp) WRITE(numout,*) '   tke option          : ', NINT( zinfo(5) )
321      IF(lwp) WRITE(numout,*) '   date ndastp         : ', NINT( zinfo(6) )
322      IF(lwp) WRITE(numout,*) '   number of variables : ', ibvar
323      IF(lwp) WRITE(numout,*) '   NetCDF variables    : ', clvnames(1:ibvar)
324      IF(lwp) WRITE(numout,*)
325
326      ! Control of date
327      IF( nit000 - NINT( zinfo(2) )  /= 1 .AND. nrstdt /= 0 ) THEN
328         IF(lwp) WRITE(numout,cform_err)
329         IF(lwp) WRITE(numout,*) ' ===>>>> : problem with nit000 for the restart'
330         IF(lwp) WRITE(numout,*) ' verify the restart file or rerun with nrstdt = 0 (namelist)'
331         nstop = nstop + 1
332      ENDIF
333
334      ! re-initialisation of  adatrj0
335      adatrj0 =  ( FLOAT( nit000-1 ) * rdttra(1) ) / rday
336
337      IF ( nrstdt == 2 ) THEN
338!                             by default ndatsp has been set to ndate0 in dom_nam
339!                             ndate0 has been read in the namelist (standard OPA 8)
340!                             here when nrstdt=2 we keep the  final date of previous run
341        ndastp = NINT( zinfo(6) )
342        adatrj0 =  zinfo(7)
343      ENDIF
344
345
346
347      CALL restget( inum, 'ub'     , jpi, jpj, jpk, 0, llog, ub      )    ! Read prognostic variables
348      CALL restget( inum, 'vb'     , jpi, jpj, jpk, 0, llog, vb      )
349      CALL restget( inum, 'tb'     , jpi, jpj, jpk, 0, llog, tb      )
350      CALL restget( inum, 'sb'     , jpi, jpj, jpk, 0, llog, sb      )
351      CALL restget( inum, 'rotb'   , jpi, jpj, jpk, 0, llog, rotb    )
352      CALL restget( inum, 'hdivb'  , jpi, jpj, jpk, 0, llog, hdivb   )
353      CALL restget( inum, 'un'     , jpi, jpj, jpk, 0, llog, un      )
354      CALL restget( inum, 'vn'     , jpi, jpj, jpk, 0, llog, vn      )
355      CALL restget( inum, 'tn'     , jpi, jpj, jpk, 0, llog, tn      )
356      CALL restget( inum, 'sn'     , jpi, jpj, jpk, 0, llog, sn      )
357      CALL restget( inum, 'rotn'   , jpi, jpj, jpk, 0, llog, rotn    )
358      CALL restget( inum, 'hdivn'  , jpi, jpj, jpk, 0, llog, hdivn   )
359
360      CALL restget( inum, 'gcxb'   , jpi, jpj, 1  , 0, llog, ztab    )   ! Read elliptic solver arrays
361      gcxb(1:jpi,1:jpj) = ztab(:,:) 
362      CALL restget( inum, 'gcx'    , jpi, jpj, 1  , 0, llog, ztab    )
363      gcx(1:jpi,1:jpj) = ztab(:,:) 
364# if defined key_dynspg_rl
365      CALL restget( inum, 'bsfb'   , jpi, jpj, 1  , 0, llog, bsfb    )   ! Rigid-lid formulation (bsf)
366      CALL restget( inum, 'bsfn'   , jpi, jpj, 1  , 0, llog, bsfn    )
367      CALL restget( inum, 'bsfd'   , jpi, jpj, 1  , 0, llog, bsfd    )
368# else
369      CALL restget( inum, 'sshb'   , jpi, jpj, 1  , 0, llog, sshb    )   ! free surface formulation (ssh)
370      CALL restget( inum, 'sshn'   , jpi, jpj, 1  , 0, llog, sshn    )
371#  if defined key_dynspg_ts
372      CALL restget( inum, 'sshb_b' , jpi, jpj, 1  , 0, llog, sshb_b  )   ! free surface formulation (ssh)
373      CALL restget( inum, 'sshn_b' , jpi, jpj, 1  , 0, llog, sshn_b  )   ! issued from barotropic loop
374      CALL restget( inum, 'un_b'   , jpi, jpj, 1  , 0, llog, un_b    )   ! horizontal transports
375      CALL restget( inum, 'vn_b'   , jpi, jpj, 1  , 0, llog, vn_b    )   ! issued from barotropic loop
376#  endif
377# endif
378# if defined key_zdftke   ||   defined key_esopa
379      IF( lk_zdftke ) THEN
380         IF( NINT( zinfo(5) ) == 1 ) THEN                                ! Read tke arrays
381            CALL restget( inum, 'en',jpi,jpj, jpk,0  , llog, en )
382            ln_rstke = .FALSE.
383         ELSE
384            IF(lwp) WRITE(numout,*) ' ===>>>> : the previous restart file didnot used  tke scheme'
385            IF(lwp) WRITE(numout,*) ' =======                ======='
386            nrstdt = 2
387            ln_rstke = .TRUE.
388         ENDIF
389      ENDIF
390# endif
391# if defined key_ice_lim
392      ! Louvain La Neuve Sea Ice Model
393      ios1 = 0
394      DO jn = 1, 30
395         IF( clvnames(jn) == 'nfice' )  ios1 = 1
396      END DO
397      IF( ios1 == 1 ) THEN
398         CALL restget( inum, 'nfice' ,   1,   1, 1 , 0, llog, zfice  )
399         CALL restget( inum, 'sst_io', jpi, jpj, 1 , 0, llog, sst_io )
400         CALL restget( inum, 'sss_io', jpi, jpj, 1 , 0, llog, sss_io )
401         CALL restget( inum, 'u_io'  , jpi, jpj, 1 , 0, llog, u_io   )
402         CALL restget( inum, 'v_io'  , jpi, jpj, 1 , 0, llog, v_io   )
403#if defined key_coupled
404         CALL restget( inum, 'alb_ice', jpi, jpj, 1 , 0, llog, alb_ice )
405#endif
406      ENDIF
407      IF( zfice(1) /= FLOAT(nfice) .OR. ios1 == 0 ) THEN
408         IF(lwp) WRITE(numout,*)
409         IF(lwp) WRITE(numout,*) 'rst_read :  LLN sea Ice Model => Ice initialization'
410         IF(lwp) WRITE(numout,*)
411         sst_io(:,:) = ( nfice-1 )*( tn(:,:,1) + rt0 )          !!bug a explanation is needed here!
412         sss_io(:,:) = ( nfice-1 )*  sn(:,:,1)
413         DO jj = 2, jpj
414            DO ji = 2, jpi
415               u_io(ji,jj) = ( nfice-1 ) * 0.5 * ( un(ji-1,jj  ,1) + un(ji-1,jj-1,1) )
416               v_io(ji,jj) = ( nfice-1 ) * 0.5 * ( vn(ji  ,jj-1,1) + vn(ji-1,jj-1,1) )
417            END DO
418         END DO
419#    if defined key_coupled
420         alb_ice(:,:) = 0.8 * tmask(:,:,1)
421#    endif
422      ENDIF
423# endif
424# if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
425      ! Louvain La Neuve Sea Ice Model
426      ios2 = 0
427      DO jk = 1, 30
428         IF( clvnames(jk) == 'nfbulk' )  ios2 = 1
429      END DO
430      IF( ios2 == 1 ) THEN
431         CALL restget( inum, 'nfbulk',   1,   1, 1 , 0, llog, zfblk )
432         CALL restget( inum, 'gsst'  , jpi, jpj, 1 , 0, llog, gsst  )
433      ENDIF
434      IF( zfblk(1) /= FLOAT(nfbulk) .OR. ios2 == 0 ) THEN
435         IF(lwp) WRITE(numout,*)
436         IF(lwp) WRITE(numout,*) 'rst_read :  LLN sea Ice Model => Ice initialization'
437         IF(lwp) WRITE(numout,*)
438         gsst(:,:) = 0.
439         gsst(:,:) = gsst(:,:) + ( nfbulk-1 )*( tn(:,:,1) + rt0 )
440      ENDIF
441# endif
442     
443      CALL restclo( inum )
444  ! In case of restart with neuler = 0 then put all before fields = to now fields
445    IF ( neuler == 0 ) THEN
446      tb(:,:,:)=tn(:,:,:)
447      sb(:,:,:)=sn(:,:,:)
448      ub(:,:,:)=un(:,:,:)
449      vb(:,:,:)=vn(:,:,:)
450      rotb(:,:,:)=rotn(:,:,:)
451      hdivb(:,:,:)=hdivn(:,:,:)
452#if defined key_dynspg_rl
453    ! rigid lid
454      bsfb(:,:)=bsfn(:,:)
455#else
456    ! free surface formulation (eta)
457      sshb(:,:)=sshn(:,:)
458#endif
459    ENDIF
460
461   END SUBROUTINE rst_read
462
463#endif
464   !!=====================================================================
465END MODULE restart
Note: See TracBrowser for help on using the repository browser.