kind-generics-0.1.1.0: Generic programming in GHC style for arbitrary kinds and GADTs.

Safe HaskellSafe
LanguageHaskell2010

Generics.Kind

Contents

Description

Main module of kind-generics. Please refer to the README file for documentation on how to use this package.

Synopsis

Generic representation types

data ((f :: k -> Type) :+: (g :: k -> Type)) (p :: k) :: forall k. (k -> Type) -> (k -> Type) -> k -> Type infixr 5 #

Sums: encode choice between constructors

Constructors

L1 (f p) 
R1 (g p) 
Instances
Generic1 (f :+: g :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (f :+: g) :: k -> Type #

Methods

from1 :: (f :+: g) a -> Rep1 (f :+: g) a #

to1 :: Rep1 (f :+: g) a -> (f :+: g) a #

(GEq f tys, GEq g tys) => GEq (f :+: g :: LoT k -> Type) (tys :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Eq

Methods

geq :: (f :+: g) tys -> (f :+: g) tys -> Bool Source #

(GFunctor f v as bs, GFunctor g v as bs) => GFunctor (f :+: g :: LoT k -> Type) v (as :: LoT k) (bs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Functor

Methods

gfmap :: Mappings v as bs -> (f :+: g) as -> (f :+: g) bs Source #

(Conv f f' tys, Conv g g' tys) => Conv (f :+: g) (f' :+: g' :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: (f' :+: g') tys -> (f :+: g) a Source #

toKindGenerics :: (f :+: g) a -> (f' :+: g') tys Source #

(Functor f, Functor g) => Functor (f :+: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> (f :+: g) a -> (f :+: g) b #

(<$) :: a -> (f :+: g) b -> (f :+: g) a #

(Foldable f, Foldable g) => Foldable (f :+: g)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => (f :+: g) m -> m #

foldMap :: Monoid m => (a -> m) -> (f :+: g) a -> m #

foldr :: (a -> b -> b) -> b -> (f :+: g) a -> b #

foldr' :: (a -> b -> b) -> b -> (f :+: g) a -> b #

foldl :: (b -> a -> b) -> b -> (f :+: g) a -> b #

foldl' :: (b -> a -> b) -> b -> (f :+: g) a -> b #

foldr1 :: (a -> a -> a) -> (f :+: g) a -> a #

foldl1 :: (a -> a -> a) -> (f :+: g) a -> a #

toList :: (f :+: g) a -> [a] #

null :: (f :+: g) a -> Bool #

length :: (f :+: g) a -> Int #

elem :: Eq a => a -> (f :+: g) a -> Bool #

maximum :: Ord a => (f :+: g) a -> a #

minimum :: Ord a => (f :+: g) a -> a #

sum :: Num a => (f :+: g) a -> a #

product :: Num a => (f :+: g) a -> a #

(Traversable f, Traversable g) => Traversable (f :+: g)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) #

sequenceA :: Applicative f0 => (f :+: g) (f0 a) -> f0 ((f :+: g) a) #

mapM :: Monad m => (a -> m b) -> (f :+: g) a -> m ((f :+: g) b) #

sequence :: Monad m => (f :+: g) (m a) -> m ((f :+: g) a) #

(Eq (f p), Eq (g p)) => Eq ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: (f :+: g) p -> (f :+: g) p -> Bool #

(/=) :: (f :+: g) p -> (f :+: g) p -> Bool #

(Ord (f p), Ord (g p)) => Ord ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: (f :+: g) p -> (f :+: g) p -> Ordering #

(<) :: (f :+: g) p -> (f :+: g) p -> Bool #

(<=) :: (f :+: g) p -> (f :+: g) p -> Bool #

(>) :: (f :+: g) p -> (f :+: g) p -> Bool #

(>=) :: (f :+: g) p -> (f :+: g) p -> Bool #

max :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p #

min :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p #

(Read (f p), Read (g p)) => Read ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

readsPrec :: Int -> ReadS ((f :+: g) p) #

readList :: ReadS [(f :+: g) p] #

readPrec :: ReadPrec ((f :+: g) p) #

readListPrec :: ReadPrec [(f :+: g) p] #

(Show (f p), Show (g p)) => Show ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :+: g) p -> ShowS #

show :: (f :+: g) p -> String #

showList :: [(f :+: g) p] -> ShowS #

Generic ((f :+: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p) :: Type -> Type #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

type Rep1 (f :+: g :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

data ((f :: k -> Type) :*: (g :: k -> Type)) (p :: k) :: forall k. (k -> Type) -> (k -> Type) -> k -> Type infixr 6 #

Products: encode multiple arguments to constructors

Constructors

(f p) :*: (g p) infixr 6 
Instances
Generic1 (f :*: g :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (f :*: g) :: k -> Type #

Methods

from1 :: (f :*: g) a -> Rep1 (f :*: g) a #

to1 :: Rep1 (f :*: g) a -> (f :*: g) a #

(GEq f tys, GEq g tys) => GEq (f :*: g :: LoT k -> Type) (tys :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Eq

Methods

geq :: (f :*: g) tys -> (f :*: g) tys -> Bool Source #

(GFunctor f v as bs, GFunctor g v as bs) => GFunctor (f :*: g :: LoT k -> Type) v (as :: LoT k) (bs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Functor

Methods

gfmap :: Mappings v as bs -> (f :*: g) as -> (f :*: g) bs Source #

(Conv f f' tys, Conv g g' tys) => Conv (f :*: g) (f' :*: g' :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: (f' :*: g') tys -> (f :*: g) a Source #

toKindGenerics :: (f :*: g) a -> (f' :*: g') tys Source #

(Monad f, Monad g) => Monad (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(>>=) :: (f :*: g) a -> (a -> (f :*: g) b) -> (f :*: g) b #

(>>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b #

return :: a -> (f :*: g) a #

fail :: String -> (f :*: g) a #

(Functor f, Functor g) => Functor (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> (f :*: g) a -> (f :*: g) b #

(<$) :: a -> (f :*: g) b -> (f :*: g) a #

(Applicative f, Applicative g) => Applicative (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> (f :*: g) a #

(<*>) :: (f :*: g) (a -> b) -> (f :*: g) a -> (f :*: g) b #

liftA2 :: (a -> b -> c) -> (f :*: g) a -> (f :*: g) b -> (f :*: g) c #

(*>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b #

(<*) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) a #

(Foldable f, Foldable g) => Foldable (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => (f :*: g) m -> m #

foldMap :: Monoid m => (a -> m) -> (f :*: g) a -> m #

foldr :: (a -> b -> b) -> b -> (f :*: g) a -> b #

foldr' :: (a -> b -> b) -> b -> (f :*: g) a -> b #

foldl :: (b -> a -> b) -> b -> (f :*: g) a -> b #

foldl' :: (b -> a -> b) -> b -> (f :*: g) a -> b #

foldr1 :: (a -> a -> a) -> (f :*: g) a -> a #

foldl1 :: (a -> a -> a) -> (f :*: g) a -> a #

toList :: (f :*: g) a -> [a] #

null :: (f :*: g) a -> Bool #

length :: (f :*: g) a -> Int #

elem :: Eq a => a -> (f :*: g) a -> Bool #

maximum :: Ord a => (f :*: g) a -> a #

minimum :: Ord a => (f :*: g) a -> a #

sum :: Num a => (f :*: g) a -> a #

product :: Num a => (f :*: g) a -> a #

(Traversable f, Traversable g) => Traversable (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :*: g) a -> f0 ((f :*: g) b) #

sequenceA :: Applicative f0 => (f :*: g) (f0 a) -> f0 ((f :*: g) a) #

mapM :: Monad m => (a -> m b) -> (f :*: g) a -> m ((f :*: g) b) #

sequence :: Monad m => (f :*: g) (m a) -> m ((f :*: g) a) #

(Alternative f, Alternative g) => Alternative (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: (f :*: g) a #

(<|>) :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a #

some :: (f :*: g) a -> (f :*: g) [a] #

many :: (f :*: g) a -> (f :*: g) [a] #

(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

mzero :: (f :*: g) a #

mplus :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a #

(Eq (f p), Eq (g p)) => Eq ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: (f :*: g) p -> (f :*: g) p -> Bool #

(/=) :: (f :*: g) p -> (f :*: g) p -> Bool #

(Ord (f p), Ord (g p)) => Ord ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: (f :*: g) p -> (f :*: g) p -> Ordering #

(<) :: (f :*: g) p -> (f :*: g) p -> Bool #

(<=) :: (f :*: g) p -> (f :*: g) p -> Bool #

(>) :: (f :*: g) p -> (f :*: g) p -> Bool #

(>=) :: (f :*: g) p -> (f :*: g) p -> Bool #

max :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

min :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

(Read (f p), Read (g p)) => Read ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

readsPrec :: Int -> ReadS ((f :*: g) p) #

readList :: ReadS [(f :*: g) p] #

readPrec :: ReadPrec ((f :*: g) p) #

readListPrec :: ReadPrec [(f :*: g) p] #

(Show (f p), Show (g p)) => Show ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :*: g) p -> ShowS #

show :: (f :*: g) p -> String #

showList :: [(f :*: g) p] -> ShowS #

Generic ((f :*: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p) :: Type -> Type #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

sconcat :: NonEmpty ((f :*: g) p) -> (f :*: g) p #

stimes :: Integral b => b -> (f :*: g) p -> (f :*: g) p #

(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :*: g) p #

mappend :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

mconcat :: [(f :*: g) p] -> (f :*: g) p #

type Rep1 (f :*: g :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

data U1 (p :: k) :: forall k. k -> Type #

Unit: used for constructors without arguments

Constructors

U1 
Instances
Generic1 (U1 :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 U1 :: k -> Type #

Methods

from1 :: U1 a -> Rep1 U1 a #

to1 :: Rep1 U1 a -> U1 a #

GEq (U1 :: LoT k -> Type) (tys :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Eq

Methods

geq :: U1 tys -> U1 tys -> Bool Source #

GFunctor (U1 :: LoT k -> Type) v (as :: LoT k) (bs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Functor

Methods

gfmap :: Mappings v as bs -> U1 as -> U1 bs Source #

Conv (U1 :: Type -> Type) (U1 :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: U1 tys -> U1 a Source #

toKindGenerics :: U1 a -> U1 tys Source #

Monad (U1 :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(>>=) :: U1 a -> (a -> U1 b) -> U1 b #

(>>) :: U1 a -> U1 b -> U1 b #

return :: a -> U1 a #

fail :: String -> U1 a #

Functor (U1 :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> U1 a -> U1 b #

(<$) :: a -> U1 b -> U1 a #

Applicative (U1 :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> U1 a #

(<*>) :: U1 (a -> b) -> U1 a -> U1 b #

liftA2 :: (a -> b -> c) -> U1 a -> U1 b -> U1 c #

(*>) :: U1 a -> U1 b -> U1 b #

(<*) :: U1 a -> U1 b -> U1 a #

Foldable (U1 :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => U1 m -> m #

foldMap :: Monoid m => (a -> m) -> U1 a -> m #

foldr :: (a -> b -> b) -> b -> U1 a -> b #

foldr' :: (a -> b -> b) -> b -> U1 a -> b #

foldl :: (b -> a -> b) -> b -> U1 a -> b #

foldl' :: (b -> a -> b) -> b -> U1 a -> b #

foldr1 :: (a -> a -> a) -> U1 a -> a #

foldl1 :: (a -> a -> a) -> U1 a -> a #

toList :: U1 a -> [a] #

null :: U1 a -> Bool #

length :: U1 a -> Int #

elem :: Eq a => a -> U1 a -> Bool #

maximum :: Ord a => U1 a -> a #

minimum :: Ord a => U1 a -> a #

sum :: Num a => U1 a -> a #

product :: Num a => U1 a -> a #

Traversable (U1 :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> U1 a -> f (U1 b) #

sequenceA :: Applicative f => U1 (f a) -> f (U1 a) #

mapM :: Monad m => (a -> m b) -> U1 a -> m (U1 b) #

sequence :: Monad m => U1 (m a) -> m (U1 a) #

Alternative (U1 :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: U1 a #

(<|>) :: U1 a -> U1 a -> U1 a #

some :: U1 a -> U1 [a] #

many :: U1 a -> U1 [a] #

MonadPlus (U1 :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

mzero :: U1 a #

mplus :: U1 a -> U1 a -> U1 a #

Eq (U1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: U1 p -> U1 p -> Bool #

(/=) :: U1 p -> U1 p -> Bool #

Ord (U1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: U1 p -> U1 p -> Ordering #

(<) :: U1 p -> U1 p -> Bool #

(<=) :: U1 p -> U1 p -> Bool #

(>) :: U1 p -> U1 p -> Bool #

(>=) :: U1 p -> U1 p -> Bool #

max :: U1 p -> U1 p -> U1 p #

min :: U1 p -> U1 p -> U1 p #

Read (U1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show (U1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> U1 p -> ShowS #

show :: U1 p -> String #

showList :: [U1 p] -> ShowS #

Generic (U1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (U1 p) :: Type -> Type #

Methods

from :: U1 p -> Rep (U1 p) x #

to :: Rep (U1 p) x -> U1 p #

Semigroup (U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: U1 p -> U1 p -> U1 p #

sconcat :: NonEmpty (U1 p) -> U1 p #

stimes :: Integral b => b -> U1 p -> U1 p #

Monoid (U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: U1 p #

mappend :: U1 p -> U1 p -> U1 p #

mconcat :: [U1 p] -> U1 p #

type Rep1 (U1 :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (U1 :: k -> Type) = D1 (MetaData "U1" "GHC.Generics" "base" False) (C1 (MetaCons "U1" PrefixI False) (U1 :: k -> Type))
type Rep (U1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

type Rep (U1 p) = D1 (MetaData "U1" "GHC.Generics" "base" False) (C1 (MetaCons "U1" PrefixI False) (U1 :: Type -> Type))

newtype M1 i (c :: Meta) (f :: k -> Type) (p :: k) :: forall k. Type -> Meta -> (k -> Type) -> k -> Type #

Meta-information (constructor names, etc.)

Constructors

M1 

Fields

Instances
Generic1 (M1 i c f :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (M1 i c f) :: k -> Type #

Methods

from1 :: M1 i c f a -> Rep1 (M1 i c f) a #

to1 :: Rep1 (M1 i c f) a -> M1 i c f a #

GEq f tys => GEq (M1 i c f :: LoT k -> Type) (tys :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Eq

Methods

geq :: M1 i c f tys -> M1 i c f tys -> Bool Source #

Conv f f' tys => Conv (M1 i c f) (f' :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: f' tys -> M1 i c f a Source #

toKindGenerics :: M1 i c f a -> f' tys Source #

GFunctor f v as bs => GFunctor (M1 i c f :: LoT k -> Type) v (as :: LoT k) (bs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Functor

Methods

gfmap :: Mappings v as bs -> M1 i c f as -> M1 i c f bs Source #

Conv f f' tys => Conv (M1 i c f) (M1 i c f' :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: M1 i c f' tys -> M1 i c f a Source #

toKindGenerics :: M1 i c f a -> M1 i c f' tys Source #

Monad f => Monad (M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(>>=) :: M1 i c f a -> (a -> M1 i c f b) -> M1 i c f b #

(>>) :: M1 i c f a -> M1 i c f b -> M1 i c f b #

return :: a -> M1 i c f a #

fail :: String -> M1 i c f a #

Functor f => Functor (M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> M1 i c f a -> M1 i c f b #

(<$) :: a -> M1 i c f b -> M1 i c f a #

Applicative f => Applicative (M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> M1 i c f a #

(<*>) :: M1 i c f (a -> b) -> M1 i c f a -> M1 i c f b #

liftA2 :: (a -> b -> c0) -> M1 i c f a -> M1 i c f b -> M1 i c f c0 #

(*>) :: M1 i c f a -> M1 i c f b -> M1 i c f b #

(<*) :: M1 i c f a -> M1 i c f b -> M1 i c f a #

Foldable f => Foldable (M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => M1 i c f m -> m #

foldMap :: Monoid m => (a -> m) -> M1 i c f a -> m #

foldr :: (a -> b -> b) -> b -> M1 i c f a -> b #

foldr' :: (a -> b -> b) -> b -> M1 i c f a -> b #

foldl :: (b -> a -> b) -> b -> M1 i c f a -> b #

foldl' :: (b -> a -> b) -> b -> M1 i c f a -> b #

foldr1 :: (a -> a -> a) -> M1 i c f a -> a #

foldl1 :: (a -> a -> a) -> M1 i c f a -> a #

toList :: M1 i c f a -> [a] #

null :: M1 i c f a -> Bool #

length :: M1 i c f a -> Int #

elem :: Eq a => a -> M1 i c f a -> Bool #

maximum :: Ord a => M1 i c f a -> a #

minimum :: Ord a => M1 i c f a -> a #

sum :: Num a => M1 i c f a -> a #

product :: Num a => M1 i c f a -> a #

Traversable f => Traversable (M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> M1 i c f a -> f0 (M1 i c f b) #

sequenceA :: Applicative f0 => M1 i c f (f0 a) -> f0 (M1 i c f a) #

mapM :: Monad m => (a -> m b) -> M1 i c f a -> m (M1 i c f b) #

sequence :: Monad m => M1 i c f (m a) -> m (M1 i c f a) #

Alternative f => Alternative (M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: M1 i c f a #

(<|>) :: M1 i c f a -> M1 i c f a -> M1 i c f a #

some :: M1 i c f a -> M1 i c f [a] #

many :: M1 i c f a -> M1 i c f [a] #

MonadPlus f => MonadPlus (M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

mzero :: M1 i c f a #

mplus :: M1 i c f a -> M1 i c f a -> M1 i c f a #

Eq (f p) => Eq (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: M1 i c f p -> M1 i c f p -> Bool #

(/=) :: M1 i c f p -> M1 i c f p -> Bool #

Ord (f p) => Ord (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: M1 i c f p -> M1 i c f p -> Ordering #

(<) :: M1 i c f p -> M1 i c f p -> Bool #

(<=) :: M1 i c f p -> M1 i c f p -> Bool #

(>) :: M1 i c f p -> M1 i c f p -> Bool #

(>=) :: M1 i c f p -> M1 i c f p -> Bool #

max :: M1 i c f p -> M1 i c f p -> M1 i c f p #

min :: M1 i c f p -> M1 i c f p -> M1 i c f p #

Read (f p) => Read (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

readsPrec :: Int -> ReadS (M1 i c f p) #

readList :: ReadS [M1 i c f p] #

readPrec :: ReadPrec (M1 i c f p) #

readListPrec :: ReadPrec [M1 i c f p] #

Show (f p) => Show (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> M1 i c f p -> ShowS #

show :: M1 i c f p -> String #

showList :: [M1 i c f p] -> ShowS #

Generic (M1 i c f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (M1 i c f p) :: Type -> Type #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x #

to :: Rep (M1 i c f p) x -> M1 i c f p #

Semigroup (f p) => Semigroup (M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: M1 i c f p -> M1 i c f p -> M1 i c f p #

sconcat :: NonEmpty (M1 i c f p) -> M1 i c f p #

stimes :: Integral b => b -> M1 i c f p -> M1 i c f p #

Monoid (f p) => Monoid (M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: M1 i c f p #

mappend :: M1 i c f p -> M1 i c f p -> M1 i c f p #

mconcat :: [M1 i c f p] -> M1 i c f p #

type Rep1 (M1 i c f :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (M1 i c f :: k -> Type) = D1 (MetaData "M1" "GHC.Generics" "base" True) (C1 (MetaCons "M1" PrefixI True) (S1 (MetaSel (Just "unM1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f)))
type Rep (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

type Rep (M1 i c f p) = D1 (MetaData "M1" "GHC.Generics" "base" True) (C1 (MetaCons "M1" PrefixI True) (S1 (MetaSel (Just "unM1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f p))))

newtype F (t :: Atom d *) (x :: LoT d) Source #

Fields: used to represent each of the (visible) arguments to a constructor. Replaces the K1 type from GHC.Generics. The type of the field is represented by an Atom from Data.PolyKinded.Atom.

instance GenericK [] (a :&&: LoT0) where
  type RepK [] = F V0 :*: F ([] :$: V0)

Constructors

F 

Fields

  • unF :: Ty t x
     
Instances
Eq (Ty t tys) => GEq (F t :: LoT k -> Type) (tys :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Eq

Methods

geq :: F t tys -> F t tys -> Bool Source #

GFunctorArg t v Co as bs => GFunctor (F t :: LoT k -> Type) v (as :: LoT k) (bs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Functor

Methods

gfmap :: Mappings v as bs -> F t as -> F t bs Source #

k ~ Ty t tys => Conv (K1 p k :: Type -> Type) (F t :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: F t tys -> K1 p k a Source #

toKindGenerics :: K1 p k a -> F t tys Source #

Show (Ty t x) => Show (F t x) Source # 
Instance details

Defined in Generics.Kind

Methods

showsPrec :: Int -> F t x -> ShowS #

show :: F t x -> String #

showList :: [F t x] -> ShowS #

data ((c :: Atom d Constraint) :=>: (f :: LoT d -> *)) (x :: LoT d) where Source #

Constraints: used to represent constraints in a constructor. Replaces the '(:=>:)' type from GHC.Generics.Extra.

data Showable a = Show a => a -> X a

instance GenericK Showable (a :&&: LoT0) where
  type RepK Showable = (Show :$: a) :=>: (F V0)

Constructors

C :: Ty c x => f x -> (c :=>: f) x 
Instances
Ty c tys -> GEq f tys => GEq (c :=>: f :: LoT k -> Type) (tys :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Eq

Methods

geq :: (c :=>: f) tys -> (c :=>: f) tys -> Bool Source #

(Ty c as -> GFunctor f v as bs, Ty c bs) => GFunctor (c :=>: f :: LoT k -> Type) v (as :: LoT k) (bs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Functor

Methods

gfmap :: Mappings v as bs -> (c :=>: f) as -> (c :=>: f) bs Source #

(k ~ Ty t tys, Conv f f' tys) => Conv (k :=>: f) (t :=>: f' :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: (t :=>: f') tys -> (k :=>: f) a Source #

toKindGenerics :: (k :=>: f) a -> (t :=>: f') tys Source #

data E (f :: LoT (k -> d) -> *) (x :: LoT d) where Source #

Existentials: a representation of the form E f describes a constructor whose inner type is represented by f, and where the type variable at index 0, V0, is existentially quantified.

data Exists where
 E :: t -> Exists

instance GenericK Exists LoT0 where
  type RepK Exists = E (F V0)

Constructors

E :: forall (t :: k) d (f :: LoT (k -> d) -> *) (x :: LoT d). f (t :&&: x) -> E f x 
Instances
(forall (t :: k1). (GEq f (t :&&: tys), Typeable t)) => GEq (E f :: LoT k2 -> Type) (tys :: LoT k2) Source # 
Instance details

Defined in Generics.Kind.Derive.Eq

Methods

geq :: E f tys -> E f tys -> Bool Source #

(forall t. GFunctor f (Co ': v) (t :&&: as) (t :&&: bs)) => GFunctor (E f :: LoT k -> Type) v (as :: LoT k) (bs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Functor

Methods

gfmap :: Mappings v as bs -> E f as -> E f bs Source #

data ERefl (f :: LoT (k -> d) -> *) (x :: LoT d) where Source #

Existentials with reflection: similar to E, but in addition we remember the type of the existential variable.

data Exists where
 E :: Typeable t => t -> Exists

instance GenericK Exists LoT0 where
  type RepK Exists = ERefl (F V0)

Constructors

ERefl :: forall (t :: k) d (f :: LoT (k -> d) -> *) (x :: LoT d). Typeable t => f (t :&&: x) -> ERefl f x 
Instances
(forall (t :: k1). GEq f (t :&&: tys)) => GEq (ERefl f :: LoT k2 -> Type) (tys :: LoT k2) Source # 
Instance details

Defined in Generics.Kind.Derive.Eq

Methods

geq :: ERefl f tys -> ERefl f tys -> Bool Source #

(forall t. GFunctor f (Co ': v) (t :&&: as) (t :&&: bs)) => GFunctor (ERefl f :: LoT k -> Type) v (as :: LoT k) (bs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Derive.Functor

Methods

gfmap :: Mappings v as bs -> ERefl f as -> ERefl f bs Source #

Generic type classes

class GenericK (f :: k) (x :: LoT k) where Source #

Representable types of any kind. The definition of an instance must mention the type constructor along with a list of types of the corresponding length. For example:

instance GenericK Int    LoT0
instance GenericK []     (a :&&: LoT0)
instance GenericK Either (a :&&: b :&&: LoT0)

Minimal complete definition

Nothing

Associated Types

type RepK f :: LoT k -> * Source #

Methods

fromK :: (f :@@: x) -> RepK f x Source #

Convert the data type to its representation.

fromK :: (Generic (f :@@: x), Conv (Rep (f :@@: x)) (RepK f) x) => (f :@@: x) -> RepK f x Source #

Convert the data type to its representation.

toK :: RepK f x -> f :@@: x Source #

Convert from a representation to its corresponding data type.

toK :: (Generic (f :@@: x), Conv (Rep (f :@@: x)) (RepK f) x) => RepK f x -> f :@@: x Source #

Convert from a representation to its corresponding data type.

Instances
GenericK Maybe (a :&&: LoT0 :: LoT (Type -> Type)) Source # 
Instance details

Defined in Generics.Kind.Examples

Associated Types

type RepK Maybe :: LoT k -> Type Source #

Methods

fromK :: (Maybe :@@: (a :&&: LoT0)) -> RepK Maybe (a :&&: LoT0) Source #

toK :: RepK Maybe (a :&&: LoT0) -> Maybe :@@: (a :&&: LoT0) Source #

GenericK WeirdTreeR (a :&&: LoT0 :: LoT (Type -> Type)) Source # 
Instance details

Defined in Generics.Kind.Examples

Associated Types

type RepK WeirdTreeR :: LoT k -> Type Source #

Methods

fromK :: (WeirdTreeR :@@: (a :&&: LoT0)) -> RepK WeirdTreeR (a :&&: LoT0) Source #

toK :: RepK WeirdTreeR (a :&&: LoT0) -> WeirdTreeR :@@: (a :&&: LoT0) Source #

GenericK WeirdTree (a :&&: LoT0 :: LoT (Type -> Type)) Source # 
Instance details

Defined in Generics.Kind.Examples

Associated Types

type RepK WeirdTree :: LoT k -> Type Source #

Methods

fromK :: (WeirdTree :@@: (a :&&: LoT0)) -> RepK WeirdTree (a :&&: LoT0) Source #

toK :: RepK WeirdTree (a :&&: LoT0) -> WeirdTree :@@: (a :&&: LoT0) Source #

GenericK Tree (a :&&: LoT0 :: LoT (Type -> Type)) Source # 
Instance details

Defined in Generics.Kind.Examples

Associated Types

type RepK Tree :: LoT k -> Type Source #

Methods

fromK :: (Tree :@@: (a :&&: LoT0)) -> RepK Tree (a :&&: LoT0) Source #

toK :: RepK Tree (a :&&: LoT0) -> Tree :@@: (a :&&: LoT0) Source #

type GenericF t f x = (GenericK f x, x ~ SplitF t f, t ~ (f :@@: x)) Source #

fromF :: forall f t x. GenericF t f x => t -> RepK f x Source #

toF :: forall f t x. GenericF t f x => RepK f x -> t Source #

type GenericN n t f x = (GenericK f x, TyEnv f x ~ SplitN n t, t ~ (f :@@: x)) Source #

fromN :: forall n t f x. GenericN n t f x => t -> RepK f x Source #

toN :: forall n t f x. GenericN n t f x => RepK f x -> t Source #

type GenericS t f x = (Split t f x, GenericK f x) Source #

GenericS t f x states that the ground type t is split by default as the constructor f and a list of types @x$, and that a GenericK instance exists for that constructor.

This constraint provides an external interface similar to that provided by Generic in GHC.Generics.

fromS :: forall t f x. GenericS t f x => t -> RepK f x Source #

toS :: forall t f x. GenericS t f x => RepK f x -> t Source #

Bridging with GHC.Generics

class Conv (gg :: * -> *) (kg :: LoT d -> *) (tys :: LoT d) where Source #

Bridges a representation of a data type using the combinators in GHC.Generics with a representation using this module. You are never expected to manipulate this type class directly, it is part of the deriving mechanism for GenericK.

Methods

toGhcGenerics :: kg tys -> gg a Source #

toKindGenerics :: gg a -> kg tys Source #

Instances
Conv (U1 :: Type -> Type) (U1 :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: U1 tys -> U1 a Source #

toKindGenerics :: U1 a -> U1 tys Source #

k ~ Ty t tys => Conv (K1 p k :: Type -> Type) (F t :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: F t tys -> K1 p k a Source #

toKindGenerics :: K1 p k a -> F t tys Source #

(k ~ Ty t tys, Conv f f' tys) => Conv (k :=>: f) (t :=>: f' :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: (t :=>: f') tys -> (k :=>: f) a Source #

toKindGenerics :: (k :=>: f) a -> (t :=>: f') tys Source #

(Conv f f' tys, Conv g g' tys) => Conv (f :*: g) (f' :*: g' :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: (f' :*: g') tys -> (f :*: g) a Source #

toKindGenerics :: (f :*: g) a -> (f' :*: g') tys Source #

(Conv f f' tys, Conv g g' tys) => Conv (f :+: g) (f' :+: g' :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: (f' :+: g') tys -> (f :+: g) a Source #

toKindGenerics :: (f :+: g) a -> (f' :+: g') tys Source #

Conv f f' tys => Conv (M1 i c f) (f' :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: f' tys -> M1 i c f a Source #

toKindGenerics :: M1 i c f a -> f' tys Source #

Conv f f' tys => Conv (M1 i c f) (M1 i c f' :: LoT d -> Type) (tys :: LoT d) Source # 
Instance details

Defined in Generics.Kind

Methods

toGhcGenerics :: M1 i c f' tys -> M1 i c f a Source #

toKindGenerics :: M1 i c f a -> M1 i c f' tys Source #