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

source: branches/UKMO/dev_r5518_GO6_package_XIOS_read/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90 @ 8014

Last change on this file since 8014 was 8009, checked in by andmirek, 7 years ago

remove prints

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