Copyright | (c) Universiteit Utrecht 2010-2011 University of Oxford 2012-2014 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | libraries@haskell.org |
Stability | internal |
Portability | non-portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
If you're using GHC.Generics
, you should consider using the
http://hackage.haskell.org/package/generic-deriving package, which
contains many useful generic functions.
Since: base-4.6.0.0
Synopsis
- data V1 (p :: k)
- data U1 (p :: k) = U1
- newtype Par1 p = Par1 {
- unPar1 :: p
- newtype Rec1 (f :: k -> Type) (p :: k) = Rec1 {
- unRec1 :: f p
- newtype K1 i c (p :: k) = K1 {
- unK1 :: c
- newtype M1 i (c :: Meta) (f :: k -> Type) (p :: k) = M1 {
- unM1 :: f p
- data ((f :: k -> Type) :+: (g :: k -> Type)) (p :: k)
- data ((f :: k -> Type) :*: (g :: k -> Type)) (p :: k) = (f p) :*: (g p)
- newtype ((f :: k2 -> Type) :.: (g :: k1 -> k2)) (p :: k1) = Comp1 {
- unComp1 :: f (g p)
- data family URec a (p :: k)
- type UAddr = URec (Ptr ()) :: k -> Type
- type UChar = URec Char :: k -> Type
- type UDouble = URec Double :: k -> Type
- type UFloat = URec Float :: k -> Type
- type UInt = URec Int :: k -> Type
- type UWord = URec Word :: k -> Type
- type Rec0 = K1 R :: Type -> k -> Type
- data R
- type D1 = M1 D :: Meta -> (k -> Type) -> k -> Type
- type C1 = M1 C :: Meta -> (k -> Type) -> k -> Type
- type S1 = M1 S :: Meta -> (k -> Type) -> k -> Type
- data D
- data C
- data S
- class Datatype (d :: k) where
- datatypeName :: forall k1 t (f :: k1 -> Type) (a :: k1). t d f a -> [Char]
- moduleName :: forall k1 t (f :: k1 -> Type) (a :: k1). t d f a -> [Char]
- packageName :: forall k1 t (f :: k1 -> Type) (a :: k1). t d f a -> [Char]
- isNewtype :: forall k1 t (f :: k1 -> Type) (a :: k1). t d f a -> Bool
- class Constructor (c :: k) where
- class Selector (s :: k) where
- selName :: forall k1 t (f :: k1 -> Type) (a :: k1). t s f a -> [Char]
- selSourceUnpackedness :: forall k1 t (f :: k1 -> Type) (a :: k1). t s f a -> SourceUnpackedness
- selSourceStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t s f a -> SourceStrictness
- selDecidedStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t s f a -> DecidedStrictness
- data Fixity
- data FixityI
- data Associativity
- prec :: Fixity -> Int
- data SourceUnpackedness
- data SourceStrictness
- data DecidedStrictness
- data Meta
- class Generic a where
- class Generic1 (f :: k -> Type) where
- newtype Generically a = Generically a
- newtype Generically1 (f :: k -> Type) (a :: k) where
- Generically1 :: forall {k} (f :: k -> Type) (a :: k). f a -> Generically1 f a
Introduction
Datatype-generic functions are based on the idea of converting values of
a datatype T
into corresponding values of a (nearly) isomorphic type
.
The type Rep
T
is
built from a limited set of type constructors, all provided by this module. A
datatype-generic function is then an overloaded function with instances
for most of these type constructors, together with a wrapper that performs
the mapping between Rep
TT
and
. By using this technique, we merely need
a few generic instances in order to implement functionality that works for any
representable type.Rep
T
Representable types are collected in the Generic
class, which defines the
associated type Rep
as well as conversion functions from
and to
.
Typically, you will not define Generic
instances by hand, but have the compiler
derive them for you.
Representing datatypes
The key to defining your own datatype-generic functions is to understand how to represent datatypes using the given set of type constructors.
Let us look at an example first:
data Tree a = Leaf a | Node (Tree a) (Tree a)
deriving Generic
The above declaration (which requires the language pragma DeriveGeneric
)
causes the following representation to be generated:
instanceGeneric
(Tree a) where typeRep
(Tree a) =D1
('MetaData "Tree" "Main" "package-name" 'False) (C1
('MetaCons "Leaf" 'PrefixI 'False) (S1
('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0
a)):+:
C1
('MetaCons "Node" 'PrefixI 'False) (S1
('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0
(Tree a)):*:
S1
('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0
(Tree a)))) ...
Hint: You can obtain information about the code being generated from GHC by passing
the -ddump-deriv
flag. In GHCi, you can expand a type family such as Rep
using
the :kind!
command.
This is a lot of information! However, most of it is actually merely meta-information that makes names of datatypes and constructors and more available on the type level.
Here is a reduced representation for Tree
with nearly all meta-information removed,
for now keeping only the most essential aspects:
instanceGeneric
(Tree a) where typeRep
(Tree a) =Rec0
a:+:
(Rec0
(Tree a):*:
Rec0
(Tree a))
The Tree
datatype has two constructors. The representation of individual constructors
is combined using the binary type constructor :+:
.
The first constructor consists of a single field, which is the parameter a
. This is
represented as
.Rec0
a
The second constructor consists of two fields. Each is a recursive field of type Tree a
,
represented as
. Representations of individual fields are combined using
the binary type constructor Rec0
(Tree a):*:
.
Now let us explain the additional tags being used in the complete representation:
- The
tag indicates several things. TheS1
('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)'Nothing
indicates that there is no record field selector associated with this field of the constructor (if there were, it would have been marked'Just "recordName"
instead). The other types contain meta-information on the field's strictness: - There is no
{-# UNPACK #-}
or{-# NOUNPACK #-}
annotation in the source, so it is tagged with'NoSourceUnpackedness
. - There is no strictness (
!
) or laziness (~
) annotation in the source, so it is tagged with'NoSourceStrictness
. - The compiler infers that the field is lazy, so it is tagged with
'DecidedLazy
. Bear in mind that what the compiler decides may be quite different from what is written in the source. SeeDecidedStrictness
for a more detailed explanation.
The 'MetaSel
type is also an instance of the type class Selector
,
which can be used to obtain information about the field at the value
level.
- The
andC1
('MetaCons "Leaf" 'PrefixI 'False)
invocations indicate that the enclosed part is the representation of the first and second constructor of datatypeC1
('MetaCons "Node" 'PrefixI 'False)Tree
, respectively. Here, the meta-information regarding constructor names, fixity and whether it has named fields or not is encoded at the type level. The'MetaCons
type is also an instance of the type classConstructor
. This type class can be used to obtain information about the constructor at the value level. - The
tag indicates that the enclosed part is the representation of the datatypeD1
('MetaData "Tree" "Main" "package-name" 'False)Tree
. Again, the meta-information is encoded at the type level. The'MetaData
type is an instance of classDatatype
, which can be used to obtain the name of a datatype, the module it has been defined in, the package it is located under, and whether it has been defined usingdata
ornewtype
at the value level.
Derived and fundamental representation types
There are many datatype-generic functions that do not distinguish between positions that are parameters or positions that are recursive calls. There are also many datatype-generic functions that do not care about the names of datatypes and constructors at all. To keep the number of cases to consider in generic functions in such a situation to a minimum, it turns out that many of the type constructors introduced above are actually synonyms, defining them to be variants of a smaller set of constructors.
Individual fields of constructors: K1
The type constructor Rec0
is a variant of K1
:
typeRec0
=K1
R
Here, R
is a type-level proxy that does not have any associated values.
There used to be another variant of K1
(namely Par0
), but it has since
been deprecated.
Meta information: M1
The type constructors S1
, C1
and D1
are all variants of M1
:
typeS1
=M1
S
typeC1
=M1
C
typeD1
=M1
D
The types S
, C
and D
are once again type-level proxies, just used to create
several variants of M1
.
Additional generic representation type constructors
Next to K1
, M1
, :+:
and :*:
there are a few more type constructors that occur
in the representations of other datatypes.
Empty datatypes: V1
For empty datatypes, V1
is used as a representation. For example,
data Empty deriving Generic
yields
instanceGeneric
Empty where typeRep
Empty =D1
('MetaData "Empty" "Main" "package-name" 'False)V1
Constructors without fields: U1
If a constructor has no arguments, then U1
is used as its representation. For example
the representation of Bool
is
instanceGeneric
Bool where typeRep
Bool =D1
('MetaData "Bool" "Data.Bool" "package-name" 'False) (C1
('MetaCons "False" 'PrefixI 'False)U1
:+:
C1
('MetaCons "True" 'PrefixI 'False)U1
)
Representation of types with many constructors or many fields
As :+:
and :*:
are just binary operators, one might ask what happens if the
datatype has more than two constructors, or a constructor with more than two
fields. The answer is simple: the operators are used several times, to combine
all the constructors and fields as needed. However, users /should not rely on
a specific nesting strategy/ for :+:
and :*:
being used. The compiler is
free to choose any nesting it prefers. (In practice, the current implementation
tries to produce a more-or-less balanced nesting, so that the traversal of
the structure of the datatype from the root to a particular component can be
performed in logarithmic rather than linear time.)
Defining datatype-generic functions
A datatype-generic function comprises two parts:
- Generic instances for the function, implementing it for most of the representation type constructors introduced above.
- A wrapper that for any datatype that is in
Generic
, performs the conversion between the original value and itsRep
-based representation and then invokes the generic instances.
As an example, let us look at a function encode
that produces a naive, but lossless
bit encoding of values of various datatypes. So we are aiming to define a function
encode :: Generic
a => a -> [Bool]
where we use Bool
as our datatype for bits.
For part 1, we define a class Encode'
. Perhaps surprisingly, this class is parameterized
over a type constructor f
of kind * -> *
. This is a technicality: all the representation
type constructors operate with kind * -> *
as base kind. But the type argument is never
being used. This may be changed at some point in the future. The class has a single method,
and we use the type we want our final function to have, but we replace the occurrences of
the generic type argument a
with f p
(where the p
is any argument; it will not be used).
class Encode' f where encode' :: f p -> [Bool]
With the goal in mind to make encode
work on Tree
and other datatypes, we now define
instances for the representation type constructors V1
, U1
, :+:
, :*:
, K1
, and M1
.
Definition of the generic representation types
In order to be able to do this, we need to know the actual definitions of these types:
dataV1
p -- lifted version of Empty dataU1
p =U1
-- lifted version of () data (:+:
) f g p =L1
(f p) |R1
(g p) -- lifted version ofEither
data (:*:
) f g p = (f p):*:
(g p) -- lifted version of (,) newtypeK1
i c p =K1
{unK1
:: c } -- a container for a c newtypeM1
i t f p =M1
{unM1
:: f p } -- a wrapper
So, U1
is just the unit type, :+:
is just a binary choice like Either
,
:*:
is a binary pair like the pair constructor (,)
, and K1
is a value
of a specific type c
, and M1
wraps a value of the generic type argument,
which in the lifted world is an f p
(where we do not care about p
).
Generic instances
To deal with the V1
case, we use the following code (which requires the pragma EmptyCase
):
instance Encode' V1
where
encode' x = case x of { }
There are no values of type V1 p
to pass, so it is impossible for this
function to be invoked. One can ask why it is useful to define an instance
for V1
at all in this case? Well, an empty type can be used as an argument
to a non-empty type, and you might still want to encode the resulting type.
As a somewhat contrived example, consider [Empty]
, which is not an empty
type, but contains just the empty list. The V1
instance ensures that we
can call the generic function on such types.
There is exactly one value of type U1
, so encoding it requires no
knowledge, and we can use zero bits:
instance Encode'U1
where encode'U1
= []
In the case for :+:
, we produce False
or True
depending on whether
the constructor of the value provided is located on the left or on the right:
instance (Encode' f, Encode' g) => Encode' (f:+:
g) where encode' (L1
x) = False : encode' x encode' (R1
x) = True : encode' x
(Note that this encoding strategy may not be reliable across different
versions of GHC. Recall that the compiler is free to choose any nesting
of :+:
it chooses, so if GHC chooses (a
, then the
encoding for :+:
b) :+:
ca
would be [False, False]
, b
would be [False, True]
,
and c
would be [True]
. However, if GHC chooses a
,
then the encoding for :+:
(b :+:
c)a
would be [False]
, b
would be [True, False]
,
and c
would be [True, True]
.)
In the case for :*:
, we append the encodings of the two subcomponents:
instance (Encode' f, Encode' g) => Encode' (f:*:
g) where encode' (x:*:
y) = encode' x ++ encode' y
The case for K1
is rather interesting. Here, we call the final function
encode
that we yet have to define, recursively. We will use another type
class Encode
for that function:
instance (Encode c) => Encode' (K1
i c) where encode' (K1
x) = encode x
Note how we can define a uniform instance for M1
, because we completely
disregard all meta-information:
instance (Encode' f) => Encode' (M1
i t f) where encode' (M1
x) = encode' x
Unlike in K1
, the instance for M1
refers to encode'
, not encode
.
The wrapper and generic default
We now define class Encode
for the actual encode
function:
class Encode a where
encode :: a -> [Bool]
default encode :: (Generic a, Encode' (Rep a)) => a -> [Bool]
encode x = encode' (from
x)
The incoming x
is converted using from
, then we dispatch to the
generic instances using encode'
. We use this as a default definition
for encode
. We need the default encode
signature because ordinary
Haskell default methods must not introduce additional class constraints,
but our generic default does.
Defining a particular instance is now as simple as saying
instance (Encode a) => Encode (Tree a)
Omitting generic instances
It is not always required to provide instances for all the generic representation types, but omitting instances restricts the set of datatypes the functions will work for:
- If no
:+:
instance is given, the function may still work for empty datatypes or datatypes that have a single constructor, but will fail on datatypes with more than one constructor. - If no
:*:
instance is given, the function may still work for datatypes where each constructor has just zero or one field, in particular for enumeration types. - If no
K1
instance is given, the function may still work for enumeration types, where no constructor has any fields. - If no
V1
instance is given, the function may still work for any datatype that is not empty. - If no
U1
instance is given, the function may still work for any datatype where each constructor has at least one field.
An M1
instance is always required (but it can just ignore the
meta-information, as is the case for encode
above).
Generic constructor classes
Datatype-generic functions as defined above work for a large class
of datatypes, including parameterized datatypes. (We have used Tree
as our example above, which is of kind * -> *
.) However, the
Generic
class ranges over types of kind *
, and therefore, the
resulting generic functions (such as encode
) must be parameterized
by a generic type argument of kind *
.
What if we want to define generic classes that range over type
constructors (such as Functor
,
Traversable
, or Foldable
)?
The Generic1
class
Like Generic
, there is a class Generic1
that defines a
representation Rep1
and conversion functions from1
and to1
,
only that Generic1
ranges over types of kind * -> *
. (More generally,
it can range over types of kind k -> *
, for any kind k
, if the
PolyKinds
extension is enabled. More on this later.)
The Generic1
class is also derivable.
The representation Rep1
is ever so slightly different from Rep
.
Let us look at Tree
as an example again:
data Tree a = Leaf a | Node (Tree a) (Tree a)
deriving Generic1
The above declaration causes the following representation to be generated:
instanceGeneric1
Tree where typeRep1
Tree =D1
('MetaData "Tree" "Main" "package-name" 'False) (C1
('MetaCons "Leaf" 'PrefixI 'False) (S1
('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)Par1
):+:
C1
('MetaCons "Node" 'PrefixI 'False) (S1
('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1
Tree):*:
S1
('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1
Tree))) ...
The representation reuses D1
, C1
, S1
(and thereby M1
) as well
as :+:
and :*:
from Rep
. (This reusability is the reason that we
carry around the dummy type argument for kind-*
-types, but there are
already enough different names involved without duplicating each of
these.)
What's different is that we now use Par1
to refer to the parameter
(and that parameter, which used to be a
), is not mentioned explicitly
by name anywhere; and we use Rec1
to refer to a recursive use of Tree a
.
Representation of * -> *
types
Unlike Rec0
, the Par1
and Rec1
type constructors do not
map to K1
. They are defined directly, as follows:
newtypePar1
p =Par1
{unPar1
:: p } -- gives access to parameter p newtypeRec1
f p =Rec1
{unRec1
:: f p } -- a wrapper
In Par1
, the parameter p
is used for the first time, whereas Rec1
simply
wraps an application of f
to p
.
Note that K1
(in the guise of Rec0
) can still occur in a Rep1
representation,
namely when the datatype has a field that does not mention the parameter.
The declaration
data WithInt a = WithInt Int a
deriving Generic1
yields
instanceGeneric1
WithInt where typeRep1
WithInt =D1
('MetaData "WithInt" "Main" "package-name" 'False) (C1
('MetaCons "WithInt" 'PrefixI 'False) (S1
('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0
Int):*:
S1
('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)Par1
))
If the parameter a
appears underneath a composition of other type constructors,
then the representation involves composition, too:
data Rose a = Fork a [Rose a]
yields
instanceGeneric1
Rose where typeRep1
Rose =D1
('MetaData "Rose" "Main" "package-name" 'False) (C1
('MetaCons "Fork" 'PrefixI 'False) (S1
('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)Par1
:*:
S1
('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([]:.:
Rec1
Rose)))
where
newtype (:.:
) f g p =Comp1
{unComp1
:: f (g p) }
Representation of k -> *
types
The Generic1
class can be generalized to range over types of kind
k -> *
, for any kind k
. To do so, derive a Generic1
instance with the
PolyKinds
extension enabled. For example, the declaration
data Proxy (a :: k) = Proxy deriving Generic1
yields a slightly different instance depending on whether PolyKinds
is
enabled. If compiled without PolyKinds
, then
, but
if compiled with Rep1
Proxy :: * -> *PolyKinds
, then
.Rep1
Proxy :: k -> *
Representation of unlifted types
If one were to attempt to derive a Generic instance for a datatype with an
unlifted argument (for example, Int#
), one might expect the occurrence of
the Int#
argument to be marked with
. This won't work,
though, since Rec0
Int#
Int#
is of an unlifted kind, and Rec0
expects a type of
kind *
.
One solution would be to represent an occurrence of Int#
with 'Rec0 Int'
instead. With this approach, however, the programmer has no way of knowing
whether the Int
is actually an Int#
in disguise.
Instead of reusing Rec0
, a separate data family URec
is used to mark
occurrences of common unlifted types:
data family URec a p data instanceURec
(Ptr
()) p =UAddr
{uAddr#
::Addr#
} data instanceURec
Char
p =UChar
{uChar#
::Char#
} data instanceURec
Double
p =UDouble
{uDouble#
::Double#
} data instanceURec
Int
p =UFloat
{uFloat#
::Float#
} data instanceURec
Float
p =UInt
{uInt#
::Int#
} data instanceURec
Word
p =UWord
{uWord#
::Word#
}
Several type synonyms are provided for convenience:
typeUAddr
=URec
(Ptr
()) typeUChar
=URec
Char
typeUDouble
=URec
Double
typeUFloat
=URec
Float
typeUInt
=URec
Int
typeUWord
=URec
Word
The declaration
data IntHash = IntHash Int#
deriving Generic
yields
instanceGeneric
IntHash where typeRep
IntHash =D1
('MetaData "IntHash" "Main" "package-name" 'False) (C1
('MetaCons "IntHash" 'PrefixI 'False) (S1
('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)UInt
))
Currently, only the six unlifted types listed above are generated, but this may be extended to encompass more unlifted types in the future.
Generic representation types
Void: used for datatypes without constructors
Instances
Generic1 (V1 :: k -> Type) Source # | |
Defined in GHC.Generics | |
Foldable (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => V1 m -> m Source # foldMap :: Monoid m => (a -> m) -> V1 a -> m Source # foldMap' :: Monoid m => (a -> m) -> V1 a -> m Source # foldr :: (a -> b -> b) -> b -> V1 a -> b Source # foldr' :: (a -> b -> b) -> b -> V1 a -> b Source # foldl :: (b -> a -> b) -> b -> V1 a -> b Source # foldl' :: (b -> a -> b) -> b -> V1 a -> b Source # foldr1 :: (a -> a -> a) -> V1 a -> a Source # foldl1 :: (a -> a -> a) -> V1 a -> a Source # toList :: V1 a -> [a] Source # length :: V1 a -> Int Source # elem :: Eq a => a -> V1 a -> Bool Source # maximum :: Ord a => V1 a -> a Source # minimum :: Ord a => V1 a -> a Source # | |
Foldable1 (V1 :: Type -> Type) Source # | Since: base-4.18.0.0 |
Defined in Data.Foldable1 fold1 :: Semigroup m => V1 m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> V1 a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> V1 a -> m Source # toNonEmpty :: V1 a -> NonEmpty a Source # maximum :: Ord a => V1 a -> a Source # minimum :: Ord a => V1 a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> V1 a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> V1 a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> V1 a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> V1 a -> b Source # | |
Contravariant (V1 :: Type -> Type) Source # | |
Traversable (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Data p => Data (V1 p) Source # | Since: base-4.9.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V1 p -> c (V1 p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V1 p) Source # toConstr :: V1 p -> Constr Source # dataTypeOf :: V1 p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V1 p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 p)) Source # gmapT :: (forall b. Data b => b -> b) -> V1 p -> V1 p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> V1 p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> V1 p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # | |
Semigroup (V1 p) Source # | Since: base-4.12.0.0 |
Generic (V1 p) Source # | |
Read (V1 p) Source # | Since: base-4.9.0.0 |
Show (V1 p) Source # | Since: base-4.9.0.0 |
Eq (V1 p) Source # | Since: base-4.9.0.0 |
Ord (V1 p) Source # | Since: base-4.9.0.0 |
type Rep1 (V1 :: k -> Type) Source # | Since: base-4.9.0.0 |
type Rep (V1 p) Source # | Since: base-4.9.0.0 |
Unit: used for constructors without arguments
Instances
Generic1 (U1 :: k -> Type) Source # | |
Defined in GHC.Generics | |
MonadZip (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Foldable (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => U1 m -> m Source # foldMap :: Monoid m => (a -> m) -> U1 a -> m Source # foldMap' :: Monoid m => (a -> m) -> U1 a -> m Source # foldr :: (a -> b -> b) -> b -> U1 a -> b Source # foldr' :: (a -> b -> b) -> b -> U1 a -> b Source # foldl :: (b -> a -> b) -> b -> U1 a -> b Source # foldl' :: (b -> a -> b) -> b -> U1 a -> b Source # foldr1 :: (a -> a -> a) -> U1 a -> a Source # foldl1 :: (a -> a -> a) -> U1 a -> a Source # toList :: U1 a -> [a] Source # length :: U1 a -> Int Source # elem :: Eq a => a -> U1 a -> Bool Source # maximum :: Ord a => U1 a -> a Source # minimum :: Ord a => U1 a -> a Source # | |
Contravariant (U1 :: Type -> Type) Source # | |
Traversable (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Alternative (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Applicative (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Monad (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
MonadPlus (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Data p => Data (U1 p) Source # | Since: base-4.9.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> U1 p -> c (U1 p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (U1 p) Source # toConstr :: U1 p -> Constr Source # dataTypeOf :: U1 p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (U1 p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (U1 p)) Source # gmapT :: (forall b. Data b => b -> b) -> U1 p -> U1 p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> U1 p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> U1 p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> U1 p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> U1 p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # | |
Monoid (U1 p) Source # | Since: base-4.12.0.0 |
Semigroup (U1 p) Source # | Since: base-4.12.0.0 |
Generic (U1 p) Source # | |
Read (U1 p) Source # | Since: base-4.9.0.0 |
Show (U1 p) Source # | Since: base-4.9.0.0 |
Eq (U1 p) Source # | Since: base-4.9.0.0 |
Ord (U1 p) Source # | Since: base-4.7.0.0 |
type Rep1 (U1 :: k -> Type) Source # | Since: base-4.9.0.0 |
type Rep (U1 p) Source # | Since: base-4.7.0.0 |
Used for marking occurrences of the parameter
Instances
MonadFix Par1 Source # | Since: base-4.9.0.0 | ||||
MonadZip Par1 Source # | Since: base-4.9.0.0 | ||||
Foldable Par1 Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => Par1 m -> m Source # foldMap :: Monoid m => (a -> m) -> Par1 a -> m Source # foldMap' :: Monoid m => (a -> m) -> Par1 a -> m Source # foldr :: (a -> b -> b) -> b -> Par1 a -> b Source # foldr' :: (a -> b -> b) -> b -> Par1 a -> b Source # foldl :: (b -> a -> b) -> b -> Par1 a -> b Source # foldl' :: (b -> a -> b) -> b -> Par1 a -> b Source # foldr1 :: (a -> a -> a) -> Par1 a -> a Source # foldl1 :: (a -> a -> a) -> Par1 a -> a Source # toList :: Par1 a -> [a] Source # null :: Par1 a -> Bool Source # length :: Par1 a -> Int Source # elem :: Eq a => a -> Par1 a -> Bool Source # maximum :: Ord a => Par1 a -> a Source # minimum :: Ord a => Par1 a -> a Source # | |||||
Foldable1 Par1 Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => Par1 m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Par1 a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Par1 a -> m Source # toNonEmpty :: Par1 a -> NonEmpty a Source # maximum :: Ord a => Par1 a -> a Source # minimum :: Ord a => Par1 a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Par1 a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Par1 a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Par1 a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Par1 a -> b Source # | |||||
Traversable Par1 Source # | Since: base-4.9.0.0 | ||||
Applicative Par1 Source # | Since: base-4.9.0.0 | ||||
Functor Par1 Source # | Since: base-4.9.0.0 | ||||
Monad Par1 Source # | Since: base-4.9.0.0 | ||||
Generic1 Par1 Source # | |||||
Defined in GHC.Generics
| |||||
Data p => Data (Par1 p) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Par1 p -> c (Par1 p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Par1 p) Source # toConstr :: Par1 p -> Constr Source # dataTypeOf :: Par1 p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Par1 p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Par1 p)) Source # gmapT :: (forall b. Data b => b -> b) -> Par1 p -> Par1 p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Par1 p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Par1 p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Par1 p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Par1 p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Par1 p -> m (Par1 p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Par1 p -> m (Par1 p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Par1 p -> m (Par1 p) Source # | |||||
Monoid p => Monoid (Par1 p) Source # | Since: base-4.12.0.0 | ||||
Semigroup p => Semigroup (Par1 p) Source # | Since: base-4.12.0.0 | ||||
Generic (Par1 p) Source # | |||||
Defined in GHC.Generics
| |||||
Read p => Read (Par1 p) Source # | Since: base-4.7.0.0 | ||||
Show p => Show (Par1 p) Source # | Since: base-4.7.0.0 | ||||
Eq p => Eq (Par1 p) Source # | Since: base-4.7.0.0 | ||||
Ord p => Ord (Par1 p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep1 Par1 Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep (Par1 p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics |
newtype Rec1 (f :: k -> Type) (p :: k) Source #
Recursive calls of kind * -> *
(or kind k -> *
, when PolyKinds
is enabled)
Instances
Generic1 (Rec1 f :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
MonadFix f => MonadFix (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
MonadZip f => MonadZip (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Foldable f => Foldable (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => Rec1 f m -> m Source # foldMap :: Monoid m => (a -> m) -> Rec1 f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Rec1 f a -> m Source # foldr :: (a -> b -> b) -> b -> Rec1 f a -> b Source # foldr' :: (a -> b -> b) -> b -> Rec1 f a -> b Source # foldl :: (b -> a -> b) -> b -> Rec1 f a -> b Source # foldl' :: (b -> a -> b) -> b -> Rec1 f a -> b Source # foldr1 :: (a -> a -> a) -> Rec1 f a -> a Source # foldl1 :: (a -> a -> a) -> Rec1 f a -> a Source # toList :: Rec1 f a -> [a] Source # null :: Rec1 f a -> Bool Source # length :: Rec1 f a -> Int Source # elem :: Eq a => a -> Rec1 f a -> Bool Source # maximum :: Ord a => Rec1 f a -> a Source # minimum :: Ord a => Rec1 f a -> a Source # | |||||
Foldable1 f => Foldable1 (Rec1 f) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => Rec1 f m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Rec1 f a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Rec1 f a -> m Source # toNonEmpty :: Rec1 f a -> NonEmpty a Source # maximum :: Ord a => Rec1 f a -> a Source # minimum :: Ord a => Rec1 f a -> a Source # head :: Rec1 f a -> a Source # last :: Rec1 f a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Rec1 f a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Rec1 f a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Rec1 f a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Rec1 f a -> b Source # | |||||
Contravariant f => Contravariant (Rec1 f) Source # | |||||
Traversable f => Traversable (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Traversable | |||||
Alternative f => Alternative (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Applicative f => Applicative (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Functor f => Functor (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Monad f => Monad (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
MonadPlus f => MonadPlus (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
(Data (f p), Typeable f, Data p) => Data (Rec1 f p) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rec1 f p -> c (Rec1 f p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Rec1 f p) Source # toConstr :: Rec1 f p -> Constr Source # dataTypeOf :: Rec1 f p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Rec1 f p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Rec1 f p)) Source # gmapT :: (forall b. Data b => b -> b) -> Rec1 f p -> Rec1 f p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 f p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 f p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Rec1 f p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rec1 f p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # | |||||
Monoid (f p) => Monoid (Rec1 f p) Source # | Since: base-4.12.0.0 | ||||
Semigroup (f p) => Semigroup (Rec1 f p) Source # | Since: base-4.12.0.0 | ||||
Generic (Rec1 f p) Source # | |||||
Defined in GHC.Generics
| |||||
Read (f p) => Read (Rec1 f p) Source # | Since: base-4.7.0.0 | ||||
Show (f p) => Show (Rec1 f p) Source # | Since: base-4.7.0.0 | ||||
Eq (f p) => Eq (Rec1 f p) Source # | Since: base-4.7.0.0 | ||||
Ord (f p) => Ord (Rec1 f p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep1 (Rec1 f :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep (Rec1 f p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics |
newtype K1 i c (p :: k) Source #
Constants, additional parameters and recursion of kind *
Instances
Generic1 (K1 i c :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Bifoldable (K1 i :: Type -> Type -> Type) Source # | Since: base-4.10.0.0 | ||||
Bifunctor (K1 i :: Type -> Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Bitraversable (K1 i :: Type -> Type -> Type) Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> K1 i a b -> f (K1 i c d) Source # | |||||
Foldable (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => K1 i c m -> m Source # foldMap :: Monoid m => (a -> m) -> K1 i c a -> m Source # foldMap' :: Monoid m => (a -> m) -> K1 i c a -> m Source # foldr :: (a -> b -> b) -> b -> K1 i c a -> b Source # foldr' :: (a -> b -> b) -> b -> K1 i c a -> b Source # foldl :: (b -> a -> b) -> b -> K1 i c a -> b Source # foldl' :: (b -> a -> b) -> b -> K1 i c a -> b Source # foldr1 :: (a -> a -> a) -> K1 i c a -> a Source # foldl1 :: (a -> a -> a) -> K1 i c a -> a Source # toList :: K1 i c a -> [a] Source # null :: K1 i c a -> Bool Source # length :: K1 i c a -> Int Source # elem :: Eq a => a -> K1 i c a -> Bool Source # maximum :: Ord a => K1 i c a -> a Source # minimum :: Ord a => K1 i c a -> a Source # | |||||
Contravariant (K1 i c :: Type -> Type) Source # | |||||
Traversable (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Monoid c => Applicative (K1 i c :: Type -> Type) Source # | Since: base-4.12.0.0 | ||||
Functor (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
(Typeable i, Data p, Data c) => Data (K1 i c p) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> K1 i c p -> c0 (K1 i c p) Source # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (K1 i c p) Source # toConstr :: K1 i c p -> Constr Source # dataTypeOf :: K1 i c p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (K1 i c p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (K1 i c p)) Source # gmapT :: (forall b. Data b => b -> b) -> K1 i c p -> K1 i c p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> K1 i c p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> K1 i c p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> K1 i c p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> K1 i c p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # | |||||
Monoid c => Monoid (K1 i c p) Source # | Since: base-4.12.0.0 | ||||
Semigroup c => Semigroup (K1 i c p) Source # | Since: base-4.12.0.0 | ||||
Generic (K1 i c p) Source # | |||||
Defined in GHC.Generics
| |||||
Read c => Read (K1 i c p) Source # | Since: base-4.7.0.0 | ||||
Show c => Show (K1 i c p) Source # | Since: base-4.7.0.0 | ||||
Eq c => Eq (K1 i c p) Source # | Since: base-4.7.0.0 | ||||
Ord c => Ord (K1 i c p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep1 (K1 i c :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep (K1 i c p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics |
newtype M1 i (c :: Meta) (f :: k -> Type) (p :: k) Source #
Meta-information (constructor names, etc.)
Instances
Generic1 (M1 i c f :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
MonadFix f => MonadFix (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
MonadZip f => MonadZip (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Foldable f => Foldable (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => M1 i c f m -> m Source # foldMap :: Monoid m => (a -> m) -> M1 i c f a -> m Source # foldMap' :: Monoid m => (a -> m) -> M1 i c f a -> m Source # foldr :: (a -> b -> b) -> b -> M1 i c f a -> b Source # foldr' :: (a -> b -> b) -> b -> M1 i c f a -> b Source # foldl :: (b -> a -> b) -> b -> M1 i c f a -> b Source # foldl' :: (b -> a -> b) -> b -> M1 i c f a -> b Source # foldr1 :: (a -> a -> a) -> M1 i c f a -> a Source # foldl1 :: (a -> a -> a) -> M1 i c f a -> a Source # toList :: M1 i c f a -> [a] Source # null :: M1 i c f a -> Bool Source # length :: M1 i c f a -> Int Source # elem :: Eq a => a -> M1 i c f a -> Bool Source # maximum :: Ord a => M1 i c f a -> a Source # minimum :: Ord a => M1 i c f a -> a Source # | |||||
Foldable1 f => Foldable1 (M1 i c f) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => M1 i c f m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> M1 i c f a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> M1 i c f a -> m Source # toNonEmpty :: M1 i c f a -> NonEmpty a Source # maximum :: Ord a => M1 i c f a -> a Source # minimum :: Ord a => M1 i c f a -> a Source # head :: M1 i c f a -> a Source # last :: M1 i c f a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> M1 i c f a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> M1 i c f a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> M1 i c f a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> M1 i c f a -> b Source # | |||||
Contravariant f => Contravariant (M1 i c f) Source # | |||||
Traversable f => Traversable (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Traversable | |||||
Alternative f => Alternative (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Applicative f => Applicative (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
Functor f => Functor (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Monad f => Monad (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
MonadPlus f => MonadPlus (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
(Data p, Data (f p), Typeable c, Typeable i, Typeable f) => Data (M1 i c f p) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> M1 i c f p -> c0 (M1 i c f p) Source # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (M1 i c f p) Source # toConstr :: M1 i c f p -> Constr Source # dataTypeOf :: M1 i c f p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (M1 i c f p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (M1 i c f p)) Source # gmapT :: (forall b. Data b => b -> b) -> M1 i c f p -> M1 i c f p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> M1 i c f p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> M1 i c f p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> M1 i c f p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> M1 i c f p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # | |||||
Monoid (f p) => Monoid (M1 i c f p) Source # | Since: base-4.12.0.0 | ||||
Semigroup (f p) => Semigroup (M1 i c f p) Source # | Since: base-4.12.0.0 | ||||
Generic (M1 i c f p) Source # | |||||
Defined in GHC.Generics
| |||||
Read (f p) => Read (M1 i c f p) Source # | Since: base-4.7.0.0 | ||||
Show (f p) => Show (M1 i c f p) Source # | Since: base-4.7.0.0 | ||||
Eq (f p) => Eq (M1 i c f p) Source # | Since: base-4.7.0.0 | ||||
Ord (f p) => Ord (M1 i c f p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics compare :: M1 i c f p -> M1 i c f p -> Ordering Source # (<) :: M1 i c f p -> M1 i c f p -> Bool Source # (<=) :: M1 i c f p -> M1 i c f p -> Bool Source # (>) :: M1 i c f p -> M1 i c f p -> Bool Source # (>=) :: M1 i c f p -> M1 i c f p -> Bool Source # | |||||
type Rep1 (M1 i c f :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep (M1 i c f p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics |
data ((f :: k -> Type) :+: (g :: k -> Type)) (p :: k) infixr 5 Source #
Sums: encode choice between constructors
Instances
Generic1 (f :+: g :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
(Foldable f, Foldable g) => Foldable (f :+: g) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => (f :+: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :+: g) a -> m Source # foldMap' :: Monoid m => (a -> m) -> (f :+: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :+: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :+: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :+: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :+: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :+: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :+: g) a -> a Source # toList :: (f :+: g) a -> [a] Source # null :: (f :+: g) a -> Bool Source # length :: (f :+: g) a -> Int Source # elem :: Eq a => a -> (f :+: g) a -> Bool Source # maximum :: Ord a => (f :+: g) a -> a Source # minimum :: Ord a => (f :+: g) a -> a Source # | |||||
(Foldable1 f, Foldable1 g) => Foldable1 (f :+: g) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => (f :+: g) m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> (f :+: g) a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> (f :+: g) a -> m Source # toNonEmpty :: (f :+: g) a -> NonEmpty a Source # maximum :: Ord a => (f :+: g) a -> a Source # minimum :: Ord a => (f :+: g) a -> a Source # head :: (f :+: g) a -> a Source # last :: (f :+: g) a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> (f :+: g) a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> (f :+: g) a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> (f :+: g) a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> (f :+: g) a -> b Source # | |||||
(Contravariant f, Contravariant g) => Contravariant (f :+: g) Source # | |||||
(Traversable f, Traversable g) => Traversable (f :+: g) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Traversable | |||||
(Functor f, Functor g) => Functor (f :+: g) Source # | Since: base-4.9.0.0 | ||||
(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :+: g) p) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :+: g) p -> c ((f :+: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :+: g) p) Source # toConstr :: (f :+: g) p -> Constr Source # dataTypeOf :: (f :+: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :+: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :+: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :+: g) p -> (f :+: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :+: g) p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :+: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :+: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :+: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # | |||||
Generic ((f :+: g) p) Source # | |||||
Defined in GHC.Generics
| |||||
(Read (f p), Read (g p)) => Read ((f :+: g) p) Source # | Since: base-4.7.0.0 | ||||
(Show (f p), Show (g p)) => Show ((f :+: g) p) Source # | Since: base-4.7.0.0 | ||||
(Eq (f p), Eq (g p)) => Eq ((f :+: g) p) Source # | Since: base-4.7.0.0 | ||||
(Ord (f p), Ord (g p)) => Ord ((f :+: g) p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics compare :: (f :+: g) p -> (f :+: g) p -> Ordering Source # (<) :: (f :+: g) p -> (f :+: g) p -> Bool Source # (<=) :: (f :+: g) p -> (f :+: g) p -> Bool Source # (>) :: (f :+: g) p -> (f :+: g) p -> Bool Source # (>=) :: (f :+: g) p -> (f :+: g) p -> Bool Source # | |||||
type Rep1 (f :+: g :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics type Rep1 (f :+: g :: k -> Type) = D1 ('MetaData ":+:" "GHC.Generics" "base" 'False) (C1 ('MetaCons "L1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f)) :+: C1 ('MetaCons "R1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 g))) | |||||
type Rep ((f :+: g) p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics type Rep ((f :+: g) p) = D1 ('MetaData ":+:" "GHC.Generics" "base" 'False) (C1 ('MetaCons "L1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f p))) :+: C1 ('MetaCons "R1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (g p)))) |
data ((f :: k -> Type) :*: (g :: k -> Type)) (p :: k) infixr 6 Source #
Products: encode multiple arguments to constructors
(f p) :*: (g p) infixr 6 |
Instances
Generic1 (f :*: g :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
(MonadFix f, MonadFix g) => MonadFix (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(MonadZip f, MonadZip g) => MonadZip (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Foldable f, Foldable g) => Foldable (f :*: g) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => (f :*: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :*: g) a -> m Source # foldMap' :: Monoid m => (a -> m) -> (f :*: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :*: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :*: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :*: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :*: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :*: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :*: g) a -> a Source # toList :: (f :*: g) a -> [a] Source # null :: (f :*: g) a -> Bool Source # length :: (f :*: g) a -> Int Source # elem :: Eq a => a -> (f :*: g) a -> Bool Source # maximum :: Ord a => (f :*: g) a -> a Source # minimum :: Ord a => (f :*: g) a -> a Source # | |||||
(Foldable1 f, Foldable1 g) => Foldable1 (f :*: g) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => (f :*: g) m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> (f :*: g) a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> (f :*: g) a -> m Source # toNonEmpty :: (f :*: g) a -> NonEmpty a Source # maximum :: Ord a => (f :*: g) a -> a Source # minimum :: Ord a => (f :*: g) a -> a Source # head :: (f :*: g) a -> a Source # last :: (f :*: g) a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> (f :*: g) a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> (f :*: g) a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> (f :*: g) a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> (f :*: g) a -> b Source # | |||||
(Contravariant f, Contravariant g) => Contravariant (f :*: g) Source # | |||||
(Traversable f, Traversable g) => Traversable (f :*: g) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Traversable | |||||
(Alternative f, Alternative g) => Alternative (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Applicative f, Applicative g) => Applicative (f :*: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
(Functor f, Functor g) => Functor (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Monad f, Monad g) => Monad (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :*: g) p) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :*: g) p -> c ((f :*: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :*: g) p) Source # toConstr :: (f :*: g) p -> Constr Source # dataTypeOf :: (f :*: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :*: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :*: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :*: g) p -> (f :*: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :*: g) p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :*: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :*: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :*: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # | |||||
(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) Source # | Since: base-4.12.0.0 | ||||
(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p) Source # | Since: base-4.12.0.0 | ||||
Generic ((f :*: g) p) Source # | |||||
Defined in GHC.Generics
| |||||
(Read (f p), Read (g p)) => Read ((f :*: g) p) Source # | Since: base-4.7.0.0 | ||||
(Show (f p), Show (g p)) => Show ((f :*: g) p) Source # | Since: base-4.7.0.0 | ||||
(Eq (f p), Eq (g p)) => Eq ((f :*: g) p) Source # | Since: base-4.7.0.0 | ||||
(Ord (f p), Ord (g p)) => Ord ((f :*: g) p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics compare :: (f :*: g) p -> (f :*: g) p -> Ordering Source # (<) :: (f :*: g) p -> (f :*: g) p -> Bool Source # (<=) :: (f :*: g) p -> (f :*: g) p -> Bool Source # (>) :: (f :*: g) p -> (f :*: g) p -> Bool Source # (>=) :: (f :*: g) p -> (f :*: g) p -> Bool Source # | |||||
type Rep1 (f :*: g :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics type Rep1 (f :*: g :: k -> Type) = D1 ('MetaData ":*:" "GHC.Generics" "base" 'False) (C1 ('MetaCons ":*:" ('InfixI 'RightAssociative 6) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 g))) | |||||
type Rep ((f :*: g) p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics type Rep ((f :*: g) p) = D1 ('MetaData ":*:" "GHC.Generics" "base" 'False) (C1 ('MetaCons ":*:" ('InfixI 'RightAssociative 6) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f p)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (g p)))) |
newtype ((f :: k2 -> Type) :.: (g :: k1 -> k2)) (p :: k1) infixr 7 Source #
Composition of functors
Instances
Functor f => Generic1 (f :.: g :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
(Foldable f, Foldable g) => Foldable (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => (f :.: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m Source # foldMap' :: Monoid m => (a -> m) -> (f :.: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :.: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :.: g) a -> a Source # toList :: (f :.: g) a -> [a] Source # null :: (f :.: g) a -> Bool Source # length :: (f :.: g) a -> Int Source # elem :: Eq a => a -> (f :.: g) a -> Bool Source # maximum :: Ord a => (f :.: g) a -> a Source # minimum :: Ord a => (f :.: g) a -> a Source # | |||||
(Foldable1 f, Foldable1 g) => Foldable1 (f :.: g) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => (f :.: g) m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> (f :.: g) a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> (f :.: g) a -> m Source # toNonEmpty :: (f :.: g) a -> NonEmpty a Source # maximum :: Ord a => (f :.: g) a -> a Source # minimum :: Ord a => (f :.: g) a -> a Source # head :: (f :.: g) a -> a Source # last :: (f :.: g) a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> (f :.: g) a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> (f :.: g) a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> (f :.: g) a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> (f :.: g) a -> b Source # | |||||
(Functor f, Contravariant g) => Contravariant (f :.: g) Source # | |||||
(Traversable f, Traversable g) => Traversable (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Traversable | |||||
(Alternative f, Applicative g) => Alternative (f :.: g) Source # | Since: base-4.9.0.0 | ||||
(Applicative f, Applicative g) => Applicative (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
(Functor f, Functor g) => Functor (f :.: g) Source # | Since: base-4.9.0.0 | ||||
(Typeable f, Typeable g, Data p, Data (f (g p))) => Data ((f :.: g) p) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :.: g) p -> c ((f :.: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :.: g) p) Source # toConstr :: (f :.: g) p -> Constr Source # dataTypeOf :: (f :.: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :.: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :.: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :.: g) p -> (f :.: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :.: g) p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :.: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :.: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :.: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # | |||||
Monoid (f (g p)) => Monoid ((f :.: g) p) Source # | Since: base-4.12.0.0 | ||||
Semigroup (f (g p)) => Semigroup ((f :.: g) p) Source # | Since: base-4.12.0.0 | ||||
Generic ((f :.: g) p) Source # | |||||
Defined in GHC.Generics
| |||||
Read (f (g p)) => Read ((f :.: g) p) Source # | Since: base-4.7.0.0 | ||||
Show (f (g p)) => Show ((f :.: g) p) Source # | Since: base-4.7.0.0 | ||||
Eq (f (g p)) => Eq ((f :.: g) p) Source # | Since: base-4.7.0.0 | ||||
Ord (f (g p)) => Ord ((f :.: g) p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics compare :: (f :.: g) p -> (f :.: g) p -> Ordering Source # (<) :: (f :.: g) p -> (f :.: g) p -> Bool Source # (<=) :: (f :.: g) p -> (f :.: g) p -> Bool Source # (>) :: (f :.: g) p -> (f :.: g) p -> Bool Source # (>=) :: (f :.: g) p -> (f :.: g) p -> Bool Source # | |||||
type Rep1 (f :.: g :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep ((f :.: g) p) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics |
Unboxed representation types
data family URec a (p :: k) Source #
Constants of unlifted kinds
Since: base-4.9.0.0
Instances
Generic1 (URec (Ptr ()) :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (URec Char :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (URec Double :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (URec Float :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (URec Int :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (URec Word :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Foldable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => UAddr m -> m Source # foldMap :: Monoid m => (a -> m) -> UAddr a -> m Source # foldMap' :: Monoid m => (a -> m) -> UAddr a -> m Source # foldr :: (a -> b -> b) -> b -> UAddr a -> b Source # foldr' :: (a -> b -> b) -> b -> UAddr a -> b Source # foldl :: (b -> a -> b) -> b -> UAddr a -> b Source # foldl' :: (b -> a -> b) -> b -> UAddr a -> b Source # foldr1 :: (a -> a -> a) -> UAddr a -> a Source # foldl1 :: (a -> a -> a) -> UAddr a -> a Source # toList :: UAddr a -> [a] Source # null :: UAddr a -> Bool Source # length :: UAddr a -> Int Source # elem :: Eq a => a -> UAddr a -> Bool Source # maximum :: Ord a => UAddr a -> a Source # minimum :: Ord a => UAddr a -> a Source # | |||||
Foldable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => UChar m -> m Source # foldMap :: Monoid m => (a -> m) -> UChar a -> m Source # foldMap' :: Monoid m => (a -> m) -> UChar a -> m Source # foldr :: (a -> b -> b) -> b -> UChar a -> b Source # foldr' :: (a -> b -> b) -> b -> UChar a -> b Source # foldl :: (b -> a -> b) -> b -> UChar a -> b Source # foldl' :: (b -> a -> b) -> b -> UChar a -> b Source # foldr1 :: (a -> a -> a) -> UChar a -> a Source # foldl1 :: (a -> a -> a) -> UChar a -> a Source # toList :: UChar a -> [a] Source # null :: UChar a -> Bool Source # length :: UChar a -> Int Source # elem :: Eq a => a -> UChar a -> Bool Source # maximum :: Ord a => UChar a -> a Source # minimum :: Ord a => UChar a -> a Source # | |||||
Foldable (UDouble :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => UDouble m -> m Source # foldMap :: Monoid m => (a -> m) -> UDouble a -> m Source # foldMap' :: Monoid m => (a -> m) -> UDouble a -> m Source # foldr :: (a -> b -> b) -> b -> UDouble a -> b Source # foldr' :: (a -> b -> b) -> b -> UDouble a -> b Source # foldl :: (b -> a -> b) -> b -> UDouble a -> b Source # foldl' :: (b -> a -> b) -> b -> UDouble a -> b Source # foldr1 :: (a -> a -> a) -> UDouble a -> a Source # foldl1 :: (a -> a -> a) -> UDouble a -> a Source # toList :: UDouble a -> [a] Source # null :: UDouble a -> Bool Source # length :: UDouble a -> Int Source # elem :: Eq a => a -> UDouble a -> Bool Source # maximum :: Ord a => UDouble a -> a Source # minimum :: Ord a => UDouble a -> a Source # | |||||
Foldable (UFloat :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => UFloat m -> m Source # foldMap :: Monoid m => (a -> m) -> UFloat a -> m Source # foldMap' :: Monoid m => (a -> m) -> UFloat a -> m Source # foldr :: (a -> b -> b) -> b -> UFloat a -> b Source # foldr' :: (a -> b -> b) -> b -> UFloat a -> b Source # foldl :: (b -> a -> b) -> b -> UFloat a -> b Source # foldl' :: (b -> a -> b) -> b -> UFloat a -> b Source # foldr1 :: (a -> a -> a) -> UFloat a -> a Source # foldl1 :: (a -> a -> a) -> UFloat a -> a Source # toList :: UFloat a -> [a] Source # null :: UFloat a -> Bool Source # length :: UFloat a -> Int Source # elem :: Eq a => a -> UFloat a -> Bool Source # maximum :: Ord a => UFloat a -> a Source # minimum :: Ord a => UFloat a -> a Source # | |||||
Foldable (UInt :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => UInt m -> m Source # foldMap :: Monoid m => (a -> m) -> UInt a -> m Source # foldMap' :: Monoid m => (a -> m) -> UInt a -> m Source # foldr :: (a -> b -> b) -> b -> UInt a -> b Source # foldr' :: (a -> b -> b) -> b -> UInt a -> b Source # foldl :: (b -> a -> b) -> b -> UInt a -> b Source # foldl' :: (b -> a -> b) -> b -> UInt a -> b Source # foldr1 :: (a -> a -> a) -> UInt a -> a Source # foldl1 :: (a -> a -> a) -> UInt a -> a Source # toList :: UInt a -> [a] Source # null :: UInt a -> Bool Source # length :: UInt a -> Int Source # elem :: Eq a => a -> UInt a -> Bool Source # maximum :: Ord a => UInt a -> a Source # minimum :: Ord a => UInt a -> a Source # | |||||
Foldable (UWord :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => UWord m -> m Source # foldMap :: Monoid m => (a -> m) -> UWord a -> m Source # foldMap' :: Monoid m => (a -> m) -> UWord a -> m Source # foldr :: (a -> b -> b) -> b -> UWord a -> b Source # foldr' :: (a -> b -> b) -> b -> UWord a -> b Source # foldl :: (b -> a -> b) -> b -> UWord a -> b Source # foldl' :: (b -> a -> b) -> b -> UWord a -> b Source # foldr1 :: (a -> a -> a) -> UWord a -> a Source # foldl1 :: (a -> a -> a) -> UWord a -> a Source # toList :: UWord a -> [a] Source # null :: UWord a -> Bool Source # length :: UWord a -> Int Source # elem :: Eq a => a -> UWord a -> Bool Source # maximum :: Ord a => UWord a -> a Source # minimum :: Ord a => UWord a -> a Source # | |||||
Traversable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Traversable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Traversable (UDouble :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Traversable | |||||
Traversable (UFloat :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Traversable (UInt :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Traversable (UWord :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec (Ptr ()) :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Char :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Double :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Float :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Int :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Word :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Generic (URec (Ptr ()) p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (URec Char p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (URec Double p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (URec Float p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (URec Int p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (URec Word p) Source # | |||||
Defined in GHC.Generics
| |||||
Show (URec Char p) Source # | Since: base-4.9.0.0 | ||||
Show (URec Double p) Source # | Since: base-4.9.0.0 | ||||
Show (URec Float p) Source # | |||||
Show (URec Int p) Source # | Since: base-4.9.0.0 | ||||
Show (URec Word p) Source # | Since: base-4.9.0.0 | ||||
Eq (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 | ||||
Eq (URec Char p) Source # | Since: base-4.9.0.0 | ||||
Eq (URec Double p) Source # | Since: base-4.9.0.0 | ||||
Eq (URec Float p) Source # | |||||
Eq (URec Int p) Source # | Since: base-4.9.0.0 | ||||
Eq (URec Word p) Source # | Since: base-4.9.0.0 | ||||
Ord (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering Source # (<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source # | |||||
Ord (URec Char p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics compare :: URec Char p -> URec Char p -> Ordering Source # (<) :: URec Char p -> URec Char p -> Bool Source # (<=) :: URec Char p -> URec Char p -> Bool Source # (>) :: URec Char p -> URec Char p -> Bool Source # (>=) :: URec Char p -> URec Char p -> Bool Source # | |||||
Ord (URec Double p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics compare :: URec Double p -> URec Double p -> Ordering Source # (<) :: URec Double p -> URec Double p -> Bool Source # (<=) :: URec Double p -> URec Double p -> Bool Source # (>) :: URec Double p -> URec Double p -> Bool Source # (>=) :: URec Double p -> URec Double p -> Bool Source # max :: URec Double p -> URec Double p -> URec Double p Source # min :: URec Double p -> URec Double p -> URec Double p Source # | |||||
Ord (URec Float p) Source # | |||||
Defined in GHC.Generics compare :: URec Float p -> URec Float p -> Ordering Source # (<) :: URec Float p -> URec Float p -> Bool Source # (<=) :: URec Float p -> URec Float p -> Bool Source # (>) :: URec Float p -> URec Float p -> Bool Source # (>=) :: URec Float p -> URec Float p -> Bool Source # max :: URec Float p -> URec Float p -> URec Float p Source # min :: URec Float p -> URec Float p -> URec Float p Source # | |||||
Ord (URec Int p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics compare :: URec Int p -> URec Int p -> Ordering Source # (<) :: URec Int p -> URec Int p -> Bool Source # (<=) :: URec Int p -> URec Int p -> Bool Source # (>) :: URec Int p -> URec Int p -> Bool Source # (>=) :: URec Int p -> URec Int p -> Bool Source # | |||||
Ord (URec Word p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics compare :: URec Word p -> URec Word p -> Ordering Source # (<) :: URec Word p -> URec Word p -> Bool Source # (<=) :: URec Word p -> URec Word p -> Bool Source # (>) :: URec Word p -> URec Word p -> Bool Source # (>=) :: URec Word p -> URec Word p -> Bool Source # | |||||
data URec Char (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
data URec Double (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
data URec Float (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
data URec Int (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
data URec Word (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
data URec (Ptr ()) (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
type Rep1 (URec (Ptr ()) :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep1 (URec Char :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep1 (URec Double :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep1 (URec Float :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep1 (URec Int :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep1 (URec Word :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep (URec Char p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep (URec Double p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep (URec Float p) Source # | |||||
Defined in GHC.Generics | |||||
type Rep (URec Int p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep (URec Word p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics |
Synonyms for convenience
type D1 = M1 D :: Meta -> (k -> Type) -> k -> Type Source #
Type synonym for encoding meta-information for datatypes
type C1 = M1 C :: Meta -> (k -> Type) -> k -> Type Source #
Type synonym for encoding meta-information for constructors
type S1 = M1 S :: Meta -> (k -> Type) -> k -> Type Source #
Type synonym for encoding meta-information for record selectors
Meta-information
class Datatype (d :: k) where Source #
Class for datatypes that represent datatypes
datatypeName :: forall k1 t (f :: k1 -> Type) (a :: k1). t d f a -> [Char] Source #
The name of the datatype (unqualified)
moduleName :: forall k1 t (f :: k1 -> Type) (a :: k1). t d f a -> [Char] Source #
The fully-qualified name of the module where the type is declared
packageName :: forall k1 t (f :: k1 -> Type) (a :: k1). t d f a -> [Char] Source #
The package name of the module where the type is declared
Since: base-4.9.0.0
isNewtype :: forall k1 t (f :: k1 -> Type) (a :: k1). t d f a -> Bool Source #
Marks if the datatype is actually a newtype
Since: base-4.7.0.0
Instances
(KnownSymbol n, KnownSymbol m, KnownSymbol p, SingI nt) => Datatype ('MetaData n m p nt :: Meta) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics datatypeName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> [Char] Source # moduleName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> [Char] Source # packageName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> [Char] Source # isNewtype :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> Bool Source # |
class Constructor (c :: k) where Source #
Class for datatypes that represent data constructors
conName :: forall k1 t (f :: k1 -> Type) (a :: k1). t c f a -> [Char] Source #
The name of the constructor
conFixity :: forall k1 t (f :: k1 -> Type) (a :: k1). t c f a -> Fixity Source #
The fixity of the constructor
conIsRecord :: forall k1 t (f :: k1 -> Type) (a :: k1). t c f a -> Bool Source #
Marks if this constructor is a record
Instances
(KnownSymbol n, SingI f, SingI r) => Constructor ('MetaCons n f r :: Meta) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics |
class Selector (s :: k) where Source #
Class for datatypes that represent records
selName :: forall k1 t (f :: k1 -> Type) (a :: k1). t s f a -> [Char] Source #
The name of the selector
selSourceUnpackedness :: forall k1 t (f :: k1 -> Type) (a :: k1). t s f a -> SourceUnpackedness Source #
The selector's unpackedness annotation (if any)
Since: base-4.9.0.0
selSourceStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t s f a -> SourceStrictness Source #
The selector's strictness annotation (if any)
Since: base-4.9.0.0
selDecidedStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t s f a -> DecidedStrictness Source #
The strictness that the compiler inferred for the selector
Since: base-4.9.0.0
Instances
(SingI mn, SingI su, SingI ss, SingI ds) => Selector ('MetaSel mn su ss ds :: Meta) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics selName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> [Char] Source # selSourceUnpackedness :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> SourceUnpackedness Source # selSourceStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> SourceStrictness Source # selDecidedStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> DecidedStrictness Source # |
Datatype to represent the fixity of a constructor. An infix
| declaration directly corresponds to an application of Infix
.
Instances
Data Fixity Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixity -> c Fixity Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Fixity Source # toConstr :: Fixity -> Constr Source # dataTypeOf :: Fixity -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Fixity) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity) Source # gmapT :: (forall b. Data b => b -> b) -> Fixity -> Fixity Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Fixity -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixity -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity Source # | |||||
Generic Fixity Source # | |||||
Defined in GHC.Generics
| |||||
Read Fixity Source # | Since: base-4.6.0.0 | ||||
Show Fixity Source # | Since: base-4.6.0.0 | ||||
Eq Fixity Source # | Since: base-4.6.0.0 | ||||
Ord Fixity Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep Fixity Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Generics type Rep Fixity = D1 ('MetaData "Fixity" "GHC.Generics" "base" 'False) (C1 ('MetaCons "Prefix" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Infix" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Associativity) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
This variant of Fixity
appears at the type level.
Since: base-4.9.0.0
data Associativity Source #
Datatype to represent the associativity of a constructor
Instances
data SourceUnpackedness Source #
The unpackedness of a field as the user wrote it in the source code. For example, in the following data type:
data E = ExampleConstructor Int {-# NOUNPACK #-} Int {-# UNPACK #-} Int
The fields of ExampleConstructor
have NoSourceUnpackedness
,
SourceNoUnpack
, and SourceUnpack
, respectively.
Since: base-4.9.0.0
Instances
Data SourceUnpackedness Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceUnpackedness -> c SourceUnpackedness Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceUnpackedness Source # toConstr :: SourceUnpackedness -> Constr Source # dataTypeOf :: SourceUnpackedness -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceUnpackedness) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceUnpackedness) Source # gmapT :: (forall b. Data b => b -> b) -> SourceUnpackedness -> SourceUnpackedness Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceUnpackedness -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceUnpackedness -> r Source # gmapQ :: (forall d. Data d => d -> u) -> SourceUnpackedness -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceUnpackedness -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceUnpackedness -> m SourceUnpackedness Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceUnpackedness -> m SourceUnpackedness Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceUnpackedness -> m SourceUnpackedness Source # | |||||
Bounded SourceUnpackedness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
Enum SourceUnpackedness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics succ :: SourceUnpackedness -> SourceUnpackedness Source # pred :: SourceUnpackedness -> SourceUnpackedness Source # toEnum :: Int -> SourceUnpackedness Source # fromEnum :: SourceUnpackedness -> Int Source # enumFrom :: SourceUnpackedness -> [SourceUnpackedness] Source # enumFromThen :: SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] Source # enumFromTo :: SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] Source # enumFromThenTo :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] Source # | |||||
Generic SourceUnpackedness Source # | |||||
Defined in GHC.Generics
from :: SourceUnpackedness -> Rep SourceUnpackedness x Source # to :: Rep SourceUnpackedness x -> SourceUnpackedness Source # | |||||
Ix SourceUnpackedness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics range :: (SourceUnpackedness, SourceUnpackedness) -> [SourceUnpackedness] Source # index :: (SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Int Source # unsafeIndex :: (SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Int Source # inRange :: (SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Bool Source # rangeSize :: (SourceUnpackedness, SourceUnpackedness) -> Int Source # unsafeRangeSize :: (SourceUnpackedness, SourceUnpackedness) -> Int Source # | |||||
Read SourceUnpackedness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
Show SourceUnpackedness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
Eq SourceUnpackedness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics (==) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (/=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # | |||||
Ord SourceUnpackedness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics compare :: SourceUnpackedness -> SourceUnpackedness -> Ordering Source # (<) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (<=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (>) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (>=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # max :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness Source # min :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness Source # | |||||
type Rep SourceUnpackedness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics type Rep SourceUnpackedness = D1 ('MetaData "SourceUnpackedness" "GHC.Generics" "base" 'False) (C1 ('MetaCons "NoSourceUnpackedness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourceNoUnpack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourceUnpack" 'PrefixI 'False) (U1 :: Type -> Type))) |
data SourceStrictness Source #
The strictness of a field as the user wrote it in the source code. For example, in the following data type:
data E = ExampleConstructor Int ~Int !Int
The fields of ExampleConstructor
have NoSourceStrictness
,
SourceLazy
, and SourceStrict
, respectively.
Since: base-4.9.0.0
Instances
Data SourceStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceStrictness -> c SourceStrictness Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceStrictness Source # toConstr :: SourceStrictness -> Constr Source # dataTypeOf :: SourceStrictness -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceStrictness) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceStrictness) Source # gmapT :: (forall b. Data b => b -> b) -> SourceStrictness -> SourceStrictness Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceStrictness -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceStrictness -> r Source # gmapQ :: (forall d. Data d => d -> u) -> SourceStrictness -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceStrictness -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceStrictness -> m SourceStrictness Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceStrictness -> m SourceStrictness Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceStrictness -> m SourceStrictness Source # | |||||
Bounded SourceStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
Enum SourceStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics succ :: SourceStrictness -> SourceStrictness Source # pred :: SourceStrictness -> SourceStrictness Source # toEnum :: Int -> SourceStrictness Source # fromEnum :: SourceStrictness -> Int Source # enumFrom :: SourceStrictness -> [SourceStrictness] Source # enumFromThen :: SourceStrictness -> SourceStrictness -> [SourceStrictness] Source # enumFromTo :: SourceStrictness -> SourceStrictness -> [SourceStrictness] Source # enumFromThenTo :: SourceStrictness -> SourceStrictness -> SourceStrictness -> [SourceStrictness] Source # | |||||
Generic SourceStrictness Source # | |||||
Defined in GHC.Generics
from :: SourceStrictness -> Rep SourceStrictness x Source # to :: Rep SourceStrictness x -> SourceStrictness Source # | |||||
Ix SourceStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics range :: (SourceStrictness, SourceStrictness) -> [SourceStrictness] Source # index :: (SourceStrictness, SourceStrictness) -> SourceStrictness -> Int Source # unsafeIndex :: (SourceStrictness, SourceStrictness) -> SourceStrictness -> Int Source # inRange :: (SourceStrictness, SourceStrictness) -> SourceStrictness -> Bool Source # rangeSize :: (SourceStrictness, SourceStrictness) -> Int Source # unsafeRangeSize :: (SourceStrictness, SourceStrictness) -> Int Source # | |||||
Read SourceStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
Show SourceStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
Eq SourceStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics (==) :: SourceStrictness -> SourceStrictness -> Bool Source # (/=) :: SourceStrictness -> SourceStrictness -> Bool Source # | |||||
Ord SourceStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics compare :: SourceStrictness -> SourceStrictness -> Ordering Source # (<) :: SourceStrictness -> SourceStrictness -> Bool Source # (<=) :: SourceStrictness -> SourceStrictness -> Bool Source # (>) :: SourceStrictness -> SourceStrictness -> Bool Source # (>=) :: SourceStrictness -> SourceStrictness -> Bool Source # max :: SourceStrictness -> SourceStrictness -> SourceStrictness Source # min :: SourceStrictness -> SourceStrictness -> SourceStrictness Source # | |||||
type Rep SourceStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics type Rep SourceStrictness = D1 ('MetaData "SourceStrictness" "GHC.Generics" "base" 'False) (C1 ('MetaCons "NoSourceStrictness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourceLazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourceStrict" 'PrefixI 'False) (U1 :: Type -> Type))) |
data DecidedStrictness Source #
The strictness that GHC infers for a field during compilation. Whereas
there are nine different combinations of SourceUnpackedness
and
SourceStrictness
, the strictness that GHC decides will ultimately be one
of lazy, strict, or unpacked. What GHC decides is affected both by what the
user writes in the source code and by GHC flags. As an example, consider
this data type:
data E = ExampleConstructor {-# UNPACK #-} !Int !Int Int
- If compiled without optimization or other language extensions, then the
fields of
ExampleConstructor
will haveDecidedStrict
,DecidedStrict
, andDecidedLazy
, respectively. - If compiled with
-XStrictData
enabled, then the fields will haveDecidedStrict
,DecidedStrict
, andDecidedStrict
, respectively. - If compiled with
-O2
enabled, then the fields will haveDecidedUnpack
,DecidedStrict
, andDecidedLazy
, respectively.
Since: base-4.9.0.0
Instances
Data DecidedStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DecidedStrictness -> c DecidedStrictness Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DecidedStrictness Source # toConstr :: DecidedStrictness -> Constr Source # dataTypeOf :: DecidedStrictness -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DecidedStrictness) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DecidedStrictness) Source # gmapT :: (forall b. Data b => b -> b) -> DecidedStrictness -> DecidedStrictness Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DecidedStrictness -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DecidedStrictness -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DecidedStrictness -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DecidedStrictness -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DecidedStrictness -> m DecidedStrictness Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DecidedStrictness -> m DecidedStrictness Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DecidedStrictness -> m DecidedStrictness Source # | |||||
Bounded DecidedStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
Enum DecidedStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics succ :: DecidedStrictness -> DecidedStrictness Source # pred :: DecidedStrictness -> DecidedStrictness Source # toEnum :: Int -> DecidedStrictness Source # fromEnum :: DecidedStrictness -> Int Source # enumFrom :: DecidedStrictness -> [DecidedStrictness] Source # enumFromThen :: DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] Source # enumFromTo :: DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] Source # enumFromThenTo :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] Source # | |||||
Generic DecidedStrictness Source # | |||||
Defined in GHC.Generics
from :: DecidedStrictness -> Rep DecidedStrictness x Source # to :: Rep DecidedStrictness x -> DecidedStrictness Source # | |||||
Ix DecidedStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics range :: (DecidedStrictness, DecidedStrictness) -> [DecidedStrictness] Source # index :: (DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Int Source # unsafeIndex :: (DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Int Source # inRange :: (DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Bool Source # rangeSize :: (DecidedStrictness, DecidedStrictness) -> Int Source # unsafeRangeSize :: (DecidedStrictness, DecidedStrictness) -> Int Source # | |||||
Read DecidedStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
Show DecidedStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
Eq DecidedStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics (==) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (/=) :: DecidedStrictness -> DecidedStrictness -> Bool Source # | |||||
Ord DecidedStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics compare :: DecidedStrictness -> DecidedStrictness -> Ordering Source # (<) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (<=) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (>) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (>=) :: DecidedStrictness -> DecidedStrictness -> Bool Source # max :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness Source # min :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness Source # | |||||
type Rep DecidedStrictness Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics type Rep DecidedStrictness = D1 ('MetaData "DecidedStrictness" "GHC.Generics" "base" 'False) (C1 ('MetaCons "DecidedLazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DecidedStrict" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DecidedUnpack" 'PrefixI 'False) (U1 :: Type -> Type))) |
Datatype to represent metadata associated with a datatype (MetaData
),
constructor (MetaCons
), or field selector (MetaSel
).
- In
MetaData n m p nt
,n
is the datatype's name,m
is the module in which the datatype is defined,p
is the package in which the datatype is defined, andnt
is'True
if the datatype is anewtype
. - In
MetaCons n f s
,n
is the constructor's name,f
is its fixity, ands
is'True
if the constructor contains record selectors. - In
MetaSel mn su ss ds
, if the field uses record syntax, thenmn
isJust
the record name. Otherwise,mn
isNothing
.su
andss
are the field's unpackedness and strictness annotations, andds
is the strictness that GHC infers for the field.
Since: base-4.9.0.0
MetaData Symbol Symbol Symbol Bool | |
MetaCons Symbol FixityI Bool | |
MetaSel (Maybe Symbol) SourceUnpackedness SourceStrictness DecidedStrictness |
Instances
(KnownSymbol n, SingI f, SingI r) => Constructor ('MetaCons n f r :: Meta) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
(KnownSymbol n, KnownSymbol m, KnownSymbol p, SingI nt) => Datatype ('MetaData n m p nt :: Meta) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics datatypeName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> [Char] Source # moduleName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> [Char] Source # packageName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> [Char] Source # isNewtype :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> Bool Source # | |
(SingI mn, SingI su, SingI ss, SingI ds) => Selector ('MetaSel mn su ss ds :: Meta) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics selName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> [Char] Source # selSourceUnpackedness :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> SourceUnpackedness Source # selSourceStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> SourceStrictness Source # selDecidedStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> DecidedStrictness Source # |
Generic type classes
class Generic a where Source #
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id
Convert from the datatype to its representation
Convert from the representation to the datatype
Instances
Generic All Source # | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic Any Source # | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic Version Source # | |||||
Defined in Data.Version
| |||||
Generic Void Source # | |||||
Generic ByteOrder Source # | |||||
Defined in GHC.ByteOrder | |||||
Generic Fingerprint Source # | |||||
Defined in GHC.Generics
from :: Fingerprint -> Rep Fingerprint x Source # to :: Rep Fingerprint x -> Fingerprint Source # | |||||
Generic Associativity Source # | |||||
Defined in GHC.Generics
from :: Associativity -> Rep Associativity x Source # to :: Rep Associativity x -> Associativity Source # | |||||
Generic DecidedStrictness Source # | |||||
Defined in GHC.Generics
from :: DecidedStrictness -> Rep DecidedStrictness x Source # to :: Rep DecidedStrictness x -> DecidedStrictness Source # | |||||
Generic Fixity Source # | |||||
Defined in GHC.Generics
| |||||
Generic SourceStrictness Source # | |||||
Defined in GHC.Generics
from :: SourceStrictness -> Rep SourceStrictness x Source # to :: Rep SourceStrictness x -> SourceStrictness Source # | |||||
Generic SourceUnpackedness Source # | |||||
Defined in GHC.Generics
from :: SourceUnpackedness -> Rep SourceUnpackedness x Source # to :: Rep SourceUnpackedness x -> SourceUnpackedness Source # | |||||
Generic ExitCode Source # | |||||
Defined in GHC.IO.Exception
| |||||
Generic CCFlags Source # | |||||
Defined in GHC.RTS.Flags
| |||||
Generic ConcFlags Source # | |||||
Defined in GHC.RTS.Flags
| |||||
Generic DebugFlags Source # | |||||
Defined in GHC.RTS.Flags
from :: DebugFlags -> Rep DebugFlags x Source # to :: Rep DebugFlags x -> DebugFlags Source # | |||||
Generic DoCostCentres Source # | |||||
Defined in GHC.RTS.Flags
from :: DoCostCentres -> Rep DoCostCentres x Source # to :: Rep DoCostCentres x -> DoCostCentres Source # | |||||
Generic DoHeapProfile Source # | |||||
Defined in GHC.RTS.Flags
from :: DoHeapProfile -> Rep DoHeapProfile x Source # to :: Rep DoHeapProfile x -> DoHeapProfile Source # | |||||
Generic DoTrace Source # | |||||
Defined in GHC.RTS.Flags
| |||||
Generic GCFlags Source # | |||||
Defined in GHC.RTS.Flags
| |||||
Generic GiveGCStats Source # | |||||
Defined in GHC.RTS.Flags
from :: GiveGCStats -> Rep GiveGCStats x Source # to :: Rep GiveGCStats x -> GiveGCStats Source # | |||||
Generic MiscFlags Source # | |||||
Defined in GHC.RTS.Flags
| |||||
Generic ParFlags Source # | |||||
Defined in GHC.RTS.Flags
| |||||
Generic ProfFlags Source # | |||||
Defined in GHC.RTS.Flags
| |||||
Generic RTSFlags Source # | |||||
Defined in GHC.RTS.Flags
| |||||
Generic TickyFlags Source # | |||||
Defined in GHC.RTS.Flags
from :: TickyFlags -> Rep TickyFlags x Source # to :: Rep TickyFlags x -> TickyFlags Source # | |||||
Generic TraceFlags Source # | |||||
Defined in GHC.RTS.Flags
from :: TraceFlags -> Rep TraceFlags x Source # to :: Rep TraceFlags x -> TraceFlags Source # | |||||
Generic SrcLoc Source # | |||||
Defined in GHC.Generics
| |||||
Generic GCDetails Source # | |||||
Defined in GHC.Stats
| |||||
Generic RTSStats Source # | |||||
Defined in GHC.Stats
| |||||
Generic GeneralCategory Source # | |||||
Defined in GHC.Generics
from :: GeneralCategory -> Rep GeneralCategory x Source # to :: Rep GeneralCategory x -> GeneralCategory Source # | |||||
Generic Ordering Source # | |||||
Defined in GHC.Generics | |||||
Generic () Source # | |||||
Generic Bool Source # | |||||
Defined in GHC.Generics | |||||
Generic (ZipList a) Source # | |||||
Defined in Control.Applicative
| |||||
Generic (Complex a) Source # | |||||
Defined in Data.Complex
| |||||
Generic (Identity a) Source # | |||||
Defined in Data.Functor.Identity
| |||||
Generic (First a) Source # | |||||
Defined in Data.Monoid
| |||||
Generic (Last a) Source # | |||||
Defined in Data.Monoid
| |||||
Generic (Down a) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (First a) Source # | |||||
Defined in Data.Semigroup
| |||||
Generic (Last a) Source # | |||||
Defined in Data.Semigroup
| |||||
Generic (Max a) Source # | |||||
Defined in Data.Semigroup
| |||||
Generic (Min a) Source # | |||||
Defined in Data.Semigroup
| |||||
Generic (WrappedMonoid m) Source # | |||||
Defined in Data.Semigroup
from :: WrappedMonoid m -> Rep (WrappedMonoid m) x Source # to :: Rep (WrappedMonoid m) x -> WrappedMonoid m Source # | |||||
Generic (Dual a) Source # | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic (Endo a) Source # | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic (Product a) Source # | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic (Sum a) Source # | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic (NonEmpty a) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (Par1 p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (Maybe a) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (Solo a) Source # | |||||
Defined in GHC.Generics
| |||||
Generic [a] Source # | |||||
Defined in GHC.Generics
| |||||
Generic (WrappedMonad m a) Source # | |||||
Defined in Control.Applicative
from :: WrappedMonad m a -> Rep (WrappedMonad m a) x Source # to :: Rep (WrappedMonad m a) x -> WrappedMonad m a Source # | |||||
Generic (Either a b) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (Proxy t) Source # | |||||
Defined in GHC.Generics | |||||
Generic (Arg a b) Source # | |||||
Defined in Data.Semigroup
| |||||
Generic (U1 p) Source # | |||||
Generic (V1 p) Source # | |||||
Generic (a, b) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (WrappedArrow a b c) Source # | |||||
Defined in Control.Applicative
from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x Source # to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c Source # | |||||
Generic (Kleisli m a b) Source # | |||||
Defined in Control.Arrow
| |||||
Generic (Const a b) Source # | |||||
Defined in Data.Functor.Const
| |||||
Generic (Ap f a) Source # | |||||
Defined in Data.Monoid
| |||||
Generic (Alt f a) Source # | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic (Rec1 f p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (URec (Ptr ()) p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (URec Char p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (URec Double p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (URec Float p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (URec Int p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (URec Word p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (Product f g a) Source # | |||||
Defined in Data.Functor.Product
| |||||
Generic (Sum f g a) Source # | |||||
Defined in Data.Functor.Sum
| |||||
Generic ((f :*: g) p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic ((f :+: g) p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (K1 i c p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (Compose f g a) Source # | |||||
Defined in Data.Functor.Compose
| |||||
Generic ((f :.: g) p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (M1 i c f p) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i, j) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |||||
Defined in GHC.Generics
|
class Generic1 (f :: k -> Type) where Source #
Representable types of kind * -> *
(or kind k -> *
, when PolyKinds
is enabled).
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic1
instance must satisfy the following laws:
from1
.to1
≡id
to1
.from1
≡id
from1 :: forall (a :: k). f a -> Rep1 f a Source #
Convert from the datatype to its representation
to1 :: forall (a :: k). Rep1 f a -> f a Source #
Convert from the representation to the datatype
Instances
Generic1 ZipList Source # | |||||
Defined in Control.Applicative
| |||||
Generic1 Complex Source # | |||||
Defined in Data.Complex
| |||||
Generic1 Identity Source # | |||||
Defined in Data.Functor.Identity
| |||||
Generic1 First Source # | |||||
Defined in Data.Monoid
| |||||
Generic1 Last Source # | |||||
Defined in Data.Monoid
| |||||
Generic1 Down Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 First Source # | |||||
Defined in Data.Semigroup
| |||||
Generic1 Last Source # | |||||
Defined in Data.Semigroup
| |||||
Generic1 Max Source # | |||||
Defined in Data.Semigroup
| |||||
Generic1 Min Source # | |||||
Defined in Data.Semigroup
| |||||
Generic1 WrappedMonoid Source # | |||||
Defined in Data.Semigroup
from1 :: WrappedMonoid a -> Rep1 WrappedMonoid a Source # to1 :: Rep1 WrappedMonoid a -> WrappedMonoid a Source # | |||||
Generic1 Dual Source # | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic1 Product Source # | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic1 Sum Source # | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic1 NonEmpty Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 Par1 Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 Maybe Source # | |||||
Defined in GHC.Generics | |||||
Generic1 Solo Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 [] Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (WrappedMonad m :: Type -> Type) Source # | |||||
Defined in Control.Applicative
from1 :: WrappedMonad m a -> Rep1 (WrappedMonad m) a Source # to1 :: Rep1 (WrappedMonad m) a -> WrappedMonad m a Source # | |||||
Generic1 (Either a :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (Arg a :: Type -> Type) Source # | |||||
Defined in Data.Semigroup
| |||||
Generic1 ((,) a :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (Proxy :: k -> Type) Source # | |||||
Defined in GHC.Generics | |||||
Generic1 (U1 :: k -> Type) Source # | |||||
Defined in GHC.Generics | |||||
Generic1 (V1 :: k -> Type) Source # | |||||
Defined in GHC.Generics | |||||
Generic1 (WrappedArrow a b :: Type -> Type) Source # | |||||
Defined in Control.Applicative
from1 :: WrappedArrow a b a0 -> Rep1 (WrappedArrow a b) a0 Source # to1 :: Rep1 (WrappedArrow a b) a0 -> WrappedArrow a b a0 Source # | |||||
Generic1 (Kleisli m a :: Type -> Type) Source # | |||||
Defined in Control.Arrow | |||||
Generic1 ((,,) a b :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (Const a :: k -> Type) Source # | |||||
Defined in Data.Functor.Const
| |||||
Generic1 (Ap f :: k -> Type) Source # | |||||
Defined in Data.Monoid
| |||||
Generic1 (Alt f :: k -> Type) Source # | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic1 (Rec1 f :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (URec (Ptr ()) :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (URec Char :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (URec Double :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (URec Float :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (URec Int :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (URec Word :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 ((,,,) a b c :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (Product f g :: k -> Type) Source # | |||||
Defined in Data.Functor.Product
| |||||
Generic1 (Sum f g :: k -> Type) Source # | |||||
Defined in Data.Functor.Sum
| |||||
Generic1 (f :*: g :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (f :+: g :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (K1 i c :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 ((,,,,) a b c d :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Functor f => Generic1 (Compose f g :: k -> Type) Source # | |||||
Defined in Data.Functor.Compose
| |||||
Functor f => Generic1 (f :.: g :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 (M1 i c f :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 ((,,,,,) a b c d e :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 ((,,,,,,) a b c d e f :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Generic1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source # | |||||
Defined in GHC.Generics
from1 :: (a, b, c, d, e, f, g, h, a0) -> Rep1 ((,,,,,,,,) a b c d e f g h) a0 Source # to1 :: Rep1 ((,,,,,,,,) a b c d e f g h) a0 -> (a, b, c, d, e, f, g, h, a0) Source # | |||||
Generic1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) Source # | |||||
Defined in GHC.Generics
from1 :: (a, b, c, d, e, f, g, h, i, a0) -> Rep1 ((,,,,,,,,,) a b c d e f g h i) a0 Source # to1 :: Rep1 ((,,,,,,,,,) a b c d e f g h i) a0 -> (a, b, c, d, e, f, g, h, i, a0) Source # | |||||
Generic1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) Source # | |||||
Defined in GHC.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, a0) -> Rep1 ((,,,,,,,,,,) a b c d e f g h i j) a0 Source # to1 :: Rep1 ((,,,,,,,,,,) a b c d e f g h i j) a0 -> (a, b, c, d, e, f, g, h, i, j, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) Source # | |||||
Defined in GHC.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, a0) -> Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) a0 -> (a, b, c, d, e, f, g, h, i, j, k, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) Source # | |||||
Defined in GHC.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, a0) -> Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) Source # | |||||
Defined in GHC.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, m, a0) -> Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, m, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) Source # | |||||
Defined in GHC.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a0) -> Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a0) Source # |
Generic wrapper
newtype Generically a Source #
A datatype whose instances are defined generically, using the
Generic
representation. Generically1
is a higher-kinded version
of Generically
that uses Generic1
.
Generic instances can be derived via
using
Generically
A-XDerivingVia
.
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DerivingVia #-} import GHC.Generics (Generic) data V4 a = V4 a a a a deriving stock Generic deriving (Semigroup, Monoid) via Generically (V4 a)
This corresponds to Semigroup
and Monoid
instances defined by
pointwise lifting:
instance Semigroup a => Semigroup (V4 a) where (<>) :: V4 a -> V4 a -> V4 a V4 a1 b1 c1 d1 <> V4 a2 b2 c2 d2 = V4 (a1 <> a2) (b1 <> b2) (c1 <> c2) (d1 <> d2) instance Monoid a => Monoid (V4 a) where mempty :: V4 a mempty = V4 mempty mempty mempty mempty
Historically this required modifying the type class to include
generic method definitions (-XDefaultSignatures
) and deriving it
with the anyclass
strategy (-XDeriveAnyClass
). Having a /via
type/ like Generically
decouples the instance from the type
class.
Since: base-4.17.0.0
Instances
(Generic a, Monoid (Rep a ())) => Monoid (Generically a) Source # | Since: base-4.17.0.0 |
Defined in GHC.Generics mempty :: Generically a Source # mappend :: Generically a -> Generically a -> Generically a Source # mconcat :: [Generically a] -> Generically a Source # | |
(Generic a, Semigroup (Rep a ())) => Semigroup (Generically a) Source # | Since: base-4.17.0.0 |
Defined in GHC.Generics (<>) :: Generically a -> Generically a -> Generically a Source # sconcat :: NonEmpty (Generically a) -> Generically a Source # stimes :: Integral b => b -> Generically a -> Generically a Source # |
newtype Generically1 (f :: k -> Type) (a :: k) where Source #
A type whose instances are defined generically, using the
Generic1
representation. Generically1
is a higher-kinded
version of Generically
that uses Generic
.
Generic instances can be derived for type constructors via
using Generically1
F-XDerivingVia
.
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DerivingVia #-} import GHC.Generics (Generic) data V4 a = V4 a a a a deriving stock (Functor, Generic1) deriving Applicative via Generically1 V4
This corresponds to Applicative
instances defined by pointwise
lifting:
instance Applicative V4 where pure :: a -> V4 a pure a = V4 a a a a liftA2 :: (a -> b -> c) -> (V4 a -> V4 b -> V4 c) liftA2 (·) (V4 a1 b1 c1 d1) (V4 a2 b2 c2 d2) = V4 (a1 · a2) (b1 · b2) (c1 · c2) (d1 · d2)
Historically this required modifying the type class to include
generic method definitions (-XDefaultSignatures
) and deriving it
with the anyclass
strategy (-XDeriveAnyClass
). Having a /via
type/ like Generically1
decouples the instance from the type
class.
Since: base-4.17.0.0
Generically1 :: forall {k} (f :: k -> Type) (a :: k). f a -> Generically1 f a |
Instances
(Generic1 f, Eq1 (Rep1 f)) => Eq1 (Generically1 f) Source # | Since: base-4.17.0.0 |
Defined in Data.Functor.Classes liftEq :: (a -> b -> Bool) -> Generically1 f a -> Generically1 f b -> Bool Source # | |
(Generic1 f, Ord1 (Rep1 f)) => Ord1 (Generically1 f) Source # | Since: base-4.17.0.0 |
Defined in Data.Functor.Classes liftCompare :: (a -> b -> Ordering) -> Generically1 f a -> Generically1 f b -> Ordering Source # | |
(Generic1 f, Alternative (Rep1 f)) => Alternative (Generically1 f) Source # | Since: base-4.17.0.0 |
Defined in GHC.Generics empty :: Generically1 f a Source # (<|>) :: Generically1 f a -> Generically1 f a -> Generically1 f a Source # some :: Generically1 f a -> Generically1 f [a] Source # many :: Generically1 f a -> Generically1 f [a] Source # | |
(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) Source # | Since: base-4.17.0.0 |
Defined in GHC.Generics pure :: a -> Generically1 f a Source # (<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b Source # liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c Source # (*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b Source # (<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a Source # | |
(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source # | Since: base-4.17.0.0 |
Defined in GHC.Generics fmap :: (a -> b) -> Generically1 f a -> Generically1 f b Source # (<$) :: a -> Generically1 f b -> Generically1 f a Source # | |
(Generic1 f, Eq (Rep1 f a)) => Eq (Generically1 f a) Source # | Since: base-4.18.0.0 |
Defined in GHC.Generics (==) :: Generically1 f a -> Generically1 f a -> Bool Source # (/=) :: Generically1 f a -> Generically1 f a -> Bool Source # | |
(Generic1 f, Ord (Rep1 f a)) => Ord (Generically1 f a) Source # | Since: base-4.18.0.0 |
Defined in GHC.Generics compare :: Generically1 f a -> Generically1 f a -> Ordering Source # (<) :: Generically1 f a -> Generically1 f a -> Bool Source # (<=) :: Generically1 f a -> Generically1 f a -> Bool Source # (>) :: Generically1 f a -> Generically1 f a -> Bool Source # (>=) :: Generically1 f a -> Generically1 f a -> Bool Source # max :: Generically1 f a -> Generically1 f a -> Generically1 f a Source # min :: Generically1 f a -> Generically1 f a -> Generically1 f a Source # |