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 @ 593

Last change on this file since 593 was 593, checked in by opalod, 17 years ago

nemo_v2_update_001 : CT : - add non linear free surface (variable volume) with new cpp key key_vvl

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 17.8 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 daymod          ! calendar
21   USE ice_oce         ! ice variables
22   USE blk_oce         ! bulk variables
23   USE cpl_oce, ONLY : lk_cpl              !
24   USE in_out_manager  ! I/O manager
25   USE iom             ! I/O module
26   USE ini1d           ! re-initialization of u-v mask for the 1D configuration
27   USE zpshde          ! partial step: hor. derivative (zps_hde routine)
28   USE eosbn2          ! equation of state            (eos bn2 routine)
29   USE trdmld_oce      ! ocean active mixed layer tracers trends variables
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   rst_opn    ! routine called by step module
35   PUBLIC   rst_write  ! routine called by step module
36   PUBLIC   rst_read   ! routine called by opa  module
37
38   LOGICAL, PUBLIC ::   lrst_oce                  !: logical to control the oce restart write
39   INTEGER, PUBLIC ::   numror, numrow            !: logical unit for cean restart (read and write)
40
41   !! * Substitutions
42#  include "vectopt_loop_substitute.h90"
43   !!----------------------------------------------------------------------
44   !!  OPA 9.0 , LOCEAN-IPSL (2006)
45   !! $Header$
46   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
47   !!----------------------------------------------------------------------
48
49CONTAINS
50
51   SUBROUTINE rst_opn( kt )
52      !!---------------------------------------------------------------------
53      !!                   ***  ROUTINE rst_opn  ***
54      !!                     
55      !! ** Purpose : + initialization (should be read in the namelist) of nitrst
56      !!              + open the restart when we are one time step before nitrst
57      !!                   - restart header is defined when kt = nitrst-1
58      !!                   - restart data  are written when kt = nitrst
59      !!              + define lrst_oce to .TRUE. when we need to define or write the restart
60      !!----------------------------------------------------------------------
61      INTEGER, INTENT(in) ::   kt     ! ocean time-step
62      !!
63      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character
64      CHARACTER(LEN=50)   ::   clname   ! ice output restart file name
65      !!----------------------------------------------------------------------
66      !
67      IF( kt == nit000 ) THEN   ! default initialization, to do: should be read in the namelist...
68         nitrst = nitend        ! to do: should be read in the namelist in a cleaver way...
69         lrst_oce = .FALSE.
70      ENDIF
71     
72      IF    ( kt == nitrst-1 .AND. lrst_oce         ) THEN
73         CALL ctl_stop( 'rst_opn: we cannot create an ocean restart at every time step',    &
74            &           'if the run ahs more than one tie step!!!' )
75         numrow = 0
76      ELSEIF( kt == nitrst-1 .OR.  nitend == nit000 ) THEN   ! beware if model runs only one time step
77         ! beware of the format used to write kt (default is i8.8, that should be large enough)
78         IF( nitrst > 1.0e9 ) THEN   
79            WRITE(clkt,*) nitrst
80         ELSE
81            WRITE(clkt,'(i8.8)') nitrst
82         ENDIF
83         ! create the file
84         IF(lwp) WRITE(numout,*)
85         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_restart"
86         IF(lwp) WRITE(numout,*) '             open ocean restart.output NetCDF file: '//clname
87         CALL iom_open( clname, numrow, ldwrt = .TRUE., kiolib = jprstlib )
88         lrst_oce = .TRUE.
89      ENDIF
90      !
91   END SUBROUTINE rst_opn
92
93
94   SUBROUTINE rst_write( kt )
95      !!---------------------------------------------------------------------
96      !!                   ***  ROUTINE rstwrite  ***
97      !!                     
98      !! ** Purpose :   Write restart fields in NetCDF format
99      !!
100      !! ** Method  :   Write in numrow when kt == nitrst in NetCDF
101      !!      file, save fields which are necessary for restart
102      !!----------------------------------------------------------------------
103      INTEGER, INTENT(in) ::   kt   ! ocean time-step
104      !!----------------------------------------------------------------------
105
106      IF(lwp) THEN
107         WRITE(numout,*)
108         WRITE(numout,*) 'rst_write : write ocean NetCDF restart file  kt =', kt,' date= ', ndastp
109         WRITE(numout,*) '~~~~~~~~~'
110      ENDIF
111
112      ! calendar control
113      CALL iom_rstput( kt, nitrst, numrow, 'kt'     , REAL( kt    , wp) )   ! time-step
114      CALL iom_rstput( kt, nitrst, numrow, 'ndastp' , REAL( ndastp, wp) )   ! date
115      CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj            )   ! number of elapsed days since
116      !                                                                     ! the begining of the run [s]
117      CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt               )   ! dynamics time step
118      CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1)         )   ! surface tracer time step
119
120      ! prognostic variables
121      CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub      )   
122      CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb      )
123      CALL iom_rstput( kt, nitrst, numrow, 'tb'     , tb      )
124      CALL iom_rstput( kt, nitrst, numrow, 'sb'     , sb      )
125      CALL iom_rstput( kt, nitrst, numrow, 'rotb'   , rotb    )
126      CALL iom_rstput( kt, nitrst, numrow, 'hdivb'  , hdivb   )
127      CALL iom_rstput( kt, nitrst, numrow, 'un'     , un      )
128      CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vn      )
129      IF( lk_vvl ) CALL iom_rstput( kt, nitrst, numrow, 'wn'     , wn      )
130      CALL iom_rstput( kt, nitrst, numrow, 'tn'     , tn      )
131      CALL iom_rstput( kt, nitrst, numrow, 'sn'     , sn      )
132      CALL iom_rstput( kt, nitrst, numrow, 'rotn'   , rotn    )
133      CALL iom_rstput( kt, nitrst, numrow, 'hdivn'  , hdivn   )
134     
135#if defined key_ice_lim       
136      CALL iom_rstput( kt, nitrst, numrow, 'nfice'  , REAL( nfice, wp) )   !  ice computation frequency
137      CALL iom_rstput( kt, nitrst, numrow, 'sst_io' , sst_io  )
138      CALL iom_rstput( kt, nitrst, numrow, 'sss_io' , sss_io  )
139      CALL iom_rstput( kt, nitrst, numrow, 'u_io'   , u_io    )
140      CALL iom_rstput( kt, nitrst, numrow, 'v_io'   , v_io    )
141# if defined key_coupled
142      CALL iom_rstput( kt, nitrst, numrow, 'alb_ice', alb_ice )
143# endif
144#endif
145#if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
146      CALL iom_rstput( kt, nitrst, numrow, 'nfbulk' , REAL( nfbulk, wp) )   !  bulk computation frequency
147      CALL iom_rstput( kt, nitrst, numrow, 'gsst'   , gsst    )
148#endif
149
150      IF( nn_dynhpg_rst == 1 .OR. lk_vvl ) THEN
151         CALL iom_rstput( kt, nitrst, numrow, 'rhd' , rhd  )
152         CALL iom_rstput( kt, nitrst, numrow, 'rhop', rhop )
153         IF( ln_zps ) THEN
154            CALL iom_rstput( kt, nitrst, numrow, 'gtu' , gtu )
155            CALL iom_rstput( kt, nitrst, numrow, 'gsu' , gsu )
156            CALL iom_rstput( kt, nitrst, numrow, 'gru' , gru )
157            CALL iom_rstput( kt, nitrst, numrow, 'gtv' , gtv )
158            CALL iom_rstput( kt, nitrst, numrow, 'gsv' , gsv )
159            CALL iom_rstput( kt, nitrst, numrow, 'grv' , grv )
160         ENDIF
161      ENDIF
162
163      IF( kt == nitrst ) THEN
164         CALL iom_close( numrow )     ! close the restart file (only at last time step)
165         IF( .NOT. lk_trdmld )   lrst_oce = .FALSE.
166      ENDIF
167      !
168   END SUBROUTINE rst_write
169
170
171   SUBROUTINE rst_read
172      !!----------------------------------------------------------------------
173      !!                   ***  ROUTINE rst_read  ***
174      !!
175      !! ** Purpose :   Read files for restart
176      !!
177      !! ** Method  :   Read the previous fields on the NetCDF file
178      !!      the first record indicates previous characterics
179      !!      after control with the present run, we read :
180      !!      - prognostic variables on the second record
181      !!      - elliptic solver arrays
182      !!      - barotropic stream function arrays ("key_dynspg_rl" defined)
183      !!        or free surface arrays
184      !!      - tke arrays (lk_zdftke=T)
185      !!      for this last three records,  the previous characteristics
186      !!      could be different with those used in the present run.
187      !!
188      !!   According to namelist parameter nrstdt,
189      !!       nrstdt = 0  no control on the date (nit000 is  arbitrary).
190      !!       nrstdt = 1  we verify that nit000 is equal to the last
191      !!                   time step of previous run + 1.
192      !!       In both those options, the  exact duration of the experiment
193      !!       since the beginning (cumulated duration of all previous restart runs)
194      !!       is not stored in the restart and is assumed to be (nit000-1)*rdt.
195      !!       This is valid is the time step has remained constant.
196      !!
197      !!       nrstdt = 2  the duration of the experiment in days (adatrj)
198      !!                    has been stored in the restart file.
199      !!----------------------------------------------------------------------
200      REAL(wp) ::   zcoef, zkt, zrdt, zrdttra1, zndastp, znfice, znfbulk
201#if defined key_ice_lim
202      INTEGER  ::   ji, jj
203#endif
204      !!----------------------------------------------------------------------
205
206      IF(lwp) THEN                                             ! Contol prints
207         WRITE(numout,*)
208         WRITE(numout,*) 'rst_read : read oce NetCDF restart file'
209         WRITE(numout,*) '~~~~~~~~'
210         
211         WRITE(numout,*) ' *** Info on the present job : '
212         WRITE(numout,*) '   time-step           : ', nit000
213         WRITE(numout,*) '   date ndastp         : ', ndastp
214         WRITE(numout,*)
215         WRITE(numout,*) ' *** restart option'
216         SELECT CASE ( nrstdt )
217         CASE ( 0 ) 
218            WRITE(numout,*) ' nrstdt = 0 no control of nit000'
219         CASE ( 1 ) 
220            WRITE(numout,*) ' nrstdt = 1 we control the date of nit000'
221         CASE ( 2 )
222            WRITE(numout,*) ' nrstdt = 2 the date adatrj is read in restart file'
223         CASE DEFAULT
224            WRITE(numout,*) '  ===>>>> nrstdt not equal 0, 1 or 2 : no control of the date'
225            WRITE(numout,*) '  =======                  ========='
226         END SELECT
227         WRITE(numout,*)
228      ENDIF
229
230      CALL iom_open( 'restart', numror, kiolib = jprstlib )
231
232      ! Calendar informations
233      CALL iom_get( numror, 'kt'     , zkt      )   ! time-step
234      CALL iom_get( numror, 'ndastp' , zndastp  )   ! date
235      IF(lwp) THEN
236         WRITE(numout,*)
237         WRITE(numout,*) ' *** Info on the restart file read : '
238         WRITE(numout,*) '   time-step           : ', NINT( zkt )
239         WRITE(numout,*) '   date ndastp         : ', NINT( zndastp )
240         WRITE(numout,*)
241      ENDIF
242      ! Control of date
243      IF( nit000 - NINT( zkt )  /= 1 .AND. nrstdt /= 0 ) &
244           & CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart', &
245           & ' verify the restart file or rerun with nrstdt = 0 (namelist)' )
246      ! re-initialisation of  adatrj0
247      adatrj0 = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday
248      IF ( nrstdt == 2 ) THEN
249         ! by default ndatsp has been set to ndate0 in dom_nam
250         ! ndate0 has been read in the namelist (standard OPA 8)
251         ! here when nrstdt=2 we keep the  final date of previous run
252         ndastp = NINT( zndastp )
253         CALL iom_get( numror, 'adatrj', adatrj )   ! number of elapsed days since the begining of last run
254      ENDIF
255      ! Check dynamics and tracer time-step consistency and force Euler restart if changed
256      IF( iom_varid( numror, 'rdt' ) > 0 )   THEN
257         CALL iom_get( numror, 'rdt', zrdt )
258         IF( zrdt /= rdt )   neuler = 0
259      ENDIF
260      IF( iom_varid( numror, 'rdttra1' ) > 0 )   THEN
261         CALL iom_get( numror, 'rdttra1', zrdttra1 )
262         IF( zrdttra1 /= rdttra(1) )   neuler = 0
263      ENDIF
264      !
265      !                                                       ! Read prognostic variables
266      CALL iom_get( numror, jpdom_local, 'ub'   , ub    )        ! before i-component velocity
267      CALL iom_get( numror, jpdom_local, 'vb'   , vb    )        ! before j-component velocity
268      CALL iom_get( numror, jpdom_local, 'tb'   , tb    )        ! before temperature
269      CALL iom_get( numror, jpdom_local, 'sb'   , sb    )        ! before salinity
270      CALL iom_get( numror, jpdom_local, 'rotb' , rotb  )        ! before curl
271      CALL iom_get( numror, jpdom_local, 'hdivb', hdivb )        ! before horizontal divergence
272      CALL iom_get( numror, jpdom_local, 'un'   , un    )        ! now    i-component velocity
273      CALL iom_get( numror, jpdom_local, 'vn'   , vn    )        ! now    j-component velocity
274      IF( lk_vvl ) CALL iom_get( numror, jpdom_local, 'wn'   , wn    )        ! now    k-component velocity
275      CALL iom_get( numror, jpdom_local, 'tn'   , tn    )        ! now    temperature
276      CALL iom_get( numror, jpdom_local, 'sn'   , sn    )        ! now    salinity
277      CALL iom_get( numror, jpdom_local, 'rotn' , rotn  )        ! now    curl
278      CALL iom_get( numror, jpdom_local, 'hdivn', hdivn )        ! now    horizontal divergence
279
280
281      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0)
282         tb   (:,:,:) = tn   (:,:,:)                             ! all before fields set to now field values
283         sb   (:,:,:) = sn   (:,:,:)
284         ub   (:,:,:) = un   (:,:,:)
285         vb   (:,:,:) = vn   (:,:,:)
286         rotb (:,:,:) = rotn (:,:,:)
287         hdivb(:,:,:) = hdivn(:,:,:)
288      ENDIF
289
290      !!sm: TO BE MOVED IN NEW SURFACE MODULE...
291
292#if defined key_ice_lim
293      ! Louvain La Neuve Sea Ice Model
294      IF( iom_varid( numror, 'nfice' ) > 0 ) then
295         CALL iom_get( numror             , 'nfice'  , znfice  )   ! ice computation frequency
296         CALL iom_get( numror, jpdom_local, 'sst_io' , sst_io  )
297         CALL iom_get( numror, jpdom_local, 'sss_io' , sss_io  )
298         CALL iom_get( numror, jpdom_local, 'u_io'   , u_io    )
299         CALL iom_get( numror, jpdom_local, 'v_io'   , v_io    )
300# if defined key_coupled
301         CALL iom_get( numror, jpdom_local, 'alb_ice', alb_ice )
302# endif
303         IF( znfice /= REAL( nfice, wp ) ) THEN      ! if nfice changed between 2 runs
304            zcoef = REAL( nfice-1, wp ) / znfice
305            sst_io(:,:) = zcoef * sst_io(:,:)
306            sss_io(:,:) = zcoef * sss_io(:,:)
307            u_io  (:,:) = zcoef * u_io  (:,:)
308            v_io  (:,:) = zcoef * v_io  (:,:)
309         ENDIF
310      ELSE
311         IF(lwp) WRITE(numout,*)
312         IF(lwp) WRITE(numout,*) 'rst_read :  LLN sea Ice Model => Ice initialization'
313         IF(lwp) WRITE(numout,*)
314         zcoef = REAL( nfice-1, wp )
315         sst_io(:,:) = zcoef *( tn(:,:,1) + rt0 )          !!bug a explanation is needed here!
316         sss_io(:,:) = zcoef *  sn(:,:,1)
317         zcoef = 0.5 * REAL( nfice-1, wp )
318         DO jj = 2, jpj
319            DO ji = fs_2, jpi   ! vector opt.
320               u_io(ji,jj) = zcoef * ( un(ji-1,jj  ,1) + un(ji-1,jj-1,1) )
321               v_io(ji,jj) = zcoef * ( vn(ji  ,jj-1,1) + vn(ji-1,jj-1,1) )
322            END DO
323         END DO
324# if defined key_coupled
325         alb_ice(:,:) = 0.8 * tmask(:,:,1)
326# endif
327      ENDIF
328#endif
329#if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
330      ! Louvain La Neuve Sea Ice Model
331      IF( iom_varid( numror, 'nfbulk' ) > 0 ) THEN
332         CALL iom_get( numror             , 'nfbulk', znfbulk )   ! bulk computation frequency
333         CALL iom_get( numror, jpdom_local, 'gsst'  , gsst    )
334         IF( znfbulk /= REAL(nfbulk, wp) ) THEN      ! if you change nfbulk between 2 runs
335            zcoef = REAL( nfbulk-1, wp ) / znfbulk
336            gsst(:,:) = zcoef * gsst(:,:)
337         ENDIF
338      ELSE
339         IF(lwp) WRITE(numout,*)
340         IF(lwp) WRITE(numout,*) 'rst_read :  LLN sea Ice Model => Ice initialization'
341         IF(lwp) WRITE(numout,*)
342         gsst(:,:) = REAL( nfbulk - 1, wp )*( tn(:,:,1) + rt0 )
343      ENDIF
344#endif
345     
346      !!sm: end of TO BE MOVED IN NEW SURFACE MODULE...
347
348      IF( iom_varid( numror, 'rhd' ) > 0 ) THEN
349         CALL iom_get( numror, jpdom_local, 'rhd' , rhd  )
350         CALL iom_get( numror, jpdom_local, 'rhop', rhop )
351      ELSE
352         CALL eos( tb, sb, rhd, rhop )        ! before potential and in situ densities
353      ENDIF
354      IF( ln_zps .AND. .NOT. lk_cfg_1d ) THEN
355         IF( iom_varid( numror, 'gtu' ) > 0 ) THEN
356            CALL iom_get( numror, jpdom_local, 'gtu' , gtu )
357            CALL iom_get( numror, jpdom_local, 'gsu' , gsu )
358            CALL iom_get( numror, jpdom_local, 'gru' , gru )
359            CALL iom_get( numror, jpdom_local, 'gtv' , gtv )
360            CALL iom_get( numror, jpdom_local, 'gsv' , gsv )
361            CALL iom_get( numror, jpdom_local, 'grv' , grv )
362         ELSE
363            CALL zps_hde( nit000, tb , sb , rhd,   &  ! Partial steps: before Horizontal DErivative
364               &                  gtu, gsu, gru,   &  ! of t, s, rd at the bottom ocean level
365               &                  gtv, gsv, grv )
366         ENDIF
367      ENDIF
368      !
369   END SUBROUTINE rst_read
370
371
372   !!=====================================================================
373END MODULE restart
Note: See TracBrowser for help on using the repository browser.