Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  FRP and a set of pairwise interacting    (colliding) objects
      (Nathan H?sken)
   2. Re:  FRP and a set of pairwise interacting        (colliding)
      objects (Ertugrul S?ylemez)
   3. Re:  test-framework (Michael Orlitzky)
   4. Re:  Help with Why Do Monads Matter blog post understanding
      (Brent Yorgey)
   5. Re:  Help with Why Do Monads Matter blog post     understanding
      (Matt Ford)
   6. Re:  test-framework (Mateusz Neumann)
   7. Re:  Help with Why Do Monads Matter blog post     understanding
      (Paulo Pocinho)
   8. Re:  FRP and a set of pairwise interacting (colliding)
      objects (Nathan H?sken)


----------------------------------------------------------------------

Message: 1
Date: Fri, 29 Jun 2012 14:07:13 +0200
From: Nathan H?sken <nathan.hues...@posteo.de>
Subject: [Haskell-beginners] FRP and a set of pairwise interacting
        (colliding) objects
To: beginners@haskell.org
Message-ID: <4fed9a71.2070...@posteo.de>
Content-Type: text/plain; charset=ISO-8859-1

Hi,

I want to simulate as set of 2D objects, which can collide pairs wise
with each other.
In an OOP language, I would do this:

  for (o1 in objects) {
    for (o2 in objets) {
      if (testCollision(o1, o2)) {
        CollData cd = getCollisionData(o1,o2);
        o1.reactToCollision(cd);
        o2.reactToCollision(cd):
      }
    }
  }

Now I want to do the same thing in Haskell with FRP.
Normally in FRP (correct me if I am wrong) I have for my objects a
Signal (or whatever it is called in the specific library), which gets as
input the collision events for this object (and probably more data, but
let's assume collision events are enough):

  object :: Signal (Event CollData) ObjectState

The CollData events themself are generated at another place:

  collisions :: Signal [ObjectState] (Event CollData)

But now the collisions are generated at one place, and processed at
another. This means that CollData must be somehow tagged to the objects
it belongs to (an ID for example). This again means that some function
must take the pool of all collision datas and distribute them to the
"object" Signals.

When I have a lot of objects, this means a significant overhead!

Now I am wondering if there is a nicer approach which avoids this overhead.

Thanks!
Nathan



------------------------------

Message: 2
Date: Fri, 29 Jun 2012 16:47:44 +0200
From: Ertugrul S?ylemez <e...@ertes.de>
Subject: Re: [Haskell-beginners] FRP and a set of pairwise interacting
        (colliding) objects
To: beginners@haskell.org
Message-ID: <20120629164744.0c5cf...@angst.streitmacht.eu>
Content-Type: text/plain; charset="utf-8"

Nathan H?sken <nathan.hues...@posteo.de> wrote:

> [...]
>
> But now the collisions are generated at one place, and processed at
> another. This means that CollData must be somehow tagged to the
> objects it belongs to (an ID for example). This again means that some
> function must take the pool of all collision datas and distribute them
> to the "object" Signals.
>
> When I have a lot of objects, this means a significant overhead!
>
> Now I am wondering if there is a nicer approach which avoids this
> overhead.

You can get around the overhead by letting the objects do the collisions
themselves, much like in your OOP variant.  For instance in Netwire you
could have this:

    planets :: MyWire [Planet] Planet

This naive way still causes the overhead of lists and a planet
distinguishing between others and itself.  But now this is simply a
matter of choosing proper data structures and starting to identify
planets:

    type PlanetSet = Map PlanetId Planet

    planets :: MyWire PlanetSet (PlanetId, Planet)

This looks more promising.  Now the last thing is that this looks like a
chicken/egg problem, but it's easy to resolve using ArrowLoop and
one-instant delays.


Greets,
Ertugrul

-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120629/af3e6653/attachment-0001.pgp>

------------------------------

Message: 3
Date: Fri, 29 Jun 2012 11:50:13 -0400
From: Michael Orlitzky <mich...@orlitzky.com>
Subject: Re: [Haskell-beginners] test-framework
To: beginners@haskell.org
Message-ID: <4fedceb5.2010...@orlitzky.com>
Content-Type: text/plain; charset=UTF-8

On 06/29/12 03:58, Mateusz Neumann wrote:
> On Fri, 29 Jun 2012 08:43:33 +0100
> Lorenzo Bolla <lbo...@gmail.com> wrote:
> 
>> Are the examples in the package distribution of any help?
>> https://github.com/batterseapower/test-framework/blob/master/example/Test/Framework/Example.lhs
>>
>> L.
> 
> I was thinking more about parametres set in Haskell code itself.  There
> is something like TestOptions
> (http://hackage.haskell.org/packages/archive/test-framework/0.6/doc/html/Test-Framework-Options.html#t:TestOptions)
> and RunnerOptions
> (http://hackage.haskell.org/packages/archive/test-framework/0.6/doc/html/Test-Framework-Runners-Options.html)
> but I do not find any examples of using them.  Similarly, I do not know
> how to set them up.
> 

Here's an example main function that also uses test-framework-doctest.

There's only one trick used: because TestOptions/RunnerOptions are
instances of monoid, we can use "mempty" to get an empty set of options.
This is a little more fun than creating an empty record by hand.


main :: IO ()
main = do
  dt <- docTest ["src/Everything.hs"] ["-isrc"]

  let empty_test_opts = mempty :: TestOptions
  let my_test_opts = empty_test_opts {
    topt_maximum_generated_tests = Just 500
  }

  let empty_runner_opts = mempty :: RunnerOptions
  let my_runner_opts = empty_runner_opts {
    ropt_test_options = Just my_test_opts
  }

  defaultMainWithOpts ([dt] ++ tests) my_runner_opts



------------------------------

Message: 4
Date: Fri, 29 Jun 2012 14:52:38 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Help with Why Do Monads Matter blog
        post understanding
To: beginners@haskell.org
Message-ID: <20120629185238.ga16...@seas.upenn.edu>
Content-Type: text/plain; charset=utf-8

On Fri, Jun 29, 2012 at 09:57:42AM +0100, Matt Ford wrote:
> Hi,
> 
> I've been reading the following blog post
> 
> https://cdsmith.wordpress.com/2012/04/18/why-do-monads-matter/
> 
> And I think I like it.  But there's a part that I don't get.
> 
> "For a set A, we will define the set Pref(A) to be the set of functions
> from application settings to the set A. Now watch closely: a function in
> context from A to B is just an ordinary function from A to Pref(B). In
> other words, you give it a value from the set A, and it gives you back
> another function that maps from application settings to the set B."
> 
> This is in the "functioning with dependency" section and is talking about a
> procedure that uses outside info from preferences or application settings.
> 
> If I set my prefs as follows
> 
> configvar = 3
> 
> and define a function as follows
> 
> add x = configvar + 6
> 
> So add?s signature is
> 
> add: int -> int
> 
> What does prefs(int) look like? Is that even the right thing to ask?

prefs(int) looks like  Config -> Int (in your example perhaps we
define  type Config = Int), so add should have type

  Int -> (Config -> Int)

The thing that is confusing the issue here is that you just made add
implicitly use the 'configvar' which is in scope, so it does not need
to take it as a parameter.  But imagine that you want to be able to
do multiple runs with different configurations, without recompiling
your program -- then you will need to have any function that needs the
configuation take it as an input.  Like this:

  add x config = config + 6

> By substituting the B for Prefs(B) and returning now only functions from
> Pref(B) don't we lose the rest of the mapping for add i.e., " + 6"?

I don't think I understand this question.

-Brent



------------------------------

Message: 5
Date: Fri, 29 Jun 2012 21:30:58 +0100
From: Matt Ford <m...@dancingfrog.co.uk>
Subject: Re: [Haskell-beginners] Help with Why Do Monads Matter blog
        post    understanding
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID:
        <CA+FwTn8-32rYZh++aL5jc7aFbzmjWoOYR=3r7f5lyrtbxmd...@mail.gmail.com>
Content-Type: text/plain; charset=windows-1252

On 29 June 2012 19:52, Brent Yorgey <byor...@seas.upenn.edu> wrote:

>> "For a set A, we will define the set Pref(A) to be the set of functions
>> from application settings to the set A. Now watch closely: a function in
>> context from A to B is just an ordinary function from A to Pref(B). In
>> other words, you give it a value from the set A, and it gives you back
>> another function that maps from application settings to the set B."
>>
>> This is in the "functioning with dependency" section and is talking about a
>> procedure that uses outside info from preferences or application settings.
>>
>> If I set my prefs as follows
>>
>> configvar = 3
>>
>> and define a function as follows
>>
>> add x = configvar + 6
>>
>> So add?s signature is
>>
>> add: int -> int
>>
>> What does prefs(int) look like? Is that even the right thing to ask?
>
> prefs(int) looks like ?Config -> Int (in your example perhaps we
> define ?type Config = Int), so add should have type
>
> ?Int -> (Config -> Int)
>
> The thing that is confusing the issue here is that you just made add
> implicitly use the 'configvar' which is in scope, so it does not need
> to take it as a parameter.

That's what I'm trying to understand, how we switch from "impure"
functions to "pure" functions which don't rely on external state.

And I see that passing in functions that act on the state helps do
this.  But I don't understand how, for a function that looks like
A->B, that has a whole load dependencies on external variables and
functions (of perhaps lot's of different types) all these variables
and functions are captured by the definition of Pref(B).

And by changing the actual type of the result of A->B in this case
from an Int to a function that returns an Int how can this hope to
match the original intention of the impure A->B.  Say for example
Pref(b) is the empty set as no functions map to from the config to B.
Changing the range means we will never get a sensible result??

I feel as though I'm missing something.

Cheers.

>?But imagine that you want to be able to
> do multiple runs with different configurations, without recompiling
> your program -- then you will need to have any function that needs the
> configuation take it as an input. ?Like this:
>
> ?add x config = config + 6
>
>> By substituting the B for Prefs(B) and returning now only functions from
>> Pref(B) don't we lose the rest of the mapping for add i.e., " + 6"?
>
> I don't think I understand this question.
>
> -Brent
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



------------------------------

Message: 6
Date: Fri, 29 Jun 2012 23:34:33 +0200
From: Mateusz Neumann <mate...@neumanny.net>
Subject: Re: [Haskell-beginners] test-framework
To: Michael Orlitzky <mich...@orlitzky.com>
Cc: beginners@haskell.org
Message-ID: <20120629233433.31475833@dragonfly.localdomain>
Content-Type: text/plain; charset="us-ascii"

On Fri, 29 Jun 2012 11:50:13 -0400
Michael Orlitzky <mich...@orlitzky.com> wrote:

> On 06/29/12 03:58, Mateusz Neumann wrote:
> > On Fri, 29 Jun 2012 08:43:33 +0100
> > Lorenzo Bolla <lbo...@gmail.com> wrote:
> > 
> >> Are the examples in the package distribution of any help?
> >> https://github.com/batterseapower/test-framework/blob/master/example/Test/Framework/Example.lhs
> >>
> >> L.
> > 
> > I was thinking more about parametres set in Haskell code itself.
> > There is something like TestOptions
> > (http://hackage.haskell.org/packages/archive/test-framework/0.6/doc/html/Test-Framework-Options.html#t:TestOptions)
> > and RunnerOptions
> > (http://hackage.haskell.org/packages/archive/test-framework/0.6/doc/html/Test-Framework-Runners-Options.html)
> > but I do not find any examples of using them.  Similarly, I do not
> > know how to set them up.
> > 
> 
> Here's an example main function that also uses test-framework-doctest.
> 
> There's only one trick used: because TestOptions/RunnerOptions are
> instances of monoid, we can use "mempty" to get an empty set of
> options. This is a little more fun than creating an empty record by
> hand.
> 
> 
> main :: IO ()
> main = do
>   dt <- docTest ["src/Everything.hs"] ["-isrc"]
> 
>   let empty_test_opts = mempty :: TestOptions
>   let my_test_opts = empty_test_opts {
>     topt_maximum_generated_tests = Just 500
>   }
> 
>   let empty_runner_opts = mempty :: RunnerOptions
>   let my_runner_opts = empty_runner_opts {
>     ropt_test_options = Just my_test_opts
>   }
> 
>   defaultMainWithOpts ([dt] ++ tests) my_runner_opts

Thanks a lot.  That works just as I wanted it to do :)  Just for the
record, the relevant part of my code looks like this:

main :: IO ()
main = defaultMainWithOpts tests runnerOpts
  where
    testOpts = (mempty :: TestOptions)
        { topt_maximum_generated_tests = Just 500
        }
    runnerOpts = (mempty :: RunnerOptions)
        { ropt_test_options = Just testOpts
        }


> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
> 



-- 
Mateusz
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 230 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120629/8e5324b6/attachment-0001.pgp>

------------------------------

Message: 7
Date: Sat, 30 Jun 2012 02:51:19 +0100
From: Paulo Pocinho <poci...@gmail.com>
Subject: Re: [Haskell-beginners] Help with Why Do Monads Matter blog
        post    understanding
To: Matt Ford <m...@dancingfrog.co.uk>
Cc: beginners@haskell.org
Message-ID:
        <cak4i1qt4alkbghfkkstrngsvdvlq8kak+jdt8730pbpo-97...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On 29 June 2012 21:30, Matt Ford <m...@dancingfrog.co.uk> wrote:
> On 29 June 2012 19:52, Brent Yorgey <byor...@seas.upenn.edu> wrote:
>
> And I see that passing in functions that act on the state helps do
> this. ?But I don't understand how, for a function that looks like
> A->B, that has a whole load dependencies on external variables and
> functions (of perhaps lot's of different types) all these variables
> and functions are captured by the definition of Pref(B).
>
> And by changing the actual type of the result of A->B in this case
> from an Int to a function that returns an Int how can this hope to
> match the original intention of the impure A->B. ?Say for example
> Pref(b) is the empty set as no functions map to from the config to B.
> Changing the range means we will never get a sensible result??
>
> I feel as though I'm missing something.

That paragraph introduces the notion of currying. Fast forward - the
objective is to test the returning function. Usually, with "maybe"
result or "just" result. This is a way to isolate (the understanding
of) what the code does from (side) effects that are not expected.
Effects do happen. The idea is to restrict their "area of effect"
inside a monad, so the code just does what we expect (machines are
funny like that) and nothing else.

"Abstraction Over Monads" introduces the advantage of having this
abstraction in Haskell "by design".

[quote]
sequence :: Monad m => [m a] -> m [a]

(...) It?s basically a convenient way to check a whole list of
computations for a failure.
[/quote]



------------------------------

Message: 8
Date: Sat, 30 Jun 2012 10:42:37 +0200
From: Nathan H?sken <nathan.hues...@posteo.de>
Subject: Re: [Haskell-beginners] FRP and a set of pairwise interacting
        (colliding) objects
To: beginners@haskell.org
Message-ID: <4feebbfd.8050...@posteo.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

On 06/29/2012 04:47 PM, Ertugrul S?ylemez wrote:
> Nathan H?sken <nathan.hues...@posteo.de> wrote:
>
>> [...]
>>
>> But now the collisions are generated at one place, and processed at
>> another. This means that CollData must be somehow tagged to the
>> objects it belongs to (an ID for example). This again means that some
>> function must take the pool of all collision datas and distribute them
>> to the "object" Signals.
>>
>> When I have a lot of objects, this means a significant overhead!
>>
>> Now I am wondering if there is a nicer approach which avoids this
>> overhead.
> You can get around the overhead by letting the objects do the collisions
> themselves, much like in your OOP variant.  For instance in Netwire you
> could have this:
>
>      planets :: MyWire [Planet] Planet
>
> This naive way still causes the overhead of lists and a planet
> distinguishing between others and itself.  But now this is simply a
> matter of choosing proper data structures and starting to identify
> planets:
>
>      type PlanetSet = Map PlanetId Planet
>
>      planets :: MyWire PlanetSet (PlanetId, Planet)
>
> This looks more promising.  Now the last thing is that this looks like a
> chicken/egg problem, but it's easy to resolve using ArrowLoop and
> one-instant delays.

So I would have a main arrow like this (leaving out the Map for which I 
have to lookup the syntax):

main = proc in -> do
       planet1 <- planets initPlanet1 -< allPlanets
       planet2 <- ...
       ...
       allPlanets <- delay [] -< [planet1,planet2 ...]

(I would probably have some arrow managing all planets instead of 
listing them separately)
Correct?

Yes, that makes sense. There is still a little overhead. Assuming 
collisions are symmetric, the OOP approach would only test every pair of 
planets once ... not in the way I wrote it down, but it could easily be 
changed so that it does.
But here they have to tested twice.
Thats only factor 2 and probably acceptable. Still, is it avoidable?

Thanks!
Nathan



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 48, Issue 31
*****************************************

Reply via email to