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

source: trunk/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90 @ 4528

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