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 NEMO/branches/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/OCE/IOM – NEMO

source: NEMO/branches/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/OCE/IOM/restart.F90 @ 14644

Last change on this file since 14644 was 14644, checked in by sparonuz, 3 years ago

Merge trunk -r14642:HEAD

  • Property svn:keywords set to Id
File size: 20.6 KB
Line 
1MODULE restart
2   !!======================================================================
3   !!                     ***  MODULE  restart  ***
4   !! Ocean restart :  write the ocean restart file
5   !!======================================================================
6   !! History :  OPA  !  1999-11  (M. Imbard)  Original code
7   !!   NEMO     1.0  !  2002-08  (G. Madec)  F90: Free form
8   !!            2.0  !  2006-07  (S. Masson)  use IOM for restart
9   !!            3.3  !  2010-04  (M. Leclair, G. Madec)  modified LF-RA
10   !!            - -  !  2010-10  (C. Ethe, G. Madec) TRC-TRA merge (T-S in 4D)
11   !!            3.7  !  2014-01  (G. Madec) suppression of curl and hdiv from the restart
12   !!             -   !  2014-12  (G. Madec) remove KPP scheme
13   !!            4.1  !  2020-11  (S. Techene, G. Madec)  move ssh initiatlisation in rst_read_ssh
14   !!             -   !                                   add restart in Shallow Water Eq. case
15   !!----------------------------------------------------------------------
16
17   !!----------------------------------------------------------------------
18   !!   rst_opn       : open the ocean restart file for writting
19   !!   rst_write     : write the ocean restart file
20   !!   rst_read_open : open the restart file for reading
21   !!   rst_read      : read the ocean restart file
22   !!   rst_read_ssh  : ssh set from restart or domcfg.nc file or usr_def_istat_ssh
23   !!----------------------------------------------------------------------
24   USE oce            ! ocean dynamics and tracers
25   USE dom_oce        ! ocean space and time domain
26   USE sbc_ice        ! only lk_si3
27   USE phycst         ! physical constants
28   USE eosbn2         ! equation of state
29   USE wet_dry        ! Wetting/Drying flux limiting
30   USE usrdef_istate, ONLY : usr_def_istate_ssh   ! user defined ssh initial state
31   USE trdmxl_oce     ! ocean active mixed layer tracers trends variables
32   USE diu_bulk       ! ???
33   !
34   USE in_out_manager ! I/O manager
35   USE iom            ! I/O module
36   USE lib_mpp        ! distribued memory computing library
37
38   IMPLICIT NONE
39   PRIVATE
40
41   PUBLIC   rst_opn         ! called by step.F90
42   PUBLIC   rst_write       ! called by step.F90
43   PUBLIC   rst_read_open   ! called in rst_read_ssh
44   PUBLIC   rst_read        ! called by istate.F90
45   PUBLIC   rst_read_ssh    ! called by domain.F90
46   
47   !! * Substitutions
48#  include "do_loop_substitute.h90"
49#  include "domzgr_substitute.h90"
50#  include "single_precision_substitute.h90"
51   !!----------------------------------------------------------------------
52   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
53   !! $Id$
54   !! Software governed by the CeCILL license (see ./LICENSE)
55   !!----------------------------------------------------------------------
56CONTAINS
57
58   SUBROUTINE rst_opn( kt )
59      !!---------------------------------------------------------------------
60      !!                   ***  ROUTINE rst_opn  ***
61      !!
62      !! ** Purpose : + initialization (should be read in the namelist) of nitrst
63      !!              + open the restart when we are one time step before nitrst
64      !!                   - restart header is defined when kt = nitrst-1
65      !!                   - restart data  are written when kt = nitrst
66      !!              + define lrst_oce to .TRUE. when we need to define or write the restart
67      !!----------------------------------------------------------------------
68      INTEGER, INTENT(in) ::   kt     ! ocean time-step
69      !!
70      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character
71      CHARACTER(LEN=50)   ::   clname   ! ocean output restart file name
72      CHARACTER(lc)       ::   clpath   ! full path to ocean output restart file
73      CHARACTER(LEN=52)   ::   clpname   ! ocean output restart file name including prefix for AGRIF
74      CHARACTER(LEN=256)  ::   clinfo    ! info character
75      !!----------------------------------------------------------------------
76      !
77      IF( kt == nit000 ) THEN   ! default definitions
78         lrst_oce = .FALSE.
79         IF( ln_rst_list ) THEN
80            nrst_lst = 1
81            nitrst = nn_stocklist( nrst_lst )
82         ELSE
83            nitrst = nitend
84         ENDIF
85      ENDIF
86
87      IF( .NOT. ln_rst_list .AND. nn_stock == -1 )   RETURN   ! we will never do any restart
88
89      ! frequency-based restart dumping (nn_stock)
90      IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nn_stock ) == 0 ) THEN
91         ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment
92         nitrst = kt + nn_stock - 1                  ! define the next value of nitrst for restart writing
93         IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run
94      ENDIF
95      ! to get better performances with NetCDF format:
96      ! we open and define the ocean restart file one time step before writing the data (-> at nitrst - 1)
97      ! except if we write ocean restart files every time step or if an ocean restart file was writen at nitend - 1
98      IF( kt == nitrst - 1 .OR. nn_stock == 1 .OR. ( kt == nitend .AND. .NOT. lrst_oce ) ) THEN
99         IF( nitrst <= nitend .AND. nitrst > 0 ) THEN
100            ! beware of the format used to write kt (default is i8.8, that should be large enough...)
101            IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst
102            ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst
103            ENDIF
104            ! create the file
105            clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_ocerst_out)
106            clpath = TRIM(cn_ocerst_outdir)
107            IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
108            IF(lwp) THEN
109               WRITE(numout,*)
110               IF(.NOT.lwxios) THEN
111                  WRITE(numout,*) '             open ocean restart NetCDF file: ',TRIM(clpath)//TRIM(clname)
112                  IF ( snc4set%luse )      WRITE(numout,*) '             opened for NetCDF4 chunking and compression'
113                  IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt
114                  ELSE                          ;   WRITE(numout,*) '             kt = '             , kt
115                  ENDIF
116               ENDIF
117            ENDIF
118            !
119            IF(.NOT.lwxios) THEN
120               CALL iom_open( TRIM(clpath)//TRIM(clname), numrow, ldwrt = .TRUE. )
121            ELSE
122#if defined key_xios
123               cw_ocerst_cxt = "rstw_"//TRIM(ADJUSTL(clkt))
124               IF( TRIM(Agrif_CFixed()) == '0' ) THEN
125                  clpname = clname
126               ELSE
127                  clpname = TRIM(Agrif_CFixed())//"_"//clname
128               ENDIF
129               numrow = iom_xios_setid(TRIM(clpath)//TRIM(clpname))
130               CALL iom_init( cw_ocerst_cxt, kdid = numrow, ld_closedef = .false. )
131               CALL iom_swap(      cxios_context          )
132#else
133               clinfo = 'Can not use XIOS in rst_opn'
134               CALL ctl_stop(TRIM(clinfo))
135#endif
136            ENDIF
137            lrst_oce = .TRUE.
138         ENDIF
139      ENDIF
140      !
141   END SUBROUTINE rst_opn
142
143
144   SUBROUTINE rst_write( kt, Kbb, Kmm )
145      !!---------------------------------------------------------------------
146      !!                   ***  ROUTINE rstwrite  ***
147      !!
148      !! ** Purpose :   Write restart fields in NetCDF format
149      !!
150      !! ** Method  :   Write in numrow when kt == nitrst in NetCDF
151      !!              file, save fields which are necessary for restart
152      !!
153      !!                NB: ssh is written here (rst_write)
154      !!                    but is read or set in rst_read_ssh
155      !!----------------------------------------------------------------------
156      INTEGER, INTENT(in) ::   kt         ! ocean time-step
157      INTEGER, INTENT(in) ::   Kbb, Kmm   ! ocean time level indices
158      !!----------------------------------------------------------------------
159      !
160         CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rn_Dt       )   ! dynamics time step
161      !
162      IF( .NOT.lwxios )   CALL iom_delay_rst( 'WRITE', 'OCE', numrow )   ! save only ocean delayed global communication variables
163      !
164      IF( .NOT.ln_diurnal_only ) THEN
165         CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , ssh(:,:        ,Kbb) )     ! before fields
166         CALL iom_rstput( kt, nitrst, numrow, 'ub'     , uu(:,:,:       ,Kbb) )
167         CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vv(:,:,:       ,Kbb) )
168         IF( .NOT.lk_SWE ) THEN
169            CALL iom_rstput( kt, nitrst, numrow, 'tb'  , ts(:,:,:,jp_tem,Kbb) )
170            CALL iom_rstput( kt, nitrst, numrow, 'sb'  , ts(:,:,:,jp_sal,Kbb) )
171         ENDIF
172         !
173#if ! defined key_RK3
174         CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , ssh(:,:        ,Kmm) )     ! now fields
175         CALL iom_rstput( kt, nitrst, numrow, 'un'     , uu(:,:,:       ,Kmm) )
176         CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vv(:,:,:       ,Kmm) )
177         IF( .NOT.lk_SWE ) THEN
178            CALL iom_rstput( kt, nitrst, numrow, 'tn'  , ts(:,:,:,jp_tem,Kmm) )
179            CALL iom_rstput( kt, nitrst, numrow, 'sn'  , ts(:,:,:,jp_sal,Kmm) )
180            CALL iom_rstput( kt, nitrst, numrow, 'rhop', rhop                 )
181         ENDIF
182#endif
183      ENDIF
184
185      IF( ln_diurnal )   CALL iom_rstput( kt, nitrst, numrow, 'Dsst', x_dsst )
186      IF( kt == nitrst ) THEN
187         IF( .NOT.lwxios ) THEN
188            CALL iom_close( numrow )     ! close the restart file (only at last time step)
189         ELSE
190            CALL iom_context_finalize(      cw_ocerst_cxt          )
191            iom_file(numrow)%nfid       = 0
192            numrow = 0
193         ENDIF
194!!gm         IF( .NOT. lk_trdmld )   lrst_oce = .FALSE.
195!!gm  not sure what to do here   ===>>>  ask to Sebastian
196         lrst_oce = .FALSE.
197         IF( ln_rst_list ) THEN
198            nrst_lst = MIN(nrst_lst + 1, SIZE(nn_stocklist,1))
199            nitrst   = nn_stocklist( nrst_lst )
200         ENDIF
201      ENDIF
202      !
203   END SUBROUTINE rst_write
204
205
206   SUBROUTINE rst_read_open
207      !!----------------------------------------------------------------------
208      !!                   ***  ROUTINE rst_read_open  ***
209      !!
210      !! ** Purpose :   Open read files for NetCDF restart
211      !!
212      !! ** Method  :   Use a non-zero, positive value of numror to assess whether or not
213      !!                the file has already been opened
214      !!----------------------------------------------------------------------
215      LOGICAL             ::   llok
216      CHARACTER(len=lc)   ::   clpath   ! full path to ocean output restart file
217      CHARACTER(len=lc+2) ::   clpname  ! file name including agrif prefix
218      !!----------------------------------------------------------------------
219      !
220      IF( numror <= 0 ) THEN
221         IF(lwp) THEN                                             ! Contol prints
222            WRITE(numout,*)
223            WRITE(numout,*) 'rst_read : read oce NetCDF restart file'
224            IF ( snc4set%luse )      WRITE(numout,*) 'rst_read : configured with NetCDF4 support'
225            WRITE(numout,*) '~~~~~~~~'
226         ENDIF
227         lxios_sini = .FALSE.
228         clpath = TRIM(cn_ocerst_indir)
229         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
230         CALL iom_open( TRIM(clpath)//cn_ocerst_in, numror )
231! are we using XIOS to read the data? Part above will have to modified once XIOS
232! can handle checking if variable is in the restart file (there will be no need to open
233! restart)
234         lrxios = lrxios.AND.lxios_sini
235
236         IF( lrxios) THEN
237             cr_ocerst_cxt = 'oce_rst'
238             IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS'
239!            IF( TRIM(Agrif_CFixed()) == '0' ) THEN
240!               clpname = cn_ocerst_in
241!            ELSE
242!               clpname = TRIM(Agrif_CFixed())//"_"//cn_ocerst_in
243!            ENDIF
244             CALL iom_init( cr_ocerst_cxt, kdid = numror, ld_closedef = .TRUE. )
245             CALL iom_swap(      cxios_context          )
246         ENDIF
247
248      ENDIF
249
250   END SUBROUTINE rst_read_open
251
252
253   SUBROUTINE rst_read( Kbb, Kmm )
254      !!----------------------------------------------------------------------
255      !!                   ***  ROUTINE rst_read  ***
256      !!
257      !! ** Purpose :   Read velocity and T-S fields in the restart file
258      !!
259      !! ** Method  :   Read in restart.nc fields which are necessary for restart
260      !!
261      !!                NB: restart file openned           in DOM/domain.F90:dom_init
262      !!                    before field in restart tested in DOM/domain.F90:dom_init
263      !!                    (sshb)
264      !!
265      !!                NB: ssh is read or set in rst_read_ssh
266      !!----------------------------------------------------------------------
267      INTEGER          , INTENT(in) ::   Kbb, Kmm   ! ocean time level indices
268      INTEGER  ::   jk
269      REAL(wp), DIMENSION(jpi, jpj, jpk) :: w3d
270      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   :: zgdept       ! 3D workspace for QCO
271      !!----------------------------------------------------------------------
272      !
273      IF(.NOT.lrxios )   CALL iom_delay_rst( 'READ', 'OCE', numror )   ! read only ocean delayed global communication variables
274      !
275      !                             !*  Diurnal DSST
276      IF( ln_diurnal )   CALL iom_get( numror, jpdom_auto, 'Dsst' , x_dsst )
277      IF( ln_diurnal_only ) THEN
278         IF(lwp) WRITE( numout, * ) &
279         &   "rst_read:- ln_diurnal_only set, setting rhop=rho0"
280         rhop = rho0
281         CALL iom_get( numror, jpdom_auto, 'tn'     , w3d )
282         ts(:,:,1,jp_tem,Kmm) = w3d(:,:,1)
283         RETURN
284      ENDIF
285      !
286#if defined key_RK3
287      !                             !*  Read Kbb fields   (NB: in RK3 Kmm = Kbb = Nbb)
288      IF(lwp) WRITE(numout,*) '           Kbb u, v and T-S fields read in the restart file'
289      CALL iom_get( numror, jpdom_auto, 'ub'   , uu(:,:,:       ,Kbb), cd_type = 'U', psgn = -1._wp )
290      CALL iom_get( numror, jpdom_auto, 'vb'   , vv(:,:,:       ,Kbb), cd_type = 'V', psgn = -1._wp )
291      IF( .NOT.lk_SWE ) THEN
292         CALL iom_get( numror, jpdom_auto, 'tb', ts(:,:,:,jp_tem,Kbb) )
293         CALL iom_get( numror, jpdom_auto, 'sb', ts(:,:,:,jp_sal,Kbb) )
294      ENDIF
295#else
296      !                             !*  Read Kmm fields   (MLF only)
297      IF(lwp) WRITE(numout,*)    '           Kmm u, v and T-S fields read in the restart file'
298      CALL iom_get( numror, jpdom_auto, 'un'   , uu(:,:,:       ,Kmm), cd_type = 'U', psgn = -1._wp )
299      CALL iom_get( numror, jpdom_auto, 'vn'   , vv(:,:,:       ,Kmm), cd_type = 'V', psgn = -1._wp )
300      IF( .NOT.lk_SWE ) THEN
301         CALL iom_get( numror, jpdom_auto, 'tn', ts(:,:,:,jp_tem,Kmm) )
302         CALL iom_get( numror, jpdom_auto, 'sn', ts(:,:,:,jp_sal,Kmm) )
303      ENDIF
304      !
305      IF( l_1st_euler ) THEN        !*  Euler restart   (MLF only)
306         IF(lwp) WRITE(numout,*) '           Kbb u, v and T-S fields set to Kmm values'
307         uu(:,:,:  ,Kbb) = uu(:,:,:  ,Kmm)         ! all before fields set to now values
308         vv(:,:,:  ,Kbb) = vv(:,:,:  ,Kmm)
309         IF( .NOT.lk_SWE ) ts(:,:,:,:,Kbb) = ts(:,:,:,:,Kmm)
310         !
311      ELSE                          !* Leap frog restart   (MLF only)
312         IF(lwp) WRITE(numout,*) '           Kbb u, v and T-S fields read in the restart file'
313         CALL iom_get( numror, jpdom_auto, 'ub'   , uu(:,:,:       ,Kbb), cd_type = 'U', psgn = -1._wp )
314         CALL iom_get( numror, jpdom_auto, 'vb'   , vv(:,:,:       ,Kbb), cd_type = 'V', psgn = -1._wp )
315         IF( .NOT.lk_SWE ) THEN
316            CALL iom_get( numror, jpdom_auto, 'tb', ts(:,:,:,jp_tem,Kbb) )
317            CALL iom_get( numror, jpdom_auto, 'sb', ts(:,:,:,jp_sal,Kbb) )
318         ENDIF
319      ENDIF
320#endif
321      !
322      IF( .NOT.lk_SWE ) THEN
323         IF( iom_varid( numror, 'rhop', ldstop = .FALSE. ) > 0 ) THEN
324            CALL iom_get( numror, jpdom_auto, 'rhop'   , rhop )   ! now    potential density
325         ELSE
326#if defined key_qco
327            ALLOCATE( zgdept(jpi,jpj,jpk) )
328            DO jk = 1, jpk
329               zgdept(:,:,jk) = gdept(:,:,jk,Kmm)
330            END DO
331            CALL eos( CASTWP(ts(:,:,:,:,Kmm)), rhd, rhop, zgdept )
332            DEALLOCATE( zgdept )
333#else
334            CALL eos( CASTWP(ts(:,:,:,:,Kmm)), rhd, rhop, CASTWP(gdept(:,:,:,Kmm)) )
335#endif
336         ENDIF
337      ENDIF
338      !
339   END SUBROUTINE rst_read
340
341
342   SUBROUTINE rst_read_ssh( Kbb, Kmm, Kaa )
343      !!---------------------------------------------------------------------
344      !!                   ***  ROUTINE rst_read_ssh  ***
345      !!
346      !! ** Purpose :   ssh initialization of the sea surface height (ssh)
347      !!
348      !! ** Method  :   set ssh from restart or read configuration, or user_def
349      !!              * ln_rstart = T
350      !!                   USE of IOM library to read ssh in the restart file
351      !!                   Leap-Frog: Kbb and Kmm are read except for l_1st_euler=T
352      !!
353      !!              * otherwise
354      !!                   call user defined ssh or
355      !!                   set to -ssh_ref in wet and drying case with domcfg.nc
356      !!
357      !!              NB: ssh_b/n are written by restart.F90
358      !!----------------------------------------------------------------------
359      INTEGER, INTENT(in) ::   Kbb, Kmm, Kaa   ! ocean time level indices
360      !
361      INTEGER ::   ji, jj, jk
362      !!----------------------------------------------------------------------
363      !
364      IF(lwp) THEN
365         WRITE(numout,*)
366         WRITE(numout,*) 'rst_read_ssh : ssh initialization'
367         WRITE(numout,*) '~~~~~~~~~~~~ '
368      ENDIF
369      !
370      !                            !=============================!
371      IF( ln_rstart ) THEN         !==  Read the restart file  ==!
372         !                         !=============================!
373         !
374#if defined key_RK3
375         !                                     !*  RK3: Read ssh at Kbb
376         IF(lwp) WRITE(numout,*)
377         IF(lwp) WRITE(numout,*)    '      Kbb sea surface height read in the restart file'
378         CALL iom_get( numror, jpdom_auto, 'sshb'   , ssh(:,:,Kbb) )
379         !
380         !                                     !*  RK3: Set ssh at Kmm for AGRIF
381         ssh(:,:,Kmm) = 0._wp
382#else
383         !                                     !*  MLF: Read ssh at Kmm
384         IF(lwp) WRITE(numout,*)
385         IF(lwp) WRITE(numout,*)    '      Kmm sea surface height read in the restart file'
386         CALL iom_get( numror, jpdom_auto, 'sshn'   , ssh(:,:,Kmm) )
387         !
388         IF( l_1st_euler ) THEN                !*  MLF: Euler at first time-step
389            IF(lwp) WRITE(numout,*)
390            IF(lwp) WRITE(numout,*) '      Euler first time step : ssh(Kbb) = ssh(Kmm)'
391            ssh(:,:,Kbb) = ssh(:,:,Kmm)
392            !
393         ELSE                                  !*  MLF: read ssh at Kbb
394            IF(lwp) WRITE(numout,*)
395            IF(lwp) WRITE(numout,*) '      Kbb sea surface height read in the restart file'
396            CALL iom_get( numror, jpdom_auto, 'sshb', ssh(:,:,Kbb) )
397         ENDIF
398#endif
399         !                         !============================!
400      ELSE                         !==  Initialize at "rest"  ==!
401         !                         !============================!
402         !
403         IF(lwp) WRITE(numout,*)
404         IF(lwp) WRITE(numout,*)    '      initialization at rest'
405         !
406         IF( ll_wd ) THEN                      !* wet and dry
407            !
408            IF( ln_read_cfg  ) THEN                 ! read configuration : ssh_ref is read in domain_cfg file
409!!st  why ssh is not masked : i.e. ssh(:,:,Kmm) = -ssh_ref*ssmask(:,:),
410!!st  since at the 1st time step lbclnk will be applied on ssh at Kaa but not initially at Kbb and Kmm
411               ssh(:,:,Kbb) = -ssh_ref
412               !
413               DO_2D( 1, 1, 1, 1 )
414                  IF( ht_0(ji,jj)-ssh_ref <  rn_wdmin1 ) THEN   ! if total depth is less than min depth
415                     ssh(ji,jj,Kbb) = rn_wdmin1 - ht_0(ji,jj)
416                  ENDIF
417               END_2D
418            ELSE                                    ! user define configuration case 
419               CALL usr_def_istate_ssh( tmask, ssh(:,:,Kbb) )
420            ENDIF
421            !
422         ELSE                                  !* user defined configuration
423            CALL usr_def_istate_ssh( tmask, ssh(:,:,Kbb) )
424            !
425         ENDIF
426         !
427#if defined key_RK3
428         ssh(:,:,Kmm) = 0._wp                  !* RK3: set Kmm to 0 for AGRIF
429#else
430         ssh(:,:,Kmm) = ssh(:,:,Kbb)           !* MLF: set now values from to before ones
431#endif
432      ENDIF
433      !
434      !                            !==========================!
435      ssh(:,:,Kaa) = 0._wp         !==  Set to 0 for AGRIF  ==!
436      !                            !==========================!
437      !
438   END SUBROUTINE rst_read_ssh
439
440   !!=====================================================================
441END MODULE restart
Note: See TracBrowser for help on using the repository browser.