Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Dhall.Marshal.Encode
Description
Please read the Dhall.Tutorial module, which contains a tutorial explaining how to use the language, the compiler, and this library
Synopsis
- data Encoder a = Encoder {}
- class ToDhall a where
- injectWith :: InputNormalizer -> Encoder a
- type Inject = ToDhall
- inject :: ToDhall a => Encoder a
- newtype RecordEncoder a = RecordEncoder (Map Text (Encoder a))
- recordEncoder :: RecordEncoder a -> Encoder a
- encodeField :: ToDhall a => Text -> RecordEncoder a
- encodeFieldWith :: Text -> Encoder a -> RecordEncoder a
- newtype UnionEncoder a = UnionEncoder (Product (Const (Map Text (Expr Src Void))) (Op (Text, Expr Src Void)) a)
- unionEncoder :: UnionEncoder a -> Encoder a
- encodeConstructor :: ToDhall a => Text -> UnionEncoder a
- encodeConstructorWith :: Text -> Encoder a -> UnionEncoder a
- (>|<) :: UnionEncoder a -> UnionEncoder b -> UnionEncoder (Either a b)
- class GenericToDhall f where
- genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (f a))
- genericToDhall :: (Generic a, GenericToDhall (Rep a)) => Encoder a
- genericToDhallWith :: (Generic a, GenericToDhall (Rep a)) => InterpretOptions -> Encoder a
- genericToDhallWithInputNormalizer :: (Generic a, GenericToDhall (Rep a)) => InterpretOptions -> InputNormalizer -> Encoder a
- data InterpretOptions = InterpretOptions {}
- data SingletonConstructors
- defaultInterpretOptions :: InterpretOptions
- newtype InputNormalizer = InputNormalizer {
- getInputNormalizer :: ReifiedNormalizer Void
- defaultInputNormalizer :: InputNormalizer
- data Result f
- (>$<) :: Contravariant f => (a -> b) -> f b -> f a
- (>*<) :: Divisible f => f a -> f b -> f (a, b)
- data Natural
- data Seq a
- data Text
- data Vector a
- class Generic a
General
An (Encoder a)
represents a way to marshal a value of type 'a'
from
Haskell into Dhall.
Constructors
Encoder | |
class ToDhall a where Source #
This class is used by FromDhall
instance for functions:
instance (ToDhall a, FromDhall b) => FromDhall (a -> b)
You can convert Dhall functions with "simple" inputs (i.e. instances of this class) into Haskell functions. This works by:
- Marshaling the input to the Haskell function into a Dhall expression (i.e.
x :: Expr Src Void
) - Applying the Dhall function (i.e.
f :: Expr Src Void
) to the Dhall input (i.e.App f x
) - Normalizing the syntax tree (i.e.
normalize (App f x)
) - Marshaling the resulting Dhall expression back into a Haskell value
This class auto-generates a default implementation for types that
implement Generic
. This does not auto-generate an instance for recursive
types.
The default instance can be tweaked using genericToDhallWith
/genericToDhallWithInputNormalizer
and custom InterpretOptions
, or using
DerivingVia
and Codec
from Dhall.Deriving.
Minimal complete definition
Nothing
Methods
injectWith :: InputNormalizer -> Encoder a Source #
default injectWith :: (Generic a, GenericToDhall (Rep a)) => InputNormalizer -> Encoder a Source #
Instances
ToDhall Void Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Void Source # | |
ToDhall Int16 Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Int16 Source # | |
ToDhall Int32 Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Int32 Source # | |
ToDhall Int64 Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Int64 Source # | |
ToDhall Int8 Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Int8 Source # | |
ToDhall Word16 Source # | Encode a
|
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Word16 Source # | |
ToDhall Word32 Source # | Encode a
|
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Word32 Source # | |
ToDhall Word64 Source # | Encode a
|
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Word64 Source # | |
ToDhall Word8 Source # | Encode a
|
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Word8 Source # | |
ToDhall Scientific Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Scientific Source # | |
ToDhall Text Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Text Source # | |
ToDhall Text Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Text Source # | |
ToDhall ShortText Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder ShortText Source # | |
ToDhall Day Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Day Source # | |
ToDhall DayOfWeek Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder DayOfWeek Source # | |
ToDhall UTCTime Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder UTCTime Source # | |
ToDhall LocalTime Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder LocalTime Source # | |
ToDhall TimeOfDay Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder TimeOfDay Source # | |
ToDhall TimeZone Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder TimeZone Source # | |
ToDhall ZonedTime Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder ZonedTime Source # | |
ToDhall String Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder String Source # | |
ToDhall Integer Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Integer Source # | |
ToDhall Natural Source # | |
Defined in Dhall.Marshal.Encode Methods | |
ToDhall () Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder () Source # | |
ToDhall Bool Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Bool Source # | |
ToDhall Double Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Double Source # | |
ToDhall Int Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Int Source # | |
ToDhall Word Source # | Encode a
|
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Word Source # | |
ToDhall a => ToDhall (Seq a) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Seq a) Source # | |
ToDhall a => ToDhall (Set a) Source # | Note that the output list will be sorted.
|
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Set a) Source # | |
(Functor f, ToDhall (f (Result f))) => ToDhall (Fix f) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Fix f) Source # | |
ToDhall (f (Result f)) => ToDhall (Result f) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Result f) Source # | |
ToDhall a => ToDhall (HashSet a) Source # | Note that the output list may not be sorted |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (HashSet a) Source # | |
ToDhall a => ToDhall (Vector a) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Vector a) Source # | |
ToDhall a => ToDhall (Maybe a) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Maybe a) Source # | |
ToDhall a => ToDhall [a] Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder [a] Source # | |
(ToDhall k, ToDhall v) => ToDhall (Map k v) Source # | Embed a
|
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Map k v) Source # | |
(ToDhall k, ToDhall v) => ToDhall (HashMap k v) Source # | Embed a
|
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (HashMap k v) Source # | |
(ToDhall a, ToDhall b) => ToDhall (a, b) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (a, b) Source # | |
(Generic a, GenericToDhall (Rep a), ModifyOptions tag) => ToDhall (Codec tag a) Source # | |
Defined in Dhall.Deriving Methods injectWith :: InputNormalizer -> Encoder (Codec tag a) Source # |
inject :: ToDhall a => Encoder a Source #
Use the default input normalizer for injecting a value.
inject = injectWith defaultInputNormalizer
Building encoders
Records
newtype RecordEncoder a Source #
The RecordEncoder
divisible (contravariant) functor allows you to build
an Encoder
for a Dhall record.
For example, let's take the following Haskell data type:
>>>
:{
data Project = Project { projectName :: Text , projectDescription :: Text , projectStars :: Natural } :}
And assume that we have the following Dhall record that we would like to
parse as a Project
:
{ name = "dhall-haskell" , description = "A configuration language guaranteed to terminate" , stars = 289 }
Our encoder has type Encoder
Project
, but we can't build that out of any
smaller encoders, as Encoder
s cannot be combined (they are only Contravariant
s).
However, we can use an RecordEncoder
to build an Encoder
for Project
:
>>>
:{
injectProject :: Encoder Project injectProject = recordEncoder ( adapt >$< encodeFieldWith "name" inject >*< encodeFieldWith "description" inject >*< encodeFieldWith "stars" inject ) where adapt (Project{..}) = (projectName, (projectDescription, projectStars)) :}
Or, since we are simply using the ToDhall
instance to inject each field, we could write
>>>
:{
injectProject :: Encoder Project injectProject = recordEncoder ( adapt >$< encodeField "name" >*< encodeField "description" >*< encodeField "stars" ) where adapt (Project{..}) = (projectName, (projectDescription, projectStars)) :}
Constructors
RecordEncoder (Map Text (Encoder a)) |
Instances
Contravariant RecordEncoder Source # | |
Defined in Dhall.Marshal.Encode Methods contramap :: (a' -> a) -> RecordEncoder a -> RecordEncoder a' (>$) :: b -> RecordEncoder b -> RecordEncoder a | |
Divisible RecordEncoder Source # | |
Defined in Dhall.Marshal.Encode Methods divide :: (a -> (b, c)) -> RecordEncoder b -> RecordEncoder c -> RecordEncoder a conquer :: RecordEncoder a |
recordEncoder :: RecordEncoder a -> Encoder a Source #
Convert a RecordEncoder
into the equivalent Encoder
.
encodeField :: ToDhall a => Text -> RecordEncoder a Source #
Specify how to encode one field of a record using the default ToDhall
instance for that type.
encodeFieldWith :: Text -> Encoder a -> RecordEncoder a Source #
Specify how to encode one field of a record by supplying an explicit
Encoder
for that field.
Unions
newtype UnionEncoder a Source #
UnionEncoder
allows you to build an Encoder
for a Dhall record.
For example, let's take the following Haskell data type:
>>>
:{
data Status = Queued Natural | Result Text | Errored Text :}
And assume that we have the following Dhall union that we would like to
parse as a Status
:
< Result : Text | Queued : Natural | Errored : Text >.Result "Finish successfully"
Our encoder has type Encoder
Status
, but we can't build that out of any
smaller encoders, as Encoder
s cannot be combined.
However, we can use an UnionEncoder
to build an Encoder
for Status
:
>>>
:{
injectStatus :: Encoder Status injectStatus = adapt >$< unionEncoder ( encodeConstructorWith "Queued" inject >|< encodeConstructorWith "Result" inject >|< encodeConstructorWith "Errored" inject ) where adapt (Queued n) = Left n adapt (Result t) = Right (Left t) adapt (Errored e) = Right (Right e) :}
Or, since we are simply using the ToDhall
instance to inject each branch, we could write
>>>
:{
injectStatus :: Encoder Status injectStatus = adapt >$< unionEncoder ( encodeConstructor "Queued" >|< encodeConstructor "Result" >|< encodeConstructor "Errored" ) where adapt (Queued n) = Left n adapt (Result t) = Right (Left t) adapt (Errored e) = Right (Right e) :}
Instances
Contravariant UnionEncoder Source # | |
Defined in Dhall.Marshal.Encode Methods contramap :: (a' -> a) -> UnionEncoder a -> UnionEncoder a' (>$) :: b -> UnionEncoder b -> UnionEncoder a |
unionEncoder :: UnionEncoder a -> Encoder a Source #
Convert a UnionEncoder
into the equivalent Encoder
.
encodeConstructor :: ToDhall a => Text -> UnionEncoder a Source #
Specify how to encode an alternative by using the default ToDhall
instance
for that type.
encodeConstructorWith :: Text -> Encoder a -> UnionEncoder a Source #
Specify how to encode an alternative by providing an explicit Encoder
for that alternative.
(>|<) :: UnionEncoder a -> UnionEncoder b -> UnionEncoder (Either a b) infixr 5 Source #
Combines two UnionEncoder
values. See UnionEncoder
for usage
notes.
Ideally, this matches chosen
;
however, this allows UnionEncoder
to not need a Divisible
instance
itself (since no instance is possible).
Generic encoding
class GenericToDhall f where Source #
This is the underlying class that powers the FromDhall
class's support
for automatically deriving a generic implementation.
Methods
genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (f a)) Source #
Instances
GenericToDhall (U1 :: Type -> Type) Source # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (U1 a)) Source # | |
(GenericToDhall (f :*: g), GenericToDhall (h :*: i)) => GenericToDhall ((f :*: g) :*: (h :*: i)) Source # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (((f :*: g) :*: (h :*: i)) a)) Source # | |
(GenericToDhall (f :*: g), Selector s, ToDhall a) => GenericToDhall ((f :*: g) :*: M1 S s (K1 i a :: Type -> Type)) Source # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (((f :*: g) :*: M1 S s (K1 i a)) a0)) Source # | |
(Selector s, ToDhall a, GenericToDhall (f :*: g)) => GenericToDhall (M1 S s (K1 i a :: Type -> Type) :*: (f :*: g)) Source # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder ((M1 S s (K1 i a) :*: (f :*: g)) a0)) Source # | |
(Selector s1, Selector s2, ToDhall a1, ToDhall a2) => GenericToDhall (M1 S s1 (K1 i1 a1 :: Type -> Type) :*: M1 S s2 (K1 i2 a2 :: Type -> Type)) Source # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder ((M1 S s1 (K1 i1 a1) :*: M1 S s2 (K1 i2 a2)) a)) Source # | |
(GenericToDhall (f :+: g), GenericToDhall (h :+: i)) => GenericToDhall ((f :+: g) :+: (h :+: i)) Source # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (((f :+: g) :+: (h :+: i)) a)) Source # | |
(Constructor c, GenericToDhall (f :+: g), GenericToDhall h) => GenericToDhall ((f :+: g) :+: M1 C c h) Source # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (((f :+: g) :+: M1 C c h) a)) Source # | |
(Constructor c, GenericToDhall f, GenericToDhall (g :+: h)) => GenericToDhall (M1 C c f :+: (g :+: h)) Source # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder ((M1 C c f :+: (g :+: h)) a)) Source # | |
(Constructor c1, Constructor c2, GenericToDhall f1, GenericToDhall f2) => GenericToDhall (M1 C c1 f1 :+: M1 C c2 f2) Source # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder ((M1 C c1 f1 :+: M1 C c2 f2) a)) Source # | |
GenericToDhall f => GenericToDhall (M1 C c f) Source # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (M1 C c f a)) Source # | |
GenericToDhall f => GenericToDhall (M1 D d f) Source # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (M1 D d f a)) Source # | |
(Selector s, ToDhall a) => GenericToDhall (M1 S s (K1 i a :: Type -> Type)) Source # | |
Defined in Dhall.Marshal.Encode Methods genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (M1 S s (K1 i a) a0)) Source # |
genericToDhall :: (Generic a, GenericToDhall (Rep a)) => Encoder a Source #
Use the default options for injecting a value, whose structure is determined generically.
This can be used when you want to use ToDhall
on types that you don't
want to define orphan instances for.
genericToDhallWith :: (Generic a, GenericToDhall (Rep a)) => InterpretOptions -> Encoder a Source #
Use custom options for injecting a value, whose structure is determined generically.
This can be used when you want to use ToDhall
on types that you don't
want to define orphan instances for.
genericToDhallWithInputNormalizer :: (Generic a, GenericToDhall (Rep a)) => InterpretOptions -> InputNormalizer -> Encoder a Source #
genericToDhallWithInputNormalizer
is like genericToDhallWith
, but
instead of using the defaultInputNormalizer
it expects an custom
InputNormalizer
.
data InterpretOptions Source #
Use these options to tweak how Dhall derives a generic implementation of
FromDhall
.
Constructors
InterpretOptions | |
Fields
|
data SingletonConstructors Source #
This type specifies how to model a Haskell constructor with 1 field in Dhall
For example, consider the following Haskell datatype definition:
data Example = Foo { x :: Double } | Bar Double
Depending on which option you pick, the corresponding Dhall type could be:
< Foo : Double | Bar : Double > -- Bare
< Foo : { x : Double } | Bar : { _1 : Double } > -- Wrapped
< Foo : { x : Double } | Bar : Double > -- Smart
Constructors
Bare | Never wrap the field in a record |
Wrapped | Always wrap the field in a record |
Smart | Only fields in a record if they are named |
Instances
ToSingletonConstructors a => ModifyOptions (SetSingletonConstructors a :: Type) Source # | |
Defined in Dhall.Deriving Methods modifyOptions :: InterpretOptions -> InterpretOptions Source # |
defaultInterpretOptions :: InterpretOptions Source #
Default interpret options for generics-based instances, which you can tweak or override, like this:
genericAutoWith (defaultInterpretOptions { fieldModifier = Data.Text.Lazy.dropWhile (== '_') })
Miscellaneous
newtype InputNormalizer Source #
This is only used by the FromDhall
instance for
functions in order to normalize the function input before marshaling the
input into a Dhall expression.
Constructors
InputNormalizer | |
Fields
|
defaultInputNormalizer :: InputNormalizer Source #
Default normalization-related settings (no custom normalization)
This type is exactly the same as Fix
except with a different
FromDhall
instance. This intermediate type
simplifies the implementation of the inner loop for the
FromDhall
instance for Fix
.
Instances
FromDhall (f (Result f)) => FromDhall (Result f) Source # | |
Defined in Dhall.Marshal.Decode | |
ToDhall (f (Result f)) => ToDhall (Result f) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Result f) Source # |
Re-exports
Instances
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 | |
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 | |
Bits Natural | |
Defined in GHC.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 | |
Enum Natural | |
Defined in GHC.Enum | |
Ix Natural | |
Num Natural | |
Read Natural | |
Integral Natural | |
Defined in GHC.Real | |
Real Natural | |
Defined in GHC.Real Methods toRational :: Natural -> Rational | |
Show Natural | |
PrintfArg Natural | |
Defined in Text.Printf | |
Subtractive Natural | |
NFData Natural | |
Defined in Control.DeepSeq | |
FromDhall Natural Source # | |
Defined in Dhall.Marshal.Decode | |
ToDhall Natural Source # | |
Defined in Dhall.Marshal.Encode Methods | |
Eq Natural | |
Ord Natural | |
Hashable Natural | |
Defined in Data.Hashable.Class | |
Pretty Natural | |
Defined in Prettyprinter.Internal | |
UniformRange Natural | |
Defined in System.Random.Internal | |
Serialise Natural | |
Defined in Codec.Serialise.Class | |
KnownNat n => HasResolution (n :: Nat) | |
Defined in Data.Fixed Methods resolution :: p n -> Integer | |
Lift Natural | |
type Difference Natural | |
Defined in Basement.Numerical.Subtractive | |
type Compare (a :: Natural) (b :: Natural) | |
Defined in Data.Type.Ord |
Instances
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 | |
MonadFix Seq | |
Defined in Data.Sequence.Internal | |
MonadZip Seq | |
Foldable Seq | |
Defined in Data.Sequence.Internal Methods fold :: Monoid m => Seq m -> m foldMap :: Monoid m => (a -> m) -> Seq a -> m foldMap' :: Monoid m => (a -> m) -> Seq a -> m foldr :: (a -> b -> b) -> b -> Seq a -> b foldr' :: (a -> b -> b) -> b -> Seq a -> b foldl :: (b -> a -> b) -> b -> Seq a -> b foldl' :: (b -> a -> b) -> b -> Seq a -> b foldr1 :: (a -> a -> a) -> Seq a -> a foldl1 :: (a -> a -> a) -> Seq a -> a elem :: Eq a => a -> Seq a -> Bool maximum :: Ord a => Seq a -> a | |
Eq1 Seq | |
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 | |
Traversable Seq | |
Alternative Seq | |
Applicative Seq | |
Functor Seq | |
Monad Seq | |
MonadPlus Seq | |
UnzipWith Seq | |
Defined in Data.Sequence.Internal Methods unzipWith' :: (x -> (a, b)) -> Seq x -> (Seq a, Seq b) | |
Hashable1 Seq | |
Defined in Data.Hashable.Class Methods liftHashWithSalt :: (Int -> a -> Int) -> Int -> Seq a -> Int | |
FoldableWithIndex Int Seq | |
FunctorWithIndex Int Seq | |
TraversableWithIndex Int Seq | |
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 | |
Data a => Data (Seq a) | |
Defined in Data.Sequence.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seq a -> c (Seq a) gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) dataTypeOf :: Seq a -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) | |
a ~ Char => IsString (Seq a) | |
Defined in Data.Sequence.Internal Methods fromString :: String -> Seq a | |
Monoid (Seq a) | |
Semigroup (Seq a) | |
IsList (Seq a) | |
Read a => Read (Seq a) | |
Defined in Data.Sequence.Internal | |
Show a => Show (Seq a) | |
NFData a => NFData (Seq a) | |
Defined in Data.Sequence.Internal | |
FromDhall a => FromDhall (Seq a) Source # | |
Defined in Dhall.Marshal.Decode | |
ToDhall a => ToDhall (Seq a) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Seq a) Source # | |
Eq a => Eq (Seq a) | |
Ord a => Ord (Seq a) | |
Hashable v => Hashable (Seq v) | |
Defined in Data.Hashable.Class | |
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 | |
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
FromJSON Text | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSONKey Text | |
Defined in Data.Aeson.Types.FromJSON | |
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 | |
FromDhall Text Source # | |
Defined in Dhall.Marshal.Decode | |
ToDhall Text Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder Text Source # | |
Hashable Text | |
Defined in Data.Hashable.Class | |
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 | |
Pretty Text | |
Defined in Prettyprinter.Internal | |
Serialise Text | |
Defined in Codec.Serialise.Class | |
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 | |
type ChunkElem Text | |
Defined in Data.Attoparsec.Internal.Types type ChunkElem Text = Char | |
type State Text | |
Defined in Data.Attoparsec.Internal.Types type State Text = Buffer | |
type Item Text | |
type Token Text | |
Defined in Text.Megaparsec.Stream type Token Text = Char | |
type Tokens Text | |
Defined in Text.Megaparsec.Stream |
Instances
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 | |
MonadFail Vector | |
Defined in Data.Vector | |
MonadFix Vector | |
Defined in Data.Vector | |
MonadZip Vector | |
Foldable Vector | |
Defined in Data.Vector Methods fold :: Monoid m => Vector m -> m foldMap :: Monoid m => (a -> m) -> Vector a -> m foldMap' :: Monoid m => (a -> m) -> Vector a -> m foldr :: (a -> b -> b) -> b -> Vector a -> b foldr' :: (a -> b -> b) -> b -> Vector a -> b foldl :: (b -> a -> b) -> b -> Vector a -> b foldl' :: (b -> a -> b) -> b -> Vector a -> b foldr1 :: (a -> a -> a) -> Vector a -> a foldl1 :: (a -> a -> a) -> Vector a -> a elem :: Eq a => a -> Vector a -> Bool maximum :: Ord a => Vector a -> a | |
Eq1 Vector | |
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 | |
Traversable Vector | |
Alternative Vector | |
Applicative Vector | |
Functor Vector | |
Monad Vector | |
MonadPlus Vector | |
NFData1 Vector | |
Defined in Data.Vector | |
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 () | |
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 | |
Data a => Data (Vector a) | |
Defined in Data.Vector Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) toConstr :: Vector a -> Constr dataTypeOf :: Vector a -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) | |
Monoid (Vector a) | |
Semigroup (Vector a) | |
IsList (Vector a) | |
Read a => Read (Vector a) | |
Defined in Data.Vector | |
Show a => Show (Vector a) | |
NFData a => NFData (Vector a) | |
Defined in Data.Vector | |
FromDhall a => FromDhall (Vector a) Source # | |
Defined in Dhall.Marshal.Decode | |
ToDhall a => ToDhall (Vector a) Source # | |
Defined in Dhall.Marshal.Encode Methods injectWith :: InputNormalizer -> Encoder (Vector a) Source # | |
Eq a => Eq (Vector a) | |
Ord a => Ord (Vector a) | |
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] | |
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 Value | |
Defined in Data.Aeson.Types.Internal Associated Types type Rep Value :: 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 Version | |
Defined in Data.Version Associated Types type Rep Version :: Type -> Type | |
Generic Void | |
Generic Fingerprint | |
Defined in GHC.Generics Associated Types type Rep Fingerprint :: Type -> Type | |
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 ExitCode | |
Defined in GHC.IO.Exception Associated Types type Rep ExitCode :: Type -> Type | |
Generic CCFlags | |
Defined in GHC.RTS.Flags Associated Types type Rep CCFlags :: Type -> Type | |
Generic ConcFlags | |
Defined in GHC.RTS.Flags Associated Types type Rep ConcFlags :: Type -> Type | |
Generic DebugFlags | |
Defined in GHC.RTS.Flags Associated Types type Rep DebugFlags :: Type -> Type | |
Generic DoCostCentres | |
Defined in GHC.RTS.Flags Associated Types type Rep DoCostCentres :: Type -> Type | |
Generic DoHeapProfile | |
Defined in GHC.RTS.Flags Associated Types type Rep DoHeapProfile :: Type -> Type | |
Generic DoTrace | |
Defined in GHC.RTS.Flags Associated Types type Rep DoTrace :: Type -> Type | |
Generic GCFlags | |
Defined in GHC.RTS.Flags Associated Types type Rep GCFlags :: Type -> Type | |
Generic GiveGCStats | |
Defined in GHC.RTS.Flags Associated Types type Rep GiveGCStats :: Type -> Type | |
Generic MiscFlags | |
Defined in GHC.RTS.Flags Associated Types type Rep MiscFlags :: Type -> Type | |
Generic ParFlags | |
Defined in GHC.RTS.Flags Associated Types type Rep ParFlags :: Type -> Type | |
Generic ProfFlags | |
Defined in GHC.RTS.Flags Associated Types type Rep ProfFlags :: Type -> Type | |
Generic RTSFlags | |
Defined in GHC.RTS.Flags Associated Types type Rep RTSFlags :: Type -> Type | |
Generic TickyFlags | |
Defined in GHC.RTS.Flags Associated Types type Rep TickyFlags :: Type -> Type | |
Generic TraceFlags | |
Defined in GHC.RTS.Flags Associated Types type Rep TraceFlags :: Type -> Type | |
Generic SrcLoc | |
Defined in GHC.Generics Associated Types type Rep SrcLoc :: Type -> Type | |
Generic GeneralCategory | |
Defined in GHC.Generics Associated Types type Rep GeneralCategory :: Type -> Type | |
Generic SHA256Digest Source # | |
Defined in Dhall.Crypto Associated Types type Rep SHA256Digest :: Type -> Type | |
Generic CharacterSet Source # | |
Defined in Dhall.Pretty.Internal Associated Types type Rep CharacterSet :: Type -> Type | |
Generic Src Source # | |
Generic Const Source # | |
Generic DhallDouble Source # | |
Defined in Dhall.Syntax Associated Types type Rep DhallDouble :: Type -> Type | |
Generic Directory Source # | |
Generic File Source # | |
Generic FilePrefix Source # | |
Defined in Dhall.Syntax Associated Types type Rep FilePrefix :: 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 Scheme Source # | |
Generic URL Source # | |
Generic Var Source # | |
Generic WithComponent Source # | |
Defined in Dhall.Syntax Associated Types type Rep WithComponent :: 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 Ordering | |
Defined in GHC.Generics Associated Types type Rep Ordering :: Type -> Type | |
Generic Half | |
Defined in Numeric.Half.Internal Associated Types type Rep Half :: Type -> Type | |
Generic IP | |
Defined in Data.IP.Addr Associated Types type Rep IP :: Type -> Type | |
Generic IPv4 | |
Defined in Data.IP.Addr Associated Types type Rep IPv4 :: Type -> Type | |
Generic IPv6 | |
Defined in Data.IP.Addr Associated Types type Rep IPv6 :: Type -> Type | |
Generic IPRange | |
Defined in Data.IP.Range Associated Types type Rep IPRange :: Type -> Type | |
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 URI | |
Defined in Network.URI Associated Types type Rep URI :: Type -> Type | |
Generic URIAuth | |
Defined in Network.URI Associated Types type Rep URIAuth :: 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 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 Expr | |
Defined in Text.Pretty.Simple.Internal.Expr Associated Types type Rep Expr :: 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 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 Clause | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Clause :: Type -> Type | |
Generic Con | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Con :: Type -> Type | |
Generic Dec | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Dec :: 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 DocLoc | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep DocLoc :: Type -> Type | |
Generic Exp | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Exp :: 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 FunDep | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep FunDep :: 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 InjectivityAnn | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep InjectivityAnn :: Type -> Type | |
Generic Inline | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Inline :: Type -> Type | |
Generic Lit | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Lit :: Type -> Type | |
Generic Loc | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Loc :: Type -> Type | |
Generic Match | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Match :: 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 Name | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Name :: Type -> Type | |
Generic NameFlavour | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep NameFlavour :: 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 Overlap | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Overlap :: Type -> Type | |
Generic Pat | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Pat :: 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 Specificity | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Specificity :: 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 Type | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep Type :: Type -> Type | |
Generic TypeFamilyHead | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep TypeFamilyHead :: 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 () | |
Defined in GHC.Generics Associated Types type Rep () :: Type -> Type | |
Generic Bool | |
Defined in GHC.Generics Associated Types type Rep Bool :: 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 (Identity a) | |
Defined in Data.Functor.Identity Associated Types type Rep (Identity a) :: Type -> Type | |
Generic (First a) | |
Defined in Data.Monoid Associated Types type Rep (First a) :: Type -> Type | |
Generic (Last a) | |
Defined in Data.Monoid Associated Types type Rep (Last a) :: Type -> Type | |
Generic (Down a) | |
Defined in GHC.Generics Associated Types type Rep (Down a) :: Type -> Type | |
Generic (First a) | |
Defined in Data.Semigroup Associated Types type Rep (First a) :: Type -> Type | |
Generic (Last a) | |
Defined in Data.Semigroup 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 (WrappedMonoid m) | |
Defined in Data.Semigroup Associated Types type Rep (WrappedMonoid m) :: Type -> Type | |
Generic (Dual a) | |
Defined in Data.Semigroup.Internal Associated Types type Rep (Dual a) :: Type -> Type | |
Generic (Endo a) | |
Defined in Data.Semigroup.Internal Associated Types type Rep (Endo 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 (Par1 p) | |
Defined in GHC.Generics Associated Types type Rep (Par1 p) :: Type -> Type | |
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 (Tree a) | |
Generic (Fix f) | |
Generic (Set a) Source # | |
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 (HistoriedResponse body) | |
Defined in Network.HTTP.Client Associated Types type Rep (HistoriedResponse body) :: Type -> Type | |
Generic (AddrRange a) | |
Defined in Data.IP.Range Associated Types type Rep (AddrRange a) :: 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 (Doc a) | |
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types type Rep (Doc a) :: Type -> Type | |
Generic (CommaSeparated a) | |
Defined in Text.Pretty.Simple.Internal.Expr Associated Types type Rep (CommaSeparated a) :: Type -> Type | |
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 (Maybe a) | |
Defined in Data.Strict.Maybe Associated Types type Rep (Maybe a) :: Type -> Type | |
Generic (TyVarBndr flag) | |
Defined in Language.Haskell.TH.Syntax Associated Types type Rep (TyVarBndr flag) :: Type -> Type | |
Generic (NonEmpty a) | |
Defined in GHC.Generics Associated Types type Rep (NonEmpty a) :: Type -> Type | |
Generic (Maybe a) | |
Defined in GHC.Generics Associated Types type Rep (Maybe a) :: Type -> Type | |
Generic (a) | |
Defined in GHC.Generics Associated Types type Rep (a) :: Type -> Type | |
Generic [a] | |
Defined in GHC.Generics Associated Types type Rep [a] :: Type -> Type | |
Generic (WrappedMonad m a) | |
Defined in Control.Applicative Associated Types type Rep (WrappedMonad m a) :: Type -> Type | |
Generic (Either a b) | |
Defined in GHC.Generics Associated Types type Rep (Either a b) :: Type -> Type | |
Generic (Proxy t) | |
Defined in GHC.Generics Associated Types type Rep (Proxy t) :: Type -> Type | |
Generic (Arg a b) | |
Defined in Data.Semigroup Associated Types type Rep (Arg a b) :: Type -> Type | |
Generic (U1 p) | |
Defined in GHC.Generics Associated Types type Rep (U1 p) :: Type -> Type | |
Generic (V1 p) | |
Defined in GHC.Generics Associated Types type Rep (V1 p) :: Type -> Type | |
Generic (Map k v) Source # | |
Generic (Binding s a) Source # | |
Generic (Chunks s a) Source # | |
Generic (Expr s a) Source # | |
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 (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 (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 (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 (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 (Pair a b) | |
Defined in Data.Strict.Tuple Associated Types type Rep (Pair a b) :: Type -> Type | |
Generic (These a b) | |
Defined in Data.These Associated Types type Rep (These a b) :: Type -> Type | |
Generic (a, b) | |
Defined in GHC.Generics Associated Types type Rep (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 (Const a b) | |
Defined in Data.Functor.Const Associated Types type Rep (Const 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 (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 (Join p a) | |
Defined in Data.Bifunctor.Join Associated Types type Rep (Join p 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 (a, b, c) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c) :: 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 ((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 (K1 i c p) | |
Defined in GHC.Generics Associated Types type Rep (K1 i c p) :: Type -> Type | |
Generic (a, b, c, d) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d) :: Type -> Type | |
Generic (Compose f g a) | |
Defined in Data.Functor.Compose Associated Types type Rep (Compose f g a) :: Type -> Type | |
Generic ((f :.: g) p) | |
Defined in GHC.Generics Associated Types type Rep ((f :.: g) p) :: Type -> Type | |
Generic (M1 i c f p) | |
Defined in GHC.Generics Associated Types type Rep (M1 i c f p) :: Type -> Type | |
Generic (Clown f a b) | |
Defined in Data.Bifunctor.Clown Associated Types type Rep (Clown f 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 (Joker g a b) | |
Defined in Data.Bifunctor.Joker Associated Types type Rep (Joker g 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) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e) :: 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) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e, f) :: 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 (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 (a, b, c, d, e, f, g, h) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e, f, g, h) :: 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 | |
Generic (a, b, c, d, e, f, g, h, i) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e, f, g, h, i) :: Type -> Type | |
Generic (a, b, c, d, e, f, g, h, i, j) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e, f, g, h, i, j) :: Type -> Type | |
Generic (a, b, c, d, e, f, g, h, i, j, k) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e, f, g, h, i, j, k) :: Type -> Type | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e, f, g, h, i, j, k, l) :: Type -> Type | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) :: Type -> Type | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: Type -> Type | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
Defined in GHC.Generics Associated Types type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: Type -> Type |