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 branches/UKMO/dev_merge_2017_restart_datestamp_GO6_mixing/NEMOGCM/NEMO/OPA_SRC/IOM – NEMO

source: branches/UKMO/dev_merge_2017_restart_datestamp_GO6_mixing/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90 @ 9493

Last change on this file since 9493 was 9493, checked in by davestorkey, 6 years ago
  1. Datestamp restart files.
  2. Add extra mixing options.
  3. Add vertically interpolated MLD diagnostics.
  • Property svn:keywords set to Id
File size: 16.3 KB
Line 
1MODULE restart
2   !!======================================================================
3   !!                     ***  MODULE  restart  ***
4   !! Ocean restart :  write the ocean restart file
5   !!======================================================================
6   !! History :  OPA  !  1999-11  (M. Imbard)  Original code
7   !!   NEMO     1.0  !  2002-08  (G. Madec)  F90: Free form
8   !!            2.0  !  2006-07  (S. Masson)  use IOM for restart
9   !!            3.3  !  2010-04  (M. Leclair, G. Madec)  modified LF-RA
10   !!            - -  !  2010-10  (C. Ethe, G. Madec) TRC-TRA merge (T-S in 4D)
11   !!            3.7  !  2014-01  (G. Madec) suppression of curl and hdiv from the restart
12   !!             -   !  2014-12  (G. Madec) remove KPP scheme
13   !!----------------------------------------------------------------------
14
15   !!----------------------------------------------------------------------
16   !!   rst_opn    : open the ocean restart file
17   !!   rst_write  : write the ocean restart file
18   !!   rst_read   : read the ocean restart file
19   !!----------------------------------------------------------------------
20   USE oce             ! ocean dynamics and tracers
21   USE dom_oce         ! ocean space and time domain
22   USE sbc_ice         ! only lk_lim3
23   USE phycst          ! physical constants
24   USE eosbn2          ! equation of state            (eos bn2 routine)
25   USE trdmxl_oce      ! ocean active mixed layer tracers trends variables
26   !
27   USE in_out_manager  ! I/O manager
28   USE iom             ! I/O module
29   USE ioipsl, ONLY : ju2ymds    ! for calendar
30   USE diurnal_bulk
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   rst_opn         ! routine called by step module
36   PUBLIC   rst_write       ! routine called by step module
37   PUBLIC   rst_read        ! routine called by istate module
38   PUBLIC   rst_read_open   ! routine called in rst_read and (possibly) in dom_vvl_init
39
40   !! * Substitutions
41#  include "vectopt_loop_substitute.h90"
42   !!----------------------------------------------------------------------
43   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
44   !! $Id$
45   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
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      INTEGER             ::   iyear, imonth, iday
62      REAL (wp)           ::   zsec
63      REAL (wp)           ::   zfjulday
64      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character
65      CHARACTER(LEN=50)   ::   clname   ! ocean output restart file name
66      CHARACTER(lc)       ::   clpath   ! full path to ocean output restart file
67      CHARACTER(LEN=52)   ::   clpname   ! ocean output restart file name including prefix for AGRIF
68      !!----------------------------------------------------------------------
69      !
70      IF( kt == nit000 ) THEN   ! default definitions
71         lrst_oce = .FALSE.   
72         IF( ln_rst_list ) THEN
73            nrst_lst = 1
74            nitrst = nstocklist( nrst_lst )
75         ELSE
76            nitrst = nitend
77         ENDIF
78      ENDIF
79
80      ! frequency-based restart dumping (nn_stock)
81      IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nstock ) == 0 ) THEN   
82         ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment
83         nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing
84         IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run
85      ENDIF
86      ! to get better performances with NetCDF format:
87      ! we open and define the ocean restart file one time step before writing the data (-> at nitrst - 1)
88      ! except if we write ocean restart files every time step or if an ocean restart file was writen at nitend - 1
89      IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend .AND. .NOT. lrst_oce ) ) THEN
90         IF( nitrst <= nitend .AND. nitrst > 0 ) THEN 
91            ! beware of the format used to write kt (default is i8.8, that should be large enough...)
92            IF ( ln_rstdate ) THEN
93               zfjulday = fjulday + rdt / rday
94               IF( ABS(zfjulday - REAL(NINT(zfjulday),wp)) < 0.1 / rday )   zfjulday = REAL(NINT(zfjulday),wp)   ! avoid truncation error
95               CALL ju2ymds( zfjulday, iyear, imonth, iday, zsec )           
96               WRITE(clkt, '(i4.4,2i2.2)') iyear, imonth, iday
97            ELSE
98               IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst
99               ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst
100               ENDIF
101            ENDIF
102            ! create the file
103            clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_ocerst_out)
104            clpath = TRIM(cn_ocerst_outdir)
105            IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
106            IF(lwp) THEN
107               WRITE(numout,*)
108               IF(.NOT.lwxios) THEN
109                  SELECT CASE ( jprstlib )
110                  CASE DEFAULT         ;   WRITE(numout,*)                            &
111                      '             open ocean restart NetCDF file: ',TRIM(clpath)//TRIM(clname)
112                  END SELECT
113                  IF ( snc4set%luse )      WRITE(numout,*) '             opened for NetCDF4 chunking and compression'
114                  IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt
115                  ELSE                          ;   WRITE(numout,*) '             kt = '             , kt
116                  ENDIF
117               ENDIF
118            ENDIF
119            !
120            IF(.NOT.lwxios) THEN
121               CALL iom_open( TRIM(clpath)//TRIM(clname), numrow, ldwrt = .TRUE., kiolib = jprstlib )
122            ELSE
123               cwxios_context = "rstw_"//TRIM(ADJUSTL(clkt))
124               IF( TRIM(Agrif_CFixed()) == '0' ) THEN
125                  clpname = clname
126               ELSE
127                  clpname = TRIM(Agrif_CFixed())//"_"//clname   
128               ENDIF
129               CALL iom_init( cwxios_context, TRIM(clpath)//TRIM(clpname))
130               CALL xios_update_calendar(nitrst)
131               CALL iom_swap(      cxios_context          )
132            ENDIF
133            lrst_oce = .TRUE.
134         ENDIF
135      ENDIF
136      !
137   END SUBROUTINE rst_opn
138
139
140   SUBROUTINE rst_write( kt )
141      !!---------------------------------------------------------------------
142      !!                   ***  ROUTINE rstwrite  ***
143      !!                     
144      !! ** Purpose :   Write restart fields in the format corresponding to jprstlib
145      !!
146      !! ** Method  :   Write in numrow when kt == nitrst in NetCDF
147      !!              file, save fields which are necessary for restart
148      !!----------------------------------------------------------------------
149      INTEGER, INTENT(in) ::   kt   ! ocean time-step
150      !!----------------------------------------------------------------------
151                     IF(lwxios) CALL iom_swap(      cwxios_context          )
152                     CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       , ldxios = lwxios)   ! dynamics time step
153
154      IF ( .NOT. ln_diurnal_only ) THEN
155                     CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub, ldxios = lwxios        )     ! before fields
156                     CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb, ldxios = lwxios        )
157                     CALL iom_rstput( kt, nitrst, numrow, 'tb'     , tsb(:,:,:,jp_tem), ldxios = lwxios )
158                     CALL iom_rstput( kt, nitrst, numrow, 'sb'     , tsb(:,:,:,jp_sal), ldxios = lwxios )
159                     CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , sshb, ldxios = lwxios      )
160                     !
161                     CALL iom_rstput( kt, nitrst, numrow, 'un'     , un, ldxios = lwxios        )     ! now fields
162                     CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vn, ldxios = lwxios        )
163                     CALL iom_rstput( kt, nitrst, numrow, 'tn'     , tsn(:,:,:,jp_tem), ldxios = lwxios )
164                     CALL iom_rstput( kt, nitrst, numrow, 'sn'     , tsn(:,:,:,jp_sal), ldxios = lwxios )
165                     CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , sshn, ldxios = lwxios      )
166                     CALL iom_rstput( kt, nitrst, numrow, 'rhop'   , rhop, ldxios = lwxios      )
167                  ! extra variable needed for the ice sheet coupling
168                  IF ( ln_iscpl ) THEN
169                     CALL iom_rstput( kt, nitrst, numrow, 'tmask'  , tmask, ldxios = lwxios ) ! need to extrapolate T/S
170                     CALL iom_rstput( kt, nitrst, numrow, 'umask'  , umask, ldxios = lwxios ) ! need to correct barotropic velocity
171                     CALL iom_rstput( kt, nitrst, numrow, 'vmask'  , vmask, ldxios = lwxios ) ! need to correct barotropic velocity
172                     CALL iom_rstput( kt, nitrst, numrow, 'smask'  , ssmask, ldxios = lwxios) ! need to correct barotropic velocity
173                     CALL iom_rstput( kt, nitrst, numrow, 'e3t_n', e3t_n(:,:,:), ldxios = lwxios )   ! need to compute temperature correction
174                     CALL iom_rstput( kt, nitrst, numrow, 'e3u_n', e3u_n(:,:,:), ldxios = lwxios )   ! need to compute bt conservation
175                     CALL iom_rstput( kt, nitrst, numrow, 'e3v_n', e3v_n(:,:,:), ldxios = lwxios )   ! need to compute bt conservation
176                     CALL iom_rstput( kt, nitrst, numrow, 'gdepw_n', gdepw_n(:,:,:), ldxios = lwxios ) ! need to compute extrapolation if vvl
177                  END IF
178      ENDIF
179     
180      IF (ln_diurnal) CALL iom_rstput( kt, nitrst, numrow, 'Dsst', x_dsst, ldxios = lwxios ) 
181      IF(lwxios) CALL iom_swap(      cxios_context          )
182      IF( kt == nitrst ) THEN
183         IF(.NOT.lwxios) THEN
184            CALL iom_close( numrow )     ! close the restart file (only at last time step)
185         ELSE
186            CALL iom_context_finalize(      cwxios_context          )
187         ENDIF
188!!gm         IF( .NOT. lk_trdmld )   lrst_oce = .FALSE.
189!!gm  not sure what to do here   ===>>>  ask to Sebastian
190         lrst_oce = .FALSE.
191            IF( ln_rst_list ) THEN
192               nrst_lst = MIN(nrst_lst + 1, SIZE(nstocklist,1))
193               nitrst = nstocklist( nrst_lst )
194            ENDIF
195      ENDIF
196      !
197   END SUBROUTINE rst_write
198
199
200   SUBROUTINE rst_read_open
201      !!----------------------------------------------------------------------
202      !!                   ***  ROUTINE rst_read_open  ***
203      !!
204      !! ** Purpose :   Open read files for restart (format fixed by jprstlib )
205      !!
206      !! ** Method  :   Use a non-zero, positive value of numror to assess whether or not
207      !!                the file has already been opened
208      !!----------------------------------------------------------------------
209      INTEGER        ::   jlibalt = jprstlib
210      LOGICAL        ::   llok
211      CHARACTER(lc)  ::   clpath   ! full path to ocean output restart file
212      !!----------------------------------------------------------------------
213      !
214      IF( numror <= 0 ) THEN
215         IF(lwp) THEN                                             ! Contol prints
216            WRITE(numout,*)
217            SELECT CASE ( jprstlib )
218            CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file'
219            END SELECT
220            IF ( snc4set%luse )      WRITE(numout,*) 'rst_read : configured with NetCDF4 support'
221            WRITE(numout,*) '~~~~~~~~'
222         ENDIF
223         lxios_sini = .FALSE.
224         clpath = TRIM(cn_ocerst_indir)
225         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
226         CALL iom_open( TRIM(clpath)//cn_ocerst_in, numror, kiolib = jlibalt )
227! are we using XIOS to read the data? Part above will have to modified once XIOS
228! can handle checking if variable is in the restart file (there will be no need to open
229! restart)
230         IF(.NOT.lxios_set) lrxios = lrxios.AND.lxios_sini
231         IF( lrxios) THEN
232             crxios_context = 'nemo_rst'
233             IF( .NOT.lxios_set ) THEN
234                 IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS'
235                 CALL iom_init( crxios_context )
236                 lxios_set = .TRUE.
237             ENDIF
238         ENDIF
239         IF( TRIM(Agrif_CFixed()) /= '0' .AND. lrxios) THEN
240             CALL iom_init( crxios_context )
241             IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS for AGRIF'
242             lxios_set = .TRUE.
243         ENDIF
244      ENDIF
245
246   END SUBROUTINE rst_read_open
247
248
249   SUBROUTINE rst_read
250      !!----------------------------------------------------------------------
251      !!                   ***  ROUTINE rst_read  ***
252      !!
253      !! ** Purpose :   Read files for restart (format fixed by jprstlib )
254      !!
255      !! ** Method  :   Read in restart.nc file fields which are necessary for restart
256      !!----------------------------------------------------------------------
257      REAL(wp) ::   zrdt
258      INTEGER  ::   jk
259      REAL(wp), DIMENSION(jpi, jpj, jpk) :: w3d
260      !!----------------------------------------------------------------------
261
262      CALL rst_read_open           ! open restart for reading (if not already opened)
263
264      ! Check dynamics and tracer time-step consistency and force Euler restart if changed
265      IF( iom_varid( numror, 'rdt', ldstop = .FALSE. ) > 0 )   THEN
266         CALL iom_get( numror, 'rdt', zrdt, ldxios = lrxios )
267         IF( zrdt /= rdt )   neuler = 0
268      ENDIF
269
270      ! Diurnal DSST
271      IF( ln_diurnal ) CALL iom_get( numror, jpdom_autoglo, 'Dsst' , x_dsst, ldxios = lrxios ) 
272      IF ( ln_diurnal_only ) THEN
273         IF(lwp) WRITE( numout, * ) &
274         &   "rst_read:- ln_diurnal_only set, setting rhop=rau0" 
275         rhop = rau0
276         CALL iom_get( numror, jpdom_autoglo, 'tn'     , w3d, ldxios = lrxios ) 
277         tsn(:,:,1,jp_tem) = w3d(:,:,1)
278         RETURN
279      ENDIF 
280     
281      IF( iom_varid( numror, 'ub', ldstop = .FALSE. ) > 0 ) THEN
282         CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub, ldxios = lrxios                )   ! before fields
283         CALL iom_get( numror, jpdom_autoglo, 'vb'     , vb, ldxios = lrxios                )
284         CALL iom_get( numror, jpdom_autoglo, 'tb'     , tsb(:,:,:,jp_tem), ldxios = lrxios )
285         CALL iom_get( numror, jpdom_autoglo, 'sb'     , tsb(:,:,:,jp_sal), ldxios = lrxios )
286         CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb, ldxios = lrxios              )
287      ELSE
288         neuler = 0
289      ENDIF
290      !
291      CALL iom_get( numror, jpdom_autoglo, 'un'     , un, ldxios = lrxios )   ! now    fields
292      CALL iom_get( numror, jpdom_autoglo, 'vn'     , vn, ldxios = lrxios )
293      CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,:,jp_tem), ldxios = lrxios )
294      CALL iom_get( numror, jpdom_autoglo, 'sn'     , tsn(:,:,:,jp_sal), ldxios = lrxios )
295      CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn, ldxios = lrxios )
296      IF( iom_varid( numror, 'rhop', ldstop = .FALSE. ) > 0 ) THEN
297         CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop, ldxios = lrxios )   ! now    potential density
298      ELSE
299         CALL eos( tsn, rhd, rhop, gdept_n(:,:,:) )   
300      ENDIF
301      !
302      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0)
303         tsb  (:,:,:,:) = tsn  (:,:,:,:)                             ! all before fields set to now values
304         ub   (:,:,:)   = un   (:,:,:)
305         vb   (:,:,:)   = vn   (:,:,:)
306         sshb (:,:)     = sshn (:,:)
307         !
308         IF( .NOT.ln_linssh ) THEN
309            DO jk = 1, jpk
310               e3t_b(:,:,jk) = e3t_n(:,:,jk)
311            END DO
312         ENDIF
313         !
314      ENDIF
315      !
316   END SUBROUTINE rst_read
317
318   !!=====================================================================
319END MODULE restart
Note: See TracBrowser for help on using the repository browser.