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

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90 @ 4405

Last change on this file since 4405 was 3211, checked in by spickles2, 13 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

  • Property svn:keywords set to Id
File size: 12.1 KB
RevLine 
[3]1MODULE restart
2   !!======================================================================
3   !!                     ***  MODULE  restart  ***
4   !! Ocean restart :  write the ocean restart file
[508]5   !!======================================================================
[2528]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)
[508]11   !!----------------------------------------------------------------------
[3]12
13   !!----------------------------------------------------------------------
[508]14   !!   rst_opn    : open the ocean restart file
15   !!   rst_write  : write the ocean restart file
16   !!   rst_read   : read the ocean restart file
[3]17   !!----------------------------------------------------------------------
[2528]18   USE oce             ! ocean dynamics and tracers
[3]19   USE dom_oce         ! ocean space and time domain
20   USE phycst          ! physical constants
[508]21   USE in_out_manager  ! I/O manager
22   USE iom             ! I/O module
[544]23   USE eosbn2          ! equation of state            (eos bn2 routine)
[579]24   USE trdmld_oce      ! ocean active mixed layer tracers trends variables
[2528]25   USE domvvl          ! variable volume
26   USE traswp          ! swap from 4D T-S to 3D T & S and vice versa
[3]27
28   IMPLICIT NONE
29   PRIVATE
30
[508]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 opa  module
[3]34
[2528]35   LOGICAL, PUBLIC ::   lrst_oce =  .FALSE.   !: logical to control the oce restart write
36   INTEGER, PUBLIC ::   numror, numrow        !: logical unit for cean restart (read and write)
[508]37
[3211]38   !! * Control permutation of array indices
39#  include "oce_ftrans.h90"
40#  include "dom_oce_ftrans.h90"
41#  include "trdmld_oce_ftrans.h90"
42#  include "domvvl_ftrans.h90"
43
[508]44   !! * Substitutions
[2528]45#  include "domzgr_substitute.h90"
[508]46#  include "vectopt_loop_substitute.h90"
[3]47   !!----------------------------------------------------------------------
[2528]48   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[888]49   !! $Id$
[2528]50   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[359]51   !!----------------------------------------------------------------------
[3]52CONTAINS
53
[508]54   SUBROUTINE rst_opn( kt )
55      !!---------------------------------------------------------------------
56      !!                   ***  ROUTINE rst_opn  ***
57      !!                     
58      !! ** Purpose : + initialization (should be read in the namelist) of nitrst
59      !!              + open the restart when we are one time step before nitrst
60      !!                   - restart header is defined when kt = nitrst-1
61      !!                   - restart data  are written when kt = nitrst
62      !!              + define lrst_oce to .TRUE. when we need to define or write the restart
63      !!----------------------------------------------------------------------
64      INTEGER, INTENT(in) ::   kt     ! ocean time-step
65      !!
66      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character
67      CHARACTER(LEN=50)   ::   clname   ! ice output restart file name
68      !!----------------------------------------------------------------------
69      !
[783]70      IF( kt == nit000 ) THEN   ! default definitions
71         lrst_oce = .FALSE.   
72         nitrst = nitend
[508]73      ENDIF
[783]74      IF( MOD( kt - 1, nstock ) == 0 ) THEN   
75         ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment
76         nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing
77         IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run
78      ENDIF
79      ! to get better performances with NetCDF format:
80      ! we open and define the ocean restart file one time step before writing the data (-> at nitrst - 1)
81      ! except if we write ocean restart files every time step or if an ocean restart file was writen at nitend - 1
82      IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend .AND. .NOT. lrst_oce ) ) THEN
83         ! beware of the format used to write kt (default is i8.8, that should be large enough...)
84         IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst
85         ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst
[508]86         ENDIF
87         ! create the file
[1229]88         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_ocerst_out)
[611]89         IF(lwp) THEN
90            WRITE(numout,*)
[632]91            SELECT CASE ( jprstlib )
[783]92            CASE ( jprstdimg )   ;   WRITE(numout,*) '             open ocean restart binary file: '//clname
93            CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart NetCDF file: '//clname
[632]94            END SELECT
[2528]95            IF ( snc4set%luse )      WRITE(numout,*) '             opened for NetCDF4 chunking and compression'
[1130]96            IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt
97            ELSE                          ;   WRITE(numout,*) '             kt = '             , kt
[611]98            ENDIF
99         ENDIF
[2528]100         !
[547]101         CALL iom_open( clname, numrow, ldwrt = .TRUE., kiolib = jprstlib )
[508]102         lrst_oce = .TRUE.
103      ENDIF
104      !
105   END SUBROUTINE rst_opn
106
107
[3]108   SUBROUTINE rst_write( kt )
109      !!---------------------------------------------------------------------
110      !!                   ***  ROUTINE rstwrite  ***
111      !!                     
[632]112      !! ** Purpose :   Write restart fields in the format corresponding to jprstlib
[3]113      !!
[508]114      !! ** Method  :   Write in numrow when kt == nitrst in NetCDF
[2528]115      !!              file, save fields which are necessary for restart
[3]116      !!----------------------------------------------------------------------
[508]117      INTEGER, INTENT(in) ::   kt   ! ocean time-step
[3]118      !!----------------------------------------------------------------------
[1239]119
[2528]120                     CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics time step
121                     CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1) )   ! surface tracer time step
[3]122
[2528]123                     CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub        )     ! before fields
124                     CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb        )
125                     CALL iom_rstput( kt, nitrst, numrow, 'tb'     , tb        )
126                     CALL iom_rstput( kt, nitrst, numrow, 'sb'     , sb        )
127                     CALL iom_rstput( kt, nitrst, numrow, 'rotb'   , rotb      )
128                     CALL iom_rstput( kt, nitrst, numrow, 'hdivb'  , hdivb     )
129                     CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , sshb      )
130      IF( lk_vvl )   CALL iom_rstput( kt, nitrst, numrow, 'fse3t_b', fse3t_b(:,:,:) )
131                     !
132                     CALL iom_rstput( kt, nitrst, numrow, 'un'     , un        )     ! now fields
133                     CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vn        )
134                     CALL iom_rstput( kt, nitrst, numrow, 'tn'     , tn        )
135                     CALL iom_rstput( kt, nitrst, numrow, 'sn'     , sn        )
136                     CALL iom_rstput( kt, nitrst, numrow, 'rotn'   , rotn      )
137                     CALL iom_rstput( kt, nitrst, numrow, 'hdivn'  , hdivn     )
138                     CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , sshn      )
139                     CALL iom_rstput( kt, nitrst, numrow, 'rhop'   , rhop      )
[1545]140#if defined key_zdfkpp
[2528]141                     CALL iom_rstput( kt, nitrst, numrow, 'rhd'    , rhd       )
[1483]142#endif
[508]143      IF( kt == nitrst ) THEN
144         CALL iom_close( numrow )     ! close the restart file (only at last time step)
[579]145         IF( .NOT. lk_trdmld )   lrst_oce = .FALSE.
[3]146      ENDIF
[508]147      !
[3]148   END SUBROUTINE rst_write
149
150
151   SUBROUTINE rst_read
152      !!----------------------------------------------------------------------
153      !!                   ***  ROUTINE rst_read  ***
154      !!
[632]155      !! ** Purpose :   Read files for restart (format fixed by jprstlib )
[3]156      !!
[1531]157      !! ** Method  :   Read in restart.nc file fields which are necessary for restart
[3]158      !!----------------------------------------------------------------------
[1130]159      REAL(wp) ::   zrdt, zrdttra1
[2528]160      INTEGER  ::   jk, jlibalt = jprstlib
[1473]161      LOGICAL  ::   llok
[3]162      !!----------------------------------------------------------------------
163
[508]164      IF(lwp) THEN                                             ! Contol prints
165         WRITE(numout,*)
[632]166         SELECT CASE ( jprstlib )
[1130]167         CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file'
168         CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file'
[632]169         END SELECT
[2528]170         IF ( snc4set%luse )      WRITE(numout,*) 'rst_read : configured with NetCDF4 support'
[508]171         WRITE(numout,*) '~~~~~~~~'
[3]172      ENDIF
173
[1473]174      IF ( jprstlib == jprstdimg ) THEN
175        ! eventually read netcdf file (monobloc)  for restarting on different number of processors
176        ! if {cn_ocerst_in}.nc exists, then set jlibalt to jpnf90
177        INQUIRE( FILE = TRIM(cn_ocerst_in)//'.nc', EXIST = llok )
178        IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF
179      ENDIF
180      CALL iom_open( cn_ocerst_in, numror, kiolib = jlibalt )
[3]181
[544]182      ! Check dynamics and tracer time-step consistency and force Euler restart if changed
[746]183      IF( iom_varid( numror, 'rdt', ldstop = .FALSE. ) > 0 )   THEN
[544]184         CALL iom_get( numror, 'rdt', zrdt )
185         IF( zrdt /= rdt )   neuler = 0
186      ENDIF
[746]187      IF( iom_varid( numror, 'rdttra1', ldstop = .FALSE. ) > 0 )   THEN
[544]188         CALL iom_get( numror, 'rdttra1', zrdttra1 )
189         IF( zrdttra1 /= rdttra(1) )   neuler = 0
190      ENDIF
[1607]191      !
[2528]192                     CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub      )   ! before fields
193                     CALL iom_get( numror, jpdom_autoglo, 'vb'     , vb      )
194                     CALL iom_get( numror, jpdom_autoglo, 'tb'     , tb      )
195                     CALL iom_get( numror, jpdom_autoglo, 'sb'     , sb      )
196                     CALL iom_get( numror, jpdom_autoglo, 'rotb'   , rotb    )
197                     CALL iom_get( numror, jpdom_autoglo, 'hdivb'  , hdivb   )
198                     CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb    )
199      IF( lk_vvl )   CALL iom_get( numror, jpdom_autoglo, 'fse3t_b', fse3t_b(:,:,:) )
200                     !
201                     CALL iom_get( numror, jpdom_autoglo, 'un'     , un      )   ! now    fields
202                     CALL iom_get( numror, jpdom_autoglo, 'vn'     , vn      )
203                     CALL iom_get( numror, jpdom_autoglo, 'tn'     , tn      )
204                     CALL iom_get( numror, jpdom_autoglo, 'sn'     , sn      )
205                     CALL iom_get( numror, jpdom_autoglo, 'rotn'   , rotn    )
206                     CALL iom_get( numror, jpdom_autoglo, 'hdivn'  , hdivn   )
207                     CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn    )
208                     CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop    )   ! now    potential density
[1545]209#if defined key_zdfkpp
210      IF( iom_varid( numror, 'rhd', ldstop = .FALSE. ) > 0 ) THEN
[2528]211                     CALL iom_get( numror, jpdom_autoglo, 'rhd'    , rhd     )   ! now    in situ density anomaly
[1545]212      ELSE
[2528]213                     CALL tra_swap
214                     CALL eos( tsn, rhd )   ! compute rhd
[1545]215      ENDIF
[1483]216#endif
[2528]217      !
[508]218      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0)
[1607]219         tb   (:,:,:) = tn   (:,:,:)                             ! all before fields set to now values
[508]220         sb   (:,:,:) = sn   (:,:,:)
221         ub   (:,:,:) = un   (:,:,:)
222         vb   (:,:,:) = vn   (:,:,:)
223         rotb (:,:,:) = rotn (:,:,:)
224         hdivb(:,:,:) = hdivn(:,:,:)
[1607]225         sshb (:,:)   = sshn (:,:)
[2528]226         IF( lk_vvl ) THEN
227            DO jk = 1, jpk
228               fse3t_b(:,:,jk) = fse3t_n(:,:,jk)
229            END DO
230         ENDIF
[3]231      ENDIF
[508]232      !
233   END SUBROUTINE rst_read
[473]234
[3]235   !!=====================================================================
236END MODULE restart
Note: See TracBrowser for help on using the repository browser.