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

source: branches/UKMO/dev_r5107_mld_zint/NEMOGCM/NEMO/TOP_SRC/trcrst.F90 @ 5447

Last change on this file since 5447 was 5447, checked in by davestorkey, 9 years ago

Update UKMO/dev_r5107_mld_zint branch to revision 5442 of the trunk.

File size: 14.7 KB
RevLine 
[268]1MODULE trcrst
[335]2   !!======================================================================
[1801]3   !!                         ***  MODULE trcrst  ***
4   !! TOP :   Manage the passive tracer restart
[335]5   !!======================================================================
[1801]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
[274]10   !!----------------------------------------------------------------------
[945]11#if defined key_top
[335]12   !!----------------------------------------------------------------------
[945]13   !!   'key_top'                                                TOP models
14   !!----------------------------------------------------------------------
[1801]15   !!----------------------------------------------------------------------
16   !!   trc_rst :   Restart for passive tracer
17   !!----------------------------------------------------------------------
18   !!----------------------------------------------------------------------
19   !!   'key_top'                                                TOP models
20   !!----------------------------------------------------------------------
[945]21   !!   trc_rst_opn    : open  restart file
22   !!   trc_rst_read   : read  restart file
23   !!   trc_rst_wri    : write restart file
24   !!----------------------------------------------------------------------
[335]25   USE oce_trc
26   USE trc
[2528]27   USE trcnam_trp
[616]28   USE iom
[2528]29   USE daymod
[335]30   IMPLICIT NONE
31   PRIVATE
[1801]32
[945]33   PUBLIC   trc_rst_opn       ! called by ???
34   PUBLIC   trc_rst_read      ! called by ???
35   PUBLIC   trc_rst_wri       ! called by ???
[3294]36   PUBLIC   trc_rst_cal
[1801]37
[350]38   !! * Substitutions
[945]39#  include "top_substitute.h90"
[335]40   
[268]41CONTAINS
[335]42   
[616]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
[5447]53      CHARACTER(LEN=256)  ::   clpath   ! full path to ocean output restart file
[616]54      !!----------------------------------------------------------------------
55      !
[2528]56      IF( lk_offline ) THEN
[3294]57         IF( kt == nittrc000 ) THEN
[2528]58            lrst_trc = .FALSE.
[5447]59            IF( ln_rst_list ) THEN
60               nrst_lst = 1
61               nitrst = nstocklist( nrst_lst )
62            ELSE
63               nitrst = nitend
64            ENDIF
[2528]65         ENDIF
66
[5447]67         IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nstock ) == 0 ) THEN
[3294]68            ! we use kt - 1 and not kt - nittrc000 to keep the same periodicity from the beginning of the experiment
[2528]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
[3294]73         IF( kt == nittrc000 ) lrst_trc = .FALSE.
[1655]74      ENDIF
75
[2528]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
[3294]79      IF( kt == nitrst - 2*nn_dttrc .OR. nstock == nn_dttrc .OR. ( kt == nitend - nn_dttrc .AND. .NOT. lrst_trc ) ) THEN
[616]80         ! beware of the format used to write kt (default is i8.8, that should be large enough)
[945]81         IF( nitrst > 1.0e9 ) THEN   ;   WRITE(clkt,*       ) nitrst
82         ELSE                        ;   WRITE(clkt,'(i8.8)') nitrst
[616]83         ENDIF
84         ! create the file
85         IF(lwp) WRITE(numout,*)
[1254]86         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_trcrst_out)
[5447]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 )
[616]92         lrst_trc = .TRUE.
93      ENDIF
94      !
95   END SUBROUTINE trc_rst_opn
96
[1801]97   SUBROUTINE trc_rst_read
[945]98      !!----------------------------------------------------------------------
99      !!                    ***  trc_rst_opn  ***
[335]100      !!
[945]101      !! ** purpose  :   read passive tracer fields in restart files
102      !!----------------------------------------------------------------------
[1801]103      INTEGER  ::  jn     
[1287]104
[945]105      !!----------------------------------------------------------------------
[3294]106      !
[945]107      IF(lwp) WRITE(numout,*)
[3294]108      IF(lwp) WRITE(numout,*) 'trc_rst_read : read data in the TOP restart file'
[945]109      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
[350]110
[945]111      ! READ prognostic variables and computes diagnostic variable
[494]112      DO jn = 1, jptra
[1801]113         CALL iom_get( numrtr, jpdom_autoglo, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
[335]114      END DO
[1077]115
[1287]116      DO jn = 1, jptra
[1801]117         CALL iom_get( numrtr, jpdom_autoglo, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
[1077]118      END DO
[945]119      !
120   END SUBROUTINE trc_rst_read
[494]121
[945]122   SUBROUTINE trc_rst_wri( kt )
123      !!----------------------------------------------------------------------
124      !!                    ***  trc_rst_wri  ***
[335]125      !!
[945]126      !! ** purpose  :   write passive tracer fields in restart files
127      !!----------------------------------------------------------------------
128      INTEGER, INTENT( in ) ::   kt    ! ocean time-step index
[335]129      !!
[1287]130      INTEGER  :: jn
131      REAL(wp) :: zarak0
[945]132      !!----------------------------------------------------------------------
[3294]133      !
[2528]134      CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rdttrc(1) )   ! surface passive tracer time step
[1801]135      ! prognostic variables
136      ! --------------------
[1100]137      DO jn = 1, jptra
138         CALL iom_rstput( kt, nitrst, numrtw, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
139      END DO
[1077]140
[1100]141      DO jn = 1, jptra
142         CALL iom_rstput( kt, nitrst, numrtw, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
143      END DO
[3680]144      !
[1287]145      IF( kt == nitrst ) THEN
[1119]146          CALL trc_rst_stat            ! statistics
[1100]147          CALL iom_close( numrtw )     ! close the restart file (only at last time step)
[4990]148#if ! defined key_trdmxl_trc
[1100]149          lrst_trc = .FALSE.
[1177]150#endif
[5447]151          IF( lk_offline .AND. ln_rst_list ) THEN
152             nrst_lst = nrst_lst + 1
153             nitrst = nstocklist( nrst_lst )
154          ENDIF
[1287]155      ENDIF
[945]156      !
[1801]157   END SUBROUTINE trc_rst_wri 
[268]158
[1801]159
[1287]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,
[3294]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
[1287]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)
[3294]179      !!       is not stored in the restart and is assumed to be (nittrc000-1)*rdt.
[1287]180      !!       This is valid is the time step has remained constant.
181      !!
[2528]182      !!       nn_rsttr = 2  the duration of the experiment in days (adatrj)
[1287]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      !
[3294]188      INTEGER  ::  jlibalt = jprstlib
189      LOGICAL  ::  llok
[2528]190      REAL(wp) ::  zkt, zrdttrc1
[1287]191      REAL(wp) ::  zndastp
192
193      ! Time domain : restart
194      ! ---------------------
195
196      IF( TRIM(cdrw) == 'READ' ) THEN
[3294]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
[5447]205           INQUIRE( FILE = TRIM(cn_trcrst_indir)//'/'//TRIM(cn_trcrst_in)//'.nc', EXIST = llok )
[3294]206           IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF
207         ENDIF
208
[5447]209         CALL iom_open( TRIM(cn_trcrst_indir)//'/'//cn_trcrst_in, numrtr, kiolib = jlibalt )
[3294]210
[1287]211         CALL iom_get ( numrtr, 'kt', zkt )   ! last time-step of previous run
[4152]212
[1287]213         IF(lwp) THEN
214            WRITE(numout,*) ' *** Info read in restart : '
215            WRITE(numout,*) '   previous time-step                               : ', NINT( zkt )
216            WRITE(numout,*) ' *** restart option'
[2528]217            SELECT CASE ( nn_rsttr )
[3294]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)'
[2528]220            CASE ( 2 )   ;   WRITE(numout,*) ' nn_rsttr = 2 : calendar parameters read in restart'
[1287]221            END SELECT
222            WRITE(numout,*)
223         ENDIF
224         ! Control of date
[3294]225         IF( nittrc000  - NINT( zkt ) /= nn_dttrc .AND.  nn_rsttr /= 0 )                                  &
226            &   CALL ctl_stop( ' ===>>>> : problem with nittrc000 for the restart',                 &
[2528]227            &                  ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' )
228         IF( lk_offline ) THEN      ! set the date in offline mode
229            ! Check dynamics and tracer time-step consistency and force Euler restart if changed
230            IF( iom_varid( numrtr, 'rdttrc1', ldstop = .FALSE. ) > 0 )   THEN
231               CALL iom_get( numrtr, 'rdttrc1', zrdttrc1 )
[4152]232               IF( zrdttrc1 /= rdt * nn_dttrc )   neuler = 0
[2528]233            ENDIF
234            !                          ! define ndastp and adatrj
[4152]235            IF( nn_rsttr == 2 ) THEN
[2528]236               CALL iom_get( numrtr, 'ndastp', zndastp ) 
237               ndastp = NINT( zndastp )
238               CALL iom_get( numrtr, 'adatrj', adatrj  )
239            ELSE
240               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam
[3294]241               adatrj = ( REAL( nittrc000-1, wp ) * rdttra(1) ) / rday
[2528]242               ! note this is wrong if time step has changed during run
243            ENDIF
244            !
245            IF(lwp) THEN
246              WRITE(numout,*) ' *** Info used values : '
247              WRITE(numout,*) '   date ndastp                                      : ', ndastp
248              WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj
249              WRITE(numout,*)
250            ENDIF
251            !
252            CALL day_init          ! compute calendar
253            !
[1287]254         ENDIF
255         !
256      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
257         !
258         IF(  kt == nitrst ) THEN
259            IF(lwp) WRITE(numout,*)
260            IF(lwp) WRITE(numout,*) 'trc_wri : write the TOP restart file (NetCDF) at it= ', kt, ' date= ', ndastp
261            IF(lwp) WRITE(numout,*) '~~~~~~~'
262         ENDIF
263         CALL iom_rstput( kt, nitrst, numrtw, 'kt'     , REAL( kt    , wp) )   ! time-step
264         CALL iom_rstput( kt, nitrst, numrtw, 'ndastp' , REAL( ndastp, wp) )   ! date
265         CALL iom_rstput( kt, nitrst, numrtw, 'adatrj' , adatrj            )   ! number of elapsed days since
266         !                                                                     ! the begining of the run [s]
267      ENDIF
268
269   END SUBROUTINE trc_rst_cal
270
[1119]271
272   SUBROUTINE trc_rst_stat
273      !!----------------------------------------------------------------------
274      !!                    ***  trc_rst_stat  ***
275      !!
276      !! ** purpose  :   Compute tracers statistics
277      !!----------------------------------------------------------------------
[3294]278      INTEGER  :: jk, jn
279      REAL(wp) :: ztraf, zmin, zmax, zmean, zdrift
[5447]280      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zvol
[1119]281      !!----------------------------------------------------------------------
282
283      IF( lwp ) THEN
284         WRITE(numout,*) 
285         WRITE(numout,*) '           ----TRACER STAT----             '
286         WRITE(numout,*) 
287      ENDIF
[3294]288      !
[5447]289      DO jk = 1, jpk
290         zvol(:,:,jk) = e1e2t(:,:) * fse3t_a(:,:,jk) * tmask(:,:,jk)
291      END DO
292      !
[1119]293      DO jn = 1, jptra
[5447]294         ztraf = glob_sum( trn(:,:,:,jn) * zvol(:,:,:) )
[3294]295         zmin  = MINVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
296         zmax  = MAXVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
[1119]297         IF( lk_mpp ) THEN
[3294]298            CALL mpp_min( zmin )      ! min over the global domain
299            CALL mpp_max( zmax )      ! max over the global domain
[1119]300         END IF
[3294]301         zmean  = ztraf / areatot
302         zdrift = ( ( ztraf - trai(jn) ) / ( trai(jn) + 1.e-12 )  ) * 100._wp
303         IF(lwp) WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), zmean, zmin, zmax, zdrift
[1119]304      END DO
[3294]305      WRITE(numout,*) 
3069000  FORMAT(' tracer nb :',i2,'    name :',a10,'    mean :',e18.10,'    min :',e18.10, &
307      &      '    max :',e18.10,'    drift :',e18.10, ' %')
308      !
[1119]309   END SUBROUTINE trc_rst_stat
310
[268]311#else
[945]312   !!----------------------------------------------------------------------
313   !!  Dummy module :                                     No passive tracer
314   !!----------------------------------------------------------------------
[335]315CONTAINS
[945]316   SUBROUTINE trc_rst_read                      ! Empty routines
[616]317   END SUBROUTINE trc_rst_read
[945]318   SUBROUTINE trc_rst_wri( kt )
[335]319      INTEGER, INTENT ( in ) :: kt
[616]320      WRITE(*,*) 'trc_rst_wri: You should not have seen this print! error?', kt
[945]321   END SUBROUTINE trc_rst_wri   
[268]322#endif
[945]323
[2528]324   !!----------------------------------------------------------------------
325   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[5247]326   !! $Id$
[2528]327   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[945]328   !!======================================================================
[335]329END MODULE trcrst
Note: See TracBrowser for help on using the repository browser.