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

Ben midfield at gmail.com
Thu Apr 29 14:08:00 EDT 2010


Felipe --

Thanks!  I tried using existential types but didn't get far -- the
GADT syntax makes them much clearer, thanks.  In my defense this is my
first time working with a lot of these sexy type gadgets!

I think what you have written will work great for me.  In particular I
think I can write down computations for lagged time series nicely
using a lagging arrow which saves the window as it's state, and laying
the real computations on top of that.  So in particular you can
restart the computation without having to replay old data, it's nice.
I think I can also make an instance of ArrowCircuit.

A technical question: it seems like the instance of ArrowLoop is too
strict (this is something I've wondered about in Liu's paper too.)
Shouldn't it be

 instance ArrowLoop SFAuto where
     loop (SFAuto s f) = SFAuto s f'
         where
           f' (b, s1) = let (~(c, d), s2) = f ((b, d), s1)
                        in (c, s2)

or do I misunderstand lazy pattern matching?

Best, B

Date: Thu, 29 Apr 2010 00:09:22 -0300
From: Felipe Lessa <felipe.lessa at gmail.com>
Subject: Re: [Haskell-cafe] Re: FRP for game programming / artifical
       life    simulation
To: haskell-cafe at haskell.org
Message-ID: <20100429030922.GA7369 at kira.casa>
Content-Type: text/plain; charset=us-ascii

On Wed, Apr 28, 2010 at 04:16:08PM -0700, Ben wrote:
> so i tried state machines of a sort
>
> newtype STAuto s a b = STAuto { unSTAuto : (a, s) -> (b, s) }
>
> where the interruptibility would come from being able to save out the
> state s.  i was not successful, unfortunately, in this level of
> generality.  the fully-polymorphic state doesn't work, because one
> needs to be able to compose arrows, which means composing state, so
> like Hughes (see below) one needs some way of nesting states inside
> one another.  also, to implement delay in ArrowCircuit, one needs to
> be able to store in the state s something of type a.  this is a
> dependency i was not able to model right.

You may try encapsulating the state within an existential:

 {-# LANGUAGE GADTs #-}

 import Prelude hiding ((.), id)
 import Control.Category
 import Control.Arrow

 data SFAuto a b where
     SFAuto :: (Read s, Show s) => s -> ((a, s) -> (b, s)) -> SFAuto a b

 instance Category SFAuto where
     id = SFAuto () id
     (SFAuto s f) . (SFAuto r g) = SFAuto (s, r) h
         where h (x, (s, r)) = let (gx,  r') = g (x,  r)
                                   (fgx, s') = f (gx, s)
                               in (fgx, (s', r'))

 instance Arrow SFAuto where
     arr f = SFAuto () (\(x, _) -> (f x, ()))

     first (SFAuto s f) = SFAuto s f'
         where
           f' ((x, y), s1) = let (fx, s2) = f (x, s1)
                             in ((fx, y), s2)

 instance ArrowChoice SFAuto where
     left (SFAuto s f) = SFAuto s f'
         where
           f' (Right x, s1) = (Right x, s1)
           f' (Left x,  s1) = first Left $ f (x, s1)

 instance ArrowLoop SFAuto where
     loop (SFAuto s f) = SFAuto s f'
         where
           f' (b, s1) = let ((c, d), s2) = f ((b, d), s1)
                        in (c, s2)

Now, if you want to serialize an (SFAuto a b), you may if you
know where the original arrow is.  I mean, if you have

 something :: SFAuto a b
 something = ...

and you want to apply it to a huge list, you may

 A1) 'applyN k', where k is adjustable.

 A2) Save the results so far, the remaining input and the
     current state (which is Showable and Readable in my
     example, but could be an instance of Binary, for example).

 A3) Go to A1.

If anything bad happens, to recover:

 B1) Read results, input, and last state.

 B2) 'changeState something stateThatWasRead'

 B3) Go to A1.

Helper functions mentioned above:

 applyN :: Int -> SFAuto a b -> [a] -> ([b], (SFAuto a b, [a]))
 applyN 0 sf           xs     = ([], (sf, xs))
 applyN _ sf           []     = ([], (sf, []))
 applyN n (SFAuto s f) (x:xs) =
     let (fx, s') = f (x,s)
     in first (fx :) $ applyN (n-1) (SFAuto s' f) xs

 changeState :: SFAuto a b -> String -> SFAuto a b
 changeState (SFAuto _ f) str = SFAuto (read str) f

I don't have any idea if this is what you're looking for, but I
hope it helps :).

Cheers,

--
Felipe.



On Wed, Apr 28, 2010 at 9:58 PM, Peter Gammie <peteg42 at gmail.com> wrote:
> Ben,
>
> On 29/04/2010, at 6:16 AM, Ben wrote:
>
>> [...]
>>
>> newtype STAuto s a b = STAuto { unSTAuto : (a, s) -> (b, s) }
>
> As Felipe observes in detail, this can be made to work. He uses Read and Show for serialisation, but clearly you can use whatever you like instead.
>
> I just wanted to add that one can go to town with the approach: after you understand Felipe's stuff, take a look at Caspi and Pouzet's coalgebraic streams stuff. (I'd recommend looking at both the tech report and the published paper, and there is some Haskell code too.)
>
> BTW I was referring (off-list) to the original Arrows paper by John Hughes.
>
> cheers
> peter
>
> --
> http://peteg.org/
>
>


More information about the Haskell-Cafe mailing list