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

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

CL + CT: BUGFIX091: Add missing "USE flx_oce" module

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 18.5 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_fdir
43   !!----------------------------------------------------------------------
44   !!   'key_fdir'                                       direct access file
45   !!----------------------------------------------------------------------
46#  include "restart_fdir.h90"
47
48#elif  ( defined key_mpp_mpi   ||   defined key_mpp_shmem ) && defined key_dimgout
49   !!----------------------------------------------------------------------
50   !!   'key_mpp_mpi'     OR      MPI massively parallel processing library
51   !!   'key_mpp_shmem'         SHMEM massively parallel processing library
52   !!                     AND
53   !!   'key_dimgout'         
54   !!----------------------------------------------------------------------
55   !!                 direct acces file one per processor
56   !!          (merging/splitting is done off-line, eventually)
57   !!-----------------------------------------------------------------------
58#  include "restart_dimg.h90"
59
60#else
61   !!----------------------------------------------------------------------
62   !!   Default option                                          NetCDF file
63   !!----------------------------------------------------------------------
64
65   SUBROUTINE rst_write( kt )
66      !!---------------------------------------------------------------------
67      !!                   ***  ROUTINE rstwrite  ***
68      !!                     
69      !! ** Purpose :   Write restart fields in NetCDF format
70      !!
71      !! ** Method  :   Write in numwrs file each nstock time step in NetCDF
72      !!      file, save fields which are necessary for restart
73      !!
74      !! History :
75      !!        !  99-11  (M. Imbard)  Original code
76      !!   8.5  !  02-08  (G. Madec)  F90: Free form
77      !!----------------------------------------------------------------------
78      !! * Modules used
79      USE ioipsl
80
81      !! * Arguments
82      INTEGER, INTENT( in ) ::   kt         ! ocean time-step
83
84      !! * Local declarations
85      LOGICAL ::   llbon
86      CHARACTER (len=50) ::   clname, cln
87      INTEGER ::   ic, jc, itime
88      REAL(wp) ::   zdate0
89      REAL(wp), DIMENSION( 1) ::   zfice, zfblk   ! used only in case of ice & bulk
90      REAL(wp), DIMENSION(10) ::   zinfo(10)
91      !!----------------------------------------------------------------------
92      !!  OPA 8.5, LODYC-IPSL (2002)
93      !!----------------------------------------------------------------------
94
95      IF( kt == nit000 ) THEN
96         IF(lwp) WRITE(numout,*)
97         IF(lwp) WRITE(numout,*) 'rst_wri : write restart.output NetCDF file'
98         IF(lwp) WRITE(numout,*) '~~~~~~~'
99         zfice(1) = 1.e0   ;   zfblk(1) = 1.e0
100      ENDIF
101
102
103      IF( MOD( kt, nstock ) == 0 .OR. kt == nitend ) THEN
104         
105         ! 0. Initializations
106         ! ------------------
107
108         IF(lwp) WRITE(numout,*) ' '
109         IF(lwp) WRITE(numout,*) 'rst_write : write the restart file in NetCDF format ',   &
110                                              'at it= ',kt,' date= ',ndastp
111         IF(lwp) WRITE(numout,*) '~~~~~~~~~'
112
113         ! Job informations
114         zinfo(1) = FLOAT( no        )   ! job number
115         zinfo(2) = FLOAT( kt        )   ! time-step
116         zinfo(3) = FLOAT( 2 - nsolv )   ! pcg solver
117         zinfo(4) = FLOAT( nsolv - 1 )   ! sor solver
118         IF( lk_zdftke ) THEN
119            zinfo(5) = 1.e0              ! TKE
120         ELSE
121            zinfo(5) = 0.e0              ! no TKE
122         ENDIF
123         zinfo(6) = FLOAT( ndastp )      ! date
124         zinfo(7) = adatrj               ! ???
125
126         ! delete the restart file if it exists
127         INQUIRE( FILE=crestart, EXIST=llbon )
128         IF(llbon) THEN
129            OPEN( UNIT=numwrs, FILE=crestart, STATUS='old' )
130            CLOSE( numwrs, STATUS='delete' )
131         ENDIF
132
133         ! Name of the new restart file
134         ic     = 1
135         DO jc = 1, 16
136            IF( cexper(jc:jc) /= ' ' )   ic = jc
137         END DO
138         WRITE(cln,'("_",i4.4,i2.2,i2.2,"_restart")') nyear, nmonth, nday
139         clname = cexper(1:ic)//cln
140         ic = 1
141         DO jc = 1, 48
142            IF( clname(jc:jc) /= ' ' ) ic = jc
143         END DO
144         crestart = clname(1:ic)//".nc"
145         itime = 0
146         CALL ymds2ju( nyear, nmonth, nday, 0.e0, zdate0 )
147         CALL restini( 'NONE', jpi, jpj, glamt, gphit, jpk, gdept, clname,   &
148                        itime, zdate0, rdt*nstock ,numwrs )
149
150         CALL restput( numwrs, 'info'   , 1  , 1  , 10 , 0, zinfo   )   ! restart informations
151         
152         CALL restput( numwrs, 'ub'     , jpi, jpj, jpk, 0, ub      )   ! prognostic variables
153         CALL restput( numwrs, 'vb'     , jpi, jpj, jpk, 0, vb      )
154         CALL restput( numwrs, 'tb'     , jpi, jpj, jpk, 0, tb      )
155         CALL restput( numwrs, 'sb'     , jpi, jpj, jpk, 0, sb      )
156         CALL restput( numwrs, 'rotb'   , jpi, jpj, jpk, 0, rotb    )
157         CALL restput( numwrs, 'hdivb'  , jpi, jpj, jpk, 0, hdivb   )
158         CALL restput( numwrs, 'un'     , jpi, jpj, jpk, 0, un      )
159         CALL restput( numwrs, 'vn'     , jpi, jpj, jpk, 0, vn      )
160         CALL restput( numwrs, 'tn'     , jpi, jpj, jpk, 0, tn      )
161         CALL restput( numwrs, 'sn'     , jpi, jpj, jpk, 0, sn      )
162         CALL restput( numwrs, 'rotn'   , jpi, jpj, jpk, 0, rotn    )
163         CALL restput( numwrs, 'hdivn'  , jpi, jpj, jpk, 0, hdivn   )
164
165         CALL restput( numwrs, 'gcx'    , jpi, jpj, 1  , 0, gcx     )   ! Read elliptic solver arrays
166         CALL restput( numwrs, 'gcxb'   , jpi, jpj, 1  , 0, gcxb    )
167# if defined key_dynspg_fsc
168         CALL restput( numwrs, 'sshb'   , jpi, jpj, 1  , 0, sshb    )   ! free surface formulation (ssh)
169         CALL restput( numwrs, 'sshn'   , jpi, jpj, 1  , 0, sshn    )
170# else
171         CALL restput( numwrs, 'bsfb'   , jpi, jpj, 1  , 0, bsfb    )   ! Rigid-lid formulation (bsf)
172         CALL restput( numwrs, 'bsfn'   , jpi, jpj, 1  , 0, bsfn    )
173         CALL restput( numwrs, 'bsfd'   , jpi, jpj, 1  , 0, bsfd    )
174# endif
175# if defined key_zdftke   ||   defined key_esopa
176         IF( lk_zdftke ) THEN
177            CALL restput( numwrs, 'en'     , jpi, jpj, jpk, 0, en      )   ! TKE arrays
178         ENDIF
179# endif
180# if defined key_ice_lim
181         zfice(1) = FLOAT( nfice )                                      ! Louvain La Neuve Sea Ice Model
182         CALL restput( numwrs, 'nfice'  ,   1,   1, 1  , 0, zfice   )
183         CALL restput( numwrs, 'sst_io' , jpi, jpj, 1  , 0, sst_io  )
184         CALL restput( numwrs, 'sss_io' , jpi, jpj, 1  , 0, sss_io  )
185         CALL restput( numwrs, 'u_io'   , jpi, jpj, 1  , 0, u_io    )
186         CALL restput( numwrs, 'v_io'   , jpi, jpj, 1  , 0, v_io    )
187# if defined key_coupled
188         CALL restput( numwrs, 'alb_ice', jpi, jpj, 1  , 0, alb_ice )
189# endif
190# endif
191# if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
192         zfblk(1) = FLOAT( nfbulk )                                 ! Bulk
193         CALL restput( numwrs, 'nfbulk' ,   1,   1, 1  , 0, zfblk   )
194         CALL restput( numwrs, 'gsst'   , jpi, jpj, 1  , 0, gsst    )
195# endif
196
197         CALL restclo( numwrs )                                         ! close the restart file
198         
199      ENDIF
200
201   END SUBROUTINE rst_write
202
203
204   SUBROUTINE rst_read
205      !!----------------------------------------------------------------------
206      !!                   ***  ROUTINE rst_read  ***
207      !!
208      !! ** Purpose :   Read files for restart
209      !!
210      !! ** Method  :   Read the previous fields on the NetCDF file
211      !!      the first record indicates previous characterics
212      !!      after control with the present run, we read :
213      !!      - prognostic variables on the second record
214      !!      - elliptic solver arrays
215      !!      - barotropic stream function arrays (default option)
216      !!        or free surface arrays ("key_dynspg_fsc" defined)
217      !!      - tke arrays (lk_zdftke=T)
218      !!      for this last three records,  the previous characteristics
219      !!      could be different with those used in the present run.
220      !!
221      !!   According to namelist parameter nrstdt,
222      !!       nrstdt = 0  no control on the date (nit000 is  arbitrary).
223      !!       nrstdt = 1  we verify that nit000 is equal to the last
224      !!                   time step of previous run + 1.
225      !!       In both those options, the  exact duration of the experiment
226      !!       since the beginning (cumulated duration of all previous restart runs)
227      !!       is not stored in the restart and is assumed to be (nit000-1)*rdt.
228      !!       This is valid is the time step has remained constant.
229      !!
230      !!       nrstdt = 2  the duration of the experiment in days (adatrj)
231      !!                    has been stored in the restart file.
232      !!
233      !! History :
234      !!        !  99-05  (M. Imbard)  Original code
235      !!   8.5  !  02-09  (G. Madec)  F90: Free form
236      !!----------------------------------------------------------------------
237      !! * Modules used
238      USE ioipsl
239
240      !! * Local declarations
241      LOGICAL ::   llog
242      CHARACTER (len=8 ) ::   clvnames(30)
243      CHARACTER (len=32) ::   clname = 'restart'
244      INTEGER  ::   &
245         itime, ibvar,     &  !
246         inum                 ! temporary logical unit
247      REAL(wp) ::   zdate0, zdt, zinfo(10)
248      REAL(wp) ::   zdept(jpk), zlamt(jpi,jpj), zphit(jpi,jpj)
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
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, gcxb    )   ! Read elliptic solver arrays
353      CALL restget( inum, 'gcx'    , jpi, jpj, 1  , 0, llog, gcx     )
354# if defined key_dynspg_fsc
355      CALL restget( inum, 'sshb'   , jpi, jpj, 1  , 0, llog, sshb    )   ! free surface formulation (ssh)
356      CALL restget( inum, 'sshn'   , jpi, jpj, 1  , 0, llog, sshn    )
357# else
358      CALL restget( inum, 'bsfb'   , jpi, jpj, 1  , 0, llog, bsfb    )   ! Rigid-lid formulation (bsf)
359      CALL restget( inum, 'bsfn'   , jpi, jpj, 1  , 0, llog, bsfn    )
360      CALL restget( inum, 'bsfd'   , jpi, jpj, 1  , 0, llog, bsfd    )
361# endif
362# if defined key_zdftke   ||   defined key_esopa
363      IF( lk_zdftke ) THEN
364         IF( NINT( zinfo(5) ) == 1 ) THEN                                ! Read tke arrays
365            CALL restget( inum, 'en',jpi,jpj, jpk,0  , llog, en )
366            ln_rstke = .FALSE.
367         ELSE
368            IF(lwp) WRITE(numout,*) ' ===>>>> : the previous restart file didnot used  tke scheme'
369            IF(lwp) WRITE(numout,*) ' =======                ======='
370            nrstdt = 2
371            ln_rstke = .TRUE.
372         ENDIF
373      ENDIF
374# endif
375# if defined key_ice_lim
376      ! Louvain La Neuve Sea Ice Model
377      ios1 = 0
378      DO jn = 1, 30
379         IF( clvnames(jn) == 'nfice' )  ios1 = 1
380      END DO
381      IF( ios1 == 1 ) THEN
382         CALL restget( inum, 'nfice' ,   1,   1, 1 , 0, llog, zfice  )
383         CALL restget( inum, 'sst_io', jpi, jpj, 1 , 0, llog, sst_io )
384         CALL restget( inum, 'sss_io', jpi, jpj, 1 , 0, llog, sss_io )
385         CALL restget( inum, 'u_io'  , jpi, jpj, 1 , 0, llog, u_io   )
386         CALL restget( inum, 'v_io'  , jpi, jpj, 1 , 0, llog, v_io   )
387#if defined key_coupled
388         CALL restget( inum, 'alb_ice', jpi, jpj, 1 , 0, llog, alb_ice )
389#endif
390      ENDIF
391      IF( zfice(1) /= FLOAT(nfice) .OR. ios1 == 0 ) THEN
392         IF(lwp) WRITE(numout,*)
393         IF(lwp) WRITE(numout,*) 'rst_read :  LLN sea Ice Model => Ice initialization'
394         IF(lwp) WRITE(numout,*)
395         sst_io(:,:) = ( nfice-1 )*( tn(:,:,1) + rt0 )          !!bug a explanation is needed here!
396         sss_io(:,:) = ( nfice-1 )*  sn(:,:,1)
397         DO jj = 2, jpj
398            DO ji = 2, jpi
399               u_io(ji,jj) = ( nfice-1 ) * 0.5 * ( un(ji-1,jj  ,1) + un(ji-1,jj-1,1) )
400               v_io(ji,jj) = ( nfice-1 ) * 0.5 * ( vn(ji  ,jj-1,1) + vn(ji-1,jj-1,1) )
401            END DO
402         END DO
403#    if defined key_coupled
404         alb_ice(:,:) = 0.8 * tmask(:,:,1)
405#    endif
406      ENDIF
407# endif
408# if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
409      ! Louvain La Neuve Sea Ice Model
410      ios2 = 0
411      DO jk = 1, 30
412         IF( clvnames(jk) == 'nfbulk' )  ios2 = 1
413      END DO
414      IF( ios2 == 1 ) THEN
415         CALL restget( inum, 'nfbulk',   1,   1, 1 , 0, llog, zfblk )
416         CALL restget( inum, 'gsst'  , jpi, jpj, 1 , 0, llog, gsst  )
417      ENDIF
418      IF( zfblk(1) /= FLOAT(nfbulk) .OR. ios2 == 0 ) THEN
419         IF(lwp) WRITE(numout,*)
420         IF(lwp) WRITE(numout,*) 'rst_read :  LLN sea Ice Model => Ice initialization'
421         IF(lwp) WRITE(numout,*)
422         gsst(:,:) = 0.
423         gsst(:,:) = gsst(:,:) + ( nfbulk-1 )*( tn(:,:,1) + rt0 )
424      ENDIF
425# endif
426     
427      CALL restclo( inum )
428
429   END SUBROUTINE rst_read
430
431#endif
432   !!=====================================================================
433END MODULE restart
Note: See TracBrowser for help on using the repository browser.