Send Beginners mailing list submissions to
        [email protected]

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
        [email protected]

You can reach the person managing the list at
        [email protected]

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


Today's Topics:

   1. Re:  Lazy variant of sequence (or other way to approach
      problem) (Chadda? Fouch?)
   2. Re:  Lazy variant of sequence (or other way to    approach
      problem) (Ertugrul S?ylemez)
   3. Re:  FRP (Miguel Negrao)
   4. Re:  confused by <- (Bryce Verdier)
   5. Re:  confused by <- (Brent Yorgey)
   6. Re:  confused by <- (Bryce Verdier)


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

Message: 1
Date: Thu, 27 Sep 2012 12:00:42 +0200
From: Chadda? Fouch? <[email protected]>
Subject: Re: [Haskell-beginners] Lazy variant of sequence (or other
        way to approach problem)
To: Nathan H?sken <[email protected]>
Cc: [email protected]
Message-ID:
        <CANfjZRb8RCRmcNoe=GbFT=23nO6jYR6XsXNc++sae=asza-...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Thu, Sep 27, 2012 at 9:14 AM, Nathan H?sken <[email protected]>wrote:

> On 09/27/2012 01:45 AM, Ertugrul S?ylemez wrote:
> > Nathan H?sken <[email protected]> wrote:
> >
> >> In my (SDL based) haskell program, I do:
> >>
> >> events <- liftM ( takeWhile (/= NoEvent)) $ sequence $ repeat
> >> pollEvent
> >>
> >> The execution of this never returns, I am guessing that is because
> >> sequence evaluation never stops.
>

Yes, which is why you should include the condition in the loop, the
standard library doesn't include facilities for that but the monad-loop
package has this function (amongst others) :

> unfoldWhileM :: 
> Monad<http://hackage.haskell.org/packages/archive/base/4.5.0.0/doc/html/Control-Monad.html#t:Monad>m
>  => (a ->
Bool<http://hackage.haskell.org/packages/archive/base/4.5.0.0/doc/html/Data-Bool.html#t:Bool>)
-> m a -> m [a]

which you could use as :

> events <- unfoldWhileM (=/ NoEvent) pollEvent

(note that if this is the only thing you use from this library, you may
just write this function for yourself, it is quite easy in the direct style
like the pollEvent_ proposed by Ertugrul)


> >>
> >> But if sequence would be lazy (and assuming pollEvent returns NoEvent
> >> at some point) this should stop, should it not?
> >> Is there a lazy variant of sequence? Or am I missing something here
> >> completely?
> >
> > The sequence function itself cannot be lazy, and there can't be a lazy
> > variant of it.
>
> I understand, that it is a bad Idea. But why is it impossible to have an
> lazy sequence? Why can it not wait with the execution of the action for
> the list elements to be evaluated?
>
>
Normally, with the normal semantics of monads, you can't have a lazy
sequence because it could mean that monad evaluation could be interspersed
in pure code without it being apparent (which is particularly dangerous
with IO) which is why you need to use unsafe functions to get this
unnatural result. It is also generally a bad idea for the same reason as
lazy IO is, to illustrate this in your particular case : you don't have
_any_ guarantee that it would work correctly : if you only start consuming
"events" a few seconds later, you wouldn't get the result from a few
seconds ago, you would get the current events... Maybe this doesn't happen
now in your application but can you be _sure_ that you'll never need to
stock those lists of events to consult them later on ?

-- 
Jeda?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120927/5647c5dd/attachment-0001.htm>

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

Message: 2
Date: Thu, 27 Sep 2012 13:14:08 +0200
From: Ertugrul S?ylemez <[email protected]>
Subject: Re: [Haskell-beginners] Lazy variant of sequence (or other
        way to  approach problem)
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset="utf-8"

Nathan H?sken <[email protected]> wrote:

> On 09/27/2012 01:45 AM, Ertugrul S?ylemez wrote:
> > Nathan H?sken <[email protected]> wrote:
> > 
> >> In my (SDL based) haskell program, I do:
> >>
> >> events <- liftM ( takeWhile (/= NoEvent)) $ sequence $ repeat
> >> pollEvent
> >>
> >> The execution of this never returns, I am guessing that is because
> >> sequence evaluation never stops.
> >>
> >> But if sequence would be lazy (and assuming pollEvent returns
> >> NoEvent at some point) this should stop, should it not?
> >> Is there a lazy variant of sequence? Or am I missing something here
> >> completely?
> > 
> > The sequence function itself cannot be lazy, and there can't be a
> > lazy variant of it.
> 
> I understand, that it is a bad Idea. But why is it impossible to have
> an lazy sequence? Why can it not wait with the execution of the action
> for the list elements to be evaluated?

Because the Monad class does not have a combinator for that.  Unsafe
interleaving is a feature of the IO monad, not of monads in general.
However I was lying a bit.  Whether sequence is lazy does not depend on
its implementation, but on the monad.  If asking for the head of the
result list only ever depends on part of the computation, then only that
part has to be performed.  This is especially true for the 'Reader e'
and '(->) e' monads (which are the isomorphic, btw.):

    sequence (sin : undefined)
        = liftM2 (:) sin (sequence undefined)
        = \e -> sin e : sequence undefined e

A trivial example is Identity:

    sequence (return 3 : undefined)
        = liftM2 (:) (return 3) (sequence undefined)
        = Identity (3 : runIdentity (sequence undefined))

IIRC monads with that property are called affine monads.  The Maybe
monad does not have this property:

    sequence (Just 3, undefined)
        = liftM2 (:) (Just 3) (sequence undefined)
        = case Just 3 of
            Just x ->
                case sequence undefined of
                  Just xs -> Just (x:xs)
                  Nothing -> Nothing
            Nothing -> Nothing

This will reach the undefined in the inner case, before it gets the
opportunity to deliver a result, because the ability to deliver a
results depends on whether 'sequence undefined' is a Just.  The Maybe
monad's counterpart to unsafeInterleaveIO is:

    unsafeInterleaveMaybe :: Maybe a -> Maybe a
    unsafeInterleaveMaybe ~(Just x) = Just x

With the help of this combinator you can actually write
unsafeLazySequenceMaybe.


> > By the way, if your application is non-continuously rendered, which
> > is suggested by your ignoring of NoEvent, you shouldn't use
> > pollEvent at all.
>
> The Idea of the line what to return all events that happened in the
> current frame (which are to my understanding all events until
> pollEvent returns NoEvent).

Lazy sequence is not what you want for that.  It would be semantically
wrong or at least weird if a second invocation of that action could ever
produce a result, because the first one is supposed to have produced all
events that ever happened.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.
-------------- 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/20120927/65d8d493/attachment-0001.pgp>

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

Message: 3
Date: Thu, 27 Sep 2012 12:58:50 +0100
From: Miguel Negrao <[email protected]>
Subject: Re: [Haskell-beginners] FRP
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=windows-1252


A 20/09/2012, ?s 03:56, Ertugrul S?ylemez escreveu:

> Miguel Negrao <[email protected]> wrote:
> 
>>> Netwire follows a more algebraic path and drops the classic notion.
>>> The line between signals and events is blurred.  It's a bit more
>>> difficult to understand, but is more expressive and concise.  Also
>>> it's pretty much time-leak-free.  The library is designed to be very
>>> elegant while preserving non-FRP performance to a high degree.
>>> 
>>> (To be fair, I'm the author of Netwire.) =)
>> 
>> Having recently looked a bit on Yampa, what are the main differences
>> between Yampa and Netwire ?
> 
> The way events are handled.  Yampa uses the classic automaton category
> with an additional time delta argument for its signal function [...]


Thanks for the explanation. I was wondering, how would one translate this Yampa 
code into reactive-banana:

fallingBall :: Pos -> Vel -> SF () (Pos, Vel)
        fallingBall y0 v0 = proc () -> do
                v <- (v0 +) ?<< integral -< -9.81
                y <- (y0 +) ?<< integral -< v
                returnA -< (y, v)

fallingBall? :: Pos -> Vel -> SF () ((Pos,Vel), Event (Pos,Vel))
fallingBall? y0 v0 = proc () -> do
        yv@(y, _) <- fallingBall y0 v0 -< ()
        hit <- edge -< y <= 0
        returnA -< (yv, hit ?tag? yv)

bouncingBall :: Pos -> SF () (Pos, Vel)
bouncingBall y0 = bbAux y0 0.0
        where
                bbAux y0 v0 = switch (fallingBall? y0 v0) $ \(y,v) -> bbAux y 
(-v)

Would it be possible to do this without dynamic event switching ? What about 
with the new event switching in v0.7 ?  Also, is it possible (and is it easy ?) 
to do looping such as it is done in Yampa using the the loop arrow in 
reactive-banana/classic FRP ?

best,
Miguel Negr?o


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

Message: 4
Date: Thu, 27 Sep 2012 10:01:25 -0700
From: Bryce Verdier <[email protected]>
Subject: Re: [Haskell-beginners] confused by <-
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset="iso-8859-1"; Format="flowed"

On 9/26/12 6:00 PM, Ertugrul S?ylemez wrote:
> Bryce Verdier <[email protected]> wrote:
>
>>       body <- L.try (simpleHttp "http://www.google.com";) :: IO (Either
>> L.SomeException Data.ByteString.Lazy.Internal.ByteString)
> Almost right, but your type signature is lying. =)
>
>
> Greets,
> Ertugrul

Thanks for your hint, with a fair amount of head bashing against a wall 
I was able to figure this out. At the end of day I got :

     body <- try (simpleHttp "http://www.google.com";) :: GHandler 
PlayHaven PlayHaven (Either SomeException ByteString)

But what I don't understand, is why do I have GHandler PlayHaven 
PlayHaven (Either SomeException ByteString)
instead of IO (Either SomeException ByteString)?

Thanks again,
Bryce

>
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120927/93d18840/attachment-0001.htm>

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

Message: 5
Date: Thu, 27 Sep 2012 13:33:27 -0400
From: Brent Yorgey <[email protected]>
Subject: Re: [Haskell-beginners] confused by <-
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=iso-8859-1

On Thu, Sep 27, 2012 at 10:01:25AM -0700, Bryce Verdier wrote:
> On 9/26/12 6:00 PM, Ertugrul S?ylemez wrote:
> >Bryce Verdier <[email protected]> wrote:
> >
> >>      body <- L.try (simpleHttp "http://www.google.com";) :: IO (Either
> >>L.SomeException Data.ByteString.Lazy.Internal.ByteString)
> >Almost right, but your type signature is lying. =)
> >
> >
> >Greets,
> >Ertugrul
> 
> Thanks for your hint, with a fair amount of head bashing against a
> wall I was able to figure this out. At the end of day I got :
> 
>     body <- try (simpleHttp "http://www.google.com";) :: GHandler
> PlayHaven PlayHaven (Either SomeException ByteString)

Do you need a type signature there at all?

-Brent



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

Message: 6
Date: Thu, 27 Sep 2012 10:38:31 -0700
From: Bryce Verdier <[email protected]>
Subject: Re: [Haskell-beginners] confused by <-
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

On 9/27/12 10:33 AM, Brent Yorgey wrote:
> On Thu, Sep 27, 2012 at 10:01:25AM -0700, Bryce Verdier wrote:
>> On 9/26/12 6:00 PM, Ertugrul S?ylemez wrote:
>>> Bryce Verdier <[email protected]> wrote:
>>>
>>>>       body <- L.try (simpleHttp "http://www.google.com";) :: IO (Either
>>>> L.SomeException Data.ByteString.Lazy.Internal.ByteString)
>>> Almost right, but your type signature is lying. =)
>>>
>>>
>>> Greets,
>>> Ertugrul
>> Thanks for your hint, with a fair amount of head bashing against a
>> wall I was able to figure this out. At the end of day I got :
>>
>>      body <- try (simpleHttp "http://www.google.com";) :: GHandler
>> PlayHaven PlayHaven (Either SomeException ByteString)
> Do you need a type signature there at all?
>
> -Brent
That is an awesome question. Originally I tried:

        body <- try (simpleHttp "http://www.google.com";)

and I got this error:
playhaven.hs:54:73:
     Ambiguous type variable `a0' in the constraints:
       (Show a0) arising from a use of `show' at playhaven.hs:54:73-76
       (Exception a0) arising from a use of `try' at playhaven.hs:52:13-15
     Probable fix: add a type signature that fixes these type variable(s)

So I figured that adding the type signature would help with it. If you 
know of another way to make this work I would really like to hear about it.

Thanks,
Bryce




> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners




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

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 51, Issue 40
*****************************************

Reply via email to