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

2010-05-03 Thread Edward Kmett
On Sun, May 2, 2010 at 6:23 PM, Ben  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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-05-03 Thread Heinrich Apfelmus
Peter Verswyvelen wrote:
> Actually, I believe that many Yampa examples do separate the drawing
> from the update... The arrow provides the game data that *can* be
> rendered. If you provide interpolators for that game data, you can
> still achieve the same as is explained in "fix your timesteps" (in my
> own FRP experiments I have an update thread and a render thread).

But the arrow implementation determines the  dt  at which the arrows ~
(Time -> a) -> (Time -> b)  are sampled, no? The end result of a Yampa
arrows is a graphic, after all.

> But IMHO "fix your timestep" still misses an important detail, in that
> the delta-time that is measured is the duration of the previous frame,
> and it assumed that the next frame will take as long as the previous
> (who says that "integrate" from the article won't take longer than
> dt?). Now say you are updating at 100 FPS = 10ms, but the next frame
> actually takes longer, say 20ms. That actually means that you should
> have passed 20ms as the delta-time of the this frame, because the real
> time is ahead now! This is really noticeable as little jerky frame
> hick-up in the motion. In my first game (1987), I added an estimator
> to compute how long the delta-time of the next frame would be, which
> results in much smoother motion: you notice that the
> frame-sampling-rate drops, but you don't see a frame hick-up. I rarely
> see this in modern games, most PC and even console games suffer from
> frame hick-up (which could be defined as the real-time moving ahead of
> the game-time for a brief moment)

I'm not sure I follow, could you elaborate on what exactly causes the
frame hick-up?

As far as I understand it, the approach of "fix your time-step" is that
you have a physics simulation and a rendering engine. To ensure
numerical stability, the physics are calculated with a fixed time step
dt  which can be larger than the rendering frame rate. In particular,
one step of physics simulation should take less than  dt  real time,
because otherwise you're screwed.

The graphics engine just draws as fast as possible. To ensure
smoothness, it interpolates slightly into the future. The FPS number
measures the frequency of drawn graphics, not the rate of physics
updates. There may be multiple physics steps per drawing when the latter
is slow, or the other way round, when the latter is fast.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-05-02 Thread Ben
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.)

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

for example, given the data type

data StreamState a b where
SS :: (Binary s) => s -> ((a,s) -> (b,s)) -> StreamState a b

with instances of Arrow, ArrowLoop, etc, i'd like to create the instance

instance ArrowCircuit StreamState where
delay a = (SS a f)
where f (x, s) = (s, x)

where the delay arrow saves the first element of the stream into the
state.  but this requires that the arrow has input (and output) which
is an instance of Binary.  i can't put that constraint in the instance
head as the input and output types are not mentioned.  i would prefer
not to add it as a constraint on the data type itself, as it would
restrict it's usefulness, and anyways it makes problems for the other
instances.  so i'm forced to create a shadow class

class ArrowLoop a => ArrowBinaryCircuit a where
delay :: (Binary b) => b -> a b b

and make an instance of that.

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.

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] . ??

perhaps it is not a good idea to mix monads and arrows in this way?

best regards, b

On Thu, Apr 29, 2010 at 11:08 AM, Ben  wrote:
> 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 
> Subject: Re: [Haskell-cafe] Re: FRP for game programming / artifical
>       life    simulation
> To: haskell-cafe@haskell.org
> Message-ID: <20100429030922.ga7...@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 

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

2010-04-30 Thread Ben
FYI i got the lazy pattern match from Patterson's "Programming with
Arrows," so I'm assuming it makes a difference.  (I'll work out a real
example later.)

B

On Fri, Apr 30, 2010 at 8:45 AM, Daniel Fischer
 wrote:
> Am Freitag 30 April 2010 17:23:19 schrieb Antoine Latter:
>> On Fri, Apr 30, 2010 at 3:37 AM, Daniel Fischer
>>
>>  wrote:
>> > Am Donnerstag 29 April 2010 20:08:00 schrieb Ben:
>> >> 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)
>> >
>> > Let-bindings are already lazy, so the '~' makes no difference here.
>> > Apart from the readability, both are the same as
>> >
>> > where
>> >  f' (b,s1) = let x = f ((b, snd $ fst x),s1) in (fst $ fst x, snd x)
>>
>> Ben's version is slightly lazier - even though the let binding is
>> lazy, pattern matching is strict.
>>
>> so (let ((x,y).z) = (undefined, "hello") in z) will exception out, but
>> (let (~(x,y),z) = (undefined, "hello") in z) will not.
>>
>> I don't know if you need that level of laziness, though.
>
> Probably not. Although, you're right, if only s2 is ever looked at and not
> c, Ben's version can give a result where the library instance throws an
> exception.
> Was fooled by the use of c in the result.
>
>>
>> Antoine
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-30 Thread Daniel Fischer
Am Freitag 30 April 2010 17:23:19 schrieb Antoine Latter:
> On Fri, Apr 30, 2010 at 3:37 AM, Daniel Fischer
>
>  wrote:
> > Am Donnerstag 29 April 2010 20:08:00 schrieb Ben:
> >> 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)
> >
> > Let-bindings are already lazy, so the '~' makes no difference here.
> > Apart from the readability, both are the same as
> >
> > where
> >  f' (b,s1) = let x = f ((b, snd $ fst x),s1) in (fst $ fst x, snd x)
>
> Ben's version is slightly lazier - even though the let binding is
> lazy, pattern matching is strict.
>
> so (let ((x,y).z) = (undefined, "hello") in z) will exception out, but
> (let (~(x,y),z) = (undefined, "hello") in z) will not.
>
> I don't know if you need that level of laziness, though.

Probably not. Although, you're right, if only s2 is ever looked at and not 
c, Ben's version can give a result where the library instance throws an 
exception.
Was fooled by the use of c in the result.

>
> Antoine

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-30 Thread Antoine Latter
On Fri, Apr 30, 2010 at 3:37 AM, Daniel Fischer
 wrote:
> Am Donnerstag 29 April 2010 20:08:00 schrieb Ben:
>> 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)
>
> Let-bindings are already lazy, so the '~' makes no difference here.
> Apart from the readability, both are the same as
>
> where
>  f' (b,s1) = let x = f ((b, snd $ fst x),s1) in (fst $ fst x, snd x)

Ben's version is slightly lazier - even though the let binding is
lazy, pattern matching is strict.

so (let ((x,y).z) = (undefined, "hello") in z) will exception out, but
(let (~(x,y),z) = (undefined, "hello") in z) will not.

I don't know if you need that level of laziness, though.

Antoine
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-29 Thread Christopher Lane Hinson


Basically, this is the "differential equation hairball" I mentioned earlier.  You can 
define a set of Operators -- a modification of Mealy automata that accepts two inputs -- and any 
mapping of inputs to outputs within the "Operation" monad.

The Operation monad uses an existentially quantified parameter for the same 
purpose as the 'ST' monad, to prevent the introduction of foreign values.

Within the 'Hairball' type, (Int,Int,Int,o) means (destination address, first 
source address, second source address, automaton).  I don't actually use the 
destination address because the list is built in indexable order anyway.

'alpha' and 'beta' correspond to the two inputs that every automaton receives.  
The Hairball is itself a valid automaton.

This is roughly the system I imagine people should be used when I keep saying, 
"don't use FRP to implement something that isn't I/O."  The whole thing is 
trivially readable, writable, recursive, and actually a stream processor.  On the 
downside you need to specify an entire interpreted DSL just to use it.

In the 'Numeric' example, 'alpha' is the variable and 'beta' is time.  Or it 
least it integrates alpha with respect to beta.

That's all the non-obvious stuff that comes to mind for the moment.

Friendly,
--Lane

On Thu, 29 Apr 2010, Ben wrote:


Lane --

Thanks for the suggestion, I'll take a closer look shortly.  At the
moment I have to confess to not exactly understanding what your code
is doing, it's a little "hairy" for me?  Right now I'm going to focus
on what Felipe has given me, it fits in nicely with the arrow
framework, which I'm excited about.

Thanks all for your help.  I'm sure I'll have more questions soon enough!

Best, B

On Thu, Apr 29, 2010 at 10:06 AM, Christopher Lane Hinson
 wrote:


On Wed, 28 Apr 2010, Ben wrote:


thanks for the comments, i'll try to respond to them all.  but to
start off with, let me mention that my ultimate goal is to have a way
of writing down causal and robust (restartable) computations which
happen on infinite streams of data "in a nice way" -- by which i mean
the declarative / whole-meal style ala Bird.  loosely, these are
functions [a] -> [b] on infinite lists; the causal constraint just
means that the output at time (index) t only depends on the inputs for
times (indices) <= t.

the catch is the robust bit.  by robust, i mean i need to be able to
suspend the computation, and restart it where it left off (the data
might be only sporadically or unreliably available, the computation
needs to be able to survive machine reboots.)  unfortunately the
obvious way (to me) of writing down such suspendible computations is
to use explicit state-machines, e.g. to reify function computation as
data, and save that.  this is unfortunately very piece-meal and
imperative.


Ben,

Do you want this?


{-# LANGUAGE TypeFamilies, Rank2Types, GeneralizedNewtypeDeriving #-}

module Hairball
(Operator(..),Hairball,Value,alpha,beta,Operation,apply,buildHairball) where

import Control.Monad
import Control.Monad.State

class Operator o where
   type Domain o :: *
   operation :: o -> Domain o -> Domain o -> (Domain o,o)

data Hairball o = Hairball {
   hair_unique_supply :: Int,
   hair_map :: [(Int,Int,Int,o)],
   hair_output :: Int }
   deriving (Read,Show)

data Value e = Value { address :: Int }

alpha :: Value e
alpha = Value 0

beta :: Value e
beta = Value 1

newtype Operation e o a = Operation { fromOperation :: State (Hairball o) a
} deriving (Monad,MonadFix)

apply :: o -> Value e -> Value e -> Operation e o (Value e)
apply op v1 v2 =
   do hair <- Operation get
  Operation $ put $ hair {
hair_unique_supply = succ $ hair_unique_supply hair,
hair_map = (hair_unique_supply hair,address v1,address
v2,op) : hair_map hair }
  return $ Value $ hair_unique_supply hair

buildHairball :: (forall e. Operation e o (Value e)) -> Hairball o
buildHairball o = hair { hair_output = address v, hair_map = reverse $
hair_map hair }
   where (v,hair) = runState (fromOperation o) (Hairball 2 [] $ error
"Hairball: impossible: output value undefined")

instance Operator o => Operator (Hairball o) where
   type Domain (Hairball o) = Domain o
   operation hair v1 v2 = (fst $ results !! hair_output hair, hair {
hair_map = drop 2 $ map snd results })
   where results = (v1,undefined):(v2,undefined):flip map (hair_map
hair) (\(i,s1,s2,o) ->
   let (r,o') = operation o (fst $ results !! s1)
(fst $ results !! s2)
   in (r,(i,s1,s2,o')))





{-# LANGUAGE TypeFamilies, DoRec #-}

module Numeric () where

import Prelude hiding (subtract)
import Hairball

data Numeric n = Add | Subtract | Multiply | Delay n deriving (Read,Show)

instance (Num n) => Operator (Numeric n) where
   type Domain (Numeric n) = n
   operation Add x y = (x+y,Add)
   operation Subtract x y = (x-y,Subtract)
   operation Multiply x y = (x*y,Multiply)
   operation (Delay x) x' _ = (x,Delay x')


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

2010-04-29 Thread Ben
Ah, thanks!

b

On Thu, Apr 29, 2010 at 11:37 AM, Daniel Fischer
 wrote:
> Am Donnerstag 29 April 2010 20:08:00 schrieb Ben:
>> 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)
>
> Let-bindings are already lazy, so the '~' makes no difference here.
> Apart from the readability, both are the same as
>
> where
>  f' (b,s1) = let x = f ((b, snd $ fst x),s1) in (fst $ fst x, snd x)
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-29 Thread Daniel Fischer
Am Donnerstag 29 April 2010 20:08:00 schrieb Ben:
> 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)

Let-bindings are already lazy, so the '~' makes no difference here.
Apart from the readability, both are the same as

where
  f' (b,s1) = let x = f ((b, snd $ fst x),s1) in (fst $ fst x, snd x)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-29 Thread Ben
Lane --

Thanks for the suggestion, I'll take a closer look shortly.  At the
moment I have to confess to not exactly understanding what your code
is doing, it's a little "hairy" for me?  Right now I'm going to focus
on what Felipe has given me, it fits in nicely with the arrow
framework, which I'm excited about.

Thanks all for your help.  I'm sure I'll have more questions soon enough!

Best, B

On Thu, Apr 29, 2010 at 10:06 AM, Christopher Lane Hinson
 wrote:
>
> On Wed, 28 Apr 2010, Ben wrote:
>
>> thanks for the comments, i'll try to respond to them all.  but to
>> start off with, let me mention that my ultimate goal is to have a way
>> of writing down causal and robust (restartable) computations which
>> happen on infinite streams of data "in a nice way" -- by which i mean
>> the declarative / whole-meal style ala Bird.  loosely, these are
>> functions [a] -> [b] on infinite lists; the causal constraint just
>> means that the output at time (index) t only depends on the inputs for
>> times (indices) <= t.
>>
>> the catch is the robust bit.  by robust, i mean i need to be able to
>> suspend the computation, and restart it where it left off (the data
>> might be only sporadically or unreliably available, the computation
>> needs to be able to survive machine reboots.)  unfortunately the
>> obvious way (to me) of writing down such suspendible computations is
>> to use explicit state-machines, e.g. to reify function computation as
>> data, and save that.  this is unfortunately very piece-meal and
>> imperative.
>
> Ben,
>
> Do you want this?
>
>
> {-# LANGUAGE TypeFamilies, Rank2Types, GeneralizedNewtypeDeriving #-}
>
> module Hairball
> (Operator(..),Hairball,Value,alpha,beta,Operation,apply,buildHairball) where
>
> import Control.Monad
> import Control.Monad.State
>
> class Operator o where
>    type Domain o :: *
>    operation :: o -> Domain o -> Domain o -> (Domain o,o)
>
> data Hairball o = Hairball {
>    hair_unique_supply :: Int,
>    hair_map :: [(Int,Int,Int,o)],
>    hair_output :: Int }
>        deriving (Read,Show)
>
> data Value e = Value { address :: Int }
>
> alpha :: Value e
> alpha = Value 0
>
> beta :: Value e
> beta = Value 1
>
> newtype Operation e o a = Operation { fromOperation :: State (Hairball o) a
> } deriving (Monad,MonadFix)
>
> apply :: o -> Value e -> Value e -> Operation e o (Value e)
> apply op v1 v2 =
>    do hair <- Operation get
>       Operation $ put $ hair {
>                 hair_unique_supply = succ $ hair_unique_supply hair,
>                 hair_map = (hair_unique_supply hair,address v1,address
> v2,op) : hair_map hair }
>       return $ Value $ hair_unique_supply hair
>
> buildHairball :: (forall e. Operation e o (Value e)) -> Hairball o
> buildHairball o = hair { hair_output = address v, hair_map = reverse $
> hair_map hair }
>    where (v,hair) = runState (fromOperation o) (Hairball 2 [] $ error
> "Hairball: impossible: output value undefined")
>
> instance Operator o => Operator (Hairball o) where
>    type Domain (Hairball o) = Domain o
>    operation hair v1 v2 = (fst $ results !! hair_output hair, hair {
> hair_map = drop 2 $ map snd results })
>        where results = (v1,undefined):(v2,undefined):flip map (hair_map
> hair) (\(i,s1,s2,o) ->
>                            let (r,o') = operation o (fst $ results !! s1)
> (fst $ results !! s2)
>                                in (r,(i,s1,s2,o')))
>
>
>
>
>
> {-# LANGUAGE TypeFamilies, DoRec #-}
>
> module Numeric () where
>
> import Prelude hiding (subtract)
> import Hairball
>
> data Numeric n = Add | Subtract | Multiply | Delay n deriving (Read,Show)
>
> instance (Num n) => Operator (Numeric n) where
>    type Domain (Numeric n) = n
>    operation Add x y = (x+y,Add)
>    operation Subtract x y = (x-y,Subtract)
>    operation Multiply x y = (x*y,Multiply)
>    operation (Delay x) x' _ = (x,Delay x')
>
> type NumericOperation e n = Operation e (Numeric n)
> type NumericHairball n = Hairball (Numeric n)
>
> add :: Value e -> Value e -> NumericOperation e n (Value e)
> add v1 v2 = apply Add v1 v2
>
> subtract :: Value e -> Value e -> NumericOperation e n (Value e)
> subtract v1 v2 = apply Subtract v1 v2
>
> multiply :: Value e -> Value e -> NumericOperation e n (Value e)
> multiply v1 v2 = apply Multiply v1 v2
>
> delay :: n -> Value e -> NumericOperation e n (Value e)
> delay initial_value v1 = apply (Delay initial_value) v1 alpha
>
> integratorProgram :: String
> integratorProgram = show $ buildHairball $
>   do rec prev_beta <- delay 0 beta
>          d_beta <- subtract beta prev_beta
>          add_alpha <- multiply alpha d_beta
>          prev_sum <- delay 0 sum
>          sum <- add prev_sum add_alpha
>      return sum
>
> runNumericProgram :: (Read n,Show n,Num n) => String -> n -> n -> (n,String)
> runNumericProgram program value time = (result,show hairball')
>    where hairball :: (Read n) => NumericHairball n
>          hairball = read program
>          (result,hairball') = operation hairball value

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

2010-04-29 Thread Ben
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 
Subject: Re: [Haskell-cafe] Re: FRP for game programming / artifical
   lifesimulation
To: haskell-cafe@haskell.org
Message-ID: <20100429030922.ga7...@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  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 recommen

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

2010-04-29 Thread Ben
Peter --

Thanks for the pointers.  Have you seen

Uustalu T., Vene V. The Essence of Dataflow Programming

?

Can't say I understand it all but it is a compelling picture.  I do
like the notion of distributive laws between monads and comonads.

B

On Wed, Apr 28, 2010 at 9:58 PM, Peter Gammie  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/
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-29 Thread Christopher Lane Hinson


On Wed, 28 Apr 2010, Ben wrote:


thanks for the comments, i'll try to respond to them all.  but to
start off with, let me mention that my ultimate goal is to have a way
of writing down causal and robust (restartable) computations which
happen on infinite streams of data "in a nice way" -- by which i mean
the declarative / whole-meal style ala Bird.  loosely, these are
functions [a] -> [b] on infinite lists; the causal constraint just
means that the output at time (index) t only depends on the inputs for
times (indices) <= t.

the catch is the robust bit.  by robust, i mean i need to be able to
suspend the computation, and restart it where it left off (the data
might be only sporadically or unreliably available, the computation
needs to be able to survive machine reboots.)  unfortunately the
obvious way (to me) of writing down such suspendible computations is
to use explicit state-machines, e.g. to reify function computation as
data, and save that.  this is unfortunately very piece-meal and
imperative.


Ben,

Do you want this?


{-# LANGUAGE TypeFamilies, Rank2Types, GeneralizedNewtypeDeriving #-}

module Hairball 
(Operator(..),Hairball,Value,alpha,beta,Operation,apply,buildHairball) where

import Control.Monad
import Control.Monad.State

class Operator o where
type Domain o :: *
operation :: o -> Domain o -> Domain o -> (Domain o,o)

data Hairball o = Hairball {
hair_unique_supply :: Int,
hair_map :: [(Int,Int,Int,o)],
hair_output :: Int }
deriving (Read,Show)

data Value e = Value { address :: Int }

alpha :: Value e
alpha = Value 0

beta :: Value e
beta = Value 1

newtype Operation e o a = Operation { fromOperation :: State (Hairball o) a } 
deriving (Monad,MonadFix)

apply :: o -> Value e -> Value e -> Operation e o (Value e)
apply op v1 v2 =
do hair <- Operation get
   Operation $ put $ hair {
 hair_unique_supply = succ $ hair_unique_supply hair,
 hair_map = (hair_unique_supply hair,address v1,address v2,op) 
: hair_map hair }
   return $ Value $ hair_unique_supply hair

buildHairball :: (forall e. Operation e o (Value e)) -> Hairball o
buildHairball o = hair { hair_output = address v, hair_map = reverse $ hair_map 
hair }
where (v,hair) = runState (fromOperation o) (Hairball 2 [] $ error "Hairball: 
impossible: output value undefined")

instance Operator o => Operator (Hairball o) where
type Domain (Hairball o) = Domain o
operation hair v1 v2 = (fst $ results !! hair_output hair, hair { hair_map 
= drop 2 $ map snd results })
where results = (v1,undefined):(v2,undefined):flip map (hair_map hair) 
(\(i,s1,s2,o) ->
let (r,o') = operation o (fst $ results !! s1) (fst 
$ results !! s2)
in (r,(i,s1,s2,o')))





{-# LANGUAGE TypeFamilies, DoRec #-}

module Numeric () where

import Prelude hiding (subtract)
import Hairball

data Numeric n = Add | Subtract | Multiply | Delay n deriving (Read,Show)

instance (Num n) => Operator (Numeric n) where
type Domain (Numeric n) = n
operation Add x y = (x+y,Add)
operation Subtract x y = (x-y,Subtract)
operation Multiply x y = (x*y,Multiply)
operation (Delay x) x' _ = (x,Delay x')

type NumericOperation e n = Operation e (Numeric n)
type NumericHairball n = Hairball (Numeric n)

add :: Value e -> Value e -> NumericOperation e n (Value e)
add v1 v2 = apply Add v1 v2

subtract :: Value e -> Value e -> NumericOperation e n (Value e)
subtract v1 v2 = apply Subtract v1 v2

multiply :: Value e -> Value e -> NumericOperation e n (Value e)
multiply v1 v2 = apply Multiply v1 v2

delay :: n -> Value e -> NumericOperation e n (Value e)
delay initial_value v1 = apply (Delay initial_value) v1 alpha

integratorProgram :: String
integratorProgram = show $ buildHairball $
   do rec prev_beta <- delay 0 beta
  d_beta <- subtract beta prev_beta
  add_alpha <- multiply alpha d_beta
  prev_sum <- delay 0 sum
  sum <- add prev_sum add_alpha
  return sum

runNumericProgram :: (Read n,Show n,Num n) => String -> n -> n -> (n,String)
runNumericProgram program value time = (result,show hairball')
where hairball :: (Read n) => NumericHairball n
  hairball = read program
  (result,hairball') = operation hairball value time

numericStream :: (Read n,Show n,Num n) => [(n,n)] -> (n,String) -> (n,String)
numericStream [] (n,s) = (n,s)
numericStream ((a,t):ats) (_,s) = numericStream ats $ runNumericProgram s a t


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-29 Thread Heinrich Apfelmus
Chris Eidhof wrote:
> I agree. This would be an extremely useful feature, not only for game
> development, but also for web development. We often use continuations
> as a way to add state to the web, but this fails for two reasons:
> whenever the server restarts, or when we scale to multiple machines.

Note that for web development, you could also store a log of client
responses on the client side and replay that whenever a request is made
to get some kind of persistent session. This is only suited for
lightweight use cases, of course.

I've implemented a small demonstration as part of the "operational"
package, it's the  WebSessionState.lhs  on

  http://projects.haskell.org/operational/examples.html


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-28 Thread Peter Gammie
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/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-28 Thread Felipe Lessa
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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-28 Thread Ben
thanks for the comments, i'll try to respond to them all.  but to
start off with, let me mention that my ultimate goal is to have a way
of writing down causal and robust (restartable) computations which
happen on infinite streams of data "in a nice way" -- by which i mean
the declarative / whole-meal style ala Bird.  loosely, these are
functions [a] -> [b] on infinite lists; the causal constraint just
means that the output at time (index) t only depends on the inputs for
times (indices) <= t.

the catch is the robust bit.  by robust, i mean i need to be able to
suspend the computation, and restart it where it left off (the data
might be only sporadically or unreliably available, the computation
needs to be able to survive machine reboots.)  unfortunately the
obvious way (to me) of writing down such suspendible computations is
to use explicit state-machines, e.g. to reify function computation as
data, and save that.  this is unfortunately very piece-meal and
imperative.

so i tried to turn state-machine computations on streams into an
arrow.  as an exercise for myself i tried to implement instances of
ArrowChoice, ArrowLoop, and ArrowCircuit for other various versions of
"stream arrows."  i was successful with automatons / mealy machines

newtype Auto a b = Auto { unAuto : a -> (b, Auto a b) }

functions on infinite lists (Data.Stream)

newtype InfSF a b = ISF { unISF : Stream a -> Stream b }

and length-preserving functions on finite lists

newtype SF a b = SF { unSF : [a] -> [b] }

this was promising, if elementary (these are all well-known.)  but
none of these are particularly interruptible, at least in GHC -- i
can't save a mealy machine, and the list versions are not particularly
causal.  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.

perhaps i have entirely the wrong approach -- if anyone can think of a
way of writing such a robust program in a declarative style, i would
love to know it!  of interest are the coalgebraic / comonadic
approaches, and the CCA stuff of liu et al.

Peter G : i have looked at the original CGI Arrow, it's a nice paper.
i don't think i understand all the subtleties, but my impression is
that he has a less polymorphic state type, and i don't know if he
addressed ArrowCircuit.  also he was unable to get it to work,
entirely, at least in that paper -- there were some type issues iirc.

Chris H : in my state-machine setup, saving the "state" of pure
functions is not exactly necessary -- as stream arrows, pure functions
lift to stateless gadgets, e.g. lift = map.  on the other hand, if i
was able to save functions / closures, or whole state of the program,
it would certainly suffice (i could use mealy machines or the
continuation monad), but is probably more than i need.

Peter V, Chris E : the CGI Arrow paper that Peter G mentioned may be
of interest to you.

the rest of you haskellers -- sorry, this is like the tenth time i've
posed this question, in one form or another!  i keep on feeling like
i've made a little progress, but then

Best, Ben

On Wed, Apr 28, 2010 at 11:49 AM, Chris Eidhof  wrote:
> I agree. This would be an extremely useful feature, not only for game 
> development, but also for web development. We often use continuations as a 
> way to add state to the web, but this fails for two reasons: whenever the 
> server restarts, or when we scale to multiple machines.
>
> However, I think it is not easy to do this: traversing the heap should be 
> relatively simple, however: what if a function implementation changes?
>
> An interesting approach is taken by the Clean guys: they use dynamics, which 
> can store a function, a type representation and the heap to disk. See also 
> this old thread: 
> http://www.mail-archive.com/haskell-cafe@haskell.org/msg34054.html
>
> -chris
>
> On 28 apr 2010, at 19:50, Peter Verswyvelen wrote:
>
>> Interesting topic. I find it a bit annoying that Haskell doesn't
>> provide support to save functions. I understand this is problematic,
>> but it would be very nice if the Haskell runtime provided a way to
>> serialize (part of) the heap, making sure that pointers to compiled
>> functions get resolved correctly.
>>
>>
>>
>> On Wed, Apr 28, 2010 at 6:42 PM, Christopher Lane Hinson
>>  wrote:
>>>
>>> On Wed, 28 Apr 2010, Ben wrote:
>>>
 I want to save the state of the system to disk, I want to be able to
 play the game, pick a point to stop, freeze it and turn off the
 comp

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

2010-04-28 Thread Christopher Lane Hinson


I think y'all are talking past each other, a little bit.  There are two ways to 
serialize a function:

1) Serialize the bytecode for the function.
2) Serialize a persistant reference to a function that resides inside the 
executable.

Personally, I think that either strategy is dubious.  If you really need this, 
I would recommend building a DSL to support your specific needs.  When I was 
working in Java I trusted the default serializer about as far as I could 
physically throw it, and IIRC my associates at the time had the same instinct.

Functions in general can contain references to any data, including objects such 
as MVar's who's behavior is actually determined by unreachable entities.

There's no amount of type system magic that can hold off monsters like _|_ or 
things like lazy bytestrings that are finite but never intended to be fully 
resident in memory.  Or do we intend to serialize unevaluated thunks?

Friendly,
--Lane




On Wed, Apr 28, 2010 at 6:42 PM, Christopher Lane Hinson
 wrote:


On Wed, 28 Apr 2010, Ben wrote:


I want to save the state of the system to disk, I want to be able to
play the game, pick a point to stop, freeze it and turn off the
computer, and then come back later and resume.  Why is that unwise?
What are the alternatives?

B


On Tue, 27 Apr 2010, Ben wrote:


slightly off topic, but how does one handle pausing / saving /
restarting in the FRP framework, especially the arrowized version?


If we're about Arrow FRP, remember that the arrow typeclass includes a
function, 'arr', that admits any function as a parameter, and these are in
general impossible to serialize to disk. Since Arrow FRP ends up roughly in
a form of: FRP a b c = a b (c, FRP a b c), an Arrow instance is actually the
state of the system.  There are a few tactics that would get us around this
limitation, but they are rather severe.   You could render 'arr' useless in
several ways, or you could save all the input to a system and replay it.

But I would argue that even if you wanted to do this, "saving an FRP system"
is, to me, like "saving a system in the IO monad," (which, there are tactics
that would let you do this, too).  It's probablematic in part because the
FRP system probably has active hooks into the user interface, such as
windows and other widgits that it owns, and possibly other devices (such as
physical rocket engines).  Even if the FRP system is completely pure and can
be referenced by a single pointer, it is easily and rightfully aware of
specific details of the hardware it is embedded in.

So it seems to me that what we actually want, to do complex simulations with
persistance, is not an FRP system that interacts with the outside world, but
a "self-contained, self-interacting, differential equation hairball."  Such
a system would be very cool, but I think that the numerical algorithms
needed exceed what an FRP system should try to provide.

Friendly,
--Lane
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe





On Wed, 28 Apr 2010, Peter Verswyvelen wrote:


As a side note, it's interesting that C# doesn't allow serialization
of closures (anonymous delegates). The compiler-generated name
assigned to an anonymous delegate can be different after each
re-compilation. This is also really annoying in C#/.NET, since one
must explicitly add a named method if serialization is needed. So I
wander how Clean solves this. I mean, consider


data MyData = MD (Int->Int)

myFunc x = x+1
myState1 = MyData myFunc
myState2 = MyData (\x -> x+1)

I can imagine that serializing myState1 is not too difficult, since it
should be possible to lookup the name of the compiled function
"myFunc".

However, what about serializing myState2? The lambda function has no
name, and it is not obvious to me how to give it a name that is unique
enough to survive a couple of iterations of source code modifications.





On Wed, Apr 28, 2010 at 9:56 PM, Gregory Crosswhite
 wrote:


On Apr 28, 2010, at 3:41 PM, Limestra?l wrote:


I think the problem with function serialization is that unlike languages which 
run over a virtual machine, bytecode generated by GHC is platform-specific 
(just as compilated C or C++) and therefore can run directly on top of the 
system, which is far faster but less portable.


Is this true?  I thought that ghc has separate machine code and byte-code 
modes, and inferred that the latter was platform-independent.  Is the latter 
platform-specific because it is just a different way of organizing different 
ways of (unlinked) machine code, or because parts of the byte-code depend on 
things like the size of integers in the compilation machine that are 
platform-dependent?

Also, it is worth noting that Clean supports serialization of values including 
closures.  It's not entirely clear to me how they do this, but looks like some 
combination of seeing whether a referenced routine is already in the curre

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

2010-04-28 Thread Peter Verswyvelen
As a side note, it's interesting that C# doesn't allow serialization
of closures (anonymous delegates). The compiler-generated name
assigned to an anonymous delegate can be different after each
re-compilation. This is also really annoying in C#/.NET, since one
must explicitly add a named method if serialization is needed. So I
wander how Clean solves this. I mean, consider


data MyData = MD (Int->Int)

myFunc x = x+1
myState1 = MyData myFunc
myState2 = MyData (\x -> x+1)

I can imagine that serializing myState1 is not too difficult, since it
should be possible to lookup the name of the compiled function
"myFunc".

However, what about serializing myState2? The lambda function has no
name, and it is not obvious to me how to give it a name that is unique
enough to survive a couple of iterations of source code modifications.





On Wed, Apr 28, 2010 at 9:56 PM, Gregory Crosswhite
 wrote:
>
> On Apr 28, 2010, at 3:41 PM, Limestraël wrote:
>
>> I think the problem with function serialization is that unlike languages 
>> which run over a virtual machine, bytecode generated by GHC is 
>> platform-specific (just as compilated C or C++) and therefore can run 
>> directly on top of the system, which is far faster but less portable.
>
> Is this true?  I thought that ghc has separate machine code and byte-code 
> modes, and inferred that the latter was platform-independent.  Is the latter 
> platform-specific because it is just a different way of organizing different 
> ways of (unlinked) machine code, or because parts of the byte-code depend on 
> things like the size of integers in the compilation machine that are 
> platform-dependent?
>
> Also, it is worth noting that Clean supports serialization of values 
> including closures.  It's not entirely clear to me how they do this, but 
> looks like some combination of seeing whether a referenced routine is already 
> in the current executable, then seeing whether it is in a nearby library, and 
> then finally just-in-type compiling the serialized platform-independent 
> bytecode into native code.
>
> Cheers,
> Greg
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-28 Thread Gregory Crosswhite

On Apr 28, 2010, at 3:41 PM, Limestraël wrote:

> I think the problem with function serialization is that unlike languages 
> which run over a virtual machine, bytecode generated by GHC is 
> platform-specific (just as compilated C or C++) and therefore can run 
> directly on top of the system, which is far faster but less portable.

Is this true?  I thought that ghc has separate machine code and byte-code 
modes, and inferred that the latter was platform-independent.  Is the latter 
platform-specific because it is just a different way of organizing different 
ways of (unlinked) machine code, or because parts of the byte-code depend on 
things like the size of integers in the compilation machine that are 
platform-dependent?

Also, it is worth noting that Clean supports serialization of values including 
closures.  It's not entirely clear to me how they do this, but looks like some 
combination of seeing whether a referenced routine is already in the current 
executable, then seeing whether it is in a nearby library, and then finally 
just-in-type compiling the serialized platform-independent bytecode into native 
code.

Cheers,
Greg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-28 Thread Limestraël
I think the problem with function serialization is that unlike languages
which run over a virtual machine, bytecode generated by GHC is
platform-specific (just as compilated C or C++) and therefore can run
directly on top of the system, which is far faster but less portable.

It wouldn't make much sense if, when sending functions through network, the
receiver had to have the exact same system as the sender.

Back to FRP, now. I was wondering, Ben, which FRP framework you were using.
I'm trying to get into the whole FRP stuff, but I don't know which one is
better/simpler when you have almost no knowledge about the field.


2010/4/28 Chris Eidhof 

> I agree. This would be an extremely useful feature, not only for game
> development, but also for web development. We often use continuations as a
> way to add state to the web, but this fails for two reasons: whenever the
> server restarts, or when we scale to multiple machines.
>
> However, I think it is not easy to do this: traversing the heap should be
> relatively simple, however: what if a function implementation changes?
>
> An interesting approach is taken by the Clean guys: they use dynamics,
> which can store a function, a type representation and the heap to disk. See
> also this old thread:
> http://www.mail-archive.com/haskell-cafe@haskell.org/msg34054.html
>
> -chris
>
> On 28 apr 2010, at 19:50, Peter Verswyvelen wrote:
>
> > Interesting topic. I find it a bit annoying that Haskell doesn't
> > provide support to save functions. I understand this is problematic,
> > but it would be very nice if the Haskell runtime provided a way to
> > serialize (part of) the heap, making sure that pointers to compiled
> > functions get resolved correctly.
> >
> >
> >
> > On Wed, Apr 28, 2010 at 6:42 PM, Christopher Lane Hinson
> >  wrote:
> >>
> >> On Wed, 28 Apr 2010, Ben wrote:
> >>
> >>> I want to save the state of the system to disk, I want to be able to
> >>> play the game, pick a point to stop, freeze it and turn off the
> >>> computer, and then come back later and resume.  Why is that unwise?
> >>> What are the alternatives?
> >>>
> >>> B
> >>>
>  On Tue, 27 Apr 2010, Ben wrote:
> 
> > slightly off topic, but how does one handle pausing / saving /
> > restarting in the FRP framework, especially the arrowized version?
> >>
> >> If we're about Arrow FRP, remember that the arrow typeclass includes a
> >> function, 'arr', that admits any function as a parameter, and these are
> in
> >> general impossible to serialize to disk. Since Arrow FRP ends up roughly
> in
> >> a form of: FRP a b c = a b (c, FRP a b c), an Arrow instance is actually
> the
> >> state of the system.  There are a few tactics that would get us around
> this
> >> limitation, but they are rather severe.   You could render 'arr' useless
> in
> >> several ways, or you could save all the input to a system and replay it.
> >>
> >> But I would argue that even if you wanted to do this, "saving an FRP
> system"
> >> is, to me, like "saving a system in the IO monad," (which, there are
> tactics
> >> that would let you do this, too).  It's probablematic in part because
> the
> >> FRP system probably has active hooks into the user interface, such as
> >> windows and other widgits that it owns, and possibly other devices (such
> as
> >> physical rocket engines).  Even if the FRP system is completely pure and
> can
> >> be referenced by a single pointer, it is easily and rightfully aware of
> >> specific details of the hardware it is embedded in.
> >>
> >> So it seems to me that what we actually want, to do complex simulations
> with
> >> persistance, is not an FRP system that interacts with the outside world,
> but
> >> a "self-contained, self-interacting, differential equation hairball."
>  Such
> >> a system would be very cool, but I think that the numerical algorithms
> >> needed exceed what an FRP system should try to provide.
> >>
> >> Friendly,
> >> --Lane
> >> ___
> >> Haskell-Cafe mailing list
> >> Haskell-Cafe@haskell.org
> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
> >>
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-28 Thread Chris Eidhof
I agree. This would be an extremely useful feature, not only for game 
development, but also for web development. We often use continuations as a way 
to add state to the web, but this fails for two reasons: whenever the server 
restarts, or when we scale to multiple machines.

However, I think it is not easy to do this: traversing the heap should be 
relatively simple, however: what if a function implementation changes?

An interesting approach is taken by the Clean guys: they use dynamics, which 
can store a function, a type representation and the heap to disk. See also this 
old thread: http://www.mail-archive.com/haskell-cafe@haskell.org/msg34054.html

-chris

On 28 apr 2010, at 19:50, Peter Verswyvelen wrote:

> Interesting topic. I find it a bit annoying that Haskell doesn't
> provide support to save functions. I understand this is problematic,
> but it would be very nice if the Haskell runtime provided a way to
> serialize (part of) the heap, making sure that pointers to compiled
> functions get resolved correctly.
> 
> 
> 
> On Wed, Apr 28, 2010 at 6:42 PM, Christopher Lane Hinson
>  wrote:
>> 
>> On Wed, 28 Apr 2010, Ben wrote:
>> 
>>> I want to save the state of the system to disk, I want to be able to
>>> play the game, pick a point to stop, freeze it and turn off the
>>> computer, and then come back later and resume.  Why is that unwise?
>>> What are the alternatives?
>>> 
>>> B
>>> 
 On Tue, 27 Apr 2010, Ben wrote:
 
> slightly off topic, but how does one handle pausing / saving /
> restarting in the FRP framework, especially the arrowized version?
>> 
>> If we're about Arrow FRP, remember that the arrow typeclass includes a
>> function, 'arr', that admits any function as a parameter, and these are in
>> general impossible to serialize to disk. Since Arrow FRP ends up roughly in
>> a form of: FRP a b c = a b (c, FRP a b c), an Arrow instance is actually the
>> state of the system.  There are a few tactics that would get us around this
>> limitation, but they are rather severe.   You could render 'arr' useless in
>> several ways, or you could save all the input to a system and replay it.
>> 
>> But I would argue that even if you wanted to do this, "saving an FRP system"
>> is, to me, like "saving a system in the IO monad," (which, there are tactics
>> that would let you do this, too).  It's probablematic in part because the
>> FRP system probably has active hooks into the user interface, such as
>> windows and other widgits that it owns, and possibly other devices (such as
>> physical rocket engines).  Even if the FRP system is completely pure and can
>> be referenced by a single pointer, it is easily and rightfully aware of
>> specific details of the hardware it is embedded in.
>> 
>> So it seems to me that what we actually want, to do complex simulations with
>> persistance, is not an FRP system that interacts with the outside world, but
>> a "self-contained, self-interacting, differential equation hairball."  Such
>> a system would be very cool, but I think that the numerical algorithms
>> needed exceed what an FRP system should try to provide.
>> 
>> Friendly,
>> --Lane
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-28 Thread Peter Verswyvelen
Interesting topic. I find it a bit annoying that Haskell doesn't
provide support to save functions. I understand this is problematic,
but it would be very nice if the Haskell runtime provided a way to
serialize (part of) the heap, making sure that pointers to compiled
functions get resolved correctly.



On Wed, Apr 28, 2010 at 6:42 PM, Christopher Lane Hinson
 wrote:
>
> On Wed, 28 Apr 2010, Ben wrote:
>
>> I want to save the state of the system to disk, I want to be able to
>> play the game, pick a point to stop, freeze it and turn off the
>> computer, and then come back later and resume.  Why is that unwise?
>> What are the alternatives?
>>
>> B
>>
>>> On Tue, 27 Apr 2010, Ben wrote:
>>>
 slightly off topic, but how does one handle pausing / saving /
 restarting in the FRP framework, especially the arrowized version?
>
> If we're about Arrow FRP, remember that the arrow typeclass includes a
> function, 'arr', that admits any function as a parameter, and these are in
> general impossible to serialize to disk. Since Arrow FRP ends up roughly in
> a form of: FRP a b c = a b (c, FRP a b c), an Arrow instance is actually the
> state of the system.  There are a few tactics that would get us around this
> limitation, but they are rather severe.   You could render 'arr' useless in
> several ways, or you could save all the input to a system and replay it.
>
> But I would argue that even if you wanted to do this, "saving an FRP system"
> is, to me, like "saving a system in the IO monad," (which, there are tactics
> that would let you do this, too).  It's probablematic in part because the
> FRP system probably has active hooks into the user interface, such as
> windows and other widgits that it owns, and possibly other devices (such as
> physical rocket engines).  Even if the FRP system is completely pure and can
> be referenced by a single pointer, it is easily and rightfully aware of
> specific details of the hardware it is embedded in.
>
> So it seems to me that what we actually want, to do complex simulations with
> persistance, is not an FRP system that interacts with the outside world, but
> a "self-contained, self-interacting, differential equation hairball."  Such
> a system would be very cool, but I think that the numerical algorithms
> needed exceed what an FRP system should try to provide.
>
> Friendly,
> --Lane
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-28 Thread Christopher Lane Hinson


On Wed, 28 Apr 2010, Ben wrote:


I want to save the state of the system to disk, I want to be able to
play the game, pick a point to stop, freeze it and turn off the
computer, and then come back later and resume.  Why is that unwise?
What are the alternatives?

B


On Tue, 27 Apr 2010, Ben wrote:


slightly off topic, but how does one handle pausing / saving /
restarting in the FRP framework, especially the arrowized version?


If we're about Arrow FRP, remember that the arrow typeclass includes a 
function, 'arr', that admits any function as a parameter, and these are in 
general impossible to serialize to disk. Since Arrow FRP ends up roughly in a 
form of: FRP a b c = a b (c, FRP a b c), an Arrow instance is actually the 
state of the system.  There are a few tactics that would get us around this 
limitation, but they are rather severe.   You could render 'arr' useless in 
several ways, or you could save all the input to a system and replay it.

But I would argue that even if you wanted to do this, "saving an FRP system" is, to me, 
like "saving a system in the IO monad," (which, there are tactics that would let you do 
this, too).  It's probablematic in part because the FRP system probably has active hooks into the 
user interface, such as windows and other widgits that it owns, and possibly other devices (such as 
physical rocket engines).  Even if the FRP system is completely pure and can be referenced by a 
single pointer, it is easily and rightfully aware of specific details of the hardware it is 
embedded in.

So it seems to me that what we actually want, to do complex simulations with persistance, 
is not an FRP system that interacts with the outside world, but a "self-contained, 
self-interacting, differential equation hairball."  Such a system would be very 
cool, but I think that the numerical algorithms needed exceed what an FRP system should 
try to provide.

Friendly,
--Lane
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-28 Thread Ben
I want to save the state of the system to disk, I want to be able to
play the game, pick a point to stop, freeze it and turn off the
computer, and then come back later and resume.  Why is that unwise?
What are the alternatives?

B

On Tue, Apr 27, 2010 at 9:28 PM, Christopher Lane Hinson
 wrote:
>
> I'm not sure exactly what you want to do.  It should certainly be easy to
> "freeze" an FRP program by lying about the amount of time that is passing
> and witholding all events.  Do you want to save an FRP system instance to
> disk (generally unwise), or something else (what?).
>
> Friendly,
> --Lane
>
> On Tue, 27 Apr 2010, Ben wrote:
>
>> slightly off topic, but how does one handle pausing / saving /
>> restarting in the FRP framework, especially the arrowized version?
>> i've only been able to do this via explicit (or monadic)
>> state-passing, e.g. imperative / piecemeal versus declarative /
>> wholemeal, which seems against the spirit of FRP.
>>
>> b
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-27 Thread Christopher Lane Hinson


I'm not sure exactly what you want to do.  It should certainly be easy to 
"freeze" an FRP program by lying about the amount of time that is passing and 
witholding all events.  Do you want to save an FRP system instance to disk (generally 
unwise), or something else (what?).

Friendly,
--Lane

On Tue, 27 Apr 2010, Ben wrote:


slightly off topic, but how does one handle pausing / saving /
restarting in the FRP framework, especially the arrowized version?
i've only been able to do this via explicit (or monadic)
state-passing, e.g. imperative / piecemeal versus declarative /
wholemeal, which seems against the spirit of FRP.

b
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-27 Thread Ben
slightly off topic, but how does one handle pausing / saving /
restarting in the FRP framework, especially the arrowized version?
i've only been able to do this via explicit (or monadic)
state-passing, e.g. imperative / piecemeal versus declarative /
wholemeal, which seems against the spirit of FRP.

b
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-26 Thread Peter Verswyvelen
2010/4/25 Patai Gergely :
>> (in my own FRP experiments I have an update thread and a render thread).
> I wonder how to nicely deal with state that requires communication with
> the outer world, even though it is functional at heart. For instance, if
> you want to change a vertex buffer or a texture or whatever during the
> update, how do you organise your code? Do you maintain separate pure and
> impure state information blocks?

I don't have a vertex buffers or texture in my update loop. These are
low level details, left to the render loop. Indeed I maintained a pure
information block in the update. If you really wanted to have
low-level access in the update loop, I wouldn't know how to do that,
although keeping two copies could work. Now my experiments were really
simple 2D games, so not really state of the art.

> Deciding between push and pull according to profiling results is a nice
> idea. :) It might be too expensive to do it adaptively during runtime
> (the overhead might easily distort the results and thus render them
> invalid), but treating it as just a flag could give us an interesting
> architecture to play with.

Yes, I see it more in the line of "profile based optimization", where
a compiler performs static optimization based on a previous profile.

I kind of abandoned the FRP thing because Haskell just feels a bit too
complicated/abstract for me. It might also be that for the average
person to learn Haskell really well, one needs a mentor. I would love
to follow courses about it actually :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-25 Thread Patai Gergely
> (in my own FRP experiments I have an update thread and a render thread).
I wonder how to nicely deal with state that requires communication with
the outer world, even though it is functional at heart. For instance, if
you want to change a vertex buffer or a texture or whatever during the
update, how do you organise your code? Do you maintain separate pure and
impure state information blocks?

> However, it is not clear if you want to "pull" or "push" such a network
>From what I've seen so far, I think you really need both at the same
time. Pull for continuous signals and push for events. The tricky part
is that events can be derived from signals (cf. Fran's predicate
events), and you really don't want the signals depending on these events
to be reevaluated even when there are no occurrences. The best you can
do with pull is to explicitly keep the previous output when there's no
incoming event. However, if you fmap over this output, the function will
be evaluated in every step regardless of the lack of change, since
functions are not memoised. I believe this is a problem Grapefruit aims
to solve with its notion of segmented signals [1].

Deciding between push and pull according to profiling results is a nice
idea. :) It might be too expensive to do it adaptively during runtime
(the overhead might easily distort the results and thus render them
invalid), but treating it as just a flag could give us an interesting
architecture to play with.

Gergely

[1]
http://hackage.haskell.org/packages/archive/grapefruit-frp/0.0.0.0/doc/html/FRP-Grapefruit-Signal-Segmented.html

-- 
http://www.fastmail.fm - A fast, anti-spam email service.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-25 Thread Peter Verswyvelen
Actually, I believe that many Yampa examples do separate the drawing
from the update... The arrow provides the game data that *can* be
rendered. If you provide interpolators for that game data, you can
still achieve the same as is explained in "fix your timesteps" (in my
own FRP experiments I have an update thread and a render thread).

But IMHO "fix your timestep" still misses an important detail, in that
the delta-time that is measured is the duration of the previous frame,
and it assumed that the next frame will take as long as the previous
(who says that "integrate" from the article won't take longer than
dt?). Now say you are updating at 100 FPS = 10ms, but the next frame
actually takes longer, say 20ms. That actually means that you should
have passed 20ms as the delta-time of the this frame, because the real
time is ahead now! This is really noticeable as little jerky frame
hick-up in the motion. In my first game (1987), I added an estimator
to compute how long the delta-time of the next frame would be, which
results in much smoother motion: you notice that the
frame-sampling-rate drops, but you don't see a frame hick-up. I rarely
see this in modern games, most PC and even console games suffer from
frame hick-up (which could be defined as the real-time moving ahead of
the game-time for a brief moment)

Regarding FRP, I like to look at this as a kind of a data flow system
(a network of "signal transformers", or just "nodes"). However, it is
not clear if you want to "pull" or "push" such a network: if side
effects are not present, there should be no difference in the "game
state" if you push or pull it, but one can be far more optimal than
the other. Of example, nodes connected to an analog joystick would
most likely benefit from a pull approach, since the joystick always
moves a little. But nodes connected to a timer that changes once each
second clearly should benefit from a push approach. Although sometimes
a static "change frequency" could help to determine wether to push or
pull, I believe this can only be determined with profiling. So in a
sense, push or pull should  be some kind of attribute...

Okay, a bit off topic :)


On Sun, Apr 25, 2010 at 5:09 PM, Christopher Lane Hinson
 wrote:
>
>> 1) In FRP, there is no global *type*  GameState  that stores the whole
>> game state. Rather, the game state is implicit in the collection of
>> "active" computations. This is also why state updating and drawing is
>> woven together in FRP, which is good syntactically, but hard to
>> disentangle for interpolation.
>
> I disagree somewhat with this.  FRP should be thought of like the IO monad,
> out of which everything that can be lifted, should be, especially the
> GameState.
>
> I like to imagine that the FRP's job is to observe the GameState and reenact
> changes therein.  Some changes take a little while to act out, and the FRP
> element that is doing the action can signal that it isn't ready for the next
> transition.  Or, if no changes occur, the actors can stand around doing idle
> animations.
>
> Friendly,
> --Lane
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-25 Thread Christopher Lane Hinson



1) In FRP, there is no global *type*  GameState  that stores the whole
game state. Rather, the game state is implicit in the collection of
"active" computations. This is also why state updating and drawing is
woven together in FRP, which is good syntactically, but hard to
disentangle for interpolation.


I disagree somewhat with this.  FRP should be thought of like the IO 
monad, out of which everything that can be lifted, should be, especially 
the GameState.


I like to imagine that the FRP's job is to observe the GameState and 
reenact changes therein.  Some changes take a little while to act out, and 
the FRP element that is doing the action can signal that it isn't ready 
for the next transition.  Or, if no changes occur, the actors can stand 
around doing idle animations.


Friendly,
--Lane
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-25 Thread Heinrich Apfelmus
Luke Palmer wrote:
> 
> The workhorse of our game has so far been "generalized differentials".
>  While not entirely rigorous, they have provided a very nice framework
> in which to express our thoughts and designs, and are very good at
> "highly dynamic" situations which appear in games.  For example, with
> arrows it is painful to maintain a list of moving actors such that can
> be added and removed.  With differentials this is quite natural.

Interesting! I've experimented with writing a game in Haskell recently,
albeit in a rather traditional imperative style, and I have a few
thoughts on what your style does and does not accomplish.


> A differential is implemented as a function that takes a timestep and
> returns an update function.  Don't expose the D constructor; step is
> okay to expose, it's kind of a generalized "linear approximation".
> 
>> newtype D a = D { step :: Double -> a -> a }
> 
>> instance Monoid (D a) where
>> mempty = D (const id)
>> mappend da db = D (\dt -> step da dt . step db dt)
> 
> Given a differential for a component of a value, we can construct a
> differential for that value.
> 
>> accessor :: Acc.T s a -> D a -> D s
>> accessor acc da = D (Acc.modify acc . step da)
>>
>> product :: D a -> D b -> D (a, b)
>> product da db = D (\dt (x,y) -> (step da dt x, step db dt y))
>>
>> comonad :: (Comonad w) => (w a -> D a) -> D (w a)
>> comonad f = D (\dt -> let h w = step (f w) dt (extract w) in extend h)


I appears to me that your differentials are "just" functional references
/ state updates (a -> a) , the interesting conceptual interpretation
notwithstanding. The telltale sign is that your main logic is given by
dGameState , which is, in essence, just a function that updates the
global game state:

>> dGameState :: Input -> D GameState
>> dGameState = ... -- built out of simpler Ds of its components

On one hand, this is disappointing because it's all too close to the
imperative style, but on the other hand, the idea of treating state
changes as *first class values* gives rise to powerful combinators like
 comonad  and clearly exceeds what imperative languages usually offer.
In a sense, it is quite ironic that imperative languages don't abstract
over what they are best at doing, namely updating state.


The interpretation as differentials is, unfortunately, not fundamental.
The only part where it would come to fruition, namely the definition of
continuous functions

> The arrow we are using is implemented in terms of differentials:
>
>> data Continuous a b = forall s. Continuous s (s -> a -> (b, D s))
>
>> mainGame = proc input -> do
>> gameState <- integral initialGameState -< dGameState input
>> returnA -< drawGameState gameState

only appears as "driver code" at the very end and does not have any
impact; you can just as well implement your game loop in the traditional
imperative fashion:

   mainGame = loop initialGameState
   where
   loop s = do
   i  <- getInput
   s' <- dGameState i dt s
   drawGameState s'
   loop s'

In fact, it is preferable to do so because physics simulations usually
require a fixed time step  dt  which is slightly tricky to synchronize
to the clock on the wall, see also

   Glenn Fiedler. Fix your timestep!
   http://gafferongames.com/game-physics/fix-your-timestep/

Arrows don't help with that, in fact, it is difficult to do this with
arrow style FRP! That's because FRP tends to mingle game state updates
and drawing, but you have to separate them if you want decent interpolation.

Thus, it is no accident that your main loop factorizes into updating and
drawing, and that the arrows pretty much disappear from your code, Luke.



So, in my opinion, this style is a traditional imperative approach,
though with a proper and powerful abstraction for state updates.

But since we're also on a quest to find the "functional game programming
nirvana", can we do better? I have no answer, but for starters, I think
I can explicitly describe two qualities that FRP has and that are not
available in Luke's approach:

1) In FRP, there is no global *type*  GameState  that stores the whole
game state. Rather, the game state is implicit in the collection of
"active" computations. This is also why state updating and drawing is
woven together in FRP, which is good syntactically, but hard to
disentangle for interpolation.

2) In FRP, all dependencies that may influence the evolution of a value
in time are made explicit in its definition. In contrast, a state update
can change *any* value later on; the only "protection" against unwanted
change are the combinators. For instance,

product :: D a -> D b -> D (a,b)

guarantees that the  D b  argument cannot change the  a  component of
the pair  (a,b) .

Maybe the "nirvana" is closer if we could somehow incorporate one of these.

Note that these are purely "syntactic" qualities. In fact, I am
convinced that it's not a good idea to focus on the semantics of FRP,
the ke