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

Last change on this file since 311 was 311, checked in by opalod, 19 years ago

nemo_v1_update_017:RB: added extra outer halo (parameters jpr2di and jpr2dj) and the corresponding lbc_lnk_e for boundary conditions.It will be use for nsolv=4.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 19.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
24   USE dynspg_fsc,      ONLY : lk_dynspg_fsc       ! ( mpp version )
25   USE dynspg_fsc_atsk, ONLY : lk_dynspg_fsc_tsk   !
26   USE cpl_oce,         ONLY : lk_cpl              !
27
28   IMPLICIT NONE
29   PRIVATE
30
31   !! * Routine accessibility
32   PUBLIC rst_write  ! routine called by step.F90
33   PUBLIC rst_read   ! routine called by inidtr.F90
34
35   !! * Module variables
36   CHARACTER (len=48) ::   &
37      crestart = 'initial.nc'   ! restart file name
38   !!----------------------------------------------------------------------
39
40CONTAINS
41
42#if  ( defined key_mpp_mpi   ||   defined key_mpp_shmem ) && defined key_dimgout
43   !!----------------------------------------------------------------------
44   !!   'key_mpp_mpi'     OR      MPI massively parallel processing library
45   !!   'key_mpp_shmem'         SHMEM massively parallel processing library
46   !!                     AND
47   !!   'key_dimgout'         
48   !!----------------------------------------------------------------------
49   !!                 direct acces file one per processor
50   !!          (merging/splitting is done off-line, eventually)
51   !!-----------------------------------------------------------------------
52#  include "restart_dimg.h90"
53
54#else
55   !!----------------------------------------------------------------------
56   !!   Default option                                          NetCDF file
57   !!----------------------------------------------------------------------
58
59   SUBROUTINE rst_write( kt )
60      !!---------------------------------------------------------------------
61      !!                   ***  ROUTINE rstwrite  ***
62      !!                     
63      !! ** Purpose :   Write restart fields in NetCDF format
64      !!
65      !! ** Method  :   Write in numwrs file each nstock time step in NetCDF
66      !!      file, save fields which are necessary for restart
67      !!
68      !! History :
69      !!        !  99-11  (M. Imbard)  Original code
70      !!   8.5  !  02-08  (G. Madec)  F90: Free form
71      !!----------------------------------------------------------------------
72      !! * Modules used
73      USE ioipsl
74
75      !! * Arguments
76      INTEGER, INTENT( in ) ::   kt         ! ocean time-step
77
78      !! * Local declarations
79      LOGICAL ::   llbon
80      CHARACTER (len=50) ::   clname, cln
81      INTEGER ::   ic, jc, itime
82      REAL(wp) ::   zdate0
83      REAL(wp), DIMENSION( 1) ::   zfice, zfblk   ! used only in case of ice & bulk
84      REAL(wp), DIMENSION(10) ::   zinfo(10)
85      REAL(wp), DIMENSION(jpi,jpj) :: ztab 
86      !!----------------------------------------------------------------------
87      !!  OPA 9.0 , LOCEAN-IPSL (2005)
88      !! $Header$
89      !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
90      !!----------------------------------------------------------------------
91
92      IF( kt == nit000 ) THEN
93         IF(lwp) WRITE(numout,*)
94         IF(lwp) WRITE(numout,*) 'rst_wri : write restart.output NetCDF file'
95         IF(lwp) WRITE(numout,*) '~~~~~~~'
96         zfice(1) = 1.e0   ;   zfblk(1) = 1.e0
97      ENDIF
98
99
100      IF( MOD( kt, nstock ) == 0 .OR. kt == nitend ) THEN
101         
102         ! 0. Initializations
103         ! ------------------
104
105         IF(lwp) WRITE(numout,*) ' '
106         IF(lwp) WRITE(numout,*) 'rst_write : write the restart file in NetCDF format ',   &
107                                              'at it= ',kt,' date= ',ndastp
108         IF(lwp) WRITE(numout,*) '~~~~~~~~~'
109
110         ! Job informations
111         zinfo(1) = FLOAT( no        )   ! job number
112         zinfo(2) = FLOAT( kt        )   ! time-step
113         zinfo(3) = FLOAT( 2 - nsolv )   ! pcg solver
114         zinfo(4) = FLOAT( nsolv - 1 )   ! sor solver
115         IF( lk_zdftke ) THEN
116            zinfo(5) = 1.e0              ! TKE
117         ELSE
118            zinfo(5) = 0.e0              ! no TKE
119         ENDIF
120         zinfo(6) = FLOAT( ndastp )      ! date
121         zinfo(7) = adatrj               ! ???
122
123         ! delete the restart file if it exists
124         INQUIRE( FILE=crestart, EXIST=llbon )
125         IF(llbon) THEN
126            OPEN( UNIT=numwrs, FILE=crestart, STATUS='old' )
127            CLOSE( numwrs, STATUS='delete' )
128         ENDIF
129
130         ! Name of the new restart file
131         ic     = 1
132         DO jc = 1, 16
133            IF( cexper(jc:jc) /= ' ' )   ic = jc
134         END DO
135         WRITE(cln,'("_",i4.4,i2.2,i2.2,"_restart")') nyear, nmonth, nday
136         clname = cexper(1:ic)//cln
137         ic = 1
138         DO jc = 1, 48
139            IF( clname(jc:jc) /= ' ' ) ic = jc
140         END DO
141         crestart = clname(1:ic)//".nc"
142         itime = 0
143         CALL ymds2ju( nyear, nmonth, nday, 0.e0, zdate0 )
144         CALL restini( 'NONE', jpi, jpj, glamt, gphit, jpk, gdept, clname,   &
145                        itime, zdate0, rdt*nstock ,numwrs )
146
147         CALL restput( numwrs, 'info'   , 1  , 1  , 10 , 0, zinfo   )   ! restart informations
148         
149         CALL restput( numwrs, 'ub'     , jpi, jpj, jpk, 0, ub      )   ! prognostic variables
150         CALL restput( numwrs, 'vb'     , jpi, jpj, jpk, 0, vb      )
151         CALL restput( numwrs, 'tb'     , jpi, jpj, jpk, 0, tb      )
152         CALL restput( numwrs, 'sb'     , jpi, jpj, jpk, 0, sb      )
153         CALL restput( numwrs, 'rotb'   , jpi, jpj, jpk, 0, rotb    )
154         CALL restput( numwrs, 'hdivb'  , jpi, jpj, jpk, 0, hdivb   )
155         CALL restput( numwrs, 'un'     , jpi, jpj, jpk, 0, un      )
156         CALL restput( numwrs, 'vn'     , jpi, jpj, jpk, 0, vn      )
157         CALL restput( numwrs, 'tn'     , jpi, jpj, jpk, 0, tn      )
158         CALL restput( numwrs, 'sn'     , jpi, jpj, jpk, 0, sn      )
159         CALL restput( numwrs, 'rotn'   , jpi, jpj, jpk, 0, rotn    )
160         CALL restput( numwrs, 'hdivn'  , jpi, jpj, jpk, 0, hdivn   )
161
162         ztab(:,:) = gcx(1:jpi,1:jpj)
163         CALL restput( numwrs, 'gcx'    , jpi, jpj, 1  , 0, ztab    )   ! Read elliptic solver arrays
164         ztab(:,:) = gcxb(1:jpi,1:jpj)
165         CALL restput( numwrs, 'gcxb'   , jpi, jpj, 1  , 0, ztab    )
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      REAL(wp), DIMENSION(jpi,jpj) :: ztab 
249#   if defined key_ice_lim
250      INTEGER  ::   ios1, ji, jj, jn
251      REAL(wp) ::   zfice(1)
252#   endif
253# if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
254      INTEGER  ::   ios2, jk
255      REAL(wp) ::   zfblk(1)
256#   endif
257      !!----------------------------------------------------------------------
258      !!  OPA 8.5, LODYC-IPSL (2002)
259      !!----------------------------------------------------------------------
260
261      IF(lwp) WRITE(numout,*)
262      IF(lwp) WRITE(numout,*) 'rst_read : read the NetCDF restart file'
263      IF(lwp) WRITE(numout,*) '~~~~~~~~'
264
265      IF(lwp) WRITE(numout,*) ' Info on the present job : '
266      IF(lwp) WRITE(numout,*) '   job number          : ', no
267      IF(lwp) WRITE(numout,*) '   time-step           : ', nit000
268      IF(lwp) WRITE(numout,*) '   solver type         : ', nsolv
269      IF( lk_zdftke ) THEN
270         IF(lwp) WRITE(numout,*) '   tke option          : 1 '
271      ELSE
272         IF(lwp) WRITE(numout,*) '   tke option          : 0 '
273      ENDIF
274      IF(lwp) WRITE(numout,*) '   date ndastp         : ', ndastp
275      IF(lwp) WRITE(numout,*)
276
277      ! Time domain : restart
278      ! -------------------------
279
280      IF(lwp) WRITE(numout,*)
281      IF(lwp) WRITE(numout,*)
282      IF(lwp) WRITE(numout,*) ' *** restart option'
283      SELECT CASE ( nrstdt )
284      CASE ( 0 ) 
285         IF(lwp) WRITE(numout,*) ' nrstdt = 0 no control of nit000'
286      CASE ( 1 ) 
287         IF(lwp) WRITE(numout,*) ' nrstdt = 1 we control the date of nit000'
288      CASE ( 2 )
289         IF(lwp) WRITE(numout,*) ' nrstdt = 2 the date adatrj is read in restart file'
290      CASE DEFAULT
291         IF(lwp) WRITE(numout,*) '  ===>>>> nrstdt not equal 0, 1 or 2 : no control of the date'
292         IF(lwp) WRITE(numout,*) ' =======                   ========='
293      END SELECT
294
295      itime = 0
296      llog  = .FALSE.
297      zlamt(:,:) = 0.e0
298      zphit(:,:) = 0.e0
299      zdept(:)   = 0.e0
300      CALL restini( clname, jpi, jpj, zlamt, zphit, jpk, zdept, clname,   &
301         &          itime, zdate0, zdt, inum )
302
303      CALL ioget_vname( inum, ibvar, clvnames)
304      CALL restget( inum, 'info', 1, 1, 10, 0, llog, zinfo )
305
306      IF(lwp) WRITE(numout,*)
307      IF(lwp) WRITE(numout,*) ' Info on the restart file read : '
308      IF(lwp) WRITE(numout,*) '   FILE name           : ', clname
309      IF(lwp) WRITE(numout,*) '   job number          : ', NINT( zinfo(1) )
310      IF(lwp) WRITE(numout,*) '   time-step           : ', NINT( zinfo(2) )
311      IF(lwp) WRITE(numout,*) '   solver type         : ', NINT( zinfo(4) ) + 1
312      IF(lwp) WRITE(numout,*) '   tke option          : ', NINT( zinfo(5) )
313      IF(lwp) WRITE(numout,*) '   date ndastp         : ', NINT( zinfo(6) )
314      IF(lwp) WRITE(numout,*) '   number of variables : ', ibvar
315      IF(lwp) WRITE(numout,*) '   NetCDF variables    : ', clvnames(1:ibvar)
316      IF(lwp) WRITE(numout,*)
317
318      ! Control of date
319      IF( nit000 - NINT( zinfo(2) )  /= 1 .AND. nrstdt /= 0 ) THEN
320         IF(lwp) WRITE(numout,cform_err)
321         IF(lwp) WRITE(numout,*) ' ===>>>> : problem with nit000 for the restart'
322         IF(lwp) WRITE(numout,*) ' verify the restart file or rerun with nrstdt = 0 (namelist)'
323         nstop = nstop + 1
324      ENDIF
325
326      ! re-initialisation of  adatrj0
327      adatrj0 =  ( FLOAT( nit000-1 ) * rdttra(1) ) / rday
328
329      IF ( nrstdt == 2 ) THEN
330!                             by default ndatsp has been set to ndate0 in dom_nam
331!                             ndate0 has been read in the namelist (standard OPA 8)
332!                             here when nrstdt=2 we keep the  final date of previous run
333        ndastp = NINT( zinfo(6) )
334        adatrj0 =  zinfo(7)
335      ENDIF
336
337
338
339      CALL restget( inum, 'ub'     , jpi, jpj, jpk, 0, llog, ub      )    ! Read prognostic variables
340      CALL restget( inum, 'vb'     , jpi, jpj, jpk, 0, llog, vb      )
341      CALL restget( inum, 'tb'     , jpi, jpj, jpk, 0, llog, tb      )
342      CALL restget( inum, 'sb'     , jpi, jpj, jpk, 0, llog, sb      )
343      CALL restget( inum, 'rotb'   , jpi, jpj, jpk, 0, llog, rotb    )
344      CALL restget( inum, 'hdivb'  , jpi, jpj, jpk, 0, llog, hdivb   )
345      CALL restget( inum, 'un'     , jpi, jpj, jpk, 0, llog, un      )
346      CALL restget( inum, 'vn'     , jpi, jpj, jpk, 0, llog, vn      )
347      CALL restget( inum, 'tn'     , jpi, jpj, jpk, 0, llog, tn      )
348      CALL restget( inum, 'sn'     , jpi, jpj, jpk, 0, llog, sn      )
349      CALL restget( inum, 'rotn'   , jpi, jpj, jpk, 0, llog, rotn    )
350      CALL restget( inum, 'hdivn'  , jpi, jpj, jpk, 0, llog, hdivn   )
351
352      CALL restget( inum, 'gcxb'   , jpi, jpj, 1  , 0, llog, ztab    )   ! Read elliptic solver arrays
353      gcxb(1:jpi,1:jpj) = ztab(:,:) 
354      CALL restget( inum, 'gcx'    , jpi, jpj, 1  , 0, llog, ztab    )
355      gcx(1:jpi,1:jpj) = ztab(:,:) 
356# if defined key_dynspg_fsc
357      CALL restget( inum, 'sshb'   , jpi, jpj, 1  , 0, llog, sshb    )   ! free surface formulation (ssh)
358      CALL restget( inum, 'sshn'   , jpi, jpj, 1  , 0, llog, sshn    )
359# else
360      CALL restget( inum, 'bsfb'   , jpi, jpj, 1  , 0, llog, bsfb    )   ! Rigid-lid formulation (bsf)
361      CALL restget( inum, 'bsfn'   , jpi, jpj, 1  , 0, llog, bsfn    )
362      CALL restget( inum, 'bsfd'   , jpi, jpj, 1  , 0, llog, bsfd    )
363# endif
364# if defined key_zdftke   ||   defined key_esopa
365      IF( lk_zdftke ) THEN
366         IF( NINT( zinfo(5) ) == 1 ) THEN                                ! Read tke arrays
367            CALL restget( inum, 'en',jpi,jpj, jpk,0  , llog, en )
368            ln_rstke = .FALSE.
369         ELSE
370            IF(lwp) WRITE(numout,*) ' ===>>>> : the previous restart file didnot used  tke scheme'
371            IF(lwp) WRITE(numout,*) ' =======                ======='
372            nrstdt = 2
373            ln_rstke = .TRUE.
374         ENDIF
375      ENDIF
376# endif
377# if defined key_ice_lim
378      ! Louvain La Neuve Sea Ice Model
379      ios1 = 0
380      DO jn = 1, 30
381         IF( clvnames(jn) == 'nfice' )  ios1 = 1
382      END DO
383      IF( ios1 == 1 ) THEN
384         CALL restget( inum, 'nfice' ,   1,   1, 1 , 0, llog, zfice  )
385         CALL restget( inum, 'sst_io', jpi, jpj, 1 , 0, llog, sst_io )
386         CALL restget( inum, 'sss_io', jpi, jpj, 1 , 0, llog, sss_io )
387         CALL restget( inum, 'u_io'  , jpi, jpj, 1 , 0, llog, u_io   )
388         CALL restget( inum, 'v_io'  , jpi, jpj, 1 , 0, llog, v_io   )
389#if defined key_coupled
390         CALL restget( inum, 'alb_ice', jpi, jpj, 1 , 0, llog, alb_ice )
391#endif
392      ENDIF
393      IF( zfice(1) /= FLOAT(nfice) .OR. ios1 == 0 ) THEN
394         IF(lwp) WRITE(numout,*)
395         IF(lwp) WRITE(numout,*) 'rst_read :  LLN sea Ice Model => Ice initialization'
396         IF(lwp) WRITE(numout,*)
397         sst_io(:,:) = ( nfice-1 )*( tn(:,:,1) + rt0 )          !!bug a explanation is needed here!
398         sss_io(:,:) = ( nfice-1 )*  sn(:,:,1)
399         DO jj = 2, jpj
400            DO ji = 2, jpi
401               u_io(ji,jj) = ( nfice-1 ) * 0.5 * ( un(ji-1,jj  ,1) + un(ji-1,jj-1,1) )
402               v_io(ji,jj) = ( nfice-1 ) * 0.5 * ( vn(ji  ,jj-1,1) + vn(ji-1,jj-1,1) )
403            END DO
404         END DO
405#    if defined key_coupled
406         alb_ice(:,:) = 0.8 * tmask(:,:,1)
407#    endif
408      ENDIF
409# endif
410# if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
411      ! Louvain La Neuve Sea Ice Model
412      ios2 = 0
413      DO jk = 1, 30
414         IF( clvnames(jk) == 'nfbulk' )  ios2 = 1
415      END DO
416      IF( ios2 == 1 ) THEN
417         CALL restget( inum, 'nfbulk',   1,   1, 1 , 0, llog, zfblk )
418         CALL restget( inum, 'gsst'  , jpi, jpj, 1 , 0, llog, gsst  )
419      ENDIF
420      IF( zfblk(1) /= FLOAT(nfbulk) .OR. ios2 == 0 ) THEN
421         IF(lwp) WRITE(numout,*)
422         IF(lwp) WRITE(numout,*) 'rst_read :  LLN sea Ice Model => Ice initialization'
423         IF(lwp) WRITE(numout,*)
424         gsst(:,:) = 0.
425         gsst(:,:) = gsst(:,:) + ( nfbulk-1 )*( tn(:,:,1) + rt0 )
426      ENDIF
427# endif
428     
429      CALL restclo( inum )
430  ! In case of restart with neuler = 0 then put all before fields = to now fields
431    IF ( neuler == 0 ) THEN
432      tb(:,:,:)=tn(:,:,:)
433      sb(:,:,:)=sn(:,:,:)
434      ub(:,:,:)=un(:,:,:)
435      vb(:,:,:)=vn(:,:,:)
436      rotb(:,:,:)=rotn(:,:,:)
437      hdivb(:,:,:)=hdivn(:,:,:)
438#if defined key_dynspg_fsc
439    ! free surface formulation (eta)
440      sshb(:,:)=sshn(:,:)
441#else
442    ! rigid lid
443      bsfb(:,:)=bsfn(:,:)
444#endif
445    ENDIF
446
447   END SUBROUTINE rst_read
448
449#endif
450   !!=====================================================================
451END MODULE restart
Note: See TracBrowser for help on using the repository browser.