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

source: branches/2012/dev_LOCEAN_2012/NEMOGCM/NEMO/TOP_SRC/trcrst.F90 @ 3584

Last change on this file since 3584 was 3584, checked in by cetlod, 11 years ago

Add in branch 2012/dev_LOCEAN_2012 changes from dev_r3438_LOCEAN15_PISLOB & dev_r3387_LOCEAN6_AGRIF_LIM, see ticket 1000

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