Re: [Haskell-cafe] Helper classes for Generics

2012-03-12 Thread José Pedro Magalhães
Hi Reiner,

It is indeed not strictly necessary to define such helper classes for kind
* generic functions. You do need them for kind * - * functions, though.
Also, I think they should always be used because they help keep things
separate. If we use an implementation of generics with DataKinds [1], then
the helper classes always have a different kind from the user-facing
classes.


Cheers,
Pedro

[1]
http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#Kindpolymorphicoverhaul

On Mon, Mar 12, 2012 at 04:27, Reiner Pope reiner.p...@gmail.com wrote:

 Hi all,

 I've been playing with GHC's new generics features (see
 http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html).
 All the documentation I've seen suggests creating a helper class -- for
 instance, the GSerialize class in the above link -- on which one defines
 generic instances.

 It seems to me that this isn't necessary. For example, here's the the
 example from the GHC docs, but without a helper class:

  -- set the phantom type of Rep to (), to avoid ambiguity
  from0 :: Generic a = a - Rep a ()
  from0 = from
 
  data Bit = O | I
 
  class Serialize a where
put :: a - [Bit]
 
default put :: (Generic a, Serialize (Rep a ())) = a - [Bit]
put = put . from0
 
  instance Serialize (U1 x) where
put U1 = []
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :*: b) x)
 where
put (x :*: y) = put x ++ put y
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :+: b) x)
 where
put (L1 x) = O : put x
put (R1 x) = I : put x
 
  instance (Serialize (a x)) = Serialize (M1 i c a x) where
put (M1 x) = put x
 
  instance (Serialize a) = Serialize (K1 i a x) where
put (K1 x) = put x

 Is there a reason to prefer using helper classes? Or perhaps we should
 update the wiki page (http://www.haskell.org/haskellwiki/Generics) to
 avoid using helper classes?

 Regards,
 Reiner

 ___
 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] Helper classes for Generics

2012-03-12 Thread Yves Parès
I'd have a question concerning GHC.Generics: how does it relate to SYB's
Data.Generics?
Is it intended to replace it or complete it?
In other words: does class Data.Generics.Data class do things that class
GHC.Generics.Generic can't do?


Le 12 mars 2012 04:27, Reiner Pope reiner.p...@gmail.com a écrit :

 Hi all,

 I've been playing with GHC's new generics features (see
 http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html).
 All the documentation I've seen suggests creating a helper class -- for
 instance, the GSerialize class in the above link -- on which one defines
 generic instances.

 It seems to me that this isn't necessary. For example, here's the the
 example from the GHC docs, but without a helper class:

  -- set the phantom type of Rep to (), to avoid ambiguity
  from0 :: Generic a = a - Rep a ()
  from0 = from
 
  data Bit = O | I
 
  class Serialize a where
put :: a - [Bit]
 
default put :: (Generic a, Serialize (Rep a ())) = a - [Bit]
put = put . from0
 
  instance Serialize (U1 x) where
put U1 = []
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :*: b) x)
 where
put (x :*: y) = put x ++ put y
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :+: b) x)
 where
put (L1 x) = O : put x
put (R1 x) = I : put x
 
  instance (Serialize (a x)) = Serialize (M1 i c a x) where
put (M1 x) = put x
 
  instance (Serialize a) = Serialize (K1 i a x) where
put (K1 x) = put x

 Is there a reason to prefer using helper classes? Or perhaps we should
 update the wiki page (http://www.haskell.org/haskellwiki/Generics) to
 avoid using helper classes?

 Regards,
 Reiner

 ___
 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] Helper classes for Generics

2012-03-12 Thread José Pedro Magalhães
Hi Yves,

GHC.Generics [1] and SYB [2] are two rather different approaches to generic
programming. There are things that can be done in one but not in the other,
and there are things that are easier on one rather than the other. For
instance, SYB tends to be very useful for large AST transformations, with
functions that have a general behaviour but a couple of particular cases
for a few constructors. GHC.Generics, on the other hand, can encode
functions such as generic fmap and traverse. It lends itself better to
optimisation since it doesn't use runtime casts, and as such tends to be
faster than SYB. It isn't planned to replace SYB.


Cheers,
Pedro

[1] http://www.haskell.org/haskellwiki/Generics
[2] http://www.cs.uu.nl/wiki/bin/view/GenericProgramming/SYB

On Mon, Mar 12, 2012 at 16:35, Yves Parès yves.pa...@gmail.com wrote:

 I'd have a question concerning GHC.Generics: how does it relate to SYB's
 Data.Generics?
 Is it intended to replace it or complete it?
 In other words: does class Data.Generics.Data class do things that class
 GHC.Generics.Generic can't do?


 Le 12 mars 2012 04:27, Reiner Pope reiner.p...@gmail.com a écrit :

  Hi all,

 I've been playing with GHC's new generics features (see
 http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html).
 All the documentation I've seen suggests creating a helper class -- for
 instance, the GSerialize class in the above link -- on which one defines
 generic instances.

 It seems to me that this isn't necessary. For example, here's the the
 example from the GHC docs, but without a helper class:

  -- set the phantom type of Rep to (), to avoid ambiguity
  from0 :: Generic a = a - Rep a ()
  from0 = from
 
  data Bit = O | I
 
  class Serialize a where
put :: a - [Bit]
 
default put :: (Generic a, Serialize (Rep a ())) = a - [Bit]
put = put . from0
 
  instance Serialize (U1 x) where
put U1 = []
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :*: b) x)
 where
put (x :*: y) = put x ++ put y
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :+: b) x)
 where
put (L1 x) = O : put x
put (R1 x) = I : put x
 
  instance (Serialize (a x)) = Serialize (M1 i c a x) where
put (M1 x) = put x
 
  instance (Serialize a) = Serialize (K1 i a x) where
put (K1 x) = put x

 Is there a reason to prefer using helper classes? Or perhaps we should
 update the wiki page (http://www.haskell.org/haskellwiki/Generics) to
 avoid using helper classes?

 Regards,
 Reiner

 ___
 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] Helper classes for Generics

2012-03-12 Thread Yves Parès
Thanks for the clarification.
But could not class Data have been used for generic Deriving of classes? I
imagine it would have been harder, but I fail to see if would have been
possible...

Le 12 mars 2012 16:58, José Pedro Magalhães j...@cs.uu.nl a écrit :

 Hi Yves,

 GHC.Generics [1] and SYB [2] are two rather different approaches to
 generic programming. There are things that can be done in one but not in
 the other, and there are things that are easier on one rather than the
 other. For instance, SYB tends to be very useful for large AST
 transformations, with functions that have a general behaviour but a couple
 of particular cases for a few constructors. GHC.Generics, on the other
 hand, can encode functions such as generic fmap and traverse. It lends
 itself better to optimisation since it doesn't use runtime casts, and as
 such tends to be faster than SYB. It isn't planned to replace SYB.


 Cheers,
 Pedro

 [1] http://www.haskell.org/haskellwiki/Generics
 [2] http://www.cs.uu.nl/wiki/bin/view/GenericProgramming/SYB


 On Mon, Mar 12, 2012 at 16:35, Yves Parès yves.pa...@gmail.com wrote:

 I'd have a question concerning GHC.Generics: how does it relate to SYB's
 Data.Generics?
 Is it intended to replace it or complete it?
 In other words: does class Data.Generics.Data class do things that class
 GHC.Generics.Generic can't do?


 Le 12 mars 2012 04:27, Reiner Pope reiner.p...@gmail.com a écrit :

  Hi all,

 I've been playing with GHC's new generics features (see
 http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html).
 All the documentation I've seen suggests creating a helper class -- for
 instance, the GSerialize class in the above link -- on which one defines
 generic instances.

 It seems to me that this isn't necessary. For example, here's the the
 example from the GHC docs, but without a helper class:

  -- set the phantom type of Rep to (), to avoid ambiguity
  from0 :: Generic a = a - Rep a ()
  from0 = from
 
  data Bit = O | I
 
  class Serialize a where
put :: a - [Bit]
 
default put :: (Generic a, Serialize (Rep a ())) = a - [Bit]
put = put . from0
 
  instance Serialize (U1 x) where
put U1 = []
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :*: b) x)
 where
put (x :*: y) = put x ++ put y
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :+: b) x)
 where
put (L1 x) = O : put x
put (R1 x) = I : put x
 
  instance (Serialize (a x)) = Serialize (M1 i c a x) where
put (M1 x) = put x
 
  instance (Serialize a) = Serialize (K1 i a x) where
put (K1 x) = put x

 Is there a reason to prefer using helper classes? Or perhaps we should
 update the wiki page (http://www.haskell.org/haskellwiki/Generics) to
 avoid using helper classes?

 Regards,
 Reiner

 ___
 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] Helper classes for Generics

2012-03-12 Thread José Pedro Magalhães
It could, yes. Actually, using DefaultSignatures you can probably use SYB
for defining classes with generic default methods, by adding Data and
Typeable constraints instead of Generic.


Cheers,
Pedro

2012/3/12 Yves Parès yves.pa...@gmail.com

 Thanks for the clarification.
 But could not class Data have been used for generic Deriving of classes? I
 imagine it would have been harder, but I fail to see if would have been
 possible...

 Le 12 mars 2012 16:58, José Pedro Magalhães j...@cs.uu.nl a écrit :

 Hi Yves,

 GHC.Generics [1] and SYB [2] are two rather different approaches to
 generic programming. There are things that can be done in one but not in
 the other, and there are things that are easier on one rather than the
 other. For instance, SYB tends to be very useful for large AST
 transformations, with functions that have a general behaviour but a couple
 of particular cases for a few constructors. GHC.Generics, on the other
 hand, can encode functions such as generic fmap and traverse. It lends
 itself better to optimisation since it doesn't use runtime casts, and as
 such tends to be faster than SYB. It isn't planned to replace SYB.


 Cheers,
 Pedro

 [1] http://www.haskell.org/haskellwiki/Generics
 [2] http://www.cs.uu.nl/wiki/bin/view/GenericProgramming/SYB


 On Mon, Mar 12, 2012 at 16:35, Yves Parès yves.pa...@gmail.com wrote:

 I'd have a question concerning GHC.Generics: how does it relate to SYB's
 Data.Generics?
 Is it intended to replace it or complete it?
 In other words: does class Data.Generics.Data class do things that class
 GHC.Generics.Generic can't do?


 Le 12 mars 2012 04:27, Reiner Pope reiner.p...@gmail.com a écrit :

  Hi all,

 I've been playing with GHC's new generics features (see
 http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html).
 All the documentation I've seen suggests creating a helper class -- for
 instance, the GSerialize class in the above link -- on which one defines
 generic instances.

 It seems to me that this isn't necessary. For example, here's the the
 example from the GHC docs, but without a helper class:

  -- set the phantom type of Rep to (), to avoid ambiguity
  from0 :: Generic a = a - Rep a ()
  from0 = from
 
  data Bit = O | I
 
  class Serialize a where
put :: a - [Bit]
 
default put :: (Generic a, Serialize (Rep a ())) = a - [Bit]
put = put . from0
 
  instance Serialize (U1 x) where
put U1 = []
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :*: b)
 x) where
put (x :*: y) = put x ++ put y
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :+: b)
 x) where
put (L1 x) = O : put x
put (R1 x) = I : put x
 
  instance (Serialize (a x)) = Serialize (M1 i c a x) where
put (M1 x) = put x
 
  instance (Serialize a) = Serialize (K1 i a x) where
put (K1 x) = put x

 Is there a reason to prefer using helper classes? Or perhaps we should
 update the wiki page (http://www.haskell.org/haskellwiki/Generics) to
 avoid using helper classes?

 Regards,
 Reiner

 ___
 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


[Haskell-cafe] Helper classes for Generics

2012-03-11 Thread Reiner Pope
Hi all,

I've been playing with GHC's new generics features (see 
http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html).
 All the documentation I've seen suggests creating a helper class -- for 
instance, the GSerialize class in the above link -- on which one defines 
generic instances. 

It seems to me that this isn't necessary. For example, here's the the example 
from the GHC docs, but without a helper class:

 -- set the phantom type of Rep to (), to avoid ambiguity
 from0 :: Generic a = a - Rep a ()
 from0 = from
 
 data Bit = O | I
 
 class Serialize a where
   put :: a - [Bit]
 
   default put :: (Generic a, Serialize (Rep a ())) = a - [Bit]
   put = put . from0
 
 instance Serialize (U1 x) where
   put U1 = []
 
 instance (Serialize (a x), Serialize (b x)) = Serialize ((a :*: b) x) where
   put (x :*: y) = put x ++ put y
 
 instance (Serialize (a x), Serialize (b x)) = Serialize ((a :+: b) x) where
   put (L1 x) = O : put x
   put (R1 x) = I : put x
 
 instance (Serialize (a x)) = Serialize (M1 i c a x) where
   put (M1 x) = put x
 
 instance (Serialize a) = Serialize (K1 i a x) where
   put (K1 x) = put x

Is there a reason to prefer using helper classes? Or perhaps we should update 
the wiki page (http://www.haskell.org/haskellwiki/Generics) to avoid using 
helper classes?

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