GHC.Generics
| 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 | Safe |
| Language | Haskell2010 |
Description
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
Introduction
Datatype-generic functions are based on the idea of converting values of a datatype T into corresponding values of a (nearly) isomorphic type Rep T. 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 T and Rep T. By using this technique, we merely need a few generic instances in order to implement functionality that works for any representable type.
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:
instance Generic (Tree a) where type Rep (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:
instance Generic (Tree a) where type Rep (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 Rec0 (Tree a). Representations of individual fields are combined using the binary type constructor :*:.
Now let us explain the additional tags being used in the complete representation:
- The
S1 ('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)tag indicates several things. The'Nothingindicates 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. SeeDecidedStrictnessfor 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
C1 ('MetaCons "Leaf" 'PrefixI 'False)andC1 ('MetaCons "Node" 'PrefixI 'False)invocations indicate that the enclosed part is the representation of the first and second constructor of datatypeTree, respectively. Here, the meta-information regarding constructor names, fixity and whether it has named fields or not is encoded at the type level. The'MetaConstype 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
D1 ('MetaData "Tree" "Main" "package-name" 'False)tag indicates that the enclosed part is the representation of the datatypeTree. Again, the meta-information is encoded at the type level. The'MetaDatatype 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 usingdataornewtypeat 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:
type Rec0 = 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:
type S1 = M1 S type C1 = M1 C type D1 = 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
instance Generic Empty where type Rep 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
instance Generic Bool where type Rep 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:
data V1 p -- lifted version of Empty data U1 p = U1 -- lifted version of () data (:+:) f g p = L1 (f p) | R1 (g p) -- lifted version of Either data (:*:) f g p = (f p) :*: (g p) -- lifted version of (,) newtype K1 i c p = K1 { unK1 :: c } -- a container for a c newtype M1 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 :+: b) :+: c, then the encoding for a would be [False, False], b would be [False, True], and c would be [True]. However, if GHC chooses a :+: (b :+: c), then the encoding for 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)
The generic default is being used. In the future, it will hopefully be possible to use deriving Encode as well, but GHC does not yet support that syntax for this situation.
Having Encode as a class has the advantage that we can define non-generic special cases, which is particularly useful for abstract datatypes that have no structural representation. For example, given a suitable integer encoding function encodeInt, we can define
instance Encode Int where encode = encodeInt
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
K1instance is given, the function may still work for enumeration types, where no constructor has any fields. - If no
V1instance is given, the function may still work for any datatype that is not empty. - If no
U1instance 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:
instance Generic1 Tree where type Rep1 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:
newtype Par1 p = Par1 { unPar1 :: p } -- gives access to parameter p newtype Rec1 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
instance Generic1 WithInt where type Rep1 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
instance Generic1 Rose where type Rep1 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 Rep1 Proxy :: * -> *, but if compiled with 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 Rec0 'Int#'. This won't work, though, since '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 instance URec (Ptr ()) p = UAddr { 'uAddr#' :: 'Addr#' } data instance URec Char p = UChar { 'uChar#' :: 'Char#' } data instance URec Double p = UDouble { 'uDouble#' :: 'Double#' } data instance URec Int p = UFloat { 'uFloat#' :: 'Float#' } data instance URec Float p = UInt { 'uInt#' :: 'Int#' } data instance URec Word p = UWord { 'uWord#' :: 'Word#' }
Several type synonyms are provided for convenience:
type UAddr = URec (Ptr ()) type UChar = URec Char type UDouble = URec Double type UFloat = URec Float type UInt = URec Int type UWord = URec Word
The declaration
data IntHash = IntHash Int# deriving Generic
yields
instance Generic IntHash where type Rep 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.Internal.Generics | |
| Foldable1 (V1 :: Type -> Type) Source | Since: base-4.18.0.0 |
Defined in Data.Foldable1 Methodsfold1 :: 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 | |
| Eq1 (V1 :: Type -> Type) Source | Since: base-4.21.0.0 |
| Ord1 (V1 :: Type -> Type) Source | Since: base-4.21.0.0 |
Defined in Data.Functor.Classes | |
| Read1 (V1 :: Type -> Type) Source | Since: base-4.21.0.0 |
Defined in Data.Functor.Classes | |
| Show1 (V1 :: Type -> Type) Source | Since: base-4.21.0.0 |
| Contravariant (V1 :: Type -> Type) Source | |
| Functor (V1 :: Type -> Type) Source | Since: base-4.9.0.0 |
| Foldable (V1 :: Type -> Type) Source | Since: base-4.9.0.0 |
Defined in GHC.Internal.Data.Foldable Methodsfold :: 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 elem :: Eq a => a -> V1 a -> Bool Source maximum :: Ord a => V1 a -> a Source minimum :: Ord a => V1 a -> a Source | |
| Traversable (V1 :: Type -> Type) Source | Since: base-4.9.0.0 |
| Semigroup (V1 p) Source | Since: base-4.12.0.0 |
| Data p => Data (V1 p) Source | Since: base-4.9.0.0 |
Defined in GHC.Internal.Data.Data Methodsgfoldl :: (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 | |
| Generic (V1 p) Source | |
Defined in GHC.Internal.Generics | |
| 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
Constructors
| U1 |
Instances
| Generic1 (U1 :: k -> Type) Source | |
Defined in GHC.Internal.Generics | |
| Eq1 (U1 :: Type -> Type) Source | Since: base-4.21.0.0 |
| Ord1 (U1 :: Type -> Type) Source | Since: base-4.21.0.0 |
Defined in Data.Functor.Classes | |
| Read1 (U1 :: Type -> Type) Source | Since: base-4.21.0.0 |
Defined in Data.Functor.Classes | |
| Show1 (U1 :: Type -> Type) Source | Since: base-4.21.0.0 |
| Contravariant (U1 :: Type -> Type) Source | |
| 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 |
| MonadZip (U1 :: Type -> Type) Source | Since: ghc-internal-4.9.0.0 |
| Foldable (U1 :: Type -> Type) Source | Since: base-4.9.0.0 |
Defined in GHC.Internal.Data.Foldable Methodsfold :: 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 elem :: Eq a => a -> U1 a -> Bool Source maximum :: Ord a => U1 a -> a Source minimum :: Ord a => U1 a -> a Source | |
| Traversable (U1 :: Type -> Type) Source | Since: base-4.9.0.0 |
| Monoid (U1 p) Source | Since: base-4.12.0.0 |
| Semigroup (U1 p) Source | Since: base-4.12.0.0 |
| Data p => Data (U1 p) Source | Since: base-4.9.0.0 |
Defined in GHC.Internal.Data.Data Methodsgfoldl :: (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 | |
| Generic (U1 p) Source | |
Defined in GHC.Internal.Generics | |
| 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
| Foldable1 Par1 Source | Since: base-4.18.0.0 |
||||
Defined in Data.Foldable1 Methodsfold1 :: 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 | |||||
| Eq1 Par1 Source | Since: base-4.21.0.0 |
||||
| Ord1 Par1 Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| Read1 Par1 Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Par1 a) Source liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Par1 a] Source liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Par1 a) Source liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Par1 a] Source | |||||
| Show1 Par1 Source | Since: base-4.21.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 |
||||
| MonadFix Par1 Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Control.Monad.Fix | |||||
| MonadZip Par1 Source | Since: ghc-internal-4.9.0.0 |
||||
| Foldable Par1 Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Foldable Methodsfold :: 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 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 | |||||
| Traversable Par1 Source | Since: base-4.9.0.0 |
||||
| Generic1 Par1 Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Monoid p => Monoid (Par1 p) Source | Since: base-4.12.0.0 |
||||
| Semigroup p => Semigroup (Par1 p) Source | Since: base-4.12.0.0 |
||||
| Data p => Data (Par1 p) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Data Methodsgfoldl :: (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 | |||||
| Generic (Par1 p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| 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.Internal.Generics | |||||
| type Rep1 Par1 Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type Rep (Par1 p) Source | Since: base-4.7.0.0 |
||||
Defined in GHC.Internal.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.Internal.Generics Associated Types
| |||||
| Foldable1 f => Foldable1 (Rec1 f) Source | Since: base-4.18.0.0 |
||||
Defined in Data.Foldable1 Methodsfold1 :: 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 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 | |||||
| Eq1 f => Eq1 (Rec1 f) Source | Since: base-4.21.0.0 |
||||
| Ord1 f => Ord1 (Rec1 f) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| Read1 f => Read1 (Rec1 f) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Rec1 f a) Source liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Rec1 f a] Source liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Rec1 f a) Source liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Rec1 f a] Source | |||||
| Show1 f => Show1 (Rec1 f) Source | Since: base-4.21.0.0 |
||||
| Contravariant f => Contravariant (Rec1 f) Source | |||||
| 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 |
||||
| MonadFix f => MonadFix (Rec1 f) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Control.Monad.Fix | |||||
| MonadZip f => MonadZip (Rec1 f) Source | Since: ghc-internal-4.9.0.0 |
||||
| Foldable f => Foldable (Rec1 f) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Foldable Methodsfold :: 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 | |||||
| Traversable f => Traversable (Rec1 f) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Traversable | |||||
| 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 |
||||
| (Data (f p), Typeable f, Data p) => Data (Rec1 f p) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Data Methodsgfoldl :: (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 | |||||
| Generic (Rec1 f p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| 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.Internal.Generics | |||||
| type Rep1 (Rec1 f :: k -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type Rep (Rec1 f p) Source | Since: base-4.7.0.0 |
||||
Defined in GHC.Internal.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.Internal.Generics Associated Types
| |||||
| 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 Methodsbitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> K1 i a b -> f (K1 i c d) Source | |||||
| Eq c => Eq1 (K1 i c :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Ord c => Ord1 (K1 i c :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| Read c => Read1 (K1 i c :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (K1 i c a) Source liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [K1 i c a] Source liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (K1 i c a) Source liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [K1 i c a] Source | |||||
| Show c => Show1 (K1 i c :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Contravariant (K1 i c :: Type -> Type) Source | |||||
| 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 |
||||
| Foldable (K1 i c :: Type -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Foldable Methodsfold :: 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 | |||||
| Traversable (K1 i c :: Type -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Traversable | |||||
| 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 |
||||
| (Typeable i, Data p, Data c) => Data (K1 i c p) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Data Methodsgfoldl :: (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 | |||||
| Generic (K1 i c p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| 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.Internal.Generics | |||||
| type Rep1 (K1 i c :: k -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type Rep (K1 i c p) Source | Since: base-4.7.0.0 |
||||
Defined in GHC.Internal.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.Internal.Generics Associated Types
| |||||
| Foldable1 f => Foldable1 (M1 i c f) Source | Since: base-4.18.0.0 |
||||
Defined in Data.Foldable1 Methodsfold1 :: 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 | |||||
| Eq1 f => Eq1 (M1 i c f) Source | Since: base-4.21.0.0 |
||||
| Ord1 f => Ord1 (M1 i c f) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| Read1 f => Read1 (M1 i c f) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (M1 i c f a) Source liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [M1 i c f a] Source liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (M1 i c f a) Source liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [M1 i c f a] Source | |||||
| Show1 f => Show1 (M1 i c f) Source | Since: base-4.21.0.0 |
||||
| Contravariant f => Contravariant (M1 i c f) Source | |||||
| 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.Internal.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 |
||||
| MonadFix f => MonadFix (M1 i c f) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Control.Monad.Fix | |||||
| MonadZip f => MonadZip (M1 i c f) Source | Since: ghc-internal-4.9.0.0 |
||||
| Foldable f => Foldable (M1 i c f) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Foldable Methodsfold :: 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 | |||||
| Traversable f => Traversable (M1 i c f) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Traversable | |||||
| 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 |
||||
| (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 GHC.Internal.Data.Data Methodsgfoldl :: (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 | |||||
| Generic (M1 i c f p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| 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.Internal.Generics Methodscompare :: 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.Internal.Generics | |||||
| type Rep (M1 i c f p) Source | Since: base-4.7.0.0 |
||||
Defined in GHC.Internal.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.Internal.Generics Associated Types
| |||||
| (Foldable1 f, Foldable1 g) => Foldable1 (f :+: g) Source | Since: base-4.18.0.0 |
||||
Defined in Data.Foldable1 Methodsfold1 :: 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 | |||||
| (Eq1 f, Eq1 g) => Eq1 (f :+: g) Source | Since: base-4.21.0.0 |
||||
| (Ord1 f, Ord1 g) => Ord1 (f :+: g) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| (Read1 f, Read1 g) => Read1 (f :+: g) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :+: g) a) Source liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :+: g) a] Source liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :+: g) a) Source liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :+: g) a] Source | |||||
| (Show1 f, Show1 g) => Show1 (f :+: g) Source | Since: base-4.21.0.0 |
||||
| (Contravariant f, Contravariant g) => Contravariant (f :+: g) Source | |||||
| (Functor f, Functor g) => Functor (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 GHC.Internal.Data.Foldable Methodsfold :: 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 | |||||
| (Traversable f, Traversable g) => Traversable (f :+: g) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Traversable Methodstraverse :: Applicative f0 => (a -> f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) Source sequenceA :: Applicative f0 => (f :+: g) (f0 a) -> f0 ((f :+: g) a) Source mapM :: Monad m => (a -> m b) -> (f :+: g) a -> m ((f :+: g) b) Source sequence :: Monad m => (f :+: g) (m a) -> m ((f :+: g) a) Source | |||||
| (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 GHC.Internal.Data.Data Methodsgfoldl :: (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.Internal.Generics Associated Types
| |||||
| (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.Internal.Generics Methodscompare :: (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.Internal.Generics type Rep1 (f :+: g :: k -> Type) = D1 ('MetaData ":+:" "GHC.Internal.Generics" "ghc-internal" '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.Internal.Generics type Rep ((f :+: g) p) = D1 ('MetaData ":+:" "GHC.Internal.Generics" "ghc-internal" '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
Constructors
| (f p) :*: (g p) infixr 6 |
Instances
| Generic1 (f :*: g :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| (Foldable1 f, Foldable1 g) => Foldable1 (f :*: g) Source | Since: base-4.18.0.0 |
||||
Defined in Data.Foldable1 Methodsfold1 :: 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 | |||||
| (Eq1 f, Eq1 g) => Eq1 (f :*: g) Source | Since: base-4.21.0.0 |
||||
| (Ord1 f, Ord1 g) => Ord1 (f :*: g) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| (Read1 f, Read1 g) => Read1 (f :*: g) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :*: g) a) Source liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :*: g) a] Source liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :*: g) a) Source liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :*: g) a] Source | |||||
| (Show1 f, Show1 g) => Show1 (f :*: g) Source | Since: base-4.21.0.0 |
||||
| (Contravariant f, Contravariant g) => Contravariant (f :*: g) Source | |||||
| (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.Internal.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 |
||||
| (MonadFix f, MonadFix g) => MonadFix (f :*: g) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Control.Monad.Fix | |||||
| (MonadZip f, MonadZip g) => MonadZip (f :*: g) Source | Since: ghc-internal-4.9.0.0 |
||||
| (Foldable f, Foldable g) => Foldable (f :*: g) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Foldable Methodsfold :: 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 | |||||
| (Traversable f, Traversable g) => Traversable (f :*: g) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Traversable Methodstraverse :: Applicative f0 => (a -> f0 b) -> (f :*: g) a -> f0 ((f :*: g) b) Source sequenceA :: Applicative f0 => (f :*: g) (f0 a) -> f0 ((f :*: g) a) Source mapM :: Monad m => (a -> m b) -> (f :*: g) a -> m ((f :*: g) b) Source sequence :: Monad m => (f :*: g) (m a) -> m ((f :*: g) a) 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 |
||||
| (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 GHC.Internal.Data.Data Methodsgfoldl :: (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.Internal.Generics Associated Types
| |||||
| (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.Internal.Generics Methodscompare :: (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.Internal.Generics type Rep1 (f :*: g :: k -> Type) = D1 ('MetaData ":*:" "GHC.Internal.Generics" "ghc-internal" '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.Internal.Generics type Rep ((f :*: g) p) = D1 ('MetaData ":*:" "GHC.Internal.Generics" "ghc-internal" '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.Internal.Generics Associated Types
| |||||
| (Foldable1 f, Foldable1 g) => Foldable1 (f :.: g) Source | Since: base-4.18.0.0 |
||||
Defined in Data.Foldable1 Methodsfold1 :: 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 | |||||
| (Eq1 f, Eq1 g) => Eq1 (f :.: g) Source | Since: base-4.21.0.0 |
||||
| (Ord1 f, Ord1 g) => Ord1 (f :.: g) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| (Read1 f, Read1 g) => Read1 (f :.: g) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :.: g) a) Source liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :.: g) a] Source liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :.: g) a) Source liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :.: g) a] Source | |||||
| (Show1 f, Show1 g) => Show1 (f :.: g) Source | Since: base-4.21.0.0 |
||||
| (Functor f, Contravariant g) => Contravariant (f :.: g) Source | |||||
| (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.Internal.Generics | |||||
| (Functor f, Functor g) => Functor (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 GHC.Internal.Data.Foldable Methodsfold :: 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 | |||||
| (Traversable f, Traversable g) => Traversable (f :.: g) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Traversable Methodstraverse :: Applicative f0 => (a -> f0 b) -> (f :.: g) a -> f0 ((f :.: g) b) Source sequenceA :: Applicative f0 => (f :.: g) (f0 a) -> f0 ((f :.: g) a) Source mapM :: Monad m => (a -> m b) -> (f :.: g) a -> m ((f :.: g) b) Source sequence :: Monad m => (f :.: g) (m a) -> m ((f :.: g) a) 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 |
||||
| (Typeable f, Typeable g, Data p, Data (f (g p))) => Data ((f :.: g) p) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Data Methodsgfoldl :: (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.Internal.Generics Associated Types
| |||||
| 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.Internal.Generics Methodscompare :: (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.Internal.Generics | |||||
| type Rep ((f :.: g) p) Source | Since: base-4.7.0.0 |
||||
Defined in GHC.Internal.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.Internal.Generics Associated Types
| |||||
| Generic1 (URec Char :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (URec Double :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (URec Float :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (URec Int :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (URec Word :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Eq1 (UAddr :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Eq1 (UChar :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Eq1 (UDouble :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Eq1 (UFloat :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Eq1 (UInt :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Eq1 (UWord :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Ord1 (UAddr :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| Ord1 (UChar :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| Ord1 (UDouble :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| Ord1 (UFloat :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| Ord1 (UInt :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| Ord1 (UWord :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| Show1 (UAddr :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Show1 (UChar :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Show1 (UDouble :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Show1 (UFloat :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Show1 (UInt :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Show1 (UWord :: Type -> Type) Source | Since: base-4.21.0.0 |
||||
| Foldable (UAddr :: Type -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Foldable Methodsfold :: 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 GHC.Internal.Data.Foldable Methodsfold :: 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 GHC.Internal.Data.Foldable Methodsfold :: 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 GHC.Internal.Data.Foldable Methodsfold :: 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 GHC.Internal.Data.Foldable Methodsfold :: 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 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 GHC.Internal.Data.Foldable Methodsfold :: 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 |
||||
Defined in GHC.Internal.Data.Traversable | |||||
| Traversable (UChar :: Type -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Traversable | |||||
| Traversable (UDouble :: Type -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Traversable | |||||
| Traversable (UFloat :: Type -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Traversable | |||||
| Traversable (UInt :: Type -> Type) Source | Since: base-4.9.0.0 |
||||
| Traversable (UWord :: Type -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Traversable | |||||
| 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 |
||||
| Show (UAddr p) Source | Since: base-4.21.0.0 |
||||
| Generic (URec (Ptr ()) p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (URec Char p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (URec Double p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (URec Float p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (URec Int p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (URec Word p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| 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.Internal.Generics Methodscompare :: 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.Internal.Generics Methodscompare :: 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.Internal.Generics Methodscompare :: 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.Internal.Generics Methodscompare :: 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 | |||||
| Ord (URec Int p) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodscompare :: 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.Internal.Generics Methodscompare :: 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.Internal.Generics | |||||
| type Rep1 (URec Char :: k -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type Rep1 (URec Double :: k -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type Rep1 (URec Float :: k -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type Rep1 (URec Int :: k -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type Rep1 (URec Word :: k -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type Rep (URec (Ptr ()) p) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type Rep (URec Char p) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type Rep (URec Double p) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type Rep (URec Float p) Source | |||||
Defined in GHC.Internal.Generics | |||||
| type Rep (URec Int p) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type Rep (URec Word p) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
type UAddr = URec (Ptr ()) :: k -> Type Source
Since: base-4.9.0.0
type UChar = URec Char :: k -> Type Source
Since: base-4.9.0.0
type UDouble = URec Double :: k -> Type Source
Since: base-4.9.0.0
type UFloat = URec Float :: k -> Type Source
Since: base-4.9.0.0
type UInt = URec Int :: k -> Type Source
Since: base-4.9.0.0
type UWord = URec Word :: k -> Type Source
Since: base-4.9.0.0
Synonyms for convenience
type Rec0 = K1 R :: Type -> k -> Type Source
Type synonym for encoding recursion (of kind Type)
Tag for K1: recursion (of kind Type)
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
Tag for M1: datatype
Tag for M1: constructor
Tag for M1: record selector
Meta-information
class Datatype (d :: k) where Source
Class for datatypes that represent datatypes
Minimal complete definition
Methods
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.Internal.Generics MethodsdatatypeName :: 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
Minimal complete definition
Methods
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.Internal.Generics | |
class Selector (s :: k) where Source
Class for datatypes that represent records
Methods
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.Internal.Generics MethodsselName :: 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.
Constructors
| Prefix | |
| Infix Associativity Int |
Instances
| Data Fixity Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Data Methodsgfoldl :: (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.Internal.Generics Associated Types
| |||||
| 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.Internal.Generics | |||||
| type Rep Fixity Source | Since: base-4.7.0.0 |
||||
Defined in GHC.Internal.Generics type Rep Fixity = D1 ('MetaData "Fixity" "GHC.Internal.Generics" "ghc-internal" '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
Constructors
| PrefixI | |
| InfixI Associativity Nat |
Instances
| SingKind FixityI | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| SingI 'PrefixI | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| (SingI a, KnownNat n) => SingI ('InfixI a n :: FixityI) | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics | |||||
| type DemoteRep FixityI Source | |||||
Defined in GHC.Internal.Generics | |||||
| data Sing (a :: FixityI) Source | |||||
Defined in GHC.Internal.Generics | |||||
data Associativity Source
Datatype to represent the associativity of a constructor
Constructors
| LeftAssociative | |
| RightAssociative | |
| NotAssociative |
Instances
Get the precedence of a fixity value.
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
Constructors
| NoSourceUnpackedness | |
| SourceNoUnpack | |
| SourceUnpack |
Instances
| Data SourceUnpackedness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Data Methodsgfoldl :: (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.Internal.Generics | |||||
| Enum SourceUnpackedness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodssucc :: 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.Internal.Generics Associated Types
Methodsfrom :: SourceUnpackedness -> Rep SourceUnpackedness x Source to :: Rep SourceUnpackedness x -> SourceUnpackedness Source | |||||
| SingKind SourceUnpackedness | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Associated Types
MethodsfromSing :: forall (a :: SourceUnpackedness). Sing a -> DemoteRep SourceUnpackedness | |||||
| Ix SourceUnpackedness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodsrange :: (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.Internal.Generics MethodsreadsPrec :: Int -> ReadS SourceUnpackedness Source readList :: ReadS [SourceUnpackedness] Source | |||||
| Show SourceUnpackedness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics MethodsshowsPrec :: Int -> SourceUnpackedness -> ShowS Source show :: SourceUnpackedness -> String Source showList :: [SourceUnpackedness] -> ShowS Source | |||||
| Eq SourceUnpackedness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methods(==) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source (/=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source | |||||
| Ord SourceUnpackedness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodscompare :: 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 | |||||
| SingI 'NoSourceUnpackedness | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodssing :: Sing 'NoSourceUnpackedness | |||||
| SingI 'SourceNoUnpack | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodssing :: Sing 'SourceNoUnpack | |||||
| SingI 'SourceUnpack | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodssing :: Sing 'SourceUnpack | |||||
| type DemoteRep SourceUnpackedness Source | |||||
Defined in GHC.Internal.Generics type DemoteRep SourceUnpackedness = SourceUnpackedness
| |||||
| type Rep SourceUnpackedness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics type Rep SourceUnpackedness = D1 ('MetaData "SourceUnpackedness" "GHC.Internal.Generics" "ghc-internal" '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 Sing (a :: SourceUnpackedness) Source | |||||
Defined in GHC.Internal.Generics data Sing (a :: SourceUnpackedness) where
| |||||
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
Constructors
| NoSourceStrictness | |
| SourceLazy | |
| SourceStrict |
Instances
| Data SourceStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Data Methodsgfoldl :: (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.Internal.Generics | |||||
| Enum SourceStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodssucc :: 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.Internal.Generics Associated Types
Methodsfrom :: SourceStrictness -> Rep SourceStrictness x Source to :: Rep SourceStrictness x -> SourceStrictness Source | |||||
| SingKind SourceStrictness | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Associated Types
MethodsfromSing :: forall (a :: SourceStrictness). Sing a -> DemoteRep SourceStrictness | |||||
| Ix SourceStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodsrange :: (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.Internal.Generics MethodsreadsPrec :: Int -> ReadS SourceStrictness Source readList :: ReadS [SourceStrictness] Source | |||||
| Show SourceStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics MethodsshowsPrec :: Int -> SourceStrictness -> ShowS Source show :: SourceStrictness -> String Source showList :: [SourceStrictness] -> ShowS Source | |||||
| Eq SourceStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methods(==) :: SourceStrictness -> SourceStrictness -> Bool Source (/=) :: SourceStrictness -> SourceStrictness -> Bool Source | |||||
| Ord SourceStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodscompare :: 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 | |||||
| SingI 'NoSourceStrictness | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodssing :: Sing 'NoSourceStrictness | |||||
| SingI 'SourceLazy | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodssing :: Sing 'SourceLazy | |||||
| SingI 'SourceStrict | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodssing :: Sing 'SourceStrict | |||||
| type DemoteRep SourceStrictness Source | |||||
Defined in GHC.Internal.Generics type DemoteRep SourceStrictness = SourceStrictness
| |||||
| type Rep SourceStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics type Rep SourceStrictness = D1 ('MetaData "SourceStrictness" "GHC.Internal.Generics" "ghc-internal" '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 Sing (a :: SourceStrictness) Source | |||||
Defined in GHC.Internal.Generics data Sing (a :: SourceStrictness) where
| |||||
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
ExampleConstructorwill haveDecidedStrict,DecidedStrict, andDecidedLazy, respectively. - If compiled with
-XStrictDataenabled, then the fields will haveDecidedStrict,DecidedStrict, andDecidedStrict, respectively. - If compiled with
-O2enabled, then the fields will haveDecidedUnpack,DecidedStrict, andDecidedLazy, respectively.
Since: base-4.9.0.0
Constructors
| DecidedLazy | |
| DecidedStrict | |
| DecidedUnpack |
Instances
| Data DecidedStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Data Methodsgfoldl :: (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.Internal.Generics | |||||
| Enum DecidedStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodssucc :: 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.Internal.Generics Associated Types
Methodsfrom :: DecidedStrictness -> Rep DecidedStrictness x Source to :: Rep DecidedStrictness x -> DecidedStrictness Source | |||||
| SingKind DecidedStrictness | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Associated Types
MethodsfromSing :: forall (a :: DecidedStrictness). Sing a -> DemoteRep DecidedStrictness | |||||
| Ix DecidedStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodsrange :: (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.Internal.Generics MethodsreadsPrec :: Int -> ReadS DecidedStrictness Source readList :: ReadS [DecidedStrictness] Source | |||||
| Show DecidedStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics MethodsshowsPrec :: Int -> DecidedStrictness -> ShowS Source show :: DecidedStrictness -> String Source showList :: [DecidedStrictness] -> ShowS Source | |||||
| Eq DecidedStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methods(==) :: DecidedStrictness -> DecidedStrictness -> Bool Source (/=) :: DecidedStrictness -> DecidedStrictness -> Bool Source | |||||
| Ord DecidedStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodscompare :: 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 | |||||
| SingI 'DecidedLazy | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodssing :: Sing 'DecidedLazy | |||||
| SingI 'DecidedStrict | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodssing :: Sing 'DecidedStrict | |||||
| SingI 'DecidedUnpack | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics Methodssing :: Sing 'DecidedUnpack | |||||
| type DemoteRep DecidedStrictness Source | |||||
Defined in GHC.Internal.Generics type DemoteRep DecidedStrictness = DecidedStrictness
| |||||
| type Rep DecidedStrictness Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Generics type Rep DecidedStrictness = D1 ('MetaData "DecidedStrictness" "GHC.Internal.Generics" "ghc-internal" '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))) | |||||
| data Sing (a :: DecidedStrictness) Source | |||||
Defined in GHC.Internal.Generics data Sing (a :: DecidedStrictness) where
| |||||
Datatype to represent metadata associated with a datatype (MetaData), constructor (MetaCons), or field selector (MetaSel).
- In
MetaData n m p nt,nis the datatype's name,mis the module in which the datatype is defined,pis the package in which the datatype is defined, andntis'Trueif the datatype is anewtype. - In
MetaCons n f s,nis the constructor's name,fis its fixity, andsis'Trueif the constructor contains record selectors. - In
MetaSel mn su ss ds, if the field uses record syntax, thenmnisJustthe record name. Otherwise,mnisNothing.suandssare the field's unpackedness and strictness annotations, anddsis the strictness that GHC infers for the field.
Since: base-4.9.0.0
Constructors
| 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.Internal.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.Internal.Generics MethodsdatatypeName :: 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.Internal.Generics MethodsselName :: 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
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
Methods
Convert from the datatype to its representation
Convert from the representation to the datatype
Instances
| Generic Void Source | |||||
| Generic ByteOrder Source | |||||
Defined in GHC.Internal.ByteOrder | |||||
| Generic ClosureType Source | |||||
Defined in GHC.Internal.ClosureTypes Associated Types
Methodsfrom :: ClosureType -> Rep ClosureType x Source to :: Rep ClosureType x -> ClosureType Source | |||||
| Generic All Source | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Generic Any Source | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Generic Version Source | |||||
Defined in GHC.Internal.Data.Version Associated Types
| |||||
| Generic Fingerprint Source | |||||
Defined in GHC.Internal.Generics Associated Types
Methodsfrom :: Fingerprint -> Rep Fingerprint x Source to :: Rep Fingerprint x -> Fingerprint Source | |||||
| Generic ForeignSrcLang Source | |||||
Defined in GHC.Internal.ForeignSrcLang Associated Types
Methodsfrom :: ForeignSrcLang -> Rep ForeignSrcLang x Source to :: Rep ForeignSrcLang x -> ForeignSrcLang Source | |||||
| Generic Associativity Source | |||||
Defined in GHC.Internal.Generics Associated Types
Methodsfrom :: Associativity -> Rep Associativity x Source to :: Rep Associativity x -> Associativity Source | |||||
| Generic DecidedStrictness Source | |||||
Defined in GHC.Internal.Generics Associated Types
Methodsfrom :: DecidedStrictness -> Rep DecidedStrictness x Source to :: Rep DecidedStrictness x -> DecidedStrictness Source | |||||
| Generic Fixity Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic SourceStrictness Source | |||||
Defined in GHC.Internal.Generics Associated Types
Methodsfrom :: SourceStrictness -> Rep SourceStrictness x Source to :: Rep SourceStrictness x -> SourceStrictness Source | |||||
| Generic SourceUnpackedness Source | |||||
Defined in GHC.Internal.Generics Associated Types
Methodsfrom :: SourceUnpackedness -> Rep SourceUnpackedness x Source to :: Rep SourceUnpackedness x -> SourceUnpackedness Source | |||||
| Generic ExitCode Source | |||||
Defined in GHC.Internal.IO.Exception Associated Types
| |||||
| Generic Extension Source | |||||
Defined in GHC.Internal.LanguageExtensions Associated Types
| |||||
| Generic CCFlags Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
| Generic ConcFlags Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
| Generic DebugFlags Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
| Generic DoCostCentres Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
Methodsfrom :: DoCostCentres -> Rep DoCostCentres x Source to :: Rep DoCostCentres x -> DoCostCentres Source | |||||
| Generic DoHeapProfile Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
Methodsfrom :: DoHeapProfile -> Rep DoHeapProfile x Source to :: Rep DoHeapProfile x -> DoHeapProfile Source | |||||
| Generic DoTrace Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
| Generic GCFlags Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
| Generic GiveGCStats Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
Methodsfrom :: GiveGCStats -> Rep GiveGCStats x Source to :: Rep GiveGCStats x -> GiveGCStats Source | |||||
| Generic HpcFlags Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
| Generic MiscFlags Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
| Generic ParFlags Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
| Generic ProfFlags Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
| Generic RTSFlags Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
| Generic TickyFlags Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
| Generic TraceFlags Source | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
| Generic SrcLoc Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic GCDetails Source | |||||
Defined in GHC.Internal.Stats Associated Types
| |||||
| Generic RTSStats Source | |||||
Defined in GHC.Internal.Stats Associated Types
| |||||
| Generic AnnLookup Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic AnnTarget Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Bang Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic BndrVis Source | |||||
Defined in GHC.Internal.TH.Syntax | |||||
| Generic Body Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Bytes Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Callconv Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Clause Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Con Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Dec Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic DecidedStrictness Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
Methodsfrom :: DecidedStrictness -> Rep DecidedStrictness x Source to :: Rep DecidedStrictness x -> DecidedStrictness Source | |||||
| Generic DerivClause Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
Methodsfrom :: DerivClause -> Rep DerivClause x Source to :: Rep DerivClause x -> DerivClause Source | |||||
| Generic DerivStrategy Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
Methodsfrom :: DerivStrategy -> Rep DerivStrategy x Source to :: Rep DerivStrategy x -> DerivStrategy Source | |||||
| Generic DocLoc Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Exp Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic FamilyResultSig Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
Methodsfrom :: FamilyResultSig -> Rep FamilyResultSig x Source to :: Rep FamilyResultSig x -> FamilyResultSig Source | |||||
| Generic Fixity Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic FixityDirection Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
Methodsfrom :: FixityDirection -> Rep FixityDirection x Source to :: Rep FixityDirection x -> FixityDirection Source | |||||
| Generic Foreign Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic FunDep Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Guard Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Info Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic InjectivityAnn Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
Methodsfrom :: InjectivityAnn -> Rep InjectivityAnn x Source to :: Rep InjectivityAnn x -> InjectivityAnn Source | |||||
| Generic Inline Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Lit Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Loc Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Match Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic ModName Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Module Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic ModuleInfo Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Name Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic NameFlavour Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
Methodsfrom :: NameFlavour -> Rep NameFlavour x Source to :: Rep NameFlavour x -> NameFlavour Source | |||||
| Generic NameSpace Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic NamespaceSpecifier Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
Methodsfrom :: NamespaceSpecifier -> Rep NamespaceSpecifier x Source to :: Rep NamespaceSpecifier x -> NamespaceSpecifier Source | |||||
| Generic OccName Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Overlap Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Pat Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic PatSynArgs Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic PatSynDir Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Phases Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic PkgName Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Pragma Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Range Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Role Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic RuleBndr Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic RuleMatch Source | |||||
Defined in GHC.Internal.TH.Syntax | |||||
| Generic Safety Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic SourceStrictness Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
Methodsfrom :: SourceStrictness -> Rep SourceStrictness x Source to :: Rep SourceStrictness x -> SourceStrictness Source | |||||
| Generic SourceUnpackedness Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
Methodsfrom :: SourceUnpackedness -> Rep SourceUnpackedness x Source to :: Rep SourceUnpackedness x -> SourceUnpackedness Source | |||||
| Generic Specificity Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
Methodsfrom :: Specificity -> Rep Specificity x Source to :: Rep Specificity x -> Specificity Source | |||||
| Generic Stmt Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic TyLit Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic TySynEqn Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic Type Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic TypeFamilyHead Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
Methodsfrom :: TypeFamilyHead -> Rep TypeFamilyHead x Source to :: Rep TypeFamilyHead x -> TypeFamilyHead Source | |||||
| Generic GeneralCategory Source | |||||
Defined in GHC.Internal.Generics Associated Types
Methodsfrom :: GeneralCategory -> Rep GeneralCategory x Source to :: Rep GeneralCategory x -> GeneralCategory Source | |||||
| Generic Ordering Source | |||||
Defined in GHC.Internal.Generics | |||||
| Generic () Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic Bool Source | |||||
Defined in GHC.Internal.Generics | |||||
| Generic (Complex a) Source | |||||
Defined in Data.Complex Associated Types
| |||||
| Generic (First a) Source | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic (Last a) Source | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic (Max a) Source | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic (Min a) Source | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic (WrappedMonoid m) Source | |||||
Defined in Data.Semigroup Associated Types
Methodsfrom :: WrappedMonoid m -> Rep (WrappedMonoid m) x Source to :: Rep (WrappedMonoid m) x -> WrappedMonoid m Source | |||||
| Generic (NonEmpty a) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (Identity a) Source | |||||
Defined in GHC.Internal.Data.Functor.Identity Associated Types
| |||||
| Generic (First a) Source | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
| Generic (Last a) Source | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
| Generic (Down a) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (Dual a) Source | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Generic (Endo a) Source | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Generic (Product a) Source | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Generic (Sum a) Source | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Generic (ZipList a) Source | |||||
Defined in GHC.Internal.Functor.ZipList Associated Types
| |||||
| Generic (Par1 p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (TyVarBndr flag) Source | |||||
Defined in GHC.Internal.TH.Syntax Associated Types
| |||||
| Generic (Maybe a) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (Solo a) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic [a] Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (WrappedMonad m a) Source | |||||
Defined in Control.Applicative Associated Types
Methodsfrom :: WrappedMonad m a -> Rep (WrappedMonad m a) x Source to :: Rep (WrappedMonad m a) x -> WrappedMonad m a Source | |||||
| Generic (Arg a b) Source | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic (Either a b) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (Proxy t) Source | |||||
Defined in GHC.Internal.Generics | |||||
| Generic (U1 p) Source | |||||
Defined in GHC.Internal.Generics | |||||
| Generic (V1 p) Source | |||||
Defined in GHC.Internal.Generics | |||||
| Generic (a, b) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (WrappedArrow a b c) Source | |||||
Defined in Control.Applicative Associated Types
Methodsfrom :: 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 GHC.Internal.Control.Arrow Associated Types
| |||||
| Generic (Const a b) Source | |||||
Defined in GHC.Internal.Data.Functor.Const Associated Types
| |||||
| Generic (Ap f a) Source | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
| Generic (Alt f a) Source | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Generic (Rec1 f p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (URec (Ptr ()) p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (URec Char p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (URec Double p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (URec Float p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (URec Int p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (URec Word p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (Product f g a) Source | |||||
Defined in Data.Functor.Product Associated Types
| |||||
| Generic (Sum f g a) Source | |||||
Defined in Data.Functor.Sum Associated Types
| |||||
| Generic ((f :*: g) p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic ((f :+: g) p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (K1 i c p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c, d) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (Compose f g a) Source | |||||
Defined in Data.Functor.Compose Associated Types
| |||||
| Generic ((f :.: g) p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (M1 i c f p) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c, d, e) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i, j) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i, j, k) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i, j, k, l) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
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
Methods
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 Complex Source | |||||
Defined in Data.Complex Associated Types
| |||||
| Generic1 First Source | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic1 Last Source | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic1 Max Source | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic1 Min Source | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic1 WrappedMonoid Source | |||||
Defined in Data.Semigroup Associated Types
Methodsfrom1 :: WrappedMonoid a -> Rep1 WrappedMonoid a Source to1 :: Rep1 WrappedMonoid a -> WrappedMonoid a Source | |||||
| Generic1 NonEmpty Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 Identity Source | |||||
Defined in GHC.Internal.Data.Functor.Identity Associated Types
| |||||
| Generic1 First Source | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
| Generic1 Last Source | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
| Generic1 Down Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 Dual Source | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Generic1 Product Source | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Generic1 Sum Source | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Generic1 ZipList Source | |||||
Defined in GHC.Internal.Functor.ZipList Associated Types
| |||||
| Generic1 Par1 Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 Maybe Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 Solo Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 [] Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (WrappedMonad m :: Type -> Type) Source | |||||
Defined in Control.Applicative Associated Types
Methodsfrom1 :: WrappedMonad m a -> Rep1 (WrappedMonad m) a Source to1 :: Rep1 (WrappedMonad m) a -> WrappedMonad m a Source | |||||
| Generic1 (Arg a :: Type -> Type) Source | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic1 (Either a :: Type -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 ((,) a :: Type -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (Proxy :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics | |||||
| Generic1 (U1 :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics | |||||
| Generic1 (V1 :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics | |||||
| Generic1 (WrappedArrow a b :: Type -> Type) Source | |||||
Defined in Control.Applicative Associated Types
Methodsfrom1 :: 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 GHC.Internal.Control.Arrow Associated Types
| |||||
| Generic1 ((,,) a b :: Type -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (Const a :: k -> Type) Source | |||||
Defined in GHC.Internal.Data.Functor.Const Associated Types
| |||||
| Generic1 (Ap f :: k -> Type) Source | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
| Generic1 (Alt f :: k -> Type) Source | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Generic1 (Rec1 f :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (URec (Ptr ()) :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (URec Char :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (URec Double :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (URec Float :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (URec Int :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (URec Word :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 ((,,,) a b c :: Type -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (Product f g :: k -> Type) Source | |||||
Defined in Data.Functor.Product Associated Types
| |||||
| Generic1 (Sum f g :: k -> Type) Source | |||||
Defined in Data.Functor.Sum Associated Types
| |||||
| Generic1 (f :*: g :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (f :+: g :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (K1 i c :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 ((,,,,) a b c d :: Type -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Functor f => Generic1 (Compose f g :: k -> Type) Source | |||||
Defined in Data.Functor.Compose Associated Types
| |||||
| Functor f => Generic1 (f :.: g :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 (M1 i c f :: k -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 ((,,,,,) a b c d e :: Type -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 ((,,,,,,) a b c d e f :: Type -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
| Generic1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source | |||||
Defined in GHC.Internal.Generics Associated Types
Methodsfrom1 :: (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.Internal.Generics Associated Types
Methodsfrom1 :: (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.Internal.Generics Associated Types
Methodsfrom1 :: (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.Internal.Generics Associated Types
Methodsfrom1 :: (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.Internal.Generics Associated Types
Methodsfrom1 :: (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.Internal.Generics Associated Types
Methodsfrom1 :: (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.Internal.Generics Associated Types
Methodsfrom1 :: (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 Generically A using -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
Constructors
| Generically a |
Instances
| (Generic a, Monoid (Rep a ())) => Monoid (Generically a) Source | Since: base-4.17.0.0 |
Defined in GHC.Internal.Generics Methodsmempty :: 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.Internal.Generics Methods(<>) :: 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 Generically1 F using -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
Constructors
| 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 MethodsliftEq :: (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 MethodsliftCompare :: (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.Internal.Generics Methodsempty :: 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.Internal.Generics Methodspure :: 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.Internal.Generics Methodsfmap :: (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.Internal.Generics Methods(==) :: 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.Internal.Generics Methodscompare :: 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 | |
© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/9.12.1/docs/libraries/base-4.21.0.0-8e62/GHC-Generics.html