[commit: base] master: Add Generic instances to GHC.Generics representation types (d642155)
José Pedro Magalhães
jpm at cs.uu.nl
Tue Jan 15 14:12:49 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/packages/base
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/d642155c44fa2b09f38d77d8ebda9dec0a18c890
>---------------------------------------------------------------
commit d642155c44fa2b09f38d77d8ebda9dec0a18c890
Author: Jose Pedro Magalhaes <jpm at cs.ox.ac.uk>
Date: Tue Jan 15 13:12:37 2013 +0000
Add Generic instances to GHC.Generics representation types
>---------------------------------------------------------------
GHC/Generics.hs | 22 +++++++++++-----------
1 files changed, 11 insertions(+), 11 deletions(-)
diff --git a/GHC/Generics.hs b/GHC/Generics.hs
index 5ebaa18..649f1f1 100644
--- a/GHC/Generics.hs
+++ b/GHC/Generics.hs
@@ -63,38 +63,38 @@ data V1 p
-- | Unit: used for constructors without arguments
data U1 p = U1
- deriving (Eq, Read, Show)
+ deriving (Eq, Read, Show, Generic)
-- | Used for marking occurrences of the parameter
newtype Par1 p = Par1 { unPar1 :: p }
- deriving (Eq, Read, Show)
+ deriving (Eq, Read, Show, Generic)
-- | Recursive calls of kind * -> *
newtype Rec1 f p = Rec1 { unRec1 :: f p }
- deriving (Eq, Read, Show)
+ deriving (Eq, Read, Show, Generic)
-- | Constants, additional parameters and recursion of kind *
newtype K1 i c p = K1 { unK1 :: c }
- deriving (Eq, Read, Show)
+ deriving (Eq, Read, Show, Generic)
-- | Meta-information (constructor names, etc.)
newtype M1 i c f p = M1 { unM1 :: f p }
- deriving (Eq, Read, Show)
+ deriving (Eq, Read, Show, Generic)
-- | Sums: encode choice between constructors
infixr 5 :+:
data (:+:) f g p = L1 (f p) | R1 (g p)
- deriving (Eq, Read, Show)
+ deriving (Eq, Read, Show, Generic)
-- | Products: encode multiple arguments to constructors
infixr 6 :*:
data (:*:) f g p = f p :*: g p
- deriving (Eq, Read, Show)
+ deriving (Eq, Read, Show, Generic)
-- | Composition of functors
infixr 7 :.:
newtype (:.:) f g p = Comp1 { unComp1 :: f (g p) }
- deriving (Eq, Read, Show)
+ deriving (Eq, Read, Show, Generic)
-- | Tag for K1: recursion (of kind *)
data R
@@ -159,12 +159,12 @@ class Constructor c where
-- | Datatype to represent the arity of a tuple.
data Arity = NoArity | Arity Int
- deriving (Eq, Show, Ord, Read)
+ deriving (Eq, Show, Ord, Read, Generic)
-- | Datatype to represent the fixity of a constructor. An infix
-- | declaration directly corresponds to an application of 'Infix'.
data Fixity = Prefix | Infix Associativity Int
- deriving (Eq, Show, Ord, Read)
+ deriving (Eq, Show, Ord, Read, Generic)
-- | Get the precedence of a fixity value.
prec :: Fixity -> Int
@@ -175,7 +175,7 @@ prec (Infix _ n) = n
data Associativity = LeftAssociative
| RightAssociative
| NotAssociative
- deriving (Eq, Show, Ord, Read)
+ deriving (Eq, Show, Ord, Read, Generic)
-- | Representable types of kind *.
-- This class is derivable in GHC with the DeriveGeneric flag on.
More information about the ghc-commits
mailing list