[reactive] Feedback on my first Reactive program: Monad Laws
Freddie Manners
f.manners at gmail.com
Mon Mar 30 16:19:24 EDT 2009
I believe this is the right identity law (m >>= return === m), though it may
have the same root cause. The annoying thing is that this and a probably
related bug affect all functions (I know of) with type:
Event (Maybe a) -> Event a
, namely justE, joinMaybes & the somewhat artificial "fmap fromJust .
filterE (not . isNothing)". An example is:--
module Main
where
import FRP.Reactive
import FRP.Reactive.LegacyAdapters
import Control.Concurrent
import Control.Applicative
import Control.Monad
import Data.Monoid
import Data.Maybe
aFilter :: String -> Maybe String
aFilter (_:_) = Just "A Non-Empty Line!"
aFilter _ = Nothing
justEventFilterFunction :: (Show a) => Event (Maybe a) -> Event a
--justEventFilterFunction = justE
justEventFilterFunction = fmap fromJust . filterE (not.isNothing)
--justEventFilterFunction = joinMaybes
main = do
clock <- makeClock
(sink, evnt) <- makeEvent clock
forkIO $ forever (getLine >>= sink)
adaptE $ fmap putStrLn (pure "The First Line!" `mappend` (justE .
fmap aFilter $ evnt))
which again delays the `pure "The First Line!"` until the first line of
input is scanned, with all suitable uncommentings of the code. The problem
is definitely in justEventFilterFunction; removing it (sensibly) removes the
delay. The joinMaybes version clearly suffers from the Monad problem I
mentioned before; the fact that justE does the same thing leads me to
suspect the problem is adjustE not doing its job or being too strict, but I
know far too little about the internals to have a clue.
Freddie
2009/3/30 Conal Elliott <conal at conal.net>
> We discovered during quickchecking that a monad associativity law can
> fail. And that it's a semantic bug, not an implementation bug. I don't
> know whether Freddie is running into this same issue or something else. -
> Conal
>
> On Sun, Mar 29, 2009 at 8:27 PM, Jake McArthur <jake.mcarthur at gmail.com>wrote:
>
>> Freddie Manners wrote:
>>
>>> I've hit a rather fundamental problem: it seems Event doesn't obey the
>>> Monad laws.
>>>
>>
>> Yes, this is a known problem. Event is not a Monad. I don't think there
>> are plans to correct it any time soon. My personal preference is to pretend
>> that Event has no Monad instance.
>>
>> - Jake
>>
>> _______________________________________________
>> Reactive mailing list
>> Reactive at haskell.org
>> http://www.haskell.org/mailman/listinfo/reactive
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/reactive/attachments/20090330/3219d2d3/attachment.htm
More information about the Reactive
mailing list