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_r12563_ASINTER-06_ABL_improvement/src/TOP – NEMO

source: NEMO/branches/2020/dev_r12563_ASINTER-06_ABL_improvement/src/TOP/trcrst.F90 @ 12587

Last change on this file since 12587 was 12489, checked in by davestorkey, 4 years ago

Preparation for new timestepping scheme #2390.
Main changes:

  1. Initial euler timestep now handled in stp and not in TRA/DYN routines.
  2. Renaming of all timestep parameters. In summary, the namelist parameter is now rn_Dt and the current timestep is rDt (and rDt_ice, rDt_trc etc).
  3. Renaming of a few miscellaneous parameters, eg. atfp -> rn_atfp (namelist parameter used everywhere) and rau0 -> rho0.

This version gives bit-comparable results to the previous version of the trunk.

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