Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
Instances
Generic (Tree a) Source # | |
GenericK (Tree a :: Type) LoT0 Source # | |
GenericK Tree (a :&&: LoT0 :: LoT (Type -> Type)) Source # | |
type Rep (Tree a) Source # | |
Defined in Generics.Kind.Examples type Rep (Tree a) = D1 (MetaData "Tree" "Generics.Kind.Examples" "kind-generics-0.3.0.0-Laoknq7ZzM0L0KOt6edhQd" False) (C1 (MetaCons "Branch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Tree a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Tree a))) :+: C1 (MetaCons "Leaf" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))) | |
type RepK (Tree a :: Type) Source # | |
type RepK Tree Source # | |
data family HappyFamily t Source #
Instances
data SimpleIndex :: * -> * -> * where Source #
MkSimpleIndex :: [a] -> SimpleIndex [a] b |
Instances
GenericK (SimpleIndex a b :: Type) LoT0 Source # | |
Defined in Generics.Kind.Examples type RepK (SimpleIndex a b) :: LoT k -> Type Source # fromK :: (SimpleIndex a b :@@: LoT0) -> RepK (SimpleIndex a b) LoT0 Source # toK :: RepK (SimpleIndex a b) LoT0 -> SimpleIndex a b :@@: LoT0 Source # | |
GenericK SimpleIndex (a :&&: (b :&&: LoT0) :: LoT (Type -> Type -> Type)) Source # | |
Defined in Generics.Kind.Examples type RepK SimpleIndex :: LoT k -> Type Source # fromK :: (SimpleIndex :@@: (a :&&: (b :&&: LoT0))) -> RepK SimpleIndex (a :&&: (b :&&: LoT0)) Source # toK :: RepK SimpleIndex (a :&&: (b :&&: LoT0)) -> SimpleIndex :@@: (a :&&: (b :&&: LoT0)) Source # | |
GenericK (SimpleIndex a :: Type -> Type) (b :&&: LoT0 :: LoT (Type -> Type)) Source # | |
Defined in Generics.Kind.Examples type RepK (SimpleIndex a) :: LoT k -> Type Source # fromK :: (SimpleIndex a :@@: (b :&&: LoT0)) -> RepK (SimpleIndex a) (b :&&: LoT0) Source # toK :: RepK (SimpleIndex a) (b :&&: LoT0) -> SimpleIndex a :@@: (b :&&: LoT0) Source # | |
type RepK (SimpleIndex a b :: Type) Source # | |
type RepK SimpleIndex Source # | |
type RepK (SimpleIndex a :: Type -> Type) Source # | |
data WeirdTree a where Source #
WeirdBranch :: WeirdTree a -> WeirdTree a -> WeirdTree a | |
WeirdLeaf :: Show a => t -> a -> WeirdTree a |
Instances
GenericK WeirdTree (a :&&: LoT0 :: LoT (Type -> Type)) Source # | |
type RepK WeirdTree Source # | |
Defined in Generics.Kind.Examples type RepK WeirdTree = (Field (WeirdTree :$: (Var0 :: Atom (Type -> Type) Type)) :*: Field (WeirdTree :$: (Var0 :: Atom (Type -> Type) Type))) :+: Exists Type ((Show :$: (Var1 :: Atom (Type -> Type -> Type) Type)) :=>: (Field (Var0 :: Atom (Type -> Type -> Type) Type) :*: Field (Var1 :: Atom (Type -> Type -> Type) Type))) |
data WeirdTreeR a where Source #
WeirdBranchR :: WeirdTreeR a -> WeirdTreeR a -> WeirdTreeR a | |
WeirdLeafR :: (Show a, Eq t, Typeable t) => t -> a -> WeirdTreeR a |
Instances
GenericK (WeirdTreeR a :: Type) LoT0 Source # | |
Defined in Generics.Kind.Examples type RepK (WeirdTreeR a) :: LoT k -> Type Source # fromK :: (WeirdTreeR a :@@: LoT0) -> RepK (WeirdTreeR a) LoT0 Source # toK :: RepK (WeirdTreeR a) LoT0 -> WeirdTreeR a :@@: LoT0 Source # | |
GenericK WeirdTreeR (a :&&: LoT0 :: LoT (Type -> Type)) Source # | |
Defined in Generics.Kind.Examples type RepK WeirdTreeR :: LoT k -> Type Source # fromK :: (WeirdTreeR :@@: (a :&&: LoT0)) -> RepK WeirdTreeR (a :&&: LoT0) Source # toK :: RepK WeirdTreeR (a :&&: LoT0) -> WeirdTreeR :@@: (a :&&: LoT0) Source # | |
type RepK (WeirdTreeR a :: Type) Source # | |
Defined in Generics.Kind.Examples type RepK (WeirdTreeR a :: Type) = (Field (Kon (WeirdTreeR a) :: Atom Type Type) :*: Field (Kon (WeirdTreeR a) :: Atom Type Type)) :+: Exists Type (((Kon (Show a) :: Atom (Type -> Type) Constraint) :&: ((Eq :$: (Var0 :: Atom (Type -> Type) Type)) :&: ((Typeable :: Type -> Constraint) :$: (Var0 :: Atom (Type -> Type) Type)))) :=>: (Field (Var0 :: Atom (Type -> Type) Type) :*: Field (Kon a :: Atom (Type -> Type) Type))) | |
type RepK WeirdTreeR Source # | |
Defined in Generics.Kind.Examples type RepK WeirdTreeR = (Field (WeirdTreeR :$: (Var0 :: Atom (Type -> Type) Type)) :*: Field (WeirdTreeR :$: (Var0 :: Atom (Type -> Type) Type))) :+: Exists Type (((Show :$: (Var1 :: Atom (Type -> Type -> Type) Type)) :&: ((Eq :$: (Var0 :: Atom (Type -> Type -> Type) Type)) :&: ((Typeable :: Type -> Constraint) :$: (Var0 :: Atom (Type -> Type -> Type) Type)))) :=>: (Field (Var0 :: Atom (Type -> Type -> Type) Type) :*: Field (Var1 :: Atom (Type -> Type -> Type) Type))) |
MkRanky2 ((forall a. a -> a) -> b) |
Orphan instances
GenericK (Maybe a :: Type) LoT0 Source # | |
GenericK (Either a b :: Type) LoT0 Source # | |
GenericK Either (a :&&: (b :&&: LoT0) :: LoT (Type -> Type -> Type)) Source # | |
GenericK Maybe (a :&&: LoT0 :: LoT (Type -> Type)) Source # | |
GenericK (Either a :: Type -> Type) (b :&&: LoT0 :: LoT (Type -> Type)) Source # | |