[Haskell-cafe] Fwd: Composable events: Applicative and Alternative

Tikhon Jelvis tikhon at jelv.is
Fri May 16 19:28:24 UTC 2014


Oops, forgot to include the list.

---------- Forwarded message ----------
From: Tikhon Jelvis <tikhon at jelv.is>
Date: Fri, May 16, 2014 at 12:27 PM
Subject: Re: [Haskell-cafe] Composable events: Applicative and Alternative
To: Corentin Dupont <corentin.dupont at gmail.com>


It sounds like you're trying to solve the same problems as FRP. In fact,
this was basically the original impetus for FRP: making events (and
reactive programs in general) nicely composable.

Perhaps you could take a look at how event streams work in frameworks like
Reactive-Banana? Reactive-Banana doesn't make its events applicatives, but
it's a perfectly reasonable thing to do: there's a great explanation in
Conal's "Push-Pull Functional Reactive Programming"[1] in section 2.2.4.


On Fri, May 16, 2014 at 12:15 PM, Corentin Dupont <corentin.dupont at gmail.com
> wrote:

>
> I created a DSL to manage and create events (see under). It's an instance
> of Applicative and Alternative, which make them compose nicely.
> The idea is that when an event is firing, I look the corresponding event
> in the tree and replace it by its value using Pure.
>
> For example onInputText will trigger the display of a form with a text
> field on the screen, and when the player validates the form, the same
> onInputText is searched in the tree by the engine and replaced by the
> text value. This is where the difficulty begins:
>
> --> How to make Event an instance of Eq? How to search and replace
> through it?
>
> The problem is the EventProduct primitive, that forbids to make the DSL an
> instance of Eq:
> EventProduct :: Event (a -> b) -> Event a -> Event b
>
> Should I replace it by:
> EventProduct :: Event a -> Event b -> Event (a,b)
>
> But then, bye-bye Applicative/Alternative instances!
> How can I make the tree of events searchable/traversable and still
> maintain the Applicative instance?
>
> Thanks!!
> Corentin
>
>
> On Sat, May 3, 2014 at 8:02 PM, Corentin Dupont <corentin.dupont at gmail.com
> > wrote:
>
>> Hi Cafe!!
>>
>> For my game Nomyx, I am using events that the player can program. For
>> example, the player can register a callback that will be triggered when a
>> new player arrives. He can also program some forms (with buttons,
>> checkboxes, textboxes...) to appear on the Web GUI. The problem is those
>> events are not composable: he has to create and handle them one by one.
>>
>> So I'm thinking of making those events composable by making them an
>> instance of Applicative and Alternative.
>> For Applicative, this makes events composable very much like in
>> Applicative-Functors and Reform. I can build neat composed events such as
>> (full program below):
>>
>> onInputMyRecord :: Event MyRecord
>> onInputMyRecord = MyRecord <$> onInputText <*> onInputCheckbox
>>
>> For Alternative, I haven't seen any example of it on the net. The idea
>> is that the first event that fires is used to build the alternative:
>>
>> onInputMyAlternative :: Event Bool
>> onInputMyAlternative = (True <$ onInputButton) <|> (False <$
>> onInputButton)
>>
>> Here is an example program:
>>
>> {-# LANGUAGE GADTs #-}
>>
>> module ComposableEvents where
>>
>> import Control.Applicative
>> import Data.Time
>> import Data.Traversable
>>
>> type PlayerNumber = Int
>>
>> data Event a where
>>    OnInputText :: PlayerNumber -> Event String           -- A textbox
>> will be created for the player. When filled, this event will fire and
>> return the result
>>    OnInputCheckbox :: PlayerNumber -> Event Bool         -- Idem with a
>> checkbox
>>    OnInputButton :: PlayerNumber -> Event ()             -- Idem with a
>> button
>>    OnTime :: UTCTime -> Event ()                         -- time event
>>    EventSum :: Event a -> Event a -> Event a             -- The first
>> event to fire will be returned
>>    EventProduct :: Event (a -> b) -> Event a -> Event b  -- both events
>> should fire, and then the result is returned
>>    Fmap :: (a -> b) -> Event a -> Event b                -- transforms
>> the value returned by an event.
>>    Pure :: a -> Event a                                  -- Create a fake
>> event. The result is useable with no delay.
>>    Empty :: Event a                                      -- An event that
>> is never fired.
>>
>> instance Functor Event where
>>    fmap = Fmap
>>
>> instance Applicative Event where
>>    pure = Pure
>>    (<*>) = EventProduct
>>
>> instance Alternative Event where
>>    (<|>) = EventSum
>>    empty = Empty
>>
>> onInputText = OnInputText
>> onInputCheckbox = OnInputCheckbox
>> onInputButton = OnInputButton
>> onTime = OnTime
>>
>> -- A product type
>> data MyRecord = MyRecord String Bool
>>
>> -- A sum type
>> data MyAlternative = A | B
>>
>> -- Using the Applicative instance, we can build a product type from two
>> separate event results.
>> -- The event callback should be called only when all two events have
>> fired.
>> onInputMyRecord :: Event MyRecord
>> onInputMyRecord = MyRecord <$> onInputText 1 <*> onInputCheckbox 1
>>
>> -- other possible implementation (given a monad instance)
>> -- onInputMyRecord' = do
>> --    s <- onInputText
>> --    b <- onInputCheckbox
>> --    return $ MyRecord s b
>>
>> -- Using the Alternative instance, we build a sum type.
>> -- The event callback should be called when the first event have fired.
>> onInputMyAlternative :: Event MyAlternative
>> onInputMyAlternative = (const A <$> onInputButton 1) <|> (const B <$>
>> onInputButton 1)
>>
>> allPlayers = [1 .. 10]
>>
>> -- Now complex events can be created, such as voting systems:
>> voteEvent :: UTCTime -> Event ([Maybe Bool])
>> voteEvent time = sequenceA $ map (singleVote time) allPlayers
>>
>> singleVote :: UTCTime -> PlayerNumber -> Event (Maybe Bool)
>> singleVote timeLimit pn = (Just <$> onInputCheckbox pn) <|> (const
>> Nothing <$> onTime timeLimit)
>>
>> vote :: UTCTime -> Event Bool
>> vote timeLimit = unanimity <$> (voteEvent timeLimit)
>>
>> unanimity :: [Maybe Bool] -> Bool
>> unanimity = all (== Just True)
>>
>>
>> --Evaluation
>> --evalEvent :: Event a -> State Game a
>> --evalEvent = undefined
>>
>> With this DSL, I can create complex events such as time limited votes
>> very neatly...
>> There is much left to do for a full implem: the way to register callbacks
>> on complex events, the evaluator and the event manager.
>> Have you heard about a similar implementation? It seems pretty useful.
>> Maybe in FRP frameworks?
>>
>> Thanks a lot!!
>> Corentin
>> PS: I copied this example also in
>> https://github.com/cdupont/Nomyx-design/blob/master/ComposableEvents.hs.
>>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140516/ad7a4f33/attachment.html>


More information about the Haskell-Cafe mailing list