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"), (++"20")] "3"
"310320"
I think this is the most general solution?
import Control.Category
import Data.Foldable
import Prelude hiding (foldr, (.), id)
compose :: (Foldable t, Category cat) => t (cat a a) -> cat a a
compose = foldr (.) id
Usage:
> compose [(+10), (+20)] 3
Real-world use case:
> let parseOrIgnore p = either (const s) id . parse p s
> parseAllOrIgnore = compose . map parseOrIgnore [p1, p2, p3]
Naming:
"(.)/compose" is consistent with "(+)/sum", "(*)/product", "(&&)/and", etc.
Thoughts?
-Greg
On Fri, Oct 26, 2012 at 12:31 PM, John Wiegley
<jwiegley@gmail.com> wrote:
>>>>> Greg Fitzgerald <
garious@gmail.com> 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