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 @ 3634

Last change on this file since 3634 was 3294, checked in by rblod, 12 years ago

Merge of 3.4beta into the trunk

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