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/UKMO/NEMO_4.0.4_GO8_paquage_branch/src/TOP – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.4_GO8_paquage_branch/src/TOP/trcrst.F90 @ 15701

Last change on this file since 15701 was 15701, checked in by jpalmier, 2 years ago

enable TOP restart with date instead of time-step

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