{-# LANGUAGE StandaloneDeriving, UndecidableInstances #-}
module Generics.SOP.Metadata
( module Generics.SOP.Metadata
, Associativity(..)
, DecidedStrictness(..)
, SourceStrictness(..)
, SourceUnpackedness(..)
) where
import Data.Kind (Type)
import GHC.Generics
( Associativity(..)
, DecidedStrictness(..)
, SourceStrictness(..)
, SourceUnpackedness(..)
)
import Generics.SOP.Constraint
import Generics.SOP.NP
data DatatypeInfo :: [[Type]] -> Type where
ADT ::
ModuleName
-> DatatypeName
-> NP ConstructorInfo xss
-> POP StrictnessInfo xss
-> DatatypeInfo xss
Newtype ::
ModuleName
-> DatatypeName
-> ConstructorInfo '[x]
-> DatatypeInfo '[ '[x] ]
moduleName :: DatatypeInfo xss -> ModuleName
moduleName :: forall (xss :: [[*]]). DatatypeInfo xss -> ConstructorName
moduleName (ADT ConstructorName
name ConstructorName
_ NP ConstructorInfo xss
_ POP StrictnessInfo xss
_) = ConstructorName
name
moduleName (Newtype ConstructorName
name ConstructorName
_ ConstructorInfo '[x]
_) = ConstructorName
name
datatypeName :: DatatypeInfo xss -> DatatypeName
datatypeName :: forall (xss :: [[*]]). DatatypeInfo xss -> ConstructorName
datatypeName (ADT ConstructorName
_ ConstructorName
name NP ConstructorInfo xss
_ POP StrictnessInfo xss
_) = ConstructorName
name
datatypeName (Newtype ConstructorName
_ ConstructorName
name ConstructorInfo '[x]
_) = ConstructorName
name
constructorInfo :: DatatypeInfo xss -> NP ConstructorInfo xss
constructorInfo :: forall (xss :: [[*]]). DatatypeInfo xss -> NP ConstructorInfo xss
constructorInfo (ADT ConstructorName
_ ConstructorName
_ NP ConstructorInfo xss
cs POP StrictnessInfo xss
_) = NP ConstructorInfo xss
cs
constructorInfo (Newtype ConstructorName
_ ConstructorName
_ ConstructorInfo '[x]
c) = ConstructorInfo '[x]
c ConstructorInfo '[x]
-> NP ConstructorInfo '[] -> NP ConstructorInfo '[ '[x]]
forall {k} (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP ConstructorInfo '[]
forall {k} (a :: k -> *). NP a '[]
Nil
deriving instance
( All (Show `Compose` ConstructorInfo) xs
, All (Show `Compose` NP StrictnessInfo) xs
) => Show (DatatypeInfo xs)
deriving instance
( All (Eq `Compose` ConstructorInfo) xs
, All (Eq `Compose` NP StrictnessInfo) xs
) => Eq (DatatypeInfo xs)
deriving instance
( All (Eq `Compose` ConstructorInfo) xs
, All (Ord `Compose` ConstructorInfo) xs
, All (Eq `Compose` NP StrictnessInfo) xs
, All (Ord `Compose` NP StrictnessInfo) 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 :: forall (xs :: [*]). ConstructorInfo xs -> ConstructorName
constructorName (Constructor ConstructorName
name) = ConstructorName
name
constructorName (Infix ConstructorName
name Associativity
_ Fixity
_) = ConstructorName
name
constructorName (Record ConstructorName
name NP FieldInfo xs
_) = ConstructorName
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 StrictnessInfo :: Type -> Type where
StrictnessInfo ::
SourceUnpackedness
-> SourceStrictness
-> DecidedStrictness
-> StrictnessInfo a
deriving (Fixity -> StrictnessInfo a -> ShowS
[StrictnessInfo a] -> ShowS
StrictnessInfo a -> ConstructorName
(Fixity -> StrictnessInfo a -> ShowS)
-> (StrictnessInfo a -> ConstructorName)
-> ([StrictnessInfo a] -> ShowS)
-> Show (StrictnessInfo a)
forall a. Fixity -> StrictnessInfo a -> ShowS
forall a. [StrictnessInfo a] -> ShowS
forall a. StrictnessInfo a -> ConstructorName
forall a.
(Fixity -> a -> ShowS)
-> (a -> ConstructorName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Fixity -> StrictnessInfo a -> ShowS
showsPrec :: Fixity -> StrictnessInfo a -> ShowS
$cshow :: forall a. StrictnessInfo a -> ConstructorName
show :: StrictnessInfo a -> ConstructorName
$cshowList :: forall a. [StrictnessInfo a] -> ShowS
showList :: [StrictnessInfo a] -> ShowS
Show, StrictnessInfo a -> StrictnessInfo a -> Bool
(StrictnessInfo a -> StrictnessInfo a -> Bool)
-> (StrictnessInfo a -> StrictnessInfo a -> Bool)
-> Eq (StrictnessInfo a)
forall a. StrictnessInfo a -> StrictnessInfo a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. StrictnessInfo a -> StrictnessInfo a -> Bool
== :: StrictnessInfo a -> StrictnessInfo a -> Bool
$c/= :: forall a. StrictnessInfo a -> StrictnessInfo a -> Bool
/= :: StrictnessInfo a -> StrictnessInfo a -> Bool
Eq, Eq (StrictnessInfo a)
Eq (StrictnessInfo a) =>
(StrictnessInfo a -> StrictnessInfo a -> Ordering)
-> (StrictnessInfo a -> StrictnessInfo a -> Bool)
-> (StrictnessInfo a -> StrictnessInfo a -> Bool)
-> (StrictnessInfo a -> StrictnessInfo a -> Bool)
-> (StrictnessInfo a -> StrictnessInfo a -> Bool)
-> (StrictnessInfo a -> StrictnessInfo a -> StrictnessInfo a)
-> (StrictnessInfo a -> StrictnessInfo a -> StrictnessInfo a)
-> Ord (StrictnessInfo a)
StrictnessInfo a -> StrictnessInfo a -> Bool
StrictnessInfo a -> StrictnessInfo a -> Ordering
StrictnessInfo a -> StrictnessInfo a -> StrictnessInfo a
forall a. Eq (StrictnessInfo a)
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. StrictnessInfo a -> StrictnessInfo a -> Bool
forall a. StrictnessInfo a -> StrictnessInfo a -> Ordering
forall a. StrictnessInfo a -> StrictnessInfo a -> StrictnessInfo a
$ccompare :: forall a. StrictnessInfo a -> StrictnessInfo a -> Ordering
compare :: StrictnessInfo a -> StrictnessInfo a -> Ordering
$c< :: forall a. StrictnessInfo a -> StrictnessInfo a -> Bool
< :: StrictnessInfo a -> StrictnessInfo a -> Bool
$c<= :: forall a. StrictnessInfo a -> StrictnessInfo a -> Bool
<= :: StrictnessInfo a -> StrictnessInfo a -> Bool
$c> :: forall a. StrictnessInfo a -> StrictnessInfo a -> Bool
> :: StrictnessInfo a -> StrictnessInfo a -> Bool
$c>= :: forall a. StrictnessInfo a -> StrictnessInfo a -> Bool
>= :: StrictnessInfo a -> StrictnessInfo a -> Bool
$cmax :: forall a. StrictnessInfo a -> StrictnessInfo a -> StrictnessInfo a
max :: StrictnessInfo a -> StrictnessInfo a -> StrictnessInfo a
$cmin :: forall a. StrictnessInfo a -> StrictnessInfo a -> StrictnessInfo a
min :: StrictnessInfo a -> StrictnessInfo a -> StrictnessInfo a
Ord, (forall a b. (a -> b) -> StrictnessInfo a -> StrictnessInfo b)
-> (forall a b. a -> StrictnessInfo b -> StrictnessInfo a)
-> Functor StrictnessInfo
forall a b. a -> StrictnessInfo b -> StrictnessInfo a
forall a b. (a -> b) -> StrictnessInfo a -> StrictnessInfo b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> StrictnessInfo a -> StrictnessInfo b
fmap :: forall a b. (a -> b) -> StrictnessInfo a -> StrictnessInfo b
$c<$ :: forall a b. a -> StrictnessInfo b -> StrictnessInfo a
<$ :: forall a b. a -> StrictnessInfo b -> StrictnessInfo a
Functor)
data FieldInfo :: Type -> Type where
FieldInfo :: FieldName -> FieldInfo a
deriving (Fixity -> FieldInfo a -> ShowS
[FieldInfo a] -> ShowS
FieldInfo a -> ConstructorName
(Fixity -> FieldInfo a -> ShowS)
-> (FieldInfo a -> ConstructorName)
-> ([FieldInfo a] -> ShowS)
-> Show (FieldInfo a)
forall a. Fixity -> FieldInfo a -> ShowS
forall a. [FieldInfo a] -> ShowS
forall a. FieldInfo a -> ConstructorName
forall a.
(Fixity -> a -> ShowS)
-> (a -> ConstructorName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Fixity -> FieldInfo a -> ShowS
showsPrec :: Fixity -> FieldInfo a -> ShowS
$cshow :: forall a. FieldInfo a -> ConstructorName
show :: FieldInfo a -> ConstructorName
$cshowList :: forall a. [FieldInfo a] -> ShowS
showList :: [FieldInfo a] -> ShowS
Show, FieldInfo a -> FieldInfo a -> Bool
(FieldInfo a -> FieldInfo a -> Bool)
-> (FieldInfo a -> FieldInfo a -> Bool) -> Eq (FieldInfo a)
forall a. FieldInfo a -> FieldInfo a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. FieldInfo a -> FieldInfo a -> Bool
== :: FieldInfo a -> FieldInfo a -> Bool
$c/= :: forall a. FieldInfo a -> FieldInfo a -> Bool
/= :: FieldInfo a -> FieldInfo a -> Bool
Eq, Eq (FieldInfo a)
Eq (FieldInfo a) =>
(FieldInfo a -> FieldInfo a -> Ordering)
-> (FieldInfo a -> FieldInfo a -> Bool)
-> (FieldInfo a -> FieldInfo a -> Bool)
-> (FieldInfo a -> FieldInfo a -> Bool)
-> (FieldInfo a -> FieldInfo a -> Bool)
-> (FieldInfo a -> FieldInfo a -> FieldInfo a)
-> (FieldInfo a -> FieldInfo a -> FieldInfo a)
-> Ord (FieldInfo a)
FieldInfo a -> FieldInfo a -> Bool
FieldInfo a -> FieldInfo a -> Ordering
FieldInfo a -> FieldInfo a -> FieldInfo a
forall a. Eq (FieldInfo a)
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. FieldInfo a -> FieldInfo a -> Bool
forall a. FieldInfo a -> FieldInfo a -> Ordering
forall a. FieldInfo a -> FieldInfo a -> FieldInfo a
$ccompare :: forall a. FieldInfo a -> FieldInfo a -> Ordering
compare :: FieldInfo a -> FieldInfo a -> Ordering
$c< :: forall a. FieldInfo a -> FieldInfo a -> Bool
< :: FieldInfo a -> FieldInfo a -> Bool
$c<= :: forall a. FieldInfo a -> FieldInfo a -> Bool
<= :: FieldInfo a -> FieldInfo a -> Bool
$c> :: forall a. FieldInfo a -> FieldInfo a -> Bool
> :: FieldInfo a -> FieldInfo a -> Bool
$c>= :: forall a. FieldInfo a -> FieldInfo a -> Bool
>= :: FieldInfo a -> FieldInfo a -> Bool
$cmax :: forall a. FieldInfo a -> FieldInfo a -> FieldInfo a
max :: FieldInfo a -> FieldInfo a -> FieldInfo a
$cmin :: forall a. FieldInfo a -> FieldInfo a -> FieldInfo a
min :: FieldInfo a -> FieldInfo a -> FieldInfo a
Ord, (forall a b. (a -> b) -> FieldInfo a -> FieldInfo b)
-> (forall a b. a -> FieldInfo b -> FieldInfo a)
-> Functor FieldInfo
forall a b. a -> FieldInfo b -> FieldInfo a
forall a b. (a -> b) -> FieldInfo a -> FieldInfo b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> FieldInfo a -> FieldInfo b
fmap :: forall a b. (a -> b) -> FieldInfo a -> FieldInfo b
$c<$ :: forall a b. a -> FieldInfo b -> FieldInfo a
<$ :: forall a b. a -> FieldInfo b -> FieldInfo a
Functor)
fieldName :: FieldInfo a -> FieldName
fieldName :: forall a. FieldInfo a -> ConstructorName
fieldName (FieldInfo ConstructorName
n) = ConstructorName
n
type DatatypeName = String
type ModuleName = String
type ConstructorName = String
type FieldName = String
type Fixity = Int