dhall-1.39.0: A configuration language guaranteed to terminate
Safe HaskellNone
LanguageHaskell2010

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

General

data Encoder a Source #

An (Encoder a) represents a way to marshal a value of type 'a' from Haskell into Dhall.

Constructors

Encoder 

Fields

Instances

Instances details
Contravariant Encoder Source # 
Instance details

Defined in Dhall.Marshal.Encode

Methods

contramap :: (a -> b) -> Encoder b -> Encoder a

(>$) :: b -> Encoder b -> Encoder a

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 and custom InterpretOptions, or using DerivingVia and Codec from Dhall.Deriving.

Minimal complete definition

Nothing

Instances

Instances details
ToDhall Bool Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Double Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Int Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Integer Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Natural Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Word Source #

Encode a Word to a Dhall Natural.

>>> embed inject (12 :: Word)
NaturalLit 12
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Word8 Source #

Encode a Word8 to a Dhall Natural.

>>> embed inject (12 :: Word8)
NaturalLit 12
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Word16 Source #

Encode a Word16 to a Dhall Natural.

>>> embed inject (12 :: Word16)
NaturalLit 12
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Word32 Source #

Encode a Word32 to a Dhall Natural.

>>> embed inject (12 :: Word32)
NaturalLit 12
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Word64 Source #

Encode a Word64 to a Dhall Natural.

>>> embed inject (12 :: Word64)
NaturalLit 12
Instance details

Defined in Dhall.Marshal.Encode

ToDhall () Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Text Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall String Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Void Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Text Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Scientific Source # 
Instance details

Defined in Dhall.Marshal.Encode

Methods

injectWith :: InputNormalizer -> Encoder Scientific Source #

ToDhall a => ToDhall [a] Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall a => ToDhall (Maybe a) Source # 
Instance details

Defined in Dhall.Marshal.Encode

Methods

injectWith :: InputNormalizer -> Encoder (Maybe a) Source #

ToDhall a => ToDhall (Seq a) Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall a => ToDhall (Set a) Source #

Note that the output list will be sorted.

>>> let x = Data.Set.fromList ["mom", "hi" :: Text]
>>> prettyExpr $ embed inject x
[ "hi", "mom" ]
Instance details

Defined in Dhall.Marshal.Encode

ToDhall a => ToDhall (Vector a) Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall a => ToDhall (HashSet a) Source #

Note that the output list may not be sorted

Instance details

Defined in Dhall.Marshal.Encode

Methods

injectWith :: InputNormalizer -> Encoder (HashSet a) Source #

(Functor f, ToDhall (f (Result f))) => ToDhall (Fix f) Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall (f (Result f)) => ToDhall (Result f) Source # 
Instance details

Defined in Dhall.Marshal.Encode

(ToDhall a, ToDhall b) => ToDhall (a, b) Source # 
Instance details

Defined in Dhall.Marshal.Encode

(ToDhall k, ToDhall v) => ToDhall (Map k v) Source #

Embed a Map as a Prelude.Map.Type.

>>> prettyExpr $ embed inject (Data.Map.fromList [(1 :: Natural, True)])
[ { mapKey = 1, mapValue = True } ]
>>> prettyExpr $ embed inject (Data.Map.fromList [] :: Data.Map.Map Natural Bool)
[] : List { mapKey : Natural, mapValue : Bool }
Instance details

Defined in Dhall.Marshal.Encode

Methods

injectWith :: InputNormalizer -> Encoder (Map k v) Source #

(ToDhall k, ToDhall v) => ToDhall (HashMap k v) Source #

Embed a HashMap as a Prelude.Map.Type.

>>> prettyExpr $ embed inject (HashMap.fromList [(1 :: Natural, True)])
[ { mapKey = 1, mapValue = True } ]
>>> prettyExpr $ embed inject (HashMap.fromList [] :: HashMap Natural Bool)
[] : List { mapKey : Natural, mapValue : Bool }
Instance details

Defined in Dhall.Marshal.Encode

Methods

injectWith :: InputNormalizer -> Encoder (HashMap k v) Source #

(Generic a, GenericToDhall (Rep a), ModifyOptions tag) => ToDhall (Codec tag a) Source # 
Instance details

Defined in Dhall.Deriving

type Inject = ToDhall Source #

Deprecated: Use ToDhall instead

A compatibility alias for ToDhall

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 Encoders cannot be combined (they are only Contravariants). 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

Instances details
Contravariant RecordEncoder Source # 
Instance details

Defined in Dhall.Marshal.Encode

Methods

contramap :: (a -> b) -> RecordEncoder b -> RecordEncoder a

(>$) :: b -> RecordEncoder b -> RecordEncoder a

Divisible RecordEncoder Source # 
Instance details

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 Encoders cannot be combined. However, we can use an UnionEncoder to build an Encoder for Status:

>>> :{
injectStatus :: Encoder Status
injectStatus = adapt >$< unionEncoder
  (   encodeConstructorWith "Queued"  inject
  >|< encodeConstructorWith "Result"  inject
  >|< encodeConstructorWith "Errored" inject
  )
  where
    adapt (Queued  n) = Left n
    adapt (Result  t) = Right (Left t)
    adapt (Errored e) = Right (Right e)
:}

Or, since we are simply using the ToDhall instance to inject each branch, we could write

>>> :{
injectStatus :: Encoder Status
injectStatus = adapt >$< unionEncoder
  (   encodeConstructor "Queued"
  >|< encodeConstructor "Result"
  >|< encodeConstructor "Errored"
  )
  where
    adapt (Queued  n) = Left n
    adapt (Result  t) = Right (Left t)
    adapt (Errored e) = Right (Right e)
:}

Constructors

UnionEncoder (Product (Const (Map Text (Expr Src Void))) (Op (Text, Expr Src Void)) a) 

Instances

Instances details
Contravariant UnionEncoder Source # 
Instance details

Defined in Dhall.Marshal.Encode

Methods

contramap :: (a -> b) -> UnionEncoder b -> 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.

Instances

Instances details
GenericToDhall (U1 :: Type -> Type) Source # 
Instance details

Defined in Dhall.Marshal.Encode

(Constructor c, GenericToDhall f, GenericToDhall (g :+: h)) => GenericToDhall (M1 C c f :+: (g :+: h)) Source # 
Instance details

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 # 
Instance details

Defined in Dhall.Marshal.Encode

Methods

genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder ((M1 C c1 f1 :+: M1 C c2 f2) a)) Source #

(GenericToDhall (f :+: g), GenericToDhall (h :+: i)) => GenericToDhall ((f :+: g) :+: (h :+: i)) Source # 
Instance details

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 # 
Instance details

Defined in Dhall.Marshal.Encode

Methods

genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (((f :+: g) :+: M1 C c h) a)) 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 # 
Instance details

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 #

(Selector s, ToDhall a, GenericToDhall (f :*: g)) => GenericToDhall (M1 S s (K1 i a :: Type -> Type) :*: (f :*: g)) Source # 
Instance details

Defined in Dhall.Marshal.Encode

Methods

genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder ((M1 S s (K1 i a) :*: (f :*: g)) a0)) Source #

(GenericToDhall (f :*: g), Selector s, ToDhall a) => GenericToDhall ((f :*: g) :*: M1 S s (K1 i a :: Type -> Type)) Source # 
Instance details

Defined in Dhall.Marshal.Encode

Methods

genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (((f :*: g) :*: M1 S s (K1 i a)) a0)) Source #

(GenericToDhall (f :*: g), GenericToDhall (h :*: i)) => GenericToDhall ((f :*: g) :*: (h :*: i)) Source # 
Instance details

Defined in Dhall.Marshal.Encode

Methods

genericToDhallWithNormalizer :: InputNormalizer -> InterpretOptions -> State Int (Encoder (((f :*: g) :*: (h :*: i)) a)) Source #

GenericToDhall f => GenericToDhall (M1 D d f) Source # 
Instance details

Defined in Dhall.Marshal.Encode

GenericToDhall f => GenericToDhall (M1 C c f) Source # 
Instance details

Defined in Dhall.Marshal.Encode

(Selector s, ToDhall a) => GenericToDhall (M1 S s (K1 i a :: Type -> Type)) Source # 
Instance details

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.

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

Instances details
ToSingletonConstructors a => ModifyOptions (SetSingletonConstructors a :: Type) Source # 
Instance details

Defined in Dhall.Deriving

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.

defaultInputNormalizer :: InputNormalizer Source #

Default normalization-related settings (no custom normalization)

data Result f Source #

This type is exactly the same as Fix except with a different FromDhall instance. This intermediate type simplifies the implementation of the inner loop for the FromDhall instance for Fix.

Instances

Instances details
ToDhall (f (Result f)) => ToDhall (Result f) Source # 
Instance details

Defined in Dhall.Marshal.Encode

FromDhall (f (Result f)) => FromDhall (Result f) Source # 
Instance details

Defined in Dhall.Marshal.Decode

(>$<) :: Contravariant f => (a -> b) -> f b -> f a #

(>*<) :: Divisible f => f a -> f b -> f (a, b) infixr 5 Source #

Infix divided

Re-exports

data Natural #

Instances

Instances details
Enum Natural 
Instance details

Defined in GHC.Enum

Eq Natural 
Instance details

Defined in GHC.Natural

Methods

(==) :: Natural -> Natural -> Bool

(/=) :: Natural -> Natural -> Bool

Integral Natural 
Instance details

Defined in GHC.Real

Data Natural 
Instance details

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

toConstr :: Natural -> Constr

dataTypeOf :: Natural -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Natural)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Natural)

gmapT :: (forall b. Data b => b -> b) -> Natural -> Natural

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r

gmapQ :: (forall d. Data d => d -> u) -> Natural -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Natural -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Natural -> m Natural

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural

Num Natural 
Instance details

Defined in GHC.Num

Ord Natural 
Instance details

Defined in GHC.Natural

Methods

compare :: Natural -> Natural -> Ordering

(<) :: Natural -> Natural -> Bool

(<=) :: Natural -> Natural -> Bool

(>) :: Natural -> Natural -> Bool

(>=) :: Natural -> Natural -> Bool

max :: Natural -> Natural -> Natural

min :: Natural -> Natural -> Natural

Read Natural 
Instance details

Defined in GHC.Read

Methods

readsPrec :: Int -> ReadS Natural

readList :: ReadS [Natural]

readPrec :: ReadPrec Natural

readListPrec :: ReadPrec [Natural]

Real Natural 
Instance details

Defined in GHC.Real

Methods

toRational :: Natural -> Rational

Show Natural 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Natural -> ShowS

show :: Natural -> String

showList :: [Natural] -> ShowS

Ix Natural 
Instance details

Defined in GHC.Ix

NFData Natural 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Natural -> ()

PrintfArg Natural 
Instance details

Defined in Text.Printf

Methods

formatArg :: Natural -> FieldFormatter

parseFormat :: Natural -> ModifierParser

Bits Natural 
Instance details

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

zeroBits :: Natural

bit :: Int -> Natural

setBit :: Natural -> Int -> Natural

clearBit :: Natural -> Int -> Natural

complementBit :: Natural -> Int -> Natural

testBit :: Natural -> Int -> Bool

bitSizeMaybe :: Natural -> Maybe Int

bitSize :: Natural -> Int

isSigned :: Natural -> Bool

shiftL :: Natural -> Int -> Natural

unsafeShiftL :: Natural -> Int -> Natural

shiftR :: Natural -> Int -> Natural

unsafeShiftR :: Natural -> Int -> Natural

rotateL :: Natural -> Int -> Natural

rotateR :: Natural -> Int -> Natural

popCount :: Natural -> Int

Subtractive Natural 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Natural

Methods

(-) :: Natural -> Natural -> Difference Natural

Hashable Natural 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Natural -> Int

hash :: Natural -> Int

Pretty Natural 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Natural -> Doc ann

prettyList :: [Natural] -> Doc ann

Serialise Natural 
Instance details

Defined in Codec.Serialise.Class

Methods

encode :: Natural -> Encoding

decode :: Decoder s Natural

encodeList :: [Natural] -> Encoding

decodeList :: Decoder s [Natural]

FromJSON Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Natural

parseJSONList :: Value -> Parser [Natural]

FromJSONKey Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey :: FromJSONKeyFunction Natural

fromJSONKeyList :: FromJSONKeyFunction [Natural]

ToJSON Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Natural -> Value

toEncoding :: Natural -> Encoding

toJSONList :: [Natural] -> Value

toEncodingList :: [Natural] -> Encoding

ToJSONKey Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey :: ToJSONKeyFunction Natural

toJSONKeyList :: ToJSONKeyFunction [Natural]

UniformRange Natural 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Natural, Natural) -> g -> m Natural

ToDhall Natural Source # 
Instance details

Defined in Dhall.Marshal.Encode

FromDhall Natural Source # 
Instance details

Defined in Dhall.Marshal.Decode

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Natural -> Q Exp

liftTyped :: Natural -> Q (TExp Natural)

type Difference Natural 
Instance details

Defined in Basement.Numerical.Subtractive

type Difference Natural = Maybe Natural

data Seq a #

Instances

Instances details
Monad Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

(>>=) :: Seq a -> (a -> Seq b) -> Seq b

(>>) :: Seq a -> Seq b -> Seq b

return :: a -> Seq a

Functor Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

fmap :: (a -> b) -> Seq a -> Seq b

(<$) :: a -> Seq b -> Seq a

MonadFix Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

mfix :: (a -> Seq a) -> Seq a

Applicative Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

pure :: a -> Seq a

(<*>) :: Seq (a -> b) -> Seq a -> Seq b

liftA2 :: (a -> b -> c) -> Seq a -> Seq b -> Seq c

(*>) :: Seq a -> Seq b -> Seq b

(<*) :: Seq a -> Seq b -> Seq a

Foldable Seq 
Instance details

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

toList :: Seq a -> [a]

null :: Seq a -> Bool

length :: Seq a -> Int

elem :: Eq a => a -> Seq a -> Bool

maximum :: Ord a => Seq a -> a

minimum :: Ord a => Seq a -> a

sum :: Num a => Seq a -> a

product :: Num a => Seq a -> a

Traversable Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Seq a -> f (Seq b)

sequenceA :: Applicative f => Seq (f a) -> f (Seq a)

mapM :: Monad m => (a -> m b) -> Seq a -> m (Seq b)

sequence :: Monad m => Seq (m a) -> m (Seq a)

MonadPlus Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

mzero :: Seq a

mplus :: Seq a -> Seq a -> Seq a

Alternative Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

empty :: Seq a

(<|>) :: Seq a -> Seq a -> Seq a

some :: Seq a -> Seq [a]

many :: Seq a -> Seq [a]

Eq1 Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

liftEq :: (a -> b -> Bool) -> Seq a -> Seq b -> Bool

Ord1 Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

liftCompare :: (a -> b -> Ordering) -> Seq a -> Seq b -> Ordering

Read1 Seq 
Instance details

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 
Instance details

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 
Instance details

Defined in Data.Sequence.Internal

Methods

mzip :: Seq a -> Seq b -> Seq (a, b)

mzipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c

munzip :: Seq (a, b) -> (Seq a, Seq b)

UnzipWith Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

unzipWith' :: (x -> (a, b)) -> Seq x -> (Seq a, Seq b)

FromJSON1 Seq 
Instance details

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 
Instance details

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) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Item (Seq a)

Methods

fromList :: [Item (Seq a)] -> Seq a

fromListN :: Int -> [Item (Seq a)] -> Seq a

toList :: Seq a -> [Item (Seq a)]

Eq a => Eq (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

(==) :: Seq a -> Seq a -> Bool

(/=) :: Seq a -> Seq a -> Bool

Data a => Data (Seq a) 
Instance details

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)

toConstr :: Seq a -> Constr

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) 
Instance details

Defined in Data.Sequence.Internal

Methods

compare :: Seq a -> Seq a -> Ordering

(<) :: Seq a -> Seq a -> Bool

(<=) :: Seq a -> Seq a -> Bool

(>) :: Seq a -> Seq a -> Bool

(>=) :: Seq a -> Seq a -> Bool

max :: Seq a -> Seq a -> Seq a

min :: Seq a -> Seq a -> Seq a

Read a => Read (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

readsPrec :: Int -> ReadS (Seq a)

readList :: ReadS [Seq a]

readPrec :: ReadPrec (Seq a)

readListPrec :: ReadPrec [Seq a]

Show a => Show (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

showsPrec :: Int -> Seq a -> ShowS

show :: Seq a -> String

showList :: [Seq a] -> ShowS

a ~ Char => IsString (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

fromString :: String -> Seq a

Semigroup (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

(<>) :: Seq a -> Seq a -> Seq a

sconcat :: NonEmpty (Seq a) -> Seq a

stimes :: Integral b => b -> Seq a -> Seq a

Monoid (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

mempty :: Seq a

mappend :: Seq a -> Seq a -> Seq a

mconcat :: [Seq a] -> Seq a

NFData a => NFData (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

rnf :: Seq a -> ()

Ord a => Stream (Seq a) 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token (Seq a)

type Tokens (Seq a)

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) 
Instance details

Defined in Codec.Serialise.Class

Methods

encode :: Seq a -> Encoding

decode :: Decoder s (Seq a)

encodeList :: [Seq a] -> Encoding

decodeList :: Decoder s [Seq a]

FromJSON a => FromJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Seq a)

parseJSONList :: Value -> Parser [Seq a]

ToJSON a => ToJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Seq a -> Value

toEncoding :: Seq a -> Encoding

toJSONList :: [Seq a] -> Value

toEncodingList :: [Seq a] -> Encoding

ToDhall a => ToDhall (Seq a) Source # 
Instance details

Defined in Dhall.Marshal.Encode

FromDhall a => FromDhall (Seq a) Source # 
Instance details

Defined in Dhall.Marshal.Decode

type Item (Seq a) 
Instance details

Defined in Data.Sequence.Internal

type Item (Seq a) = a
type Token (Seq a) 
Instance details

Defined in Text.Megaparsec.Stream

type Token (Seq a) = a
type Tokens (Seq a) 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens (Seq a) = Seq a

data Text #

Instances

Instances details
Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int

hash :: Text -> Int

Pretty Text 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann

prettyList :: [Text] -> Doc ann

Stream Text 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token Text

type Tokens Text

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 
Instance details

Defined in Text.Megaparsec.Stream

Methods

reachOffset :: Int -> PosState Text -> (Maybe String, PosState Text)

reachOffsetNoLine :: Int -> PosState Text -> PosState Text

VisualStream Text 
Instance details

Defined in Text.Megaparsec.Stream

Methods

showTokens :: Proxy Text -> NonEmpty (Token Text) -> String

tokensLength :: Proxy Text -> NonEmpty (Token Text) -> Int

Serialise Text 
Instance details

Defined in Codec.Serialise.Class

Methods

encode :: Text -> Encoding

decode :: Decoder s Text

encodeList :: [Text] -> Encoding

decodeList :: Decoder s [Text]

FromJSON Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Text

parseJSONList :: Value -> Parser [Text]

FromJSONKey Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey :: FromJSONKeyFunction Text

fromJSONKeyList :: FromJSONKeyFunction [Text]

KeyValue Object 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Text -> v -> Object

KeyValue Pair 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Text -> v -> Pair

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Text -> Value

toEncoding :: Text -> Encoding

toJSONList :: [Text] -> Value

toEncodingList :: [Text] -> Encoding

ToJSONKey Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey :: ToJSONKeyFunction Text

toJSONKeyList :: ToJSONKeyFunction [Text]

Chunk Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem Text

Methods

nullChunk :: Text -> Bool

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 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

foldCase :: Text -> Text

foldCaseList :: [Text] -> [Text]

ToDhall Text Source # 
Instance details

Defined in Dhall.Marshal.Encode

FromDhall Text Source # 
Instance details

Defined in Dhall.Marshal.Decode

MonadParsec Void Text Parser 
Instance details

Defined in Dhall.Parser.Combinators

Methods

parseError :: ParseError Text Void -> Parser a

label :: String -> Parser a -> Parser a

hidden :: Parser a -> Parser a

try :: 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)

eof :: Parser ()

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 
Instance details

Defined in Text.Parsec.Prim

Methods

uncons :: Text -> m (Maybe (Char, Text))

FromPairs Value (DList Pair) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

fromPairs :: DList Pair -> Value

v ~ Value => KeyValuePair v (DList Pair) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

pair :: String -> v -> DList Pair

type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char
type Token Text 
Instance details

Defined in Text.Megaparsec.Stream

type Token Text = Char
type Tokens Text 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens Text = Text
type State Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State Text = Buffer
type ChunkElem Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type ChunkElem Text = Char

data Vector a #

Instances

Instances details
Monad Vector 
Instance details

Defined in Data.Vector

Methods

(>>=) :: Vector a -> (a -> Vector b) -> Vector b

(>>) :: Vector a -> Vector b -> Vector b

return :: a -> Vector a

Functor Vector 
Instance details

Defined in Data.Vector

Methods

fmap :: (a -> b) -> Vector a -> Vector b

(<$) :: a -> Vector b -> Vector a

MonadFix Vector 
Instance details

Defined in Data.Vector

Methods

mfix :: (a -> Vector a) -> Vector a

MonadFail Vector 
Instance details

Defined in Data.Vector

Methods

fail :: String -> Vector a

Applicative Vector 
Instance details

Defined in Data.Vector

Methods

pure :: a -> Vector a

(<*>) :: Vector (a -> b) -> Vector a -> Vector b

liftA2 :: (a -> b -> c) -> Vector a -> Vector b -> Vector c

(*>) :: Vector a -> Vector b -> Vector b

(<*) :: Vector a -> Vector b -> Vector a

Foldable Vector 
Instance details

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

toList :: Vector a -> [a]

null :: Vector a -> Bool

length :: Vector a -> Int

elem :: Eq a => a -> Vector a -> Bool

maximum :: Ord a => Vector a -> a

minimum :: Ord a => Vector a -> a

sum :: Num a => Vector a -> a

product :: Num a => Vector a -> a

Traversable Vector 
Instance details

Defined in Data.Vector

Methods

traverse :: Applicative f => (a -> f b) -> Vector a -> f (Vector b)

sequenceA :: Applicative f => Vector (f a) -> f (Vector a)

mapM :: Monad m => (a -> m b) -> Vector a -> m (Vector b)

sequence :: Monad m => Vector (m a) -> m (Vector a)

MonadPlus Vector 
Instance details

Defined in Data.Vector

Methods

mzero :: Vector a

mplus :: Vector a -> Vector a -> Vector a

Alternative Vector 
Instance details

Defined in Data.Vector

Methods

empty :: Vector a

(<|>) :: Vector a -> Vector a -> Vector a

some :: Vector a -> Vector [a]

many :: Vector a -> Vector [a]

NFData1 Vector 
Instance details

Defined in Data.Vector

Methods

liftRnf :: (a -> ()) -> Vector a -> ()

Eq1 Vector 
Instance details

Defined in Data.Vector

Methods

liftEq :: (a -> b -> Bool) -> Vector a -> Vector b -> Bool

Ord1 Vector 
Instance details

Defined in Data.Vector

Methods

liftCompare :: (a -> b -> Ordering) -> Vector a -> Vector b -> Ordering

Read1 Vector 
Instance details

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 
Instance details

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 
Instance details

Defined in Data.Vector

Methods

mzip :: Vector a -> Vector b -> Vector (a, b)

mzipWith :: (a -> b -> c) -> Vector a -> Vector b -> Vector c

munzip :: Vector (a, b) -> (Vector a, Vector b)

FromJSON1 Vector 
Instance details

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 
Instance details

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 
Instance details

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 ()

elemseq :: Vector a -> a -> b -> b

IsList (Vector a) 
Instance details

Defined in Data.Vector

Associated Types

type Item (Vector a)

Methods

fromList :: [Item (Vector a)] -> Vector a

fromListN :: Int -> [Item (Vector a)] -> Vector a

toList :: Vector a -> [Item (Vector a)]

Eq a => Eq (Vector a) 
Instance details

Defined in Data.Vector

Methods

(==) :: Vector a -> Vector a -> Bool

(/=) :: Vector a -> Vector a -> Bool

Data a => Data (Vector a) 
Instance details

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) 
Instance details

Defined in Data.Vector

Methods

compare :: Vector a -> Vector a -> Ordering

(<) :: Vector a -> Vector a -> Bool

(<=) :: Vector a -> Vector a -> Bool

(>) :: Vector a -> Vector a -> Bool

(>=) :: Vector a -> Vector a -> Bool

max :: Vector a -> Vector a -> Vector a

min :: Vector a -> Vector a -> Vector a

Read a => Read (Vector a) 
Instance details

Defined in Data.Vector

Methods

readsPrec :: Int -> ReadS (Vector a)

readList :: ReadS [Vector a]

readPrec :: ReadPrec (Vector a)

readListPrec :: ReadPrec [Vector a]

Show a => Show (Vector a) 
Instance details

Defined in Data.Vector

Methods

showsPrec :: Int -> Vector a -> ShowS

show :: Vector a -> String

showList :: [Vector a] -> ShowS

Semigroup (Vector a) 
Instance details

Defined in Data.Vector

Methods

(<>) :: Vector a -> Vector a -> Vector a

sconcat :: NonEmpty (Vector a) -> Vector a

stimes :: Integral b => b -> Vector a -> Vector a

Monoid (Vector a) 
Instance details

Defined in Data.Vector

Methods

mempty :: Vector a

mappend :: Vector a -> Vector a -> Vector a

mconcat :: [Vector a] -> Vector a

NFData a => NFData (Vector a) 
Instance details

Defined in Data.Vector

Methods

rnf :: Vector a -> ()

Serialise a => Serialise (Vector a) 
Instance details

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) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Vector a)

parseJSONList :: Value -> Parser [Vector a]

ToJSON a => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value

toEncoding :: Vector a -> Encoding

toJSONList :: [Vector a] -> Value

toEncodingList :: [Vector a] -> Encoding

ToDhall a => ToDhall (Vector a) Source # 
Instance details

Defined in Dhall.Marshal.Encode

FromDhall a => FromDhall (Vector a) Source # 
Instance details

Defined in Dhall.Marshal.Decode

type Mutable Vector 
Instance details

Defined in Data.Vector

type Mutable Vector = MVector
type Item (Vector a) 
Instance details

Defined in Data.Vector

type Item (Vector a) = a

class Generic a #

Minimal complete definition

from, to

Instances

Instances details
Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type

Methods

from :: Bool -> Rep Bool x

to :: Rep Bool x -> Bool

Generic Ordering 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type

Methods

from :: Ordering -> Rep Ordering x

to :: Rep Ordering x -> Ordering

Generic Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Exp :: Type -> Type

Methods

from :: Exp -> Rep Exp x

to :: Rep Exp x -> Exp

Generic Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Match :: Type -> Type

Methods

from :: Match -> Rep Match x

to :: Rep Match x -> Match

Generic Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Clause :: Type -> Type

Methods

from :: Clause -> Rep Clause x

to :: Rep Clause x -> Clause

Generic Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pat :: Type -> Type

Methods

from :: Pat -> Rep Pat x

to :: Rep Pat x -> Pat

Generic Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Type :: Type -> Type

Methods

from :: Type -> Rep Type x

to :: Rep Type x -> Type

Generic Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Dec :: Type -> Type

Methods

from :: Dec -> Rep Dec x

to :: Rep Dec x -> Dec

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name :: Type -> Type

Methods

from :: Name -> Rep Name x

to :: Rep Name x -> Name

Generic FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FunDep :: Type -> Type

Methods

from :: FunDep -> Rep FunDep x

to :: Rep FunDep x -> FunDep

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnn :: Type -> Type

Methods

from :: InjectivityAnn -> Rep InjectivityAnn x

to :: Rep InjectivityAnn x -> InjectivityAnn

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: Type -> Type

Methods

from :: Overlap -> Rep Overlap x

to :: Rep Overlap x -> Overlap

Generic () 
Instance details

Defined in GHC.Generics

Associated Types

type Rep () :: Type -> Type

Methods

from :: () -> Rep () x

to :: Rep () x -> ()

Generic Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Lit :: Type -> Type

Methods

from :: Lit -> Rep Lit x

to :: Rep Lit x -> Lit

Generic NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameFlavour :: Type -> Type

Methods

from :: NameFlavour -> Rep NameFlavour x

to :: Rep NameFlavour x -> NameFlavour

Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type

Methods

from :: All -> Rep All x

to :: Rep All x -> All

Generic Any 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type

Methods

from :: Any -> Rep Any x

to :: Rep Any x -> Any

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type

Methods

from :: ExitCode -> Rep ExitCode x

to :: Rep ExitCode x -> ExitCode

Generic Version 
Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type

Methods

from :: Version -> Rep Version x

to :: Rep Version x -> Version

Generic Void 
Instance details

Defined in Data.Void

Associated Types

type Rep Void :: Type -> Type

Methods

from :: Void -> Rep Void x

to :: Rep Void x -> Void

Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type

Methods

from :: Associativity -> Rep Associativity x

to :: Rep Associativity x -> Associativity

Generic DecidedStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type

Methods

from :: DecidedStrictness -> Rep DecidedStrictness x

to :: Rep DecidedStrictness x -> DecidedStrictness

Generic Fixity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type

Methods

from :: Fixity -> Rep Fixity x

to :: Rep Fixity x -> Fixity

Generic SourceStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type

Methods

from :: SourceStrictness -> Rep SourceStrictness x

to :: Rep SourceStrictness x -> SourceStrictness

Generic SourceUnpackedness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type

Methods

from :: SourceUnpackedness -> Rep SourceUnpackedness x

to :: Rep SourceUnpackedness x -> SourceUnpackedness

Generic SHA256Digest Source # 
Instance details

Defined in Dhall.Crypto

Associated Types

type Rep SHA256Digest :: Type -> Type

Generic URIAuth 
Instance details

Defined in Network.URI

Associated Types

type Rep URIAuth :: Type -> Type

Methods

from :: URIAuth -> Rep URIAuth x

to :: Rep URIAuth x -> URIAuth

Generic URI 
Instance details

Defined in Network.URI

Associated Types

type Rep URI :: Type -> Type

Methods

from :: URI -> Rep URI x

to :: Rep URI x -> URI

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type

Methods

from :: ForeignSrcLang -> Rep ForeignSrcLang x

to :: Rep ForeignSrcLang x -> ForeignSrcLang

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension :: Type -> Type

Methods

from :: Extension -> Rep Extension x

to :: Rep Extension x -> Extension

Generic AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookup :: Type -> Type

Methods

from :: AnnLookup -> Rep AnnLookup x

to :: Rep AnnLookup x -> AnnLookup

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget :: Type -> Type

Methods

from :: AnnTarget -> Rep AnnTarget x

to :: Rep AnnTarget x -> AnnTarget

Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bang :: Type -> Type

Methods

from :: Bang -> Rep Bang x

to :: Rep Bang x -> Bang

Generic Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Body :: Type -> Type

Methods

from :: Body -> Rep Body x

to :: Rep Body x -> Body

Generic Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bytes :: Type -> Type

Methods

from :: Bytes -> Rep Bytes x

to :: Rep Bytes x -> Bytes

Generic Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Callconv :: Type -> Type

Methods

from :: Callconv -> Rep Callconv x

to :: Rep Callconv x -> Callconv

Generic Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Con :: Type -> Type

Methods

from :: Con -> Rep Con x

to :: Rep Con x -> Con

Generic DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecidedStrictness :: Type -> Type

Methods

from :: DecidedStrictness -> Rep DecidedStrictness x

to :: Rep DecidedStrictness x -> DecidedStrictness

Generic DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause :: Type -> Type

Methods

from :: DerivClause -> Rep DerivClause x

to :: Rep DerivClause x -> DerivClause

Generic DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy :: Type -> Type

Methods

from :: DerivStrategy -> Rep DerivStrategy x

to :: Rep DerivStrategy x -> DerivStrategy

Generic FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FamilyResultSig :: Type -> Type

Methods

from :: FamilyResultSig -> Rep FamilyResultSig x

to :: Rep FamilyResultSig x -> FamilyResultSig

Generic Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Fixity :: Type -> Type

Methods

from :: Fixity -> Rep Fixity x

to :: Rep Fixity x -> Fixity

Generic FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FixityDirection :: Type -> Type

Methods

from :: FixityDirection -> Rep FixityDirection x

to :: Rep FixityDirection x -> FixityDirection

Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Foreign :: Type -> Type

Methods

from :: Foreign -> Rep Foreign x

to :: Rep Foreign x -> Foreign

Generic Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Guard :: Type -> Type

Methods

from :: Guard -> Rep Guard x

to :: Rep Guard x -> Guard

Generic Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Info :: Type -> Type

Methods

from :: Info -> Rep Info x

to :: Rep Info x -> Info

Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Inline :: Type -> Type

Methods

from :: Inline -> Rep Inline x

to :: Rep Inline x -> Inline

Generic Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Loc :: Type -> Type

Methods

from :: Loc -> Rep Loc x

to :: Rep Loc x -> Loc

Generic ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModName :: Type -> Type

Methods

from :: ModName -> Rep ModName x

to :: Rep ModName x -> ModName

Generic Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Module :: Type -> Type

Methods

from :: Module -> Rep Module x

to :: Rep Module x -> Module

Generic ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleInfo :: Type -> Type

Methods

from :: ModuleInfo -> Rep ModuleInfo x

to :: Rep ModuleInfo x -> ModuleInfo

Generic NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameSpace :: Type -> Type

Methods

from :: NameSpace -> Rep NameSpace x

to :: Rep NameSpace x -> NameSpace

Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccName :: Type -> Type

Methods

from :: OccName -> Rep OccName x

to :: Rep OccName x -> OccName

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgs :: Type -> Type

Methods

from :: PatSynArgs -> Rep PatSynArgs x

to :: Rep PatSynArgs x -> PatSynArgs

Generic PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDir :: Type -> Type

Methods

from :: PatSynDir -> Rep PatSynDir x

to :: Rep PatSynDir x -> PatSynDir

Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Phases :: Type -> Type

Methods

from :: Phases -> Rep Phases x

to :: Rep Phases x -> Phases

Generic PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PkgName :: Type -> Type

Methods

from :: PkgName -> Rep PkgName x

to :: Rep PkgName x -> PkgName

Generic Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pragma :: Type -> Type

Methods

from :: Pragma -> Rep Pragma x

to :: Rep Pragma x -> Pragma

Generic Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Range :: Type -> Type

Methods

from :: Range -> Rep Range x

to :: Rep Range x -> Range

Generic Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Role :: Type -> Type

Methods

from :: Role -> Rep Role x

to :: Rep Role x -> Role

Generic RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleBndr :: Type -> Type

Methods

from :: RuleBndr -> Rep RuleBndr x

to :: Rep RuleBndr x -> RuleBndr

Generic RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleMatch :: Type -> Type

Methods

from :: RuleMatch -> Rep RuleMatch x

to :: Rep RuleMatch x -> RuleMatch

Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Safety :: Type -> Type

Methods

from :: Safety -> Rep Safety x

to :: Rep Safety x -> Safety

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictness :: Type -> Type

Methods

from :: SourceStrictness -> Rep SourceStrictness x

to :: Rep SourceStrictness x -> SourceStrictness

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness :: Type -> Type

Methods

from :: SourceUnpackedness -> Rep SourceUnpackedness x

to :: Rep SourceUnpackedness x -> SourceUnpackedness

Generic Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Stmt :: Type -> Type

Methods

from :: Stmt -> Rep Stmt x

to :: Rep Stmt x -> Stmt

Generic TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyLit :: Type -> Type

Methods

from :: TyLit -> Rep TyLit x

to :: Rep TyLit x -> TyLit

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TySynEqn :: Type -> Type

Methods

from :: TySynEqn -> Rep TySynEqn x

to :: Rep TySynEqn x -> TySynEqn

Generic TyVarBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyVarBndr :: Type -> Type

Methods

from :: TyVarBndr -> Rep TyVarBndr x

to :: Rep TyVarBndr x -> TyVarBndr

Generic TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeFamilyHead :: Type -> Type

Methods

from :: TypeFamilyHead -> Rep TypeFamilyHead x

to :: Rep TypeFamilyHead x -> TypeFamilyHead

Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode :: Type -> Type

Methods

from :: Mode -> Rep Mode x

to :: Rep Mode x -> Mode

Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Style :: Type -> Type

Methods

from :: Style -> Rep Style x

to :: Rep Style x -> Style

Generic TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep TextDetails :: Type -> Type

Methods

from :: TextDetails -> Rep TextDetails x

to :: Rep TextDetails x -> TextDetails

Generic Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Associated Types

type Rep Doc :: Type -> Type

Methods

from :: Doc -> Rep Doc x

to :: Rep Doc x -> Doc

Generic Const Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep Const :: Type -> Type

Methods

from :: Const -> Rep Const x

to :: Rep Const x -> Const

Generic Var Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep Var :: Type -> Type

Methods

from :: Var -> Rep Var x

to :: Rep Var x -> Var

Generic InvalidPosException 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep InvalidPosException :: Type -> Type

Methods

from :: InvalidPosException -> Rep InvalidPosException x

to :: Rep InvalidPosException x -> InvalidPosException

Generic Pos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep Pos :: Type -> Type

Methods

from :: Pos -> Rep Pos x

to :: Rep Pos x -> Pos

Generic SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep SourcePos :: Type -> Type

Methods

from :: SourcePos -> Rep SourcePos x

to :: Rep SourcePos x -> SourcePos

Generic Src Source # 
Instance details

Defined in Dhall.Src

Associated Types

type Rep Src :: Type -> Type

Methods

from :: Src -> Rep Src x

to :: Rep Src x -> Src

Generic CharacterSet Source # 
Instance details

Defined in Dhall.Pretty.Internal

Associated Types

type Rep CharacterSet :: Type -> Type

Generic Import Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep Import :: Type -> Type

Methods

from :: Import -> Rep Import x

to :: Rep Import x -> Import

Generic ImportHashed Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep ImportHashed :: Type -> Type

Generic ImportMode Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep ImportMode :: Type -> Type

Methods

from :: ImportMode -> Rep ImportMode x

to :: Rep ImportMode x -> ImportMode

Generic ImportType Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep ImportType :: Type -> Type

Methods

from :: ImportType -> Rep ImportType x

to :: Rep ImportType x -> ImportType

Generic URL Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep URL :: Type -> Type

Methods

from :: URL -> Rep URL x

to :: Rep URL x -> URL

Generic Scheme Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep Scheme :: Type -> Type

Methods

from :: Scheme -> Rep Scheme x

to :: Rep Scheme x -> Scheme

Generic FilePrefix Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep FilePrefix :: Type -> Type

Methods

from :: FilePrefix -> Rep FilePrefix x

to :: Rep FilePrefix x -> FilePrefix

Generic File Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep File :: Type -> Type

Methods

from :: File -> Rep File x

to :: Rep File x -> File

Generic Directory Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep Directory :: Type -> Type

Methods

from :: Directory -> Rep Directory x

to :: Rep Directory x -> Directory

Generic DhallDouble Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep DhallDouble :: Type -> Type

Methods

from :: DhallDouble -> Rep DhallDouble x

to :: Rep DhallDouble x -> DhallDouble

Generic Half 
Instance details

Defined in Numeric.Half.Internal

Associated Types

type Rep Half :: Type -> Type

Methods

from :: Half -> Rep Half x

to :: Rep Half x -> Half

Generic Value 
Instance details

Defined in Data.Aeson.Types.Internal

Associated Types

type Rep Value :: Type -> Type

Methods

from :: Value -> Rep Value x

to :: Rep Value x -> Value

Generic CompressionLevel 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep CompressionLevel :: Type -> Type

Methods

from :: CompressionLevel -> Rep CompressionLevel x

to :: Rep CompressionLevel x -> CompressionLevel

Generic CompressionStrategy 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep CompressionStrategy :: Type -> Type

Methods

from :: CompressionStrategy -> Rep CompressionStrategy x

to :: Rep CompressionStrategy x -> CompressionStrategy

Generic Format 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep Format :: Type -> Type

Methods

from :: Format -> Rep Format x

to :: Rep Format x -> Format

Generic MemoryLevel 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep MemoryLevel :: Type -> Type

Methods

from :: MemoryLevel -> Rep MemoryLevel x

to :: Rep MemoryLevel x -> MemoryLevel

Generic Method 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep Method :: Type -> Type

Methods

from :: Method -> Rep Method x

to :: Rep Method x -> Method

Generic WindowBits 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep WindowBits :: Type -> Type

Methods

from :: WindowBits -> Rep WindowBits x

to :: Rep WindowBits x -> WindowBits

Generic ColorOptions 
Instance details

Defined in Text.Pretty.Simple.Internal.Color

Associated Types

type Rep ColorOptions :: Type -> Type

Methods

from :: ColorOptions -> Rep ColorOptions x

to :: Rep ColorOptions x -> ColorOptions

Generic Style 
Instance details

Defined in Text.Pretty.Simple.Internal.Color

Associated Types

type Rep Style :: Type -> Type

Methods

from :: Style -> Rep Style x

to :: Rep Style x -> Style

Generic CheckColorTty 
Instance details

Defined in Text.Pretty.Simple.Internal.Printer

Associated Types

type Rep CheckColorTty :: Type -> Type

Methods

from :: CheckColorTty -> Rep CheckColorTty x

to :: Rep CheckColorTty x -> CheckColorTty

Generic OutputOptions 
Instance details

Defined in Text.Pretty.Simple.Internal.Printer

Associated Types

type Rep OutputOptions :: Type -> Type

Methods

from :: OutputOptions -> Rep OutputOptions x

to :: Rep OutputOptions x -> OutputOptions

Generic StringOutputStyle 
Instance details

Defined in Text.Pretty.Simple.Internal.Printer

Associated Types

type Rep StringOutputStyle :: Type -> Type

Methods

from :: StringOutputStyle -> Rep StringOutputStyle x

to :: Rep StringOutputStyle x -> StringOutputStyle

Generic Expr 
Instance details

Defined in Text.Pretty.Simple.Internal.Expr

Associated Types

type Rep Expr :: Type -> Type

Methods

from :: Expr -> Rep Expr x

to :: Rep Expr x -> Expr

Generic [a] 
Instance details

Defined in GHC.Generics

Associated Types

type Rep [a] :: Type -> Type

Methods

from :: [a] -> Rep [a] x

to :: Rep [a] x -> [a]

Generic (Maybe a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: Type -> Type

Methods

from :: Maybe a -> Rep (Maybe a) x

to :: Rep (Maybe a) x -> Maybe a

Generic (Par1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Par1 p) :: Type -> Type

Methods

from :: Par1 p -> Rep (Par1 p) x

to :: Rep (Par1 p) x -> Par1 p

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x

to :: Rep (NonEmpty a) x -> NonEmpty a

Generic (Down a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a) :: Type -> Type

Methods

from :: Down a -> Rep (Down a) x

to :: Rep (Down a) x -> Down a

Generic (Dual a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Dual a) :: Type -> Type

Methods

from :: Dual a -> Rep (Dual a) x

to :: Rep (Dual a) x -> Dual a

Generic (First a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (First a) :: Type -> Type

Methods

from :: First a -> Rep (First a) x

to :: Rep (First a) x -> First a

Generic (First a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (First a) :: Type -> Type

Methods

from :: First a -> Rep (First a) x

to :: Rep (First a) x -> First a

Generic (Identity a) 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a) :: Type -> Type

Methods

from :: Identity a -> Rep (Identity a) x

to :: Rep (Identity a) x -> Identity a

Generic (Last a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Last a) :: Type -> Type

Methods

from :: Last a -> Rep (Last a) x

to :: Rep (Last a) x -> Last a

Generic (Last a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Last a) :: Type -> Type

Methods

from :: Last a -> Rep (Last a) x

to :: Rep (Last a) x -> Last a

Generic (Max a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Max a) :: Type -> Type

Methods

from :: Max a -> Rep (Max a) x

to :: Rep (Max a) x -> Max a

Generic (Min a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Min a) :: Type -> Type

Methods

from :: Min a -> Rep (Min a) x

to :: Rep (Min a) x -> Min a

Generic (Option a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Option a) :: Type -> Type

Methods

from :: Option a -> Rep (Option a) x

to :: Rep (Option a) x -> Option a

Generic (Product a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a) :: Type -> Type

Methods

from :: Product a -> Rep (Product a) x

to :: Rep (Product a) x -> Product a

Generic (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a) :: Type -> Type

Methods

from :: Sum a -> Rep (Sum a) x

to :: Rep (Sum a) x -> Sum a

Generic (WrappedMonoid m) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (WrappedMonoid m) :: Type -> Type

Methods

from :: WrappedMonoid m -> Rep (WrappedMonoid m) x

to :: Rep (WrappedMonoid m) x -> WrappedMonoid m

Generic (ZipList a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (ZipList a) :: Type -> Type

Methods

from :: ZipList a -> Rep (ZipList a) x

to :: Rep (ZipList a) x -> ZipList a

Generic (Complex a) 
Instance details

Defined in Data.Complex

Associated Types

type Rep (Complex a) :: Type -> Type

Methods

from :: Complex a -> Rep (Complex a) x

to :: Rep (Complex a) x -> Complex a

Generic (Endo a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Endo a) :: Type -> Type

Methods

from :: Endo a -> Rep (Endo a) x

to :: Rep (Endo a) x -> Endo a

Generic (HistoriedResponse body) 
Instance details

Defined in Network.HTTP.Client

Associated Types

type Rep (HistoriedResponse body) :: Type -> Type

Methods

from :: HistoriedResponse body -> Rep (HistoriedResponse body) x

to :: Rep (HistoriedResponse body) x -> HistoriedResponse body

Generic (Tree a) 
Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a) :: Type -> Type

Methods

from :: Tree a -> Rep (Tree a) x

to :: Rep (Tree a) x -> Tree a

Generic (Digit a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Digit a) :: Type -> Type

Methods

from :: Digit a -> Rep (Digit a) x

to :: Rep (Digit a) x -> Digit a

Generic (Elem a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Elem a) :: Type -> Type

Methods

from :: Elem a -> Rep (Elem a) x

to :: Rep (Elem a) x -> Elem a

Generic (FingerTree a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (FingerTree a) :: Type -> Type

Methods

from :: FingerTree a -> Rep (FingerTree a) x

to :: Rep (FingerTree a) x -> FingerTree a

Generic (Node a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Node a) :: Type -> Type

Methods

from :: Node a -> Rep (Node a) x

to :: Rep (Node a) x -> Node a

Generic (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewL a) :: Type -> Type

Methods

from :: ViewL a -> Rep (ViewL a) x

to :: Rep (ViewL a) x -> ViewL a

Generic (ViewR a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewR a) :: Type -> Type

Methods

from :: ViewR a -> Rep (ViewR a) x

to :: Rep (ViewR a) x -> ViewR a

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep (Doc a) :: Type -> Type

Methods

from :: Doc a -> Rep (Doc a) x

to :: Rep (Doc a) x -> Doc a

Generic (Set a) Source # 
Instance details

Defined in Dhall.Set

Associated Types

type Rep (Set a) :: Type -> Type

Methods

from :: Set a -> Rep (Set a) x

to :: Rep (Set a) x -> Set a

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (Doc ann) :: Type -> Type

Methods

from :: Doc ann -> Rep (Doc ann) x

to :: Rep (Doc ann) x -> Doc ann

Generic (SimpleDocStream ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (SimpleDocStream ann) :: Type -> Type

Methods

from :: SimpleDocStream ann -> Rep (SimpleDocStream ann) x

to :: Rep (SimpleDocStream ann) x -> SimpleDocStream ann

Generic (ErrorFancy e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ErrorFancy e) :: Type -> Type

Methods

from :: ErrorFancy e -> Rep (ErrorFancy e) x

to :: Rep (ErrorFancy e) x -> ErrorFancy e

Generic (ErrorItem t) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ErrorItem t) :: Type -> Type

Methods

from :: ErrorItem t -> Rep (ErrorItem t) x

to :: Rep (ErrorItem t) x -> ErrorItem t

Generic (PosState s) 
Instance details

Defined in Text.Megaparsec.State

Associated Types

type Rep (PosState s) :: Type -> Type

Methods

from :: PosState s -> Rep (PosState s) x

to :: Rep (PosState s) x -> PosState s

Generic (FieldSelection s) Source # 
Instance details

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 (Fix f) 
Instance details

Defined in Data.Fix

Associated Types

type Rep (Fix f) :: Type -> Type

Methods

from :: Fix f -> Rep (Fix f) x

to :: Rep (Fix f) x -> Fix f

Generic (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Associated Types

type Rep (Maybe a) :: Type -> Type

Methods

from :: Maybe a -> Rep (Maybe a) x

to :: Rep (Maybe a) x -> Maybe a

Generic (CommaSeparated a) 
Instance details

Defined in Text.Pretty.Simple.Internal.Expr

Associated Types

type Rep (CommaSeparated a) :: Type -> Type

Methods

from :: CommaSeparated a -> Rep (CommaSeparated a) x

to :: Rep (CommaSeparated a) x -> CommaSeparated a

Generic (Either a b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Either a b) :: Type -> Type

Methods

from :: Either a b -> Rep (Either a b) x

to :: Rep (Either a b) x -> Either a b

Generic (V1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (V1 p) :: Type -> Type

Methods

from :: V1 p -> Rep (V1 p) x

to :: Rep (V1 p) x -> V1 p

Generic (U1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (U1 p) :: Type -> Type

Methods

from :: U1 p -> Rep (U1 p) x

to :: Rep (U1 p) x -> U1 p

Generic (a, b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b) :: Type -> Type

Methods

from :: (a, b) -> Rep (a, b) x

to :: Rep (a, b) x -> (a, b)

Generic (Arg a b) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Arg a b) :: Type -> Type

Methods

from :: Arg a b -> Rep (Arg a b) x

to :: Rep (Arg a b) x -> Arg a b

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type

Methods

from :: Proxy t -> Rep (Proxy t) x

to :: Rep (Proxy t) x -> Proxy t

Generic (WrappedMonad m a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedMonad m a) :: Type -> Type

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a

Generic (Map k v) Source # 
Instance details

Defined in Dhall.Map

Associated Types

type Rep (Map k v) :: Type -> Type

Methods

from :: Map k v -> Rep (Map k v) x

to :: Rep (Map k v) x -> Map k v

Generic (Expr s a) Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep (Expr s a) :: Type -> Type

Methods

from :: Expr s a -> Rep (Expr s a) x

to :: Rep (Expr s a) x -> Expr s a

Generic (ParseError s e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ParseError s e) :: Type -> Type

Methods

from :: ParseError s e -> Rep (ParseError s e) x

to :: Rep (ParseError s e) x -> ParseError s e

Generic (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ParseErrorBundle s e) :: Type -> Type

Methods

from :: ParseErrorBundle s e -> Rep (ParseErrorBundle s e) x

to :: Rep (ParseErrorBundle s e) x -> ParseErrorBundle s e

Generic (State s e) 
Instance details

Defined in Text.Megaparsec.State

Associated Types

type Rep (State s e) :: Type -> Type

Methods

from :: State s e -> Rep (State s e) x

to :: Rep (State s e) x -> State s e

Generic (FunctionBinding s a) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep (Chunks s a) :: Type -> Type

Methods

from :: Chunks s a -> Rep (Chunks s a) x

to :: Rep (Chunks s a) x -> Chunks s a

Generic (Binding s a) Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep (Binding s a) :: Type -> Type

Methods

from :: Binding s a -> Rep (Binding s a) x

to :: Rep (Binding s a) x -> Binding s a

Generic (Either a b) 
Instance details

Defined in Data.Strict.Either

Associated Types

type Rep (Either a b) :: Type -> Type

Methods

from :: Either a b -> Rep (Either a b) x

to :: Rep (Either a b) x -> Either a b

Generic (These a b) 
Instance details

Defined in Data.Strict.These

Associated Types

type Rep (These a b) :: Type -> Type

Methods

from :: These a b -> Rep (These a b) x

to :: Rep (These a b) x -> These a b

Generic (These a b) 
Instance details

Defined in Data.These

Associated Types

type Rep (These a b) :: Type -> Type

Methods

from :: These a b -> Rep (These a b) x

to :: Rep (These a b) x -> These a b

Generic (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Associated Types

type Rep (Pair a b) :: Type -> Type

Methods

from :: Pair a b -> Rep (Pair a b) x

to :: Rep (Pair a b) x -> Pair a b

Generic (Rec1 f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Rec1 f p) :: Type -> Type

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x

to :: Rep (Rec1 f p) x -> Rec1 f p

Generic (URec (Ptr ()) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p

Generic (URec Char p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p) :: Type -> Type

Methods

from :: URec Char p -> Rep (URec Char p) x

to :: Rep (URec Char p) x -> URec Char p

Generic (URec Double p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p) :: Type -> Type

Methods

from :: URec Double p -> Rep (URec Double p) x

to :: Rep (URec Double p) x -> URec Double p

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) :: Type -> Type

Methods

from :: URec Float p -> Rep (URec Float p) x

to :: Rep (URec Float p) x -> URec Float p

Generic (URec Int p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p) :: Type -> Type

Methods

from :: URec Int p -> Rep (URec Int p) x

to :: Rep (URec Int p) x -> URec Int p

Generic (URec Word p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type

Methods

from :: URec Word p -> Rep (URec Word p) x

to :: Rep (URec Word p) x -> URec Word p

Generic (a, b, c) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c) :: Type -> Type

Methods

from :: (a, b, c) -> Rep (a, b, c) x

to :: Rep (a, b, c) x -> (a, b, c)

Generic (Const a b) 
Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b) :: Type -> Type

Methods

from :: Const a b -> Rep (Const a b) x

to :: Rep (Const a b) x -> Const a b

Generic (WrappedArrow a b c) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedArrow a b c) :: Type -> Type

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c

Generic (Kleisli m a b) 
Instance details

Defined in Control.Arrow

Associated Types

type Rep (Kleisli m a b) :: Type -> Type

Methods

from :: Kleisli m a b -> Rep (Kleisli m a b) x

to :: Rep (Kleisli m a b) x -> Kleisli m a b

Generic (Ap f a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a) :: Type -> Type

Methods

from :: Ap f a -> Rep (Ap f a) x

to :: Rep (Ap f a) x -> Ap f a

Generic (Alt f a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a) :: Type -> Type

Methods

from :: Alt f a -> Rep (Alt f a) x

to :: Rep (Alt f a) x -> Alt f a

Generic (Tagged s b) 
Instance details

Defined in Data.Tagged

Associated Types

type Rep (Tagged s b) :: Type -> Type

Methods

from :: Tagged s b -> Rep (Tagged s b) x

to :: Rep (Tagged s b) x -> Tagged s b

Generic (These1 f g a) 
Instance details

Defined in Data.Functor.These

Associated Types

type Rep (These1 f g a) :: Type -> Type

Methods

from :: These1 f g a -> Rep (These1 f g a) x

to :: Rep (These1 f g a) x -> These1 f g a

Generic (Join p a) 
Instance details

Defined in Data.Bifunctor.Join

Associated Types

type Rep (Join p a) :: Type -> Type

Methods

from :: Join p a -> Rep (Join p a) x

to :: Rep (Join p a) x -> Join p a

Generic (K1 i c p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (K1 i c p) :: Type -> Type

Methods

from :: K1 i c p -> Rep (K1 i c p) x

to :: Rep (K1 i c p) x -> K1 i c p

Generic ((f :+: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p) :: Type -> Type

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x

to :: Rep ((f :+: g) p) x -> (f :+: g) p

Generic ((f :*: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p) :: Type -> Type

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x

to :: Rep ((f :*: g) p) x -> (f :*: g) p

Generic (a, b, c, d) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d) :: Type -> Type

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x

to :: Rep (a, b, c, d) x -> (a, b, c, d)

Generic (Product f g a) 
Instance details

Defined in Data.Functor.Product

Associated Types

type Rep (Product f g a) :: Type -> Type

Methods

from :: Product f g a -> Rep (Product f g a) x

to :: Rep (Product f g a) x -> Product f g a

Generic (Sum f g a) 
Instance details

Defined in Data.Functor.Sum

Associated Types

type Rep (Sum f g a) :: Type -> Type

Methods

from :: Sum f g a -> Rep (Sum f g a) x

to :: Rep (Sum f g a) x -> Sum f g a

Generic (M1 i c f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (M1 i c f p) :: Type -> Type

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x

to :: Rep (M1 i c f p) x -> M1 i c f p

Generic ((f :.: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :.: g) p) :: Type -> Type

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x

to :: Rep ((f :.: g) p) x -> (f :.: g) p

Generic (a, b, c, d, e) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e) :: Type -> Type

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e)

Generic (Compose f g a) 
Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep (Compose f g a) :: Type -> Type

Methods

from :: Compose f g a -> Rep (Compose f g a) x

to :: Rep (Compose f g a) x -> Compose f g a

Generic (Clown f a b) 
Instance details

Defined in Data.Bifunctor.Clown

Associated Types

type Rep (Clown f a b) :: Type -> Type

Methods

from :: Clown f a b -> Rep (Clown f a b) x

to :: Rep (Clown f a b) x -> Clown f a b

Generic (Joker g a b) 
Instance details

Defined in Data.Bifunctor.Joker

Associated Types

type Rep (Joker g a b) :: Type -> Type

Methods

from :: Joker g a b -> Rep (Joker g a b) x

to :: Rep (Joker g a b) x -> Joker g a b

Generic (Flip p a b) 
Instance details

Defined in Data.Bifunctor.Flip

Associated Types

type Rep (Flip p a b) :: Type -> Type

Methods

from :: Flip p a b -> Rep (Flip p a b) x

to :: Rep (Flip p a b) x -> Flip p a b

Generic (WrappedBifunctor p a b) 
Instance details

Defined in Data.Bifunctor.Wrapped

Associated Types

type Rep (WrappedBifunctor p a b) :: Type -> Type

Methods

from :: WrappedBifunctor p a b -> Rep (WrappedBifunctor p a b) x

to :: Rep (WrappedBifunctor p a b) x -> WrappedBifunctor p a b

Generic (a, b, c, d, e, f) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f) :: Type -> Type

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f)

Generic (Product f g a b) 
Instance details

Defined in Data.Bifunctor.Product

Associated Types

type Rep (Product f g a b) :: Type -> Type

Methods

from :: Product f g a b -> Rep (Product f g a b) x

to :: Rep (Product f g a b) x -> Product f g a b

Generic (Sum p q a b) 
Instance details

Defined in Data.Bifunctor.Sum

Associated Types

type Rep (Sum p q a b) :: Type -> Type

Methods

from :: Sum p q a b -> Rep (Sum p q a b) x

to :: Rep (Sum p q a b) x -> Sum p q a b

Generic (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g) :: Type -> Type

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g)

Generic (Tannen f p a b) 
Instance details

Defined in Data.Bifunctor.Tannen

Associated Types

type Rep (Tannen f p a b) :: Type -> Type

Methods

from :: Tannen f p a b -> Rep (Tannen f p a b) x

to :: Rep (Tannen f p a b) x -> Tannen f p a b

Generic (Biff p f g a b) 
Instance details

Defined in Data.Bifunctor.Biff

Associated Types

type Rep (Biff p f g a b) :: Type -> Type

Methods

from :: Biff p f g a b -> Rep (Biff p f g a b) x

to :: Rep (Biff p f g a b) x -> Biff p f g a b