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 3294 for trunk/NEMOGCM/NEMO/TOP_SRC/trcrst.F90 – NEMO

Ignore:
Timestamp:
2012-01-28T17:44:18+01:00 (12 years ago)
Author:
rblod
Message:

Merge of 3.4beta into the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/TOP_SRC/trcrst.F90

    r2715 r3294  
    3939   PUBLIC   trc_rst_read      ! called by ??? 
    4040   PUBLIC   trc_rst_wri       ! called by ??? 
     41   PUBLIC   trc_rst_cal 
    4142 
    4243   INTEGER, PUBLIC ::   numrtr, numrtw   !: logical unit for trc restart (read and write) 
     
    6061      ! 
    6162      IF( lk_offline ) THEN 
    62          IF( kt == nit000 ) THEN 
     63         IF( kt == nittrc000 ) THEN 
    6364            lrst_trc = .FALSE. 
    6465            nitrst = nitend 
     
    6667 
    6768         IF( MOD( kt - 1, nstock ) == 0 ) THEN 
    68             ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment 
     69            ! we use kt - 1 and not kt - nittrc000 to keep the same periodicity from the beginning of the experiment 
    6970            nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing 
    7071            IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run 
    7172         ENDIF 
    7273      ELSE 
    73          IF( kt == nit000 ) lrst_trc = .FALSE. 
     74         IF( kt == nittrc000 ) lrst_trc = .FALSE. 
    7475      ENDIF 
    7576 
     
    7778      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1) 
    7879      ! 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 + 1 .OR. nstock == nn_dttrc .OR. ( kt == nitend - nn_dttrc + 1 .AND. .NOT. lrst_trc ) ) THEN 
     80      IF( kt == nitrst - 2*nn_dttrc .OR. nstock == nn_dttrc .OR. ( kt == nitend - nn_dttrc .AND. .NOT. lrst_trc ) ) THEN 
    8081         ! beware of the format used to write kt (default is i8.8, that should be large enough) 
    8182         IF( nitrst > 1.0e9 ) THEN   ;   WRITE(clkt,*       ) nitrst 
     
    99100      !!---------------------------------------------------------------------- 
    100101      INTEGER  ::  jn      
    101       INTEGER  ::  jlibalt = jprstlib 
    102       LOGICAL  ::  llok 
    103  
    104       !!---------------------------------------------------------------------- 
    105  
     102 
     103      !!---------------------------------------------------------------------- 
     104      ! 
    106105      IF(lwp) WRITE(numout,*) 
    107       IF(lwp) WRITE(numout,*) 'trc_rst_read : read the TOP restart file' 
     106      IF(lwp) WRITE(numout,*) 'trc_rst_read : read data in the TOP restart file' 
    108107      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( nit000, 'READ' )   ! calendar 
    122108 
    123109      ! READ prognostic variables and computes diagnostic variable 
     
    151137      REAL(wp) :: zarak0 
    152138      !!---------------------------------------------------------------------- 
    153  
    154  
     139      ! 
    155140      CALL trc_rst_cal( kt, 'WRITE' )   ! calendar 
    156141      CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rdttrc(1) )   ! surface passive tracer time step 
     
    196181      !! 
    197182      !!   According to namelist parameter nrstdt, 
    198       !!       nn_rsttr = 0  no control on the date (nit000 is  arbitrary). 
    199       !!       nn_rsttr = 1  we verify that nit000 is equal to the last 
     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 
    200185      !!                   time step of previous run + 1. 
    201186      !!       In both those options, the  exact duration of the experiment 
    202187      !!       since the beginning (cumulated duration of all previous restart runs) 
    203       !!       is not stored in the restart and is assumed to be (nit000-1)*rdt. 
     188      !!       is not stored in the restart and is assumed to be (nittrc000-1)*rdt. 
    204189      !!       This is valid is the time step has remained constant. 
    205190      !! 
     
    210195      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag 
    211196      ! 
     197      INTEGER  ::  jlibalt = jprstlib 
     198      LOGICAL  ::  llok 
    212199      REAL(wp) ::  zkt, zrdttrc1 
    213200      REAL(wp) ::  zndastp 
     
    217204 
    218205      IF( TRIM(cdrw) == 'READ' ) THEN 
     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 
    219220         CALL iom_get ( numrtr, 'kt', zkt )   ! last time-step of previous run 
    220221         IF(lwp) THEN 
     
    223224            WRITE(numout,*) ' *** restart option' 
    224225            SELECT CASE ( nn_rsttr ) 
    225             CASE ( 0 )   ;   WRITE(numout,*) ' nn_rsttr = 0 : no control of nit000' 
    226             CASE ( 1 )   ;   WRITE(numout,*) ' nn_rsttr = 1 : no control the date at nit000 (use ndate0 read in the namelist)' 
     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)' 
    227228            CASE ( 2 )   ;   WRITE(numout,*) ' nn_rsttr = 2 : calendar parameters read in restart' 
    228229            END SELECT 
     
    230231         ENDIF 
    231232         ! Control of date  
    232          IF( nit000  - NINT( zkt ) /= 1 .AND.  nn_rsttr /= 0 )                                  & 
    233             &   CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart',                 & 
     233         IF( nittrc000  - NINT( zkt ) /= nn_dttrc .AND.  nn_rsttr /= 0 )                                  & 
     234            &   CALL ctl_stop( ' ===>>>> : problem with nittrc000 for the restart',                 & 
    234235            &                  ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' ) 
    235236         IF( lk_offline ) THEN      ! set the date in offline mode 
     
    246247            ELSE 
    247248               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam 
    248                adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
     249               adatrj = ( REAL( nittrc000-1, wp ) * rdttra(1) ) / rday 
    249250               ! note this is wrong if time step has changed during run 
    250251            ENDIF 
     
    283284      !! ** purpose  :   Compute tracers statistics 
    284285      !!---------------------------------------------------------------------- 
    285  
    286       INTEGER  :: jn 
    287       REAL(wp) :: zdiag_var, zdiag_varmin, zdiag_varmax, zdiag_tot 
    288       REAL(wp) :: zder 
    289       !!---------------------------------------------------------------------- 
    290  
     286      INTEGER  :: jk, jn 
     287      REAL(wp) :: ztraf, zmin, zmax, zmean, zdrift 
     288      !!---------------------------------------------------------------------- 
    291289 
    292290      IF( lwp ) THEN 
     
    295293         WRITE(numout,*)  
    296294      ENDIF 
    297        
    298       zdiag_tot = 0.e0 
    299       DO jn = 1, jptra 
    300 #  if defined key_degrad 
    301          zdiag_var = glob_sum( trn(:,:,:,jn) * cvol(:,:,:) * facvol(:,:,:) ) 
    302 #  else 
    303          zdiag_var = glob_sum( trn(:,:,:,jn) * cvol(:,:,:)  ) 
    304 #  endif 
    305          zdiag_varmin = MINVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) ) 
    306          zdiag_varmax = MAXVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) ) 
     295      ! 
     296      DO jn = 1, jptra 
     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.)) ) 
    307300         IF( lk_mpp ) THEN 
    308             CALL mpp_min( zdiag_varmin )      ! min over the global domain 
    309             CALL mpp_max( zdiag_varmax )      ! max over the global domain 
     301            CALL mpp_min( zmin )      ! min over the global domain 
     302            CALL mpp_max( zmax )      ! max over the global domain 
    310303         END IF 
    311          zdiag_tot = zdiag_tot + zdiag_var 
    312          zdiag_var = zdiag_var / areatot 
    313          IF(lwp) WRITE(numout,*) '   MEAN NO ', jn, ctrcnm(jn), ' = ', zdiag_var,   & 
    314             &                    ' MIN = ', zdiag_varmin, ' MAX = ', zdiag_varmax 
    315       END DO 
    316        
    317       zder = ( ( zdiag_tot - trai ) / ( trai + 1.e-12 )  ) * 100._wp 
    318       IF(lwp) WRITE(numout,*) '   Integral of all tracers over the full domain  = ', zdiag_tot 
    319       IF(lwp) WRITE(numout,*) '   Drift of the sum of all tracers =', zder, ' %' 
    320        
     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 
     307      END DO 
     308      WRITE(numout,*)  
     3099000  FORMAT(' tracer nb :',i2,'    name :',a10,'    mean :',e18.10,'    min :',e18.10, & 
     310      &      '    max :',e18.10,'    drift :',e18.10, ' %') 
     311      ! 
    321312   END SUBROUTINE trc_rst_stat 
    322313 
Note: See TracChangeset for help on using the changeset viewer.