Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-16 Thread Edward Kmett
2009/11/15 Eugene Kirpichov ekirpic...@gmail.com

 Hey, I've found terrific slides about monoids!

 http://comonad.com/reader/wp-content/uploads/2009/08/IntroductionToMonoids.pdf
 Edward Kmett, you rock!


Glad you enjoyed the slides. =)


 There's more http://comonad.com/reader/2009/iteratees-parsec-and-monoid/
 - but the second part was too hard for me to read it fully without
 special motivation.


The iteratees, parsec and monoids talk was mostly to solve a technical
problem of my own. The result is a way to build parallel parsers that works
quite well for most practical programming language grammars, but requires
you to think about parsing a bit sideways and requires a lot of machinery
from other areas to make work.

In essence I rely on the fact that in programming languages we typically
have a point at which we can resume parsing, or at least lexing, in a
context-free manner by locating global invariants of the grammar.

These invariants are typically already present and are used to provide error
productions in real world compiler grammars, so that the compiler can try to
resume parsing. It is a hack, but it is a reasonably efficient hack. =)

To make it work, I have to borrow a lot of machinery from other areas.
Iteratees give me a resumable parser, giving that access to its input
history lets it backtrack, which lets me bolt them onto parsec, so you can
write parsers the way you are used to, at least for the tokens in your
language, and then you add a layer on top to deal with the token-stream,
which is now available to be reduced monoidally rather than just
sequentially.

What I was looking for was a good understanding of what invariants would it
make sense to design a language to have so that it could be efficiently
parsed in parallel and incrementally reparsed as the user types without
having to rescan the whole source file.

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-16 Thread Gregory Crosswhite
In my own opinion, the reason why we use the concept of a monoid or a  
monad is in order to build libraries around the concepts.


For example, the do construct could have been designed just for  
doing IO, but because it works for *any* monad you can also use the  
same syntax sugar to conveniently work with a calculation


*) that manipulates a mutable state (State)
*) that has an environment (Reader)
*) that writes out a log (Writer)

Likewise, the nice thing about monoid is that it lets us generalize  
libraries.  So for example, the Writer monad could have just been  
designed to work by concatenating strings or lists since this is what  
one might typically think of for a log.  But because it is designed  
to work with an arbitrary *monoid*, you could use it to keep track of  
a running total as well, since numbers under addition is also a monoid.


So the way I figure it, the important thing is to understand just  
enough of these patterns (monads, monoids) that you can recognize them  
when they come up in your own work so that you can be aware of what  
pre-existing libraries and/or syntax sugar you can leverage to work  
with them.


Cheers,
Greg

On Nov 13, 2009, at 8:14 AM, Magicloud Magiclouds wrote:


Hi,
 I have looked the concept of monoid and something related, but
still, I do not know why we use it?

--
竹密岂妨流水过
山高哪阻野云飞
___
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] Could someone teach me why we use Data.Monoid?

2009-11-15 Thread Nicolas Pouillard
Excerpts from Daniel Schüssler's message of Sun Nov 15 07:51:35 +0100 2009:
 Hi,
Hi,

 -- Invariant 1: There are never two adjacent Lefts or two adjacent Rights
[...]
 normalize (Left a0 : Left a1 : as) = Left (mappend a0 a1) : normalize as
 normalize (Right a0 : Right a1 : as) = Right (mappend a0 a1) : normalize as

If you want to preserve your invariant, I think you should do :

normalize (Left  a0 : Left  a1 : as) = normalize (Left  (mappend a0 a1) : as)
normalize (Right a0 : Right a1 : as) = normalize (Right (mappend a0 a1) : as)

However, maybe it is correct if you only call normalize on (xs ++ ys) where
xs and ys are already normalized so that you have only one point where you can
break this invariant.

Regards,

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-15 Thread Daniel Schüssler
On Sunday 15 November 2009 13:05:08 Nicolas Pouillard wrote:
 Excerpts from Daniel Schüssler's message of Sun Nov 15 07:51:35 +0100 2009:
  Hi,
 
 Hi,

Hi,

 
  -- Invariant 1: There are never two adjacent Lefts or two adjacent Rights
 
 [...]
 
  normalize (Left a0 : Left a1 : as) = Left (mappend a0 a1) : normalize as
  normalize (Right a0 : Right a1 : as) = Right (mappend a0 a1) : normalize
  as
 
 If you want to preserve your invariant, I think you should do :
 
 normalize (Left  a0 : Left  a1 : as) = normalize (Left  (mappend a0 a1) :
  as) normalize (Right a0 : Right a1 : as) = normalize (Right (mappend a0
  a1) : as)
 
 However, maybe it is correct if you only call normalize on (xs ++ ys) where
 xs and ys are already normalized so that you have only one point where you
  can break this invariant.
 
 Regards,
 

You are right :) If `normalize' is meant to normalize arbitrary lists, we'd 
have to use your version. If OTOH we just want to normalize xs ++ ys, we 
shouldn't iterate over the whole list; it'd be better to use Data.Sequence and 
just consider the middle, as you said (I was thinking of free groups, where 
there can be more collapse, but in that case we'd need the analogue your 
version too).


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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-15 Thread Eugene Kirpichov
Hey, I've found terrific slides about monoids!
http://comonad.com/reader/wp-content/uploads/2009/08/IntroductionToMonoids.pdf
Edward Kmett, you rock!

There's more http://comonad.com/reader/2009/iteratees-parsec-and-monoid/
- but the second part was too hard for me to read it fully without
special motivation.

2009/11/15 Daniel Schüssler anotheraddr...@gmx.de:
 On Sunday 15 November 2009 13:05:08 Nicolas Pouillard wrote:
 Excerpts from Daniel Schüssler's message of Sun Nov 15 07:51:35 +0100 2009:
  Hi,

 Hi,

 Hi,


  -- Invariant 1: There are never two adjacent Lefts or two adjacent Rights

 [...]

  normalize (Left a0 : Left a1 : as) = Left (mappend a0 a1) : normalize as
  normalize (Right a0 : Right a1 : as) = Right (mappend a0 a1) : normalize
  as

 If you want to preserve your invariant, I think you should do :

 normalize (Left  a0 : Left  a1 : as) = normalize (Left  (mappend a0 a1) :
  as) normalize (Right a0 : Right a1 : as) = normalize (Right (mappend a0
  a1) : as)

 However, maybe it is correct if you only call normalize on (xs ++ ys) where
 xs and ys are already normalized so that you have only one point where you
  can break this invariant.

 Regards,


 You are right :) If `normalize' is meant to normalize arbitrary lists, we'd
 have to use your version. If OTOH we just want to normalize xs ++ ys, we
 shouldn't iterate over the whole list; it'd be better to use Data.Sequence and
 just consider the middle, as you said (I was thinking of free groups, where
 there can be more collapse, but in that case we'd need the analogue your
 version too).


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




-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-15 Thread Dan Piponi
2009/11/14 Daniel Schüssler anotheraddr...@gmx.de:
  - Product (a,b) and co-product (Either) of monoids
 the coproduct of monoids is actually a bit tricky.

Funny, I was just thinking about that.

I was pondering the article at LTU on Lawvere theories:
http://lambda-the-ultimate.org/node/3235

Essentially the idea is this: monads correspond to algebraic theories
and monad transformers are ways to combine algebraic theories.

But Lawvere theories provide another way to describe algebraic
theories, and hence the things that monads can help with: like side
effects, state and non-determinism.

The advantage of Lawvere theories is there is some nice mathematics
for how to combine them, something that's lacking from monads.

So I just worked through a simple example: combining the Writer monad
with itself. As Lawvere theories there are two ways to combine them:
the product and the sum.

The product corresponds, I think, to the usual monad transformer. This
gives the Writer monad corresponding to the product of monoids.

But the sum gives the Writer monad for the coproduct of monoids. (I
think this is correct, but I'm not 100% sure I totally get Lawvere
theories yet.)

If you think about it, it's a very natural thing to do. If you think
of the Writer monad as being useful to make logs then the coproduct
allows you to interleave two different kinds of logs keeping the
relative order of the entries. The usual monad transformer keeps two
separate logs and so loses the relative ordering information. So it's
actually something you might frequently want in real world code. But I
can't imagine a monad transformer for Writer that would give the
coproduct when combined with another Writer, so I don't think it could
be implemented as such.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-14 Thread Daniel Schüssler
Hi,

  - Product (a,b) and co-product (Either) of monoids

the coproduct of monoids is actually a bit tricky. It could be implemented 
like this:

-- | 
-- Invariant 1: There are never two adjacent Lefts or two adjacent Rights
-- Invariant 2: No elements (Left mempty) or (Right mempty) allowed
newtype Coprod m1 m2 = C [Either m1 m2]
 
instance (Eq m1, Eq m2, Monoid m1, Monoid m2) = Monoid (Coprod m1 m2) where
mempty = C []
mappend (C x1) (C x2) = C (normalize (x1 ++ x2))

normalize [] = []
normalize (Left a0 : as)  | a0 == mempty = normalize as
normalize (Right a0 : as) | a0 == mempty = normalize as
normalize [a] = [a]
normalize (Left a0 : Left a1 : as) = Left (mappend a0 a1) : normalize as
normalize (Right a0 : Right a1 : as) = Right (mappend a0 a1) : normalize as
normalize (a0:as) = a0 : normalize as

inl x = normalize [Left x]
inr x = normalize [Right x]

fold :: (Monoid m1, Monoid m2, Monoid n) =
 (m1 - n) - (m2 - n) - Coprod m1 m2 - n
fold k1 k2 = foldMap (either k1 k2)

--
Alternative version, possibly more efficient? Represent directly as fold:
--
newtype Coprod m1 m2 = C (forall n. Monoid n = (m1 - n) - (m2 - n) - n)

instance Monoid (Coprod m1 m2) where
  mempty = C (\_ _ - mempty)
  mappend (C x) (C x') = 
C (\k1 k2 - mappend (x k1 k2) (x' k1 k2))

inl x = C (\k1 _ - k1 x)
inr x = C (\_ k2 - k2 x) 

--

Question: in the mappend of the second version, we have a choice: We could 
also, when possible, multiply on the *inside*, that is *before* applying 
k1/k2:
---
mappend (C x) (C x') =
 C (\k1 k2 -
 x (\m1 - x' (\m1' - k1 (mappend m1 m1')
(\m2' - mappend (k1 m1) (k2 m2'))
  (\m2 - x' (\m1' - mappend (k2 m2) (k1 m1'))
 (\m2' - k2 (mappend m2 m2')))
---

Now I don't know what the efficiency implications of the two different 
versions are :) Apparently it depends on the relative costs of mappend in 
m1/m2 vs. n, and the cost of computing k1/k2?

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Rafael Gustavo da Cunha Pereira Pinto
Disclaimer: I don't really know all about category theory, so some
definitions might not be absolutely correct.

Monoid is the category of all types that have a empty value and an append
operation.

The best example is a list.

instance Monoid [a] where
mempty  = []
mappend = (++)


Why do I need it? Well, you can think of a function where you need to
incrementally store data.

Storing them to a Monoid, you can start with a list and then change to a
Set, without changing the function itself, because it would be defined based
on the Monoid operations.

instance Ord a = Monoid (Set a) where
mempty  = empty
mappend = union
mconcat = unions

Hope I have helped!

Regards,

Rafael



On Fri, Nov 13, 2009 at 14:14, Magicloud Magiclouds 
magicloud.magiclo...@gmail.com wrote:

 Hi,
  I have looked the concept of monoid and something related, but
 still, I do not know why we use it?

 --
 竹密岂妨流水过
 山高哪阻野云飞

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




-- 
Rafael Gustavo da Cunha Pereira Pinto
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Stephen Tetley
2009/11/13 Rafael Gustavo da Cunha Pereira Pinto rafaelgcpp.li...@gmail.com:

 Monoid is the category of all types that have a empty value and an append
 operation.


Or more generally a neutral element and an associative operation:

The multiplication monoid (1,*)

9*1*1*1 = 9

1 is neutral but you might be hard pressed to consider it _empty_.


Best wishes

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Andrew Coppin

Stephen Tetley wrote:

2009/11/13 Rafael Gustavo da Cunha Pereira Pinto rafaelgcpp.li...@gmail.com:
  

Monoid is the category of all types that have a empty value and an append
operation.




Or more generally a neutral element and an associative operation:

The multiplication monoid (1,*)

9*1*1*1 = 9

1 is neutral but you might be hard pressed to consider it _empty_.
  


This is the thing. If we had a class specifically for containers, that 
could be useful. If we had a class specifically for algebras, that could 
be useful. But a class that represents any possible thing that can 
technically be considered a monoid seems so absurdly general as to be 
almost useless. If you don't know what an operator *does*, being able to 
abstract over it isn't especially helpful...


...in my humble opinion. (Which, obviously, nobody else will agree with.)

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Eugene Kirpichov
There is an astonishing number of things in programming that are monoids:
 - Numbers, addition, 0
 - Numbers, multiplication, 1
 - Lists, concatenation, [] (including strings)
 - Sorted lists, merge with respect to a linear order, []
 - Sets, union, {}
 - Maps, left-biased or right-biased union, {}
 - Maps K-V, union where Vs for same K get merged in some other monoid, {}
 - For any M: Subsets of M, intersection, M
 - Any lattice with an upper bound, minimum, upper bound;
symmetrically for a lower-bounded set
 - If (S, *, u)  is a monoid, then (A - S, \f g x - f x * g x, \x -
u) is a monoid
 - Product (a,b) and co-product (Either) of monoids
 - Parsers, alternation, a parser that always fails
 - etc.

The benefits of calling something a monoid arise from using
general-purpose structures operating on monoids:
 - Finger trees http://apfelmus.nfshost.com/monoid-fingertree.html
 - Aforementioned maps which merge values for a key in a given monoid
 - Aforementioned monoids lifted to functions
 - Monoidal folds (Data.Foldable)
 - ...

2009/11/13 Magicloud Magiclouds magicloud.magiclo...@gmail.com:
 Hi,
  I have looked the concept of monoid and something related, but
 still, I do not know why we use it?

 --
 竹密岂妨流水过
 山高哪阻野云飞

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





-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Magnus Therning
On Fri, Nov 13, 2009 at 4:52 PM, Andrew Coppin
andrewcop...@btinternet.com wrote:
 Stephen Tetley wrote:

 2009/11/13 Rafael Gustavo da Cunha Pereira Pinto
 rafaelgcpp.li...@gmail.com:


 Monoid is the category of all types that have a empty value and an append
 operation.



 Or more generally a neutral element and an associative operation:

 The multiplication monoid (1,*)

 9*1*1*1 = 9

 1 is neutral but you might be hard pressed to consider it _empty_.


 This is the thing. If we had a class specifically for containers, that could
 be useful. If we had a class specifically for algebras, that could be
 useful. But a class that represents any possible thing that can technically
 be considered a monoid seems so absurdly general as to be almost useless.
 If you don't know what an operator *does*, being able to abstract over it
 isn't especially helpful...

 ...in my humble opinion. (Which, obviously, nobody else will agree with.)

But can't you say exactly the same about Monads?

And at times it's useful to be able to switch between getting all
results (List) and getting one (or none, Maybe), no?

/M

-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Magicloud Magiclouds
Hum... simple like that. So you meant the Monoid just
abstracts/represents the ability to build a stack, right?

2009/11/14 Rafael Gustavo da Cunha Pereira Pinto rafaelgcpp.li...@gmail.com:
 Disclaimer: I don't really know all about category theory, so some
 definitions might not be absolutely correct.

 Monoid is the category of all types that have a empty value and an append
 operation.

 The best example is a list.

 instance Monoid [a] where

 mempty  = []
 mappend = (++)



 Why do I need it? Well, you can think of a function where you need to
 incrementally store data.

 Storing them to a Monoid, you can start with a list and then change to a
 Set, without changing the function itself, because it would be defined based
 on the Monoid operations.

 instance Ord a = Monoid (Set a) where

 mempty  = empty
 mappend = union

 mconcat = unions

 Hope I have helped!

 Regards,

 Rafael



 On Fri, Nov 13, 2009 at 14:14, Magicloud Magiclouds
 magicloud.magiclo...@gmail.com wrote:

 Hi,
  I have looked the concept of monoid and something related, but
 still, I do not know why we use it?

 --
 竹密岂妨流水过
 山高哪阻野云飞

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




 --
 Rafael Gustavo da Cunha Pereira Pinto





-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Andrew Coppin

Magnus Therning wrote:

On Fri, Nov 13, 2009 at 4:52 PM, Andrew Coppin
andrewcop...@btinternet.com wrote:
  

A class that represents any possible thing that can technically
be considered a monoid seems so absurdly general as to be almost useless.
If you don't know what an operator *does*, being able to abstract over it
isn't especially helpful...



But can't you say exactly the same about Monads?
  


I know nothing about how mathematicians use monads. However, Haskell 
uses them in one specific way: for controlling (not necessarily 
_sequencing_) statement execution. This is a fairly rigidly-defined notion.


By contrast, Integer forms an infinite family of different monoids, yet 
it can have only a single Monoid instance...


I notice that there's a an Alternative class, which is isomorphic to 
Monoid, but rather than being some arbitrary monoid, it's a monoid with 
a specific meaning. This, I would argue, is far more useful.


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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Magicloud Magiclouds
That is OK. Since understand the basic concept of monoid (I mean the
thing in actual math), the idea here is totally not hard for me. But
the sample here does not show why (or how) we use it in programming,
right?

On Sat, Nov 14, 2009 at 12:48 AM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 2009/11/13 Rafael Gustavo da Cunha Pereira Pinto rafaelgcpp.li...@gmail.com:

 Monoid is the category of all types that have a empty value and an append
 operation.


 Or more generally a neutral element and an associative operation:

 The multiplication monoid (1,*)

 9*1*1*1 = 9

 1 is neutral but you might be hard pressed to consider it _empty_.


 Best wishes

 Stephen
 ___
 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] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Stephen Tetley
2009/11/13 Magnus Therning mag...@therning.org:
 On Fri, Nov 13, 2009 at 4:52 PM, Andrew Coppin
 andrewcop...@btinternet.com wrote:


 This is the thing. If we had a class specifically for containers, that could
 be useful. If we had a class specifically for algebras, that could be
 useful. But a class that represents any possible thing that can technically
 be considered a monoid seems so absurdly general as to be almost useless.
 If you don't know what an operator *does*, being able to abstract over it
 isn't especially helpful...

 ...in my humble opinion. (Which, obviously, nobody else will agree with.)

 But can't you say exactly the same about Monads?

There's a comment about monads for programming that goes along the lines of

'Monads are a just a structure (ADT?), but they happen to be a very good one.

Does anyone know the original version (not my paraphrase) and who the
originator was?

Thanks

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Rafael Gustavo da Cunha Pereira Pinto
*...in my humble opinion. (Which, obviously, nobody else will agree with.)
*

I somewhat agree with your opinion!!

What I miss the most is practical examples:

1) A function that uses a Monoid as a container
2) A function that uses Monoid as algebra

and so on, for most of categories.

I had a hard time understanding monads, not because I didn't understand the
concept of a monad, but because practical uses are missing, except on
Wadler's paper!

Regards

Rafael

On Fri, Nov 13, 2009 at 14:52, Andrew Coppin andrewcop...@btinternet.comwrote:

 Stephen Tetley wrote:

 2009/11/13 Rafael Gustavo da Cunha Pereira Pinto 
 rafaelgcpp.li...@gmail.com:


 Monoid is the category of all types that have a empty value and an append
 operation.




 Or more generally a neutral element and an associative operation:

 The multiplication monoid (1,*)

 9*1*1*1 = 9

 1 is neutral but you might be hard pressed to consider it _empty_.



 This is the thing. If we had a class specifically for containers, that
 could be useful. If we had a class specifically for algebras, that could be
 useful. But a class that represents any possible thing that can technically
 be considered a monoid seems so absurdly general as to be almost useless.
 If you don't know what an operator *does*, being able to abstract over it
 isn't especially helpful...

 ...in my humble opinion. (Which, obviously, nobody else will agree with.)


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




-- 
Rafael Gustavo da Cunha Pereira Pinto
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Magicloud Magiclouds
I see. Then what is about Dual and Endo? Especially Endo, I completely
confused

2009/11/14 Eugene Kirpichov ekirpic...@gmail.com:
 There is an astonishing number of things in programming that are monoids:
  - Numbers, addition, 0
  - Numbers, multiplication, 1
  - Lists, concatenation, [] (including strings)
  - Sorted lists, merge with respect to a linear order, []
  - Sets, union, {}
  - Maps, left-biased or right-biased union, {}
  - Maps K-V, union where Vs for same K get merged in some other monoid, {}
  - For any M: Subsets of M, intersection, M
  - Any lattice with an upper bound, minimum, upper bound;
 symmetrically for a lower-bounded set
  - If (S, *, u)  is a monoid, then (A - S, \f g x - f x * g x, \x -
 u) is a monoid
  - Product (a,b) and co-product (Either) of monoids
  - Parsers, alternation, a parser that always fails
  - etc.

 The benefits of calling something a monoid arise from using
 general-purpose structures operating on monoids:
  - Finger trees http://apfelmus.nfshost.com/monoid-fingertree.html
  - Aforementioned maps which merge values for a key in a given monoid
  - Aforementioned monoids lifted to functions
  - Monoidal folds (Data.Foldable)
  - ...

 2009/11/13 Magicloud Magiclouds magicloud.magiclo...@gmail.com:
 Hi,
  I have looked the concept of monoid and something related, but
 still, I do not know why we use it?

 --
 竹密岂妨流水过
 山高哪阻野云飞

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





 --
 Eugene Kirpichov
 Web IR developer, market.yandex.ru




-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread David Leimbach
On Fri, Nov 13, 2009 at 8:52 AM, Andrew Coppin
andrewcop...@btinternet.comwrote:

 Stephen Tetley wrote:

 2009/11/13 Rafael Gustavo da Cunha Pereira Pinto 
 rafaelgcpp.li...@gmail.com:


 Monoid is the category of all types that have a empty value and an append
 operation.




 Or more generally a neutral element and an associative operation:

 The multiplication monoid (1,*)

 9*1*1*1 = 9

 1 is neutral but you might be hard pressed to consider it _empty_.



 This is the thing. If we had a class specifically for containers, that
 could be useful. If we had a class specifically for algebras, that could be
 useful. But a class that represents any possible thing that can technically
 be considered a monoid seems so absurdly general as to be almost useless.
 If you don't know what an operator *does*, being able to abstract over it
 isn't especially helpful...

 ...in my humble opinion. (Which, obviously, nobody else will agree with.)



Well to your credit, many people wonder what it means for something to
implement the Monoid interface, or even why the Monoid interface is useful.
 Programmers who don't know what Monoids are may not be aware of the varying
alternatives of Monoid implementations.  They're curious things to have, but
are they useful? :-)

Sum vs Product spells out two ways to use Ints in a Monoid context.  But we
could have done the same with the Functor implementation for lists via fmap
now couldn't we?  Is anyone really using Sum and Product where Functors get
the job done?

Practically speaking, I can explain to coworkers the concept of a Functor a
lot easier than Monoids so I don't choose to use Monoids explicitly in my
code.

I do use MonadPlus though, especially with Maybe as it makes a nice
short-circuit syntax around alternatives for potential Nothing results.  So
in a way I'm possibly shooting myself in the foot if I have to explain the
code to someone who was expecting a case or an if expression.






 ___
 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] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Edward Kmett
A monoid is just an associative binary operation with a unit. They appear
all over the place.

Why do we bother to talk about them in programming?

Well, it turns out that there are a lot of ways you can take advantage of
that fairly minimal amount of structure.

For one, you could take any container worth of values that can be mapped
into the monoid and apply the monoid to the elements the container in a left
to right or right to left or arbitrary ordering, and by the magic of
associativity you will get the same answer. Since you are free to
reparenthesize you can even compute the result in parallel.

Normally you have to distinguish between foldr and foldl. When the operation
you are applying is monoidal, you just have fold (from Data.Foldable). And
the container can choose the traversal that makes the most sense for it.

One particularly interesting, if somewhat complex monoid is the 'fingertree'
monoid, which lets you glue together fingertrees of values that have some
other monoidal measure on them.

This is actually a pretty tricky data structure to get right, but it can be
written once and for all (and has been tucked in Data.FingerTree) and is
parameterized on an arbitrary monoidal measure. I find uses for this
structure all over the place. For instance, FingerTrees of ByteStrings make
a great text buffer with fast splicing operations, while still allowing them
to be sliced at arbitrary positions if you use a monoidal measure for the
size.

In my monoids package I have several other monoids of interest. For
instance, if I am interested in reducing a container of values with a
monoid, I can turn to data compression techniques to build a variation on
the container that can be decompressed inside of the monoid. Lempel Ziv 78
describes a compression technique, that can be applied to improve
the sharing of monoidal intermediate results. Viewing the world this way
helps turn data compression techniques into efficiently reducible data
structures.

The fact that you can use associativity to reparenthesize for parallelism,
the unit to avoid having to perfectly subdivide into an exact number of
cores, and that you can feed the result into a fingertree lets you build
structures that you can build initially in parallel, and update
incrementally for a reduced cost.

All for the low low price of using a little bit of mathematical formalism.

I have a few posts on monoids and my monoids package on my blog at
comonad.com, which may help you get your head around their use outside of
the realm of pure mathematics.

-Edward Kmett

On Fri, Nov 13, 2009 at 12:11 PM, Magicloud Magiclouds 
magicloud.magiclo...@gmail.com wrote:

 That is OK. Since understand the basic concept of monoid (I mean the
 thing in actual math), the idea here is totally not hard for me. But
 the sample here does not show why (or how) we use it in programming,
 right?

 On Sat, Nov 14, 2009 at 12:48 AM, Stephen Tetley
 stephen.tet...@gmail.com wrote:
  2009/11/13 Rafael Gustavo da Cunha Pereira Pinto 
 rafaelgcpp.li...@gmail.com:
 
  Monoid is the category of all types that have a empty value and an
 append
  operation.
 
 
  Or more generally a neutral element and an associative operation:
 
  The multiplication monoid (1,*)
 
  9*1*1*1 = 9
 
  1 is neutral but you might be hard pressed to consider it _empty_.
 
 
  Best wishes
 
  Stephen
  ___
  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

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Eugene Kirpichov
For every monoid (M, *, u), the dual to it is the monoid (Dual M, \x y
- y * x, u)
For every type A, there exists the A-endomorphism monoid (A-A, (.),
id). Endo A is just a newtype for A - A.

More simply, dualization is flipping the binary operation, and the
endo monoid is the monoid of functions a-a with composition.

2009/11/13 Magicloud Magiclouds magicloud.magiclo...@gmail.com:
 I see. Then what is about Dual and Endo? Especially Endo, I completely
 confused

 2009/11/14 Eugene Kirpichov ekirpic...@gmail.com:
 There is an astonishing number of things in programming that are monoids:
  - Numbers, addition, 0
  - Numbers, multiplication, 1
  - Lists, concatenation, [] (including strings)
  - Sorted lists, merge with respect to a linear order, []
  - Sets, union, {}
  - Maps, left-biased or right-biased union, {}
  - Maps K-V, union where Vs for same K get merged in some other monoid, {}
  - For any M: Subsets of M, intersection, M
  - Any lattice with an upper bound, minimum, upper bound;
 symmetrically for a lower-bounded set
  - If (S, *, u)  is a monoid, then (A - S, \f g x - f x * g x, \x -
 u) is a monoid
  - Product (a,b) and co-product (Either) of monoids
  - Parsers, alternation, a parser that always fails
  - etc.

 The benefits of calling something a monoid arise from using
 general-purpose structures operating on monoids:
  - Finger trees http://apfelmus.nfshost.com/monoid-fingertree.html
  - Aforementioned maps which merge values for a key in a given monoid
  - Aforementioned monoids lifted to functions
  - Monoidal folds (Data.Foldable)
  - ...

 2009/11/13 Magicloud Magiclouds magicloud.magiclo...@gmail.com:
 Hi,
  I have looked the concept of monoid and something related, but
 still, I do not know why we use it?

 --
 竹密岂妨流水过
 山高哪阻野云飞

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





 --
 Eugene Kirpichov
 Web IR developer, market.yandex.ru




 --
 竹密岂妨流水过
 山高哪阻野云飞




-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Anton van Straaten

Andrew Coppin wrote:
This is the thing. If we had a class specifically for containers, that 
could be useful. If we had a class specifically for algebras, that could 
be useful. But a class that represents any possible thing that can 
technically be considered a monoid seems so absurdly general as to be 
almost useless. 


You don't have to look any further than the Writer monad to find an 
example of how this kind of abstraction is useful.  The Writer monad 
uses a monoid to accumulate results.  The monoid provided to Writer 
could be container-like, like a list; it could be a record whose fields 
are updated with each operation; it could be a number whose value 
changes with each operation; etc.  The point is that it's general: it 
can be any value that can be combined with another value of the same 
type, using some operation to do that combination.


Sigfpe's article about monoids goes into more detail:
http://blog.sigfpe.com/2009/01/haskell-monoids-and-their-uses.html

If you don't know what an operator *does*, being able to 
abstract over it isn't especially helpful...


The author of the Writer monad didn't know, and doesn't need to care, 
what the operator does.  To him, being able to abstract over this 
unknown operator was not only helpful, but critical: without that, you'd 
need a different type of Writer for different types of accumulator.


Indeed, we see that kind of thing regularly in lesser languages, where 
e.g. a logging class might require an instance of a container class to 
log to, so that if you want to do an accumulation that doesn't involve a 
container, you're out of luck.  Or perhaps you get clever and implement 
a container class that actually wraps some non-container like value, so 
that appending to the container updates the value.  Now you've 
reinvented monoids, and proved that the author of the logging class 
*did* need to be able to abstract over an unknown operator, but just 
didn't realize it.


Anton

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread David Place

Magicloud Magiclouds magicloud.magiclo...@gmail.com wrote:

 Message: 26
 Date: Sat, 14 Nov 2009 01:11:27 +0800
 From: Magicloud Magiclouds magicloud.magiclo...@gmail.com
 Subject: Re: [Haskell-cafe] Could someone teach me why we use
   Data.Monoid?
 To: Stephen Tetley stephen.tet...@gmail.com
 Cc: haskell-cafe haskell-cafe@haskell.org
 Message-ID:
   3bd412d40911130911v4f3ac0b9laebca79f59214...@mail.gmail.com
 Content-Type: text/plain; charset=UTF-8
 
 That is OK. Since understand the basic concept of monoid (I mean the
 thing in actual math), the idea here is totally not hard for me. But
 the sample here does not show why (or how) we use it in programming,
 right?


For an example of it's use, you might enjoy reading my article in the 
Monad.Reader  How to Refold a Map.

 http://www.haskell.org/sitewiki/images/6/6a/TMR-Issue11.pdf

Cheers,
David

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Magicloud Magiclouds
Thank you guys. I think I learned a lot. Pretty confusing and interesting.

2009/11/14 Eugene Kirpichov ekirpic...@gmail.com:
 For every monoid (M, *, u), the dual to it is the monoid (Dual M, \x y
 - y * x, u)
 For every type A, there exists the A-endomorphism monoid (A-A, (.),
 id). Endo A is just a newtype for A - A.

 More simply, dualization is flipping the binary operation, and the
 endo monoid is the monoid of functions a-a with composition.

 2009/11/13 Magicloud Magiclouds magicloud.magiclo...@gmail.com:
 I see. Then what is about Dual and Endo? Especially Endo, I completely
 confused

 2009/11/14 Eugene Kirpichov ekirpic...@gmail.com:
 There is an astonishing number of things in programming that are monoids:
  - Numbers, addition, 0
  - Numbers, multiplication, 1
  - Lists, concatenation, [] (including strings)
  - Sorted lists, merge with respect to a linear order, []
  - Sets, union, {}
  - Maps, left-biased or right-biased union, {}
  - Maps K-V, union where Vs for same K get merged in some other monoid, {}
  - For any M: Subsets of M, intersection, M
  - Any lattice with an upper bound, minimum, upper bound;
 symmetrically for a lower-bounded set
  - If (S, *, u)  is a monoid, then (A - S, \f g x - f x * g x, \x -
 u) is a monoid
  - Product (a,b) and co-product (Either) of monoids
  - Parsers, alternation, a parser that always fails
  - etc.

 The benefits of calling something a monoid arise from using
 general-purpose structures operating on monoids:
  - Finger trees http://apfelmus.nfshost.com/monoid-fingertree.html
  - Aforementioned maps which merge values for a key in a given monoid
  - Aforementioned monoids lifted to functions
  - Monoidal folds (Data.Foldable)
  - ...

 2009/11/13 Magicloud Magiclouds magicloud.magiclo...@gmail.com:
 Hi,
  I have looked the concept of monoid and something related, but
 still, I do not know why we use it?

 --
 竹密岂妨流水过
 山高哪阻野云飞

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





 --
 Eugene Kirpichov
 Web IR developer, market.yandex.ru




 --
 竹密岂妨流水过
 山高哪阻野云飞




 --
 Eugene Kirpichov
 Web IR developer, market.yandex.ru




-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Gregory Collins
Magicloud Magiclouds magicloud.magiclo...@gmail.com writes:

 I see. Then what is about Dual and Endo? Especially Endo, I completely
 confused

It should help to look at the instances:

 -- | The dual of a monoid, obtained by swapping the arguments of 'mappend'.
 newtype Dual a = Dual { getDual :: a }
 deriving (Eq, Ord, Read, Show, Bounded)
 
 instance Monoid a = Monoid (Dual a) where
 mempty = Dual mempty
 Dual x `mappend` Dual y = Dual (y `mappend` x)

You can tag a monoidal value as being Dual and then invoking mappend
will swap the argument order.

Re: Endo:

 -- | The monoid of endomorphisms under composition.
 newtype Endo a = Endo { appEndo :: a - a }
 
 instance Monoid (Endo a) where
 mempty = Endo id
 Endo f `mappend` Endo g = Endo (f . g)

It's a way of labelling functions of type a - a (endomorphism) as
being a monoid under composition (the . operator). A short example:

 GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 Prelude import Data.Monoid
 Prelude Data.Monoid let f = ((+2) :: Double - Double)
 Prelude Data.Monoid let g = ((/4) :: Double - Double)
 Prelude Data.Monoid appEndo (Endo f `mappend` Endo g) 4
 3.0

same as (f . g) 4 == 4/4 + 2

 Prelude Data.Monoid appEndo (getDual (Dual (Endo f) `mappend` Dual (Endo 
 g))) 4
 1.5

same as (g . f) 4 == (4+2)/4.

G.
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Stephen Tetley
 Magicloud Magiclouds magicloud.magiclo...@gmail.com wrote:

 That is OK. Since understand the basic concept of monoid (I mean the
 thing in actual math), the idea here is totally not hard for me. But
 the sample here does not show why (or how) we use it in programming,
 right?

Hi Magicloud

Conal Elliott has an interesting paper about designing your programs
in relation to the standard type classes:.

http://conal.net/papers/type-class-morphisms/

Thinking about the data structures and functions in your program with
regards the standard classes is very useful useful for clarifying your
design. And certainly if you decide your data structure fits the
Monoid interface then you will be presenting it to others who use your
program in the 'standard vocabulary'. But even for Monoid which
seemingly presents a simple interface (mempty, mappend) deciding
whether the _container_ you have is naturally a monoid can be
difficult.

A personal example, I've been developing a drawing library for a
couple of months and still can't decide whether a bounding box should
be a monoid (mempty, append) or a groupoid (just append) where append
in both cases is union. Even though I haven't resolved this problem,
having the framework of monoid versus groupoid at least gives me the
_terminology_ to consider the problem.

Best wishes

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Reid Barton
On Fri, Nov 13, 2009 at 08:37:57PM +0300, Eugene Kirpichov wrote:
 For every monoid (M, *, u), the dual to it is the monoid (Dual M, \x y
 - y * x, u)

The entirely standard name for this is the opposite monoid.  The only
places I have seen the name dual monoid used to mean opposite monoid
are in Data.Monoid and subsequently by some Haskellers.

A very good reason not to use the name dual monoid is that the basic
point of duality is contravariance.  The prototypical example of
duality is the dual V^* of a finite-dimensional vector space V,
defined as the vector space of all linear maps from V to the ground
field.  If f : V - W is a linear map, then we get an induced linear
map f^* : W^* - V^* by precomposing with f.  Note that f^* goes in
the other direction; the functor -^* is contravariant.

Perhaps a more familiar example is from classical Boolean algebra.  If
P is a proposition, it's sensible to call not-P the dual of P, since
an implication P - Q yields an implication not-Q - not-P.  (This is
closely related to the previous example, since not-P is the statement
P - false.)

The notion of opposite monoids is not an example of duality.  Given a
monoid homomorphism f : M - N, there is an induced opposite
homomorphism f^op : M^op - N^op, which is the same as f on elements.
It goes the same direction as f; -^op is a covariant functor.

If you're not convinced by these arguments, try googling for opposite
monoid and dual monoid to see the standard usage for yourself.
There is no standard meaning for the phrase dual monoid, but I would
venture that it is never used to mean opposite monoid in the
mathematical literature.

(Sorry for the rant.)

Regards,
Reid Barton

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Edward Kmett
On Fri, Nov 13, 2009 at 1:10 PM, Stephen Tetley stephen.tet...@gmail.comwrote:

  Magicloud Magiclouds magicloud.magiclo...@gmail.com wrote:

  That is OK. Since understand the basic concept of monoid (I mean the
  thing in actual math), the idea here is totally not hard for me. But
  the sample here does not show why (or how) we use it in programming,
  right?

 Hi Magicloud

 Conal Elliott has an interesting paper about designing your programs
 in relation to the standard type classes:.

 http://conal.net/papers/type-class-morphisms/

 Thinking about the data structures and functions in your program with
 regards the standard classes is very useful useful for clarifying your
 design. And certainly if you decide your data structure fits the
 Monoid interface then you will be presenting it to others who use your
 program in the 'standard vocabulary'. But even for Monoid which
 seemingly presents a simple interface (mempty, mappend) deciding
 whether the _container_ you have is naturally a monoid can be
 difficult.

 A personal example, I've been developing a drawing library for a
 couple of months and still can't decide whether a bounding box should
 be a monoid (mempty, append) or a groupoid (just append) where append
 in both cases is union. Even though I haven't resolved this problem,
 having the framework of monoid versus groupoid at least gives me the
 _terminology_ to consider the problem.



Watch out, in more common parlance, having just an binary operation is a
magma, while having a category with full inverses yields a groupoid. I
haven't seen many people use the older groupoid term for magmas, if only
because they started to have naming conflicts with the category theory
people, and Bourbaki's 'magma' was available and unambiguous. =)

And of course magma is not to be confused with the notion of a semigroup,
which is a binary associative operation, and is therefore much more similar
to a monoid in that all it lacks is a unit.

-Edward Kmett



 Best wishes

 Stephen
  ___
 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] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Stephen Tetley
Hi Edward

Many thanks.

I've mostly used groupoid for 'string concatenation' on types that I
don't consider to have useful empty (e.g PostScript paths, bars of
music...), as string concatenation is associative it would have been
better if I'd used semigroup in the first place (bounding box union
certainly looks associative to me as well).

Are magma and semigroup exclusive, i.e. in the presence of both a
Magma class and a Semigroup class would it be correct  that Magma
represents only 'magma-op' where op isn't associative and Semigroup
represents 'semigroup-op' where the op is associative?

When I decided to use a Groupoid class, I was being a bit lazy-minded
and felt it could represent a general binary op that _doesn't have to
be_ associative but potentially could be.


Thanks again

Stephen


2009/11/13 Edward Kmett ekm...@gmail.com:




 Watch out, in more common parlance, having just an binary operation is a
 magma, while having a category with full inverses yields a groupoid. I
 haven't seen many people use the older groupoid term for magmas, if only
 because they started to have naming conflicts with the category theory
 people, and Bourbaki's 'magma' was available and unambiguous. =)

 And of course magma is not to be confused with the notion of a semigroup,
 which is a binary associative operation, and is therefore much more similar
 to a monoid in that all it lacks is a unit.

 -Edward Kmett

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Magnus Therning
On 13/11/09 18:43, Edward Kmett wrote:
[..]
 Watch out, in more common parlance, having just an binary operation is a
 magma, while having a category with full inverses yields a groupoid. I
 haven't seen many people use the older groupoid term for magmas, if only
 because they started to have naming conflicts with the category theory
 people, and Bourbaki's 'magma' was available and unambiguous. =)
  
 And of course magma is not to be confused with the notion of a
 semigroup, which is a binary associative operation, and is therefore
 much more similar to a monoid in that all it lacks is a unit.

I suspect there'll be some bald (evil) haskeller out there filing a bug report
right now for the type class Magma (with the alias LiquidHotMagma of course).
Using it will require programming with just one hand though, since one pinkie
must be between one's teeth.

/M

-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread Duncan Coutts
On Fri, 2009-11-13 at 15:16 -0200, Rafael Gustavo da Cunha Pereira Pinto
wrote:
 
 ...in my humble opinion. (Which, obviously, nobody else will agree
 with.)
 
 I somewhat agree with your opinion!!
 
 What I miss the most is practical examples:
 
 1) A function that uses a Monoid as a container
 2) A function that uses Monoid as algebra
 
 and so on, for most of categories.

Here are two practical examples.

Most aggregate statistic functions (think of all the aggregate functions
in SQL, sum, average, stddev) are monoids. So you can write a generic
compute statistics function for some dataset and then use it for any
monoid statistic function that you come up with. Even better, your
compute statistics function can take advantage of parallelism since
the monoid operation is associative.

Another practical example is config files and (equivalently) sets of
command line flags. These things are records containing fields. But each
field is a monoid (usually list or last) and this lets you make the
whole record a monoid, point wise. This lets you do useful stuff like
combining configuration from multiple sources (like a config file,
defaults and command line) using just mappend.

Now you could say, why make it a monoid, why not just provide a function
`combineStats` or `combineConfig`. There are two reasons, one is that it
provides documentation, it says this thing is an instance of that
well-known pattern. Secondly it sometimes lets you reuse generic
functions (eg Data.Traversable).

Duncan

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


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread wren ng thornton

Magicloud Magiclouds wrote:

Hum... simple like that. So you meant the Monoid just
abstracts/represents the ability to build a stack, right?


The key idea behind monoids is that they define sequence. To get a 
handle on what that means, it helps to think first about the free 
monoid. If we have some set S, then we can generate a monoid which 
describes sequences of elements drawn from S (the neutral element is the 
empty sequence, the operator is juxtaposition). The tricky thing is that 
we *really* mean sequences. That is, what we're abstracting over is the 
tree structure behind a sequence. So if we have a sequence like abcd 
we're abstracting over all the trees (a(b(cd))), (a((bc)d)), 
((ab)(cd)),... including all the trees with neutral elements inserted 
anywhere: ((a)(b(cd))), the other ((a)(b(cd))), (a((b)(cd))),... The 
places where monoids are useful are exactly those places where we want 
to abstract over all those trees and consider them equal. By considering 
them equal, we know it's safe to pick any one of them arbitrarily so as 
to maximize performance, code legibility, or other factors.


One use is when we realize the significance of distinguishing sequences 
from lists. Sequences have no tree structure because they abstract over 
all of them, whereas lists convert everything into a canonical 
right-branching structure. Difference-lists optimize lists by replacing 
them with a different structure that better represents the true 
equivalence between different ways of appending. Finger trees are 
another way of optimizing lists which is deeply connected to monoids.


Another place that's helpful is if we want to fold over the sequence. We 
can parallelize any such fold because we know that the grouping and 
sequence of reductions are all equivalent. This is helpful for speeding 
up some computations, but it also lets us think about things like 
parallel parsing--- that is, actually building up the AST in parallel, 
working on the whole file at once rather than starting from the 
beginning and moving towards the end.


Another place it's useful is when we have some sort of accumulator where 
we want to be able to accumulate groups of things as well as individual 
things. The prime example here is Duncan Coutts' example of supporting 
multiple config files (where commandline flags can be thought of as an 
additional config file). CSS is another example of this sort of accretion.


Just to build on the config file example a bit more. What sorts of 
behavior do we expect from programs when some flag is specified more 
than once? The three most common strategies are: first one wins, last 
one wins, and take all of them as a list. All three of these are 
trivially monoids. Some of the stranger behaviors we find are also 
monoids. For example, some programs interpret more than one -v flag as 
incrementing the level of verbosity. This is just the free monoid 
generated by a singleton set, aka unary numbers, aka Peano integers. We 
could generalize this so that we accept multiple -v=N flags which 
increment the verbosity by N, in which case we get the (Int,0,+) monoid. 
Given all these different monoids, we can define the type signature of a 
config file as a mapping from flags to the monoids used to resolve them. 
And doing so is far and away the most elegant approach to config 
handling I've seen anywhere.



So monoid == sequence. Similarly, commutative monoid == set. Stacks 
don't have a heck of a lot of equivalences, so I can't think of a nice 
algebraic structure that equates to them off-hand. (And the 
sequentiality of monads comes from being monoids on the category of 
endofunctors.)


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Could someone teach me why we use Data.Monoid?

2009-11-13 Thread wren ng thornton

Stephen Tetley wrote:

Hi Edward

Many thanks.

I've mostly used groupoid for 'string concatenation' on types that I
don't consider to have useful empty (e.g PostScript paths, bars of
music...), as string concatenation is associative it would have been
better if I'd used semigroup in the first place (bounding box union
certainly looks associative to me as well).

Are magma and semigroup exclusive, i.e. in the presence of both a
Magma class and a Semigroup class would it be correct  that Magma
represents only 'magma-op' where op isn't associative and Semigroup
represents 'semigroup-op' where the op is associative?



Magma = exists S : Set
  , exists _*_ : (S,S)-S

Semigroup = exists (S,*) : Magma
  , forall a b c:S. a*(b*c) = (a*b)*c

Monoid= exists (S,*,assoc) : Semigroup
  , exists e:S. forall a:S. e*a = a = a*e

Group = exists (S,*,assoc,e) : Monoid
  , forall a:S. exists a':S. a'*a = e = a*a'

Personally, I don't think magmas are worth a type class. They have no 
structure and obey no laws which aren't already encoded in the type of 
the binop. As such, I'd just pass the binop around. There are far too 
many magmas to warrant making them implicit arguments and trying to 
deduce which one to use based only on the type of the carrier IMO.


But if we did have such a class, then yes the (Magma s) constraint would 
only imply the existence of a binary operator which s is closed under, 
whereas the (Semigroup s) constraint would add an additional implication 
that the binary operator is associative. And we should have Semigroup 
depend on Magma since every semigroup is a magma. Unfortunately, 
Haskell's type classes don't have any general mechanism for stating laws 
as part of the class definition nor providing proofs as part of the 
instance.




When I decided to use a Groupoid class, I was being a bit lazy-minded
and felt it could represent a general binary op that _doesn't have to
be_ associative but potentially could be.


But groupoids do have to be associative (when defined). They're just 
like groups, except that the binop can be a partial function, and 
instead of a neutral element they have the weaker identity criterion (if 
a*b is defined then a*b*b' = a and a'*a*b = b).


Groupoids don't make a lot of sense to me as string concatenation-like 
because of the inversion operator. Some types will support the idea of 
negative letters without supporting empty strings, but I can't think 
of any compelling examples off-hand. Then again, I deal with a lot of 
monoids which aren't groups and a lot of semirings which aren't rings, 
so I don't see a lot of inversion outside of the canonical examples.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe