Skip to content

Commit

Permalink
Extend Schedule test
Browse files Browse the repository at this point in the history
  • Loading branch information
turion committed Oct 27, 2024
1 parent 582fe5e commit c6f08ac
Showing 1 changed file with 5 additions and 2 deletions.
7 changes: 5 additions & 2 deletions rhine/test/Schedule.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ module Schedule where
import Control.Arrow ((>>>))
import Data.Functor (($>))
import Data.Functor.Identity
import Data.List (sort)

-- tasty
import Test.Tasty
Expand Down Expand Up @@ -59,14 +60,16 @@ tests =
[ testCase "chronological ticks" $ do
let
(runningClock, _time) = runSchedule (initClock $ ParallelClock (FixedStep @5) (FixedStep @3) :: RunningClockInit (Schedule Integer) Integer (Either () ()))
output = runSchedule $ embed runningClock $ replicate 6 ()
output
output = runSchedule $ embed runningClock $ replicate 1000 ()
take 6 output
@?= [ (3, Right ())
, (5, Left ())
, (6, Right ())
, (9, Right ())
, (10, Left ())
, (12, Right ())
]
let timestamps = fst <$> output
timestamps @?= sort timestamps
]
]

0 comments on commit c6f08ac

Please sign in to comment.