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 branches/2015/dev_merge_2015/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/2015/dev_merge_2015/NEMOGCM/NEMO/TOP_SRC/trcrst.F90 @ 6076

Last change on this file since 6076 was 6060, checked in by timgraham, 9 years ago

Merged dev_r5836_noc2_VVL_BY_DEFAULT into branch

  • 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   !!   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   
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   trc_rst_opn       ! called by ???
30   PUBLIC   trc_rst_read      ! called by ???
31   PUBLIC   trc_rst_wri       ! called by ???
32   PUBLIC   trc_rst_cal
33
34   !!----------------------------------------------------------------------
35   !! NEMO/TOP 3.7 , NEMO Consortium (2010)
36   !! $Id$
37   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
38   !!----------------------------------------------------------------------
39CONTAINS
40   
41   SUBROUTINE trc_rst_opn( kt )
42      !!----------------------------------------------------------------------
43      !!                    ***  trc_rst_opn  ***
44      !!
45      !! ** purpose  :   output of sea-trc variable in a netcdf file
46      !!----------------------------------------------------------------------
47      INTEGER, INTENT(in) ::   kt       ! number of iteration
48      !
49      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step define as a character
50      CHARACTER(LEN=50)   ::   clname   ! trc output restart file name
51      CHARACTER(LEN=256)  ::   clpath   ! full path to ocean output restart file
52      !!----------------------------------------------------------------------
53      !
54      IF( lk_offline ) THEN
55         IF( kt == nittrc000 ) THEN
56            lrst_trc = .FALSE.
57            IF( ln_rst_list ) THEN
58               nrst_lst = 1
59               nitrst = nstocklist( nrst_lst )
60            ELSE
61               nitrst = nitend
62            ENDIF
63         ENDIF
64
65         IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nstock ) == 0 ) THEN
66            ! we use kt - 1 and not kt - nittrc000 to keep the same periodicity from the beginning of the experiment
67            nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing
68            IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run
69         ENDIF
70      ELSE
71         IF( kt == nittrc000 ) lrst_trc = .FALSE.
72      ENDIF
73
74      ! to get better performances with NetCDF format:
75      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1)
76      ! 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
77      IF( kt == nitrst - 2*nn_dttrc .OR. nstock == nn_dttrc .OR. ( kt == nitend - nn_dttrc .AND. .NOT. lrst_trc ) ) THEN
78         ! beware of the format used to write kt (default is i8.8, that should be large enough)
79         IF( nitrst > 1.0e9 ) THEN   ;   WRITE(clkt,*       ) nitrst
80         ELSE                        ;   WRITE(clkt,'(i8.8)') nitrst
81         ENDIF
82         ! create the file
83         IF(lwp) WRITE(numout,*)
84         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_trcrst_out)
85         clpath = TRIM(cn_trcrst_outdir)
86         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
87         IF(lwp) WRITE(numout,*) &
88             '             open trc restart.output NetCDF file: ',TRIM(clpath)//clname
89         CALL iom_open( TRIM(clpath)//TRIM(clname), numrtw, ldwrt = .TRUE., kiolib = jprstlib )
90         lrst_trc = .TRUE.
91      ENDIF
92      !
93   END SUBROUTINE trc_rst_opn
94
95   SUBROUTINE trc_rst_read
96      !!----------------------------------------------------------------------
97      !!                    ***  trc_rst_opn  ***
98      !!
99      !! ** purpose  :   read passive tracer fields in restart files
100      !!----------------------------------------------------------------------
101      INTEGER  ::  jn     
102
103      !!----------------------------------------------------------------------
104      !
105      IF(lwp) WRITE(numout,*)
106      IF(lwp) WRITE(numout,*) 'trc_rst_read : read data in the TOP restart file'
107      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
108
109      ! READ prognostic variables and computes diagnostic variable
110      DO jn = 1, jptra
111         CALL iom_get( numrtr, jpdom_autoglo, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
112      END DO
113
114      DO jn = 1, jptra
115         CALL iom_get( numrtr, jpdom_autoglo, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
116      END DO
117      !
118   END SUBROUTINE trc_rst_read
119
120   SUBROUTINE trc_rst_wri( kt )
121      !!----------------------------------------------------------------------
122      !!                    ***  trc_rst_wri  ***
123      !!
124      !! ** purpose  :   write passive tracer fields in restart files
125      !!----------------------------------------------------------------------
126      INTEGER, INTENT( in ) ::   kt    ! ocean time-step index
127      !!
128      INTEGER  :: jn
129      REAL(wp) :: zarak0
130      !!----------------------------------------------------------------------
131      !
132      CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rdttrc(1) )   ! surface passive tracer time step
133      ! prognostic variables
134      ! --------------------
135      DO jn = 1, jptra
136         CALL iom_rstput( kt, nitrst, numrtw, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
137      END DO
138
139      DO jn = 1, jptra
140         CALL iom_rstput( kt, nitrst, numrtw, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
141      END DO
142      !
143      IF( kt == nitrst ) THEN
144          CALL trc_rst_stat            ! statistics
145          CALL iom_close( numrtw )     ! close the restart file (only at last time step)
146#if ! defined key_trdmxl_trc
147          lrst_trc = .FALSE.
148#endif
149          IF( lk_offline .AND. ln_rst_list ) THEN
150             nrst_lst = nrst_lst + 1
151             nitrst = nstocklist( nrst_lst )
152          ENDIF
153      ENDIF
154      !
155   END SUBROUTINE trc_rst_wri 
156
157
158   SUBROUTINE trc_rst_cal( kt, cdrw )
159      !!---------------------------------------------------------------------
160      !!                   ***  ROUTINE trc_rst_cal  ***
161      !!
162      !!  ** Purpose : Read or write calendar in restart file:
163      !!
164      !!  WRITE(READ) mode:
165      !!       kt        : number of time step since the begining of the experiment at the
166      !!                   end of the current(previous) run
167      !!       adatrj(0) : number of elapsed days since the begining of the experiment at the
168      !!                   end of the current(previous) run (REAL -> keep fractions of day)
169      !!       ndastp    : date at the end of the current(previous) run (coded as yyyymmdd integer)
170      !!
171      !!   According to namelist parameter nrstdt,
172      !!       nn_rsttr = 0  no control on the date (nittrc000 is  arbitrary).
173      !!       nn_rsttr = 1  we verify that nittrc000 is equal to the last
174      !!                   time step of previous run + 1.
175      !!       In both those options, the  exact duration of the experiment
176      !!       since the beginning (cumulated duration of all previous restart runs)
177      !!       is not stored in the restart and is assumed to be (nittrc000-1)*rdt.
178      !!       This is valid is the time step has remained constant.
179      !!
180      !!       nn_rsttr = 2  the duration of the experiment in days (adatrj)
181      !!                    has been stored in the restart file.
182      !!----------------------------------------------------------------------
183      INTEGER         , INTENT(in) ::   kt         ! ocean time-step
184      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag
185      !
186      INTEGER  ::  jlibalt = jprstlib
187      LOGICAL  ::  llok
188      REAL(wp) ::  zkt, zrdttrc1
189      REAL(wp) ::  zndastp
190
191      ! Time domain : restart
192      ! ---------------------
193
194      IF( TRIM(cdrw) == 'READ' ) THEN
195
196         IF(lwp) WRITE(numout,*)
197         IF(lwp) WRITE(numout,*) 'trc_rst_cal : read the TOP restart file for calendar'
198         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
199
200         IF ( jprstlib == jprstdimg ) THEN
201           ! eventually read netcdf file (monobloc)  for restarting on different number of processors
202           ! if {cn_trcrst_in}.nc exists, then set jlibalt to jpnf90
203           INQUIRE( FILE = TRIM(cn_trcrst_indir)//'/'//TRIM(cn_trcrst_in)//'.nc', EXIST = llok )
204           IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF
205         ENDIF
206
207         IF( ln_rsttr ) THEN
208            CALL iom_open( TRIM(cn_trcrst_indir)//'/'//cn_trcrst_in, numrtr, kiolib = jlibalt )
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 ) /= nn_dttrc .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( 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(:,:) * e3t_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.