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 12127 – NEMO

Changeset 12127


Ignore:
Timestamp:
2019-12-09T18:42:54+01:00 (4 years ago)
Author:
smasson
Message:

dev_r12114_ticket_2263: replace integer kt_offset by real pt_offset, see #2263

Location:
NEMO/branches/2019/dev_r12114_ticket_2263/src
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r12114_ticket_2263/src/OCE/BDY/bdydta.F90

    r12116 r12127  
    7575CONTAINS 
    7676 
    77    SUBROUTINE bdy_dta( kt, kit, kt_offset ) 
     77   SUBROUTINE bdy_dta( kt, kit, pt_offset ) 
    7878      !!---------------------------------------------------------------------- 
    7979      !!                   ***  SUBROUTINE bdy_dta  *** 
     
    8686      INTEGER, INTENT(in)           ::   kt           ! ocean time-step index  
    8787      INTEGER, INTENT(in), OPTIONAL ::   kit          ! subcycle time-step index (for timesplitting option) 
    88       INTEGER, INTENT(in), OPTIONAL ::   kt_offset    ! time offset in units of timesteps. NB. if kit 
     88      REAL(wp),INTENT(in), OPTIONAL ::   pt_offset    ! time offset in units of timesteps. NB. if kit 
    8989      !                                               ! is present then units = subcycle timesteps. 
    90       !                                               ! kt_offset = 0 => get data at "now" time level 
    91       !                                               ! kt_offset = -1 => get data at "before" time level 
    92       !                                               ! kt_offset = +1 => get data at "after" time level 
    93       !                                               ! etc. 
    9490      ! 
    9591      INTEGER ::  jbdy, jfld, jstart, jend, ib, jl    ! dummy loop indices 
     
    216212         ! read/update all bdy data 
    217213         ! ------------------------ 
    218          CALL fld_read( kt, 1, bf_alias, kit = kit, kt_offset = kt_offset ) 
     214         CALL fld_read( kt, 1, bf_alias, kit = kit, pt_offset = pt_offset ) 
    219215 
    220216         ! apply some corrections in some specific cases... 
     
    279275         IF( PRESENT(kit) .AND. nn_dyn2d_dta(jbdy) .GE. 2 ) THEN 
    280276            CALL bdytide_update( kt = kt, idx = idx_bdy(jbdy), dta = dta_alias, td = tides(jbdy),   &  
    281                &                 kit = kit, kt_offset = kt_offset ) 
     277               &                 kit = kit, pt_offset = pt_offset ) 
    282278         ENDIF 
    283279 
     
    343339                  nblen => idx_bdy(jbdy)%nblen 
    344340                  nblenrim => idx_bdy(jbdy)%nblenrim 
    345                   IF( cn_dyn2d(jbdy) == 'frs' ) THEN ; ilen1(:)=nblen(:) ; ELSE ; ilen1(:)=nblenrim(:) ; ENDIF  
    346                      IF ( dta_bdy(jbdy)%lneed_ssh   ) dta_bdy_s(jbdy)%ssh(1:ilen1(1)) = dta_bdy(jbdy)%ssh(1:ilen1(1)) 
    347                      IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%u2d(1:ilen1(2)) = dta_bdy(jbdy)%u2d(1:ilen1(2)) 
    348                      IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%v2d(1:ilen1(3)) = dta_bdy(jbdy)%v2d(1:ilen1(3)) 
    349                   ENDIF 
    350                END DO 
    351             ELSE ! Add tides if not split-explicit free surface else this is done in ts loop 
    352                ! 
    353                CALL bdy_dta_tides( kt=kt, kt_offset=kt_offset ) 
    354             ENDIF 
    355          ENDIF 
    356          ! 
    357          IF( ln_timing )   CALL timing_stop('bdy_dta') 
    358          ! 
    359       END SUBROUTINE bdy_dta 
     341                  IF( cn_dyn2d(jbdy) == 'frs' ) THEN   ;   ilen1(:)=nblen(:) 
     342                  ELSE                                 ;   ilen1(:)=nblenrim(:) 
     343                  ENDIF 
     344                  IF ( dta_bdy(jbdy)%lneed_ssh   ) dta_bdy_s(jbdy)%ssh(1:ilen1(1)) = dta_bdy(jbdy)%ssh(1:ilen1(1)) 
     345                  IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%u2d(1:ilen1(2)) = dta_bdy(jbdy)%u2d(1:ilen1(2)) 
     346                  IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%v2d(1:ilen1(3)) = dta_bdy(jbdy)%v2d(1:ilen1(3)) 
     347               ENDIF 
     348            END DO 
     349         ELSE ! Add tides if not split-explicit free surface else this is done in ts loop 
     350            ! 
     351            CALL bdy_dta_tides( kt=kt, pt_offset=pt_offset ) 
     352         ENDIF 
     353      ENDIF 
     354      ! 
     355      IF( ln_timing )   CALL timing_stop('bdy_dta') 
     356      ! 
     357   END SUBROUTINE bdy_dta 
    360358 
    361359 
  • NEMO/branches/2019/dev_r12114_ticket_2263/src/OCE/BDY/bdytides.F90

    r11536 r12127  
    262262 
    263263 
    264    SUBROUTINE bdytide_update( kt, idx, dta, td, kit, kt_offset ) 
     264   SUBROUTINE bdytide_update( kt, idx, dta, td, kit, pt_offset ) 
    265265      !!---------------------------------------------------------------------- 
    266266      !!                 ***  SUBROUTINE bdytide_update  *** 
     
    274274      TYPE(TIDES_DATA) , INTENT(inout) ::   td          ! tidal harmonics data 
    275275      INTEGER, OPTIONAL, INTENT(in   ) ::   kit         ! Barotropic timestep counter (for timesplitting option) 
    276       INTEGER, OPTIONAL, INTENT(in   ) ::   kt_offset   ! time offset in units of timesteps. NB. if kit 
     276      REAL(wp), OPTIONAL,INTENT(in   ) ::   pt_offset   ! time offset in units of timesteps. NB. if kit 
    277277      !                                                 ! is present then units = subcycle timesteps. 
    278       !                                                 ! kt_offset = 0  => get data at "now"    time level 
    279       !                                                 ! kt_offset = -1 => get data at "before" time level 
    280       !                                                 ! kt_offset = +1 => get data at "after"  time level 
    281       !                                                 ! etc. 
    282278      ! 
    283279      INTEGER  ::   itide, igrd, ib       ! dummy loop indices 
    284       INTEGER  ::   time_add              ! time offset in units of timesteps 
    285280      INTEGER, DIMENSION(3) ::   ilen0    ! length of boundary data (from OBC arrays) 
    286       REAL(wp) ::   z_arg, z_sarg, zflag, zramp   ! local scalars     
     281      REAL(wp) ::   z_arg, z_sarg, zflag, zramp, zt_offset  ! local scalars     
    287282      REAL(wp), DIMENSION(jpmax_harmo) :: z_sist, z_cost 
    288283      !!---------------------------------------------------------------------- 
     
    299294      IF ( (nsec_day == NINT(0.5_wp * rdt) .OR. kt==nit000) .AND. zflag==1 ) THEN 
    300295        ! 
    301         kt_tide = kt - (nsec_day - 0.5_wp * rdt)/rdt 
     296        kt_tide = kt - NINT((REAL(nsec_day,wp) - 0.5_wp * rdt)/rdt) 
    302297        ! 
    303298        IF(lwp) THEN 
     
    312307      ENDIF  
    313308 
    314       time_add = 0 
    315       IF( PRESENT(kt_offset) ) THEN 
    316          time_add = kt_offset 
    317       ENDIF 
     309      zt_offset = 0._wp 
     310      IF( PRESENT(pt_offset) )   zt_offset = pt_offset 
    318311          
    319312      IF( PRESENT(kit) ) THEN   
    320          z_arg = ((kt-kt_tide) * rdt + (kit+0.5_wp*(time_add-1)) * rdt / REAL(nn_baro,wp) ) 
     313         z_arg =   REAL( kt - kt_tide, wp) * rdt + ( REAL(kit, wp) + 0.5_wp * ( zt_offset - 1._wp ) ) * rdt / REAL(nn_baro, wp) 
    321314      ELSE                               
    322          z_arg = ((kt-kt_tide)+time_add) * rdt 
     315         z_arg = ( REAL( kt - kt_tide, wp) + zt_offset ) * rdt 
    323316      ENDIF 
    324317 
    325318      ! Linear ramp on tidal component at open boundaries  
    326319      zramp = 1._wp 
    327       IF (ln_tide_ramp) zramp = MIN(MAX( (z_arg + (kt_tide-nit000)*rdt)/(rdttideramp*rday),0._wp),1._wp) 
     320      IF (ln_tide_ramp) zramp = MIN(MAX( (z_arg + REAL(kt_tide-nit000,wp)*rdt)/(rdttideramp*rday),0._wp),1._wp) 
    328321 
    329322      DO itide = 1, nb_harmo 
     
    351344 
    352345 
    353    SUBROUTINE bdy_dta_tides( kt, kit, kt_offset ) 
     346   SUBROUTINE bdy_dta_tides( kt, kit, pt_offset ) 
    354347      !!---------------------------------------------------------------------- 
    355348      !!                 ***  SUBROUTINE bdy_dta_tides  *** 
     
    360353      INTEGER,           INTENT(in) ::   kt          ! Main timestep counter 
    361354      INTEGER, OPTIONAL, INTENT(in) ::   kit         ! Barotropic timestep counter (for timesplitting option) 
    362       INTEGER, OPTIONAL, INTENT(in) ::   kt_offset   ! time offset in units of timesteps. NB. if kit 
     355      REAL(wp),OPTIONAL, INTENT(in) ::   pt_offset   ! time offset in units of timesteps. NB. if kit 
    363356      !                                              ! is present then units = subcycle timesteps. 
    364       !                                              ! kt_offset = 0  => get data at "now"    time level 
    365       !                                              ! kt_offset = -1 => get data at "before" time level 
    366       !                                              ! kt_offset = +1 => get data at "after"  time level 
    367       !                                              ! etc. 
    368357      ! 
    369358      LOGICAL  ::   lk_first_btstp            ! =.TRUE. if time splitting and first barotropic step 
    370359      INTEGER  ::   itide, ib_bdy, ib, igrd   ! loop indices 
    371       INTEGER  ::   time_add                  ! time offset in units of timesteps 
    372360      INTEGER, DIMENSION(jpbgrd)   ::   ilen0  
    373361      INTEGER, DIMENSION(1:jpbgrd) ::   nblen, nblenrim  ! short cuts 
    374       REAL(wp) ::   z_arg, z_sarg, zramp, zoff, z_cost, z_sist       
     362      REAL(wp) ::   z_arg, z_sarg, zramp, zoff, z_cost, z_sist, zt_offset    
    375363      !!---------------------------------------------------------------------- 
    376364      ! 
     
    378366      IF ( PRESENT(kit).AND.( kit /= 1 ) ) THEN ; lk_first_btstp=.FALSE. ; ENDIF 
    379367 
    380       time_add = 0 
    381       IF( PRESENT(kt_offset) ) THEN 
    382          time_add = kt_offset 
    383       ENDIF 
     368      zt_offset = 0._wp 
     369      IF( PRESENT(pt_offset) )   zt_offset = pt_offset 
    384370       
    385371      ! Absolute time from model initialization:    
    386372      IF( PRESENT(kit) ) THEN   
    387          z_arg = ( kt + (kit+time_add-1) / REAL(nn_baro,wp) ) * rdt 
     373         z_arg = ( REAL(kt, wp) + ( REAL(kit, wp) + zt_offset - 1. ) / REAL(nn_baro, wp) ) * rdt 
    388374      ELSE                               
    389          z_arg = ( kt + time_add ) * rdt 
     375         z_arg = ( REAL(kt, wp) + zt_offset ) * rdt 
    390376      ENDIF 
    391377 
    392378      ! Linear ramp on tidal component at open boundaries  
    393379      zramp = 1. 
    394       IF (ln_tide_ramp) zramp = MIN(MAX( (z_arg - nit000*rdt)/(rdttideramp*rday),0.),1.) 
     380      IF (ln_tide_ramp) zramp = MIN(MAX( (z_arg - REAL(nit000, wp)*rdt)/(rdttideramp*rday),0.),1.) 
    395381 
    396382      DO ib_bdy = 1,nb_bdy 
     
    409395            IF ( ( nsec_day == NINT(0.5_wp * rdt) .OR. kt==nit000 ) .AND. lk_first_btstp ) THEN 
    410396               ! 
    411                kt_tide = kt - (nsec_day - 0.5_wp * rdt)/rdt 
     397               kt_tide = kt - NINT((REAL(nsec_day,wp) - 0.5_wp * rdt)/rdt) 
    412398               ! 
    413399               IF(lwp) THEN 
     
    421407               ! 
    422408            ENDIF 
    423             zoff = -kt_tide * rdt ! time offset relative to nodal factor computation time 
     409            zoff = REAL(-kt_tide,wp) * rdt ! time offset relative to nodal factor computation time 
    424410            ! 
    425411            ! If time splitting, initialize arrays from slow varying open boundary data: 
  • NEMO/branches/2019/dev_r12114_ticket_2263/src/OCE/DYN/dynspg_ts.F90

    r12072 r12127  
    423423         !                    !==  Update the forcing ==! (BDY and tides) 
    424424         ! 
    425          IF( ln_bdy      .AND. ln_tide )   CALL bdy_dta_tides( kt, kit=jn, kt_offset= noffset+1 ) 
    426          IF( ln_tide_pot .AND. ln_tide )   CALL upd_tide     ( kt, kit=jn, kt_offset= noffset   ) 
     425         IF( ln_bdy      .AND. ln_tide )   CALL bdy_dta_tides( kt, kit=jn, pt_offset= REAL(noffset,wp) + 1._wp ) 
     426         IF( ln_tide_pot .AND. ln_tide )   CALL upd_tide     ( kt, kit=jn, pt_offset= REAL(noffset,wp)         ) 
    427427         ! 
    428428         !                    !==  extrapolation at mid-step  ==!   (jn+1/2) 
  • NEMO/branches/2019/dev_r12114_ticket_2263/src/OCE/SBC/fldread.F90

    r12116 r12127  
    132132CONTAINS 
    133133 
    134    SUBROUTINE fld_read( kt, kn_fsbc, sd, kit, kt_offset ) 
     134   SUBROUTINE fld_read( kt, kn_fsbc, sd, kit, pt_offset ) 
    135135      !!--------------------------------------------------------------------- 
    136136      !!                    ***  ROUTINE fld_read  *** 
     
    148148      TYPE(FLD), INTENT(inout), DIMENSION(:) ::   sd        ! input field related variables 
    149149      INTEGER  , INTENT(in   ), OPTIONAL     ::   kit       ! subcycle timestep for timesplitting option 
    150       INTEGER  , INTENT(in   ), OPTIONAL     ::   kt_offset ! provide fields at time other than "now" 
    151       !                                                     !   kt_offset = -1 => fields at "before" time level 
    152       !                                                     !   kt_offset = +1 => fields at "after"  time level 
    153       !                                                     !   etc. 
     150      REAL(wp) , INTENT(in   ), OPTIONAL     ::   pt_offset ! provide fields at time other than "now" 
    154151      !! 
    155152      INTEGER  ::   imf          ! size of the structure sd 
     
    168165      ELSE                                      ;   zt_offset = 0. 
    169166      ENDIF 
    170       IF( PRESENT(kt_offset) )   zt_offset = REAL( kt_offset, wp ) 
     167      IF( PRESENT(pt_offset) )   zt_offset = pt_offset 
    171168 
    172169      ! Note that all varibles starting by nsec_* are shifted time by +1/2 time step to be centrered 
  • NEMO/branches/2019/dev_r12114_ticket_2263/src/OCE/SBC/updtide.F90

    r11536 r12127  
    2727CONTAINS 
    2828 
    29    SUBROUTINE upd_tide( kt, kit, kt_offset ) 
     29   SUBROUTINE upd_tide( kt, kit, pt_offset ) 
    3030      !!---------------------------------------------------------------------- 
    3131      !!                 ***  ROUTINE upd_tide  *** 
     
    3939      INTEGER, INTENT(in)           ::   kt      ! ocean time-step index 
    4040      INTEGER, INTENT(in), OPTIONAL ::   kit     ! external mode sub-time-step index (lk_dynspg_ts=T) 
    41       INTEGER, INTENT(in), OPTIONAL ::   kt_offset ! time offset in number  
     41      REAL(wp),INTENT(in), OPTIONAL ::   pt_offset ! time offset in number  
    4242                                                     ! of internal steps             (lk_dynspg_ts=F) 
    4343                                                     ! of external steps             (lk_dynspg_ts=T) 
    4444      ! 
    45       INTEGER  ::   ioffset      ! local integer 
    4645      INTEGER  ::   ji, jj, jk   ! dummy loop indices 
    4746      REAL(wp) ::   zt, zramp    ! local scalar 
     47      REAL(wp) ::   zt_offset     
    4848      REAL(wp), DIMENSION(nb_harmo) ::   zwt  
    4949      !!----------------------------------------------------------------------       
    5050      ! 
    5151      !                               ! tide pulsation at model time step (or sub-time-step) 
    52       zt = ( kt - kt_tide ) * rdt 
     52      zt = REAL( kt - kt_tide, wp ) * rdt 
    5353      ! 
    54       ioffset = 0 
    55       IF( PRESENT( kt_offset ) )   ioffset = kt_offset 
     54      zt_offset = 0._wp 
     55      IF( PRESENT( pt_offset ) )   zt_offset = pt_offset 
    5656      ! 
    5757      IF( PRESENT( kit ) )   THEN 
    58          zt = zt + ( kit +  ioffset - 1 ) * rdt / REAL( nn_baro, wp ) 
     58         zt = zt + ( REAL( kit, wp ) +  zt_offset - 1._wp ) * rdt / REAL( nn_baro, wp ) 
    5959      ELSE 
    60          zt = zt + ioffset * rdt 
     60         zt = zt + zt_offset * rdt 
    6161      ENDIF 
    6262      ! 
     
    7070      IF( ln_tide_ramp ) THEN         ! linear increase if asked 
    7171         zt = ( kt - nit000 ) * rdt 
    72          IF( PRESENT( kit ) )   zt = zt + ( kit + ioffset -1) * rdt / REAL( nn_baro, wp ) 
     72         IF( PRESENT( kit ) )   zt = zt + ( REAL( kit, wp ) + zt_offset -1._wp ) * rdt / REAL( nn_baro, wp ) 
    7373         zramp = MIN(  MAX( zt / (rdttideramp*rday) , 0._wp ) , 1._wp  ) 
    7474         pot_astro(:,:) = zramp * pot_astro(:,:) 
  • NEMO/branches/2019/dev_r12114_ticket_2263/src/OCE/step.F90

    r11993 r12127  
    112112      IF( ln_tide    )   CALL sbc_tide( kstp )                   ! update tide potential 
    113113      IF( ln_apr_dyn )   CALL sbc_apr ( kstp )                   ! atmospheric pressure (NB: call before bdy_dta which needs ssh_ib)  
    114       IF( ln_bdy     )   CALL bdy_dta ( kstp, kt_offset = +1 )   ! update dynamic & tracer data at open boundaries 
     114      IF( ln_bdy     )   CALL bdy_dta ( kstp, pt_offset = 1. )   ! update dynamic & tracer data at open boundaries 
    115115                         CALL sbc     ( kstp )                   ! Sea Boundary Condition (including sea-ice) 
    116116 
  • NEMO/branches/2019/dev_r12114_ticket_2263/src/SAS/step.F90

    r11536 r12127  
    9696      !           From SAS: ocean bdy data are wrong  (but we do not care) and ice bdy data are OK.   
    9797      !           This is not clean and should be changed in the future.  
    98       IF( ln_bdy     )       CALL bdy_dta ( kstp, kt_offset=+1 )   ! update dynamic & tracer data at open boundaries 
     98      IF( ln_bdy     )       CALL bdy_dta ( kstp, pt_offset = 1. )   ! update dynamic & tracer data at open boundaries 
    9999      ! ==> 
    100100                             CALL sbc    ( kstp )         ! Sea Boundary Condition (including sea-ice) 
  • NEMO/branches/2019/dev_r12114_ticket_2263/src/TOP/trcbc.F90

    r11536 r12127  
    368368      IF( PRESENT(jit) ) THEN  
    369369         ! 
    370          ! OPEN boundary conditions (use kt_offset=+1 as they are applied at the end of the step) 
     370         ! OPEN boundary conditions (use pt_offset=1. as they are applied at the end of the step) 
    371371         IF( nb_trcobc > 0 ) THEN 
    372372           if (lwp) write(numout,'(a,i5,a,i10)') '   reading OBC data for ', nb_trcobc ,' variable(s) at step ', kt 
    373            CALL fld_read( kt=kt, kn_fsbc=1, sd=sf_trcobc, kit=jit, kt_offset=+1) 
     373           CALL fld_read( kt=kt, kn_fsbc=1, sd=sf_trcobc, kit=jit, pt_offset=1.) 
    374374         ENDIF 
    375375         ! 
     
    388388      ELSE 
    389389         ! 
    390          ! OPEN boundary conditions (use kt_offset=+1 as they are applied at the end of the step) 
     390         ! OPEN boundary conditions (use pt_offset=1. as they are applied at the end of the step) 
    391391         IF( nb_trcobc > 0 ) THEN 
    392392           if (lwp) write(numout,'(a,i5,a,i10)') '   reading OBC data for ', nb_trcobc ,' variable(s) at step ', kt 
    393            CALL fld_read( kt=kt, kn_fsbc=1, sd=sf_trcobc, kt_offset=+1) 
     393           CALL fld_read( kt=kt, kn_fsbc=1, sd=sf_trcobc, pt_offset=1.) 
    394394         ENDIF 
    395395         ! 
Note: See TracChangeset for help on using the changeset viewer.