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_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/IOM – NEMO

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90 @ 11101

Last change on this file since 11101 was 11101, checked in by frrh, 5 years ago

Merge changes from Met Office GMED ticket 450 to reduce unnecessary
text output from NEMO.
This output, which is typically not switchable, is rarely of interest
in normal (non-debugging) runs and simply redunantley consumes extra
file space.
Further, the presence of this text output has been shown to
significantly degrade performance of models which are run during
Met Office HPC RAID (disk) checks.
The new code introduces switches which are configurable via the
changes made in the associated Met Office MOCI ticket 399.

File size: 17.0 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   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   rst_opn    : open the ocean restart file
15   !!   rst_write  : write the ocean restart file
16   !!   rst_read   : read the ocean restart file
17   !!----------------------------------------------------------------------
18   USE oce             ! ocean dynamics and tracers
19   USE dom_oce         ! ocean space and time domain
20   USE phycst          ! physical constants
21   USE in_out_manager  ! I/O manager
22   USE iom             ! I/O module
23   USE ioipsl, ONLY : ju2ymds    ! for calendar
24   USE eosbn2          ! equation of state            (eos bn2 routine)
25   USE trdmxl_oce      ! ocean active mixed layer tracers trends variables
26   USE divcur          ! hor. divergence and curl      (div & cur routines)
27   USE sbc_oce         ! for icesheet freshwater input variables
28   USE timing
29
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC   rst_opn         ! routine called by step module
34   PUBLIC   rst_write       ! routine called by step module
35   PUBLIC   rst_read        ! routine called by istate module
36   PUBLIC   rst_read_open   ! routine called in rst_read and (possibly) in dom_vvl_init
37
38   !! * Substitutions
39#  include "domzgr_substitute.h90"
40#  include "vectopt_loop_substitute.h90"
41   !!----------------------------------------------------------------------
42   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
43   !! $Id$
44   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
45   !!----------------------------------------------------------------------
46CONTAINS
47
48   SUBROUTINE rst_opn( kt )
49      !!---------------------------------------------------------------------
50      !!                   ***  ROUTINE rst_opn  ***
51      !!                     
52      !! ** Purpose : + initialization (should be read in the namelist) of nitrst
53      !!              + open the restart when we are one time step before nitrst
54      !!                   - restart header is defined when kt = nitrst-1
55      !!                   - restart data  are written when kt = nitrst
56      !!              + define lrst_oce to .TRUE. when we need to define or write the restart
57      !!----------------------------------------------------------------------
58      INTEGER, INTENT(in) ::   kt     ! ocean time-step
59      INTEGER             ::   iyear, imonth, iday
60      REAL (wp)           ::   zsec
61      REAL (wp)           ::   zfjulday
62      !!
63      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character
64      CHARACTER(LEN=50)   ::   clname   ! ocean output restart file name
65      CHARACTER(LEN=150)  ::   clpath   ! full path to ocean output restart file
66      !!----------------------------------------------------------------------
67      !
68      IF( kt == nit000 ) THEN   ! default definitions
69         lrst_oce = .FALSE.   
70         IF( ln_rst_list ) THEN
71            nrst_lst = 1
72            nitrst = nstocklist( nrst_lst )
73         ELSE
74            nitrst = nitend
75         ENDIF
76      ENDIF
77
78      ! frequency-based restart dumping (nn_stock)
79      IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nstock ) == 0 ) THEN   
80         ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment
81         nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing
82         IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run
83      ENDIF
84      ! to get better performances with NetCDF format:
85      ! we open and define the ocean restart file one time step before writing the data (-> at nitrst - 1)
86      ! except if we write ocean restart files every time step or if an ocean restart file was writen at nitend - 1
87      IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend .AND. .NOT. lrst_oce ) ) THEN
88         IF( nitrst <= nitend .AND. nitrst > 0 ) THEN
89            IF ( ln_rstdate ) THEN
90               zfjulday = fjulday + rdttra(1) / rday
91               IF( ABS(zfjulday - REAL(NINT(zfjulday),wp)) < 0.1 / rday )   zfjulday = REAL(NINT(zfjulday),wp)   ! avoid truncation error
92               CALL ju2ymds( zfjulday, iyear, imonth, iday, zsec )           
93               WRITE(clkt, '(i4.4,2i2.2)') iyear, imonth, iday
94            ELSE
95               ! beware of the format used to write kt (default is i8.8, that should be large enough...)
96               IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst
97               ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst
98               ENDIF
99            ENDIF
100            ! create the file
101            clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_ocerst_out)
102            clpath = TRIM(cn_ocerst_outdir)
103            IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
104            IF(lwp) THEN
105               WRITE(numout,*)
106               SELECT CASE ( jprstlib )
107               CASE ( jprstdimg )   ;   WRITE(numout,*)                            &
108                   '             open ocean restart binary file: ',TRIM(clpath)//clname
109               CASE DEFAULT         ;   WRITE(numout,*)                            &
110                   '             open ocean restart NetCDF file: ',TRIM(clpath)//clname
111               END SELECT
112               IF(nprint > 1) THEN
113                  IF ( snc4set%luse )      WRITE(numout,*) '             opened for NetCDF4 chunking and compression'
114                  IF( kt == nitrst - 1) THEN
115                     WRITE(numout,*) '             kt = nitrst - 1 = ', kt
116                  ELSE                         
117                     WRITE(numout,*) '             kt = '             , kt
118                  ENDIF
119               ENDIF
120               IF(lflush) CALL flush(numout)
121            ENDIF
122            !
123            CALL iom_open( TRIM(clpath)//TRIM(clname), numrow, ldwrt = .TRUE., kiolib = jprstlib )
124            lrst_oce = .TRUE.
125         ENDIF
126      ENDIF
127      !
128   END SUBROUTINE rst_opn
129
130
131   SUBROUTINE rst_write( kt )
132      !!---------------------------------------------------------------------
133      !!                   ***  ROUTINE rstwrite  ***
134      !!                     
135      !! ** Purpose :   Write restart fields in the format corresponding to jprstlib
136      !!
137      !! ** Method  :   Write in numrow when kt == nitrst in NetCDF
138      !!              file, save fields which are necessary for restart
139      !!----------------------------------------------------------------------
140      INTEGER, INTENT(in) ::   kt   ! ocean time-step
141      !!----------------------------------------------------------------------
142                     IF(nn_timing == 2)  CALL timing_start('iom_rstput')
143                     CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics time step
144                     CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1) )   ! surface tracer time step
145
146                     CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub        )     ! before fields
147                     CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb        )
148                     CALL iom_rstput( kt, nitrst, numrow, 'tb'     , tsb(:,:,:,jp_tem) )
149                     CALL iom_rstput( kt, nitrst, numrow, 'sb'     , tsb(:,:,:,jp_sal) )
150                     CALL iom_rstput( kt, nitrst, numrow, 'rotb'   , rotb      )
151                     CALL iom_rstput( kt, nitrst, numrow, 'hdivb'  , hdivb     )
152                     CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , sshb      )
153                     !
154                     CALL iom_rstput( kt, nitrst, numrow, 'un'     , un        )     ! now fields
155                     CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vn        )
156                     CALL iom_rstput( kt, nitrst, numrow, 'tn'     , tsn(:,:,:,jp_tem) )
157                     CALL iom_rstput( kt, nitrst, numrow, 'sn'     , tsn(:,:,:,jp_sal) )
158                     CALL iom_rstput( kt, nitrst, numrow, 'rotn'   , rotn      )
159                     CALL iom_rstput( kt, nitrst, numrow, 'hdivn'  , hdivn     )
160                     CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , sshn      )
161                     CALL iom_rstput( kt, nitrst, numrow, 'rhop'   , rhop      )
162#if defined key_zdfkpp
163                     CALL iom_rstput( kt, nitrst, numrow, 'rhd'    , rhd       )
164#endif
165                     IF( lk_oasis) THEN
166                     ! nn_coupled_iceshelf_fluxes uninitialised unless lk_oasis=true
167                     IF( nn_coupled_iceshelf_fluxes .eq. 1 ) THEN
168                        CALL iom_rstput( kt, nitrst, numrow, 'greenland_icesheet_mass', greenland_icesheet_mass )
169                        CALL iom_rstput( kt, nitrst, numrow, 'greenland_icesheet_timelapsed', greenland_icesheet_timelapsed )
170                        CALL iom_rstput( kt, nitrst, numrow, 'greenland_icesheet_mass_roc', greenland_icesheet_mass_rate_of_change )
171                        CALL iom_rstput( kt, nitrst, numrow, 'antarctica_icesheet_mass', antarctica_icesheet_mass )
172                        CALL iom_rstput( kt, nitrst, numrow, 'antarctica_icesheet_timelapsed', antarctica_icesheet_timelapsed )
173                        CALL iom_rstput( kt, nitrst, numrow, 'antarctica_icesheet_mass_roc', antarctica_icesheet_mass_rate_of_change )
174                     ENDIF
175                     ENDIF
176                     IF(nn_timing == 2)  CALL timing_stop('iom_rstput')
177
178      IF( kt == nitrst ) THEN
179         CALL iom_close( numrow )     ! close the restart file (only at last time step)
180!!gm         IF( .NOT. lk_trdmld )   lrst_oce = .FALSE.
181!!gm  not sure what to do here   ===>>>  ask to Sebastian
182         lrst_oce = .FALSE.
183            IF( ln_rst_list ) THEN
184               nrst_lst = MIN(nrst_lst + 1, SIZE(nstocklist,1))
185               nitrst = nstocklist( nrst_lst )
186            ENDIF
187            lrst_oce = .FALSE.
188      ENDIF
189      !
190   END SUBROUTINE rst_write
191
192
193   SUBROUTINE rst_read_open
194      !!----------------------------------------------------------------------
195      !!                   ***  ROUTINE rst_read_open  ***
196      !!
197      !! ** Purpose :   Open read files for restart (format fixed by jprstlib )
198      !!
199      !! ** Method  :   Use a non-zero, positive value of numror to assess whether or not
200      !!                the file has already been opened
201      !!----------------------------------------------------------------------
202      INTEGER        ::   jlibalt = jprstlib
203      LOGICAL        ::   llok
204      CHARACTER(lc)  ::   clpath   ! full path to ocean output restart file
205      !!----------------------------------------------------------------------
206      !
207      IF( numror <= 0 ) THEN
208         IF(lwp) THEN                                             ! Contol prints
209            WRITE(numout,*)
210            SELECT CASE ( jprstlib )
211            CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file'
212            CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file'
213            END SELECT
214            IF ( snc4set%luse )      WRITE(numout,*) 'rst_read : configured with NetCDF4 support'
215            WRITE(numout,*) '~~~~~~~~'
216            IF(lflush) CALL flush(numout)
217         ENDIF
218
219         clpath = TRIM(cn_ocerst_indir)
220         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
221         IF ( jprstlib == jprstdimg ) THEN
222           ! eventually read netcdf file (monobloc)  for restarting on different number of processors
223           ! if {cn_ocerst_in}.nc exists, then set jlibalt to jpnf90
224           INQUIRE( FILE = TRIM(cn_ocerst_indir)//'/'//TRIM(cn_ocerst_in)//'.nc', EXIST = llok )
225           IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF
226         ENDIF
227         CALL iom_open( TRIM(clpath)//cn_ocerst_in, numror, kiolib = jlibalt )
228      ENDIF
229   END SUBROUTINE rst_read_open
230
231   SUBROUTINE rst_read
232      !!----------------------------------------------------------------------
233      !!                   ***  ROUTINE rst_read  ***
234      !!
235      !! ** Purpose :   Read files for restart (format fixed by jprstlib )
236      !!
237      !! ** Method  :   Read in restart.nc file fields which are necessary for restart
238      !!----------------------------------------------------------------------
239      REAL(wp) ::   zrdt, zrdttra1
240      INTEGER  ::   jk
241      LOGICAL  ::   llok
242      !!----------------------------------------------------------------------
243
244      CALL rst_read_open           ! open restart for reading (if not already opened)
245
246      ! Check dynamics and tracer time-step consistency and force Euler restart if changed
247      IF(nn_timing == 2)  CALL timing_start('iom_rstget')
248      IF( iom_varid( numror, 'rdt', ldstop = .FALSE. ) > 0 )   THEN
249         CALL iom_get( numror, 'rdt', zrdt )
250         IF( zrdt /= rdt )   neuler = 0
251      ENDIF
252      IF( iom_varid( numror, 'rdttra1', ldstop = .FALSE. ) > 0 )   THEN
253         CALL iom_get( numror, 'rdttra1', zrdttra1 )
254         IF( zrdttra1 /= rdttra(1) )   neuler = 0
255      ENDIF
256      !
257      IF( iom_varid( numror, 'ub', ldstop = .FALSE. ) > 0 ) THEN
258         CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub      )   ! before fields
259         CALL iom_get( numror, jpdom_autoglo, 'vb'     , vb      )
260         CALL iom_get( numror, jpdom_autoglo, 'tb'     , tsb(:,:,:,jp_tem) )
261         CALL iom_get( numror, jpdom_autoglo, 'sb'     , tsb(:,:,:,jp_sal) )
262         CALL iom_get( numror, jpdom_autoglo, 'rotb'   , rotb    )
263         CALL iom_get( numror, jpdom_autoglo, 'hdivb'  , hdivb   )
264         CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb    )
265      ELSE
266         neuler = 0
267      ENDIF
268      !
269      CALL iom_get( numror, jpdom_autoglo, 'un'     , un      )   ! now    fields
270      CALL iom_get( numror, jpdom_autoglo, 'vn'     , vn      )
271      CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,:,jp_tem) )
272      CALL iom_get( numror, jpdom_autoglo, 'sn'     , tsn(:,:,:,jp_sal) )
273      CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn    )
274      IF( iom_varid( numror, 'rotn', ldstop = .FALSE. ) > 0 ) THEN
275         CALL iom_get( numror, jpdom_autoglo, 'rotn'   , rotn    )
276         CALL iom_get( numror, jpdom_autoglo, 'hdivn'  , hdivn   )
277      ELSE
278         CALL div_cur( 0 )                              ! Horizontal divergence & Relative vorticity
279      ENDIF
280      IF( iom_varid( numror, 'rhop', ldstop = .FALSE. ) > 0 ) THEN
281         CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop    )   ! now    potential density
282      ELSE
283         CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) )   
284      ENDIF
285#if defined key_zdfkpp
286      IF( iom_varid( numror, 'rhd', ldstop = .FALSE. ) > 0 ) THEN
287         CALL iom_get( numror, jpdom_autoglo, 'rhd'    , rhd     )   ! now    in situ density anomaly
288      ELSE
289         CALL eos( tsn, rhd, fsdept_n(:,:,:) )   ! compute rhd
290      ENDIF
291#endif
292      !
293      IF( iom_varid( numror, 'greenland_icesheet_mass', ldstop = .FALSE. ) > 0 )   THEN
294         CALL iom_get( numror, 'greenland_icesheet_mass', greenland_icesheet_mass )
295         CALL iom_get( numror, 'greenland_icesheet_timelapsed', greenland_icesheet_timelapsed )
296         CALL iom_get( numror, 'greenland_icesheet_mass_roc', greenland_icesheet_mass_rate_of_change )
297      ELSE
298         greenland_icesheet_mass = 0.0 
299         greenland_icesheet_mass_rate_of_change = 0.0 
300         greenland_icesheet_timelapsed = 0.0
301      ENDIF
302      IF( iom_varid( numror, 'antarctica_icesheet_mass', ldstop = .FALSE. ) > 0 )   THEN
303         CALL iom_get( numror, 'antarctica_icesheet_mass', antarctica_icesheet_mass )
304         CALL iom_get( numror, 'antarctica_icesheet_timelapsed', antarctica_icesheet_timelapsed )
305         CALL iom_get( numror, 'antarctica_icesheet_mass_roc', antarctica_icesheet_mass_rate_of_change )
306      ELSE
307         antarctica_icesheet_mass = 0.0 
308         antarctica_icesheet_mass_rate_of_change = 0.0 
309         antarctica_icesheet_timelapsed = 0.0
310      ENDIF
311      IF(nn_timing == 2)  CALL timing_stop('iom_rstget')
312      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0)
313         tsb  (:,:,:,:) = tsn  (:,:,:,:)                             ! all before fields set to now values
314         ub   (:,:,:)   = un   (:,:,:)
315         vb   (:,:,:)   = vn   (:,:,:)
316         rotb (:,:,:)   = rotn (:,:,:)
317         hdivb(:,:,:)   = hdivn(:,:,:)
318         sshb (:,:)     = sshn (:,:)
319
320         IF( lk_vvl ) THEN
321            DO jk = 1, jpk
322               fse3t_b(:,:,jk) = fse3t_n(:,:,jk)
323            END DO
324         ENDIF
325
326      ENDIF
327      !
328   END SUBROUTINE rst_read
329
330   !!=====================================================================
331END MODULE restart
Note: See TracBrowser for help on using the repository browser.