Re: [Haskell-cafe] Monoids and newtypes

2009-01-27 Thread Derek Elkins
On Tue, 2009-01-27 at 08:51 -0800, Anish Muttreja wrote:
 On Thu, 22 Jan 2009 09:46:19 -0800, Derek Elkins derek.a.elk...@gmail.com 
 wrote:
 
 
 The old wiki had an excellent page that has not been replicated either
  verbatim or in spirit in the new wiki.
  http://web.archive.org/web/20060831090007/http://www.haskell.org/hawiki/CommonHaskellIdioms
 
 Thanks, this is really useful.
 
 There is a wikisnapshot on haskell.org 
 http://haskell.org/wikisnapshot/CommonHaskellIdioms.html
 which looks like a replication and has more working links than the 
 web.archive.org page.

The snapshot is quite a bit older than what is available on archive.org.
You should be able to stick the link to any page that doesn't work into
archive.org and get a version that does work (i.e. re-search for the
page.)

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


[Haskell-cafe] Monoids and newtypes

2009-01-22 Thread Ketil Malde

One wart that was briefly mentioned during the Great Monoid Naming
Thread of 2009 is the need to wrap types in newtypes to provide multiple
instances of the same class with different semantics -- the archetypical
example being Integer as a monoid over addition as well as
multiplication. 

I was just wondering if not phantom types might serve here as an
alternative way to go about that.  Here's a small example illustrating
it: 


{-# LANGUAGE EmptyDataDecls  #-}
{-# LANGUAGE FlexibleInstances  #-}

module Monoids where
import Data.Monoid

data Foo a = Foo Integer deriving (Show, Eq)

data Additive
data Multiplicative

instance Monoid (Foo Additive) where
mappend (Foo x) (Foo y) = Foo (x+y)
mempty = Foo 0

instance Monoid (Foo Multiplicative) where
mappend (Foo x) (Foo y) = Foo (x*y)
mempty = Foo 1

instance Num (Foo a) where
fromInteger x = Foo x
Foo x + Foo y = Foo (x+y)
Foo x * Foo y = Foo (x*y)
signum (Foo x) = Foo (signum x)


Loading this into ghci, you get:
*Monoids mconcat [1,2]

interactive:1:0:
Ambiguous type variable `t' in the constraints:
  `Monoid t' arising from a use of `mconcat' at interactive:1:0-12
  `Num t' arising from the literal `2' at interactive:1:11
Probable fix: add a type signature that fixes these type variable(s)
*Monoids mconcat [1,2::Foo Additive]
Foo 3
*Monoids mconcat [1,2::Foo Multiplicative]
Foo 2

(This can of course be prettified a bit by omitting the constructor
from the Show instance).  

Any thought about this, pro/contra the newtype method?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoids and newtypes

2009-01-22 Thread Derek Elkins
On Thu, 2009-01-22 at 16:11 +0100, Ketil Malde wrote:
 One wart that was briefly mentioned during the Great Monoid Naming
 Thread of 2009 is the need to wrap types in newtypes to provide multiple
 instances of the same class with different semantics -- the archetypical
 example being Integer as a monoid over addition as well as
 multiplication. 
 
 I was just wondering if not phantom types might serve here as an
 alternative way to go about that.  Here's a small example illustrating
 it: 
 
 
 {-# LANGUAGE EmptyDataDecls  #-}
 {-# LANGUAGE FlexibleInstances  #-}
 
 module Monoids where
 import Data.Monoid
 
 data Foo a = Foo Integer deriving (Show, Eq)
 
 data Additive
 data Multiplicative
 
 instance Monoid (Foo Additive) where
 mappend (Foo x) (Foo y) = Foo (x+y)
 mempty = Foo 0
 
 instance Monoid (Foo Multiplicative) where
 mappend (Foo x) (Foo y) = Foo (x*y)
 mempty = Foo 1
 
 instance Num (Foo a) where
 fromInteger x = Foo x
 Foo x + Foo y = Foo (x+y)
 Foo x * Foo y = Foo (x*y)
 signum (Foo x) = Foo (signum x)
 
 
 Loading this into ghci, you get:
 *Monoids mconcat [1,2]
 
 interactive:1:0:
 Ambiguous type variable `t' in the constraints:
   `Monoid t' arising from a use of `mconcat' at interactive:1:0-12
   `Num t' arising from the literal `2' at interactive:1:11
 Probable fix: add a type signature that fixes these type variable(s)
 *Monoids mconcat [1,2::Foo Additive]
 Foo 3
 *Monoids mconcat [1,2::Foo Multiplicative]
 Foo 2
 
 (This can of course be prettified a bit by omitting the constructor
 from the Show instance).  
 
 Any thought about this, pro/contra the newtype method?
 

The old wiki had an excellent page that has not been replicated either
verbatim or in spirit in the new wiki.
http://web.archive.org/web/20060831090007/http://www.haskell.org/hawiki/CommonHaskellIdioms

This lists many small tips and tricks that Haskell programmers have
discovered/used throughout the years.

This particular example is an example of using wrapper types to attach a
phantom type as described here:
http://web.archive.org/web/20070614230306/http://haskell.org/hawiki/WrapperTypes

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


Re: [Haskell-cafe] Monoids and newtypes

2009-01-22 Thread David Menendez
On Thu, Jan 22, 2009 at 10:11 AM, Ketil Malde ke...@malde.org wrote:

 I was just wondering if not phantom types might serve here as an
 alternative way to go about that.  Here's a small example illustrating
 it:
...
 *Monoids mconcat [1,2::Foo Additive]
 Foo 3
 *Monoids mconcat [1,2::Foo Multiplicative]
 Foo 2

 (This can of course be prettified a bit by omitting the constructor
 from the Show instance).

 Any thought about this, pro/contra the newtype method?

I'm not sure that requiring type annotations is less intrusive than
using a wrapper or an explicit dictionary. But there may be types
where this sort of thing makes sense to do.


My favorite alternative to Monoid uses labeled instances.

data Proxy l   -- empty, to ensure that labels are never examined

class LMonoid label where
type Carrier label :: *
unit :: Proxy label - Carrier label
mult :: Proxy label - Carrier label - Carrier label - Carrier label

data Sum a
sum_ :: Proxy (Sum a)
sum_ = undefined

instance Num a = LMonoid (Sum a) where
type Carrier (Sum a) = a
unit _ = 0
mult _ = (+)

-- this works nicely with the writer monad

data Writer l a = W (Carrier l) a

instance (LMonoid l) = Monad (Writer l) where
return a = W (unit (undefined :: Proxy l)) a
(W o1 a) = f = let W o2 b = f a in W (mult (undefined :: Proxy l) o1 o2) b

tell :: Carrier l - Writer l ()
tell x = W x ()

-- and with Foldable

class Foldable f where
fold :: (LMonoid l) = Proxy l - f (Carrier l) - Carrier l

-- e.g., fold sum_ [1,2,3]

-- and it works well with Monoid

data Std a
instance (Monoid a) = LMonoid (Std a) where
unit _ = mempty
mult _ = mappend

newtype WrapL l = WrapL (Carrier l)

instance LMonoid l = Monoid (WrapL l) where
mempty = WrapL (unit (undefined :: Proxy l))
mappend (Wrap x) (Wrap y) = WrapL (mult (undefined::l) x y)

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe