{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} module Reflex.Test ( eventTrace ) where import Control.Monad import Control.Monad.Trans import Data.Dependent.Map (DSum((:=>))) import Reflex import Reflex.Host.Class import Data.Functor.Identity import Control.Monad.Ref import Test.Tasty.HUnit -- | Takes a trace of the input to a network and verifies the output at each step. -- -- In the trace, Nothing values represents an Event not firing at that step. eventTrace :: forall a b . (Eq b, Show b) => [(Maybe a, Maybe b, b)] -- ^ The trace of the input to the Event, and what output the Dynamic should -- have in terms of events and held value. -> b -- ^ The value the Dynamic result of the HostFrame should initially contain. -> (forall t. (ReflexHost t) => Event t a -> HostFrame t (Dynamic t b)) -- ^ The host frame to run the check on. -> Assertion eventTrace cases initVal frm = runSpiderHost $ do -- Setup a triger, and prepare the HostFrame using it (re, rmt) <- newEventWithTriggerRef rd <- runHostFrame (frm re::HostFrame (SpiderTimeline Global) (Dynamic (SpiderTimeline Global) b)) -- Make sure we initialized to the correct value actualStart <- sample . current $ rd liftIO $ initVal @=? actualStart -- Now check every step of our event list to make sure we get the right results. ehr <- subscribeEvent . updated $ rd mrt <- readRef rmt case mrt of Nothing -> return () -- Event isn't used in the test Just rt -> do void . forM cases $ \(ma, mb, b) -> do case ma of Nothing -> return () Just a -> do stepEventValue <- fireEventsAndRead [rt :=> (Identity a)] $ readEvent ehr >>= sequence liftIO $ mb @=? stepEventValue afterStepValue <- sample . current $ rd liftIO $ b @=? afterStepValue