Safe Haskell | None |
---|---|
Language | Haskell2010 |
Please read the Dhall.Tutorial module, which contains a tutorial explaining how to use the language, the compiler, and this library
Synopsis
- input :: Type a -> Text -> IO a
- inputWithSettings :: InputSettings -> Type a -> Text -> IO a
- inputFile :: Type a -> FilePath -> IO a
- inputFileWithSettings :: EvaluateSettings -> Type a -> FilePath -> IO a
- inputExpr :: Text -> IO (Expr Src X)
- inputExprWithSettings :: InputSettings -> Text -> IO (Expr Src X)
- rootDirectory :: Functor f => LensLike' f InputSettings FilePath
- sourceName :: Functor f => LensLike' f InputSettings FilePath
- startingContext :: (Functor f, HasEvaluateSettings s) => LensLike' f s (Context (Expr Src X))
- normalizer :: (Functor f, HasEvaluateSettings s) => LensLike' f s (Maybe (ReifiedNormalizer X))
- standardVersion :: (Functor f, HasEvaluateSettings s) => LensLike' f s StandardVersion
- defaultInputSettings :: InputSettings
- data InputSettings
- defaultEvaluateSettings :: EvaluateSettings
- data EvaluateSettings
- class HasEvaluateSettings s
- detailed :: IO a -> IO a
- data Type a = Type {}
- newtype RecordType a = RecordType (Product (Const (Map Text (Expr Src X))) (Compose ((->) (Expr Src X)) Maybe) a)
- newtype UnionType a = UnionType (Compose (Map Text) Type a)
- data InputType a = InputType {}
- class Interpret a where
- autoWith :: InterpretOptions -> Type a
- data InvalidType s a = InvalidType {
- invalidTypeExpected :: Expr s a
- invalidTypeExpression :: Expr s a
- auto :: Interpret a => Type a
- genericAuto :: (Generic a, GenericInterpret (Rep a)) => Type a
- data InterpretOptions = InterpretOptions {
- fieldModifier :: Text -> Text
- constructorModifier :: Text -> Text
- inputNormalizer :: ReifiedNormalizer X
- defaultInterpretOptions :: InterpretOptions
- bool :: Type Bool
- natural :: Type Natural
- integer :: Type Integer
- scientific :: Type Scientific
- double :: Type Double
- lazyText :: Type Text
- strictText :: Type Text
- maybe :: Type a -> Type (Maybe a)
- sequence :: Type a -> Type (Seq a)
- list :: Type a -> Type [a]
- vector :: Type a -> Type (Vector a)
- unit :: Type ()
- string :: Type String
- pair :: Type a -> Type b -> Type (a, b)
- record :: RecordType a -> Type a
- field :: Text -> Type a -> RecordType a
- union :: UnionType a -> Type a
- constructor :: Text -> Type a -> UnionType a
- class GenericInterpret f where
- genericAutoWith :: InterpretOptions -> State Int (Type (f a))
- class GenericInject f where
- genericInjectWith :: InterpretOptions -> State Int (InputType (f a))
- class Inject a where
- injectWith :: InterpretOptions -> InputType a
- inject :: Inject a => InputType a
- genericInject :: (Generic a, GenericInject (Rep a)) => InputType a
- newtype RecordInputType a = RecordInputType (Map Text (InputType a))
- inputFieldWith :: Text -> InputType a -> RecordInputType a
- inputField :: Inject a => Text -> RecordInputType a
- inputRecord :: RecordInputType a -> InputType a
- newtype UnionInputType a = UnionInputType (Product (Const (Map Text (Expr Src X))) (Op (Text, Expr Src X)) a)
- inputConstructorWith :: Text -> InputType a -> UnionInputType a
- inputConstructor :: Inject a => Text -> UnionInputType a
- inputUnion :: UnionInputType a -> InputType a
- (>|<) :: UnionInputType a -> UnionInputType b -> UnionInputType (Either a b)
- rawInput :: Alternative f => Type a -> Expr s X -> f a
- (>$<) :: 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
Input
:: Type a | The type of value to decode from Dhall to Haskell |
-> Text | The Dhall program |
-> IO a | The decoded value in Haskell |
Type-check and evaluate a Dhall program, decoding the result into Haskell
The first argument determines the type of value that you decode:
>>>
input integer "+2"
2>>>
input (vector double) "[1.0, 2.0]"
[1.0,2.0]
Use auto
to automatically select which type to decode based on the
inferred return type:
>>>
input auto "True" :: IO Bool
True
This uses the settings from defaultInputSettings
.
:: InputSettings | |
-> Type a | The type of value to decode from Dhall to Haskell |
-> Text | The Dhall program |
-> IO a | The decoded value in Haskell |
Extend input
with a root directory to resolve imports relative
to, a file to mention in errors as the source, a custom typing
context, and a custom normalization process.
Since: 1.16
:: Type a | The type of value to decode from Dhall to Haskell |
-> FilePath | The path to the Dhall program. |
-> IO a | The decoded value in Haskell. |
Type-check and evaluate a Dhall program that is read from the file-system.
This uses the settings from defaultEvaluateSettings
.
Since: 1.16
inputFileWithSettings Source #
:: EvaluateSettings | |
-> Type a | The type of value to decode from Dhall to Haskell |
-> FilePath | The path to the Dhall program. |
-> IO a | The decoded value in Haskell. |
Extend inputFile
with a custom typing context and a custom
normalization process.
Since: 1.16
Similar to input
, but without interpreting the Dhall Expr
into a Haskell
type.
Uses the settings from defaultInputSettings
.
inputExprWithSettings Source #
Extend inputExpr
with a root directory to resolve imports relative
to, a file to mention in errors as the source, a custom typing
context, and a custom normalization process.
Since: 1.16
rootDirectory :: Functor f => LensLike' f InputSettings FilePath Source #
Access the directory to resolve imports relative to.
Since: 1.16
sourceName :: Functor f => LensLike' f InputSettings FilePath Source #
Access the name of the source to report locations from; this is only used in error messages, so it's okay if this is a best guess or something symbolic.
Since: 1.16
startingContext :: (Functor f, HasEvaluateSettings s) => LensLike' f s (Context (Expr Src X)) Source #
Access the starting context used for evaluation and type-checking.
Since: 1.16
normalizer :: (Functor f, HasEvaluateSettings s) => LensLike' f s (Maybe (ReifiedNormalizer X)) Source #
Access the custom normalizer.
Since: 1.16
standardVersion :: (Functor f, HasEvaluateSettings s) => LensLike' f s StandardVersion Source #
Access the standard version (used primarily when encoding or decoding Dhall expressions to and from a binary representation)
Since: 1.17
defaultInputSettings :: InputSettings Source #
Default input settings: resolves imports relative to .
(the
current working directory), report errors as coming from (input)
,
and default evaluation settings from defaultEvaluateSettings
.
Since: 1.16
data InputSettings Source #
Since: 1.16
Instances
HasEvaluateSettings InputSettings Source # | |
Defined in Dhall |
defaultEvaluateSettings :: EvaluateSettings Source #
Default evaluation settings: no extra entries in the initial context, and no special normalizer behaviour.
Since: 1.16
data EvaluateSettings Source #
Since: 1.16
Instances
HasEvaluateSettings EvaluateSettings Source # | |
Defined in Dhall |
class HasEvaluateSettings s Source #
Since: 1.16
evaluateSettings
Instances
HasEvaluateSettings EvaluateSettings Source # | |
Defined in Dhall | |
HasEvaluateSettings InputSettings Source # | |
Defined in Dhall |
detailed :: IO a -> IO a Source #
Use this to provide more detailed error messages
> input auto "True" :: IO Integer *** Exception: Error: Expression doesn't match annotation True : Integer (input):1:1
> detailed (input auto "True") :: IO Integer *** Exception: Error: Expression doesn't match annotation Explanation: You can annotate an expression with its type or kind using the ❰:❱ symbol, like this: ┌───────┐ │ x : t │ ❰x❱ is an expression and ❰t❱ is the annotated type or kind of ❰x❱ └───────┘ The type checker verifies that the expression's type or kind matches the provided annotation For example, all of the following are valid annotations that the type checker accepts: ┌─────────────┐ │ 1 : Natural │ ❰1❱ is an expression that has type ❰Natural❱, so the type └─────────────┘ checker accepts the annotation ┌───────────────────────┐ │ Natural/even 2 : Bool │ ❰Natural/even 2❱ has type ❰Bool❱, so the type └───────────────────────┘ checker accepts the annotation ┌────────────────────┐ │ List : Type → Type │ ❰List❱ is an expression that has kind ❰Type → Type❱, └────────────────────┘ so the type checker accepts the annotation ┌──────────────────┐ │ List Text : Type │ ❰List Text❱ is an expression that has kind ❰Type❱, so └──────────────────┘ the type checker accepts the annotation However, the following annotations are not valid and the type checker will reject them: ┌──────────┐ │ 1 : Text │ The type checker rejects this because ❰1❱ does not have type └──────────┘ ❰Text❱ ┌─────────────┐ │ List : Type │ ❰List❱ does not have kind ❰Type❱ └─────────────┘ You or the interpreter annotated this expression: ↳ True ... with this type or kind: ↳ Integer ... but the inferred type or kind of the expression is actually: ↳ Bool Some common reasons why you might get this error: ● The Haskell Dhall interpreter implicitly inserts a top-level annotation matching the expected type For example, if you run the following Haskell code: ┌───────────────────────────────┐ │ >>> input auto "1" :: IO Text │ └───────────────────────────────┘ ... then the interpreter will actually type check the following annotated expression: ┌──────────┐ │ 1 : Text │ └──────────┘ ... and then type-checking will fail ──────────────────────────────────────────────────────────────────────────────── True : Integer (input):1:1
Types
A (Type a)
represents a way to marshal a value of type 'a'
from Dhall
into Haskell
You can produce Type
s either explicitly:
example :: Type (Vector Text) example = vector text
... or implicitly using auto
:
example :: Type (Vector Text) example = auto
You can consume Type
s using the input
function:
input :: Type a -> Text -> IO a
newtype RecordType a Source #
The RecordType
applicative functor allows you to build a Type
parser
from 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 parser has type Type
Project
, but we can't build that out of any
smaller parsers, as Type
s cannot be combined (they are only Functor
s).
However, we can use a RecordType
to build a Type
for Project
:
>>>
:{
project :: Type Project project = record ( Project <$> field "name" strictText <*> field "description" strictText <*> field "stars" natural ) :}
Instances
Functor RecordType Source # | |
Defined in Dhall fmap :: (a -> b) -> RecordType a -> RecordType b # (<$) :: a -> RecordType b -> RecordType a # | |
Applicative RecordType Source # | |
Defined in Dhall pure :: a -> RecordType a # (<*>) :: RecordType (a -> b) -> RecordType a -> RecordType b # liftA2 :: (a -> b -> c) -> RecordType a -> RecordType b -> RecordType c # (*>) :: RecordType a -> RecordType b -> RecordType b # (<*) :: RecordType a -> RecordType b -> RecordType a # |
The UnionType
monoid allows you to build a Type
parser
from a Dhall union
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 = "Finish succesfully" | Queued : Natural | Errored : Text >
Our parser has type Type
Status
, but we can't build that out of any
smaller parsers, as Type
s cannot be combined (they are only Functor
s).
However, we can use a UnionType
to build a Type
for Status
:
>>>
:{
status :: Type Status status = union ( ( Queued <$> constructor "Queued" natural ) <> ( Result <$> constructor "Result" strictText ) <> ( Errored <$> constructor "Errored" strictText ) ) :}
An (InputType a)
represents a way to marshal a value of type 'a'
from
Haskell into Dhall
class Interpret a where Source #
Any value that implements Interpret
can be automatically decoded based on
the inferred return type of input
>>>
input auto "[1, 2, 3]" :: IO (Vector Natural)
[1,2,3]
This class auto-generates a default implementation for records that
implement Generic
. This does not auto-generate an instance for recursive
types.
Nothing
autoWith :: InterpretOptions -> Type a Source #
autoWith :: (Generic a, GenericInterpret (Rep a)) => InterpretOptions -> Type a Source #
Instances
Interpret Bool Source # | |
Interpret Double Source # | |
Interpret Integer Source # | |
Interpret Natural Source # | |
Interpret Scientific Source # | |
Defined in Dhall | |
Interpret Text Source # | |
Interpret Text Source # | |
Interpret [Char] Source # | |
Interpret a => Interpret [a] Source # | |
Interpret a => Interpret (Maybe a) Source # | |
Interpret a => Interpret (Seq a) Source # | |
Interpret a => Interpret (Vector a) Source # | |
(Inject a, Interpret b) => Interpret (a -> b) Source # | |
(Interpret a, Interpret b) => Interpret (a, b) Source # | |
data InvalidType s a Source #
Every Type
must obey the contract that if an expression's type matches the
the expected
type then the extract
function must succeed. If not, then
this exception is thrown
This exception indicates that an invalid Type
was provided to the input
function
InvalidType | |
|
Instances
(Pretty s, Pretty a, Typeable s, Typeable a) => Show (InvalidType s a) Source # | |
Defined in Dhall showsPrec :: Int -> InvalidType s a -> ShowS # show :: InvalidType s a -> String # showList :: [InvalidType s a] -> ShowS # | |
(Pretty s, Pretty a, Typeable s, Typeable a) => Exception (InvalidType s a) Source # | |
Defined in Dhall toException :: InvalidType s a -> SomeException # fromException :: SomeException -> Maybe (InvalidType s a) # displayException :: InvalidType s a -> String # |
auto :: Interpret a => Type a Source #
Use the default options for interpreting a configuration file
auto = autoWith defaultInterpretOptions
genericAuto :: (Generic a, GenericInterpret (Rep a)) => Type a Source #
genericAuto
is the default implementation for auto
if you derive
Interpret
. The difference is that you can use genericAuto
without
having to explicitly provide an Interpret
instance for a type as long as
the type derives Generic
data InterpretOptions Source #
Use these options to tweak how Dhall derives a generic implementation of
Interpret
InterpretOptions | |
|
defaultInterpretOptions :: InterpretOptions Source #
Default interpret options, which you can tweak or override, like this:
autoWith (defaultInterpretOptions { fieldModifier = Data.Text.Lazy.dropWhile (== '_') })
scientific :: Type Scientific Source #
Decode a Scientific
>>>
input scientific "1e100"
1.0e100
sequence :: Type a -> Type (Seq a) Source #
Decode a Seq
>>>
input (sequence natural) "[1, 2, 3]"
fromList [1,2,3]
vector :: Type a -> Type (Vector a) Source #
Decode a Vector
>>>
input (vector natural) "[1, 2, 3]"
[1,2,3]
Decode ()
from an empty record.
>>>
input unit "{=}" -- GHC doesn't print the result if it is ()
pair :: Type a -> Type b -> Type (a, b) Source #
Given a pair of Type
s, decode a tuple-record into their pairing.
>>>
input (pair natural bool) "{ _1 = 42, _2 = False }"
(42,False)
record :: RecordType a -> Type a Source #
Run a RecordType
parser to build a Type
parser.
class GenericInterpret f where Source #
This is the underlying class that powers the Interpret
class's support
for automatically deriving a generic implementation
genericAutoWith :: InterpretOptions -> State Int (Type (f a)) Source #
Instances
class GenericInject f where Source #
This is the underlying class that powers the Interpret
class's support
for automatically deriving a generic implementation
genericInjectWith :: InterpretOptions -> State Int (InputType (f a)) Source #
Instances
This class is used by Interpret
instance for functions:
instance (Inject a, Interpret b) => Interpret (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 X
) - Applying the Dhall function (i.e.
f :: Expr Src X
) 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
Nothing
injectWith :: InterpretOptions -> InputType a Source #
injectWith :: (Generic a, GenericInject (Rep a)) => InterpretOptions -> InputType a Source #
Instances
inject :: Inject a => InputType a Source #
Use the default options for injecting a value
inject = inject defaultInterpretOptions
genericInject :: (Generic a, GenericInject (Rep a)) => InputType a Source #
Use the default options for injecting a value, whose structure is determined generically.
This can be used when you want to use Inject
on types that you don't
want to define orphan instances for.
newtype RecordInputType a Source #
RecordInputType (Map Text (InputType a)) |
Instances
Contravariant RecordInputType Source # | |
Defined in Dhall contramap :: (a -> b) -> RecordInputType b -> RecordInputType a # (>$) :: b -> RecordInputType b -> RecordInputType a # | |
Divisible RecordInputType Source # | |
Defined in Dhall divide :: (a -> (b, c)) -> RecordInputType b -> RecordInputType c -> RecordInputType a # conquer :: RecordInputType a # |
inputFieldWith :: Text -> InputType a -> RecordInputType a Source #
inputField :: Inject a => Text -> RecordInputType a Source #
inputRecord :: RecordInputType a -> InputType a Source #
newtype UnionInputType a Source #
The UnionInputType
monoid allows you to build
an InputType
injector 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 = "Finish succesfully" | Queued : Natural | Errored : Text >
Our injector has type InputType
Status
, but we can't build that out of any
smaller injectors, as InputType
s cannot be combined.
However, we can use an UnionInputType
to build an InputType
for Status
:
>>>
:{
injectStatus :: InputType Status injectStatus = adapt >$< inputUnion ( inputConstructorWith "Queued" inject >|< inputConstructorWith "Result" inject >|< inputConstructorWith "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 Inject
instance to inject each branch, we could write
>>>
:{
injectStatus :: InputType Status injectStatus = adapt >$< inputUnion ( inputConstructor "Queued" >|< inputConstructor "Result" >|< inputConstructor "Errored" ) where adapt (Queued n) = Left n adapt (Result t) = Right (Left t) adapt (Errored e) = Right (Right e) :}
Instances
Contravariant UnionInputType Source # | |
Defined in Dhall contramap :: (a -> b) -> UnionInputType b -> UnionInputType a # (>$) :: b -> UnionInputType b -> UnionInputType a # |
inputConstructorWith :: Text -> InputType a -> UnionInputType a Source #
inputConstructor :: Inject a => Text -> UnionInputType a Source #
inputUnion :: UnionInputType a -> InputType a Source #
(>|<) :: UnionInputType a -> UnionInputType b -> UnionInputType (Either a b) infixr 5 Source #
Combines two UnionInputType
values. See UnionInputType
for usage
notes.
Ideally, this matches chosen
;
however, this allows UnionInputType
to not need a Divisible
instance
itself (since no instance is possible).
Miscellaneous
:: Alternative f | |
=> Type a | The type of value to decode from Dhall to Haskell |
-> Expr s X | a closed form Dhall program, which evaluates to the expected type |
-> f a | The decoded value in Haskell |
Use this function to extract Haskell values directly from Dhall AST.
The intended use case is to allow easy extraction of Dhall values for
making the function normalizeWith
easier to use.
For other use cases, use input
from Dhall
module. It will give you
a much better user experience.
(>$<) :: Contravariant f => (a -> b) -> f b -> f a infixl 4 #
This is an infix alias for contramap
.
(>*<) :: Divisible f => f a -> f b -> f (a, b) infixr 5 Source #
The RecordInputType
divisible (contravariant) functor allows you to build
an InputType
injector 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 injector has type InputType
Project
, but we can't build that out of any
smaller injectors, as InputType
s cannot be combined (they are only Contravariant
s).
However, we can use an InputRecordType
to build an InputType
for Project
:
>>>
:{
injectProject :: InputType Project injectProject = inputRecord ( adapt >$< inputFieldWith "name" inject >*< inputFieldWith "description" inject >*< inputFieldWith "stars" inject ) where adapt (Project{..}) = (projectName, (projectDescription, projectStars)) :}
Or, since we are simply using the Inject
instance to inject each field, we could write
>>>
:{
injectProject :: InputType Project injectProject = inputRecord ( adapt >$< inputField "name" >*< inputField "description" >*< inputField "stars" ) where adapt (Project{..}) = (projectName, (projectDescription, projectStars)) :}
Infix divided
Re-exports
Type representing arbitrary-precision non-negative integers.
>>>
2^100 :: Natural
1267650600228229401496703205376
Operations whose result would be negative
,throw
(Underflow
:: ArithException
)
>>>
-1 :: Natural
*** Exception: arithmetic underflow
Since: base-4.8.0.0
Instances
Enum Natural | Since: base-4.8.0.0 |
Eq Natural | Since: base-4.8.0.0 |
Integral Natural | Since: base-4.8.0.0 |
Defined in GHC.Real | |
Data Natural | Since: base-4.8.0.0 |
Defined in Data.Data 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 :: (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 # | |
Num Natural | Note that Since: base-4.8.0.0 |
Ord Natural | Since: base-4.8.0.0 |
Read Natural | Since: base-4.8.0.0 |
Real Natural | Since: base-4.8.0.0 |
Defined in GHC.Real toRational :: Natural -> Rational # | |
Show Natural | Since: base-4.8.0.0 |
Ix Natural | Since: base-4.8.0.0 |
Lift Natural | |
Hashable Natural | |
Defined in Data.Hashable.Class | |
ToJSON Natural | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSONKey Natural | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON Natural | |
FromJSONKey Natural | |
PrintfArg Natural | Since: base-4.8.0.0 |
Defined in Text.Printf formatArg :: Natural -> FieldFormatter # parseFormat :: Natural -> ModifierParser # | |
Subtractive Natural | |
Defined in Basement.Numerical.Subtractive type Difference Natural :: Type # | |
Pretty Natural | |
Defined in Data.Text.Prettyprint.Doc.Internal | |
Serialise Natural | Since: serialise-0.2.0.0 |
Inject Natural Source # | |
Defined in Dhall | |
Interpret Natural Source # | |
type Difference Natural | |
Defined in Basement.Numerical.Subtractive |
General-purpose finite sequences.
Instances
Monad Seq | |
Functor Seq | |
MonadFix Seq | Since: containers-0.5.11 |
Defined in Data.Sequence.Internal | |
Applicative Seq | Since: containers-0.5.4 |
Foldable Seq | |
Defined in Data.Sequence.Internal fold :: Monoid m => Seq m -> 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 | |
ToJSON1 Seq | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON1 Seq | |
Alternative Seq | Since: containers-0.5.4 |
MonadPlus Seq | |
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 |
MonadZip Seq |
|
UnzipWith Seq | |
Defined in Data.Sequence.Internal unzipWith' :: (x -> (a, b)) -> Seq x -> (Seq a, Seq b) | |
IsList (Seq a) | |
Eq a => Eq (Seq a) | |
Data a => Data (Seq a) | |
Defined in Data.Sequence.Internal 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 :: (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) # | |
Ord a => Ord (Seq a) | |
Read a => Read (Seq a) | |
Show a => Show (Seq a) | |
a ~ Char => IsString (Seq a) | Since: containers-0.5.7 |
Defined in Data.Sequence.Internal fromString :: String -> Seq a # | |
Semigroup (Seq a) | Since: containers-0.5.7 |
Monoid (Seq a) | |
ToJSON a => ToJSON (Seq a) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON a => FromJSON (Seq a) | |
NFData a => NFData (Seq a) | |
Defined in Data.Sequence.Internal | |
Serialise a => Serialise (Seq a) | Since: serialise-0.2.0.0 |
Inject a => Inject (Seq a) Source # | |
Defined in Dhall injectWith :: InterpretOptions -> InputType (Seq a) Source # | |
Interpret a => Interpret (Seq a) Source # | |
type Item (Seq a) | |
Defined in Data.Sequence.Internal |
A space efficient, packed, unboxed Unicode text type.
Instances
Boxed vectors, supporting efficient slicing.
Instances
Monad Vector | |
Functor Vector | |
MonadFail Vector | |
Defined in Data.Vector | |
Applicative Vector | |
Foldable Vector | |
Defined in Data.Vector fold :: Monoid m => Vector m -> 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 | |
ToJSON1 Vector | |
Defined in Data.Aeson.Types.ToJSON liftToJSON :: (a -> Value) -> ([a] -> Value) -> Vector a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Vector a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Vector a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Vector a] -> Encoding # | |
FromJSON1 Vector | |
Alternative Vector | |
MonadPlus Vector | |
Eq1 Vector | |
Ord1 Vector | |
Defined in Data.Vector | |
Read1 Vector | |
Defined in Data.Vector | |
Show1 Vector | |
MonadZip Vector | |
Vector Vector a | |
Defined in Data.Vector basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) a -> m (Vector a) # basicUnsafeThaw :: PrimMonad m => Vector a -> m (Mutable Vector (PrimState m) a) # basicLength :: Vector a -> Int # basicUnsafeSlice :: Int -> Int -> Vector a -> Vector a # basicUnsafeIndexM :: Monad m => Vector a -> Int -> m a # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) a -> Vector a -> m () # | |
IsList (Vector a) | |
Eq a => Eq (Vector a) | |
Data a => Data (Vector a) | |
Defined in Data.Vector 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 :: (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) # | |
Ord a => Ord (Vector a) | |
Defined in Data.Vector | |
Read a => Read (Vector a) | |
Show a => Show (Vector a) | |
Semigroup (Vector a) | |
Monoid (Vector a) | |
ToJSON a => ToJSON (Vector a) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON a => FromJSON (Vector a) | |
NFData a => NFData (Vector a) | |
Defined in Data.Vector | |
Serialise a => Serialise (Vector a) | Since: serialise-0.2.0.0 |
Inject a => Inject (Vector a) Source # | |
Defined in Dhall injectWith :: InterpretOptions -> InputType (Vector a) Source # | |
Interpret a => Interpret (Vector a) Source # | |
type Mutable Vector | |
Defined in Data.Vector | |
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