I think I'm on the right track. I have commented out all test harness code and have changed the signature for
bufferPopulated
bufferPopulated :: UAC -> IO Bool bufferPopulated ev = do let eInput = ev <$ never eValidated = toVAC <$> eInput bBufferMap <- liftMoment ((buffer eValidated eClear) :: Moment (Behavior BufferMap)) let r2 = [(Just $ BufferMap $ M.insert (AID (Data.Text.pack "100")) (toVAC ev) (M.empty :: M.Map AID VAC))] r1 <- (interpret (eBuffer bBufferMap) []) :: IO [Maybe BufferMap]) return $ r1 == r2
I believe this should work, but here's the error
tests/Spec.hs:35:17: No instance for (MonadMoment IO) arising from a use of ‘liftMoment’ In a stmt of a 'do' block: bBufferMap <- liftMoment ((buffer eValidated eClear) :: Moment (Behavior BufferMap))
Let's take a look at
MonadMoment
fromReactive.Banana.Combinators
class Monad m => MonadMoment m where
An instance of the MonadMoment class denotes a computation that happens at one particular moment in time.
Unlike the Moment monad, it need not be pure anymore.
Methods
liftMoment :: Moment a -> m a
Instances
MonadMoment MomentIO
MonadMoment Momentm
can be anyMonad
,IO
is aMonad
. soliftMoment
should lift theMoment Behavior (BufferMap)
toIO Behavior (BufferMap)
, why doesn't it. What's wrong with my reasoning?On Fri, Nov 13, 2015 at 7:16 AM, Michael Litchard <michael@schmong.org> wrote:Below is some test code I am writing for my game, the link to the entire codebase, the error message and some discussion main :: IO () main = defaultMain [ testGroup "EventNetwork Input" [testBuffer "bBuffer" Populated] ] testBuffer :: String -> BufferState -> Test testBuffer name Populated = testCase name $ assert $ bufferPopulated (UAC (PlayerCommand (Move (ToPlanetName Mongo)) (AID (Data.Text.pack "100")))) testBuffer name Empty = testCase name $ assert $ bufferEmptied (UAC (PlayerCommand (Move (ToPlanetName Mongo)) (AID (Data.Text.pack "100")))) bufferPopulated :: UAC -> MomentIO Bool bufferPopulated ev = do let eInput = ev <$ never eValidated = toVAC <$> eInput bBufferMap <- (buffer eValidated eClear) :: MomentIO (Behavior BufferMap) let r2 = [(Just $ BufferMap $ M.insert (AID (Data.Text.pack "100")) (toVAC ev) (M.empty :: M.Map AID VAC))] r1 <- liftIO $ ((interpret (eBuffer bBufferMap) []) :: IO [Maybe BufferMap]) return $ r1 == r2 bufferEmptied :: UAC -> MomentIO Bool bufferEmptied ev = undefined eBuffer :: Behavior BufferMap -> Event a -> Event BufferMap eBuffer bBufferMap nvr = bBufferMap <@ (() <$ nvr) eClear = Clear <$ (() <$ never) When I run stack build I get tests/Spec.hs:26:19: No instance for (Test.HUnit.Base.Assertable (MomentIO Bool)) arising from a use of ‘assert’ In the expression: assert In the second argument of ‘($)’, namely ‘assert $ bufferPopulated (UAC (PlayerCommand (Move (ToPlanetName Mongo)) (AID (pack "100"))))’ In the expression: testCase name $ assert $ bufferPopulated (UAC (PlayerCommand (Move (ToPlanetName Mongo)) (AID (pack "100")))) The problem lies with buffer. It relies on accumB which requires the MomentIO monad. I considered writing an instance for Assertable, but I think that's a red-herring and the answer lies elsewhere. I need to reconcile the fact that assert wants an IO Bool, but accumB wants a MomentIO. Maybe I do need to write an instance for Assertable. Here's the link to the project: https://github.com/mlitchard/emporos/tree/banana-1.0.0/src
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe