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.
Changeset 6225 for branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/TOP_SRC/trcrst.F90 – NEMO

Ignore:
Timestamp:
2016-01-08T10:35:19+01:00 (8 years ago)
Author:
jamesharle
Message:

Update MPP_BDY_UPDATE branch to be consistent with head of trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/TOP_SRC/trcrst.F90

    r4152 r6225  
    1414   !!---------------------------------------------------------------------- 
    1515   !!---------------------------------------------------------------------- 
    16    !!   trc_rst :   Restart for passive tracer 
    17    !!---------------------------------------------------------------------- 
    18    !!---------------------------------------------------------------------- 
    19    !!   'key_top'                                                TOP models 
    20    !!---------------------------------------------------------------------- 
     16   !!   trc_rst        : Restart for passive tracer 
    2117   !!   trc_rst_opn    : open  restart file 
    2218   !!   trc_rst_read   : read  restart file 
     
    2521   USE oce_trc 
    2622   USE trc 
    27    USE trcnam_trp 
    2823   USE iom 
    2924   USE daymod 
     25    
    3026   IMPLICIT NONE 
    3127   PRIVATE 
     
    3632   PUBLIC   trc_rst_cal 
    3733 
    38    !! * Substitutions 
    39 #  include "top_substitute.h90" 
    40     
     34   !!---------------------------------------------------------------------- 
     35   !! NEMO/TOP 3.7 , NEMO Consortium (2010) 
     36   !! $Id$ 
     37   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     38   !!---------------------------------------------------------------------- 
    4139CONTAINS 
    4240    
     
    5149      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step define as a character 
    5250      CHARACTER(LEN=50)   ::   clname   ! trc output restart file name 
     51      CHARACTER(LEN=256)  ::   clpath   ! full path to ocean output restart file 
    5352      !!---------------------------------------------------------------------- 
    5453      ! 
     
    5655         IF( kt == nittrc000 ) THEN 
    5756            lrst_trc = .FALSE. 
    58             nitrst = nitend 
    59          ENDIF 
    60  
    61          IF( MOD( kt - 1, nstock ) == 0 ) THEN 
     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 
    6266            ! we use kt - 1 and not kt - nittrc000 to keep the same periodicity from the beginning of the experiment 
    6367            nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing 
     
    7983         IF(lwp) WRITE(numout,*) 
    8084         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 ) 
     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 ) 
    8390         lrst_trc = .TRUE. 
    8491      ENDIF 
     
    123130      !!---------------------------------------------------------------------- 
    124131      ! 
    125       CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rdttrc(1) )   ! surface passive tracer time step 
     132      CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rdttrc )   ! passive tracer time step 
    126133      ! prognostic variables  
    127134      ! --------------------  
     
    137144          CALL trc_rst_stat            ! statistics 
    138145          CALL iom_close( numrtw )     ! close the restart file (only at last time step) 
    139 #if ! defined key_trdmld_trc 
     146#if ! defined key_trdmxl_trc 
    140147          lrst_trc = .FALSE. 
    141148#endif 
     149          IF( lk_offline .AND. ln_rst_list ) THEN 
     150             nrst_lst = nrst_lst + 1 
     151             nitrst = nstocklist( nrst_lst ) 
     152          ENDIF 
    142153      ENDIF 
    143154      ! 
     
    187198         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~' 
    188199 
    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  
    200          IF(lwp) THEN 
    201             WRITE(numout,*) ' *** Info read in restart : ' 
    202             WRITE(numout,*) '   previous time-step                               : ', NINT( zkt ) 
    203             WRITE(numout,*) ' *** restart option' 
    204             SELECT CASE ( nn_rsttr ) 
    205             CASE ( 0 )   ;   WRITE(numout,*) ' nn_rsttr = 0 : no control of nittrc000' 
    206             CASE ( 1 )   ;   WRITE(numout,*) ' nn_rsttr = 1 : no control the date at nittrc000 (use ndate0 read in the namelist)' 
    207             CASE ( 2 )   ;   WRITE(numout,*) ' nn_rsttr = 2 : calendar parameters read in restart' 
    208             END SELECT 
    209             WRITE(numout,*) 
    210          ENDIF 
    211          ! Control of date  
    212          IF( nittrc000  - NINT( zkt ) /= nn_dttrc .AND.  nn_rsttr /= 0 )                                  & 
    213             &   CALL ctl_stop( ' ===>>>> : problem with nittrc000 for the restart',                 & 
    214             &                  ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' ) 
    215          IF( lk_offline ) THEN      ! set the date in offline mode 
    216             ! Check dynamics and tracer time-step consistency and force Euler restart if changed 
    217             IF( iom_varid( numrtr, 'rdttrc1', ldstop = .FALSE. ) > 0 )   THEN 
    218                CALL iom_get( numrtr, 'rdttrc1', zrdttrc1 ) 
    219                IF( zrdttrc1 /= rdt * nn_dttrc )   neuler = 0 
    220             ENDIF 
    221             !                          ! define ndastp and adatrj 
    222             IF( nn_rsttr == 2 ) THEN 
     200         IF( ln_rsttr ) THEN 
     201            CALL iom_open( TRIM(cn_trcrst_indir)//'/'//cn_trcrst_in, numrtr, kiolib = jlibalt ) 
     202            CALL iom_get ( numrtr, 'kt', zkt )   ! last time-step of previous run 
     203 
     204            IF(lwp) THEN 
     205               WRITE(numout,*) ' *** Info read in restart : ' 
     206               WRITE(numout,*) '   previous time-step                               : ', NINT( zkt ) 
     207               WRITE(numout,*) ' *** restart option' 
     208               SELECT CASE ( nn_rsttr ) 
     209               CASE ( 0 )   ;   WRITE(numout,*) ' nn_rsttr = 0 : no control of nittrc000' 
     210               CASE ( 1 )   ;   WRITE(numout,*) ' nn_rsttr = 1 : no control the date at nittrc000 (use ndate0 read in the namelist)' 
     211               CASE ( 2 )   ;   WRITE(numout,*) ' nn_rsttr = 2 : calendar parameters read in restart' 
     212               END SELECT 
     213               WRITE(numout,*) 
     214            ENDIF 
     215            ! Control of date  
     216            IF( nittrc000  - NINT( zkt ) /= nn_dttrc .AND.  nn_rsttr /= 0 )                                  & 
     217               &   CALL ctl_stop( ' ===>>>> : problem with nittrc000 for the restart',                 & 
     218               &                  ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' ) 
     219         ENDIF 
     220         ! 
     221         IF( lk_offline ) THEN     
     222            !                                          ! set the date in offline mode 
     223            IF( ln_rsttr .AND. nn_rsttr == 2 ) THEN 
    223224               CALL iom_get( numrtr, 'ndastp', zndastp )  
    224225               ndastp = NINT( zndastp ) 
    225226               CALL iom_get( numrtr, 'adatrj', adatrj  ) 
    226             ELSE 
     227             ELSE 
    227228               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam 
    228                adatrj = ( REAL( nittrc000-1, wp ) * rdttra(1) ) / rday 
     229               adatrj = ( REAL( nittrc000-1, wp ) * rdt ) / rday 
    229230               ! note this is wrong if time step has changed during run 
    230231            ENDIF 
     
    235236              WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
    236237              WRITE(numout,*) 
     238            ENDIF 
     239            ! 
     240            IF( ln_rsttr )  THEN   ;    neuler = 1 
     241            ELSE                   ;    neuler = 0 
    237242            ENDIF 
    238243            ! 
     
    265270      INTEGER  :: jk, jn 
    266271      REAL(wp) :: ztraf, zmin, zmax, zmean, zdrift 
     272      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zvol 
    267273      !!---------------------------------------------------------------------- 
    268274 
     
    273279      ENDIF 
    274280      ! 
    275       DO jn = 1, jptra 
    276          ztraf = glob_sum( trn(:,:,:,jn) * cvol(:,:,:) ) 
     281      DO jk = 1, jpk 
     282         zvol(:,:,jk) = e1e2t(:,:) * e3t_a(:,:,jk) * tmask(:,:,jk) 
     283      END DO 
     284      ! 
     285      DO jn = 1, jptra 
     286         ztraf = glob_sum( trn(:,:,:,jn) * zvol(:,:,:) ) 
    277287         zmin  = MINVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) ) 
    278288         zmax  = MAXVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) ) 
     
    306316   !!---------------------------------------------------------------------- 
    307317   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    308    !! $Id$  
     318   !! $Id$ 
    309319   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    310320   !!====================================================================== 
Note: See TracChangeset for help on using the changeset viewer.