[Haskell-cafe] Re: FRP for game programming / artifical life simulation

Edward Kmett ekmett at gmail.com
Mon May 3 10:35:07 EDT 2010


On Sun, May 2, 2010 at 6:23 PM, Ben <midfield at gmail.com> wrote:

> hello --
>
> i'm putting the finishing touches on a cabal package based on what
> felipe gave, i've managed to make it an arrow transformer which is
> nice.  i have a few issues though.
>
> 1) i know it is not possible to add class constraints on an
> existential type when declaring instances, but how do you get around
> that?  for example, given the data type
>
> data Foo where
>    Foo :: (Binary s) => s -> Foo
>
> i would like to do something like
>
> instance Monoid s => Monoid Foo where
>    ....
>
> this obviously doesn't make sense as it stands ..... the real-life
> example is that i want to derive ArrowZero and ArrowPlus instances for
> arrows lifted to StreamStateT where the underlying arrow already has
> ArrowZero and ArrowPlus instances.  but to make sense of this i need
> to have a "zero" state element as well as a way to add state elements,
> e.g. a monoid instance on the state, which unfortunately is
> existential (as it stands.)
>

You'd need to make container data types, since you're obscuring what
information is held about the internal data type

data FooMonoid m where
    FooMonoid :: (Binary s, Monoid s) => s -> Foo

data FooNum m where
   FooNum :: (Binary s, Num s) => s -> Foo

This of course, probably plays hell with your level of desired abstraction.

2) is it possible to add class constraints on unnamed type parameters
> when declaring instances?
>

No, it isn't. There are hacks that get something like this, but they require
you to basically rebuild the class in a 'restricted' form. Check out
Ganesh's rmonad package on hackage for a general feel for the approach.

3) this is more of a style question, but how would you model a

> potentially infinite stream of data where the values are expensive to
> construct or are only sporadically available, in the arrow context?
> an example would be the stream of data from an experiment.
>
> my initial thought is to use the type [m a] for a monad m (as opposed
> to m [a].)  i can walk the list and evaluate the monadic actions
> on-demand -- i can write functions analogous to your "applyN" function
> that work monadically, and this works great with the StreamState
> arrows.
>

That seems like a reasonable starting point.


> applyMN :: Int -> StreamState a b -> [m a] -> m ([b], (StreamState a b, [m
> a]))
>
> but it is a little weird mixing this with lifted arrows -- what is the
> signature there?
>
> applyLN :: Int -> StreamStateT arr a b -> [m a] ..... ??
>

It shouldn't be appreciably different, perhaps just:

applyLN :: Arrow arr => Int  -> StreamStateT arr a b -> [m a] -> m ([b],
StreamStateT arr a b, [m a])

-Edward Kmett
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100503/916113a2/attachment.html


More information about the Haskell-Cafe mailing list