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