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

source: branches/2012/dev_r3452_UKMO9_RESTART/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90 @ 3594

Last change on this file since 3594 was 3594, checked in by rfurner, 11 years ago

code not tested through SETTEE, builds and runs, but has not been thoroughly tested, so will not be included in 2012 merge, however submitted back to keep record of work done for 2013 developments

  • Property svn:keywords set to Id
File size: 11.7 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
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   rst_opn    ! routine called by step module
31   PUBLIC   rst_write  ! routine called by step module
32   PUBLIC   rst_read   ! routine called by opa  module
33
34   LOGICAL, PUBLIC ::   lrst_oce =  .FALSE.   !: logical to control the oce restart write
35   INTEGER, PUBLIC ::   numror, numrow        !: logical unit for cean restart (read and write)
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 defined as a character
60      CHARACTER(LEN=50)   ::   clname ! ice output restart file name
61      INTEGER             ::   js     ! dummy loop variable
62      !!----------------------------------------------------------------------
63      !
64      IF( kt == nit000 ) THEN   ! default definitions
65         lrst_oce = .FALSE.   
66         nrst = 1
67         nitrst = nn_stock( nrst )
68      ENDIF
69
70      ! to get better performances with NetCDF format:
71      ! we open and define the ocean restart file one time step before writing the data (-> at nitrst - 1)
72      ! except if we are at the first time step, or if the previous time step we outputted a restart
73      IF ( kt == nitrst - 1 .OR. nn_stock(nrst) == 1 .OR. nn_stock(nrst)==nn_stock(nrst-1)+1 ) THEN
74         ! beware of the format used to write kt (default is i8.8, that should be large enough...)
75         IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst
76         ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst
77         ENDIF
78         ! create the file
79         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_ocerst_out)
80         IF(lwp) THEN
81            WRITE(numout,*)
82            SELECT CASE ( jprstlib )
83            CASE ( jprstdimg )   ;   WRITE(numout,*) '             open ocean restart binary file: '//clname
84            CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart NetCDF file: '//clname
85            END SELECT
86            IF ( snc4set%luse )      WRITE(numout,*) '             opened for NetCDF4 chunking and compression'
87            IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt
88            ELSE                          ;   WRITE(numout,*) '             kt = '             , kt
89            ENDIF
90         ENDIF
91         !
92         CALL iom_open( clname, numrow, ldwrt = .TRUE., kiolib = jprstlib )
93         lrst_oce = .TRUE.
94      ENDIF
95      !
96   END SUBROUTINE rst_opn
97
98
99   SUBROUTINE rst_write( kt )
100      !!---------------------------------------------------------------------
101      !!                   ***  ROUTINE rstwrite  ***
102      !!                     
103      !! ** Purpose :   Write restart fields in the format corresponding to jprstlib
104      !!
105      !! ** Method  :   Write in numrow when kt == nitrst in NetCDF
106      !!              file, save fields which are necessary for restart
107      !!----------------------------------------------------------------------
108      INTEGER, INTENT(in) ::   kt   ! ocean time-step
109      !!----------------------------------------------------------------------
110
111                     CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics time step
112                     CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1) )   ! surface tracer time step
113
114                     CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub        )     ! before fields
115                     CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb        )
116                     CALL iom_rstput( kt, nitrst, numrow, 'tb'     , tsb(:,:,:,jp_tem) )
117                     CALL iom_rstput( kt, nitrst, numrow, 'sb'     , tsb(:,:,:,jp_sal) )
118                     CALL iom_rstput( kt, nitrst, numrow, 'rotb'   , rotb      )
119                     CALL iom_rstput( kt, nitrst, numrow, 'hdivb'  , hdivb     )
120                     CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , sshb      )
121      IF( lk_vvl )   CALL iom_rstput( kt, nitrst, numrow, 'fse3t_b', fse3t_b(:,:,:) )
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( kt == nitrst ) THEN
135         CALL iom_close( numrow )     ! close the restart file (only on the dump time step)
136         IF( .NOT. lk_trdmld ) THEN
137            lrst_oce = .FALSE.
138            nrst = nrst + 1   
139            nitrst = nn_stock( nrst ) 
140         ENDIF
141      ENDIF
142      !
143   END SUBROUTINE rst_write
144
145
146   SUBROUTINE rst_read
147      !!----------------------------------------------------------------------
148      !!                   ***  ROUTINE rst_read  ***
149      !!
150      !! ** Purpose :   Read files for restart (format fixed by jprstlib )
151      !!
152      !! ** Method  :   Read in restart.nc file fields which are necessary for restart
153      !!----------------------------------------------------------------------
154      REAL(wp) ::   zrdt, zrdttra1
155      INTEGER  ::   jk, jlibalt = jprstlib
156      LOGICAL  ::   llok
157      !!----------------------------------------------------------------------
158
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
177      ! Check dynamics and tracer time-step consistency and force Euler restart if changed
178      IF( iom_varid( numror, 'rdt', ldstop = .FALSE. ) > 0 )   THEN
179         CALL iom_get( numror, 'rdt', zrdt )
180         IF( zrdt /= rdt )   neuler = 0
181      ENDIF
182      IF( iom_varid( numror, 'rdttra1', ldstop = .FALSE. ) > 0 )   THEN
183         CALL iom_get( numror, 'rdttra1', zrdttra1 )
184         IF( zrdttra1 /= rdttra(1) )   neuler = 0
185      ENDIF
186      !
187                     CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub      )   ! before fields
188                     CALL iom_get( numror, jpdom_autoglo, 'vb'     , vb      )
189                     CALL iom_get( numror, jpdom_autoglo, 'tb'     , tsb(:,:,:,jp_tem) )
190                     CALL iom_get( numror, jpdom_autoglo, 'sb'     , tsb(:,:,:,jp_sal) )
191                     CALL iom_get( numror, jpdom_autoglo, 'rotb'   , rotb    )
192                     CALL iom_get( numror, jpdom_autoglo, 'hdivb'  , hdivb   )
193                     CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb    )
194      IF( lk_vvl )   CALL iom_get( numror, jpdom_autoglo, 'fse3t_b', fse3t_b(:,:,:) )
195                     !
196                     CALL iom_get( numror, jpdom_autoglo, 'un'     , un      )   ! now    fields
197                     CALL iom_get( numror, jpdom_autoglo, 'vn'     , vn      )
198                     CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,:,jp_tem) )
199                     CALL iom_get( numror, jpdom_autoglo, 'sn'     , tsn(:,:,:,jp_sal) )
200                     CALL iom_get( numror, jpdom_autoglo, 'rotn'   , rotn    )
201                     CALL iom_get( numror, jpdom_autoglo, 'hdivn'  , hdivn   )
202                     CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn    )
203                     CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop    )   ! now    potential density
204#if defined key_zdfkpp
205      IF( iom_varid( numror, 'rhd', ldstop = .FALSE. ) > 0 ) THEN
206                     CALL iom_get( numror, jpdom_autoglo, 'rhd'    , rhd     )   ! now    in situ density anomaly
207      ELSE
208                     CALL eos( tsn, rhd )   ! compute rhd
209      ENDIF
210#endif
211      !
212      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0)
213         tsb  (:,:,:,:) = tsn  (:,:,:,:)                             ! all before fields set to now values
214         ub   (:,:,:)   = un   (:,:,:)
215         vb   (:,:,:)   = vn   (:,:,:)
216         rotb (:,:,:)   = rotn (:,:,:)
217         hdivb(:,:,:)   = hdivn(:,:,:)
218         sshb (:,:)     = sshn (:,:)
219         IF( lk_vvl ) THEN
220            DO jk = 1, jpk
221               fse3t_b(:,:,jk) = fse3t_n(:,:,jk)
222            END DO
223         ENDIF
224      ENDIF
225      !
226   END SUBROUTINE rst_read
227
228   !!=====================================================================
229END MODULE restart
Note: See TracBrowser for help on using the repository browser.