Re: [Haskell-cafe] foldr (.) id

2012-10-26 Thread John Wiegley
> Greg Fitzgerald writes: > I've recently found myself using the expression: "foldr (.) id" to compose a > list (or Foldable) of functions. You want the Endo monoid: ghci> appEndo (Endo (+ 10) <> Endo (+ 20)) $ 3 33 John ___ Haskell-C

Re: [Haskell-cafe] foldr (.) id

2012-10-26 Thread Thiago Negri
Can you please show some examples where it might be useful? I miss the point. Thanks, Thiago. 2012/10/26 John Wiegley : >> Greg Fitzgerald writes: > >> I've recently found myself using the expression: "foldr (.) id" to compose a >> list (or Foldable) of functions. > > You want the Endo monoi

Re: [Haskell-cafe] foldr (.) id

2012-10-26 Thread John Wiegley
> Thiago Negri writes: > Can you please show some examples where it might be useful? > I miss the point. I guess if he already has a list of functions, Endo won't help. Endo just lets you treat functions as monoids, so you can foldMap, etc. In that case, foldr (.) id is pretty idiomatic, a

Re: [Haskell-cafe] foldr (.) id

2012-10-26 Thread Greg Fitzgerald
Hmm, neato. but didn't make life any easier! Data.Monoid> (appEndo . mconcat . map Endo) [(+10), (+20)] 3 33 Data.Monoid> (foldr (.) id) [(+10), (+20)] 3 33 I had hoped for something like: > mconcat [(+10), (+20)] 3 But I suppose that's nonsense, considering this works: > mconcat [(++"10"), (

Re: [Haskell-cafe] foldr (.) id

2012-10-26 Thread Greg Fitzgerald
sorry for the buggy code > let parseOrIgnore p s = either (const s) id $ parse p s > let parseAllOrIgnore = compose . map parseOrIgnore [p1, p2, p3] > parseAllOrIgnore "abbbcccbbba" On Fri, Oct 26, 2012 at 2:11 PM, Greg Fitzgerald wrote: > Hmm, neato. but didn't make life any easier! > > Data.

Re: [Haskell-cafe] foldr (.) id

2012-10-26 Thread Nick Vanderweit
Funny, I was thinking this morning about using something like this to convert to/from Church numerals: church n = foldl (.) id . replicate n unchurch f = f succ 0 I think it's a nice pattern. Nick On Friday, October 26, 2012 11:41:18 AM Greg Fitzgerald wrote: > Hi Haskellers, > > I've recent

Re: [Haskell-cafe] foldr (.) id

2012-10-26 Thread Tony Morris
It's the Endo monoid. ?> :t ala Endo foldMap -- see newtype package ala Endo foldMap :: Foldable t => t (a -> a) -> a -> a ?> ala Endo foldMap [(+1), (*2)] 8 17 ?> :i ala ala :: (Newtype n o, Newtype n' o') => (o -> n) -> ((o -> n) -> b -> n') -> b -> o' -- Defined in Control.Newtype O

Re: [Haskell-cafe] foldr (.) id

2012-10-27 Thread Ross Paterson
On Fri, Oct 26, 2012 at 07:41:18PM +0100, Greg Fitzgerald wrote: > I've recently found myself using the expression: "foldr (.) id" to > compose a list (or Foldable) of functions.  It's especially useful > when I need to map a function over the list before composing.  Does > this function, or the mo

Re: [Haskell-cafe] foldr (.) id

2012-10-27 Thread Greg Fitzgerald
> Alternatively: flip (foldr id) Very cool, but... Prelude> import qualified Data.Foldable as F Prelude F> :t F.foldr id F.foldr id :: F.Foldable t => b -> t (b -> b) -> b {- Generalizing -} Prelude F> import qualified Control.Category as C Prelude F C> :t F.foldr (C..) C.id F.foldr (C..) C.id

Re: [Haskell-cafe] foldr (.) id

2012-10-27 Thread wren ng thornton
On 10/26/12 2:41 PM, Greg Fitzgerald wrote: Hi Haskellers, I've recently found myself using the expression: "foldr (.) id" to compose a list (or Foldable) of functions. It's especially useful when I need to map a function over the list before composing. Does this function, or the more general

Re: [Haskell-cafe] foldr (.) id

2012-10-29 Thread Sebastian Fischer
> "(.)/compose" is consistent with "(+)/sum", "(*)/product", "(&&)/and", etc. "(to) compose" is a verb. "composition" would be consistent with "sum" and "product". "and" doesn't fit, though. Sebastian ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.

Re: [Haskell-cafe] foldr (.) id

2012-10-29 Thread David Thomas
"sum" can be a verb, but yeah, "product" can't really, so it probably makes sense to follow the noun pattern if we're wanting to be consistent more than brief. "and" as a noun is unusual, but fwiw dictionary.com says that there's a noun sense that means "conjunction" in the logical sense, which is