[Haskell-cafe] How to combine simulations

Alex Chapman alex at farfromthere.net
Tue Sep 1 04:25:59 UTC 2015


Hi Martin,

Here's a skeleton of one way you could do something like what you describe:

{-# LANGUAGE MultiParamTypeClasses #-}
module DES where

-- Typeclasses for sending and receiving events
class EventSender a e where
   send :: a -> e

class EventRecipient a e where
   receive :: a -> e -> a

-- Basic types: players and tables. These can be added to.
data Player = Player String
data Table = Table Int Player

-- Types of events: these can be added to.
data PlayerEvent = PlayerEvent Player
data OtherTableEvent = OtherTableEvent Table
data BallsAtRestEvent = BallsAtRestEvent

-- Players can send player events
instance EventSender Player PlayerEvent where
  send p = PlayerEvent p

-- Players can receive balls at rest events
instance EventRecipient Player BallsAtRestEvent where
  receive p _ = p -- TODO

-- Tables can receive player events
instance EventRecipient Table PlayerEvent where
  receive t _ = t -- TODO

-- Tables can send other table events
instance EventSender Table OtherTableEvent where
  send t = OtherTableEvent t

-- Tables can receive other table events
instance EventRecipient Table OtherTableEvent where
  receive t _ = t -- TODO

-- Now we combine two tables
data TableSystem = TableSystem (Table, Table)

-- The combined system only receives player events, and sends no events
instance EventRecipient TableSystem PlayerEvent where
  receive ts _ = ts -- TODO

Alex

On Tue, 1 Sep 2015 at 02:50 martin <martin.drautzburg at web.de> wrote:

> Hello all,
>
> I've been trying hard to come up with an idea how to build a DES from
> smaller parts. So far, I came to the conclusion,
> that somewhere there must be an operation which takes an Event and maybe
> emits an Event (and appends to a log and
> updates some state). Those Events whould come from and go to the
> "environment" the simulation runs in.
>
> My mental model is two billiard tables, which are connected through a hole
> in the cushion and which each have a player.
> When I look at one such table, it would have to respond to Events from its
> player and from the other table and it would
> send events to its player ("all balls at rest") and to the other table.
>
> If I add the other table and the two players then the combined simulation
> would not emit any events at all and it would
> not respond to any events except maybe as START event. It would only
> depend on its initial state.
>
> But if I add only the player, but not the other table, it would still send
> events to the other table and respond to
> events from that other table.
>
> My problem is the type of Events. I could create a type which encompasses
> all possible events, but that violates the
> idea of composablitly. Somehow I would need to be able to take a system
> which accepts "player events" and "other table
> events", compose it with an other table and end up with a system which
> only accepts "player events" but no more "other
> table events" and similarly for the emitted events. And I don't quite know
> how to do this.
>
> Hope this makes some sense.
>
> Any pointers (which go beyond "aivika has a simulation component") would
> also be much appreciated.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150901/f2281bbc/attachment.html>


More information about the Haskell-Cafe mailing list