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

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

CT : UPDATE068 : Add binary output possibilities with the dimg output format

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