Safe Haskell | None |
---|---|
Language | Haskell2010 |
Dhall.Marshal.Encode
Description
Please read the Dhall.Tutorial module, which contains a tutorial explaining how to use the language, the compiler, and this library
Synopsis
- data Encoder a = Encoder {}
- class ToDhall a where
- injectWith :: InputNormalizer -> Encoder a
- type Inject = ToDhall
- inject :: ToDhall a => Encoder a
- newtype RecordEncoder a = RecordEncoder (Map Text (Encoder a))
- recordEncoder :: RecordEncoder a -> Encoder a
- encodeField :: ToDhall a => Text -> RecordEncoder a
- encodeFieldWith :: Text -> Encoder a -> RecordEncoder a
- newtype UnionEncoder a = UnionEncoder (Product (Const (Map Text (Expr Src Void)) :: Type -> Type) (Op (Text, Expr Src Void)) a)
- unionEncoder :: UnionEncoder a -> Encoder a
- encodeConstructor :: ToDhall a => Text -> UnionEncoder a
- encodeConstructorWith :: Text -> Encoder a -> UnionEncoder a
- (>|<) :: UnionEncoder a -> UnionEncoder b -> UnionEncoder (Either a b)
- class GenericToDhall (f :: Type -> Type) where
- genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (f a))
- genericToDhall :: (Generic a, GenericToDhall (Rep a)) => Encoder a
- genericToDhallWith :: (Generic a, GenericToDhall (Rep a)) => InterpretOptions -> Encoder a
- genericToDhallWithInputNormalizer :: (Generic a, GenericToDhall (Rep a)) => InterpretOptions -> InputNormalizer -> Encoder a
- data InterpretOptions = InterpretOptions {}
- data SingletonConstructors
- defaultInterpretOptions :: InterpretOptions
- newtype InputNormalizer = InputNormalizer {}
- defaultInputNormalizer :: InputNormalizer
- data Result (f :: Type -> Type)
- (>$<) :: Contravariant f => (a -> b) -> f b -> f a
- (>*<) :: Divisible f => f a -> f b -> f (a, b)
- data Natural
- data Seq a
- data Text
- data Vector a
- class Generic a
General
An (Encoder a)
represents a way to marshal a value of type 'a'
from
Haskell into Dhall.
Constructors
Encoder | |
class ToDhall a where Source #
This class is used by FromDhall
instance for functions:
instance (ToDhall a, FromDhall b) => FromDhall (a -> b)
You can convert Dhall functions with "simple" inputs (i.e. instances of this class) into Haskell functions. This works by:
- Marshaling the input to the Haskell function into a Dhall expression (i.e.
x :: Expr Src Void
) - Applying the Dhall function (i.e.
f :: Expr Src Void
) to the Dhall input (i.e.App f x
) - Normalizing the syntax tree (i.e.
normalize (App f x)
) - Marshaling the resulting Dhall expression back into a Haskell value
This class auto-generates a default implementation for types that
implement Generic
. This does not auto-generate an instance for recursive
types.
The default instance can be tweaked using genericToDhallWith
/genericToDhallWithInputNormalizer
and custom InterpretOptions
, or using
DerivingVia
and Codec
from Dhall.Deriving.
Minimal complete definition
Nothing
Methods
injectWith :: InputNormalizer -> Encoder a Source #
default injectWith :: (Generic a, GenericToDhall (Rep a)) => InputNormalizer -> Encoder a Source #
Instances
inject :: ToDhall a => Encoder a Source #
Use the default input normalizer for injecting a value.
inject = injectWith defaultInputNormalizer
Building encoders
Records
newtype RecordEncoder a Source #
The RecordEncoder
divisible (contravariant) functor allows you to build
an Encoder
for a Dhall record.
For example, let's take the following Haskell data type:
>>>
:{
data Project = Project { projectName :: Text , projectDescription :: Text , projectStars :: Natural } :}
And assume that we have the following Dhall record that we would like to
parse as a Project
:
{ name = "dhall-haskell" , description = "A configuration language guaranteed to terminate" , stars = 289 }
Our encoder has type Encoder
Project
, but we can't build that out of any
smaller encoders, as Encoder
s cannot be combined (they are only Contravariant
s).
However, we can use an RecordEncoder
to build an Encoder
for Project
:
>>>
:{
injectProject :: Encoder Project injectProject = recordEncoder ( adapt >$< encodeFieldWith "name" inject >*< encodeFieldWith "description" inject >*< encodeFieldWith "stars" inject ) where adapt (Project{..}) = (projectName, (projectDescription, projectStars)) :}
Or, since we are simply using the ToDhall
instance to inject each field, we could write
>>>
:{
injectProject :: Encoder Project injectProject = recordEncoder ( adapt >$< encodeField "name" >*< encodeField "description" >*< encodeField "stars" ) where adapt (Project{..}) = (projectName, (projectDescription, projectStars)) :}
Constructors
RecordEncoder (Map Text (Encoder a)) |
Instances
Contravariant RecordEncoder Source # | |
Defined in Dhall.Marshal.Encode Methods contramap :: (a' -> a) -> RecordEncoder a -> RecordEncoder a' # (>$) :: b -> RecordEncoder b -> RecordEncoder a # | |
Divisible RecordEncoder Source # | |
Defined in Dhall.Marshal.Encode Methods divide :: (a -> (b, c)) -> RecordEncoder b -> RecordEncoder c -> RecordEncoder a # conquer :: RecordEncoder a # |
recordEncoder :: RecordEncoder a -> Encoder a Source #
Convert a RecordEncoder
into the equivalent Encoder
.
encodeField :: ToDhall a => Text -> RecordEncoder a Source #
Specify how to encode one field of a record using the default ToDhall
instance for that type.
encodeFieldWith :: Text -> Encoder a -> RecordEncoder a Source #
Specify how to encode one field of a record by supplying an explicit
Encoder
for that field.
Unions
newtype UnionEncoder a Source #
UnionEncoder
allows you to build an Encoder
for a Dhall record.
For example, let's take the following Haskell data type:
>>>
:{
data Status = Queued Natural | Result Text | Errored Text :}
And assume that we have the following Dhall union that we would like to
parse as a Status
:
< Result : Text | Queued : Natural | Errored : Text >.Result "Finish successfully"
Our encoder has type Encoder
Status
, but we can't build that out of any
smaller encoders, as Encoder
s cannot be combined.
However, we can use an UnionEncoder
to build an Encoder
for Status
:
>>>
:{
injectStatus :: Encoder Status injectStatus = adapt >$< unionEncoder ( encodeConstructorWith "Queued" inject >|< encodeConstructorWith "Result" inject >|< encodeConstructorWith "Errored" inject ) where adapt (Queued n) = Left n adapt (Result t) = Right (Left t) adapt (Errored e) = Right (Right e) :}
Or, since we are simply using the ToDhall
instance to inject each branch, we could write
>>>
:{
injectStatus :: Encoder Status injectStatus = adapt >$< unionEncoder ( encodeConstructor "Queued" >|< encodeConstructor "Result" >|< encodeConstructor "Errored" ) where adapt (Queued n) = Left n adapt (Result t) = Right (Left t) adapt (Errored e) = Right (Right e) :}
Constructors
UnionEncoder (Product (Const (Map Text (Expr Src Void)) :: Type -> Type) (Op (Text, Expr Src Void)) a) |
Instances
Contravariant UnionEncoder Source # | |
Defined in Dhall.Marshal.Encode Methods contramap :: (a' -> a) -> UnionEncoder a -> UnionEncoder a' # (>$) :: b -> UnionEncoder b -> UnionEncoder a # |
unionEncoder :: UnionEncoder a -> Encoder a Source #
Convert a UnionEncoder
into the equivalent Encoder
.
encodeConstructor :: ToDhall a => Text -> UnionEncoder a Source #
Specify how to encode an alternative by using the default ToDhall
instance
for that type.
encodeConstructorWith :: Text -> Encoder a -> UnionEncoder a Source #
Specify how to encode an alternative by providing an explicit Encoder
for that alternative.
(>|<) :: UnionEncoder a -> UnionEncoder b -> UnionEncoder (Either a b) infixr 5 Source #
Combines two UnionEncoder
values. See UnionEncoder
for usage
notes.
Ideally, this matches chosen
;
however, this allows UnionEncoder
to not need a Divisible
instance
itself (since no instance is possible).
Generic encoding
class GenericToDhall (f :: Type -> Type) where Source #
This is the underlying class that powers the FromDhall
class's support
for automatically deriving a generic implementation.
Methods
genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (f a)) Source #
Instances
genericToDhall :: (Generic a, GenericToDhall (Rep a)) => Encoder a Source #
Use the default options for injecting a value, whose structure is determined generically.
This can be used when you want to use ToDhall
on types that you don't
want to define orphan instances for.
genericToDhallWith :: (Generic a, GenericToDhall (Rep a)) => InterpretOptions -> Encoder a Source #
Use custom options for injecting a value, whose structure is determined generically.
This can be used when you want to use ToDhall
on types that you don't
want to define orphan instances for.
genericToDhallWithInputNormalizer :: (Generic a, GenericToDhall (Rep a)) => InterpretOptions -> InputNormalizer -> Encoder a Source #
genericToDhallWithInputNormalizer
is like genericToDhallWith
, but
instead of using the defaultInputNormalizer
it expects an custom
InputNormalizer
.
data InterpretOptions Source #
Use these options to tweak how Dhall derives a generic implementation of
FromDhall
.
Constructors
InterpretOptions | |
Fields
|
data SingletonConstructors Source #
This type specifies how to model a Haskell constructor with 1 field in Dhall
For example, consider the following Haskell datatype definition:
data Example = Foo { x :: Double } | Bar Double
Depending on which option you pick, the corresponding Dhall type could be:
< Foo : Double | Bar : Double > -- Bare
< Foo : { x : Double } | Bar : { _1 : Double } > -- Wrapped
< Foo : { x : Double } | Bar : Double > -- Smart
Constructors
Bare | Never wrap the field in a record |
Wrapped | Always wrap the field in a record |
Smart | Only fields in a record if they are named |
Instances
ToSingletonConstructors a => ModifyOptions (SetSingletonConstructors a :: Type) Source # | |
Defined in Dhall.Deriving Methods modifyOptions :: InterpretOptions -> InterpretOptions Source # |
defaultInterpretOptions :: InterpretOptions Source #
Default interpret options for generics-based instances, which you can tweak or override, like this:
genericAutoWith (defaultInterpretOptions { fieldModifier = Data.Text.Lazy.dropWhile (== '_') })
Miscellaneous
newtype InputNormalizer Source #
This is only used by the FromDhall
instance for
functions in order to normalize the function input before marshaling the
input into a Dhall expression.
Constructors
InputNormalizer | |
Fields |
defaultInputNormalizer :: InputNormalizer Source #
Default normalization-related settings (no custom normalization)
data Result (f :: Type -> Type) Source #
This type is exactly the same as Fix
except with a different
FromDhall
instance. This intermediate type
simplifies the implementation of the inner loop for the
FromDhall
instance for Fix
.
Instances
FromDhall (f (Result f)) => FromDhall (Result f) Source # | |
Defined in Dhall.Marshal.Decode | |
ToDhall (f (Result f)) => ToDhall (Result f) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Result f) Source # |
(>$<) :: Contravariant f => (a -> b) -> f b -> f a infixl 4 #
This is an infix alias for contramap
.
Re-exports
Natural number
Invariant: numbers <= 0xffffffffffffffff use the NS
constructor
Instances
FromJSON Natural | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
FromJSONKey Natural | |||||
Defined in Data.Aeson.Types.FromJSON Methods | |||||
ToJSON Natural | |||||
ToJSONKey Natural | |||||
Defined in Data.Aeson.Types.ToJSON | |||||
PrintfArg Natural | Since: base-4.8.0.0 | ||||
Defined in Text.Printf | |||||
Subtractive Natural | |||||
Defined in Basement.Numerical.Subtractive Associated Types
| |||||
NFData Natural | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
FromDhall Natural Source # | |||||
Defined in Dhall.Marshal.Decode | |||||
ToDhall Natural Source # | |||||
Defined in Dhall.Marshal.Encode Methods | |||||
Bits Natural | Since: base-4.8.0 | ||||
Defined in GHC.Internal.Bits Methods (.&.) :: Natural -> Natural -> Natural # (.|.) :: Natural -> Natural -> Natural # xor :: Natural -> Natural -> Natural # complement :: Natural -> Natural # shift :: Natural -> Int -> Natural # rotate :: Natural -> Int -> Natural # setBit :: Natural -> Int -> Natural # clearBit :: Natural -> Int -> Natural # complementBit :: Natural -> Int -> Natural # testBit :: Natural -> Int -> Bool # bitSizeMaybe :: Natural -> Maybe Int # shiftL :: Natural -> Int -> Natural # unsafeShiftL :: Natural -> Int -> Natural # shiftR :: Natural -> Int -> Natural # unsafeShiftR :: Natural -> Int -> Natural # rotateL :: Natural -> Int -> Natural # | |||||
Data Natural | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Natural -> c Natural # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Natural # toConstr :: Natural -> Constr # dataTypeOf :: Natural -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Natural) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Natural) # gmapT :: (forall b. Data b => b -> b) -> Natural -> Natural # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r # gmapQ :: (forall d. Data d => d -> u) -> Natural -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Natural -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Natural -> m Natural # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural # | |||||
Enum Natural | Since: base-4.8.0.0 | ||||
Num Natural | Note that Since: base-4.8.0.0 | ||||
Read Natural | Since: base-4.8.0.0 | ||||
Integral Natural | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Real | |||||
Real Natural | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Real Methods toRational :: Natural -> Rational # | |||||
Show Natural | Since: base-4.8.0.0 | ||||
Eq Natural | |||||
Ord Natural | |||||
Hashable Natural | |||||
Defined in Data.Hashable.Class | |||||
Pretty Natural | |||||
Defined in Prettyprinter.Internal | |||||
UniformRange Natural | |||||
Defined in System.Random.Internal | |||||
Serialise Natural | Since: serialise-0.2.0.0 | ||||
KnownNat n => HasResolution (n :: Nat) | For example, | ||||
Defined in Data.Fixed Methods resolution :: p n -> Integer # | |||||
TestCoercion SNat | Since: base-4.18.0.0 | ||||
Defined in GHC.Internal.TypeNats | |||||
TestEquality SNat | Since: base-4.18.0.0 | ||||
Defined in GHC.Internal.TypeNats | |||||
Lift Natural | |||||
type Difference Natural | |||||
Defined in Basement.Numerical.Subtractive | |||||
type Compare (a :: Natural) (b :: Natural) | |||||
Defined in GHC.Internal.Data.Type.Ord |
General-purpose finite sequences.
Instances
FromJSON1 Seq | |||||||||
ToJSON1 Seq | |||||||||
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> Seq a -> Value # liftToJSONList :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> [Seq a] -> Value # liftToEncoding :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> Seq a -> Encoding # liftToEncodingList :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> [Seq a] -> Encoding # liftOmitField :: (a -> Bool) -> Seq a -> Bool # | |||||||||
MonadZip Seq |
Since: containers-0.5.10.1 | ||||||||
Eq1 Seq | Since: containers-0.5.9 | ||||||||
Ord1 Seq | Since: containers-0.5.9 | ||||||||
Defined in Data.Sequence.Internal | |||||||||
Read1 Seq | Since: containers-0.5.9 | ||||||||
Defined in Data.Sequence.Internal | |||||||||
Show1 Seq | Since: containers-0.5.9 | ||||||||
UnzipWith Seq | |||||||||
Defined in Data.Sequence.Internal Methods unzipWith' :: (x -> (a, b)) -> Seq x -> (Seq a, Seq b) | |||||||||
Alternative Seq | Since: containers-0.5.4 | ||||||||
Applicative Seq | Since: containers-0.5.4 | ||||||||
Functor Seq | |||||||||
Monad Seq | |||||||||
MonadPlus Seq | |||||||||
MonadFix Seq | Since: containers-0.5.11 | ||||||||
Defined in Data.Sequence.Internal | |||||||||
Foldable Seq | |||||||||
Defined in Data.Sequence.Internal Methods fold :: Monoid m => Seq m -> m # foldMap :: Monoid m => (a -> m) -> Seq a -> m # foldMap' :: Monoid m => (a -> m) -> Seq a -> m # foldr :: (a -> b -> b) -> b -> Seq a -> b # foldr' :: (a -> b -> b) -> b -> Seq a -> b # foldl :: (b -> a -> b) -> b -> Seq a -> b # foldl' :: (b -> a -> b) -> b -> Seq a -> b # foldr1 :: (a -> a -> a) -> Seq a -> a # foldl1 :: (a -> a -> a) -> Seq a -> a # elem :: Eq a => a -> Seq a -> Bool # maximum :: Ord a => Seq a -> a # | |||||||||
Traversable Seq | |||||||||
Hashable1 Seq | Since: hashable-1.3.4.0 | ||||||||
Defined in Data.Hashable.Class | |||||||||
FoldableWithIndex Int Seq | |||||||||
FunctorWithIndex Int Seq | The position in the | ||||||||
TraversableWithIndex Int Seq | |||||||||
Lift a => Lift (Seq a :: Type) | Since: containers-0.6.6 | ||||||||
FromJSON a => FromJSON (Seq a) | |||||||||
Defined in Data.Aeson.Types.FromJSON | |||||||||
ToJSON a => ToJSON (Seq a) | |||||||||
NFData a => NFData (Seq a) | |||||||||
Defined in Data.Sequence.Internal | |||||||||
FromDhall a => FromDhall (Seq a) Source # | |||||||||
Defined in Dhall.Marshal.Decode | |||||||||
ToDhall a => ToDhall (Seq a) Source # | |||||||||
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Seq a) Source # | |||||||||
Monoid (Seq a) | |||||||||
Semigroup (Seq a) | Since: containers-0.5.7 | ||||||||
Data a => Data (Seq a) | |||||||||
Defined in Data.Sequence.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seq a -> c (Seq a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) # dataTypeOf :: Seq a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) # gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # | |||||||||
a ~ Char => IsString (Seq a) | Since: containers-0.5.7 | ||||||||
Defined in Data.Sequence.Internal Methods fromString :: String -> Seq a # | |||||||||
IsList (Seq a) | |||||||||
Read a => Read (Seq a) | |||||||||
Show a => Show (Seq a) | |||||||||
Eq a => Eq (Seq a) | |||||||||
Ord a => Ord (Seq a) | |||||||||
Hashable v => Hashable (Seq v) | Since: hashable-1.3.4.0 | ||||||||
Defined in Data.Hashable.Class | |||||||||
Ord a => Stream (Seq a) | Since: megaparsec-9.0.0 | ||||||||
Defined in Text.Megaparsec.Stream Associated Types
Methods tokenToChunk :: Proxy (Seq a) -> Token (Seq a) -> Tokens (Seq a) # tokensToChunk :: Proxy (Seq a) -> [Token (Seq a)] -> Tokens (Seq a) # chunkToTokens :: Proxy (Seq a) -> Tokens (Seq a) -> [Token (Seq a)] # chunkLength :: Proxy (Seq a) -> Tokens (Seq a) -> Int # chunkEmpty :: Proxy (Seq a) -> Tokens (Seq a) -> Bool # take1_ :: Seq a -> Maybe (Token (Seq a), Seq a) # takeN_ :: Int -> Seq a -> Maybe (Tokens (Seq a), Seq a) # takeWhile_ :: (Token (Seq a) -> Bool) -> Seq a -> (Tokens (Seq a), Seq a) # | |||||||||
Serialise a => Serialise (Seq a) | Since: serialise-0.2.0.0 | ||||||||
type Item (Seq a) | |||||||||
Defined in Data.Sequence.Internal | |||||||||
type Token (Seq a) | |||||||||
Defined in Text.Megaparsec.Stream | |||||||||
type Tokens (Seq a) | |||||||||
Defined in Text.Megaparsec.Stream |
A space efficient, packed, unboxed Unicode text type.
Instances
Instances
FromJSON1 Vector | |
Defined in Data.Aeson.Types.FromJSON | |
ToJSON1 Vector | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> Vector a -> Value # liftToJSONList :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> [Vector a] -> Value # liftToEncoding :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> Vector a -> Encoding # liftToEncodingList :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> [Vector a] -> Encoding # liftOmitField :: (a -> Bool) -> Vector a -> Bool # | |
MonadZip Vector | |
Eq1 Vector | |
Ord1 Vector | |
Defined in Data.Vector | |
Read1 Vector | |
Defined in Data.Vector | |
Show1 Vector | |
NFData1 Vector | |
Defined in Data.Vector | |
Alternative Vector | |
Applicative Vector | |
Functor Vector | |
Monad Vector | |
MonadPlus Vector | |
MonadFail Vector | |
Defined in Data.Vector | |
MonadFix Vector | |
Defined in Data.Vector | |
Foldable Vector | |
Defined in Data.Vector Methods fold :: Monoid m => Vector m -> m # foldMap :: Monoid m => (a -> m) -> Vector a -> m # foldMap' :: Monoid m => (a -> m) -> Vector a -> m # foldr :: (a -> b -> b) -> b -> Vector a -> b # foldr' :: (a -> b -> b) -> b -> Vector a -> b # foldl :: (b -> a -> b) -> b -> Vector a -> b # foldl' :: (b -> a -> b) -> b -> Vector a -> b # foldr1 :: (a -> a -> a) -> Vector a -> a # foldl1 :: (a -> a -> a) -> Vector a -> a # elem :: Eq a => a -> Vector a -> Bool # maximum :: Ord a => Vector a -> a # minimum :: Ord a => Vector a -> a # | |
Traversable Vector | |
Vector Vector a | |
Defined in Data.Vector Methods basicUnsafeFreeze :: Mutable Vector s a -> ST s (Vector a) basicUnsafeThaw :: Vector a -> ST s (Mutable Vector s a) basicLength :: Vector a -> Int basicUnsafeSlice :: Int -> Int -> Vector a -> Vector a basicUnsafeIndexM :: Vector a -> Int -> Box a basicUnsafeCopy :: Mutable Vector s a -> Vector a -> ST s () | |
FromJSON a => FromJSON (Vector a) | |
Defined in Data.Aeson.Types.FromJSON | |
ToJSON a => ToJSON (Vector a) | |
NFData a => NFData (Vector a) | |
Defined in Data.Vector | |
FromDhall a => FromDhall (Vector a) Source # | |
Defined in Dhall.Marshal.Decode | |
ToDhall a => ToDhall (Vector a) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Vector a) Source # | |
Monoid (Vector a) | |
Semigroup (Vector a) | |
Data a => Data (Vector a) | |
Defined in Data.Vector Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) # toConstr :: Vector a -> Constr # dataTypeOf :: Vector a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) # gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # | |
IsList (Vector a) | |
Read a => Read (Vector a) | |
Show a => Show (Vector a) | |
Eq a => Eq (Vector a) | |
Ord a => Ord (Vector a) | |
Defined in Data.Vector | |
Serialise a => Serialise (Vector a) | Since: serialise-0.2.0.0 |
type Mutable Vector | |
Defined in Data.Vector type Mutable Vector = MVector | |
type Item (Vector a) | |
Defined in Data.Vector |
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
Instances
Generic Value | |||||
Defined in Data.Aeson.Types.Internal Associated Types
| |||||
Generic ShortByteString | |||||
Defined in Data.ByteString.Short.Internal Associated Types
Methods from :: ShortByteString -> Rep ShortByteString x # to :: Rep ShortByteString x -> ShortByteString # | |||||
Generic SHA256Digest Source # | |||||
Defined in Dhall.Crypto Associated Types
| |||||
Generic FilesystemEntry Source # | |||||
Defined in Dhall.DirectoryTree.Types Associated Types
Methods from :: FilesystemEntry -> Rep FilesystemEntry x # to :: Rep FilesystemEntry x -> FilesystemEntry # | |||||
Generic Group Source # | |||||
Defined in Dhall.DirectoryTree.Types Associated Types
| |||||
Generic User Source # | |||||
Defined in Dhall.DirectoryTree.Types Associated Types
| |||||
Generic CharacterSet Source # | |||||
Defined in Dhall.Pretty.Internal Associated Types
| |||||
Generic Src Source # | |||||
Defined in Dhall.Src Associated Types
| |||||
Generic Const Source # | |||||
Defined in Dhall.Syntax.Const Associated Types
| |||||
Generic Directory Source # | |||||
Defined in Dhall.Syntax.Import Associated Types
| |||||
Generic File Source # | |||||
Defined in Dhall.Syntax.Import Associated Types
| |||||
Generic FilePrefix Source # | |||||
Defined in Dhall.Syntax.Import Associated Types
| |||||
Generic Import Source # | |||||
Defined in Dhall.Syntax.Import Associated Types
| |||||
Generic ImportHashed Source # | |||||
Defined in Dhall.Syntax.Import Associated Types
| |||||
Generic ImportMode Source # | |||||
Defined in Dhall.Syntax.Import Associated Types
| |||||
Generic ImportType Source # | |||||
Defined in Dhall.Syntax.Import Associated Types
| |||||
Generic Scheme Source # | |||||
Defined in Dhall.Syntax.Import | |||||
Generic URL Source # | |||||
Defined in Dhall.Syntax.Import Associated Types
| |||||
Generic DhallDouble Source # | |||||
Defined in Dhall.Syntax.Types Associated Types
| |||||
Generic PreferAnnotation Source # | |||||
Defined in Dhall.Syntax.Types Associated Types
Methods from :: PreferAnnotation -> Rep PreferAnnotation x # to :: Rep PreferAnnotation x -> PreferAnnotation # | |||||
Generic WithComponent Source # | |||||
Defined in Dhall.Syntax.Types Associated Types
| |||||
Generic Var Source # | |||||
Defined in Dhall.Syntax.Var Associated Types
| |||||
Generic ForeignSrcLang | |||||
Defined in GHC.ForeignSrcLang.Type Associated Types
Methods from :: ForeignSrcLang -> Rep ForeignSrcLang x # to :: Rep ForeignSrcLang x -> ForeignSrcLang # | |||||
Generic Extension | |||||
Defined in GHC.LanguageExtensions.Type Associated Types
| |||||
Generic Void | |||||
Generic ByteOrder | |||||
Defined in GHC.Internal.ByteOrder | |||||
Generic All | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic Any | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic Version | |||||
Defined in GHC.Internal.Data.Version Associated Types
| |||||
Generic Fingerprint | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic Associativity | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic DecidedStrictness | |||||
Defined in GHC.Internal.Generics Associated Types
Methods from :: DecidedStrictness -> Rep DecidedStrictness x # to :: Rep DecidedStrictness x -> DecidedStrictness # | |||||
Generic Fixity | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic SourceStrictness | |||||
Defined in GHC.Internal.Generics Associated Types
Methods from :: SourceStrictness -> Rep SourceStrictness x # to :: Rep SourceStrictness x -> SourceStrictness # | |||||
Generic SourceUnpackedness | |||||
Defined in GHC.Internal.Generics Associated Types
Methods from :: SourceUnpackedness -> Rep SourceUnpackedness x # to :: Rep SourceUnpackedness x -> SourceUnpackedness # | |||||
Generic ExitCode | |||||
Defined in GHC.Internal.IO.Exception Associated Types
| |||||
Generic CCFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic ConcFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic DebugFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic DoCostCentres | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic DoHeapProfile | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic DoTrace | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic GCFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic GiveGCStats | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic HpcFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic MiscFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic ParFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic ProfFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic RTSFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic TickyFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic TraceFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic SrcLoc | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic GCDetails | |||||
Defined in GHC.Internal.Stats Associated Types
| |||||
Generic RTSStats | |||||
Defined in GHC.Internal.Stats Associated Types
| |||||
Generic GeneralCategory | |||||
Defined in GHC.Internal.Generics Associated Types
Methods from :: GeneralCategory -> Rep GeneralCategory x # to :: Rep GeneralCategory x -> GeneralCategory # | |||||
Generic Ordering | |||||
Defined in GHC.Internal.Generics | |||||
Generic Half | |||||
Defined in Numeric.Half.Internal Associated Types
| |||||
Generic ByteRange | |||||
Defined in Network.HTTP.Types.Header Associated Types
| |||||
Generic StdMethod | |||||
Defined in Network.HTTP.Types.Method Associated Types
| |||||
Generic Status | |||||
Defined in Network.HTTP.Types.Status Associated Types
| |||||
Generic HttpVersion | |||||
Defined in Network.HTTP.Types.Version Associated Types
| |||||
Generic IP | |||||
Defined in Data.IP.Addr Associated Types
| |||||
Generic IPv4 | |||||
Defined in Data.IP.Addr Associated Types
| |||||
Generic IPv6 | |||||
Defined in Data.IP.Addr Associated Types
| |||||
Generic IPRange | |||||
Defined in Data.IP.Range Associated Types
| |||||
Generic InvalidPosException | |||||
Defined in Text.Megaparsec.Pos Associated Types
Methods from :: InvalidPosException -> Rep InvalidPosException x # to :: Rep InvalidPosException x -> InvalidPosException # | |||||
Generic Pos | |||||
Defined in Text.Megaparsec.Pos Associated Types
| |||||
Generic SourcePos | |||||
Defined in Text.Megaparsec.Pos Associated Types
| |||||
Generic URI | |||||
Defined in Network.URI Associated Types
| |||||
Generic URIAuth | |||||
Defined in Network.URI Associated Types
| |||||
Generic OsChar | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Generic OsString | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Generic PosixChar | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Generic PosixString | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Generic WindowsChar | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Generic WindowsString | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Generic Mode | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types
| |||||
Generic Style | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types
| |||||
Generic TextDetails | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types
| |||||
Generic Doc | |||||
Defined in Text.PrettyPrint.HughesPJ Associated Types
| |||||
Generic ColorOptions | |||||
Defined in Text.Pretty.Simple.Internal.Color Associated Types
| |||||
Generic Style | |||||
Defined in Text.Pretty.Simple.Internal.Color Associated Types
| |||||
Generic Expr | |||||
Defined in Text.Pretty.Simple.Internal.Expr Associated Types
| |||||
Generic CheckColorTty | |||||
Defined in Text.Pretty.Simple.Internal.Printer Associated Types
| |||||
Generic OutputOptions | |||||
Defined in Text.Pretty.Simple.Internal.Printer Associated Types
| |||||
Generic StringOutputStyle | |||||
Defined in Text.Pretty.Simple.Internal.Printer Associated Types
Methods from :: StringOutputStyle -> Rep StringOutputStyle x # to :: Rep StringOutputStyle x -> StringOutputStyle # | |||||
Generic AnnLookup | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic AnnTarget | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Bang | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic BndrVis | |||||
Defined in Language.Haskell.TH.Syntax | |||||
Generic Body | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Bytes | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Callconv | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Clause | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Con | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Dec | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic DecidedStrictness | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: DecidedStrictness -> Rep DecidedStrictness x # to :: Rep DecidedStrictness x -> DecidedStrictness # | |||||
Generic DerivClause | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic DerivStrategy | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic DocLoc | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Exp | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic FamilyResultSig | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: FamilyResultSig -> Rep FamilyResultSig x # to :: Rep FamilyResultSig x -> FamilyResultSig # | |||||
Generic Fixity | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic FixityDirection | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: FixityDirection -> Rep FixityDirection x # to :: Rep FixityDirection x -> FixityDirection # | |||||
Generic Foreign | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic FunDep | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Guard | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Info | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic InjectivityAnn | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: InjectivityAnn -> Rep InjectivityAnn x # to :: Rep InjectivityAnn x -> InjectivityAnn # | |||||
Generic Inline | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Lit | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Loc | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Match | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic ModName | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Module | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic ModuleInfo | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Name | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic NameFlavour | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic NameSpace | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic NamespaceSpecifier | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: NamespaceSpecifier -> Rep NamespaceSpecifier x # to :: Rep NamespaceSpecifier x -> NamespaceSpecifier # | |||||
Generic OccName | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Overlap | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Pat | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic PatSynArgs | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic PatSynDir | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Phases | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic PkgName | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Pragma | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Range | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Role | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic RuleBndr | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic RuleMatch | |||||
Defined in Language.Haskell.TH.Syntax | |||||
Generic Safety | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic SourceStrictness | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: SourceStrictness -> Rep SourceStrictness x # to :: Rep SourceStrictness x -> SourceStrictness # | |||||
Generic SourceUnpackedness | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: SourceUnpackedness -> Rep SourceUnpackedness x # to :: Rep SourceUnpackedness x -> SourceUnpackedness # | |||||
Generic Specificity | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Stmt | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic TyLit | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic TySynEqn | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Type | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic TypeFamilyHead | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: TypeFamilyHead -> Rep TypeFamilyHead x # to :: Rep TypeFamilyHead x -> TypeFamilyHead # | |||||
Generic Group | |||||
Defined in Network.TLS.Crypto.Types Associated Types
| |||||
Generic CipherId | |||||
Defined in Network.TLS.Types.Cipher Associated Types
| |||||
Generic SessionData | |||||
Defined in Network.TLS.Types.Session Associated Types
| |||||
Generic SessionFlag | |||||
Defined in Network.TLS.Types.Session Associated Types
| |||||
Generic TLS13TicketInfo | |||||
Defined in Network.TLS.Types.Session Associated Types
Methods from :: TLS13TicketInfo -> Rep TLS13TicketInfo x # to :: Rep TLS13TicketInfo x -> TLS13TicketInfo # | |||||
Generic Version | |||||
Defined in Network.TLS.Types.Version Associated Types
| |||||
Generic UnixTime | |||||
Defined in Data.UnixTime.Types Associated Types
| |||||
Generic CompressParams | |||||
Defined in Codec.Compression.Zlib.Internal Associated Types
Methods from :: CompressParams -> Rep CompressParams x # to :: Rep CompressParams x -> CompressParams # | |||||
Generic DecompressError | |||||
Defined in Codec.Compression.Zlib.Internal Associated Types
Methods from :: DecompressError -> Rep DecompressError x # to :: Rep DecompressError x -> DecompressError # | |||||
Generic DecompressParams | |||||
Defined in Codec.Compression.Zlib.Internal Associated Types
Methods from :: DecompressParams -> Rep DecompressParams x # to :: Rep DecompressParams x -> DecompressParams # | |||||
Generic CompressionLevel | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
Methods from :: CompressionLevel -> Rep CompressionLevel x # to :: Rep CompressionLevel x -> CompressionLevel # | |||||
Generic CompressionStrategy | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
Methods from :: CompressionStrategy -> Rep CompressionStrategy x # to :: Rep CompressionStrategy x -> CompressionStrategy # | |||||
Generic Format | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
| |||||
Generic MemoryLevel | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
| |||||
Generic Method | |||||
Defined in Codec.Compression.Zlib.Stream | |||||
Generic WindowBits | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
| |||||
Generic () | |||||
Generic Bool | |||||
Defined in GHC.Internal.Generics | |||||
Generic (Complex a) | |||||
Defined in Data.Complex Associated Types
| |||||
Generic (First a) | |||||
Defined in Data.Semigroup Associated Types
| |||||
Generic (Last a) | |||||
Defined in Data.Semigroup Associated Types
| |||||
Generic (Max a) | |||||
Defined in Data.Semigroup Associated Types
| |||||
Generic (Min a) | |||||
Defined in Data.Semigroup Associated Types
| |||||
Generic (WrappedMonoid m) | |||||
Defined in Data.Semigroup Associated Types
Methods from :: WrappedMonoid m -> Rep (WrappedMonoid m) x # to :: Rep (WrappedMonoid m) x -> WrappedMonoid m # | |||||
Generic (SCC vertex) | |||||
Defined in Data.Graph Associated Types
| |||||
Generic (Digit a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
Generic (Elem a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
Generic (FingerTree a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
Generic (Node a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
Generic (ViewL a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
Generic (ViewR a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
Generic (Tree a) | |||||
Defined in Data.Tree Associated Types
| |||||
Generic (Fix f) | |||||
Generic (Access f) Source # | |||||
Defined in Dhall.DirectoryTree.Types Associated Types
| |||||
Generic (Entry a) Source # | |||||
Defined in Dhall.DirectoryTree.Types Associated Types
| |||||
Generic (Mode f) Source # | |||||
Defined in Dhall.DirectoryTree.Types Associated Types
| |||||
Generic (Set a) Source # | |||||
Defined in Dhall.Set Associated Types
| |||||
Generic (FieldSelection s) Source # | |||||
Defined in Dhall.Syntax.Types Associated Types
Methods from :: FieldSelection s -> Rep (FieldSelection s) x # to :: Rep (FieldSelection s) x -> FieldSelection s # | |||||
Generic (NonEmpty a) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Identity a) | |||||
Defined in GHC.Internal.Data.Functor.Identity Associated Types
| |||||
Generic (First a) | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Generic (Last a) | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Generic (Down a) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Dual a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic (Endo a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic (Product a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic (Sum a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic (ZipList a) | |||||
Defined in GHC.Internal.Functor.ZipList Associated Types
| |||||
Generic (Par1 p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (HistoriedResponse body) | |||||
Defined in Network.HTTP.Client Associated Types
Methods from :: HistoriedResponse body -> Rep (HistoriedResponse body) x # to :: Rep (HistoriedResponse body) x -> HistoriedResponse body # | |||||
Generic (AddrRange a) | |||||
Defined in Data.IP.Range Associated Types
| |||||
Generic (ErrorFancy e) | |||||
Defined in Text.Megaparsec.Error Associated Types
| |||||
Generic (ErrorItem t) | |||||
Defined in Text.Megaparsec.Error Associated Types
| |||||
Generic (EF e) | |||||
Defined in Text.Megaparsec.Error.Builder Associated Types
| |||||
Generic (ET s) | |||||
Defined in Text.Megaparsec.Error.Builder Associated Types
| |||||
Generic (PosState s) | |||||
Defined in Text.Megaparsec.State Associated Types
| |||||
Generic (Doc a) | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types
| |||||
Generic (CommaSeparated a) | |||||
Defined in Text.Pretty.Simple.Internal.Expr Associated Types
Methods from :: CommaSeparated a -> Rep (CommaSeparated a) x # to :: Rep (CommaSeparated a) x -> CommaSeparated a # | |||||
Generic (Doc ann) | |||||
Defined in Prettyprinter.Internal Associated Types
| |||||
Generic (SimpleDocStream ann) | |||||
Defined in Prettyprinter.Internal Associated Types
Methods from :: SimpleDocStream ann -> Rep (SimpleDocStream ann) x # to :: Rep (SimpleDocStream ann) x -> SimpleDocStream ann # | |||||
Generic (SimpleDocTree ann) | |||||
Defined in Prettyprinter.Render.Util.SimpleDocTree Associated Types
Methods from :: SimpleDocTree ann -> Rep (SimpleDocTree ann) x # to :: Rep (SimpleDocTree ann) x -> SimpleDocTree ann # | |||||
Generic (Maybe a) | |||||
Defined in Data.Strict.Maybe Associated Types
| |||||
Generic (TyVarBndr flag) | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic (Maybe a) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Solo a) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic [a] | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (WrappedMonad m a) | |||||
Defined in Control.Applicative Associated Types
Methods from :: WrappedMonad m a -> Rep (WrappedMonad m a) x # to :: Rep (WrappedMonad m a) x -> WrappedMonad m a # | |||||
Generic (Arg a b) | |||||
Defined in Data.Semigroup Associated Types
| |||||
Generic (Map k v) Source # | |||||
Generic (Binding s a) Source # | |||||
Defined in Dhall.Syntax.Binding Associated Types
| |||||
Generic (Chunks s a) Source # | |||||
Defined in Dhall.Syntax.Chunks Associated Types
| |||||
Generic (Expr s a) Source # | |||||
Defined in Dhall.Syntax.Expr Associated Types
| |||||
Generic (FunctionBinding s a) Source # | |||||
Defined in Dhall.Syntax.FunctionBinding Associated Types
Methods from :: FunctionBinding s a -> Rep (FunctionBinding s a) x # to :: Rep (FunctionBinding s a) x -> FunctionBinding s a # | |||||
Generic (RecordField s a) Source # | |||||
Defined in Dhall.Syntax.RecordField Associated Types
Methods from :: RecordField s a -> Rep (RecordField s a) x # to :: Rep (RecordField s a) x -> RecordField s a # | |||||
Generic (Either a b) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Proxy t) | |||||
Defined in GHC.Internal.Generics | |||||
Generic (U1 p) | |||||
Defined in GHC.Internal.Generics | |||||
Generic (V1 p) | |||||
Generic (ParseError s e) | |||||
Defined in Text.Megaparsec.Error Associated Types
Methods from :: ParseError s e -> Rep (ParseError s e) x # to :: Rep (ParseError s e) x -> ParseError s e # | |||||
Generic (ParseErrorBundle s e) | |||||
Defined in Text.Megaparsec.Error Associated Types
Methods from :: ParseErrorBundle s e -> Rep (ParseErrorBundle s e) x # to :: Rep (ParseErrorBundle s e) x -> ParseErrorBundle s e # | |||||
Generic (State s e) | |||||
Defined in Text.Megaparsec.State Associated Types
| |||||
Generic (Either a b) | |||||
Defined in Data.Strict.Either Associated Types
| |||||
Generic (These a b) | |||||
Defined in Data.Strict.These Associated Types
| |||||
Generic (Pair a b) | |||||
Defined in Data.Strict.Tuple Associated Types
| |||||
Generic (These a b) | |||||
Defined in Data.These Associated Types
| |||||
Generic (Lift f a) | |||||
Defined in Control.Applicative.Lift Associated Types
| |||||
Generic (MaybeT m a) | |||||
Defined in Control.Monad.Trans.Maybe Associated Types
| |||||
Generic (a, b) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (WrappedArrow a b c) | |||||
Defined in Control.Applicative Associated Types
Methods from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x # to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c # | |||||
Generic (Join p a) | |||||
Defined in Data.Bifunctor.Join Associated Types
| |||||
Generic (Kleisli m a b) | |||||
Defined in GHC.Internal.Control.Arrow Associated Types
| |||||
Generic (Const a b) | |||||
Defined in GHC.Internal.Data.Functor.Const Associated Types
| |||||
Generic (Ap f a) | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Generic (Alt f a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic (Rec1 f p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (URec (Ptr ()) p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (URec Char p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (URec Double p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (URec Float p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (URec Int p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (URec Word p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Tagged s b) | |||||
Defined in Data.Tagged Associated Types
| |||||
Generic (These1 f g a) | |||||
Defined in Data.Functor.These Associated Types
| |||||
Generic (Backwards f a) | |||||
Defined in Control.Applicative.Backwards Associated Types
| |||||
Generic (AccumT w m a) | |||||
Defined in Control.Monad.Trans.Accum Associated Types
| |||||
Generic (ExceptT e m a) | |||||
Defined in Control.Monad.Trans.Except Associated Types
| |||||
Generic (IdentityT f a) | |||||
Defined in Control.Monad.Trans.Identity Associated Types
| |||||
Generic (ReaderT r m a) | |||||
Defined in Control.Monad.Trans.Reader Associated Types
| |||||
Generic (SelectT r m a) | |||||
Defined in Control.Monad.Trans.Select Associated Types
| |||||
Generic (StateT s m a) | |||||
Defined in Control.Monad.Trans.State.Lazy Associated Types
| |||||
Generic (StateT s m a) | |||||
Defined in Control.Monad.Trans.State.Strict Associated Types
| |||||
Generic (WriterT w m a) | |||||
Defined in Control.Monad.Trans.Writer.CPS Associated Types
| |||||
Generic (WriterT w m a) | |||||
Defined in Control.Monad.Trans.Writer.Lazy Associated Types
| |||||
Generic (WriterT w m a) | |||||
Defined in Control.Monad.Trans.Writer.Strict Associated Types
| |||||
Generic (Constant a b) | |||||
Defined in Data.Functor.Constant Associated Types
| |||||
Generic (Reverse f a) | |||||
Defined in Data.Functor.Reverse Associated Types
| |||||
Generic (a, b, c) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Product f g a) | |||||
Defined in Data.Functor.Product Associated Types
| |||||
Generic (Sum f g a) | |||||
Defined in Data.Functor.Sum Associated Types
| |||||
Generic ((f :*: g) p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic ((f :+: g) p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (K1 i c p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (ContT r m a) | |||||
Defined in Control.Monad.Trans.Cont Associated Types
| |||||
Generic (a, b, c, d) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Compose f g a) | |||||
Defined in Data.Functor.Compose Associated Types
| |||||
Generic (Clown f a b) | |||||
Defined in Data.Bifunctor.Clown Associated Types
| |||||
Generic (Flip p a b) | |||||
Defined in Data.Bifunctor.Flip Associated Types
| |||||
Generic (Joker g a b) | |||||
Defined in Data.Bifunctor.Joker Associated Types
| |||||
Generic (WrappedBifunctor p a b) | |||||
Defined in Data.Bifunctor.Wrapped Associated Types
Methods from :: WrappedBifunctor p a b -> Rep (WrappedBifunctor p a b) x # to :: Rep (WrappedBifunctor p a b) x -> WrappedBifunctor p a b # | |||||
Generic ((f :.: g) p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (M1 i c f p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (RWST r w s m a) | |||||
Defined in Control.Monad.Trans.RWS.CPS Associated Types
| |||||
Generic (RWST r w s m a) | |||||
Defined in Control.Monad.Trans.RWS.Lazy Associated Types
| |||||
Generic (RWST r w s m a) | |||||
Defined in Control.Monad.Trans.RWS.Strict Associated Types
| |||||
Generic (a, b, c, d, e) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Product f g a b) | |||||
Defined in Data.Bifunctor.Product Associated Types
| |||||
Generic (Sum p q a b) | |||||
Defined in Data.Bifunctor.Sum Associated Types
| |||||
Generic (a, b, c, d, e, f) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Tannen f p a b) | |||||
Defined in Data.Bifunctor.Tannen Associated Types
| |||||
Generic (a, b, c, d, e, f, g) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Biff p f g a b) | |||||
Defined in Data.Bifunctor.Biff Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i, j) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |||||
Defined in GHC.Internal.Generics Associated Types
|