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 trunk/NEMOGCM/NEMO/TOP_SRC – NEMO

source: trunk/NEMOGCM/NEMO/TOP_SRC/trcrst.F90 @ 5504

Last change on this file since 5504 was 5504, checked in by cetlod, 9 years ago

bugfix: computation of the meskmask from coordinate/bathymetry if needed in offline mode, see ticket #1545

  • Property svn:keywords set to Id
File size: 14.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   !!----------------------------------------------------------------------
18   !!----------------------------------------------------------------------
19   !!   'key_top'                                                TOP models
20   !!----------------------------------------------------------------------
21   !!   trc_rst_opn    : open  restart file
22   !!   trc_rst_read   : read  restart file
23   !!   trc_rst_wri    : write restart file
24   !!----------------------------------------------------------------------
25   USE oce_trc
26   USE trc
27   USE trcnam_trp
28   USE iom
29   USE daymod
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC   trc_rst_opn       ! called by ???
34   PUBLIC   trc_rst_read      ! called by ???
35   PUBLIC   trc_rst_wri       ! called by ???
36   PUBLIC   trc_rst_cal
37
38   !! * Substitutions
39#  include "top_substitute.h90"
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      !!----------------------------------------------------------------------
55      !
56      IF( lk_offline ) THEN
57         IF( kt == nittrc000 ) THEN
58            lrst_trc = .FALSE.
59            IF( ln_rst_list ) THEN
60               nrst_lst = 1
61               nitrst = nstocklist( nrst_lst )
62            ELSE
63               nitrst = nitend
64            ENDIF
65         ENDIF
66
67         IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nstock ) == 0 ) THEN
68            ! we use kt - 1 and not kt - nittrc000 to keep the same periodicity from the beginning of the experiment
69            nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing
70            IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run
71         ENDIF
72      ELSE
73         IF( kt == nittrc000 ) lrst_trc = .FALSE.
74      ENDIF
75
76      ! to get better performances with NetCDF format:
77      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1)
78      ! 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
79      IF( kt == nitrst - 2*nn_dttrc .OR. nstock == nn_dttrc .OR. ( kt == nitend - nn_dttrc .AND. .NOT. lrst_trc ) ) THEN
80         ! beware of the format used to write kt (default is i8.8, that should be large enough)
81         IF( nitrst > 1.0e9 ) THEN   ;   WRITE(clkt,*       ) nitrst
82         ELSE                        ;   WRITE(clkt,'(i8.8)') nitrst
83         ENDIF
84         ! create the file
85         IF(lwp) WRITE(numout,*)
86         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_trcrst_out)
87         clpath = TRIM(cn_trcrst_outdir)
88         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
89         IF(lwp) WRITE(numout,*) &
90             '             open trc restart.output NetCDF file: ',TRIM(clpath)//clname
91         CALL iom_open( TRIM(clpath)//TRIM(clname), numrtw, ldwrt = .TRUE., kiolib = jprstlib )
92         lrst_trc = .TRUE.
93      ENDIF
94      !
95   END SUBROUTINE trc_rst_opn
96
97   SUBROUTINE trc_rst_read
98      !!----------------------------------------------------------------------
99      !!                    ***  trc_rst_opn  ***
100      !!
101      !! ** purpose  :   read passive tracer fields in restart files
102      !!----------------------------------------------------------------------
103      INTEGER  ::  jn     
104
105      !!----------------------------------------------------------------------
106      !
107      IF(lwp) WRITE(numout,*)
108      IF(lwp) WRITE(numout,*) 'trc_rst_read : read data in the TOP restart file'
109      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
110
111      ! READ prognostic variables and computes diagnostic variable
112      DO jn = 1, jptra
113         CALL iom_get( numrtr, jpdom_autoglo, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
114      END DO
115
116      DO jn = 1, jptra
117         CALL iom_get( numrtr, jpdom_autoglo, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
118      END DO
119      !
120   END SUBROUTINE trc_rst_read
121
122   SUBROUTINE trc_rst_wri( kt )
123      !!----------------------------------------------------------------------
124      !!                    ***  trc_rst_wri  ***
125      !!
126      !! ** purpose  :   write passive tracer fields in restart files
127      !!----------------------------------------------------------------------
128      INTEGER, INTENT( in ) ::   kt    ! ocean time-step index
129      !!
130      INTEGER  :: jn
131      REAL(wp) :: zarak0
132      !!----------------------------------------------------------------------
133      !
134      CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rdttrc(1) )   ! surface passive tracer time step
135      ! prognostic variables
136      ! --------------------
137      DO jn = 1, jptra
138         CALL iom_rstput( kt, nitrst, numrtw, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
139      END DO
140
141      DO jn = 1, jptra
142         CALL iom_rstput( kt, nitrst, numrtw, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
143      END DO
144      !
145      IF( kt == nitrst ) THEN
146          CALL trc_rst_stat            ! statistics
147          CALL iom_close( numrtw )     ! close the restart file (only at last time step)
148#if ! defined key_trdmxl_trc
149          lrst_trc = .FALSE.
150#endif
151          IF( lk_offline .AND. ln_rst_list ) THEN
152             nrst_lst = nrst_lst + 1
153             nitrst = nstocklist( nrst_lst )
154          ENDIF
155      ENDIF
156      !
157   END SUBROUTINE trc_rst_wri 
158
159
160   SUBROUTINE trc_rst_cal( kt, cdrw )
161      !!---------------------------------------------------------------------
162      !!                   ***  ROUTINE trc_rst_cal  ***
163      !!
164      !!  ** Purpose : Read or write calendar in restart file:
165      !!
166      !!  WRITE(READ) mode:
167      !!       kt        : number of time step since the begining of the experiment at the
168      !!                   end of the current(previous) run
169      !!       adatrj(0) : number of elapsed days since the begining of the experiment at the
170      !!                   end of the current(previous) run (REAL -> keep fractions of day)
171      !!       ndastp    : date at the end of the current(previous) run (coded as yyyymmdd integer)
172      !!
173      !!   According to namelist parameter nrstdt,
174      !!       nn_rsttr = 0  no control on the date (nittrc000 is  arbitrary).
175      !!       nn_rsttr = 1  we verify that nittrc000 is equal to the last
176      !!                   time step of previous run + 1.
177      !!       In both those options, the  exact duration of the experiment
178      !!       since the beginning (cumulated duration of all previous restart runs)
179      !!       is not stored in the restart and is assumed to be (nittrc000-1)*rdt.
180      !!       This is valid is the time step has remained constant.
181      !!
182      !!       nn_rsttr = 2  the duration of the experiment in days (adatrj)
183      !!                    has been stored in the restart file.
184      !!----------------------------------------------------------------------
185      INTEGER         , INTENT(in) ::   kt         ! ocean time-step
186      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag
187      !
188      INTEGER  ::  jlibalt = jprstlib
189      LOGICAL  ::  llok
190      REAL(wp) ::  zkt, zrdttrc1
191      REAL(wp) ::  zndastp
192
193      ! Time domain : restart
194      ! ---------------------
195
196      IF( TRIM(cdrw) == 'READ' ) THEN
197
198         IF(lwp) WRITE(numout,*)
199         IF(lwp) WRITE(numout,*) 'trc_rst_cal : read the TOP restart file for calendar'
200         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
201
202         IF ( jprstlib == jprstdimg ) THEN
203           ! eventually read netcdf file (monobloc)  for restarting on different number of processors
204           ! if {cn_trcrst_in}.nc exists, then set jlibalt to jpnf90
205           INQUIRE( FILE = TRIM(cn_trcrst_indir)//'/'//TRIM(cn_trcrst_in)//'.nc', EXIST = llok )
206           IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF
207         ENDIF
208
209         CALL iom_open( TRIM(cn_trcrst_indir)//'/'//cn_trcrst_in, numrtr, kiolib = jlibalt )
210
211         CALL iom_get ( numrtr, 'kt', zkt )   ! last time-step of previous run
212
213         IF(lwp) THEN
214            WRITE(numout,*) ' *** Info read in restart : '
215            WRITE(numout,*) '   previous time-step                               : ', NINT( zkt )
216            WRITE(numout,*) ' *** restart option'
217            SELECT CASE ( nn_rsttr )
218            CASE ( 0 )   ;   WRITE(numout,*) ' nn_rsttr = 0 : no control of nittrc000'
219            CASE ( 1 )   ;   WRITE(numout,*) ' nn_rsttr = 1 : no control the date at nittrc000 (use ndate0 read in the namelist)'
220            CASE ( 2 )   ;   WRITE(numout,*) ' nn_rsttr = 2 : calendar parameters read in restart'
221            END SELECT
222            WRITE(numout,*)
223         ENDIF
224         ! Control of date
225         IF( nittrc000  - NINT( zkt ) /= nn_dttrc .AND.  nn_rsttr /= 0 )                                  &
226            &   CALL ctl_stop( ' ===>>>> : problem with nittrc000 for the restart',                 &
227            &                  ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' )
228         IF( lk_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             ELSE
235               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam
236               adatrj = ( REAL( nittrc000-1, wp ) * rdttra(1) ) / rday
237               ! note this is wrong if time step has changed during run
238            ENDIF
239            !
240            IF(lwp) THEN
241              WRITE(numout,*) ' *** Info used values : '
242              WRITE(numout,*) '   date ndastp                                      : ', ndastp
243              WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj
244              WRITE(numout,*)
245            ENDIF
246            !
247            IF( ln_rsttr )  THEN   ;    neuler = 1
248            ELSE                   ;    neuler = 0
249            ENDIF
250            !
251            CALL day_init          ! compute calendar
252            !
253         ENDIF
254         !
255      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
256         !
257         IF(  kt == nitrst ) THEN
258            IF(lwp) WRITE(numout,*)
259            IF(lwp) WRITE(numout,*) 'trc_wri : write the TOP restart file (NetCDF) at it= ', kt, ' date= ', ndastp
260            IF(lwp) WRITE(numout,*) '~~~~~~~'
261         ENDIF
262         CALL iom_rstput( kt, nitrst, numrtw, 'kt'     , REAL( kt    , wp) )   ! time-step
263         CALL iom_rstput( kt, nitrst, numrtw, 'ndastp' , REAL( ndastp, wp) )   ! date
264         CALL iom_rstput( kt, nitrst, numrtw, 'adatrj' , adatrj            )   ! number of elapsed days since
265         !                                                                     ! the begining of the run [s]
266      ENDIF
267
268   END SUBROUTINE trc_rst_cal
269
270
271   SUBROUTINE trc_rst_stat
272      !!----------------------------------------------------------------------
273      !!                    ***  trc_rst_stat  ***
274      !!
275      !! ** purpose  :   Compute tracers statistics
276      !!----------------------------------------------------------------------
277      INTEGER  :: jk, jn
278      REAL(wp) :: ztraf, zmin, zmax, zmean, zdrift
279      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zvol
280      !!----------------------------------------------------------------------
281
282      IF( lwp ) THEN
283         WRITE(numout,*) 
284         WRITE(numout,*) '           ----TRACER STAT----             '
285         WRITE(numout,*) 
286      ENDIF
287      !
288      DO jk = 1, jpk
289         zvol(:,:,jk) = e1e2t(:,:) * fse3t_a(:,:,jk) * tmask(:,:,jk)
290      END DO
291      !
292      DO jn = 1, jptra
293         ztraf = glob_sum( trn(:,:,:,jn) * zvol(:,:,:) )
294         zmin  = MINVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
295         zmax  = MAXVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
296         IF( lk_mpp ) THEN
297            CALL mpp_min( zmin )      ! min over the global domain
298            CALL mpp_max( zmax )      ! max over the global domain
299         END IF
300         zmean  = ztraf / areatot
301         zdrift = ( ( ztraf - trai(jn) ) / ( trai(jn) + 1.e-12 )  ) * 100._wp
302         IF(lwp) WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), zmean, zmin, zmax, zdrift
303      END DO
304      WRITE(numout,*) 
3059000  FORMAT(' tracer nb :',i2,'    name :',a10,'    mean :',e18.10,'    min :',e18.10, &
306      &      '    max :',e18.10,'    drift :',e18.10, ' %')
307      !
308   END SUBROUTINE trc_rst_stat
309
310#else
311   !!----------------------------------------------------------------------
312   !!  Dummy module :                                     No passive tracer
313   !!----------------------------------------------------------------------
314CONTAINS
315   SUBROUTINE trc_rst_read                      ! Empty routines
316   END SUBROUTINE trc_rst_read
317   SUBROUTINE trc_rst_wri( kt )
318      INTEGER, INTENT ( in ) :: kt
319      WRITE(*,*) 'trc_rst_wri: You should not have seen this print! error?', kt
320   END SUBROUTINE trc_rst_wri   
321#endif
322
323   !!----------------------------------------------------------------------
324   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
325   !! $Id$
326   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
327   !!======================================================================
328END MODULE trcrst
Note: See TracBrowser for help on using the repository browser.