Safe Haskell | Safe-Inferred |
---|---|
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))) (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 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 {
- getInputNormalizer :: ReifiedNormalizer Void
- defaultInputNormalizer :: InputNormalizer
- data Result f
- (>$<) :: 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 | |
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 #
default injectWith :: (Generic a, GenericToDhall (Rep a)) => InputNormalizer -> Encoder a #
Instances
inject :: ToDhall a => Encoder a #
Use the default input normalizer for injecting a value.
inject = injectWith defaultInputNormalizer
Building encoders
Records
newtype RecordEncoder a #
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 # | |
Defined in Dhall.Marshal.Encode Methods contramap :: (a' -> a) -> RecordEncoder a -> RecordEncoder a' (>$) :: b -> RecordEncoder b -> RecordEncoder a | |
Divisible RecordEncoder # | |
Defined in Dhall.Marshal.Encode Methods divide :: (a -> (b, c)) -> RecordEncoder b -> RecordEncoder c -> RecordEncoder a # conquer :: RecordEncoder a # |
recordEncoder :: RecordEncoder a -> Encoder a #
Convert a RecordEncoder
into the equivalent Encoder
.
encodeField :: ToDhall a => Text -> RecordEncoder a #
Specify how to encode one field of a record using the default ToDhall
instance for that type.
encodeFieldWith :: Text -> Encoder a -> RecordEncoder a #
Specify how to encode one field of a record by supplying an explicit
Encoder
for that field.
Unions
newtype UnionEncoder a #
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) :}
Instances
Contravariant UnionEncoder # | |
Defined in Dhall.Marshal.Encode Methods contramap :: (a' -> a) -> UnionEncoder a -> UnionEncoder a' (>$) :: b -> UnionEncoder b -> UnionEncoder a |
unionEncoder :: UnionEncoder a -> Encoder a #
Convert a UnionEncoder
into the equivalent Encoder
.
encodeConstructor :: ToDhall a => Text -> UnionEncoder a #
Specify how to encode an alternative by using the default ToDhall
instance
for that type.
encodeConstructorWith :: Text -> Encoder a -> UnionEncoder a #
Specify how to encode an alternative by providing an explicit Encoder
for that alternative.
(>|<) :: UnionEncoder a -> UnionEncoder b -> UnionEncoder (Either a b) infixr 5 #
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 where #
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)) #
Instances
GenericToDhall (U1 :: Type -> Type) # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (U1 a)) # | |
(GenericToDhall (f :*: g), GenericToDhall (h :*: i)) => GenericToDhall ((f :*: g) :*: (h :*: i)) # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (((f :*: g) :*: (h :*: i)) a)) # | |
(GenericToDhall (f :*: g), Selector s, ToDhall a) => GenericToDhall ((f :*: g) :*: M1 S s (K1 i a :: Type -> Type)) # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (((f :*: g) :*: M1 S s (K1 i a)) a0)) # | |
(Selector s, ToDhall a, GenericToDhall (f :*: g)) => GenericToDhall (M1 S s (K1 i a :: Type -> Type) :*: (f :*: g)) # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder ((M1 S s (K1 i a) :*: (f :*: g)) a0)) # | |
(Selector s1, Selector s2, ToDhall a1, ToDhall a2) => GenericToDhall (M1 S s1 (K1 i1 a1 :: Type -> Type) :*: M1 S s2 (K1 i2 a2 :: Type -> Type)) # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder ((M1 S s1 (K1 i1 a1) :*: M1 S s2 (K1 i2 a2)) a)) # | |
(GenericToDhall (f :+: g), GenericToDhall (h :+: i)) => GenericToDhall ((f :+: g) :+: (h :+: i)) # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (((f :+: g) :+: (h :+: i)) a)) # | |
(Constructor c, GenericToDhall (f :+: g), GenericToDhall h) => GenericToDhall ((f :+: g) :+: M1 C c h) # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (((f :+: g) :+: M1 C c h) a)) # | |
(Constructor c, GenericToDhall f, GenericToDhall (g :+: h)) => GenericToDhall (M1 C c f :+: (g :+: h)) # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder ((M1 C c f :+: (g :+: h)) a)) # | |
(Constructor c1, Constructor c2, GenericToDhall f1, GenericToDhall f2) => GenericToDhall (M1 C c1 f1 :+: M1 C c2 f2) # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder ((M1 C c1 f1 :+: M1 C c2 f2) a)) # | |
GenericToDhall f => GenericToDhall (M1 C c f) # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (M1 C c f a)) # | |
GenericToDhall f => GenericToDhall (M1 D d f) # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (M1 D d f a)) # | |
(Selector s, ToDhall a) => GenericToDhall (M1 S s (K1 i a :: Type -> Type)) # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (M1 S s (K1 i a) a0)) # |
genericToDhall :: (Generic a, GenericToDhall (Rep a)) => Encoder a #
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 #
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 #
genericToDhallWithInputNormalizer
is like genericToDhallWith
, but
instead of using the defaultInputNormalizer
it expects an custom
InputNormalizer
.
data InterpretOptions #
Use these options to tweak how Dhall derives a generic implementation of
FromDhall
.
Constructors
InterpretOptions | |
Fields
|
data SingletonConstructors #
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) # | |
Defined in Dhall.Deriving Methods |
defaultInterpretOptions :: InterpretOptions #
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 #
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 #
Default normalization-related settings (no custom normalization)
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) # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder (Result f) # | |
ToDhall (f (Result f)) => ToDhall (Result f) # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Result f) # |
Re-exports
Instances
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 # | |
MonadFix Seq | |
Defined in Data.Sequence.Internal | |
MonadZip Seq | |
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 | |
Eq1 Seq | |
Ord1 Seq | |
Defined in Data.Sequence.Internal Methods liftCompare :: (a -> b -> Ordering) -> Seq a -> Seq b -> Ordering | |
Read1 Seq | |
Defined in Data.Sequence.Internal Methods liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Seq a) liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Seq a] liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Seq a) liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Seq a] | |
Show1 Seq | |
Defined in Data.Sequence.Internal Methods liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Seq a -> ShowS liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Seq a] -> ShowS | |
Traversable Seq | |
Alternative Seq | |
Applicative Seq | |
Functor Seq | |
Monad Seq | |
MonadPlus Seq | |
UnzipWith Seq | |
Defined in Data.Sequence.Internal Methods unzipWith' :: (x -> (a, b)) -> Seq x -> (Seq a, Seq b) | |
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) | |
FromJSON a => FromJSON (Seq a) | |
Defined in Data.Aeson.Types.FromJSON | |
ToJSON a => ToJSON (Seq a) | |
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) | |
Defined in Data.Sequence.Internal Methods fromString :: String -> Seq a # | |
Monoid (Seq a) | |
Semigroup (Seq a) | |
IsList (Seq a) | |
Read a => Read (Seq a) | |
Show a => Show (Seq a) | |
NFData a => NFData (Seq a) | |
Defined in Data.Sequence.Internal | |
FromDhall a => FromDhall (Seq a) # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder (Seq a) # | |
ToDhall a => ToDhall (Seq a) # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (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 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 |
Instances
Boxed vectors, supporting efficient slicing.
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 # | |
MonadFail Vector | Since: vector-0.12.1.0 |
Defined in Data.Vector | |
MonadFix Vector | This instance has the same semantics as the one for lists. Since: vector-0.12.2.0 |
Defined in Data.Vector | |
MonadZip 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 | |
Eq1 Vector | |
Ord1 Vector | |
Defined in Data.Vector Methods liftCompare :: (a -> b -> Ordering) -> Vector a -> Vector b -> Ordering | |
Read1 Vector | |
Defined in Data.Vector Methods liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Vector a) liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Vector a] liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Vector a) liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Vector a] | |
Show1 Vector | |
Defined in Data.Vector Methods liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Vector a -> ShowS liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Vector a] -> ShowS | |
Traversable Vector | |
Alternative Vector | |
Applicative Vector | |
Functor Vector | |
Monad Vector | |
MonadPlus Vector | |
NFData1 Vector | Since: vector-0.12.1.0 |
Defined in Data.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) | |
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) # | |
Monoid (Vector a) | |
Semigroup (Vector a) | |
IsList (Vector a) | |
Read a => Read (Vector a) | |
Show a => Show (Vector a) | |
NFData a => NFData (Vector a) | |
Defined in Data.Vector | |
FromDhall a => FromDhall (Vector a) # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder (Vector a) # | |
ToDhall a => ToDhall (Vector a) # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (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 Item (Vector a) | |
Defined in Data.Vector |