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

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

nemo_v1_update_73 : CT : build Mixed Layer restart files using iom

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