Safe Haskell | None |
---|---|
Language | Haskell2010 |
Dhall.Marshal.Decode
Description
Please read the Dhall.Tutorial module, which contains a tutorial explaining how to use the language, the compiler, and this library
Synopsis
- data Decoder a = Decoder {}
- class FromDhall a where
- autoWith :: InputNormalizer -> Decoder a
- type Interpret = FromDhall
- auto :: FromDhall a => Decoder a
- bool :: Decoder Bool
- unit :: Decoder ()
- void :: Decoder Void
- natural :: Decoder Natural
- word :: Decoder Word
- word8 :: Decoder Word8
- word16 :: Decoder Word16
- word32 :: Decoder Word32
- word64 :: Decoder Word64
- integer :: Decoder Integer
- int :: Decoder Int
- int8 :: Decoder Int8
- int16 :: Decoder Int16
- int32 :: Decoder Int32
- int64 :: Decoder Int64
- scientific :: Decoder Scientific
- double :: Decoder Double
- string :: Decoder String
- lazyText :: Decoder Text
- strictText :: Decoder Text
- maybe :: Decoder a -> Decoder (Maybe a)
- pair :: Decoder a -> Decoder b -> Decoder (a, b)
- sequence :: Decoder a -> Decoder (Seq a)
- list :: Decoder a -> Decoder [a]
- vector :: Decoder a -> Decoder (Vector a)
- setFromDistinctList :: (Ord a, Show a) => Decoder a -> Decoder (Set a)
- setIgnoringDuplicates :: Ord a => Decoder a -> Decoder (Set a)
- hashSetFromDistinctList :: (Hashable a, Ord a, Show a) => Decoder a -> Decoder (HashSet a)
- hashSetIgnoringDuplicates :: (Hashable a, Ord a) => Decoder a -> Decoder (HashSet a)
- map :: Ord k => Decoder k -> Decoder v -> Decoder (Map k v)
- hashMap :: (Eq k, Hashable k) => Decoder k -> Decoder v -> Decoder (HashMap k v)
- pairFromMapEntry :: Decoder k -> Decoder v -> Decoder (k, v)
- function :: Encoder a -> Decoder b -> Decoder (a -> b)
- functionWith :: InputNormalizer -> Encoder a -> Decoder b -> Decoder (a -> b)
- newtype RecordDecoder a = RecordDecoder (Product (Const (Map Text (Expector (Expr Src Void)))) (Compose ((->) (Expr Src Void)) (Extractor Src Void)) a)
- record :: RecordDecoder a -> Decoder a
- field :: Text -> Decoder a -> RecordDecoder a
- newtype UnionDecoder a = UnionDecoder (Compose (Map Text) Decoder a)
- union :: UnionDecoder a -> Decoder a
- constructor :: Text -> Decoder a -> UnionDecoder a
- class GenericFromDhall t f where
- genericAutoWithNormalizer :: Proxy t -> InputNormalizer -> InterpretOptions -> State Int (Decoder (f a))
- class GenericFromDhallUnion t f where
- genericUnionAutoWithNormalizer :: Proxy t -> InputNormalizer -> InterpretOptions -> UnionDecoder (f a)
- genericAuto :: (Generic a, GenericFromDhall a (Rep a)) => Decoder a
- genericAutoWith :: (Generic a, GenericFromDhall a (Rep a)) => InterpretOptions -> Decoder a
- newtype DhallErrors e = DhallErrors {
- getErrors :: NonEmpty e
- showDhallErrors :: Show e => String -> DhallErrors e -> String
- data InvalidDecoder s a = InvalidDecoder {
- invalidDecoderExpected :: Expr s a
- invalidDecoderExpression :: Expr s a
- type ExtractErrors s a = DhallErrors (ExtractError s a)
- data ExtractError s a
- type Extractor s a = Validation (ExtractErrors s a)
- typeError :: Expector (Expr s a) -> Expr s a -> Extractor s a b
- extractError :: Text -> Extractor s a b
- type MonadicExtractor s a = Either (ExtractErrors s a)
- toMonadic :: Extractor s a b -> MonadicExtractor s a b
- fromMonadic :: MonadicExtractor s a b -> Extractor s a b
- type ExpectedTypeErrors = DhallErrors ExpectedTypeError
- data ExpectedTypeError = RecursiveTypeError
- type Expector = Validation ExpectedTypeErrors
- newtype InputNormalizer = InputNormalizer {
- getInputNormalizer :: ReifiedNormalizer Void
- defaultInputNormalizer :: InputNormalizer
- data InterpretOptions = InterpretOptions {}
- data SingletonConstructors
- defaultInterpretOptions :: InterpretOptions
- data Result f
- data Natural
- data Seq a
- data Text
- data Vector a
- class Generic a
General
A (Decoder a)
represents a way to marshal a value of type 'a'
from Dhall
into Haskell.
You can produce Decoder
s either explicitly:
example :: Decoder (Vector Text) example = vector text
... or implicitly using auto
:
example :: Decoder (Vector Text) example = auto
You can consume Decoder
s using the input
function:
input :: Decoder a -> Text -> IO a
Constructors
Decoder | |
class FromDhall a where Source #
Any value that implements FromDhall
can be automatically decoded based on
the inferred return type of input
.
>>>
input auto "[1, 2, 3]" :: IO (Vector Natural)
[1,2,3]>>>
input auto "toMap { a = False, b = True }" :: IO (Map Text Bool)
fromList [("a",False),("b",True)]
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 genericAutoWith
and custom
InterpretOptions
, or using
DerivingVia
and Codec
from Dhall.Deriving.
Minimal complete definition
Nothing
Methods
autoWith :: InputNormalizer -> Decoder a Source #
default autoWith :: (Generic a, GenericFromDhall a (Rep a)) => InputNormalizer -> Decoder a Source #
Instances
FromDhall Bool Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Bool Source # | |
FromDhall Double Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Double Source # | |
FromDhall Int Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Int Source # | |
FromDhall Int8 Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Int8 Source # | |
FromDhall Int16 Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Int16 Source # | |
FromDhall Int32 Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Int32 Source # | |
FromDhall Int64 Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Int64 Source # | |
FromDhall Integer Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Integer Source # | |
FromDhall Natural Source # | |
Defined in Dhall.Marshal.Decode | |
FromDhall Word Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Word Source # | |
FromDhall Word8 Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Word8 Source # | |
FromDhall Word16 Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Word16 Source # | |
FromDhall Word32 Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Word32 Source # | |
FromDhall Word64 Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Word64 Source # | |
FromDhall () Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder () Source # | |
FromDhall Text Source # | |
Defined in Dhall.Marshal.Decode | |
FromDhall Void Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Void Source # | |
FromDhall Text Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Text Source # | |
FromDhall Scientific Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder Scientific Source # | |
FromDhall [Char] Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder [Char] Source # | |
FromDhall a => FromDhall [a] Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder [a] Source # | |
FromDhall a => FromDhall (Maybe a) Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder (Maybe a) Source # | |
FromDhall a => FromDhall (Seq a) Source # | |
Defined in Dhall.Marshal.Decode | |
(FromDhall a, Ord a, Show a) => FromDhall (Set a) Source # | Note that this instance will throw errors in the presence of duplicates in
the list. To ignore duplicates, use |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder (Set a) Source # | |
FromDhall a => FromDhall (Vector a) Source # | |
Defined in Dhall.Marshal.Decode | |
(FromDhall a, Hashable a, Ord a, Show a) => FromDhall (HashSet a) Source # | Note that this instance will throw errors in the presence of duplicates in
the list. To ignore duplicates, use |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder (HashSet a) Source # | |
(Functor f, FromDhall (f (Result f))) => FromDhall (Fix f) Source # | You can use this instance to marshal recursive types from Dhall to Haskell. Here is an example use of this instance: {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TemplateHaskell #-} import Data.Fix (Fix(..)) import Data.Text (Text) import Dhall (FromDhall) import GHC.Generics (Generic) import Numeric.Natural (Natural) import qualified Data.Fix as Fix import qualified Data.Functor.Foldable as Foldable import qualified Data.Functor.Foldable.TH as TH import qualified Dhall import qualified NeatInterpolation data Expr = Lit Natural | Add Expr Expr | Mul Expr Expr deriving (Show) TH.makeBaseFunctor ''Expr deriving instance Generic (ExprF a) deriving instance FromDhall a => FromDhall (ExprF a) example :: Text example = [NeatInterpolation.text| \(Expr : Type) -> let ExprF = < LitF : Natural | AddF : { _1 : Expr, _2 : Expr } | MulF : { _1 : Expr, _2 : Expr } > in \(Fix : ExprF -> Expr) -> let Lit = \(x : Natural) -> Fix (ExprF.LitF x) let Add = \(x : Expr) -> \(y : Expr) -> Fix (ExprF.AddF { _1 = x, _2 = y }) let Mul = \(x : Expr) -> \(y : Expr) -> Fix (ExprF.MulF { _1 = x, _2 = y }) in Add (Mul (Lit 3) (Lit 7)) (Add (Lit 1) (Lit 2)) |] convert :: Fix ExprF -> Expr convert = Fix.foldFix Foldable.embed main :: IO () main = do x <- Dhall.input Dhall.auto example :: IO (Fix ExprF) print (convert x :: Expr) |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder (Fix f) Source # | |
FromDhall (f (Result f)) => FromDhall (Result f) Source # | |
Defined in Dhall.Marshal.Decode | |
(ToDhall a, FromDhall b) => FromDhall (a -> b) Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder (a -> b) Source # | |
(FromDhall a, FromDhall b) => FromDhall (a, b) Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder (a, b) Source # | |
(Ord k, FromDhall k, FromDhall v) => FromDhall (Map k v) Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder (Map k v) Source # | |
(Eq k, Hashable k, FromDhall k, FromDhall v) => FromDhall (HashMap k v) Source # | |
Defined in Dhall.Marshal.Decode Methods autoWith :: InputNormalizer -> Decoder (HashMap k v) Source # | |
(Generic a, GenericFromDhall a (Rep a), ModifyOptions tag) => FromDhall (Codec tag a) Source # | |
Defined in Dhall.Deriving |
type Interpret = FromDhall Source #
Deprecated: Use FromDhall instead
A compatibility alias for FromDhall
.
auto :: FromDhall a => Decoder a Source #
Use the default input normalizer for interpreting an input.
auto = autoWith defaultInputNormalizer
Building decoders
Simple decoders
Decode ()
from an empty record.
>>>
input unit "{=}" -- GHC doesn't print the result if it is ()
Numbers
scientific :: Decoder Scientific Source #
Decode a Scientific
.
>>>
input scientific "1e100"
1.0e100
Textual
Containers
maybe :: Decoder a -> Decoder (Maybe a) Source #
Decode a Maybe
.
>>>
input (maybe natural) "Some 1"
Just 1
pair :: Decoder a -> Decoder b -> Decoder (a, b) Source #
Given a pair of Decoder
s, decode a tuple-record into their pairing.
>>>
input (pair natural bool) "{ _1 = 42, _2 = False }"
(42,False)
sequence :: Decoder a -> Decoder (Seq a) Source #
Decode a Seq
.
>>>
input (sequence natural) "[1, 2, 3]"
fromList [1,2,3]
vector :: Decoder a -> Decoder (Vector a) Source #
Decode a Vector
.
>>>
input (vector natural) "[1, 2, 3]"
[1,2,3]
setFromDistinctList :: (Ord a, Show a) => Decoder a -> Decoder (Set a) Source #
Decode a Set
from a List
with distinct elements.
>>>
input (setFromDistinctList natural) "[1, 2, 3]"
fromList [1,2,3]
An error is thrown if the list contains duplicates.
>>> input (setFromDistinctList natural) "[1, 1, 3]" *** Exception: Error: Failed extraction The expression type-checked successfully but the transformation to the target type failed with the following error: One duplicate element in the list: 1
>>> input (setFromDistinctList natural) "[1, 1, 3, 3]" *** Exception: Error: Failed extraction The expression type-checked successfully but the transformation to the target type failed with the following error: 2 duplicates were found in the list, including 1
setIgnoringDuplicates :: Ord a => Decoder a -> Decoder (Set a) Source #
Decode a Set
from a List
.
>>>
input (setIgnoringDuplicates natural) "[1, 2, 3]"
fromList [1,2,3]
Duplicate elements are ignored.
>>>
input (setIgnoringDuplicates natural) "[1, 1, 3]"
fromList [1,3]
hashSetFromDistinctList :: (Hashable a, Ord a, Show a) => Decoder a -> Decoder (HashSet a) Source #
Decode a HashSet
from a List
with distinct elements.
>>>
input (hashSetFromDistinctList natural) "[1, 2, 3]"
fromList [1,2,3]
An error is thrown if the list contains duplicates.
>>> input (hashSetFromDistinctList natural) "[1, 1, 3]" *** Exception: Error: Failed extraction The expression type-checked successfully but the transformation to the target type failed with the following error: One duplicate element in the list: 1
>>> input (hashSetFromDistinctList natural) "[1, 1, 3, 3]" *** Exception: Error: Failed extraction The expression type-checked successfully but the transformation to the target type failed with the following error: 2 duplicates were found in the list, including 1
hashSetIgnoringDuplicates :: (Hashable a, Ord a) => Decoder a -> Decoder (HashSet a) Source #
Decode a HashSet
from a List
.
>>>
input (hashSetIgnoringDuplicates natural) "[1, 2, 3]"
fromList [1,2,3]
Duplicate elements are ignored.
>>>
input (hashSetIgnoringDuplicates natural) "[1, 1, 3]"
fromList [1,3]
map :: Ord k => Decoder k -> Decoder v -> Decoder (Map k v) Source #
Decode a Map
from a toMap
expression or generally a Prelude.Map.Type
.
>>>
input (Dhall.map strictText bool) "toMap { a = True, b = False }"
fromList [("a",True),("b",False)]>>>
input (Dhall.map strictText bool) "[ { mapKey = \"foo\", mapValue = True } ]"
fromList [("foo",True)]
If there are duplicate mapKey
s, later mapValue
s take precedence:
>>>
let expr = "[ { mapKey = 1, mapValue = True }, { mapKey = 1, mapValue = False } ]"
>>>
input (Dhall.map natural bool) expr
fromList [(1,False)]
hashMap :: (Eq k, Hashable k) => Decoder k -> Decoder v -> Decoder (HashMap k v) Source #
Decode a HashMap
from a toMap
expression or generally a Prelude.Map.Type
.
>>>
fmap (List.sort . HashMap.toList) (input (Dhall.hashMap strictText bool) "toMap { a = True, b = False }")
[("a",True),("b",False)]>>>
fmap (List.sort . HashMap.toList) (input (Dhall.hashMap strictText bool) "[ { mapKey = \"foo\", mapValue = True } ]")
[("foo",True)]
If there are duplicate mapKey
s, later mapValue
s take precedence:
>>>
let expr = "[ { mapKey = 1, mapValue = True }, { mapKey = 1, mapValue = False } ]"
>>>
input (Dhall.hashMap natural bool) expr
fromList [(1,False)]
pairFromMapEntry :: Decoder k -> Decoder v -> Decoder (k, v) Source #
Decode a tuple from a Prelude.Map.Entry
record.
>>>
input (pairFromMapEntry strictText natural) "{ mapKey = \"foo\", mapValue = 3 }"
("foo",3)
Functions
function :: Encoder a -> Decoder b -> Decoder (a -> b) Source #
Decode a Dhall function into a Haskell function.
>>>
f <- input (function inject bool) "Natural/even" :: IO (Natural -> Bool)
>>>
f 0
True>>>
f 1
False
functionWith :: InputNormalizer -> Encoder a -> Decoder b -> Decoder (a -> b) Source #
Decode a Dhall function into a Haskell function using the specified normalizer.
>>>
f <- input (functionWith defaultInputNormalizer inject bool) "Natural/even" :: IO (Natural -> Bool)
>>>
f 0
True>>>
f 1
False
Records
newtype RecordDecoder a Source #
The RecordDecoder
applicative functor allows you to build a Decoder
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 decoder has type Decoder
Project
, but we can't build that out of any
smaller decoders, as Decoder
s cannot be combined (they are only Functor
s).
However, we can use a RecordDecoder
to build a Decoder
for Project
:
>>>
:{
project :: Decoder Project project = record ( Project <$> field "name" strictText <*> field "description" strictText <*> field "stars" natural ) :}
Constructors
RecordDecoder (Product (Const (Map Text (Expector (Expr Src Void)))) (Compose ((->) (Expr Src Void)) (Extractor Src Void)) a) |
Instances
Functor RecordDecoder Source # | |
Defined in Dhall.Marshal.Decode Methods fmap :: (a -> b) -> RecordDecoder a -> RecordDecoder b (<$) :: a -> RecordDecoder b -> RecordDecoder a | |
Applicative RecordDecoder Source # | |
Defined in Dhall.Marshal.Decode Methods pure :: a -> RecordDecoder a (<*>) :: RecordDecoder (a -> b) -> RecordDecoder a -> RecordDecoder b liftA2 :: (a -> b -> c) -> RecordDecoder a -> RecordDecoder b -> RecordDecoder c (*>) :: RecordDecoder a -> RecordDecoder b -> RecordDecoder b (<*) :: RecordDecoder a -> RecordDecoder b -> RecordDecoder a |
record :: RecordDecoder a -> Decoder a Source #
Run a RecordDecoder
to build a Decoder
.
Unions
newtype UnionDecoder a Source #
The UnionDecoder
monoid allows you to build a Decoder
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 : Text | Queued : Natural | Errored : Text >.Result "Finish successfully"
Our decoder has type Decoder
Status
, but we can't build that out of any
smaller decoders, as Decoder
s cannot be combined (they are only Functor
s).
However, we can use a UnionDecoder
to build a Decoder
for Status
:
>>>
:{
status :: Decoder Status status = union ( ( Queued <$> constructor "Queued" natural ) <> ( Result <$> constructor "Result" strictText ) <> ( Errored <$> constructor "Errored" strictText ) ) :}
Constructors
UnionDecoder (Compose (Map Text) Decoder a) |
Instances
Functor UnionDecoder Source # | |
Defined in Dhall.Marshal.Decode Methods fmap :: (a -> b) -> UnionDecoder a -> UnionDecoder b (<$) :: a -> UnionDecoder b -> UnionDecoder a | |
Semigroup (UnionDecoder a) Source # | |
Defined in Dhall.Marshal.Decode Methods (<>) :: UnionDecoder a -> UnionDecoder a -> UnionDecoder a sconcat :: NonEmpty (UnionDecoder a) -> UnionDecoder a stimes :: Integral b => b -> UnionDecoder a -> UnionDecoder a | |
Monoid (UnionDecoder a) Source # | |
Defined in Dhall.Marshal.Decode Methods mempty :: UnionDecoder a mappend :: UnionDecoder a -> UnionDecoder a -> UnionDecoder a mconcat :: [UnionDecoder a] -> UnionDecoder a |
union :: UnionDecoder a -> Decoder a Source #
Run a UnionDecoder
to build a Decoder
.
constructor :: Text -> Decoder a -> UnionDecoder a Source #
Parse a single constructor of a union.
Generic decoding
class GenericFromDhall t f where Source #
This is the underlying class that powers the FromDhall
class's support
for automatically deriving a generic implementation.
Methods
genericAutoWithNormalizer :: Proxy t -> InputNormalizer -> InterpretOptions -> State Int (Decoder (f a)) Source #
Instances
GenericFromDhall (t :: k1) (U1 :: k2 -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a :: k). Proxy t -> InputNormalizer -> InterpretOptions -> State Int (Decoder (U1 a)) Source # | |
GenericFromDhall (t :: k1) (V1 :: k2 -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a :: k). Proxy t -> InputNormalizer -> InterpretOptions -> State Int (Decoder (V1 a)) Source # | |
(GenericFromDhall t (f :*: g), GenericFromDhall t (h :*: i)) => GenericFromDhall (t :: k1) ((f :*: g) :*: (h :*: i) :: k2 -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a :: k). Proxy t -> InputNormalizer -> InterpretOptions -> State Int (Decoder (((f :*: g) :*: (h :*: i)) a)) Source # | |
GenericFromDhallUnion t (f :+: g) => GenericFromDhall (t :: k1) (f :+: g :: k2 -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a :: k). Proxy t -> InputNormalizer -> InterpretOptions -> State Int (Decoder ((f :+: g) a)) Source # | |
(Selector s1, Selector s2, FromDhall a1, FromDhall a2) => GenericFromDhall (t :: k1) (M1 S s1 (K1 i1 a1 :: k2 -> Type) :*: M1 S s2 (K1 i2 a2 :: k2 -> Type) :: k2 -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a :: k). Proxy t -> InputNormalizer -> InterpretOptions -> State Int (Decoder ((M1 S s1 (K1 i1 a1) :*: M1 S s2 (K1 i2 a2)) a)) Source # | |
(Selector s, FromDhall a, GenericFromDhall t (f :*: g)) => GenericFromDhall (t :: k1) (M1 S s (K1 i a :: k2 -> Type) :*: (f :*: g) :: k2 -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a0 :: k). Proxy t -> InputNormalizer -> InterpretOptions -> State Int (Decoder ((M1 S s (K1 i a) :*: (f :*: g)) a0)) Source # | |
(GenericFromDhall t (f :*: g), Selector s, FromDhall a) => GenericFromDhall (t :: k1) ((f :*: g) :*: M1 S s (K1 i a :: k2 -> Type) :: k2 -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a0 :: k). Proxy t -> InputNormalizer -> InterpretOptions -> State Int (Decoder (((f :*: g) :*: M1 S s (K1 i a)) a0)) Source # | |
GenericFromDhall t f => GenericFromDhall (t :: k1) (M1 C c f :: k2 -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a :: k). Proxy t -> InputNormalizer -> InterpretOptions -> State Int (Decoder (M1 C c f a)) Source # | |
GenericFromDhall t f => GenericFromDhall (t :: k1) (M1 D d f :: k2 -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a :: k). Proxy t -> InputNormalizer -> InterpretOptions -> State Int (Decoder (M1 D d f a)) Source # | |
(Selector s, FromDhall a) => GenericFromDhall (t :: k1) (M1 S s (K1 i a :: k2 -> Type) :: k2 -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a0 :: k). Proxy t -> InputNormalizer -> InterpretOptions -> State Int (Decoder (M1 S s (K1 i a) a0)) Source # | |
GenericFromDhall (a2 :: Type) (M1 S s1 (K1 i1 a1 :: k -> Type) :*: M1 S s2 (K1 i2 a2 :: k -> Type) :: k -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a :: k0). Proxy a2 -> InputNormalizer -> InterpretOptions -> State Int (Decoder ((M1 S s1 (K1 i1 a1) :*: M1 S s2 (K1 i2 a2)) a)) Source # | |
GenericFromDhall (a1 :: Type) (M1 S s1 (K1 i1 a1 :: k -> Type) :*: M1 S s2 (K1 i2 a2 :: k -> Type) :: k -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a :: k0). Proxy a1 -> InputNormalizer -> InterpretOptions -> State Int (Decoder ((M1 S s1 (K1 i1 a1) :*: M1 S s2 (K1 i2 a2)) a)) Source # | |
GenericFromDhall (a :: Type) (M1 S s (K1 i a :: k -> Type) :: k -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericAutoWithNormalizer :: forall (a0 :: k0). Proxy a -> InputNormalizer -> InterpretOptions -> State Int (Decoder (M1 S s (K1 i a) a0)) Source # |
class GenericFromDhallUnion t f where Source #
This is the underlying class that powers the FromDhall
class's support
for automatically deriving a generic implementation for a union type.
Methods
genericUnionAutoWithNormalizer :: Proxy t -> InputNormalizer -> InterpretOptions -> UnionDecoder (f a) Source #
Instances
(GenericFromDhallUnion t f1, GenericFromDhallUnion t f2) => GenericFromDhallUnion (t :: k1) (f1 :+: f2 :: k2 -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericUnionAutoWithNormalizer :: forall (a :: k). Proxy t -> InputNormalizer -> InterpretOptions -> UnionDecoder ((f1 :+: f2) a) Source # | |
(Constructor c1, GenericFromDhall t f1) => GenericFromDhallUnion (t :: k1) (M1 C c1 f1 :: k2 -> Type) Source # | |
Defined in Dhall.Marshal.Decode Methods genericUnionAutoWithNormalizer :: forall (a :: k). Proxy t -> InputNormalizer -> InterpretOptions -> UnionDecoder (M1 C c1 f1 a) Source # |
genericAuto :: (Generic a, GenericFromDhall a (Rep a)) => Decoder a Source #
genericAuto
is the default implementation for auto
if you derive
FromDhall
. The difference is that you can use genericAuto
without
having to explicitly provide a FromDhall
instance for a type as long as
the type derives Generic
.
genericAutoWith :: (Generic a, GenericFromDhall a (Rep a)) => InterpretOptions -> Decoder a Source #
genericAutoWith
is a configurable version of genericAuto
.
Decoding errors
newtype DhallErrors e Source #
A newtype suitable for collecting one or more errors.
Constructors
DhallErrors | |
Fields
|
Instances
showDhallErrors :: Show e => String -> DhallErrors e -> String Source #
Render a given prefix and some errors to a string.
data InvalidDecoder s a Source #
Every Decoder
must obey the contract that if an expression's type matches
the expected
type then the extract
function must not fail with a type
error. However, decoding may still fail for other reasons (such as the
decoder for Set
s rejecting a Dhall List
with duplicate
elements).
This error type is used to indicate an internal error in the implementation
of a Decoder
where the expected type matched the Dhall expression, but the
expression supplied to the extraction function did not match the expected
type. If this happens that means that the Decoder
itself needs to be
fixed.
Constructors
InvalidDecoder | |
Fields
|
Instances
(Pretty s, Pretty a, Typeable s, Typeable a) => Show (InvalidDecoder s a) Source # | |
Defined in Dhall.Marshal.Decode Methods showsPrec :: Int -> InvalidDecoder s a -> ShowS show :: InvalidDecoder s a -> String showList :: [InvalidDecoder s a] -> ShowS | |
(Pretty s, Typeable s, Pretty a, Typeable a) => Exception (InvalidDecoder s a) Source # | |
Defined in Dhall.Marshal.Decode Methods toException :: InvalidDecoder s a -> SomeException fromException :: SomeException -> Maybe (InvalidDecoder s a) displayException :: InvalidDecoder s a -> String |
Extraction errors
type ExtractErrors s a = DhallErrors (ExtractError s a) Source #
One or more errors returned from extracting a Dhall expression to a Haskell expression.
data ExtractError s a Source #
Extraction of a value can fail for two reasons, either a type mismatch (which should not happen,
as expressions are type-checked against the expected type before being passed to extract
), or
a term-level error, described with a freeform text value.
Constructors
TypeMismatch (InvalidDecoder s a) | |
ExpectedTypeError ExpectedTypeError | |
ExtractError Text |
Instances
(Pretty s, Pretty a, Typeable s, Typeable a) => Show (ExtractError s a) Source # | |
Defined in Dhall.Marshal.Decode Methods showsPrec :: Int -> ExtractError s a -> ShowS show :: ExtractError s a -> String showList :: [ExtractError s a] -> ShowS | |
(Pretty s, Pretty a, Typeable s, Typeable a) => Show (ExtractErrors s a) Source # | |
Defined in Dhall.Marshal.Decode Methods showsPrec :: Int -> ExtractErrors s a -> ShowS show :: ExtractErrors s a -> String showList :: [ExtractErrors s a] -> ShowS | |
(Pretty s, Pretty a, Typeable s, Typeable a) => Exception (ExtractError s a) Source # | |
Defined in Dhall.Marshal.Decode Methods toException :: ExtractError s a -> SomeException fromException :: SomeException -> Maybe (ExtractError s a) displayException :: ExtractError s a -> String |
type Extractor s a = Validation (ExtractErrors s a) Source #
Useful synonym for the Validation
type used when marshalling Dhall
expressions.
typeError :: Expector (Expr s a) -> Expr s a -> Extractor s a b Source #
Generate a type error during extraction by specifying the expected type and the actual type. The expected type is not yet determined.
type MonadicExtractor s a = Either (ExtractErrors s a) Source #
Useful synonym for the equivalent Either
type used when marshalling Dhall
code.
toMonadic :: Extractor s a b -> MonadicExtractor s a b Source #
Switches from an Applicative
extraction result, able to accumulate errors,
to a Monad
extraction result, able to chain sequential operations.
fromMonadic :: MonadicExtractor s a b -> Extractor s a b Source #
Switches from a Monad
extraction result, able to chain sequential errors,
to an Applicative
extraction result, able to accumulate errors.
Typing errors
type ExpectedTypeErrors = DhallErrors ExpectedTypeError Source #
One or more errors returned when determining the Dhall type of a Haskell expression.
data ExpectedTypeError Source #
Error type used when determining the Dhall type of a Haskell expression.
Constructors
RecursiveTypeError |
Instances
Eq ExpectedTypeError Source # | |
Defined in Dhall.Marshal.Decode Methods (==) :: ExpectedTypeError -> ExpectedTypeError -> Bool (/=) :: ExpectedTypeError -> ExpectedTypeError -> Bool | |
Show ExpectedTypeError Source # | |
Defined in Dhall.Marshal.Decode Methods showsPrec :: Int -> ExpectedTypeError -> ShowS show :: ExpectedTypeError -> String showList :: [ExpectedTypeError] -> ShowS | |
Show ExpectedTypeErrors Source # | |
Defined in Dhall.Marshal.Decode Methods showsPrec :: Int -> ExpectedTypeErrors -> ShowS show :: ExpectedTypeErrors -> String showList :: [ExpectedTypeErrors] -> ShowS | |
Exception ExpectedTypeError Source # | |
Defined in Dhall.Marshal.Decode Methods toException :: ExpectedTypeError -> SomeException fromException :: SomeException -> Maybe ExpectedTypeError displayException :: ExpectedTypeError -> String |
type Expector = Validation ExpectedTypeErrors Source #
Useful synonym for the Validation
type used when marshalling Dhall
expressions.
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 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 (== '_') })
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
ToDhall (f (Result f)) => ToDhall (Result f) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Result f) Source # | |
FromDhall (f (Result f)) => FromDhall (Result f) Source # | |
Defined in Dhall.Marshal.Decode |
Re-exports
Instances
Enum Natural | |
Defined in GHC.Enum | |
Eq Natural | |
Integral Natural | |
Defined in GHC.Real | |
Data Natural | |
Defined in 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 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 | |
Num Natural | |
Ord Natural | |
Read Natural | |
Real Natural | |
Defined in GHC.Real Methods toRational :: Natural -> Rational | |
Show Natural | |
Ix Natural | |
NFData Natural | |
Defined in Control.DeepSeq | |
PrintfArg Natural | |
Defined in Text.Printf | |
Bits Natural | |
Defined in Data.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 | |
Subtractive Natural | |
Hashable Natural | |
Defined in Data.Hashable.Class | |
Pretty Natural | |
Defined in Prettyprinter.Internal | |
Serialise Natural | |
Defined in Codec.Serialise.Class | |
FromJSON Natural | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSONKey Natural | |
Defined in Data.Aeson.Types.FromJSON | |
ToJSON Natural | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Natural -> Encoding toJSONList :: [Natural] -> Value toEncodingList :: [Natural] -> Encoding | |
ToJSONKey Natural | |
Defined in Data.Aeson.Types.ToJSON | |
UniformRange Natural | |
Defined in System.Random.Internal | |
ToDhall Natural Source # | |
Defined in Dhall.Marshal.Encode Methods | |
FromDhall Natural Source # | |
Defined in Dhall.Marshal.Decode | |
Lift Natural | |
type Difference Natural | |
Defined in Basement.Numerical.Subtractive |
Instances
Monad Seq | |
Functor Seq | |
MonadFix Seq | |
Defined in Data.Sequence.Internal | |
Applicative 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 | |
Traversable Seq | |
MonadPlus Seq | |
Alternative Seq | |
Eq1 Seq | |
Defined in Data.Sequence.Internal | |
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 | |
MonadZip Seq | |
UnzipWith Seq | |
Defined in Data.Sequence.Internal Methods unzipWith' :: (x -> (a, b)) -> Seq x -> (Seq a, Seq b) | |
FromJSON1 Seq | |
Defined in Data.Aeson.Types.FromJSON Methods liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Seq a) liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Seq a] | |
ToJSON1 Seq | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> Seq a -> Value liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Seq a] -> Value liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Seq a -> Encoding liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Seq a] -> Encoding | |
IsList (Seq a) | |
Eq a => Eq (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) | |
Ord a => Ord (Seq a) | |
Read a => Read (Seq a) | |
Defined in Data.Sequence.Internal | |
Show a => Show (Seq a) | |
a ~ Char => IsString (Seq a) | |
Defined in Data.Sequence.Internal Methods fromString :: String -> Seq a | |
Semigroup (Seq a) | |
Monoid (Seq a) | |
NFData a => NFData (Seq a) | |
Defined in Data.Sequence.Internal | |
Ord a => Stream (Seq a) | |
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) | |
Defined in Codec.Serialise.Class | |
FromJSON a => FromJSON (Seq a) | |
Defined in Data.Aeson.Types.FromJSON | |
ToJSON a => ToJSON (Seq a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Seq a -> Encoding toJSONList :: [Seq a] -> Value toEncodingList :: [Seq a] -> Encoding | |
ToDhall a => ToDhall (Seq a) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Seq a) Source # | |
FromDhall a => FromDhall (Seq a) Source # | |
Defined in Dhall.Marshal.Decode | |
type Item (Seq a) | |
Defined in Data.Sequence.Internal type Item (Seq a) = a | |
type Token (Seq a) | |
Defined in Text.Megaparsec.Stream type Token (Seq a) = a | |
type Tokens (Seq a) | |
Defined in Text.Megaparsec.Stream |
Instances
Hashable Text | |
Defined in Data.Hashable.Class | |
Pretty Text | |
Defined in Prettyprinter.Internal | |
Stream Text | |
Defined in Text.Megaparsec.Stream Methods tokenToChunk :: Proxy Text -> Token Text -> Tokens Text tokensToChunk :: Proxy Text -> [Token Text] -> Tokens Text chunkToTokens :: Proxy Text -> Tokens Text -> [Token Text] chunkLength :: Proxy Text -> Tokens Text -> Int chunkEmpty :: Proxy Text -> Tokens Text -> Bool take1_ :: Text -> Maybe (Token Text, Text) takeN_ :: Int -> Text -> Maybe (Tokens Text, Text) takeWhile_ :: (Token Text -> Bool) -> Text -> (Tokens Text, Text) | |
TraversableStream Text | |
Defined in Text.Megaparsec.Stream Methods reachOffset :: Int -> PosState Text -> (Maybe String, PosState Text) reachOffsetNoLine :: Int -> PosState Text -> PosState Text | |
VisualStream Text | |
Defined in Text.Megaparsec.Stream Methods showTokens :: Proxy Text -> NonEmpty (Token Text) -> String tokensLength :: Proxy Text -> NonEmpty (Token Text) -> Int | |
Serialise Text | |
Defined in Codec.Serialise.Class | |
FromJSON Text | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSONKey Text | |
Defined in Data.Aeson.Types.FromJSON | |
KeyValue Object | |
Defined in Data.Aeson.Types.ToJSON | |
KeyValue Pair | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSON Text | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Text -> Encoding toJSONList :: [Text] -> Value toEncodingList :: [Text] -> Encoding | |
ToJSONKey Text | |
Defined in Data.Aeson.Types.ToJSON | |
Chunk Text | |
Defined in Data.Attoparsec.Internal.Types Associated Types type ChunkElem Text Methods pappendChunk :: State Text -> Text -> State Text atBufferEnd :: Text -> State Text -> Pos bufferElemAt :: Text -> Pos -> State Text -> Maybe (ChunkElem Text, Int) chunkElemToChar :: Text -> ChunkElem Text -> Char | |
FoldCase Text | |
Defined in Data.CaseInsensitive.Internal | |
ToDhall Text Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Text Source # | |
FromDhall Text Source # | |
Defined in Dhall.Marshal.Decode | |
MonadParsec Void Text Parser | |
Defined in Dhall.Parser.Combinators Methods parseError :: ParseError Text Void -> Parser a label :: String -> Parser a -> Parser a hidden :: Parser a -> Parser a lookAhead :: Parser a -> Parser a notFollowedBy :: Parser a -> Parser () withRecovery :: (ParseError Text Void -> Parser a) -> Parser a -> Parser a observing :: Parser a -> Parser (Either (ParseError Text Void) a) token :: (Token Text -> Maybe a) -> Set (ErrorItem (Token Text)) -> Parser a tokens :: (Tokens Text -> Tokens Text -> Bool) -> Tokens Text -> Parser (Tokens Text) takeWhileP :: Maybe String -> (Token Text -> Bool) -> Parser (Tokens Text) takeWhile1P :: Maybe String -> (Token Text -> Bool) -> Parser (Tokens Text) takeP :: Maybe String -> Int -> Parser (Tokens Text) getParserState :: Parser (State Text Void) updateParserState :: (State Text Void -> State Text Void) -> Parser () | |
Monad m => Stream Text m Char | |
Defined in Text.Parsec.Prim | |
FromPairs Value (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON Methods fromPairs :: DList Pair -> Value | |
v ~ Value => KeyValuePair v (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON Methods pair :: String -> v -> DList Pair | |
type Item Text | |
type Token Text | |
Defined in Text.Megaparsec.Stream type Token Text = Char | |
type Tokens Text | |
Defined in Text.Megaparsec.Stream | |
type State Text | |
Defined in Data.Attoparsec.Internal.Types type State Text = Buffer | |
type ChunkElem Text | |
Defined in Data.Attoparsec.Internal.Types type ChunkElem Text = Char |
Instances
Monad Vector | |
Functor Vector | |
MonadFix Vector | |
Defined in Data.Vector | |
MonadFail Vector | |
Defined in Data.Vector | |
Applicative 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 | |
Traversable Vector | |
MonadPlus Vector | |
Alternative Vector | |
NFData1 Vector | |
Defined in Data.Vector | |
Eq1 Vector | |
Defined in Data.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 | |
MonadZip Vector | |
FromJSON1 Vector | |
Defined in Data.Aeson.Types.FromJSON Methods liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Vector a) liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Vector a] | |
ToJSON1 Vector | |
Defined in Data.Aeson.Types.ToJSON Methods 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 | |
Vector Vector a | |
Defined in Data.Vector Methods 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 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) | |
Ord a => Ord (Vector a) | |
Read a => Read (Vector a) | |
Defined in Data.Vector | |
Show a => Show (Vector a) | |
Semigroup (Vector a) | |
Monoid (Vector a) | |
NFData a => NFData (Vector a) | |
Defined in Data.Vector | |
Serialise a => Serialise (Vector a) | |
Defined in Codec.Serialise.Class Methods encode :: Vector a -> Encoding decode :: Decoder s (Vector a) encodeList :: [Vector a] -> Encoding decodeList :: Decoder s [Vector a] | |
FromJSON a => FromJSON (Vector a) | |
Defined in Data.Aeson.Types.FromJSON | |
ToJSON a => ToJSON (Vector a) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Vector a -> Encoding toJSONList :: [Vector a] -> Value toEncodingList :: [Vector a] -> Encoding | |
ToDhall a => ToDhall (Vector a) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Vector a) Source # | |
FromDhall a => FromDhall (Vector a) Source # | |
Defined in Dhall.Marshal.Decode | |
type Mutable Vector | |
Defined in Data.Vector type Mutable Vector = MVector | |
type Item (Vector a) | |
Defined in Data.Vector type Item (Vector a) = a |
Minimal complete definition
from, to
Instances
Generic Bool | |
Defined in GHC.Generics Associated Types type Rep Bool :: Type -> Type | |
Generic Ordering | |
Defined in GHC.Generics Associated Types type Rep Ordering :: Type -> Type | |
Generic Exp | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Exp :: Type -> Type | |
Generic Match | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Match :: Type -> Type | |
Generic Clause | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Clause :: Type -> Type | |
Generic Pat | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Pat :: Type -> Type | |
Generic Type | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Type :: Type -> Type | |
Generic Dec | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Dec :: Type -> Type | |
Generic Name | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Name :: Type -> Type | |
Generic FunDep | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep FunDep :: Type -> Type | |
Generic InjectivityAnn | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep InjectivityAnn :: Type -> Type | |
Generic Overlap | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Overlap :: Type -> Type | |
Generic () | |
Defined in GHC.Generics Associated Types type Rep () :: Type -> Type | |
Generic Lit | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Lit :: Type -> Type | |
Generic NameFlavour | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep NameFlavour :: Type -> Type | |
Generic All | |
Defined in Data.Semigroup.Internal Associated Types type Rep All :: Type -> Type | |
Generic Any | |
Defined in Data.Semigroup.Internal Associated Types type Rep Any :: Type -> Type | |
Generic ExitCode | |
Defined in GHC.IO.Exception Associated Types type Rep ExitCode :: Type -> Type | |
Generic Version | |
Defined in Data.Version Associated Types type Rep Version :: Type -> Type | |
Generic Void | |
Generic Associativity | |
Defined in GHC.Generics Associated Types type Rep Associativity :: Type -> Type | |
Generic DecidedStrictness | |
Defined in GHC.Generics Associated Types type Rep DecidedStrictness :: Type -> Type | |
Generic Fixity | |
Defined in GHC.Generics Associated Types type Rep Fixity :: Type -> Type | |
Generic SourceStrictness | |
Defined in GHC.Generics Associated Types type Rep SourceStrictness :: Type -> Type | |
Generic SourceUnpackedness | |
Defined in GHC.Generics Associated Types type Rep SourceUnpackedness :: Type -> Type | |
Generic SHA256Digest Source # | |
Defined in Dhall.Crypto Associated Types type Rep SHA256Digest :: Type -> Type | |
Generic URIAuth | |
Defined in Network.URI Associated Types type Rep URIAuth :: Type -> Type | |
Generic URI | |
Defined in Network.URI Associated Types type Rep URI :: Type -> Type | |
Generic ForeignSrcLang | |
Defined in GHC.ForeignSrcLang.Type Associated Types type Rep ForeignSrcLang :: Type -> Type | |
Generic Extension | |
Defined in GHC.LanguageExtensions.Type Associated Types type Rep Extension :: Type -> Type | |
Generic AnnLookup | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep AnnLookup :: Type -> Type | |
Generic AnnTarget | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep AnnTarget :: Type -> Type | |
Generic Bang | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Bang :: Type -> Type | |
Generic Body | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Body :: Type -> Type | |
Generic Bytes | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Bytes :: Type -> Type | |
Generic Callconv | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Callconv :: Type -> Type | |
Generic Con | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Con :: Type -> Type | |
Generic DecidedStrictness | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep DecidedStrictness :: Type -> Type | |
Generic DerivClause | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep DerivClause :: Type -> Type | |
Generic DerivStrategy | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep DerivStrategy :: Type -> Type | |
Generic FamilyResultSig | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep FamilyResultSig :: Type -> Type | |
Generic Fixity | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Fixity :: Type -> Type | |
Generic FixityDirection | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep FixityDirection :: Type -> Type | |
Generic Foreign | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Foreign :: Type -> Type | |
Generic Guard | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Guard :: Type -> Type | |
Generic Info | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Info :: Type -> Type | |
Generic Inline | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Inline :: Type -> Type | |
Generic Loc | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Loc :: Type -> Type | |
Generic ModName | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep ModName :: Type -> Type | |
Generic Module | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Module :: Type -> Type | |
Generic ModuleInfo | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep ModuleInfo :: Type -> Type | |
Generic NameSpace | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep NameSpace :: Type -> Type | |
Generic OccName | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep OccName :: Type -> Type | |
Generic PatSynArgs | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep PatSynArgs :: Type -> Type | |
Generic PatSynDir | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep PatSynDir :: Type -> Type | |
Generic Phases | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Phases :: Type -> Type | |
Generic PkgName | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep PkgName :: Type -> Type | |
Generic Pragma | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Pragma :: Type -> Type | |
Generic Range | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Range :: Type -> Type | |
Generic Role | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Role :: Type -> Type | |
Generic RuleBndr | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep RuleBndr :: Type -> Type | |
Generic RuleMatch | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep RuleMatch :: Type -> Type | |
Generic Safety | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Safety :: Type -> Type | |
Generic SourceStrictness | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep SourceStrictness :: Type -> Type | |
Generic SourceUnpackedness | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep SourceUnpackedness :: Type -> Type | |
Generic Stmt | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Stmt :: Type -> Type | |
Generic TyLit | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep TyLit :: Type -> Type | |
Generic TySynEqn | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep TySynEqn :: Type -> Type | |
Generic TyVarBndr | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep TyVarBndr :: Type -> Type | |
Generic TypeFamilyHead | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep TypeFamilyHead :: Type -> Type | |
Generic Mode | |
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types type Rep Mode :: Type -> Type | |
Generic Style | |
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types type Rep Style :: Type -> Type | |
Generic TextDetails | |
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types type Rep TextDetails :: Type -> Type | |
Generic Doc | |
Defined in Text.PrettyPrint.HughesPJ Associated Types type Rep Doc :: Type -> Type | |
Generic Const Source # | |
Generic Var Source # | |
Generic InvalidPosException | |
Defined in Text.Megaparsec.Pos Associated Types type Rep InvalidPosException :: Type -> Type | |
Generic Pos | |
Defined in Text.Megaparsec.Pos Associated Types type Rep Pos :: Type -> Type | |
Generic SourcePos | |
Defined in Text.Megaparsec.Pos Associated Types type Rep SourcePos :: Type -> Type | |
Generic Src Source # | |
Generic CharacterSet Source # | |
Defined in Dhall.Pretty.Internal Associated Types type Rep CharacterSet :: Type -> Type | |
Generic Import Source # | |
Generic ImportHashed Source # | |
Defined in Dhall.Syntax Associated Types type Rep ImportHashed :: Type -> Type | |
Generic ImportMode Source # | |
Defined in Dhall.Syntax Associated Types type Rep ImportMode :: Type -> Type | |
Generic ImportType Source # | |
Defined in Dhall.Syntax Associated Types type Rep ImportType :: Type -> Type | |
Generic URL Source # | |
Generic Scheme Source # | |
Generic FilePrefix Source # | |
Defined in Dhall.Syntax Associated Types type Rep FilePrefix :: Type -> Type | |
Generic File Source # | |
Generic Directory Source # | |
Generic DhallDouble Source # | |
Defined in Dhall.Syntax Associated Types type Rep DhallDouble :: Type -> Type | |
Generic Half | |
Defined in Numeric.Half.Internal Associated Types type Rep Half :: Type -> Type | |
Generic Value | |
Defined in Data.Aeson.Types.Internal Associated Types type Rep Value :: Type -> Type | |
Generic CompressionLevel | |
Defined in Codec.Compression.Zlib.Stream Associated Types type Rep CompressionLevel :: Type -> Type | |
Generic CompressionStrategy | |
Defined in Codec.Compression.Zlib.Stream Associated Types type Rep CompressionStrategy :: Type -> Type | |
Generic Format | |
Defined in Codec.Compression.Zlib.Stream Associated Types type Rep Format :: Type -> Type | |
Generic MemoryLevel | |
Defined in Codec.Compression.Zlib.Stream Associated Types type Rep MemoryLevel :: Type -> Type | |
Generic Method | |
Defined in Codec.Compression.Zlib.Stream Associated Types type Rep Method :: Type -> Type | |
Generic WindowBits | |
Defined in Codec.Compression.Zlib.Stream Associated Types type Rep WindowBits :: Type -> Type | |
Generic ColorOptions | |
Defined in Text.Pretty.Simple.Internal.Color Associated Types type Rep ColorOptions :: Type -> Type | |
Generic Style | |
Defined in Text.Pretty.Simple.Internal.Color Associated Types type Rep Style :: Type -> Type | |
Generic CheckColorTty | |
Defined in Text.Pretty.Simple.Internal.Printer Associated Types type Rep CheckColorTty :: Type -> Type | |
Generic OutputOptions | |
Defined in Text.Pretty.Simple.Internal.Printer Associated Types type Rep OutputOptions :: Type -> Type | |
Generic StringOutputStyle | |
Defined in Text.Pretty.Simple.Internal.Printer Associated Types type Rep StringOutputStyle :: Type -> Type | |
Generic Expr | |
Defined in Text.Pretty.Simple.Internal.Expr Associated Types type Rep Expr :: Type -> Type | |
Generic [a] | |
Defined in GHC.Generics Associated Types type Rep [a] :: Type -> Type | |
Generic (Maybe a) | |
Defined in GHC.Generics Associated Types type Rep (Maybe a) :: Type -> Type | |
Generic (Par1 p) | |
Defined in GHC.Generics Associated Types type Rep (Par1 p) :: Type -> Type | |
Generic (NonEmpty a) | |
Defined in GHC.Generics Associated Types type Rep (NonEmpty a) :: Type -> Type | |
Generic (Down a) | |
Defined in GHC.Generics Associated Types type Rep (Down a) :: Type -> Type | |
Generic (Dual a) | |
Defined in Data.Semigroup.Internal Associated Types type Rep (Dual a) :: Type -> Type | |
Generic (First a) | |
Defined in Data.Semigroup Associated Types type Rep (First a) :: Type -> Type | |
Generic (First a) | |
Defined in Data.Monoid Associated Types type Rep (First a) :: Type -> Type | |
Generic (Identity a) | |
Defined in Data.Functor.Identity Associated Types type Rep (Identity a) :: Type -> Type | |
Generic (Last a) | |
Defined in Data.Semigroup Associated Types type Rep (Last a) :: Type -> Type | |
Generic (Last a) | |
Defined in Data.Monoid Associated Types type Rep (Last a) :: Type -> Type | |
Generic (Max a) | |
Defined in Data.Semigroup Associated Types type Rep (Max a) :: Type -> Type | |
Generic (Min a) | |
Defined in Data.Semigroup Associated Types type Rep (Min a) :: Type -> Type | |
Generic (Option a) | |
Defined in Data.Semigroup Associated Types type Rep (Option a) :: Type -> Type | |
Generic (Product a) | |
Defined in Data.Semigroup.Internal Associated Types type Rep (Product a) :: Type -> Type | |
Generic (Sum a) | |
Defined in Data.Semigroup.Internal Associated Types type Rep (Sum a) :: Type -> Type | |
Generic (WrappedMonoid m) | |
Defined in Data.Semigroup Associated Types type Rep (WrappedMonoid m) :: Type -> Type | |
Generic (ZipList a) | |
Defined in Control.Applicative Associated Types type Rep (ZipList a) :: Type -> Type | |
Generic (Complex a) | |
Defined in Data.Complex Associated Types type Rep (Complex a) :: Type -> Type | |
Generic (Endo a) | |
Defined in Data.Semigroup.Internal Associated Types type Rep (Endo a) :: Type -> Type | |
Generic (HistoriedResponse body) | |
Defined in Network.HTTP.Client Associated Types type Rep (HistoriedResponse body) :: Type -> Type | |
Generic (Tree a) | |
Generic (Digit a) | |
Defined in Data.Sequence.Internal Associated Types type Rep (Digit a) :: Type -> Type | |
Generic (Elem a) | |
Defined in Data.Sequence.Internal Associated Types type Rep (Elem a) :: Type -> Type | |
Generic (FingerTree a) | |
Defined in Data.Sequence.Internal Associated Types type Rep (FingerTree a) :: Type -> Type | |
Generic (Node a) | |
Defined in Data.Sequence.Internal Associated Types type Rep (Node a) :: Type -> Type | |
Generic (ViewL a) | |
Defined in Data.Sequence.Internal Associated Types type Rep (ViewL a) :: Type -> Type | |
Generic (ViewR a) | |
Defined in Data.Sequence.Internal Associated Types type Rep (ViewR a) :: Type -> Type | |
Generic (Doc a) | |
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types type Rep (Doc a) :: Type -> Type | |
Generic (Set a) Source # | |
Generic (Doc ann) | |
Defined in Prettyprinter.Internal Associated Types type Rep (Doc ann) :: Type -> Type | |
Generic (SimpleDocStream ann) | |
Defined in Prettyprinter.Internal Associated Types type Rep (SimpleDocStream ann) :: Type -> Type | |
Generic (ErrorFancy e) | |
Defined in Text.Megaparsec.Error Associated Types type Rep (ErrorFancy e) :: Type -> Type | |
Generic (ErrorItem t) | |
Defined in Text.Megaparsec.Error Associated Types type Rep (ErrorItem t) :: Type -> Type | |
Generic (PosState s) | |
Defined in Text.Megaparsec.State Associated Types type Rep (PosState s) :: Type -> Type | |
Generic (FieldSelection s) Source # | |
Defined in Dhall.Syntax Associated Types type Rep (FieldSelection s) :: Type -> Type Methods from :: FieldSelection s -> Rep (FieldSelection s) x to :: Rep (FieldSelection s) x -> FieldSelection s | |
Generic (Maybe a) | |
Defined in Data.Strict.Maybe Associated Types type Rep (Maybe a) :: Type -> Type | |
Generic (Fix f) | |
Generic (CommaSeparated a) | |
Defined in Text.Pretty.Simple.Internal.Expr Associated Types type Rep (CommaSeparated a) :: Type -> Type | |
Generic (Either a b) | |
Defined in GHC.Generics Associated Types type Rep (Either a b) :: Type -> Type | |
Generic (V1 p) | |
Defined in GHC.Generics Associated Types type Rep (V1 p) :: Type -> Type | |
Generic (U1 p) | |
Defined in GHC.Generics Associated Types type Rep (U1 p) :: Type -> Type | |
Generic (a, b) | |
Defined in GHC.Generics Associated Types type Rep (a, b) :: Type -> Type | |
Generic (Arg a b) | |
Defined in Data.Semigroup Associated Types type Rep (Arg a b) :: Type -> Type | |
Generic (Proxy t) | |
Defined in GHC.Generics Associated Types type Rep (Proxy t) :: Type -> Type | |
Generic (WrappedMonad m a) | |
Defined in Control.Applicative Associated Types type Rep (WrappedMonad m a) :: Type -> Type | |
Generic (Map k v) Source # | |
Generic (Expr s a) Source # | |
Generic (ParseError s e) | |
Defined in Text.Megaparsec.Error Associated Types type Rep (ParseError s e) :: Type -> Type | |
Generic (ParseErrorBundle s e) | |
Defined in Text.Megaparsec.Error Associated Types type Rep (ParseErrorBundle s e) :: Type -> Type | |
Generic (State s e) | |
Defined in Text.Megaparsec.State Associated Types type Rep (State s e) :: Type -> Type | |
Generic (FunctionBinding s a) Source # | |
Defined in Dhall.Syntax Associated Types type Rep (FunctionBinding s a) :: Type -> Type 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 Associated Types type Rep (RecordField s a) :: Type -> Type Methods from :: RecordField s a -> Rep (RecordField s a) x to :: Rep (RecordField s a) x -> RecordField s a | |
Generic (PreferAnnotation s a) Source # | |
Defined in Dhall.Syntax Associated Types type Rep (PreferAnnotation s a) :: Type -> Type Methods from :: PreferAnnotation s a -> Rep (PreferAnnotation s a) x to :: Rep (PreferAnnotation s a) x -> PreferAnnotation s a | |
Generic (Chunks s a) Source # | |
Generic (Binding s a) Source # | |
Generic (Either a b) | |
Defined in Data.Strict.Either Associated Types type Rep (Either a b) :: Type -> Type | |
Generic (These a b) | |
Defined in Data.Strict.These Associated Types type Rep (These a b) :: Type -> Type | |
Generic (These a b) | |
Defined in Data.These Associated Types type Rep (These a b) :: Type -> Type | |
Generic (Pair a b) | |
Defined in Data.Strict.Tuple Associated Types type Rep (Pair a b) :: Type -> Type | |
Generic (Rec1 f p) | |
Defined in GHC.Generics Associated Types type Rep (Rec1 f p) :: Type -> Type | |
Generic (URec (Ptr ()) p) | |
Defined in GHC.Generics Associated Types type Rep (URec (Ptr ()) p) :: Type -> Type | |
Generic (URec Char p) | |
Defined in GHC.Generics Associated Types type Rep (URec Char p) :: Type -> Type | |
Generic (URec Double p) | |
Defined in GHC.Generics Associated Types type Rep (URec Double p) :: Type -> Type | |
Generic (URec Float p) | |
Defined in GHC.Generics Associated Types type Rep (URec Float p) :: Type -> Type | |
Generic (URec Int p) | |
Defined in GHC.Generics Associated Types type Rep (URec Int p) :: Type -> Type | |
Generic (URec Word p) | |
Defined in GHC.Generics Associated Types type Rep (URec Word p) :: Type -> Type | |
Generic (a, b, c) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c) :: Type -> Type | |
Generic (Const a b) | |
Defined in Data.Functor.Const Associated Types type Rep (Const a b) :: Type -> Type | |
Generic (WrappedArrow a b c) | |
Defined in Control.Applicative Associated Types type Rep (WrappedArrow a b c) :: Type -> Type | |
Generic (Kleisli m a b) | |
Defined in Control.Arrow Associated Types type Rep (Kleisli m a b) :: Type -> Type | |
Generic (Ap f a) | |
Defined in Data.Monoid Associated Types type Rep (Ap f a) :: Type -> Type | |
Generic (Alt f a) | |
Defined in Data.Semigroup.Internal Associated Types type Rep (Alt f a) :: Type -> Type | |
Generic (Tagged s b) | |
Defined in Data.Tagged Associated Types type Rep (Tagged s b) :: Type -> Type | |
Generic (These1 f g a) | |
Defined in Data.Functor.These Associated Types type Rep (These1 f g a) :: Type -> Type | |
Generic (Join p a) | |
Defined in Data.Bifunctor.Join Associated Types type Rep (Join p a) :: Type -> Type | |
Generic (K1 i c p) | |
Defined in GHC.Generics Associated Types type Rep (K1 i c p) :: Type -> Type | |
Generic ((f :+: g) p) | |
Defined in GHC.Generics Associated Types type Rep ((f :+: g) p) :: Type -> Type | |
Generic ((f :*: g) p) | |
Defined in GHC.Generics Associated Types type Rep ((f :*: g) p) :: Type -> Type | |
Generic (a, b, c, d) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d) :: Type -> Type | |
Generic (Product f g a) | |
Defined in Data.Functor.Product Associated Types type Rep (Product f g a) :: Type -> Type | |
Generic (Sum f g a) | |
Defined in Data.Functor.Sum Associated Types type Rep (Sum f g a) :: Type -> Type | |
Generic (M1 i c f p) | |
Defined in GHC.Generics Associated Types type Rep (M1 i c f p) :: Type -> Type | |
Generic ((f :.: g) p) | |
Defined in GHC.Generics Associated Types type Rep ((f :.: g) p) :: Type -> Type | |
Generic (a, b, c, d, e) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e) :: Type -> Type | |
Generic (Compose f g a) | |
Defined in Data.Functor.Compose Associated Types type Rep (Compose f g a) :: Type -> Type | |
Generic (Clown f a b) | |
Defined in Data.Bifunctor.Clown Associated Types type Rep (Clown f a b) :: Type -> Type | |
Generic (Joker g a b) | |
Defined in Data.Bifunctor.Joker Associated Types type Rep (Joker g a b) :: Type -> Type | |
Generic (Flip p a b) | |
Defined in Data.Bifunctor.Flip Associated Types type Rep (Flip p a b) :: Type -> Type | |
Generic (WrappedBifunctor p a b) | |
Defined in Data.Bifunctor.Wrapped Associated Types type Rep (WrappedBifunctor p a b) :: Type -> Type | |
Generic (a, b, c, d, e, f) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e, f) :: Type -> Type | |
Generic (Product f g a b) | |
Defined in Data.Bifunctor.Product Associated Types type Rep (Product f g a b) :: Type -> Type | |
Generic (Sum p q a b) | |
Defined in Data.Bifunctor.Sum Associated Types type Rep (Sum p q a b) :: Type -> Type | |
Generic (a, b, c, d, e, f, g) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e, f, g) :: Type -> Type | |
Generic (Tannen f p a b) | |
Defined in Data.Bifunctor.Tannen Associated Types type Rep (Tannen f p a b) :: Type -> Type | |
Generic (Biff p f g a b) | |
Defined in Data.Bifunctor.Biff Associated Types type Rep (Biff p f g a b) :: Type -> Type |