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. Re:  Re: \x -> x < 0.5 && x > -0.5 (aditya siram)
   2. Re:  Re: parsing upto n items with parsec (Chadda? Fouch?)
   3. Re:  Re: \x -> x < 0.5 && x > -0.5 (Brent Yorgey)
   4. Re:  Re: parsing upto n items with parsec (Ashish Agarwal)
   5. Re:  Re: \x -> x < 0.5 && x > -0.5 (Michael Mossey)


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

Message: 1
Date: Mon, 19 Oct 2009 11:47:32 -0500
From: aditya siram <aditya.si...@gmail.com>
Subject: Re: [Haskell-beginners] Re: \x -> x < 0.5 && x > -0.5
To: Jordan Cooper <nefi...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <594f78210910190947l54e8ac10g53920b932a539...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

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.si...@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 <nefi...@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@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-0001.html

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

Message: 2
Date: Mon, 19 Oct 2009 18:55:15 +0200
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] Re: parsing upto n items with parsec
To: Ashish Agarwal <agarwal1...@gmail.com>
Cc: Christian Maeder <christian.mae...@dfki.de>, beginners@haskell.org
Message-ID:
        <e9350eaf0910190955n45cb1e50s664bd7c93d5e4...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Mon, Oct 19, 2009 at 6:22 PM, Ashish Agarwal <agarwal1...@gmail.com> wrote:
> The semantics of (upTo n p) should be to parse at most n tokens, but if less
> than n tokens are available that should still be a successful parse. And the
> next token should be the first one upTo failed on.
> I attempted to use the "try" parser in various locations but that doesn't
> seem to help, or maybe I'm using it incorrectly.


First, you should probably use pattern matching rather than if for
your base case/recursive case distinction, it's clearer (at least most
Haskellers seems to think it is) :

> upTo 0 p = return []

second, option was conceived for these case where you want to try a
parser and returns something if it fail :

> upTo n p = option [] $ liftM2 (:) p (upTo (n-1) p)

Even then, be careful of putting a try before any multi-token parser
that could fail harmlessly during the upTo.

-- 
Jedaï


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

Message: 3
Date: Mon, 19 Oct 2009 13:21:07 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Re: \x -> x < 0.5 && x > -0.5
To: beginners@haskell.org
Message-ID: <20091019172107.ga28...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Mon, Oct 19, 2009 at 12:07:19PM +0200, Christian Maeder wrote:
> Michael Mossey schrieb:
> > Is there a nifty way to write
> > 
> > filter (\x -> x < 0.5 && x > -0.5) xs
> > 
> > without explicitly using x?
> 
> Hoogle did not find a function of type:
> 
> (b -> b -> b) -> (a -> b) -> (a -> b) -> a -> b
> 
> or (b -> c -> d) -> (a -> b) -> (a -> c) -> a -> d

Apparently Hoogle does not know to try unifying m b with a -> b.  As
others have pointed out, a function of this type (actually, a more
general type) does exist, namely, liftM2.

-Brent


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

Message: 4
Date: Mon, 19 Oct 2009 14:08:39 -0400
From: Ashish Agarwal <agarwal1...@gmail.com>
Subject: Re: [Haskell-beginners] Re: parsing upto n items with parsec
To: Chadda? Fouch? <chaddai.fou...@gmail.com>
Cc: Christian Maeder <christian.mae...@dfki.de>, beginners@haskell.org
Message-ID:
        <d8be5ae20910191108y2f7e7561mab7422e0c9980...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Right. I took "option" out for some reason. The following definitions have
the desired behavior. I also added a base case to fromTo because otherwise
the call to count would consume m tokens even if n-m < 0, which is probably
not what we'd expect.
upTo :: Int -> GenParser tok st a -> GenParser tok st [a]
upTo n p
    | n <= 0 = return []
    | otherwise = option [] $ liftM2 (:) p (upTo (n-1) p)

fromTo :: Int -> Int -> GenParser tok st a -> GenParser tok st [a]
fromTo m n p
    | n-m < 0 = return []
    | otherwise = liftM2 (++) (count m p) (upTo (n-m) p)

Thanks!


On Mon, Oct 19, 2009 at 12:55 PM, Chaddaï Fouché
<chaddai.fou...@gmail.com>wrote:

> On Mon, Oct 19, 2009 at 6:22 PM, Ashish Agarwal <agarwal1...@gmail.com>
> wrote:
> > The semantics of (upTo n p) should be to parse at most n tokens, but if
> less
> > than n tokens are available that should still be a successful parse. And
> the
> > next token should be the first one upTo failed on.
> > I attempted to use the "try" parser in various locations but that doesn't
> > seem to help, or maybe I'm using it incorrectly.
>
>
> First, you should probably use pattern matching rather than if for
> your base case/recursive case distinction, it's clearer (at least most
> Haskellers seems to think it is) :
>
> > upTo 0 p = return []
>
> second, option was conceived for these case where you want to try a
> parser and returns something if it fail :
>
> > upTo n p = option [] $ liftM2 (:) p (upTo (n-1) p)
>
> Even then, be careful of putting a try before any multi-token parser
> that could fail harmlessly during the upTo.
>
> --
> Jedaï
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091019/86f1a98c/attachment-0001.html

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

Message: 5
Date: Mon, 19 Oct 2009 12:09:02 -0700
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: Re: [Haskell-beginners] Re: \x -> x < 0.5 && x > -0.5
To: Heinrich Apfelmus <apfel...@quantentunnel.de>
Cc: beginners@haskell.org
Message-ID: <4adcb94e.4050...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed



Heinrich Apfelmus wrote:
> Michael Mossey wrote:
>> Is there a nifty way to write
>>
>> filter (\x -> x < 0.5 && x > -0.5) xs
>>
>> without explicitly using x?
>>
>> Maybe arrows? I have a vague understanding that arrows can "send" an
>> argument to more than one computation.
> 
> 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
> 
> 

Cool.

I realized there was a way to think about this. I haven't used the reader 
monad in my own projects, but I recall it's one way to pass the same value 
into several functions:

headTail = do
   h <- head
   t <- tail
   return (h,t)

headTail "foo" = ('f',"oo")

Note also there's no need for runReader or evalReader (at least not that 
I'm aware of) because unlike other monads, the reader monad is itself a 
function that takes the state to be read.

This could be generalized to

headTail2 g = do
    h <- head
    t <- tail
    return $ g h t

headTail2 (,) "foo" = ('f',"oo")

But this form:  do { x <- m1; y <- m2; return $ g x y} is exactly the 
definition of liftM2.  Specifically, liftM2 g m1 m2.




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

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


End of Beginners Digest, Vol 16, Issue 14
*****************************************

Reply via email to