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

source: branches/2011/dev_NEMO_MERGE_2011/NEMOGCM/NEMO/TOP_SRC/trcrst.F90 @ 3124

Last change on this file since 3124 was 3124, checked in by cetlod, 12 years ago

dev_NEMO_MERGE_2011/NEMOGCM:minor modifications on the use of nittrc000 + style corrections

  • Property svn:keywords set to Id
File size: 15.1 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 trcrst_cfc      ! CFC     
30   USE trcrst_lobster  ! LOBSTER  restart
31   USE trcrst_pisces   ! PISCES   restart
32   USE trcrst_c14b     ! C14 bomb restart
33   USE trcrst_my_trc   ! MY_TRC   restart
34   USE daymod
35   IMPLICIT NONE
36   PRIVATE
37
38   PUBLIC   trc_rst_opn       ! called by ???
39   PUBLIC   trc_rst_read      ! called by ???
40   PUBLIC   trc_rst_wri       ! called by ???
41
42   INTEGER, PUBLIC ::   numrtr, numrtw   !: logical unit for trc restart (read and write)
43
44   !! * Substitutions
45#  include "top_substitute.h90"
46   
47CONTAINS
48   
49   SUBROUTINE trc_rst_opn( kt )
50      !!----------------------------------------------------------------------
51      !!                    ***  trc_rst_opn  ***
52      !!
53      !! ** purpose  :   output of sea-trc variable in a netcdf file
54      !!----------------------------------------------------------------------
55      INTEGER, INTENT(in) ::   kt       ! number of iteration
56      !
57      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step define as a character
58      CHARACTER(LEN=50)   ::   clname   ! trc output restart file name
59      !!----------------------------------------------------------------------
60      !
61      IF( lk_offline ) THEN
62         IF( kt == nittrc000 ) THEN
63            lrst_trc = .FALSE.
64            nitrst = nitend
65         ENDIF
66
67         IF( 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         IF(lwp) WRITE(numout,*) '             open trc restart.output NetCDF file: '//clname
88         CALL iom_open( clname, numrtw, ldwrt = .TRUE., kiolib = jprstlib )
89         lrst_trc = .TRUE.
90      ENDIF
91      !
92   END SUBROUTINE trc_rst_opn
93
94   SUBROUTINE trc_rst_read
95      !!----------------------------------------------------------------------
96      !!                    ***  trc_rst_opn  ***
97      !!
98      !! ** purpose  :   read passive tracer fields in restart files
99      !!----------------------------------------------------------------------
100      INTEGER  ::  jn     
101      INTEGER  ::  jlibalt = jprstlib
102      LOGICAL  ::  llok
103
104      !!----------------------------------------------------------------------
105
106      IF(lwp) WRITE(numout,*)
107      IF(lwp) WRITE(numout,*) 'trc_rst_read : read the TOP restart file'
108      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
109
110      IF ( jprstlib == jprstdimg ) THEN
111        ! eventually read netcdf file (monobloc)  for restarting on different number of processors
112        ! if {cn_trcrst_in}.nc exists, then set jlibalt to jpnf90
113        INQUIRE( FILE = TRIM(cn_trcrst_in)//'.nc', EXIST = llok )
114        IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF
115      ENDIF
116
117      CALL iom_open( cn_trcrst_in, numrtr, kiolib = jlibalt ) 
118
119      ! Time domain : restart
120      ! ---------------------
121      CALL trc_rst_cal( nittrc000, 'READ' )   ! calendar
122
123      ! READ prognostic variables and computes diagnostic variable
124      DO jn = 1, jptra
125         CALL iom_get( numrtr, jpdom_autoglo, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
126      END DO
127
128      DO jn = 1, jptra
129         CALL iom_get( numrtr, jpdom_autoglo, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
130      END DO
131
132      IF( lk_lobster )   CALL trc_rst_read_lobster( numrtr )      ! LOBSTER bio-model
133      IF( lk_pisces  )   CALL trc_rst_read_pisces ( numrtr )      ! PISCES  bio-model
134      IF( lk_cfc     )   CALL trc_rst_read_cfc    ( numrtr )      ! CFC     tracers
135      IF( lk_c14b    )   CALL trc_rst_read_c14b   ( numrtr )      ! C14 bomb  tracer
136      IF( lk_my_trc  )   CALL trc_rst_read_my_trc ( numrtr )      ! MY_TRC  tracers
137
138      CALL iom_close( numrtr )
139      !
140   END SUBROUTINE trc_rst_read
141
142   SUBROUTINE trc_rst_wri( kt )
143      !!----------------------------------------------------------------------
144      !!                    ***  trc_rst_wri  ***
145      !!
146      !! ** purpose  :   write passive tracer fields in restart files
147      !!----------------------------------------------------------------------
148      INTEGER, INTENT( in ) ::   kt    ! ocean time-step index
149      !!
150      INTEGER  :: jn
151      REAL(wp) :: zarak0
152      !!----------------------------------------------------------------------
153
154      CALL trc_rst_cal( kt, 'WRITE' )   ! calendar
155      CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rdttrc(1) )   ! surface passive tracer time step
156      ! prognostic variables
157      ! --------------------
158      DO jn = 1, jptra
159         CALL iom_rstput( kt, nitrst, numrtw, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
160      END DO
161
162      DO jn = 1, jptra
163         CALL iom_rstput( kt, nitrst, numrtw, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
164      END DO
165
166      IF( lk_lobster )   CALL trc_rst_wri_lobster( kt, nitrst, numrtw )      ! LOBSTER bio-model
167      IF( lk_pisces  )   CALL trc_rst_wri_pisces ( kt, nitrst, numrtw )      ! PISCES  bio-model
168      IF( lk_cfc     )   CALL trc_rst_wri_cfc    ( kt, nitrst, numrtw )      ! CFC     tracers
169      IF( lk_c14b    )   CALL trc_rst_wri_c14b   ( kt, nitrst, numrtw )      ! C14 bomb  tracer
170      IF( lk_my_trc  )   CALL trc_rst_wri_my_trc ( kt, nitrst, numrtw )      ! MY_TRC  tracers
171
172      IF( kt == nitrst ) THEN
173          CALL trc_rst_stat            ! statistics
174          CALL iom_close( numrtw )     ! close the restart file (only at last time step)
175#if ! defined key_trdmld_trc
176          lrst_trc = .FALSE.
177#endif
178      ENDIF
179      !
180   END SUBROUTINE trc_rst_wri 
181
182
183   SUBROUTINE trc_rst_cal( kt, cdrw )
184      !!---------------------------------------------------------------------
185      !!                   ***  ROUTINE trc_rst_cal  ***
186      !!
187      !!  ** Purpose : Read or write calendar in restart file:
188      !!
189      !!  WRITE(READ) mode:
190      !!       kt        : number of time step since the begining of the experiment at the
191      !!                   end of the current(previous) run
192      !!       adatrj(0) : number of elapsed days since the begining of the experiment at the
193      !!                   end of the current(previous) run (REAL -> keep fractions of day)
194      !!       ndastp    : date at the end of the current(previous) run (coded as yyyymmdd integer)
195      !!
196      !!   According to namelist parameter nrstdt,
197      !!       nn_rsttr = 0  no control on the date (nittrc000 is  arbitrary).
198      !!       nn_rsttr = 1  we verify that nittrc000 is equal to the last
199      !!                   time step of previous run + 1.
200      !!       In both those options, the  exact duration of the experiment
201      !!       since the beginning (cumulated duration of all previous restart runs)
202      !!       is not stored in the restart and is assumed to be (nittrc000-1)*rdt.
203      !!       This is valid is the time step has remained constant.
204      !!
205      !!       nn_rsttr = 2  the duration of the experiment in days (adatrj)
206      !!                    has been stored in the restart file.
207      !!----------------------------------------------------------------------
208      INTEGER         , INTENT(in) ::   kt         ! ocean time-step
209      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag
210      !
211      REAL(wp) ::  zkt, zrdttrc1
212      REAL(wp) ::  zndastp
213
214      ! Time domain : restart
215      ! ---------------------
216
217      IF( TRIM(cdrw) == 'READ' ) THEN
218         CALL iom_get ( numrtr, 'kt', zkt )   ! last time-step of previous run
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         IF( lk_offline ) THEN      ! set the date in offline mode
235            ! Check dynamics and tracer time-step consistency and force Euler restart if changed
236            IF( iom_varid( numrtr, 'rdttrc1', ldstop = .FALSE. ) > 0 )   THEN
237               CALL iom_get( numrtr, 'rdttrc1', zrdttrc1 )
238               IF( zrdttrc1 /= rdttrc(1) )   neuler = 0
239            ENDIF
240            !                          ! define ndastp and adatrj
241            IF ( nn_rsttr == 2 ) THEN
242               CALL iom_get( numrtr, 'ndastp', zndastp ) 
243               ndastp = NINT( zndastp )
244               CALL iom_get( numrtr, 'adatrj', adatrj  )
245            ELSE
246               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam
247               adatrj = ( REAL( nittrc000-1, wp ) * rdttra(1) ) / rday
248               ! note this is wrong if time step has changed during run
249            ENDIF
250            !
251            IF(lwp) THEN
252              WRITE(numout,*) ' *** Info used values : '
253              WRITE(numout,*) '   date ndastp                                      : ', ndastp
254              WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj
255              WRITE(numout,*)
256            ENDIF
257            !
258            CALL day_init          ! compute calendar
259            !
260         ENDIF
261         !
262      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
263         !
264         IF(  kt == nitrst ) THEN
265            IF(lwp) WRITE(numout,*)
266            IF(lwp) WRITE(numout,*) 'trc_wri : write the TOP restart file (NetCDF) at it= ', kt, ' date= ', ndastp
267            IF(lwp) WRITE(numout,*) '~~~~~~~'
268         ENDIF
269         CALL iom_rstput( kt, nitrst, numrtw, 'kt'     , REAL( kt    , wp) )   ! time-step
270         CALL iom_rstput( kt, nitrst, numrtw, 'ndastp' , REAL( ndastp, wp) )   ! date
271         CALL iom_rstput( kt, nitrst, numrtw, 'adatrj' , adatrj            )   ! number of elapsed days since
272         !                                                                     ! the begining of the run [s]
273      ENDIF
274
275   END SUBROUTINE trc_rst_cal
276
277
278   SUBROUTINE trc_rst_stat
279      !!----------------------------------------------------------------------
280      !!                    ***  trc_rst_stat  ***
281      !!
282      !! ** purpose  :   Compute tracers statistics
283      !!----------------------------------------------------------------------
284      INTEGER  :: jk, jn
285      REAL(wp) :: ztraf, zmin, zmax, zmean, zdrift
286      !!----------------------------------------------------------------------
287
288      IF( lwp ) THEN
289         WRITE(numout,*) 
290         WRITE(numout,*) '           ----TRACER STAT----             '
291         WRITE(numout,*) 
292      ENDIF
293      !
294      DO jn = 1, jptra
295         ztraf = glob_sum( trn(:,:,:,jn) * cvol(:,:,:) )
296         zmin  = MINVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
297         zmax  = MAXVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
298         IF( lk_mpp ) THEN
299            CALL mpp_min( zmin )      ! min over the global domain
300            CALL mpp_max( zmax )      ! max over the global domain
301         END IF
302         zmean  = ztraf / areatot
303         zdrift = ( ( ztraf - trai(jn) ) / ( trai(jn) + 1.e-12 )  ) * 100._wp
304         IF(lwp) WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), zmean, zmin, zmax, zdrift
305      END DO
306      WRITE(numout,*) 
3079000  FORMAT(' tracer nb :',i2,'    name :',a10,'    mean :',e18.10,'    min :',e18.10, &
308      &      '    max :',e18.10,'    drift :',e18.10, ' %')
309      !
310   END SUBROUTINE trc_rst_stat
311
312#else
313   !!----------------------------------------------------------------------
314   !!  Dummy module :                                     No passive tracer
315   !!----------------------------------------------------------------------
316CONTAINS
317   SUBROUTINE trc_rst_read                      ! Empty routines
318   END SUBROUTINE trc_rst_read
319   SUBROUTINE trc_rst_wri( kt )
320      INTEGER, INTENT ( in ) :: kt
321      WRITE(*,*) 'trc_rst_wri: You should not have seen this print! error?', kt
322   END SUBROUTINE trc_rst_wri   
323#endif
324
325   !!----------------------------------------------------------------------
326   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
327   !! $Id$
328   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
329   !!======================================================================
330END MODULE trcrst
Note: See TracBrowser for help on using the repository browser.