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

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

nemo_v1_update_078:RB: finalization of IOM (2)

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