Re: Re[Haskell-cafe] cursive to foldr

2009-11-18 Thread Edward Kmett
On Wed, Nov 18, 2009 at 7:43 AM, Ben Millwood wrote:

> It looks quite neat to use the Maybe monoid here:
>
> > import Data.Monoid
> > searchList p = foldr (\x -> if p x then mappend (Just [x]) else id)
> Nothing
>
> but it seems that the Maybe Monoid instance keeps this strict. I
> fiddled with this a bit, and came up with the following:
>
> > instance (Monoid m) => Monoid (Maybe m) where
> >  mempty = Nothing -- as usual
> >  mappend (Just x) y = Just $ mappend x (fromMaybe mempty y)
> >  mappend Nothing y = y
>

The existing Monoid instance for 'Maybe a' lifts what is logically a
Semigroup into a Monoid by extending the domain of the operation with a unit
(Nothing). Alas, This is annoyingly not the same behavior as the MonadPlus
behavior for Maybe, unlike all of the other cases where MonadPlus and Monoid
happen to exist in a manner in which they coincide, and since there is no
Semigroup class, it lies and claims that it transforms Monoid m => Monoid
(Maybe m).

Your version uses mempty from the underlying monoid, so it would break any
code that relied on the existing 'lifted Semigroup' interpretation of the
Maybe Monoid, which safely operate lift Semigroups-that-claim-to-be-Monoids
where mempty = undefined

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


Re: Re[Haskell-cafe] cursive to foldr

2009-11-18 Thread Ben Millwood
It looks quite neat to use the Maybe monoid here:

> import Data.Monoid
> searchList p = foldr (\x -> if p x then mappend (Just [x]) else id) Nothing

but it seems that the Maybe Monoid instance keeps this strict. I
fiddled with this a bit, and came up with the following:

> instance (Monoid m) => Monoid (Maybe m) where
>  mempty = Nothing -- as usual
>  mappend (Just x) y = Just $ mappend x (fromMaybe mempty y)
>  mappend Nothing y = y

which results in the expected behaviour (it's unsatisfyingly
asymmetric, since it should (but can't) produce a Just if the second
argument is Just without pattern-matching on the first, but there is
only so much one can do without involving scary things like unamb).

I'd be interested in what people thought of the relative merits of
this alternative Monoid instance, but perhaps that would be a subject
for a different thread.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[Haskell-cafe] cursive to foldr

2009-11-17 Thread David Menendez
On Tue, Nov 17, 2009 at 10:01 PM, Luke Palmer  wrote:
> filter even [0..]    -->    [0,2,4,6,8,...]
> searchList even [0...]   -->   Just [0,2,4,6,8,...]
>
> searchList gives Nothing in exactly those cases that filter gives [].
> They give _|_ in exactly the same situations.  searchList could well
> be defined as:
>
> searchList p xs = if null ys then Nothing else Just ys
>    where ys = filter p xs
>
> null is strict, so searchList is just as strict as filter.

You're right. I was thinking of traverse with an exception monad.

To make up for it, I'll note that with the recently (re)proposed
mfilter, you can define searchList as:

searchList p = mfilter (not . null) . Just . filter p

-- 
Dave Menendez 

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


Re: Re[Haskell-cafe] cursive to foldr

2009-11-17 Thread Luke Palmer
On Tue, Nov 17, 2009 at 7:39 PM, David Menendez  wrote:
> On Tue, Nov 17, 2009 at 6:31 PM, Ezra Lalonde  wrote:
>>
>> Using the same basic structure you did, and foldr, I think below is the
>> simplest method:
>>
>> 
>> import Data.Maybe
>>
>> searchList :: (a -> Bool) -> [a] -> Maybe [a]
>> searchList p xs = foldr (\x acc -> if p x then Just (x: fromMaybe [] acc)
>> else acc) Nothing xs
>> 
>
> This might be considered simpler:
>
> searchList p = foldr (\x -> if p x then Just . maybe [x] (x:) else id) Nothing
>
> The real problem with searchList is that it's strict and can't be made
> lazy. Because it returns Nothing when nothing matches the predicate,
> it has to traverse the entire list before returning anything. Instead,
> I would recommend filter, which can be used as-is or defined in terms
> of foldr.
>
> filter p = foldr (\x -> if p x then (x:) else id) []
>
> Compare the behavior of "searchList even [0..]" and "filter even [0..]".

...?

filter even [0..]-->[0,2,4,6,8,...]
searchList even [0...]   -->   Just [0,2,4,6,8,...]

searchList gives Nothing in exactly those cases that filter gives [].
They give _|_ in exactly the same situations.  searchList could well
be defined as:

searchList p xs = if null ys then Nothing else Just ys
where ys = filter p xs

null is strict, so searchList is just as strict as filter.

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


Re: Re[Haskell-cafe] cursive to foldr

2009-11-17 Thread David Menendez
On Tue, Nov 17, 2009 at 6:31 PM, Ezra Lalonde  wrote:
>
> Using the same basic structure you did, and foldr, I think below is the
> simplest method:
>
> 
> import Data.Maybe
>
> searchList :: (a -> Bool) -> [a] -> Maybe [a]
> searchList p xs = foldr (\x acc -> if p x then Just (x: fromMaybe [] acc)
> else acc) Nothing xs
> 

This might be considered simpler:

searchList p = foldr (\x -> if p x then Just . maybe [x] (x:) else id) Nothing

The real problem with searchList is that it's strict and can't be made
lazy. Because it returns Nothing when nothing matches the predicate,
it has to traverse the entire list before returning anything. Instead,
I would recommend filter, which can be used as-is or defined in terms
of foldr.

filter p = foldr (\x -> if p x then (x:) else id) []

Compare the behavior of "searchList even [0..]" and "filter even [0..]".

-- 
Dave Menendez 

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


Re: Re[Haskell-cafe] cursive to foldr

2009-11-17 Thread Ezra Lalonde

Using the same basic structure you did, and foldr, I think below is the
simplest method:


import Data.Maybe

searchList :: (a -> Bool) -> [a] -> Maybe [a]
searchList p xs = foldr (\x acc -> if p x then Just (x: fromMaybe [] acc)
else acc) Nothing xs


ghci> searchList (=='o') "A quick brown fox"
Just "oo"
ghci> searchList (==' ') "A quick brown fox"
Just "   "
ghci> searchList (=='z') "A quick brown fox"
Nothing


>From maybe gets rid of the Maybe, so that our recursive call works:
ghci> fromMaybe [] (Just [1..3])
[1,2,3]

That's why we got the error below when we tried without fromMaybe; on
subsequent applications of foldr, the type would have to change.

:1:51:
Couldn't match expected type `[a]'
   against inferred type `Maybe [a]'
In the expression: if p x then Just (x : acc) else acc
In the first argument of `foldr', namely
`(\ x acc -> if p x then Just (x : acc) else acc)'
In the expression:
foldr (\ x acc -> if p x then Just (x : acc) else acc) Nothing xs


I have a feeling that using fromMaybe is not the best way, but it gets the
job done for now.

On that note; if somebody with some more experience would chime in, that'd
be awesome. ;)

Ezra


dima.neg wrote:
> 
> How can I do this using foldr?
> 
> searchList p [] = Nothing
> searchList p (x:xs)
>   | p x = Just (x:filter p xs)
>   | otherwise = searchList p xs
> 
> 
> I try this: 
> searchList p xs = foldr (\x acc -> if p x then Just (x:acc) else acc)
> Nothing xs
> but don't work.
> 
> Thanks
> 

-- 
View this message in context: 
http://old.nabble.com/Recursive-to-foldr-tp26368900p26399795.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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