
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 "foldr fmap id", defined in a library anywhere? I googled and hoogled, but no luck so far.
While the prelude's (.) just so happens to be an fmap, that most emphatically does not mean fmap is "the" generalization of (.). In fact, fmap is almost never a helpful generalization of (.). The only time it would be helpful is if you're already explicitly depending on the fact that (e->) happens to be a functor, in which case your use of (.) was simply a specialization of fmap in the first place! Removing a specialization and adding a generalization aren't the same process. And the fact that id is showing up here should set off warning bells that the (.) you're dealing with comes from the category structure, not the functor structure. It so happens that endomorphisms form a monoid with id, hence the Endo suggested by other folks. However, Endo is just the restriction of general categories to single-object categories (aka monoids). So you could go with the monoid generalization, in which case what you want is mconcat, which is equal to foldr mappend mempty but may be implemented more efficiently for some monoids. Or, if you're trying to be general then you should go with the category generalization, in which case what you want is foldr (.) id--- using the Category definitions rather than the Prelude. Unfortunately, the full generality of foldr (.) id cannot be easily realized in Haskell since the remaining argument is a list rather than something more general like the reflexive transitive closure of a relation. In a pseudo-Haskell with full dependent types we'd say: kind Relation a = a -> a -> * data RTC (a :: *) (r :: Relation a) :: Relation a where Nil :: forall x::a. RTC a r x x Cons :: forall x y z::a. r x y -> RTC a r y z -> RTC a r x z paraRTC :: forall (a :: *) (r p :: Relation a). (forall x :: a, p x x) -> (forall x y z :: a. r x y -> RTC a r y z -> p y z -> p x z) -> forall x z :: a. RTC a r x z -> p x z -- aka foldrRTC. The only difference is that the second function -- argument doesn't get a copy of @RTC a r y z@. cataRTC :: forall (a :: *) (r p :: Relation a). (forall x :: a, p x x) -> (forall x y z :: a. r x y -> p y z -> p x z) -> forall x z :: a. RTC a r x z -> p x z class Category (r :: Relation *) where id :: forall a. r a a (.) :: forall a b c. r b c -> r a b -> r a c -- Ideally the first three arguments should be passed implicitly cataRTC * (->) (~>) (.) id :: forall a b. RTC * (->) a b -> a ~> b -- Live well, ~wren