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

source: trunk/NEMO/OPA_SRC/restart.F90 @ 1502

Last change on this file since 1502 was 1483, checked in by ctlod, 15 years ago

declaration of rrau field is missing in restart.F90 when not using double diffusive mixing key_zdfddm, see ticket: #467

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 11.6 KB
Line 
1MODULE restart
2   !!======================================================================
3   !!                     ***  MODULE  restart  ***
4   !! Ocean restart :  write the ocean restart file
5   !!======================================================================
6   !! History :        !  99-11  (M. Imbard)  Original code
7   !!             8.5  !  02-08  (G. Madec)  F90: Free form
8   !!             9.0  !  05-11  (V. Garnier) Surface pressure gradient organization
9   !!             9.0  !  06-07  (S. Masson)  use IOM for restart
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   rst_opn    : open the ocean restart file
14   !!   rst_write  : write the ocean restart file
15   !!   rst_read   : read the ocean restart file
16   !!----------------------------------------------------------------------
17   USE dom_oce         ! ocean space and time domain
18   USE oce             ! ocean dynamics and tracers
19   USE phycst          ! physical constants
20   USE in_out_manager  ! I/O manager
21   USE iom             ! I/O module
22   USE c1d             ! re-initialization of u-v mask for the 1D configuration
23   USE zpshde          ! partial step: hor. derivative (zps_hde routine)
24   USE eosbn2          ! equation of state            (eos bn2 routine)
25   USE zdfddm          ! double diffusion mixing
26   USE zdfmxl          ! mixed layer depth
27   USE trdmld_oce      ! ocean active mixed layer tracers trends variables
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 opa  module
35
36   LOGICAL, PUBLIC ::   lrst_oce =  .FALSE.       !: logical to control the oce restart write
37   INTEGER, PUBLIC ::   numror, numrow            !: logical unit for cean restart (read and write)
38
39   !! * Substitutions
40#  include "vectopt_loop_substitute.h90"
41   !!----------------------------------------------------------------------
42   !!  OPA 9.0 , LOCEAN-IPSL (2006)
43   !! $Id$
44   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
45   !!----------------------------------------------------------------------
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      !!
61      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character
62      CHARACTER(LEN=50)   ::   clname   ! ice output restart file name
63      !!----------------------------------------------------------------------
64      !
65      IF( kt == nit000 ) THEN   ! default definitions
66         lrst_oce = .FALSE.   
67         nitrst = nitend
68      ENDIF
69      IF( MOD( kt - 1, nstock ) == 0 ) THEN   
70         ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment
71         nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing
72         IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run
73      ENDIF
74      ! to get better performances with NetCDF format:
75      ! we open and define the ocean restart file one time step before writing the data (-> at nitrst - 1)
76      ! except if we write ocean restart files every time step or if an ocean restart file was writen at nitend - 1
77      IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend .AND. .NOT. lrst_oce ) ) THEN
78         ! beware of the format used to write kt (default is i8.8, that should be large enough...)
79         IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst
80         ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst
81         ENDIF
82         ! create the file
83         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_ocerst_out)
84         IF(lwp) THEN
85            WRITE(numout,*)
86            SELECT CASE ( jprstlib )
87            CASE ( jprstdimg )   ;   WRITE(numout,*) '             open ocean restart binary file: '//clname
88            CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart NetCDF file: '//clname
89            END SELECT
90            IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt
91            ELSE                          ;   WRITE(numout,*) '             kt = '             , kt
92            ENDIF
93         ENDIF
94
95         CALL iom_open( clname, numrow, ldwrt = .TRUE., kiolib = jprstlib )
96         lrst_oce = .TRUE.
97      ENDIF
98      !
99   END SUBROUTINE rst_opn
100
101
102   SUBROUTINE rst_write( kt )
103      !!---------------------------------------------------------------------
104      !!                   ***  ROUTINE rstwrite  ***
105      !!                     
106      !! ** Purpose :   Write restart fields in the format corresponding to jprstlib
107      !!
108      !! ** Method  :   Write in numrow when kt == nitrst in NetCDF
109      !!      file, save fields which are necessary for restart
110      !!----------------------------------------------------------------------
111      INTEGER, INTENT(in) ::   kt   ! ocean time-step
112      !!----------------------------------------------------------------------
113
114      !                                                                     ! the begining of the run [s]
115      CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt               )   ! dynamics time step
116      CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1)         )   ! surface tracer time step
117
118      ! prognostic variables
119      CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub      )   
120      CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb      )
121      CALL iom_rstput( kt, nitrst, numrow, 'tb'     , tb      )
122      CALL iom_rstput( kt, nitrst, numrow, 'sb'     , sb      )
123      CALL iom_rstput( kt, nitrst, numrow, 'rotb'   , rotb    )
124      CALL iom_rstput( kt, nitrst, numrow, 'hdivb'  , hdivb   )
125      CALL iom_rstput( kt, nitrst, numrow, 'un'     , un      )
126      CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vn      )
127      CALL iom_rstput( kt, nitrst, numrow, 'tn'     , tn      )
128      CALL iom_rstput( kt, nitrst, numrow, 'sn'     , sn      )
129      CALL iom_rstput( kt, nitrst, numrow, 'rotn'   , rotn    )
130      CALL iom_rstput( kt, nitrst, numrow, 'hdivn'  , hdivn   )
131
132      CALL iom_rstput( kt, nitrst, numrow, 'rhop'  , rhop   )
133
134#if defined key_zdfddm
135      IF( lk_zdfddm )   CALL iom_rstput( kt, nitrst, numrow, 'rrau' , rrau  )
136#endif
137
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
146   SUBROUTINE rst_read
147      !!----------------------------------------------------------------------
148      !!                   ***  ROUTINE rst_read  ***
149      !!
150      !! ** Purpose :   Read files for restart (format fixed by jprstlib )
151      !!
152      !! ** Method  :   Read the previous fields on the NetCDF/binary file
153      !!      the first record indicates previous characterics
154      !!      after control with the present run, we read :
155      !!      - prognostic variables on the second record
156      !!      - elliptic solver arrays
157      !!      - barotropic stream function arrays ("key_dynspg_rl" defined)
158      !!        or free surface arrays
159      !!      - tke arrays (lk_zdftke=T .OR. lk_zdftke2=T)
160      !!      for this last three records,  the previous characteristics
161      !!      could be different with those used in the present run.
162      !!----------------------------------------------------------------------
163      REAL(wp) ::   zrdt, zrdttra1
164      INTEGER  ::   jlibalt = jprstlib
165      LOGICAL  ::   llok
166      !!----------------------------------------------------------------------
167
168      IF(lwp) THEN                                             ! Contol prints
169         WRITE(numout,*)
170         SELECT CASE ( jprstlib )
171         CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file'
172         CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file'
173         END SELECT
174         WRITE(numout,*) '~~~~~~~~'
175      ENDIF
176
177      IF ( jprstlib == jprstdimg ) THEN
178        ! eventually read netcdf file (monobloc)  for restarting on different number of processors
179        ! if {cn_ocerst_in}.nc exists, then set jlibalt to jpnf90
180        INQUIRE( FILE = TRIM(cn_ocerst_in)//'.nc', EXIST = llok )
181        IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF
182      ENDIF
183      CALL iom_open( cn_ocerst_in, numror, kiolib = jlibalt )
184
185      ! Check dynamics and tracer time-step consistency and force Euler restart if changed
186      IF( iom_varid( numror, 'rdt', ldstop = .FALSE. ) > 0 )   THEN
187         CALL iom_get( numror, 'rdt', zrdt )
188         IF( zrdt /= rdt )   neuler = 0
189      ENDIF
190      IF( iom_varid( numror, 'rdttra1', ldstop = .FALSE. ) > 0 )   THEN
191         CALL iom_get( numror, 'rdttra1', zrdttra1 )
192         IF( zrdttra1 /= rdttra(1) )   neuler = 0
193      ENDIF
194      !                                                       ! Read prognostic variables
195      CALL iom_get( numror, jpdom_autoglo, 'ub'   , ub    )        ! before i-component velocity
196      CALL iom_get( numror, jpdom_autoglo, 'vb'   , vb    )        ! before j-component velocity
197      CALL iom_get( numror, jpdom_autoglo, 'tb'   , tb    )        ! before temperature
198      CALL iom_get( numror, jpdom_autoglo, 'sb'   , sb    )        ! before salinity
199      CALL iom_get( numror, jpdom_autoglo, 'rotb' , rotb  )        ! before curl
200      CALL iom_get( numror, jpdom_autoglo, 'hdivb', hdivb )        ! before horizontal divergence
201      CALL iom_get( numror, jpdom_autoglo, 'un'   , un    )        ! now    i-component velocity
202      CALL iom_get( numror, jpdom_autoglo, 'vn'   , vn    )        ! now    j-component velocity
203      CALL iom_get( numror, jpdom_autoglo, 'tn'   , tn    )        ! now    temperature
204      CALL iom_get( numror, jpdom_autoglo, 'sn'   , sn    )        ! now    salinity
205      CALL iom_get( numror, jpdom_autoglo, 'rotn' , rotn  )        ! now    curl
206      CALL iom_get( numror, jpdom_autoglo, 'hdivn', hdivn )        ! now    horizontal divergence
207
208      CALL iom_get( numror, jpdom_autoglo, 'rhop', rhop )          ! now    mixed layer depth
209
210#if defined key_zdfddm
211      IF( lk_zdfddm ) THEN
212         IF( iom_varid( numror, 'rrau', ldstop = .FALSE. ) > 0 ) THEN
213            CALL iom_get( numror, jpdom_autoglo, 'rrau' , rrau  )
214         ELSE
215            CALL eos_init                   ! read equation state type neos parameter
216            CALL eos( tb, sb, rhd, rhop )   ! compute rrau
217         ENDIF
218      ENDIF 
219#endif
220
221      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0)
222         tb   (:,:,:) = tn   (:,:,:)                             ! all before fields set to now field values
223         sb   (:,:,:) = sn   (:,:,:)
224         ub   (:,:,:) = un   (:,:,:)
225         vb   (:,:,:) = vn   (:,:,:)
226         rotb (:,:,:) = rotn (:,:,:)
227         hdivb(:,:,:) = hdivn(:,:,:)
228      ENDIF
229      !
230   END SUBROUTINE rst_read
231
232
233   !!=====================================================================
234END MODULE restart
Note: See TracBrowser for help on using the repository browser.