large-generics-0.2.1: Generic programming API for large-records and large-anon
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Record.Generic

Synopsis

Types with a generic view

class Generic a where Source #

Associated Types

type Constraints a :: (Type -> Constraint) -> Constraint Source #

Constraints a c means "all fields of a satisfy c"

type MetadataOf a :: [(Symbol, Type)] Source #

Type-level metadata

NOTE: using type-level lists without resulting in quadratic core code is extremely difficult. Any use of this type-level metadata therefore needs delibrate consideration. Some examples:

o Within the large-generics library, MetadataOf is used in the definition of HasNormalForm. This constraint is carefully defined to avoid quadratic code, as described in the presentation "Avoiding Quadratic Blow-up During Compilation" https://skillsmatter.com/skillscasts/17262-avoiding-quadratic-blow-up-during-compilation o The large-records library uses it to provide a compatibility layer between it and sop-core; this is however only for testing purposes, and the quadratic code here is simply accepted.

Methods

from :: a -> Rep I a Source #

Translate to generic representation

to :: Rep I a -> a Source #

Translate from generic representation

dict :: Constraints a c => Proxy c -> Rep (Dict c) a Source #

Construct vector of dictionaries, one for each field of the record

metadata :: proxy a -> Metadata a Source #

Metadata

newtype Rep f a Source #

Representation of some record a

The f parameter describes which functor has been applied to all fields of the record; in other words Rep I is isomorphic to the record itself.

Constructors

Rep (SmallArray (f Any)) 

Instances

Instances details
Show x => Show (Rep (K x :: Type -> Type) a) Source # 
Instance details

Defined in Data.Record.Generic.Rep.Internal

Methods

showsPrec :: Int -> Rep (K x) a -> ShowS #

show :: Rep (K x) a -> String #

showList :: [Rep (K x) a] -> ShowS #

Eq x => Eq (Rep (K x :: Type -> Type) a) Source # 
Instance details

Defined in Data.Record.Generic.Rep.Internal

Methods

(==) :: Rep (K x) a -> Rep (K x) a -> Bool #

(/=) :: Rep (K x) a -> Rep (K x) a -> Bool #

Metadata

data FieldMetadata x where Source #

Constructors

FieldMetadata :: KnownSymbol name => Proxy name -> FieldStrictness -> FieldMetadata x 

Working with type-level metadata

type family FieldName (field :: (Symbol, Type)) :: Symbol where ... Source #

Equations

FieldName '(name, _typ) = name 

type family FieldType (field :: (Symbol, Type)) :: Type where ... Source #

Equations

FieldType '(_name, typ) = typ 

class (field ~ '(FieldName field, FieldType field), KnownSymbol (FieldName field)) => IsField field Source #

Instances

Instances details
(field ~ '(FieldName field, FieldType field), KnownSymbol (FieldName field)) => IsField field Source # 
Instance details

Defined in Data.Record.Generic

Re-exports

data Dict (c :: k -> Constraint) (a :: k) where #

An explicit dictionary carrying evidence of a class constraint.

The constraint parameter is separated into a second argument so that Dict c is of the correct kind to be used directly as a parameter to e.g. NP.

Since: sop-core-0.2

Constructors

Dict :: forall {k} (c :: k -> Constraint) (a :: k). c a => Dict c a 

Instances

Instances details
Show (Dict c a) 
Instance details

Defined in Data.SOP.Dict

Methods

showsPrec :: Int -> Dict c a -> ShowS #

show :: Dict c a -> String #

showList :: [Dict c a] -> ShowS #

newtype ((f :: l -> Type) :.: (g :: k -> l)) (p :: k) infixr 7 #

Composition of functors.

Like Compose, but kind-polymorphic and with a shorter name.

Constructors

Comp (f (g p)) 

Instances

Instances details
(Foldable f, Foldable g) => Foldable (f :.: g)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> 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 #

(Eq1 f, Eq1 g) => Eq1 (f :.: g)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq :: (a -> b -> Bool) -> (f :.: g) a -> (f :.: g) b -> Bool #

(Ord1 f, Ord1 g) => Ord1 (f :.: g)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare :: (a -> b -> Ordering) -> (f :.: g) a -> (f :.: g) b -> Ordering #

(Read1 f, Read1 g) => Read1 (f :.: g)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :.: g) a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :.: g) a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :.: g) a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :.: g) a] #

(Show1 f, Show1 g) => Show1 (f :.: g)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (f :.: g) a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [(f :.: g) a] -> ShowS #

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

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

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) #

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

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

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 #

(Functor f, Functor g) => Functor (f :.: g) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

(NFData1 f, NFData1 g) => NFData1 (f :.: g)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf :: (a -> ()) -> (f :.: g) a -> () #

Monoid (f (g x)) => Monoid ((f :.: g) x)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

mempty :: (f :.: g) x #

mappend :: (f :.: g) x -> (f :.: g) x -> (f :.: g) x #

mconcat :: [(f :.: g) x] -> (f :.: g) x #

Semigroup (f (g x)) => Semigroup ((f :.: g) x)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

(<>) :: (f :.: g) x -> (f :.: g) x -> (f :.: g) x #

sconcat :: NonEmpty ((f :.: g) x) -> (f :.: g) x #

stimes :: Integral b => b -> (f :.: g) x -> (f :.: g) x #

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

Defined in Data.SOP.BasicFunctors

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 #

(Read1 f, Read1 g, Read a) => Read ((f :.: g) a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

readsPrec :: Int -> ReadS ((f :.: g) a) #

readList :: ReadS [(f :.: g) a] #

readPrec :: ReadPrec ((f :.: g) a) #

readListPrec :: ReadPrec [(f :.: g) a] #

(Show1 f, Show1 g, Show a) => Show ((f :.: g) a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

showsPrec :: Int -> (f :.: g) a -> ShowS #

show :: (f :.: g) a -> String #

showList :: [(f :.: g) a] -> ShowS #

NFData (f (g a)) => NFData ((f :.: g) a)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

rnf :: (f :.: g) a -> () #

(Eq1 f, Eq1 g, Eq a) => Eq ((f :.: g) a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

(==) :: (f :.: g) a -> (f :.: g) a -> Bool #

(/=) :: (f :.: g) a -> (f :.: g) a -> Bool #

(Ord1 f, Ord1 g, Ord a) => Ord ((f :.: g) a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

compare :: (f :.: g) a -> (f :.: g) a -> Ordering #

(<) :: (f :.: g) a -> (f :.: g) a -> Bool #

(<=) :: (f :.: g) a -> (f :.: g) a -> Bool #

(>) :: (f :.: g) a -> (f :.: g) a -> Bool #

(>=) :: (f :.: g) a -> (f :.: g) a -> Bool #

max :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a #

min :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a #

type Rep ((f :.: g) p) 
Instance details

Defined in Data.SOP.BasicFunctors

type Rep ((f :.: g) p) = D1 ('MetaData ":.:" "Data.SOP.BasicFunctors" "sop-core-0.5.0.2-8cmRYB37llUAjnR98I5kI0" 'True) (C1 ('MetaCons "Comp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (g p)))))
type Code ((f :.: g) p) 
Instance details

Defined in Generics.SOP.Instances

type Code ((f :.: g) p) = '['[f (g p)]]
type DatatypeInfoOf ((f :.: g) p) 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf ((f :.: g) p) = 'Newtype "Data.SOP.BasicFunctors" ":.:" ('Constructor "Comp")

newtype I a #

The identity type functor.

Like Identity, but with a shorter name.

Constructors

I a 

Instances

Instances details
Foldable I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> I a -> m #

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

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

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

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

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

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

toList :: I a -> [a] #

null :: I a -> Bool #

length :: I a -> Int #

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

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

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

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

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

Eq1 I

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq :: (a -> b -> Bool) -> I a -> I b -> Bool #

Ord1 I

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare :: (a -> b -> Ordering) -> I a -> I b -> Ordering #

Read1 I

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (I a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [I a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (I a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [I a] #

Show1 I

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> I a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [I a] -> ShowS #

Traversable I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

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

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

Applicative I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

pure :: a -> I a #

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

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

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

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

Functor I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

Monad I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

return :: a -> I a #

NFData1 I

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf :: (a -> ()) -> I a -> () #

Monoid a => Monoid (I a)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

mempty :: I a #

mappend :: I a -> I a -> I a #

mconcat :: [I a] -> I a #

Semigroup a => Semigroup (I a)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

(<>) :: I a -> I a -> I a #

sconcat :: NonEmpty (I a) -> I a #

stimes :: Integral b => b -> I a -> I a #

Generic (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Associated Types

type Rep (I a) :: Type -> Type #

Methods

from :: I a -> Rep (I a) x #

to :: Rep (I a) x -> I a #

Read a => Read (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

readsPrec :: Int -> ReadS (I a) #

readList :: ReadS [I a] #

readPrec :: ReadPrec (I a) #

readListPrec :: ReadPrec [I a] #

Show a => Show (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

showsPrec :: Int -> I a -> ShowS #

show :: I a -> String #

showList :: [I a] -> ShowS #

NFData a => NFData (I a)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

rnf :: I a -> () #

Eq a => Eq (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

(==) :: I a -> I a -> Bool #

(/=) :: I a -> I a -> Bool #

Ord a => Ord (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

compare :: I a -> I a -> Ordering #

(<) :: I a -> I a -> Bool #

(<=) :: I a -> I a -> Bool #

(>) :: I a -> I a -> Bool #

(>=) :: I a -> I a -> Bool #

max :: I a -> I a -> I a #

min :: I a -> I a -> I a #

type Rep (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

type Rep (I a) = D1 ('MetaData "I" "Data.SOP.BasicFunctors" "sop-core-0.5.0.2-8cmRYB37llUAjnR98I5kI0" 'True) (C1 ('MetaCons "I" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Code (I a) 
Instance details

Defined in Generics.SOP.Instances

type Code (I a) = '['[a]]
type DatatypeInfoOf (I a) 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf (I a) = 'Newtype "Data.SOP.BasicFunctors" "I" ('Constructor "I")

newtype K a (b :: k) #

The constant type functor.

Like Constant, but kind-polymorphic in its second argument and with a shorter name.

Constructors

K a 

Instances

Instances details
Eq2 (K :: Type -> Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> K a c -> K b d -> Bool #

Ord2 (K :: Type -> Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> K a c -> K b d -> Ordering #

Read2 (K :: Type -> Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (K a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [K a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (K a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [K a b] #

Show2 (K :: Type -> TYPE LiftedRep -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> K a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [K a b] -> ShowS #

NFData2 (K :: Type -> Type -> Type)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> K a b -> () #

Foldable (K a :: TYPE LiftedRep -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fold :: Monoid m => K a m -> m #

foldMap :: Monoid m => (a0 -> m) -> K a a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> K a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> K a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> K a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> K a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> K a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 #

toList :: K a a0 -> [a0] #

null :: K a a0 -> Bool #

length :: K a a0 -> Int #

elem :: Eq a0 => a0 -> K a a0 -> Bool #

maximum :: Ord a0 => K a a0 -> a0 #

minimum :: Ord a0 => K a a0 -> a0 #

sum :: Num a0 => K a a0 -> a0 #

product :: Num a0 => K a a0 -> a0 #

Eq a => Eq1 (K a :: Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq :: (a0 -> b -> Bool) -> K a a0 -> K a b -> Bool #

Ord a => Ord1 (K a :: Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare :: (a0 -> b -> Ordering) -> K a a0 -> K a b -> Ordering #

Read a => Read1 (K a :: Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (K a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [K a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (K a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [K a a0] #

Show a => Show1 (K a :: TYPE LiftedRep -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> K a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [K a a0] -> ShowS #

Traversable (K a :: TYPE LiftedRep -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

sequenceA :: Applicative f => K a (f a0) -> f (K a a0) #

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

sequence :: Monad m => K a (m a0) -> m (K a a0) #

Monoid a => Applicative (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

pure :: a0 -> K a a0 #

(<*>) :: K a (a0 -> b) -> K a a0 -> K a b #

liftA2 :: (a0 -> b -> c) -> K a a0 -> K a b -> K a c #

(*>) :: K a a0 -> K a b -> K a b #

(<*) :: K a a0 -> K a b -> K a a0 #

Functor (K a :: TYPE LiftedRep -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fmap :: (a0 -> b) -> K a a0 -> K a b #

(<$) :: a0 -> K a b -> K a a0 #

Show x => Show (Rep (K x :: Type -> Type) a) Source # 
Instance details

Defined in Data.Record.Generic.Rep.Internal

Methods

showsPrec :: Int -> Rep (K x) a -> ShowS #

show :: Rep (K x) a -> String #

showList :: [Rep (K x) a] -> ShowS #

NFData a => NFData1 (K a :: TYPE LiftedRep -> Type)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf :: (a0 -> ()) -> K a a0 -> () #

Eq x => Eq (Rep (K x :: Type -> Type) a) Source # 
Instance details

Defined in Data.Record.Generic.Rep.Internal

Methods

(==) :: Rep (K x) a -> Rep (K x) a -> Bool #

(/=) :: Rep (K x) a -> Rep (K x) a -> Bool #

Monoid a => Monoid (K a b)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

mempty :: K a b #

mappend :: K a b -> K a b -> K a b #

mconcat :: [K a b] -> K a b #

Semigroup a => Semigroup (K a b)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

(<>) :: K a b -> K a b -> K a b #

sconcat :: NonEmpty (K a b) -> K a b #

stimes :: Integral b0 => b0 -> K a b -> K a b #

Generic (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Associated Types

type Rep (K a b) :: Type -> Type #

Methods

from :: K a b -> Rep (K a b) x #

to :: Rep (K a b) x -> K a b #

Read a => Read (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

readsPrec :: Int -> ReadS (K a b) #

readList :: ReadS [K a b] #

readPrec :: ReadPrec (K a b) #

readListPrec :: ReadPrec [K a b] #

Show a => Show (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

showsPrec :: Int -> K a b -> ShowS #

show :: K a b -> String #

showList :: [K a b] -> ShowS #

NFData a => NFData (K a b)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

rnf :: K a b -> () #

Eq a => Eq (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

(==) :: K a b -> K a b -> Bool #

(/=) :: K a b -> K a b -> Bool #

Ord a => Ord (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

compare :: K a b -> K a b -> Ordering #

(<) :: K a b -> K a b -> Bool #

(<=) :: K a b -> K a b -> Bool #

(>) :: K a b -> K a b -> Bool #

(>=) :: K a b -> K a b -> Bool #

max :: K a b -> K a b -> K a b #

min :: K a b -> K a b -> K a b #

type Rep (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

type Rep (K a b) = D1 ('MetaData "K" "Data.SOP.BasicFunctors" "sop-core-0.5.0.2-8cmRYB37llUAjnR98I5kI0" 'True) (C1 ('MetaCons "K" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Code (K a b) 
Instance details

Defined in Generics.SOP.Instances

type Code (K a b) = '['[a]]
type DatatypeInfoOf (K a b) 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf (K a b) = 'Newtype "Data.SOP.BasicFunctors" "K" ('Constructor "K")

unK :: forall {k} a (b :: k). K a b -> a #

Extract the contents of a K value.

unI :: I a -> a #

Extract the contents of an I value.

unComp :: forall {l} {k} f (g :: k -> l) (p :: k). (f :.: g) p -> f (g p) #

Extract the contents of a Comp value.

mapII :: (a -> b) -> I a -> I b #

Lift the given function.

Since: sop-core-0.2.5.0

mapIK :: forall {k} a b (c :: k). (a -> b) -> I a -> K b c #

Lift the given function.

Since: sop-core-0.2.5.0

mapKI :: forall {k} a b (c :: k). (a -> b) -> K a c -> I b #

Lift the given function.

Since: sop-core-0.2.5.0

mapKK :: forall {k1} {k2} a b (c :: k1) (d :: k2). (a -> b) -> K a c -> K b d #

Lift the given function.

Since: sop-core-0.2.5.0

mapIII :: (a -> b -> c) -> I a -> I b -> I c #

Lift the given function.

Since: sop-core-0.2.5.0

mapIIK :: forall {k} a b c (d :: k). (a -> b -> c) -> I a -> I b -> K c d #

Lift the given function.

Since: sop-core-0.2.5.0

mapIKI :: forall {k} a b c (d :: k). (a -> b -> c) -> I a -> K b d -> I c #

Lift the given function.

Since: sop-core-0.2.5.0

mapIKK :: forall {k1} {k2} a b c (d :: k1) (e :: k2). (a -> b -> c) -> I a -> K b d -> K c e #

Lift the given function.

Since: sop-core-0.2.5.0

mapKII :: forall {k} a b c (d :: k). (a -> b -> c) -> K a d -> I b -> I c #

Lift the given function.

Since: sop-core-0.2.5.0

mapKIK :: forall {k1} {k2} a b c (d :: k1) (e :: k2). (a -> b -> c) -> K a d -> I b -> K c e #

Lift the given function.

Since: sop-core-0.2.5.0

mapKKI :: forall {k1} {k2} a b c (d :: k1) (e :: k2). (a -> b -> c) -> K a d -> K b e -> I c #

Lift the given function.

Since: sop-core-0.2.5.0

mapKKK :: forall {k1} {k2} {k3} a b c (d :: k1) (e :: k2) (f :: k3). (a -> b -> c) -> K a d -> K b e -> K c f #

Lift the given function.

Since: sop-core-0.2.5.0

newtype ((f :: k -> Type) -.-> (g :: k -> Type)) (a :: k) infixr 1 #

Lifted functions.

Constructors

Fn 

Fields

  • apFn :: f a -> g a
     

Instances

Instances details
type Code ((f -.-> g) a) 
Instance details

Defined in Generics.SOP.Instances

type Code ((f -.-> g) a) = '['[f a -> g a]]
type DatatypeInfoOf ((f -.-> g) a) 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf ((f -.-> g) a) = 'Newtype "Data.SOP.Classes" "-.->" ('Record "Fn" '['FieldInfo "apFn"])

data Proxy (t :: k) #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 

Instances

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

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: forall (a :: k0). Proxy a -> Rep1 Proxy a #

to1 :: forall (a :: k0). Rep1 Proxy a -> Proxy a #

FromJSON1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Proxy a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Proxy a] #

ToJSON1 (Proxy :: TYPE LiftedRep -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Proxy a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Proxy a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Proxy a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Proxy a] -> Encoding #

Foldable (Proxy :: TYPE LiftedRep -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Proxy a -> m #

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

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

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

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

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

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

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

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

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

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

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

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

Eq1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool #

Ord1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering #

Read1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] #

Show1 (Proxy :: TYPE LiftedRep -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS #

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

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

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

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

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

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

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

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

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

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

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

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

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

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

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

return :: a -> Proxy a #

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

NFData1 (Proxy :: TYPE LiftedRep -> Type)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Proxy a -> () #

Hashable1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Proxy a -> Int #

FromJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Data t => Data (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) #

toConstr :: Proxy t -> Constr #

dataTypeOf :: Proxy t -> DataType #

dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) #

dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) #

gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int #

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

NFData (Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Proxy a -> () #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int #

hash :: Proxy a -> Int #

type Rep1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))
type Code (Proxy t) 
Instance details

Defined in Generics.SOP.Instances

type Code (Proxy t) = '['[] :: [Type]]
type DatatypeInfoOf (Proxy t) 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf (Proxy t) = 'ADT "Data.Proxy" "Proxy" '['Constructor "Proxy"] '['[] :: [StrictnessInfo]]