{-# LANGUAGE StandaloneDeriving, UndecidableInstances #-}
module Generics.SOP.Metadata
( module Generics.SOP.Metadata
, Associativity(..)
) where
import Data.Kind (Type)
import GHC.Generics (Associativity(..))
import Generics.SOP.Constraint
import Generics.SOP.NP
data DatatypeInfo :: [[Type]] -> Type where
ADT :: ModuleName -> DatatypeName -> NP ConstructorInfo xss -> DatatypeInfo xss
Newtype :: ModuleName -> DatatypeName -> ConstructorInfo '[x] -> DatatypeInfo '[ '[x] ]
moduleName :: DatatypeInfo xss -> ModuleName
moduleName (ADT name _ _) = name
moduleName (Newtype name _ _) = name
datatypeName :: DatatypeInfo xss -> DatatypeName
datatypeName (ADT _ name _ ) = name
datatypeName (Newtype _ name _) = name
constructorInfo :: DatatypeInfo xss -> NP ConstructorInfo xss
constructorInfo (ADT _ _ cs) = cs
constructorInfo (Newtype _ _ c) = c :* Nil
deriving instance All (Show `Compose` ConstructorInfo) xs => Show (DatatypeInfo xs)
deriving instance All (Eq `Compose` ConstructorInfo) xs => Eq (DatatypeInfo xs)
deriving instance (All (Eq `Compose` ConstructorInfo) xs, All (Ord `Compose` ConstructorInfo) xs) => Ord (DatatypeInfo xs)
data ConstructorInfo :: [Type] -> Type where
Constructor :: SListI xs => ConstructorName -> ConstructorInfo xs
Infix :: ConstructorName -> Associativity -> Fixity -> ConstructorInfo '[ x, y ]
Record :: SListI xs => ConstructorName -> NP FieldInfo xs -> ConstructorInfo xs
constructorName :: ConstructorInfo xs -> ConstructorName
constructorName (Constructor name) = name
constructorName (Infix name _ _) = name
constructorName (Record name _) = name
deriving instance All (Show `Compose` FieldInfo) xs => Show (ConstructorInfo xs)
deriving instance All (Eq `Compose` FieldInfo) xs => Eq (ConstructorInfo xs)
deriving instance (All (Eq `Compose` FieldInfo) xs, All (Ord `Compose` FieldInfo) xs) => Ord (ConstructorInfo xs)
data FieldInfo :: Type -> Type where
FieldInfo :: FieldName -> FieldInfo a
deriving (Show, Eq, Ord, Functor)
fieldName :: FieldInfo a -> FieldName
fieldName (FieldInfo n) = n
type DatatypeName = String
type ModuleName = String
type ConstructorName = String
type FieldName = String
type Fixity = Int