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.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
exactly what we're doing here.

On Mon, Oct 29, 2012 at 1:12 PM, Sebastian Fischer m...@sebfisch.de wrote:
 (.)/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.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


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 more general foldr fmap id, defined in a
 library anywhere?  I googled and hoogled, but no luck so far.

Alternatively: flip (foldr id)

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


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 :: (F.Foldable t, C.Category cat) = t (cat b b) - cat
b b


{- Sneaky type-specialization -}

Prelude F C :t F.foldr C.id
F.foldr C.id :: F.Foldable t = b - t (b - b) - b


On Sat, Oct 27, 2012 at 3:09 AM, Ross Paterson r...@soi.city.ac.uk wrote:

 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 more general foldr fmap id, defined in a
  library anywhere?  I googled and hoogled, but no luck so far.

 Alternatively: flip (foldr id)

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

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


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 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

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


[Haskell-cafe] foldr (.) id

2012-10-26 Thread Greg Fitzgerald
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.

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


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

2012-10-26 Thread John Wiegley
 Greg Fitzgerald gari...@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


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


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 jo...@newartisans.com:
 Greg Fitzgerald gari...@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


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

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


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

2012-10-26 Thread John Wiegley
 Thiago Negri evoh...@gmail.com 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, and Google turns up several uses of it.

John

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


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), (++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 jwieg...@gmail.com wrote:

  Greg Fitzgerald gari...@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

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


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 gari...@gmail.com wrote:

 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 jwieg...@gmail.com wrote:

  Greg Fitzgerald gari...@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



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


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 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.
 
 Thanks,
 Greg

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


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


On 27/10/12 04:41, 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.

 Thanks,
 Greg



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


-- 
Tony Morris
http://tmorris.net/


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