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

source: branches/2013/dev_MERGE_2013/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90 @ 4333

Last change on this file since 4333 was 4333, checked in by clem, 10 years ago

remove remaining bugs in LIM3, so that it can run in both regional and global config

  • Property svn:keywords set to Id
File size: 13.1 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 eosbn2          ! equation of state            (eos bn2 routine)
24   USE trdmld_oce      ! ocean active mixed layer tracers trends variables
25   USE domvvl          ! variable volume
26   USE divcur          ! hor. divergence and curl      (div & cur routines)
27   USE sbc_ice, ONLY : lk_lim3
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 istate module
35   PUBLIC   rst_read_open   ! routine called in rst_read and (possibly) in dom_vvl_init
36
37   !! * Substitutions
38#  include "domzgr_substitute.h90"
39#  include "vectopt_loop_substitute.h90"
40   !!----------------------------------------------------------------------
41   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
42   !! $Id$
43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45CONTAINS
46
47   SUBROUTINE rst_opn( kt )
48      !!---------------------------------------------------------------------
49      !!                   ***  ROUTINE rst_opn  ***
50      !!                     
51      !! ** Purpose : + initialization (should be read in the namelist) of nitrst
52      !!              + open the restart when we are one time step before nitrst
53      !!                   - restart header is defined when kt = nitrst-1
54      !!                   - restart data  are written when kt = nitrst
55      !!              + define lrst_oce to .TRUE. when we need to define or write the restart
56      !!----------------------------------------------------------------------
57      INTEGER, INTENT(in) ::   kt     ! ocean time-step
58      !!
59      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character
60      CHARACTER(LEN=50)   ::   clname   ! ice output restart file name
61      !!----------------------------------------------------------------------
62      !
63      IF( kt == nit000 ) THEN   ! default definitions
64         lrst_oce = .FALSE.   
65         nitrst = nitend
66      ENDIF
67      IF( MOD( kt - 1, nstock ) == 0 ) THEN   
68         ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment
69         nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing
70         IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run
71      ENDIF
72      ! to get better performances with NetCDF format:
73      ! we open and define the ocean restart file one time step before writing the data (-> at nitrst - 1)
74      ! except if we write ocean restart files every time step or if an ocean restart file was writen at nitend - 1
75      IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend .AND. .NOT. lrst_oce ) ) THEN
76         ! beware of the format used to write kt (default is i8.8, that should be large enough...)
77         IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst
78         ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst
79         ENDIF
80         ! create the file
81         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_ocerst_out)
82         IF(lwp) THEN
83            WRITE(numout,*)
84            SELECT CASE ( jprstlib )
85            CASE ( jprstdimg )   ;   WRITE(numout,*) '             open ocean restart binary file: '//clname
86            CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart NetCDF file: '//clname
87            END SELECT
88            IF ( snc4set%luse )      WRITE(numout,*) '             opened for NetCDF4 chunking and compression'
89            IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt
90            ELSE                          ;   WRITE(numout,*) '             kt = '             , kt
91            ENDIF
92         ENDIF
93         !
94         CALL iom_open( clname, numrow, ldwrt = .TRUE., kiolib = jprstlib )
95         lrst_oce = .TRUE.
96      ENDIF
97      !
98   END SUBROUTINE rst_opn
99
100
101   SUBROUTINE rst_write( kt )
102      !!---------------------------------------------------------------------
103      !!                   ***  ROUTINE rstwrite  ***
104      !!                     
105      !! ** Purpose :   Write restart fields in the format corresponding to jprstlib
106      !!
107      !! ** Method  :   Write in numrow when kt == nitrst in NetCDF
108      !!              file, save fields which are necessary for restart
109      !!----------------------------------------------------------------------
110      INTEGER, INTENT(in) ::   kt   ! ocean time-step
111      !!----------------------------------------------------------------------
112
113                     CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics time step
114                     CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1) )   ! surface tracer time step
115
116                     CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub        )     ! before fields
117                     CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb        )
118                     CALL iom_rstput( kt, nitrst, numrow, 'tb'     , tsb(:,:,:,jp_tem) )
119                     CALL iom_rstput( kt, nitrst, numrow, 'sb'     , tsb(:,:,:,jp_sal) )
120                     CALL iom_rstput( kt, nitrst, numrow, 'rotb'   , rotb      )
121                     CALL iom_rstput( kt, nitrst, numrow, 'hdivb'  , hdivb     )
122                     CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , sshb      )
123                     !
124                     CALL iom_rstput( kt, nitrst, numrow, 'un'     , un        )     ! now fields
125                     CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vn        )
126                     CALL iom_rstput( kt, nitrst, numrow, 'tn'     , tsn(:,:,:,jp_tem) )
127                     CALL iom_rstput( kt, nitrst, numrow, 'sn'     , tsn(:,:,:,jp_sal) )
128                     CALL iom_rstput( kt, nitrst, numrow, 'rotn'   , rotn      )
129                     CALL iom_rstput( kt, nitrst, numrow, 'hdivn'  , hdivn     )
130                     CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , sshn      )
131                     CALL iom_rstput( kt, nitrst, numrow, 'rhop'   , rhop      )
132#if defined key_zdfkpp
133                     CALL iom_rstput( kt, nitrst, numrow, 'rhd'    , rhd       )
134#endif
135                  IF( lk_lim3 ) THEN
136                     CALL iom_rstput( kt, nitrst, numrow, 'iatte'  , iatte     ) !clem modif
137                     CALL iom_rstput( kt, nitrst, numrow, 'oatte'  , oatte     ) !clem modif
138                  ENDIF
139      IF( kt == nitrst ) THEN
140         CALL iom_close( numrow )     ! close the restart file (only at last time step)
141         IF( .NOT. lk_trdmld )   lrst_oce = .FALSE.
142      ENDIF
143      !
144   END SUBROUTINE rst_write
145
146   SUBROUTINE rst_read_open
147      !!----------------------------------------------------------------------
148      !!                   ***  ROUTINE rst_read_open  ***
149      !!
150      !! ** Purpose :   Open read files for restart (format fixed by jprstlib )
151      !!
152      !! ** Method  :   Use a non-zero, positive value of numror to assess whether or not
153      !!                the file has already been opened
154      !!----------------------------------------------------------------------
155      INTEGER  ::   jlibalt = jprstlib
156      LOGICAL  ::   llok
157      !!----------------------------------------------------------------------
158
159      IF( numror .LE. 0 ) THEN
160         IF(lwp) THEN                                             ! Contol prints
161            WRITE(numout,*)
162            SELECT CASE ( jprstlib )
163            CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file'
164            CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file'
165            END SELECT
166            IF ( snc4set%luse )      WRITE(numout,*) 'rst_read : configured with NetCDF4 support'
167            WRITE(numout,*) '~~~~~~~~'
168         ENDIF
169
170         IF ( jprstlib == jprstdimg ) THEN
171           ! eventually read netcdf file (monobloc)  for restarting on different number of processors
172           ! if {cn_ocerst_in}.nc exists, then set jlibalt to jpnf90
173           INQUIRE( FILE = TRIM(cn_ocerst_in)//'.nc', EXIST = llok )
174           IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF
175         ENDIF
176         CALL iom_open( cn_ocerst_in, numror, kiolib = jlibalt )
177      ENDIF
178   END SUBROUTINE rst_read_open
179
180   SUBROUTINE rst_read
181      !!----------------------------------------------------------------------
182      !!                   ***  ROUTINE rst_read  ***
183      !!
184      !! ** Purpose :   Read files for restart (format fixed by jprstlib )
185      !!
186      !! ** Method  :   Read in restart.nc file fields which are necessary for restart
187      !!----------------------------------------------------------------------
188      REAL(wp) ::   zrdt, zrdttra1
189      INTEGER  ::   jk
190      LOGICAL  ::   llok
191      !!----------------------------------------------------------------------
192
193      CALL rst_read_open           ! open restart for reading (if not already opened)
194
195      ! Check dynamics and tracer time-step consistency and force Euler restart if changed
196      IF( iom_varid( numror, 'rdt', ldstop = .FALSE. ) > 0 )   THEN
197         CALL iom_get( numror, 'rdt', zrdt )
198         IF( zrdt /= rdt )   neuler = 0
199      ENDIF
200      IF( iom_varid( numror, 'rdttra1', ldstop = .FALSE. ) > 0 )   THEN
201         CALL iom_get( numror, 'rdttra1', zrdttra1 )
202         IF( zrdttra1 /= rdttra(1) )   neuler = 0
203      ENDIF
204      !
205      IF( iom_varid( numror, 'ub', ldstop = .FALSE. ) > 0 ) THEN
206         CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub      )   ! before fields
207         CALL iom_get( numror, jpdom_autoglo, 'vb'     , vb      )
208         CALL iom_get( numror, jpdom_autoglo, 'tb'     , tsb(:,:,:,jp_tem) )
209         CALL iom_get( numror, jpdom_autoglo, 'sb'     , tsb(:,:,:,jp_sal) )
210         CALL iom_get( numror, jpdom_autoglo, 'rotb'   , rotb    )
211         CALL iom_get( numror, jpdom_autoglo, 'hdivb'  , hdivb   )
212         CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb    )
213         IF( lk_vvl )   CALL iom_get( numror, jpdom_autoglo, 'fse3t_b', fse3t_b(:,:,:) )
214      ELSE
215         neuler = 0
216      ENDIF
217      !
218      CALL iom_get( numror, jpdom_autoglo, 'un'     , un      )   ! now    fields
219      CALL iom_get( numror, jpdom_autoglo, 'vn'     , vn      )
220      CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,:,jp_tem) )
221      CALL iom_get( numror, jpdom_autoglo, 'sn'     , tsn(:,:,:,jp_sal) )
222      CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn    )
223      IF( iom_varid( numror, 'rotn', ldstop = .FALSE. ) > 0 ) THEN
224         CALL iom_get( numror, jpdom_autoglo, 'rotn'   , rotn    )
225         CALL iom_get( numror, jpdom_autoglo, 'hdivn'  , hdivn   )
226      ELSE
227         CALL div_cur( 0 )                              ! Horizontal divergence & Relative vorticity
228      ENDIF
229      IF( iom_varid( numror, 'rhop', ldstop = .FALSE. ) > 0 ) THEN
230         CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop    )   ! now    potential density
231      ELSE
232         CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) )   
233      ENDIF
234#if defined key_zdfkpp
235      IF( iom_varid( numror, 'rhd', ldstop = .FALSE. ) > 0 ) THEN
236         CALL iom_get( numror, jpdom_autoglo, 'rhd'    , rhd     )   ! now    in situ density anomaly
237      ELSE
238         CALL eos( tsn, rhd, fsdept_n(:,:,:) )   ! compute rhd
239      ENDIF
240#endif
241      !
242      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0)
243         tsb  (:,:,:,:) = tsn  (:,:,:,:)                             ! all before fields set to now values
244         ub   (:,:,:)   = un   (:,:,:)
245         vb   (:,:,:)   = vn   (:,:,:)
246         rotb (:,:,:)   = rotn (:,:,:)
247         hdivb(:,:,:)   = hdivn(:,:,:)
248         sshb (:,:)     = sshn (:,:)
249      ENDIF
250      !
251      IF( lk_lim3 ) THEN
252         CALL iom_get( numror, jpdom_autoglo, 'iatte' , iatte ) ! clem modif
253         CALL iom_get( numror, jpdom_autoglo, 'oatte' , oatte ) ! clem modif
254      ENDIF
255      !
256   END SUBROUTINE rst_read
257
258   !!=====================================================================
259END MODULE restart
Note: See TracBrowser for help on using the repository browser.