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 6827 for branches/2016/dev_r6409_SIMPLIF_2_usrdef_tools/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90 – NEMO

Ignore:
Timestamp:
2016-08-01T15:37:15+02:00 (8 years ago)
Author:
flavoni
Message:

#1692 - branch SIMPLIF_2_usrdef: commit routines Fortran to create domain_cfg.nc file, to have domain (input) files for new simplification branch. To be moved in TOOLS directory

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef_tools/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r6140 r6827  
    3333   USE ioipsl  , ONLY :   ymds2ju   ! for calendar 
    3434   USE prtctl         ! Print control 
    35    USE trc_oce , ONLY : lk_offline ! offline flag 
    3635   USE timing         ! Timing 
    37    USE restart        ! restart 
    3836 
    3937   IMPLICIT NONE 
     
    8886      ndt05   = NINT(0.5 * rdt  ) 
    8987 
    90       IF( .NOT. lk_offline ) CALL day_rst( nit000, 'READ' ) 
    9188 
    9289      ! set the calandar from ndastp (read in restart file and namelist) 
     
    281278      ENDIF 
    282279 
    283       IF( .NOT. lk_offline ) CALL rst_opn( kt )               ! Open the restart file if needed and control lrst_oce 
    284       IF( lrst_oce         ) CALL day_rst( kt, 'WRITE' )      ! write day restart information 
    285280      ! 
    286281      IF( nn_timing == 1 )  CALL timing_stop('day') 
     
    288283   END SUBROUTINE day 
    289284 
    290  
    291    SUBROUTINE day_rst( kt, cdrw ) 
    292       !!--------------------------------------------------------------------- 
    293       !!                   ***  ROUTINE ts_rst  *** 
    294       !! 
    295       !!  ** Purpose : Read or write calendar in restart file: 
    296       !! 
    297       !!  WRITE(READ) mode: 
    298       !!       kt        : number of time step since the begining of the experiment at the 
    299       !!                   end of the current(previous) run 
    300       !!       adatrj(0) : number of elapsed days since the begining of the experiment at the 
    301       !!                   end of the current(previous) run (REAL -> keep fractions of day) 
    302       !!       ndastp    : date at the end of the current(previous) run (coded as yyyymmdd integer) 
    303       !! 
    304       !!   According to namelist parameter nrstdt, 
    305       !!       nrstdt = 0  no control on the date (nit000 is  arbitrary). 
    306       !!       nrstdt = 1  we verify that nit000 is equal to the last 
    307       !!                   time step of previous run + 1. 
    308       !!       In both those options, the  exact duration of the experiment 
    309       !!       since the beginning (cumulated duration of all previous restart runs) 
    310       !!       is not stored in the restart and is assumed to be (nit000-1)*rdt. 
    311       !!       This is valid is the time step has remained constant. 
    312       !! 
    313       !!       nrstdt = 2  the duration of the experiment in days (adatrj) 
    314       !!                    has been stored in the restart file. 
    315       !!---------------------------------------------------------------------- 
    316       INTEGER         , INTENT(in) ::   kt         ! ocean time-step 
    317       CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag 
    318       ! 
    319       REAL(wp) ::   zkt, zndastp, zdayfrac, ksecs, ktime 
    320       INTEGER  ::   ihour, iminute 
    321       !!---------------------------------------------------------------------- 
    322  
    323       IF( TRIM(cdrw) == 'READ' ) THEN 
    324  
    325          IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN 
    326             ! Get Calendar informations 
    327             CALL iom_get( numror, 'kt', zkt )   ! last time-step of previous run 
    328             IF(lwp) THEN 
    329                WRITE(numout,*) ' *** Info read in restart : ' 
    330                WRITE(numout,*) '   previous time-step                               : ', NINT( zkt ) 
    331                WRITE(numout,*) ' *** restart option' 
    332                SELECT CASE ( nrstdt ) 
    333                CASE ( 0 )   ;   WRITE(numout,*) ' nrstdt = 0 : no control of nit000' 
    334                CASE ( 1 )   ;   WRITE(numout,*) ' nrstdt = 1 : no control the date at nit000 (use ndate0 read in the namelist)' 
    335                CASE ( 2 )   ;   WRITE(numout,*) ' nrstdt = 2 : calendar parameters read in restart' 
    336                END SELECT 
    337                WRITE(numout,*) 
    338             ENDIF 
    339             ! Control of date 
    340             IF( nit000 - NINT( zkt ) /= 1 .AND. nrstdt /= 0 )                                         & 
    341                  &   CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart',                 & 
    342                  &                  ' verify the restart file or rerun with nrstdt = 0 (namelist)' ) 
    343             ! define ndastp and adatrj 
    344             IF ( nrstdt == 2 ) THEN 
    345                ! read the parameters corresponding to nit000 - 1 (last time step of previous run) 
    346                CALL iom_get( numror, 'ndastp', zndastp ) 
    347                ndastp = NINT( zndastp ) 
    348                CALL iom_get( numror, 'adatrj', adatrj  ) 
    349           CALL iom_get( numror, 'ntime', ktime ) 
    350           nn_time0=INT(ktime) 
    351                ! calculate start time in hours and minutes 
    352           zdayfrac=adatrj-INT(adatrj) 
    353           ksecs = NINT(zdayfrac*86400)        ! Nearest second to catch rounding errors in adatrj          
    354           ihour = INT(ksecs/3600) 
    355           iminute = ksecs/60-ihour*60 
    356             
    357                ! Add to nn_time0 
    358                nhour   =   nn_time0 / 100 
    359                nminute = ( nn_time0 - nhour * 100 ) 
    360           nminute=nminute+iminute 
    361            
    362           IF( nminute >= 60 ) THEN 
    363              nminute=nminute-60 
    364         nhour=nhour+1 
    365           ENDIF 
    366           nhour=nhour+ihour 
    367           IF( nhour >= 24 ) THEN 
    368         nhour=nhour-24 
    369              adatrj=adatrj+1 
    370           ENDIF           
    371           nn_time0 = nhour * 100 + nminute 
    372           adatrj = INT(adatrj)                    ! adatrj set to integer as nn_time0 updated           
    373             ELSE 
    374                ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day) 
    375                ndastp = ndate0        ! ndate0 read in the namelist in dom_nam 
    376                nhour   =   nn_time0 / 100 
    377                nminute = ( nn_time0 - nhour * 100 ) 
    378                IF( nhour*3600+nminute*60-ndt05 .lt. 0 )  ndastp=ndastp-1      ! Start hour is specified in the namelist (default 0) 
    379                adatrj = ( REAL( nit000-1, wp ) * rdt ) / rday 
    380                ! note this is wrong if time step has changed during run 
    381             ENDIF 
    382          ELSE 
    383             ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day) 
    384             ndastp = ndate0           ! ndate0 read in the namelist in dom_nam 
    385             nhour   =   nn_time0 / 100 
    386        nminute = ( nn_time0 - nhour * 100 ) 
    387             IF( nhour*3600+nminute*60-ndt05 .lt. 0 )  ndastp=ndastp-1      ! Start hour is specified in the namelist (default 0) 
    388             adatrj = ( REAL( nit000-1, wp ) * rdt ) / rday 
    389          ENDIF 
    390          IF( ABS(adatrj  - REAL(NINT(adatrj),wp)) < 0.1 / rday )   adatrj = REAL(NINT(adatrj),wp)   ! avoid truncation error 
    391          ! 
    392          IF(lwp) THEN 
    393             WRITE(numout,*) ' *** Info used values : ' 
    394             WRITE(numout,*) '   date ndastp                                      : ', ndastp 
    395             WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
    396        WRITE(numout,*) '   nn_time0                                         : ',nn_time0 
    397             WRITE(numout,*) 
    398          ENDIF 
    399          ! 
    400       ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN 
    401          ! 
    402          IF( kt == nitrst ) THEN 
    403             IF(lwp) WRITE(numout,*) 
    404             IF(lwp) WRITE(numout,*) 'rst_write : write oce restart file  kt =', kt 
    405             IF(lwp) WRITE(numout,*) '~~~~~~~' 
    406          ENDIF 
    407          ! calendar control 
    408          CALL iom_rstput( kt, nitrst, numrow, 'kt'     , REAL( kt    , wp) )   ! time-step 
    409          CALL iom_rstput( kt, nitrst, numrow, 'ndastp' , REAL( ndastp, wp) )   ! date 
    410          CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj            )   ! number of elapsed days since 
    411          !                                                                     ! the begining of the run [s] 
    412     CALL iom_rstput( kt, nitrst, numrow, 'ntime'  , REAL( nn_time0, wp) ) ! time 
    413       ENDIF 
    414       ! 
    415    END SUBROUTINE day_rst 
    416285 
    417286   !!====================================================================== 
Note: See TracChangeset for help on using the changeset viewer.