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

Last change on this file since 900 was 900, checked in by rblod, 16 years ago

Update 1D configuration according to SBC and LIM3, see ticket #117

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