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

Felipe Lessa felipe.lessa at gmail.com
Wed Apr 28 23:09:22 EDT 2010


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.


More information about the Haskell-Cafe mailing list