d2170d98e23ba6493c34c12bfcd67e53e9ca77d2
[ghc-prim.git] / GHC / Generics.hs
1 {-
2
3 {-# OPTIONS_GHC -XNoImplicitPrelude -XTypeOperators #-}
4
5 module GHC.Generics where
6
7 default ()
8
9 data Unit = Unit
10 #ifndef __HADDOCK__
11 data (:+:) a b = Inl a | Inr b
12 data (:*:) a b = a :*: b
13 #endif
14
15 -}
16
17 {-# OPTIONS_GHC -XNoImplicitPrelude      #-}
18 {-# OPTIONS_GHC -XEmptyDataDecls         #-}
19 {-# OPTIONS_GHC -XMultiParamTypeClasses  #-}
20 {-# OPTIONS_GHC -XTypeSynonymInstances   #-}
21 {-# OPTIONS_GHC -XTypeOperators          #-}
22 {-# OPTIONS_GHC -XKindSignatures         #-}
23
24 module GHC.Generics  (
25   -- * Generic representation types
26     V1, U1(..), Par1(..), Rec1(..), K1(..), M1(..)
27   , (:+:)(..), (:*:)(..), (:.:)(..)
28
29   -- ** Synonyms for convenience
30   , Rec0, Par0, R, P
31   , D1, C1, S1, D, C, S
32
33   -- * Meta-information
34   , Datatype(..), Constructor(..), Selector(..), NoSelector
35   , Fixity(..), Associativity(..), Arity(..), prec
36
37   -- * Representation type families
38   , Rep0, Rep1
39
40   -- * Representable type classes
41   , Representable0(..), Representable1(..)
42
43 {-
44   -- * Representations for base types
45   , Rep0Char, Rep0Int, Rep0Float
46   , Rep0Maybe, Rep1Maybe
47   , Rep0List, Rep1List
48 -}
49   ) where
50   
51 import {-# SOURCE #-} GHC.Types -- ([](..), Int, Char, Bool(..))
52
53 --------------------------------------------------------------------------------
54 -- Representation types
55 --------------------------------------------------------------------------------
56
57 -- | Void: used for datatypes without constructors
58 data V1 p
59
60 -- | Unit: used for constructors without arguments
61 data U1 p = U1
62
63 -- | Used for marking occurrences of the parameter
64 newtype Par1 p = Par1 { unPar1 :: p }
65
66
67 -- | Recursive calls of kind * -> *
68 newtype Rec1 f p = Rec1 { unRec1 :: f p }
69
70 -- | Constants, additional parameters and recursion of kind *
71 newtype K1 i c p = K1 { unK1 :: c }
72
73 -- | Meta-information (constructor names, etc.)
74 newtype M1 i c f p = M1 { unM1 :: f p }
75
76 -- | Sums: encode choice between constructors
77 infixr 5 :+:
78 data (:+:) f g p = L1 (f p) | R1 (g p)
79
80 -- | Products: encode multiple arguments to constructors
81 infixr 6 :*:
82 data (:*:) f g p = f p :*: g p
83
84 -- | Composition of functors
85 infixr 7 :.:
86 newtype (:.:) f g p = Comp1 { unComp1 :: f (g p) }
87
88 -- | Tag for K1: recursion (of kind *)
89 data R
90 -- | Tag for K1: parameters (other than the last)
91 data P
92
93 -- | Type synonym for encoding recursion (of kind *)
94 type Rec0  = K1 R
95 -- | Type synonym for encoding parameters (other than the last)
96 type Par0  = K1 P
97
98 -- | Tag for M1: datatype
99 data D
100 -- | Tag for M1: constructor
101 data C
102 -- | Tag for M1: record selector
103 data S
104
105 -- | Type synonym for encoding meta-information for datatypes
106 type D1 = M1 D
107
108 -- | Type synonym for encoding meta-information for constructors
109 type C1 = M1 C
110
111 -- | Type synonym for encoding meta-information for record selectors
112 type S1 = M1 S
113
114
115 -- | Class for datatypes that represent datatypes
116 class Datatype d where
117   -- | The name of the datatype (unqualified)
118   datatypeName :: t d (f :: * -> *) a -> [Char]
119   -- | The fully-qualified name of the module where the type is declared
120   moduleName   :: t d (f :: * -> *) a -> [Char]
121
122
123 -- | Class for datatypes that represent records
124 class Selector s where
125   -- | The name of the selector
126   selName :: t s (f :: * -> *) a -> [Char]
127
128 -- | Used for constructor fields without a name
129 data NoSelector
130
131 instance Selector NoSelector where selName _ = ""
132
133 -- | Class for datatypes that represent data constructors
134 class Constructor c where
135   -- | The name of the constructor
136   conName :: t c (f :: * -> *) a -> [Char]
137
138   -- | The fixity of the constructor
139   conFixity :: t c (f :: * -> *) a -> Fixity
140   conFixity _ = Prefix
141
142   -- | Marks if this constructor is a record
143   conIsRecord :: t c (f :: * -> *) a -> Bool
144   conIsRecord _ = False
145
146   -- | Marks if this constructor is a tuple, 
147   -- returning arity >=0 if so, <0 if not
148   conIsTuple :: t c (f :: * -> *) a -> Arity
149   conIsTuple _ = NoArity
150
151
152 -- | Datatype to represent the arity of a tuple.
153 data Arity = NoArity | Arity Int
154 --  deriving (Eq, Show, Ord, Read)
155 -- TODO: Add these instances to the Prelude
156
157 -- | Datatype to represent the fixity of a constructor. An infix
158 -- | declaration directly corresponds to an application of 'Infix'.
159 data Fixity = Prefix | Infix Associativity Int
160 --  deriving (Eq, Show, Ord, Read)
161 -- TODO: Add these instances to the Prelude
162
163 -- | Get the precedence of a fixity value.
164 prec :: Fixity -> Int
165 prec Prefix      = I# 10#
166 prec (Infix _ n) = n
167
168 -- | Datatype to represent the associativy of a constructor
169 data Associativity =  LeftAssociative 
170                    |  RightAssociative
171                    |  NotAssociative
172 --  deriving (Eq, Show, Ord, Read)
173 -- TODO: Add these instances to the Prelude
174
175
176 -- | Representable types of kind *
177 class Representable0 a rep where
178   -- | Convert from the datatype to its representation
179   from0  :: a -> Rep0 a x
180   -- | Convert from the representation to the datatype
181   to0    :: Rep0 a x -> a
182
183 -- | Representable types of kind * -> *
184 class Representable1 f rep where
185   -- | Convert from the datatype to its representation
186   from1  :: f a -> Rep1 f a
187   -- | Convert from the representation to the datatype
188   to1    :: Rep1 f a -> f a
189
190 --------------------------------------------------------------------------------
191 -- Representation for base types
192 --------------------------------------------------------------------------------
193
194 -- Representation types
195 {-
196 type Rep1Par1 = Par1
197 instance Representable1 Par1 Rep1Par1 where
198   from1 = id
199   to1 = id
200
201 type Rep1Rec1 f = Rec1 f
202 instance Representable1 (Rec1 f) (Rep1Rec1 f) where
203   from1 = id
204   to1 = id
205 -}
206 -- Kind *
207
208 {-
209 type Rep0Char = Rec0 Char
210 instance Representable0 Char Rep0Char where
211   from0 = K1
212   to0 = unK1
213
214 type Rep0Int = Rec0 Int
215 instance Representable0 Int Rep0Int where
216   from0 = K1
217   to0 = unK1
218
219 type Rep0Float = Rec0 Float
220 instance Representable0 Float Rep0Float where
221   from0 = K1
222   to0 = unK1
223
224 -- etc...
225
226 -- Kind * -> *
227
228 data Maybe_
229 data Nothing_
230 data Just_
231
232 instance Datatype Maybe_ where
233   datatypeName _ = "Maybe"
234   moduleName   _ = "Representation"
235
236 instance Constructor Nothing_ where
237   conName _ = "Nothing"
238
239 instance Constructor Just_ where
240   conName _ = "Just"
241
242 type Rep0Maybe a = D1 Maybe_ (C1 Nothing_ U1 :+: C1 Just_ (Par0 a))
243 instance Representable0 (Maybe a) (Rep0Maybe a) where
244   from0 Nothing  = M1 (L1 (M1 U1))
245   from0 (Just x) = M1 (R1 (M1 (K1 x)))
246   to0 (M1 (L1 (M1 U1)))     = Nothing
247   to0 (M1 (R1 (M1 (K1 x)))) = Just x
248
249 type Rep1Maybe = D1 Maybe_ (C1 Nothing_ U1 :+: C1 Just_ Par1)
250 instance Representable1 Maybe Rep1Maybe where
251   from1 Nothing  = M1 (L1 (M1 U1))
252   from1 (Just x) = M1 (R1 (M1 (Par1 x)))
253   to1 (M1 (L1 (M1 U1)))       = Nothing
254   to1 (M1 (R1 (M1 (Par1 x)))) = Just x
255
256
257 data List__
258 data Nil__
259 data Cons__
260
261 instance Datatype [a] where
262   datatypeName _ = "[]"
263   moduleName   _ = "Data.List"
264
265 instance Constructor Nil__  where conName _ = "[]"
266 instance Constructor Cons__ where
267   conName   _ = ":"
268   conFixity _ = Infix RightAssociative 5
269
270 type Rep0List a = D1 List__ ((C1 Nil__ U1) :+: (C1 Cons__ (Par0 a :*: Rec0 [a])))
271 instance Representable0 [a] (Rep0List a) where
272   from0 []    = M1 (L1 (M1 U1))
273   from0 (h:t) = M1 (R1 (M1 (K1 h :*: K1 t)))
274   to0 (M1 (L1 (M1 U1)))              = []
275   to0 (M1 (R1 (M1 (K1 h :*: K1 t)))) = h : t
276
277 type Rep1List = D1 List__ ((C1 Nil__ U1) :+: (C1 Cons__ (Par1 :*: Rec1 [])))
278 instance Representable1 [] Rep1List where
279   from1 []    = M1 (L1 (M1 U1))
280   from1 (h:t) = M1 (R1 (M1 (Par1 h :*: Rec1 t)))
281   to1 (M1 (L1 (M1 U1)))                  = []
282   to1 (M1 (R1 (M1 (Par1 h :*: Rec1 t)))) = h : t
283
284 -- etc...
285 -}
286