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 12059 for NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/BDY/bdytides.F90 – NEMO

Ignore:
Timestamp:
2019-12-05T09:34:39+01:00 (4 years ago)
Author:
smueller
Message:

Reversal of changeset [10865] to avoid a conflict in the upcoming sync merge with the trunk; a new version of the modification implemented by changeset [10865] will be applied following the upcoming sync merge with the trunk (ticket #2194)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/BDY/bdytides.F90

    r10865 r12059  
    3030 
    3131   PUBLIC   bdytide_init     ! routine called in bdy_init 
     32   PUBLIC   bdytide_update   ! routine called in bdy_dta 
    3233   PUBLIC   bdy_dta_tides    ! routine called in dyn_spg_ts 
    3334 
     
    262263 
    263264 
     265   SUBROUTINE bdytide_update( kt, idx, dta, td, jit, time_offset ) 
     266      !!---------------------------------------------------------------------- 
     267      !!                 ***  SUBROUTINE bdytide_update  *** 
     268      !!                 
     269      !! ** Purpose : - Add tidal forcing to ssh, u2d and v2d OBC data arrays.  
     270      !!                 
     271      !!---------------------------------------------------------------------- 
     272      INTEGER          , INTENT(in   ) ::   kt          ! Main timestep counter 
     273      TYPE(OBC_INDEX)  , INTENT(in   ) ::   idx         ! OBC indices 
     274      TYPE(OBC_DATA)   , INTENT(inout) ::   dta         ! OBC external data 
     275      TYPE(TIDES_DATA) , INTENT(inout) ::   td          ! tidal harmonics data 
     276      INTEGER, OPTIONAL, INTENT(in   ) ::   jit         ! Barotropic timestep counter (for timesplitting option) 
     277      INTEGER, OPTIONAL, INTENT(in   ) ::   time_offset ! time offset in units of timesteps. NB. if jit 
     278      !                                                 ! is present then units = subcycle timesteps. 
     279      !                                                 ! time_offset = 0  => get data at "now"    time level 
     280      !                                                 ! time_offset = -1 => get data at "before" time level 
     281      !                                                 ! time_offset = +1 => get data at "after"  time level 
     282      !                                                 ! etc. 
     283      ! 
     284      INTEGER  ::   itide, igrd, ib       ! dummy loop indices 
     285      INTEGER  ::   time_add              ! time offset in units of timesteps 
     286      INTEGER, DIMENSION(3) ::   ilen0    ! length of boundary data (from OBC arrays) 
     287      REAL(wp) ::   z_arg, z_sarg, zflag, zramp   ! local scalars     
     288      REAL(wp), DIMENSION(jpmax_harmo) :: z_sist, z_cost 
     289      !!---------------------------------------------------------------------- 
     290      ! 
     291      ilen0(1) =  SIZE(td%ssh(:,1,1)) 
     292      ilen0(2) =  SIZE(td%u(:,1,1)) 
     293      ilen0(3) =  SIZE(td%v(:,1,1)) 
     294 
     295      zflag=1 
     296      IF ( PRESENT(jit) ) THEN 
     297        IF ( jit /= 1 ) zflag=0 
     298      ENDIF 
     299 
     300      IF ( (nsec_day == NINT(0.5_wp * rdt) .OR. kt==nit000) .AND. zflag==1 ) THEN 
     301        ! 
     302        kt_tide = kt - (nsec_day - 0.5_wp * rdt)/rdt 
     303        ! 
     304        IF(lwp) THEN 
     305           WRITE(numout,*) 
     306           WRITE(numout,*) 'bdytide_update : (re)Initialization of the tidal bdy forcing at kt=',kt 
     307           WRITE(numout,*) '~~~~~~~~~~~~~~ ' 
     308        ENDIF 
     309        ! 
     310        CALL tide_init_elevation ( idx, td ) 
     311        CALL tide_init_velocities( idx, td ) 
     312        ! 
     313      ENDIF  
     314 
     315      time_add = 0 
     316      IF( PRESENT(time_offset) ) THEN 
     317         time_add = time_offset 
     318      ENDIF 
     319          
     320      IF( PRESENT(jit) ) THEN   
     321         z_arg = ((kt-kt_tide) * rdt + (jit+0.5_wp*(time_add-1)) * rdt / REAL(nn_baro,wp) ) 
     322      ELSE                               
     323         z_arg = ((kt-kt_tide)+time_add) * rdt 
     324      ENDIF 
     325 
     326      ! Linear ramp on tidal component at open boundaries  
     327      zramp = 1._wp 
     328      IF (ln_tide_ramp) zramp = MIN(MAX( (z_arg + (kt_tide-nit000)*rdt)/(rn_tide_ramp_dt*rday),0._wp),1._wp) 
     329 
     330      DO itide = 1, nb_harmo 
     331         z_sarg = z_arg * tide_harmonics(itide)%omega 
     332         z_cost(itide) = COS( z_sarg ) 
     333         z_sist(itide) = SIN( z_sarg ) 
     334      END DO 
     335 
     336      DO itide = 1, nb_harmo 
     337         igrd=1                              ! SSH on tracer grid 
     338         DO ib = 1, ilen0(igrd) 
     339            dta%ssh(ib) = dta%ssh(ib) + zramp*(td%ssh(ib,itide,1)*z_cost(itide) + td%ssh(ib,itide,2)*z_sist(itide)) 
     340         END DO 
     341         igrd=2                              ! U grid 
     342         DO ib = 1, ilen0(igrd) 
     343            dta%u2d(ib) = dta%u2d(ib) + zramp*(td%u  (ib,itide,1)*z_cost(itide) + td%u  (ib,itide,2)*z_sist(itide)) 
     344         END DO 
     345         igrd=3                              ! V grid 
     346         DO ib = 1, ilen0(igrd)  
     347            dta%v2d(ib) = dta%v2d(ib) + zramp*(td%v  (ib,itide,1)*z_cost(itide) + td%v  (ib,itide,2)*z_sist(itide)) 
     348         END DO 
     349      END DO 
     350      ! 
     351   END SUBROUTINE bdytide_update 
     352 
     353 
    264354   SUBROUTINE bdy_dta_tides( kt, kit, time_offset ) 
    265355      !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.