[Haskell-beginners] Re: \x -> x < 0.5 && x > -0.5

aditya siram aditya.siram at gmail.com
Mon Oct 19 12:47:32 EDT 2009


There was a mistake in the trace, please ignore the previous one and look at
this. Again your viewing window should be this wide:
<----------------------------------------------------------------->
(liftM2 (&&) (< 0.5) (> -0.5))
=> do {x1 <- (< 0.5);
       x2 <- (> -0.5);
       return ((&&) x1 x2)}

=> (< 0.5) >>= \x1
   (> -0.5) >>= \x2
   return ((&&) x1 x2)

=> \r ->(\x1 ->
            (> -0.5) >>= \x2
            return ((&&) x1 x2))
        ((< 0.5) r)
        r

=> \r -> ((> -0.5) >>= \x2
          return ((&&) ((< 0.5) r) x2))
          r

=> \r -> (\r' -> (\x2 ->
                      return ((&&) (const (< 0.5) r) x2))
                 ((> -0.5) r')
                 r')
         r
=> \r -> (\r' -> (return ((&&) ((< 0.5) r) ((> -0.5) r'))) r') r
=> \r -> (\r' -> (const ((&&) ((< 0.5) r) ((> -0.5) r'))) r') r
=> \r -> (\r' -> ((&&) ((< 0.5) r) ((> -0.5) r'))) r
=> \r -> (\r' -> ((r < 0.5) && (r' > -0.5))) r


On Mon, Oct 19, 2009 at 11:42 AM, aditya siram <aditya.siram at gmail.com>wrote:

> This one had me puzzled too - so did a traced through the program below.
> Please make sure your viewing window is at least this wide:
> <---------------------------------------------------------------->
>
> It was more helpful to think of this as using the ((->) r) instance of
> Monad. It is defined in ./libraries/base/Control/Monad/Instances.hs in your
> GHC source as:
> >instance Monad ((->) r) where
> >    return = const
> >    f >>= k = \ r -> k (f r) r
>
> And const just returns its first argument like:
> const 1 3 => 1
> const "hello" "world" => "hello"
>
> And liftM2 is defined in ./libraries/base/Control/Monad.hs as :
> >liftM2  :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
> >liftM2 f m1 m2 = do { x1 <- m1; x2 <- m2; return (f x1 x2) }
>
> So a trace of the program goes like this:
>
> (liftM2 (&&) (< 0.5) (> -0.5))
> => do {x1 <- (< 0.5);
>        x2 <- (> -0.5);
>        return ((&&) x1 x2)}
>
> => (< 0.5) >>= \x1
>    (> -0.5) >>= \x2
>    return ((&&) x1 x2)
>
> => \r ->(\x1 ->
>             (> -0.5) >>= \x2
>             return ((&&) x1 x2))
>         ((< 0.5) r)
>         r
>
> => \r -> (return (> -0.5) >>= \x2
>           return ((&&) ((< 0.5) r) x2))
>           r
>
> => \r -> (\r' -> (\x2 ->
>                       return ((&&) (const (< 0.5) r) x2))
>                  ((> -0.5) r')
>                  r')
>          r
> => \r -> (\r' -> (return ((&&) ((< 0.5) r) ((> -0.5) r'))) r') r
> => \r -> (\r' -> (const ((&&) ((< 0.5) r) ((> -0.5) r'))) r') r
> => \r -> (\r' -> ((&&) ((< 0.5) r) ((> -0.5) r'))) r
> => \r -> (\r' -> ((r < 0.5) && (r' > -0.5))) r
>
> hope this helps,
> -deech
>
>
> On Mon, Oct 19, 2009 at 10:24 AM, Jordan Cooper <nefigah at gmail.com> wrote:
>
>> Whoa... how on earth does this work? How does it interpret the
>> sections as Reader monads?
>>
>> > That's a job for the reader monad.
>> >
>> >
>> > Lambda Fu, form 53 - silent reader of truth
>> >
>> >     import Control.Monad
>> >     import Control.Monad.Reader
>> >
>> >     filter (liftM2 (&&) (< 0.5) (> -0.5)) xs
>> >
>> >
>> >
>> > Regards,
>> > apfelmus
>> _______________________________________________
>> Beginners mailing list
>> Beginners at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20091019/cd9fb9ca/attachment.html


More information about the Beginners mailing list