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

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

CT : UPDATE001 : First major NEMO update

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 18.3 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 )
48   !!----------------------------------------------------------------------
49   !!   'key_mpp_mpi'     OR      MPI massively parallel processing library
50   !!   'key_mpp_shmem'         SHMEM massively parallel processing library
51   !!----------------------------------------------------------------------
52   !!                 direct acces file one per processor
53   !!          (merging/splitting is done off-line, eventually)
54   !!-----------------------------------------------------------------------
55#  include "restart_mpp.h90"
56
57#else
58   !!----------------------------------------------------------------------
59   !!   Default option                                          NetCDF file
60   !!----------------------------------------------------------------------
61
62   SUBROUTINE rst_write( kt )
63      !!---------------------------------------------------------------------
64      !!                   ***  ROUTINE rstwrite  ***
65      !!                     
66      !! ** Purpose :   Write restart fields in NetCDF format
67      !!
68      !! ** Method  :   Write in numwrs file each nstock time step in NetCDF
69      !!      file, save fields which are necessary for restart
70      !!
71      !! History :
72      !!        !  99-11  (M. Imbard)  Original code
73      !!   8.5  !  02-08  (G. Madec)  F90: Free form
74      !!----------------------------------------------------------------------
75      !! * Modules used
76      USE ioipsl
77
78      !! * Arguments
79      INTEGER, INTENT( in ) ::   kt         ! ocean time-step
80
81      !! * Local declarations
82      LOGICAL ::   llbon
83      CHARACTER (len=50) ::   clname, cln
84      INTEGER ::   ic, jc, itime
85      REAL(wp) ::   zdate0
86      REAL(wp), DIMENSION( 1) ::   zfice, zfblk   ! used only in case of ice & bulk
87      REAL(wp), DIMENSION(10) ::   zinfo(10)
88      !!----------------------------------------------------------------------
89      !!  OPA 8.5, LODYC-IPSL (2002)
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         CALL restput( numwrs, 'gcx'    , jpi, jpj, 1  , 0, gcx     )   ! Read elliptic solver arrays
163         CALL restput( numwrs, 'gcxb'   , jpi, jpj, 1  , 0, gcxb    )
164# if defined key_dynspg_fsc
165         CALL restput( numwrs, 'sshb'   , jpi, jpj, 1  , 0, sshb    )   ! free surface formulation (ssh)
166         CALL restput( numwrs, 'sshn'   , jpi, jpj, 1  , 0, sshn    )
167# else
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# endif
172# if defined key_zdftke   ||   defined key_esopa
173         IF( lk_zdftke ) THEN
174            CALL restput( numwrs, 'en'     , jpi, jpj, jpk, 0, en      )   ! TKE arrays
175         ENDIF
176# endif
177# if defined key_ice_lim
178         zfice(1) = FLOAT( nfice )                                      ! Louvain La Neuve Sea Ice Model
179         CALL restput( numwrs, 'nfice'  ,   1,   1, 1  , 0, zfice   )
180         CALL restput( numwrs, 'sst_io' , jpi, jpj, 1  , 0, sst_io  )
181         CALL restput( numwrs, 'sss_io' , jpi, jpj, 1  , 0, sss_io  )
182         CALL restput( numwrs, 'u_io'   , jpi, jpj, 1  , 0, v_io    )
183         CALL restput( numwrs, 'v_io'   , jpi, jpj, 1  , 0, v_io    )
184# if defined key_coupled
185         CALL restput( numwrs, 'alb_ice', jpi, jpj, 1  , 0, alb_ice )
186# endif
187# endif
188# if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
189         zfblk(1) = FLOAT( nfbulk )                                 ! Bulk
190         CALL restput( numwrs, 'nfbulk' ,   1,   1, 1  , 0, zfblk   )
191         CALL restput( numwrs, 'gsst'   , jpi, jpj, 1  , 0, gsst    )
192# endif
193
194         CALL restclo( numwrs )                                         ! close the restart file
195         
196      ENDIF
197
198   END SUBROUTINE rst_write
199
200
201   SUBROUTINE rst_read
202      !!----------------------------------------------------------------------
203      !!                   ***  ROUTINE rst_read  ***
204      !!
205      !! ** Purpose :   Read files for restart
206      !!
207      !! ** Method  :   Read the previous fields on the NetCDF file
208      !!      the first record indicates previous characterics
209      !!      after control with the present run, we read :
210      !!      - prognostic variables on the second record
211      !!      - elliptic solver arrays
212      !!      - barotropic stream function arrays (default option)
213      !!        or free surface arrays ("key_dynspg_fsc" defined)
214      !!      - tke arrays (lk_zdftke=T)
215      !!      for this last three records,  the previous characteristics
216      !!      could be different with those used in the present run.
217      !!
218      !!   According to namelist parameter nrstdt,
219      !!       nrstdt = 0  no control on the date (nit000 is  arbitrary).
220      !!       nrstdt = 1  we verify that nit000 is equal to the last
221      !!                   time step of previous run + 1.
222      !!       In both those options, the  exact duration of the experiment
223      !!       since the beginning (cumulated duration of all previous restart runs)
224      !!       is not stored in the restart and is assumed to be (nit000-1)*rdt.
225      !!       This is valid is the time step has remained constant.
226      !!
227      !!       nrstdt = 2  the duration of the experiment in days (adatrj)
228      !!                    has been stored in the restart file.
229      !!
230      !! History :
231      !!        !  99-05  (M. Imbard)  Original code
232      !!   8.5  !  02-09  (G. Madec)  F90: Free form
233      !!----------------------------------------------------------------------
234      !! * Modules used
235      USE ioipsl
236
237      !! * Local declarations
238      LOGICAL ::   llog
239      CHARACTER (len=8 ) ::   clvnames(30)
240      CHARACTER (len=32) ::   clname = 'restart'
241      INTEGER  ::   &
242         itime, ibvar,     &  !
243         inum                 ! temporary logical unit
244      REAL(wp) ::   zdate0, zdt, zinfo(10)
245      REAL(wp) ::   zdept(jpk), zlamt(jpi,jpj), zphit(jpi,jpj)
246#   if defined key_ice_lim
247      INTEGER  ::   ios1, ji, jj, jn
248      REAL(wp) ::   zfice(1)
249#   endif
250# if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
251      INTEGER  ::   ios2, jk
252      REAL(wp) ::   zfblk(1)
253#   endif
254      !!----------------------------------------------------------------------
255      !!  OPA 8.5, LODYC-IPSL (2002)
256      !!----------------------------------------------------------------------
257
258      IF(lwp) WRITE(numout,*)
259      IF(lwp) WRITE(numout,*) 'rst_read : read the NetCDF restart file'
260      IF(lwp) WRITE(numout,*) '~~~~~~~~'
261
262      IF(lwp) WRITE(numout,*) ' Info on the present job : '
263      IF(lwp) WRITE(numout,*) '   job number          : ', no
264      IF(lwp) WRITE(numout,*) '   time-step           : ', nit000
265      IF(lwp) WRITE(numout,*) '   solver type         : ', nsolv
266      IF( lk_zdftke ) THEN
267         IF(lwp) WRITE(numout,*) '   tke option          : 1 '
268      ELSE
269         IF(lwp) WRITE(numout,*) '   tke option          : 0 '
270      ENDIF
271      IF(lwp) WRITE(numout,*) '   date ndastp         : ', ndastp
272      IF(lwp) WRITE(numout,*)
273
274      ! Time domain : restart
275      ! -------------------------
276
277      IF(lwp) WRITE(numout,*)
278      IF(lwp) WRITE(numout,*)
279      IF(lwp) WRITE(numout,*) ' *** restart option'
280      SELECT CASE ( nrstdt )
281      CASE ( 0 ) 
282         IF(lwp) WRITE(numout,*) ' nrstdt = 0 no control of nit000'
283      CASE ( 1 ) 
284         IF(lwp) WRITE(numout,*) ' nrstdt = 1 we control the date of nit000'
285      CASE ( 2 )
286         IF(lwp) WRITE(numout,*) ' nrstdt = 2 the date adatrj is read in restart file'
287      CASE DEFAULT
288         IF(lwp) WRITE(numout,*) '  ===>>>> nrstdt not equal 0, 1 or 2 : no control of the date'
289         IF(lwp) WRITE(numout,*) ' =======                   ========='
290      END SELECT
291
292      itime = 0
293      llog  = .FALSE.
294      zlamt(:,:) = 0.e0
295      zphit(:,:) = 0.e0
296      zdept(:)   = 0.e0
297      CALL restini( clname, jpi, jpj, zlamt, zphit, jpk, zdept, clname,   &
298         &          itime, zdate0, zdt, inum )
299
300      CALL ioget_vname( inum, ibvar, clvnames)
301      CALL restget( inum, 'info', 1, 1, 10, 0, llog, zinfo )
302
303      IF(lwp) WRITE(numout,*)
304      IF(lwp) WRITE(numout,*) ' Info on the restart file read : '
305      IF(lwp) WRITE(numout,*) '   FILE name           : ', clname
306      IF(lwp) WRITE(numout,*) '   job number          : ', NINT( zinfo(1) )
307      IF(lwp) WRITE(numout,*) '   time-step           : ', NINT( zinfo(2) )
308      IF(lwp) WRITE(numout,*) '   solver type         : ', NINT( zinfo(4) ) + 1
309      IF(lwp) WRITE(numout,*) '   tke option          : ', NINT( zinfo(5) )
310      IF(lwp) WRITE(numout,*) '   date ndastp         : ', NINT( zinfo(6) )
311      IF(lwp) WRITE(numout,*) '   number of variables : ', ibvar
312      IF(lwp) WRITE(numout,*) '   NetCDF variables    : ', clvnames
313      IF(lwp) WRITE(numout,*)
314
315      ! Control of date
316      IF( nit000 - NINT( zinfo(2) )  /= 1 .AND. ABS( nrstdt ) == 1 ) THEN
317         IF(lwp) WRITE(numout,cform_err)
318         IF(lwp) WRITE(numout,*) ' ===>>>> : problem with nit000 for the restart'
319         IF(lwp) WRITE(numout,*) ' verify the restart file or rerun with nrstdt = 0 (namelist)'
320         nstop = nstop + 1
321      ENDIF
322
323      ! re-initialisation of  adatrj0
324      adatrj0 =  ( FLOAT( nit000-1 ) * rdttra(1) ) / rday
325
326      IF ( nrstdt == 2 ) THEN
327!                             by default ndatsp has been set to ndate0 in dom_nam
328!                             ndate0 has been read in the namelist (standard OPA 8)
329!                             here when nrstdt=2 we keep the  final date of previous run
330        ndastp = NINT( zinfo(6) )
331        adatrj0 =  zinfo(7)
332      ENDIF
333
334
335
336      CALL restget( inum, 'ub'     , jpi, jpj, jpk, 0, llog, ub      )    ! Read prognostic variables
337      CALL restget( inum, 'vb'     , jpi, jpj, jpk, 0, llog, vb      )
338      CALL restget( inum, 'tb'     , jpi, jpj, jpk, 0, llog, tb      )
339      CALL restget( inum, 'sb'     , jpi, jpj, jpk, 0, llog, sb      )
340      CALL restget( inum, 'rotb'   , jpi, jpj, jpk, 0, llog, rotb    )
341      CALL restget( inum, 'hdivb'  , jpi, jpj, jpk, 0, llog, hdivb   )
342      CALL restget( inum, 'un'     , jpi, jpj, jpk, 0, llog, un      )
343      CALL restget( inum, 'vn'     , jpi, jpj, jpk, 0, llog, vn      )
344      CALL restget( inum, 'tn'     , jpi, jpj, jpk, 0, llog, tn      )
345      CALL restget( inum, 'sn'     , jpi, jpj, jpk, 0, llog, sn      )
346      CALL restget( inum, 'rotn'   , jpi, jpj, jpk, 0, llog, rotn    )
347      CALL restget( inum, 'hdivn'  , jpi, jpj, jpk, 0, llog, hdivn   )
348
349      CALL restget( inum, 'gcxb'   , jpi, jpj, 1  , 0, llog, gcxb    )   ! Read elliptic solver arrays
350      CALL restget( inum, 'gcx'    , jpi, jpj, 1  , 0, llog, gcx     )
351# if defined key_dynspg_fsc
352      CALL restget( inum, 'sshb'   , jpi, jpj, 1  , 0, llog, sshb    )   ! free surface formulation (ssh)
353      CALL restget( inum, 'sshn'   , jpi, jpj, 1  , 0, llog, sshn    )
354# else
355      CALL restget( inum, 'bsfb'   , jpi, jpj, 1  , 0, llog, bsfb    )   ! Rigid-lid formulation (bsf)
356      CALL restget( inum, 'bsfn'   , jpi, jpj, 1  , 0, llog, bsfn    )
357      CALL restget( inum, 'bsfd'   , jpi, jpj, 1  , 0, llog, bsfd    )
358# endif
359# if defined key_zdftke   ||   defined key_esopa
360      IF( lk_zdftke ) THEN
361         IF( NINT( zinfo(5) ) == 1 ) THEN                                ! Read tke arrays
362            CALL restget( inum, 'en',jpi,jpj, jpk,0  , llog, en )
363            ln_rstke = .FALSE.
364         ELSE
365            IF(lwp) WRITE(numout,*) ' ===>>>> : the previous restart file didnot used  tke scheme'
366            IF(lwp) WRITE(numout,*) ' =======                ======='
367            nrstdt = 2
368            ln_rstke = .TRUE.
369         ENDIF
370      ENDIF
371# endif
372# if defined key_ice_lim
373      ! Louvain La Neuve Sea Ice Model
374      ios1 = 0
375      DO jn = 1, 30
376         IF( clvnames(jn) == 'nfice' )  ios1 = 1
377      END DO
378      IF( ios1 == 1 ) THEN
379         CALL restget( inum, 'nfice' ,   1,   1, 1 , 0, llog, zfice  )
380         CALL restget( inum, 'sst_io', jpi, jpj, 1 , 0, llog, sst_io )
381         CALL restget( inum, 'sss_io', jpi, jpj, 1 , 0, llog, sss_io )
382         CALL restget( inum, 'u_io'  , jpi, jpj, 1 , 0, llog, u_io   )
383         CALL restget( inum, 'v_io'  , jpi, jpj, 1 , 0, llog, v_io   )
384#if defined key_coupled
385         CALL restget( inum, 'alb_ice', jpi, jpj, 1 , 0, llog, alb_ice )
386#endif
387      ENDIF
388      IF( zfice(1) /= FLOAT(nfice) .OR. ios1 == 0 ) THEN
389         IF(lwp) WRITE(numout,*)
390         IF(lwp) WRITE(numout,*) 'rst_read :  LLN sea Ice Model => Ice initialization'
391         IF(lwp) WRITE(numout,*)
392         sst_io(:,:) = ( nfice-1 )*( tn(:,:,1) + rt0 )          !!bug a explanation is needed here!
393         sss_io(:,:) = ( nfice-1 )*  sn(:,:,1)
394         DO jj = 2, jpj
395            DO ji = 2, jpi
396               u_io(ji,jj) = ( nfice-1 ) * 0.5 * ( un(ji-1,jj  ,1) + un(ji-1,jj-1,1) )
397               v_io(ji,jj) = ( nfice-1 ) * 0.5 * ( vn(ji  ,jj-1,1) + vn(ji-1,jj-1,1) )
398            END DO
399         END DO
400#    if defined key_coupled
401         alb_ice(:,:) = 0.8 * tmask(:,:,1)
402#    endif
403      ENDIF
404# endif
405# if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
406      ! Louvain La Neuve Sea Ice Model
407      ios2 = 0
408      DO jk = 1, 30
409         IF( clvnames(jk) == 'nfbulk' )  ios2 = 1
410      END DO
411      IF( ios2 == 1 ) THEN
412         CALL restget( inum, 'nfbulk',   1,   1, 1 , 0, llog, zfblk )
413         CALL restget( inum, 'gsst'  , jpi, jpj, 1 , 0, llog, gsst  )
414      ENDIF
415      IF( zfblk(1) /= FLOAT(nfbulk) .OR. ios2 == 0 ) THEN
416         IF(lwp) WRITE(numout,*)
417         IF(lwp) WRITE(numout,*) 'rst_read :  LLN sea Ice Model => Ice initialization'
418         IF(lwp) WRITE(numout,*)
419         gsst(:,:) = 0.
420         gsst(:,:) = gsst(:,:) + ( nfbulk-1 )*( tn(:,:,1) + rt0 )
421      ENDIF
422# endif
423     
424      CALL restclo( inum )
425
426   END SUBROUTINE rst_read
427
428#endif
429   !!=====================================================================
430END MODULE restart
Note: See TracBrowser for help on using the repository browser.