module GHC.Generics (
V1, U1(..), Par1(..), Rec1(..), K1(..), M1(..)
, (:+:)(..), (:*:)(..), (:.:)(..)
, Rec0, Par0, R, P
, D1, C1, S1, D, C, S
, Datatype(..), Constructor(..), Selector(..), NoSelector
, Fixity(..), Associativity(..), Arity(..), prec
, Generic(..), Generic1(..)
) where
import GHC.Types
import Data.Maybe ( Maybe(..) )
import Data.Either ( Either(..) )
import GHC.Classes ( Eq, Ord )
import GHC.Read ( Read )
import GHC.Show ( Show )
data V1 p
data U1 p = U1
newtype Par1 p = Par1 { unPar1 :: p }
newtype Rec1 f p = Rec1 { unRec1 :: f p }
newtype K1 i c p = K1 { unK1 :: c }
newtype M1 i c f p = M1 { unM1 :: f p }
infixr 5 :+:
data (:+:) f g p = L1 (f p) | R1 (g p)
infixr 6 :*:
data (:*:) f g p = f p :*: g p
infixr 7 :.:
newtype (:.:) f g p = Comp1 { unComp1 :: f (g p) }
data R
data P
type Rec0 = K1 R
type Par0 = K1 P
data D
data C
data S
type D1 = M1 D
type C1 = M1 C
type S1 = M1 S
class Datatype d where
datatypeName :: t d (f :: * -> *) a -> [Char]
moduleName :: t d (f :: * -> *) a -> [Char]
class Selector s where
selName :: t s (f :: * -> *) a -> [Char]
data NoSelector
instance Selector NoSelector where selName _ = ""
class Constructor c where
conName :: t c (f :: * -> *) a -> [Char]
conFixity :: t c (f :: * -> *) a -> Fixity
conFixity _ = Prefix
conIsRecord :: t c (f :: * -> *) a -> Bool
conIsRecord _ = False
data Arity = NoArity | Arity Int
deriving (Eq, Show, Ord, Read)
data Fixity = Prefix | Infix Associativity Int
deriving (Eq, Show, Ord, Read)
prec :: Fixity -> Int
prec Prefix = 10
prec (Infix _ n) = n
data Associativity = LeftAssociative
| RightAssociative
| NotAssociative
deriving (Eq, Show, Ord, Read)
class Generic a where
type Rep a :: * -> *
from :: a -> (Rep a) x
to :: (Rep a) x -> a
class Generic1 f where
type Rep1 f :: * -> *
from1 :: f a -> (Rep1 f) a
to1 :: (Rep1 f) a -> f a
deriving instance Generic [a]
deriving instance Generic (Maybe a)
deriving instance Generic (Either a b)
deriving instance Generic Bool
deriving instance Generic Ordering
deriving instance Generic ()
deriving instance Generic ((,) a b)
deriving instance Generic ((,,) a b c)
deriving instance Generic ((,,,) a b c d)
deriving instance Generic ((,,,,) a b c d e)
deriving instance Generic ((,,,,,) a b c d e f)
deriving instance Generic ((,,,,,,) a b c d e f g)
deriving instance Generic1 []
deriving instance Generic1 Maybe
deriving instance Generic1 (Either a)
deriving instance Generic1 ((,) a)
deriving instance Generic1 ((,,) a b)
deriving instance Generic1 ((,,,) a b c)
deriving instance Generic1 ((,,,,) a b c d)
deriving instance Generic1 ((,,,,,) a b c d e)
deriving instance Generic1 ((,,,,,,) a b c d e f)
data D_Int
data C_Int
instance Datatype D_Int where
datatypeName _ = "Int"
moduleName _ = "GHC.Int"
instance Constructor C_Int where
conName _ = ""
instance Generic Int where
type Rep Int = D1 D_Int (C1 C_Int (S1 NoSelector (Rec0 Int)))
from x = M1 (M1 (M1 (K1 x)))
to (M1 (M1 (M1 (K1 x)))) = x
data D_Float
data C_Float
instance Datatype D_Float where
datatypeName _ = "Float"
moduleName _ = "GHC.Float"
instance Constructor C_Float where
conName _ = ""
instance Generic Float where
type Rep Float = D1 D_Float (C1 C_Float (S1 NoSelector (Rec0 Float)))
from x = M1 (M1 (M1 (K1 x)))
to (M1 (M1 (M1 (K1 x)))) = x
data D_Double
data C_Double
instance Datatype D_Double where
datatypeName _ = "Double"
moduleName _ = "GHC.Float"
instance Constructor C_Double where
conName _ = ""
instance Generic Double where
type Rep Double = D1 D_Double (C1 C_Double (S1 NoSelector (Rec0 Double)))
from x = M1 (M1 (M1 (K1 x)))
to (M1 (M1 (M1 (K1 x)))) = x
data D_Char
data C_Char
instance Datatype D_Char where
datatypeName _ = "Char"
moduleName _ = "GHC.Base"
instance Constructor C_Char where
conName _ = ""
instance Generic Char where
type Rep Char = D1 D_Char (C1 C_Char (S1 NoSelector (Rec0 Char)))
from x = M1 (M1 (M1 (K1 x)))
to (M1 (M1 (M1 (K1 x)))) = x