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

Last change on this file since 557 was 557, checked in by opalod, 18 years ago

nemo_v1_bugfix_069: SM+CT+CE: bugfix of mld restart + OFF line compatibiblity

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