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

Last change on this file since 717 was 717, checked in by smasson, 17 years ago

finalize the first set of modifications related to ticket:3

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 15.0 KB
Line 
1MODULE restart
2   !!======================================================================
3   !!                     ***  MODULE  restart  ***
4   !! Ocean restart :  write the ocean restart file
5   !!======================================================================
6   !! History :        !  99-11  (M. Imbard)  Original code
7   !!             8.5  !  02-08  (G. Madec)  F90: Free form
8   !!             9.0  !  05-11  (V. Garnier) Surface pressure gradient organization
9   !!             9.0  !  06-07  (S. Masson)  use IOM for restart
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   rst_opn    : open the ocean restart file
14   !!   rst_write  : write the ocean restart file
15   !!   rst_read   : read the ocean restart file
16   !!----------------------------------------------------------------------
17   USE dom_oce         ! ocean space and time domain
18   USE oce             ! ocean dynamics and tracers
19   USE phycst          ! physical constants
20   USE daymod          ! calendar
21   USE cpl_oce, ONLY : lk_cpl              !
22   USE in_out_manager  ! I/O manager
23   USE iom             ! I/O module
24   USE ini1d           ! re-initialization of u-v mask for the 1D configuration
25   USE zpshde          ! partial step: hor. derivative (zps_hde routine)
26   USE eosbn2          ! equation of state            (eos bn2 routine)
27   USE trdmld_oce      ! ocean active mixed layer tracers trends variables
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   rst_opn    ! routine called by step module
33   PUBLIC   rst_write  ! routine called by step module
34   PUBLIC   rst_read   ! routine called by opa  module
35
36   LOGICAL, PUBLIC ::   lrst_oce                  !: logical to control the oce restart write
37   INTEGER, PUBLIC ::   numror, numrow            !: logical unit for cean restart (read and write)
38
39   !! * Substitutions
40#  include "vectopt_loop_substitute.h90"
41   !!----------------------------------------------------------------------
42   !!  OPA 9.0 , LOCEAN-IPSL (2006)
43   !! $Id$
44   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
45   !!----------------------------------------------------------------------
46
47CONTAINS
48
49   SUBROUTINE rst_opn( kt )
50      !!---------------------------------------------------------------------
51      !!                   ***  ROUTINE rst_opn  ***
52      !!                     
53      !! ** Purpose : + initialization (should be read in the namelist) of nitrst
54      !!              + open the restart when we are one time step before nitrst
55      !!                   - restart header is defined when kt = nitrst-1
56      !!                   - restart data  are written when kt = nitrst
57      !!              + define lrst_oce to .TRUE. when we need to define or write the restart
58      !!----------------------------------------------------------------------
59      INTEGER, INTENT(in) ::   kt     ! ocean time-step
60      !!
61      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character
62      CHARACTER(LEN=50)   ::   clname   ! ice output restart file name
63      !!----------------------------------------------------------------------
64      !
65      IF( kt == nit000 ) THEN   ! default initialization, to do: should be read in the namelist...
66         nitrst = nitend        ! to do: should be read in the namelist in a cleaver way...
67         lrst_oce = .FALSE.
68      ENDIF
69
70      IF    ( kt == nitrst-1 .AND. lrst_oce         ) THEN
71         CALL ctl_stop( 'rst_opn: we cannot create an ocean restart at every time step',    &
72            &           'if the run has more than one time step!!!' )
73         numrow = 0
74      ELSEIF( kt == nitrst-1 .OR.  nitend == nit000 ) THEN   ! beware if model runs only one time step
75         ! beware of the format used to write kt (default is i8.8, that should be large enough)
76         IF( nitrst > 1.0e9 ) THEN   
77            WRITE(clkt,*) nitrst
78         ELSE
79            WRITE(clkt,'(i8.8)') nitrst
80         ENDIF
81         ! create the file
82         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_restart"
83         IF(lwp) THEN
84            WRITE(numout,*)
85            SELECT CASE ( jprstlib )
86            CASE ( jpnf90 )
87               WRITE(numout,*) '             open ocean restart.output NetCDF file: '//clname
88            CASE ( jprstdimg )
89               WRITE(numout,*) '             open ocean restart.output binary file: '//clname
90            END SELECT
91            IF( kt == nitrst-1 ) THEN
92               WRITE(numout,*) '             kt = nitrst - 1 = ', kt,' date= ', ndastp
93            ELSE
94               WRITE(numout,*) '             kt = ', kt,' date= ', ndastp
95            ENDIF
96         ENDIF
97
98         CALL iom_open( clname, numrow, ldwrt = .TRUE., kiolib = jprstlib )
99         lrst_oce = .TRUE.
100      ENDIF
101      !
102   END SUBROUTINE rst_opn
103
104
105   SUBROUTINE rst_write( kt )
106      !!---------------------------------------------------------------------
107      !!                   ***  ROUTINE rstwrite  ***
108      !!                     
109      !! ** Purpose :   Write restart fields in the format corresponding to jprstlib
110      !!
111      !! ** Method  :   Write in numrow when kt == nitrst in NetCDF
112      !!      file, save fields which are necessary for restart
113      !!----------------------------------------------------------------------
114      INTEGER, INTENT(in) ::   kt   ! ocean time-step
115      !!----------------------------------------------------------------------
116
117      ! calendar control
118      CALL iom_rstput( kt, nitrst, numrow, 'kt'     , REAL( kt    , wp) )   ! time-step
119      CALL iom_rstput( kt, nitrst, numrow, 'ndastp' , REAL( ndastp, wp) )   ! date
120      CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj            )   ! number of elapsed days since
121      !                                                                     ! the begining of the run [s]
122      CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt               )   ! dynamics time step
123      CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1)         )   ! surface tracer time step
124
125      ! prognostic variables
126      CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub      )   
127      CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb      )
128      CALL iom_rstput( kt, nitrst, numrow, 'tb'     , tb      )
129      CALL iom_rstput( kt, nitrst, numrow, 'sb'     , sb      )
130      CALL iom_rstput( kt, nitrst, numrow, 'rotb'   , rotb    )
131      CALL iom_rstput( kt, nitrst, numrow, 'hdivb'  , hdivb   )
132      CALL iom_rstput( kt, nitrst, numrow, 'un'     , un      )
133      CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vn      )
134      IF( lk_vvl ) CALL iom_rstput( kt, nitrst, numrow, 'wn'     , wn      )
135      CALL iom_rstput( kt, nitrst, numrow, 'tn'     , tn      )
136      CALL iom_rstput( kt, nitrst, numrow, 'sn'     , sn      )
137      CALL iom_rstput( kt, nitrst, numrow, 'rotn'   , rotn    )
138      CALL iom_rstput( kt, nitrst, numrow, 'hdivn'  , hdivn   )
139
140      IF( nn_dynhpg_rst == 1 .OR. lk_vvl ) THEN
141         CALL iom_rstput( kt, nitrst, numrow, 'rhd' , rhd  )
142         CALL iom_rstput( kt, nitrst, numrow, 'rhop', rhop )
143         IF( ln_zps ) THEN
144            CALL iom_rstput( kt, nitrst, numrow, 'gtu' , gtu )
145            CALL iom_rstput( kt, nitrst, numrow, 'gsu' , gsu )
146            CALL iom_rstput( kt, nitrst, numrow, 'gru' , gru )
147            CALL iom_rstput( kt, nitrst, numrow, 'gtv' , gtv )
148            CALL iom_rstput( kt, nitrst, numrow, 'gsv' , gsv )
149            CALL iom_rstput( kt, nitrst, numrow, 'grv' , grv )
150         ENDIF
151      ENDIF
152
153      IF( kt == nitrst ) THEN
154         CALL iom_close( numrow )     ! close the restart file (only at last time step)
155         IF( .NOT. lk_trdmld )   lrst_oce = .FALSE.
156      ENDIF
157      !
158   END SUBROUTINE rst_write
159
160
161   SUBROUTINE rst_read
162      !!----------------------------------------------------------------------
163      !!                   ***  ROUTINE rst_read  ***
164      !!
165      !! ** Purpose :   Read files for restart (format fixed by jprstlib )
166      !!
167      !! ** Method  :   Read the previous fields on the NetCDF/binary file
168      !!      the first record indicates previous characterics
169      !!      after control with the present run, we read :
170      !!      - prognostic variables on the second record
171      !!      - elliptic solver arrays
172      !!      - barotropic stream function arrays ("key_dynspg_rl" defined)
173      !!        or free surface arrays
174      !!      - tke arrays (lk_zdftke=T)
175      !!      for this last three records,  the previous characteristics
176      !!      could be different with those used in the present run.
177      !!
178      !!   According to namelist parameter nrstdt,
179      !!       nrstdt = 0  no control on the date (nit000 is  arbitrary).
180      !!       nrstdt = 1  we verify that nit000 is equal to the last
181      !!                   time step of previous run + 1.
182      !!       In both those options, the  exact duration of the experiment
183      !!       since the beginning (cumulated duration of all previous restart runs)
184      !!       is not stored in the restart and is assumed to be (nit000-1)*rdt.
185      !!       This is valid is the time step has remained constant.
186      !!
187      !!       nrstdt = 2  the duration of the experiment in days (adatrj)
188      !!                    has been stored in the restart file.
189      !!----------------------------------------------------------------------
190      REAL(wp) ::   zcoef, zkt, zrdt, zrdttra1, zndastp
191#if defined key_ice_lim
192      INTEGER  ::   ji, jj
193#endif
194      !!----------------------------------------------------------------------
195
196      IF(lwp) THEN                                             ! Contol prints
197         WRITE(numout,*)
198         SELECT CASE ( jprstlib )
199         CASE ( jpnf90 )
200            WRITE(numout,*) 'rst_read : read oce NetCDF restart file'
201         CASE ( jprstdimg )
202            WRITE(numout,*) 'rst_read : read oce binary restart file'
203         END SELECT
204         WRITE(numout,*) '~~~~~~~~'
205
206         WRITE(numout,*) ' *** Info on the present job : '
207         WRITE(numout,*) '   time-step           : ', nit000
208         WRITE(numout,*) '   date ndastp         : ', ndastp
209         WRITE(numout,*)
210         WRITE(numout,*) ' *** restart option'
211         SELECT CASE ( nrstdt )
212         CASE ( 0 ) 
213            WRITE(numout,*) ' nrstdt = 0 no control of nit000'
214         CASE ( 1 ) 
215            WRITE(numout,*) ' nrstdt = 1 we control the date of nit000'
216         CASE ( 2 )
217            WRITE(numout,*) ' nrstdt = 2 the date adatrj is read in restart file'
218         CASE DEFAULT
219            WRITE(numout,*) '  ===>>>> nrstdt not equal 0, 1 or 2 : no control of the date'
220            WRITE(numout,*) '  =======                  ========='
221         END SELECT
222         WRITE(numout,*)
223      ENDIF
224
225      CALL iom_open( 'restart', numror, kiolib = jprstlib )
226
227      ! Calendar informations
228      CALL iom_get( numror, 'kt'     , zkt      )   ! time-step
229      CALL iom_get( numror, 'ndastp' , zndastp  )   ! date
230      IF(lwp) THEN
231         WRITE(numout,*)
232         WRITE(numout,*) ' *** Info on the restart file read : '
233         WRITE(numout,*) '   time-step           : ', NINT( zkt )
234         WRITE(numout,*) '   date ndastp         : ', NINT( zndastp )
235         WRITE(numout,*)
236      ENDIF
237      ! Control of date
238      IF( nit000 - NINT( zkt )  /= 1 .AND. nrstdt /= 0 ) &
239           & CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart', &
240           & ' verify the restart file or rerun with nrstdt = 0 (namelist)' )
241      ! re-initialisation of  adatrj0
242      adatrj0 = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday
243      IF ( nrstdt == 2 ) THEN
244         ! by default ndatsp has been set to ndate0 in dom_nam
245         ! ndate0 has been read in the namelist (standard OPA 8)
246         ! here when nrstdt=2 we keep the  final date of previous run
247         ndastp = NINT( zndastp )
248         CALL iom_get( numror, 'adatrj', adatrj )   ! number of elapsed days since the begining of last run
249      ENDIF
250      ! Check dynamics and tracer time-step consistency and force Euler restart if changed
251      IF( iom_varid( numror, 'rdt' ) > 0 )   THEN
252         CALL iom_get( numror, 'rdt', zrdt )
253         IF( zrdt /= rdt )   neuler = 0
254      ENDIF
255      IF( iom_varid( numror, 'rdttra1' ) > 0 )   THEN
256         CALL iom_get( numror, 'rdttra1', zrdttra1 )
257         IF( zrdttra1 /= rdttra(1) )   neuler = 0
258      ENDIF
259      !
260      !                                                       ! Read prognostic variables
261      CALL iom_get( numror, jpdom_autoglo, 'ub'   , ub    )        ! before i-component velocity
262      CALL iom_get( numror, jpdom_autoglo, 'vb'   , vb    )        ! before j-component velocity
263      CALL iom_get( numror, jpdom_autoglo, 'tb'   , tb    )        ! before temperature
264      CALL iom_get( numror, jpdom_autoglo, 'sb'   , sb    )        ! before salinity
265      CALL iom_get( numror, jpdom_autoglo, 'rotb' , rotb  )        ! before curl
266      CALL iom_get( numror, jpdom_autoglo, 'hdivb', hdivb )        ! before horizontal divergence
267      CALL iom_get( numror, jpdom_autoglo, 'un'   , un    )        ! now    i-component velocity
268      CALL iom_get( numror, jpdom_autoglo, 'vn'   , vn    )        ! now    j-component velocity
269      IF( lk_vvl ) CALL iom_get( numror, jpdom_autoglo, 'wn'   , wn    )        ! now    k-component velocity
270      CALL iom_get( numror, jpdom_autoglo, 'tn'   , tn    )        ! now    temperature
271      CALL iom_get( numror, jpdom_autoglo, 'sn'   , sn    )        ! now    salinity
272      CALL iom_get( numror, jpdom_autoglo, 'rotn' , rotn  )        ! now    curl
273      CALL iom_get( numror, jpdom_autoglo, 'hdivn', hdivn )        ! now    horizontal divergence
274
275
276      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0)
277         tb   (:,:,:) = tn   (:,:,:)                             ! all before fields set to now field values
278         sb   (:,:,:) = sn   (:,:,:)
279         ub   (:,:,:) = un   (:,:,:)
280         vb   (:,:,:) = vn   (:,:,:)
281         rotb (:,:,:) = rotn (:,:,:)
282         hdivb(:,:,:) = hdivn(:,:,:)
283      ENDIF
284
285      IF( iom_varid( numror, 'rhd' ) > 0 ) THEN
286         CALL iom_get( numror, jpdom_autoglo, 'rhd' , rhd  )
287         CALL iom_get( numror, jpdom_autoglo, 'rhop', rhop )
288      ELSE
289         CALL eos( tb, sb, rhd, rhop )        ! before potential and in situ densities
290      ENDIF
291      IF( ln_zps .AND. .NOT. lk_cfg_1d ) THEN
292         IF( iom_varid( numror, 'gtu' ) > 0 ) THEN
293            CALL iom_get( numror, jpdom_autoglo, 'gtu' , gtu )
294            CALL iom_get( numror, jpdom_autoglo, 'gsu' , gsu )
295            CALL iom_get( numror, jpdom_autoglo, 'gru' , gru )
296            CALL iom_get( numror, jpdom_autoglo, 'gtv' , gtv )
297            CALL iom_get( numror, jpdom_autoglo, 'gsv' , gsv )
298            CALL iom_get( numror, jpdom_autoglo, 'grv' , grv )
299         ELSE
300            CALL zps_hde( nit000, tb , sb , rhd,   &  ! Partial steps: before Horizontal DErivative
301               &                  gtu, gsu, gru,   &  ! of t, s, rd at the bottom ocean level
302               &                  gtv, gsv, grv )
303         ENDIF
304      ENDIF
305      !
306   END SUBROUTINE rst_read
307
308
309   !!=====================================================================
310END MODULE restart
Note: See TracBrowser for help on using the repository browser.