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.
trcrst.F90 in NEMO/branches/2020/dev_r13787_doc_latex_recovery/src/TOP – NEMO

source: NEMO/branches/2020/dev_r13787_doc_latex_recovery/src/TOP/trcrst.F90 @ 14083

Last change on this file since 14083 was 14066, checked in by nicolasmartin, 4 years ago

#2414 Sync merge with trunk

  • Property svn:keywords set to Id
File size: 18.0 KB
Line 
1MODULE trcrst
2   !!======================================================================
3   !!                         ***  MODULE trcrst  ***
4   !! TOP :   Manage the passive tracer restart
5   !!======================================================================
6   !! History :    -   !  1991-03  ()  original code
7   !!             1.0  !  2005-03 (O. Aumont, A. El Moussaoui) F90
8   !!              -   !  2005-10 (C. Ethe) print control
9   !!             2.0  !  2005-10 (C. Ethe, G. Madec) revised architecture
10   !!----------------------------------------------------------------------
11#if defined key_top
12   !!----------------------------------------------------------------------
13   !!   'key_top'                                                TOP models
14   !!----------------------------------------------------------------------
15   !!----------------------------------------------------------------------
16   !!   trc_rst        : Restart for passive tracer
17   !!   trc_rst_opn    : open  restart file
18   !!   trc_rst_read   : read  restart file
19   !!   trc_rst_wri    : write restart file
20   !!----------------------------------------------------------------------
21   USE oce_trc
22   USE trc
23   USE iom
24   USE daymod
25   USE lib_mpp
26   
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   trc_rst_opn       ! called by ???
31   PUBLIC   trc_rst_read      ! called by ???
32   PUBLIC   trc_rst_wri       ! called by ???
33   PUBLIC   trc_rst_cal
34
35#  include "domzgr_substitute.h90"
36   !!----------------------------------------------------------------------
37   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
38   !! $Id$
39   !! Software governed by the CeCILL license (see ./LICENSE)
40   !!----------------------------------------------------------------------
41CONTAINS
42   
43   SUBROUTINE trc_rst_opn( kt )
44      !!----------------------------------------------------------------------
45      !!                    ***  trc_rst_opn  ***
46      !!
47      !! ** purpose  :   output of sea-trc variable in a netcdf file
48      !!----------------------------------------------------------------------
49      INTEGER, INTENT(in) ::   kt       ! number of iteration
50      !
51      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step define as a character
52      CHARACTER(LEN=50)   ::   clname   ! trc output restart file name
53      CHARACTER(LEN=256)  ::   clpath   ! full path to ocean output restart file
54      CHARACTER(LEN=50)   ::   clpname  ! trc output restart file name including AGRIF
55      !!----------------------------------------------------------------------
56      !
57      IF( l_offline ) THEN
58         IF( kt == nittrc000 ) THEN
59            lrst_trc = .FALSE.
60            IF( ln_rst_list ) THEN
61               nrst_lst = 1
62               nitrst = nn_stocklist( nrst_lst )
63            ELSE
64               nitrst = nitend
65            ENDIF
66         ENDIF
67
68         IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nn_stock ) == 0 ) THEN
69            ! we use kt - 1 and not kt - nittrc000 to keep the same periodicity from the beginning of the experiment
70            nitrst = kt + nn_stock - 1                  ! define the next value of nitrst for restart writing
71            IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run
72         ENDIF
73      ELSE
74         IF( kt == nittrc000 ) lrst_trc = .FALSE.
75      ENDIF
76
77      IF( .NOT. ln_rst_list .AND. nn_stock == -1 )   RETURN   ! we will never do any restart
78
79      ! to get better performances with NetCDF format:
80      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 1)
81      ! except if we write tracer restart files every tracer time step or if a tracer restart file was writen at nitend - 1
82      IF( kt == nitrst - 1 .OR. nn_stock == 1 .OR. ( kt == nitend - 1 .AND. .NOT. lrst_trc ) ) THEN
83         ! beware of the format used to write kt (default is i8.8, that should be large enough)
84         IF( nitrst > 1.0e9 ) THEN   ;   WRITE(clkt,*       ) nitrst
85         ELSE                        ;   WRITE(clkt,'(i8.8)') nitrst
86         ENDIF
87         ! create the file
88         IF(lwp) WRITE(numout,*)
89         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_trcrst_out)
90         clpath = TRIM(cn_trcrst_outdir)
91         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
92         IF(lwp) WRITE(numout,*) &
93             '             open trc restart.output NetCDF file: ',TRIM(clpath)//clname
94         IF(.NOT.lwxios) THEN
95            CALL iom_open( TRIM(clpath)//TRIM(clname), numrtw, ldwrt = .TRUE. )
96         ELSE
97#if defined key_iomput
98            cw_toprst_cxt = "rstwt_"//TRIM(ADJUSTL(clkt))
99            IF( TRIM(Agrif_CFixed()) == '0' ) THEN
100               clpname = clname
101            ELSE
102               clpname = TRIM(Agrif_CFixed())//"_"//clname
103            ENDIF
104            numrtw = iom_xios_setid(TRIM(clpath)//TRIM(clpname))
105            CALL iom_init( cw_toprst_cxt, kdid = numrtw, ld_closedef = .FALSE. )
106#else
107            CALL ctl_stop( 'Can not use XIOS in trc_rst_opn' )
108#endif
109         ENDIF
110         lrst_trc = .TRUE.
111      ENDIF
112      !
113   END SUBROUTINE trc_rst_opn
114
115   SUBROUTINE trc_rst_read( Kbb, Kmm )
116      !!----------------------------------------------------------------------
117      !!                    ***  trc_rst_opn  ***
118      !!
119      !! ** purpose  :   read passive tracer fields in restart files
120      !!----------------------------------------------------------------------
121      INTEGER, INTENT( in ) ::   Kbb, Kmm  ! time level indices
122      INTEGER  ::  jn     
123
124      !!----------------------------------------------------------------------
125      !
126      IF(lwp) WRITE(numout,*)
127      IF(lwp) WRITE(numout,*) 'trc_rst_read : read data in the TOP restart file'
128      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
129
130      ! READ prognostic variables and computes diagnostic variable
131      DO jn = 1, jptra
132         CALL iom_get( numrtr, jpdom_auto, 'TRN'//ctrcnm(jn), tr(:,:,:,jn,Kmm) )
133      END DO
134
135      DO jn = 1, jptra
136         CALL iom_get( numrtr, jpdom_auto, 'TRB'//ctrcnm(jn), tr(:,:,:,jn,Kbb) )
137      END DO
138      !
139      IF(.NOT.lrxios) CALL iom_delay_rst( 'READ', 'TOP', numrtr )   ! read only TOP delayed global communication variables
140   END SUBROUTINE trc_rst_read
141
142   SUBROUTINE trc_rst_wri( kt, Kbb, Kmm, Krhs )
143      !!----------------------------------------------------------------------
144      !!                    ***  trc_rst_wri  ***
145      !!
146      !! ** purpose  :   write passive tracer fields in restart files
147      !!----------------------------------------------------------------------
148      INTEGER, INTENT( in ) ::   kt              ! ocean time-step index
149      INTEGER, INTENT( in ) ::   Kbb, Kmm, Krhs  ! time level indices
150      !!
151      INTEGER  :: jn
152      !!----------------------------------------------------------------------
153      !
154      CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rn_Dt )   ! passive tracer time step (= ocean time step)
155      ! prognostic variables
156      ! --------------------
157      DO jn = 1, jptra
158         CALL iom_rstput( kt, nitrst, numrtw, 'TRN'//ctrcnm(jn), tr(:,:,:,jn,Kmm) )
159      END DO
160
161      DO jn = 1, jptra
162         CALL iom_rstput( kt, nitrst, numrtw, 'TRB'//ctrcnm(jn), tr(:,:,:,jn,Kbb) )
163      END DO
164
165      IF( .NOT. lwxios ) CALL iom_delay_rst( 'WRITE', 'TOP', numrtw )   ! save only TOP delayed global communication variables
166   
167      IF( kt == nitrst ) THEN
168          CALL trc_rst_stat( Kmm, Krhs )             ! statistics
169          IF(lwxios) THEN
170             CALL iom_context_finalize(      cw_toprst_cxt          )
171             iom_file(numrtw)%nfid       = 0
172             numrtw = 0
173          ELSE
174             CALL iom_close( numrtw )     ! close the restart file (only at last time step)
175          ENDIF
176#if ! defined key_trdmxl_trc
177          lrst_trc = .FALSE.
178#endif
179          IF( l_offline .AND. ln_rst_list ) THEN
180             nrst_lst = nrst_lst + 1
181             nitrst = nn_stocklist( nrst_lst )
182          ENDIF
183      ENDIF
184      !
185   END SUBROUTINE trc_rst_wri 
186
187
188   SUBROUTINE trc_rst_cal( kt, cdrw )
189      !!---------------------------------------------------------------------
190      !!                   ***  ROUTINE trc_rst_cal  ***
191      !!
192      !!  ** Purpose : Read or write calendar in restart file:
193      !!
194      !!  WRITE(READ) mode:
195      !!       kt        : number of time step since the begining of the experiment at the
196      !!                   end of the current(previous) run
197      !!       adatrj(0) : number of elapsed days since the begining of the experiment at the
198      !!                   end of the current(previous) run (REAL -> keep fractions of day)
199      !!       ndastp    : date at the end of the current(previous) run (coded as yyyymmdd integer)
200      !!
201      !!   According to namelist parameter nrstdt,
202      !!       nn_rsttr = 0  no control on the date (nittrc000 is  arbitrary).
203      !!       nn_rsttr = 1  we verify that nittrc000 is equal to the last
204      !!                   time step of previous run + 1.
205      !!       In both those options, the  exact duration of the experiment
206      !!       since the beginning (cumulated duration of all previous restart runs)
207      !!       is not stored in the restart and is assumed to be (nittrc000-1)*rn_Dt.
208      !!       This is valid is the time step has remained constant.
209      !!
210      !!       nn_rsttr = 2  the duration of the experiment in days (adatrj)
211      !!                    has been stored in the restart file.
212      !!----------------------------------------------------------------------
213      INTEGER         , INTENT(in) ::   kt         ! ocean time-step
214      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag
215      !
216      LOGICAL  ::  llok
217      REAL(wp) ::  zrdttrc1, zkt, zndastp, zdayfrac, ksecs, ktime
218      INTEGER  ::   ihour, iminute
219      CHARACTER(len=82) :: clpname
220
221      ! Time domain : restart
222      ! ---------------------
223
224      IF( TRIM(cdrw) == 'READ' ) THEN
225
226         IF(lwp) WRITE(numout,*)
227         IF(lwp) WRITE(numout,*) 'trc_rst_cal : read the TOP restart file for calendar'
228         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
229
230         IF( ln_rsttr ) THEN
231            lxios_sini = .FALSE.
232            CALL iom_open( TRIM(cn_trcrst_indir)//'/'//cn_trcrst_in, numrtr )
233            IF( lrxios) THEN
234                cr_toprst_cxt = 'top_rst'
235                IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS for TOP'
236!               IF( TRIM(Agrif_CFixed()) == '0' ) THEN
237!                  clpname = cn_trcrst_in
238!               ELSE
239!                  clpname = TRIM(Agrif_CFixed())//"_"//cn_trcrst_in   
240!               ENDIF
241                CALL iom_init( cr_toprst_cxt, kdid = numrtr, ld_closedef = .TRUE. )
242            ENDIF
243
244            CALL iom_get ( numrtr, 'kt', zkt )   ! last time-step of previous run
245
246            IF(lwp) THEN
247               WRITE(numout,*) ' *** Info read in restart : '
248               WRITE(numout,*) '   previous time-step                               : ', NINT( zkt )
249               WRITE(numout,*) ' *** restart option'
250               SELECT CASE ( nn_rsttr )
251               CASE ( 0 )   ;   WRITE(numout,*) ' nn_rsttr = 0 : no control of nittrc000'
252               CASE ( 1 )   ;   WRITE(numout,*) ' nn_rsttr = 1 : no control the date at nittrc000 (use ndate0 read in the namelist)'
253               CASE ( 2 )   ;   WRITE(numout,*) ' nn_rsttr = 2 : calendar parameters read in restart'
254               END SELECT
255               WRITE(numout,*)
256            ENDIF
257            ! Control of date
258            IF( nittrc000  - NINT( zkt ) /= 1 .AND.  nn_rsttr /= 0 )                                  &
259               &   CALL ctl_stop( ' ===>>>> : problem with nittrc000 for the restart',                 &
260               &                  ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' )
261         ENDIF
262         !
263         IF( l_offline ) THEN   
264            !                                          ! set the date in offline mode
265            IF( ln_rsttr .AND. nn_rsttr == 2 ) THEN
266               CALL iom_get( numrtr, 'ndastp', zndastp )
267               ndastp = NINT( zndastp )
268               CALL iom_get( numrtr, 'adatrj', adatrj  )
269               CALL iom_get( numrtr, 'ntime' , ktime   )
270               nn_time0=INT(ktime)
271               ! calculate start time in hours and minutes
272               zdayfrac=adatrj-INT(adatrj)
273               ksecs = NINT(zdayfrac*86400)            ! Nearest second to catch rounding errors in adatrj
274               ihour = INT(ksecs/3600)
275               iminute = ksecs/60-ihour*60
276               
277               ! Add to nn_time0
278               nhour   =   nn_time0 / 100
279               nminute = ( nn_time0 - nhour * 100 )
280               nminute=nminute+iminute
281               
282               IF( nminute >= 60 ) THEN
283                  nminute=nminute-60
284                  nhour=nhour+1
285               ENDIF
286               nhour=nhour+ihour
287               IF( nhour >= 24 ) THEN
288                  nhour=nhour-24
289                  adatrj=adatrj+1
290               ENDIF           
291               nn_time0 = nhour * 100 + nminute
292               adatrj = INT(adatrj)                    ! adatrj set to integer as nn_time0 updated           
293             ELSE
294               ndt05 = NINT( 0.5 * rn_Dt  )   !  --- WARNING --- not defined yet are we did not go through day_init
295               ! parameters corresponding to nit000 - 1 (as we start the step
296               ! loop with a call to day)
297               ndastp = ndate0        ! ndate0 read in the namelist in dom_nam
298               nhour   =   nn_time0 / 100
299               nminute = ( nn_time0 - nhour * 100 )
300               IF( nhour*3600+nminute*60-ndt05 .lt. 0 )  ndastp=ndastp-1      ! Start hour is specified in the namelist (default 0)
301               adatrj = ( REAL( nit000-1, wp ) * rn_Dt ) / rday
302               ! note this is wrong if time step has changed during run
303            ENDIF
304            IF( ABS(adatrj  - REAL(NINT(adatrj),wp)) < 0.1 / rday )   adatrj = REAL(NINT(adatrj),wp)   ! avoid truncation error
305            !
306            IF(lwp) THEN
307              WRITE(numout,*) ' *** Info used values : '
308              WRITE(numout,*) '   date ndastp                                      : ', ndastp
309              WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj
310              WRITE(numout,*) '   nn_time0                                         : ', nn_time0
311              WRITE(numout,*)
312            ENDIF
313            !
314            IF( ln_rsttr )  THEN   ;    l_1st_euler = .false.
315            ELSE                   ;    l_1st_euler = .true.
316            ENDIF
317            !
318            CALL day_init          ! compute calendar
319            !
320         ENDIF
321         !
322      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
323         !
324         IF(  kt == nitrst ) THEN
325            IF(lwp) WRITE(numout,*)
326            IF(lwp) WRITE(numout,*) 'trc_wri : write the TOP restart file (NetCDF) at it= ', kt, ' date= ', ndastp
327            IF(lwp) WRITE(numout,*) '~~~~~~~'
328         ENDIF
329         CALL iom_rstput( kt, nitrst, numrtw, 'kt'     , REAL( kt    , wp)   )   ! time-step
330         CALL iom_rstput( kt, nitrst, numrtw, 'ndastp' , REAL( ndastp, wp)   )   ! date
331         CALL iom_rstput( kt, nitrst, numrtw, 'adatrj' , adatrj              )   ! number of elapsed days since
332         !                                                                     ! the begining of the run [s]
333         CALL iom_rstput( kt, nitrst, numrtw, 'ntime'  , REAL( nn_time0, wp) ) ! time
334      ENDIF
335
336   END SUBROUTINE trc_rst_cal
337
338
339   SUBROUTINE trc_rst_stat( Kmm, Krhs )
340      !!----------------------------------------------------------------------
341      !!                    ***  trc_rst_stat  ***
342      !!
343      !! ** purpose  :   Compute tracers statistics
344      !!----------------------------------------------------------------------
345      INTEGER, INTENT( in ) ::   Kmm, Krhs  ! time level indices
346      INTEGER  :: jk, jn
347      REAL(wp) :: ztraf, zmin, zmax, zmean, zdrift
348      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zvol
349      !!----------------------------------------------------------------------
350
351      IF( lwp ) THEN
352         WRITE(numout,*) 
353         WRITE(numout,*) '           ----TRACER STAT----             '
354         WRITE(numout,*) 
355      ENDIF
356      !
357      DO jk = 1, jpk
358         zvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Krhs) * tmask(:,:,jk)
359      END DO
360      !
361      DO jn = 1, jptra
362         ztraf = glob_sum( 'trcrst', tr(:,:,:,jn,Kmm) * zvol(:,:,:) )
363         zmin  = MINVAL( tr(:,:,:,jn,Kmm), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
364         zmax  = MAXVAL( tr(:,:,:,jn,Kmm), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
365         IF( lk_mpp ) THEN
366            CALL mpp_min( 'trcrst', zmin )      ! min over the global domain
367            CALL mpp_max( 'trcrst', zmax )      ! max over the global domain
368         END IF
369         zmean  = ztraf / areatot
370         zdrift = ( ( ztraf - trai(jn) ) / ( trai(jn) + 1.e-12 )  ) * 100._wp
371         IF(lwp) WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), zmean, zmin, zmax, zdrift
372      END DO
373      IF(lwp) WRITE(numout,*) 
3749000  FORMAT(' tracer nb :',i2,'    name :',a10,'    mean :',e18.10,'    min :',e18.10, &
375      &      '    max :',e18.10,'    drift :',e18.10, ' %')
376      !
377   END SUBROUTINE trc_rst_stat
378
379#else
380   !!----------------------------------------------------------------------
381   !!  Dummy module :                                     No passive tracer
382   !!----------------------------------------------------------------------
383CONTAINS
384   SUBROUTINE trc_rst_read( Kbb, Kmm)                      ! Empty routines
385      INTEGER, INTENT( in ) :: Kbb, Kmm  ! time level indices
386   END SUBROUTINE trc_rst_read
387   SUBROUTINE trc_rst_wri( kt, Kbb, Kmm, Krhs )
388      INTEGER, INTENT( in ) :: kt
389      INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs  ! time level indices
390      WRITE(*,*) 'trc_rst_wri: You should not have seen this print! error?', kt
391   END SUBROUTINE trc_rst_wri   
392#endif
393
394   !!----------------------------------------------------------------------
395   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
396   !! $Id$
397   !! Software governed by the CeCILL license (see ./LICENSE)
398   !!======================================================================
399END MODULE trcrst
Note: See TracBrowser for help on using the repository browser.