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

source: tags/nemo_v1_13_dev7/NEMO/OPA_SRC/restart.F90 @ 3319

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

nemo_v1_update_071:RB: add iom for restart and reorganization of restart

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