dhall-1.41.2: A configuration language guaranteed to terminate
Safe HaskellSafe-Inferred
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' -> a) -> Encoder a -> Encoder a' Source #

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

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

Instances

Instances details
ToDhall Void Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Int16 Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Int32 Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Int64 Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Int8 Source # 
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 Word8 Source #

Encode a Word8 to a Dhall Natural.

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

Defined in Dhall.Marshal.Encode

ToDhall Scientific Source # 
Instance details

Defined in Dhall.Marshal.Encode

Methods

injectWith :: InputNormalizer -> Encoder Scientific Source #

ToDhall Text Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall Text Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall ShortText Source # 
Instance details

Defined in Dhall.Marshal.Encode

Methods

injectWith :: InputNormalizer -> Encoder ShortText Source #

ToDhall Day Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall DayOfWeek Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall UTCTime Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall LocalTime Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall TimeOfDay Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall TimeZone Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall ZonedTime Source # 
Instance details

Defined in Dhall.Marshal.Encode

ToDhall String 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 () Source # 
Instance details

Defined in Dhall.Marshal.Encode

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 Word Source #

Encode a Word to a Dhall Natural.

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

Defined in Dhall.Marshal.Encode

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

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

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

Defined in Dhall.Marshal.Encode

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

Defined in Dhall.Marshal.Encode

ToDhall a => ToDhall [a] 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

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

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

Defined in Dhall.Marshal.Encode

(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' -> a) -> RecordEncoder a -> RecordEncoder a' Source #

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

Divisible RecordEncoder Source # 
Instance details

Defined in Dhall.Marshal.Encode

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' -> a) -> UnionEncoder a -> UnionEncoder a' Source #

(>$) :: b -> UnionEncoder b -> UnionEncoder a Source #

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

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

Defined in Dhall.Marshal.Encode

(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

(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

(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

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

Defined in Dhall.Marshal.Encode

(Constructor c, GenericToDhall (f :+: g), GenericToDhall h) => GenericToDhall ((f :+: g) :+: M1 C c h) 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

(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

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

Defined in Dhall.Marshal.Encode

GenericToDhall f => GenericToDhall (M1 D d 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

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

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
FromDhall (f (Result f)) => FromDhall (Result f) Source # 
Instance details

Defined in Dhall.Marshal.Decode

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

Defined in Dhall.Marshal.Encode

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

This is an infix alias for contramap.

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

Infix divided

Re-exports

data Natural Source #

Natural number

Invariant: numbers <= 0xffffffffffffffff use the NS constructor

Instances

Instances details
FromJSON Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

Data Natural

Since: base-4.8.0.0

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Natural Source #

toConstr :: Natural -> Constr Source #

dataTypeOf :: Natural -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Bits Natural

Since: base-4.8.0

Instance details

Defined in GHC.Bits

Enum Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Enum

Num Natural

Note that Natural's Num instance isn't a ring: no element but 0 has an additive inverse. It is a semiring though.

Since: base-4.8.0.0

Instance details

Defined in GHC.Num

Read Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Read

Integral Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Real Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Show Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Show

PrintfArg Natural

Since: base-4.8.0.0

Instance details

Defined in Text.Printf

Subtractive Natural 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Natural

Methods

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

NFData Natural

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Natural -> () Source #

FromDhall Natural Source # 
Instance details

Defined in Dhall.Marshal.Decode

ToDhall Natural Source # 
Instance details

Defined in Dhall.Marshal.Encode

Eq Natural 
Instance details

Defined in GHC.Num.Natural

Ord Natural 
Instance details

Defined in GHC.Num.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 Source #

prettyList :: [Natural] -> Doc ann Source #

UniformRange Natural 
Instance details

Defined in System.Random.Internal

Methods

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

Serialise Natural 
Instance details

Defined in Codec.Serialise.Class

Methods

encode :: Natural -> Encoding

decode :: Decoder s Natural

encodeList :: [Natural] -> Encoding

decodeList :: Decoder s [Natural]

KnownNat n => HasResolution (n :: Nat)

For example, Fixed 1000 will give you a Fixed with a resolution of 1000.

Instance details

Defined in Data.Fixed

Methods

resolution :: p n -> Integer Source #

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Natural -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Natural -> Code m Natural Source #

type Difference Natural 
Instance details

Defined in Basement.Numerical.Subtractive

type Difference Natural = Maybe Natural
type Compare (a :: Natural) (b :: Natural) 
Instance details

Defined in Data.Type.Ord

type Compare (a :: Natural) (b :: Natural) = CmpNat a b

data Seq a Source #

General-purpose finite sequences.

Instances

Instances details
FromJSON1 Seq 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Seq a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Seq a] Source #

ToJSON1 Seq 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Seq a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Seq a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Seq a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Seq a] -> Encoding Source #

MonadFix Seq

Since: containers-0.5.11

Instance details

Defined in Data.Sequence.Internal

Methods

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

MonadZip Seq
 mzipWith = zipWith
 munzip = unzip
Instance details

Defined in Data.Sequence.Internal

Methods

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

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

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

Foldable Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

fold :: Monoid m => Seq m -> m Source #

foldMap :: Monoid m => (a -> m) -> Seq a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Seq a -> m Source #

foldr :: (a -> b -> b) -> b -> Seq a -> b Source #

foldr' :: (a -> b -> b) -> b -> Seq a -> b Source #

foldl :: (b -> a -> b) -> b -> Seq a -> b Source #

foldl' :: (b -> a -> b) -> b -> Seq a -> b Source #

foldr1 :: (a -> a -> a) -> Seq a -> a Source #

foldl1 :: (a -> a -> a) -> Seq a -> a Source #

toList :: Seq a -> [a] Source #

null :: Seq a -> Bool Source #

length :: Seq a -> Int Source #

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

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

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

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

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

Eq1 Seq

Since: containers-0.5.9

Instance details

Defined in Data.Sequence.Internal

Methods

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

Ord1 Seq

Since: containers-0.5.9

Instance details

Defined in Data.Sequence.Internal

Methods

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

Read1 Seq

Since: containers-0.5.9

Instance details

Defined in Data.Sequence.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Seq a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Seq a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Seq a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Seq a] Source #

Show1 Seq

Since: containers-0.5.9

Instance details

Defined in Data.Sequence.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Seq a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Seq a] -> ShowS Source #

Traversable Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

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

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

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

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

Alternative Seq

Since: containers-0.5.4

Instance details

Defined in Data.Sequence.Internal

Methods

empty :: Seq a Source #

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

some :: Seq a -> Seq [a] Source #

many :: Seq a -> Seq [a] Source #

Applicative Seq

Since: containers-0.5.4

Instance details

Defined in Data.Sequence.Internal

Methods

pure :: a -> Seq a Source #

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

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

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

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

Functor Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

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

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

Monad Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

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

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

return :: a -> Seq a Source #

MonadPlus Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

mzero :: Seq a Source #

mplus :: Seq a -> Seq a -> Seq a Source #

UnzipWith Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

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

Hashable1 Seq 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Seq a -> Int

FoldableWithIndex Int Seq 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> Seq a -> m Source #

ifoldMap' :: Monoid m => (Int -> a -> m) -> Seq a -> m Source #

ifoldr :: (Int -> a -> b -> b) -> b -> Seq a -> b Source #

ifoldl :: (Int -> b -> a -> b) -> b -> Seq a -> b Source #

ifoldr' :: (Int -> a -> b -> b) -> b -> Seq a -> b Source #

ifoldl' :: (Int -> b -> a -> b) -> b -> Seq a -> b Source #

FunctorWithIndex Int Seq

The position in the Seq is available as the index.

Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> Seq a -> Seq b Source #

TraversableWithIndex Int Seq 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b) Source #

Lift a => Lift (Seq a :: Type)

Since: containers-0.6.6

Instance details

Defined in Data.Sequence.Internal

Methods

lift :: Quote m => Seq a -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Seq a -> Code m (Seq a) Source #

FromJSON a => FromJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON a => ToJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) Source #

toConstr :: Seq a -> Constr Source #

dataTypeOf :: Seq a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) Source #

a ~ Char => IsString (Seq a)

Since: containers-0.5.7

Instance details

Defined in Data.Sequence.Internal

Methods

fromString :: String -> Seq a Source #

Monoid (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

mempty :: Seq a Source #

mappend :: Seq a -> Seq a -> Seq a Source #

mconcat :: [Seq a] -> Seq a Source #

Semigroup (Seq a)

Since: containers-0.5.7

Instance details

Defined in Data.Sequence.Internal

Methods

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

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

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

IsList (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Item (Seq a) Source #

Methods

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

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

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

Read a => Read (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Show a => Show (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

showsPrec :: Int -> Seq a -> ShowS Source #

show :: Seq a -> String Source #

showList :: [Seq a] -> ShowS Source #

NFData a => NFData (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

rnf :: Seq a -> () Source #

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

Defined in Dhall.Marshal.Decode

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

Defined in Dhall.Marshal.Encode

Eq a => Eq (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

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

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

Ord a => Ord (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

compare :: Seq a -> Seq a -> Ordering Source #

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

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

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

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

max :: Seq a -> Seq a -> Seq a Source #

min :: Seq a -> Seq a -> Seq a Source #

Hashable v => Hashable (Seq v) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Seq v -> Int

hash :: Seq v -> Int

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]

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 Source #

A space efficient, packed, unboxed Unicode text type.

Instances

Instances details
FromJSON Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

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]

FromDhall Text Source # 
Instance details

Defined in Dhall.Marshal.Decode

ToDhall Text Source # 
Instance details

Defined in Dhall.Marshal.Encode

Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int

hash :: Text -> Int

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

Pretty Text

Automatically converts all newlines to line.

>>> pretty ("hello\nworld" :: Text)
hello
world

Note that line can be undone by group:

>>> group (pretty ("hello\nworld" :: Text))
hello world

Manually use hardline if you definitely want newlines.

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann Source #

prettyList :: [Text] -> Doc ann Source #

Serialise Text 
Instance details

Defined in Codec.Serialise.Class

Methods

encode :: Text -> Encoding

decode :: Decoder s Text

encodeList :: [Text] -> Encoding

decodeList :: Decoder s [Text]

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

Stream (NoShareInput Text) 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token (NoShareInput Text)

type Tokens (NoShareInput Text)

Methods

tokenToChunk :: Proxy (NoShareInput Text) -> Token (NoShareInput Text) -> Tokens (NoShareInput Text)

tokensToChunk :: Proxy (NoShareInput Text) -> [Token (NoShareInput Text)] -> Tokens (NoShareInput Text)

chunkToTokens :: Proxy (NoShareInput Text) -> Tokens (NoShareInput Text) -> [Token (NoShareInput Text)]

chunkLength :: Proxy (NoShareInput Text) -> Tokens (NoShareInput Text) -> Int

chunkEmpty :: Proxy (NoShareInput Text) -> Tokens (NoShareInput Text) -> Bool

take1_ :: NoShareInput Text -> Maybe (Token (NoShareInput Text), NoShareInput Text)

takeN_ :: Int -> NoShareInput Text -> Maybe (Tokens (NoShareInput Text), NoShareInput Text)

takeWhile_ :: (Token (NoShareInput Text) -> Bool) -> NoShareInput Text -> (Tokens (NoShareInput Text), NoShareInput Text)

Stream (ShareInput Text) 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token (ShareInput Text)

type Tokens (ShareInput Text)

Methods

tokenToChunk :: Proxy (ShareInput Text) -> Token (ShareInput Text) -> Tokens (ShareInput Text)

tokensToChunk :: Proxy (ShareInput Text) -> [Token (ShareInput Text)] -> Tokens (ShareInput Text)

chunkToTokens :: Proxy (ShareInput Text) -> Tokens (ShareInput Text) -> [Token (ShareInput Text)]

chunkLength :: Proxy (ShareInput Text) -> Tokens (ShareInput Text) -> Int

chunkEmpty :: Proxy (ShareInput Text) -> Tokens (ShareInput Text) -> Bool

take1_ :: ShareInput Text -> Maybe (Token (ShareInput Text), ShareInput Text)

takeN_ :: Int -> ShareInput Text -> Maybe (Tokens (ShareInput Text), ShareInput Text)

takeWhile_ :: (Token (ShareInput Text) -> Bool) -> ShareInput Text -> (Tokens (ShareInput Text), ShareInput Text)

type ChunkElem Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type ChunkElem Text = Char
type State Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State Text = Buffer
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 = Token (ShareInput Text)
type Tokens Text 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens Text = Tokens (ShareInput Text)
type Token (NoShareInput Text) 
Instance details

Defined in Text.Megaparsec.Stream

type Token (NoShareInput Text) = Char
type Token (ShareInput Text) 
Instance details

Defined in Text.Megaparsec.Stream

type Token (ShareInput Text) = Char
type Tokens (NoShareInput Text) 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens (NoShareInput Text) = Text
type Tokens (ShareInput Text) 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens (ShareInput Text) = Text

data Vector a Source #

Boxed vectors, supporting efficient slicing.

Instances

Instances details
FromJSON1 Vector 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Vector a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Vector a] Source #

ToJSON1 Vector 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Vector a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Vector a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Vector a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Vector a] -> Encoding Source #

MonadFail Vector

Since: vector-0.12.1.0

Instance details

Defined in Data.Vector

Methods

fail :: String -> Vector a Source #

MonadFix Vector

This instance has the same semantics as the one for lists.

Since: vector-0.12.2.0

Instance details

Defined in Data.Vector

Methods

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

MonadZip Vector 
Instance details

Defined in Data.Vector

Methods

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

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

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

Foldable Vector 
Instance details

Defined in Data.Vector

Methods

fold :: Monoid m => Vector m -> m Source #

foldMap :: Monoid m => (a -> m) -> Vector a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Vector a -> m Source #

foldr :: (a -> b -> b) -> b -> Vector a -> b Source #

foldr' :: (a -> b -> b) -> b -> Vector a -> b Source #

foldl :: (b -> a -> b) -> b -> Vector a -> b Source #

foldl' :: (b -> a -> b) -> b -> Vector a -> b Source #

foldr1 :: (a -> a -> a) -> Vector a -> a Source #

foldl1 :: (a -> a -> a) -> Vector a -> a Source #

toList :: Vector a -> [a] Source #

null :: Vector a -> Bool Source #

length :: Vector a -> Int Source #

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

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

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

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

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

Eq1 Vector 
Instance details

Defined in Data.Vector

Methods

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

Ord1 Vector 
Instance details

Defined in Data.Vector

Methods

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

Read1 Vector 
Instance details

Defined in Data.Vector

Show1 Vector 
Instance details

Defined in Data.Vector

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Vector a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Vector a] -> ShowS Source #

Traversable Vector 
Instance details

Defined in Data.Vector

Methods

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

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

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

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

Alternative Vector 
Instance details

Defined in Data.Vector

Methods

empty :: Vector a Source #

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

some :: Vector a -> Vector [a] Source #

many :: Vector a -> Vector [a] Source #

Applicative Vector 
Instance details

Defined in Data.Vector

Methods

pure :: a -> Vector a Source #

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

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

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

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

Functor Vector 
Instance details

Defined in Data.Vector

Methods

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

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

Monad Vector 
Instance details

Defined in Data.Vector

Methods

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

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

return :: a -> Vector a Source #

MonadPlus Vector 
Instance details

Defined in Data.Vector

Methods

mzero :: Vector a Source #

mplus :: Vector a -> Vector a -> Vector a Source #

NFData1 Vector

Since: vector-0.12.1.0

Instance details

Defined in Data.Vector

Methods

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

Vector Vector a 
Instance details

Defined in Data.Vector

FromJSON a => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON a => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) Source #

toConstr :: Vector a -> Constr Source #

dataTypeOf :: Vector a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) Source #

Monoid (Vector a) 
Instance details

Defined in Data.Vector

Semigroup (Vector a) 
Instance details

Defined in Data.Vector

Methods

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

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

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

IsList (Vector a) 
Instance details

Defined in Data.Vector

Associated Types

type Item (Vector a) Source #

Methods

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

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

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

Read a => Read (Vector a) 
Instance details

Defined in Data.Vector

Show a => Show (Vector a) 
Instance details

Defined in Data.Vector

NFData a => NFData (Vector a) 
Instance details

Defined in Data.Vector

Methods

rnf :: Vector a -> () Source #

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

Defined in Dhall.Marshal.Decode

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

Defined in Dhall.Marshal.Encode

Eq a => Eq (Vector a) 
Instance details

Defined in Data.Vector

Methods

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

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

Ord a => Ord (Vector a) 
Instance details

Defined in Data.Vector

Methods

compare :: Vector a -> Vector a -> Ordering Source #

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

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

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

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

max :: Vector a -> Vector a -> Vector a Source #

min :: Vector a -> Vector a -> Vector a Source #

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]

type Mutable Vector 
Instance details

Defined in Data.Vector

type Item (Vector a) 
Instance details

Defined in Data.Vector

type Item (Vector a) = a

class Generic a Source #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

A Generic instance must satisfy the following laws:

from . toid
to . fromid

Minimal complete definition

from, to

Instances

Instances details
Generic Value 
Instance details

Defined in Data.Aeson.Types.Internal

Associated Types

type Rep Value :: Type -> Type Source #

Methods

from :: Value -> Rep Value x Source #

to :: Rep Value x -> Value Source #

Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type Source #

Methods

from :: All -> Rep All x Source #

to :: Rep All x -> All Source #

Generic Any 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type Source #

Methods

from :: Any -> Rep Any x Source #

to :: Rep Any x -> Any Source #

Generic Version 
Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type Source #

Generic Void 
Instance details

Defined in Data.Void

Associated Types

type Rep Void :: Type -> Type Source #

Methods

from :: Void -> Rep Void x Source #

to :: Rep Void x -> Void Source #

Generic Fingerprint 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fingerprint :: Type -> Type Source #

Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type Source #

Generic DecidedStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type Source #

Generic Fixity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type Source #

Generic SourceStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type Source #

Generic SourceUnpackedness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type Source #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type Source #

Generic CCFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep CCFlags :: Type -> Type Source #

Generic ConcFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ConcFlags :: Type -> Type Source #

Generic DebugFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DebugFlags :: Type -> Type Source #

Generic DoCostCentres 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoCostCentres :: Type -> Type Source #

Generic DoHeapProfile 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoHeapProfile :: Type -> Type Source #

Generic DoTrace 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoTrace :: Type -> Type Source #

Generic GCFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep GCFlags :: Type -> Type Source #

Generic GiveGCStats 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep GiveGCStats :: Type -> Type Source #

Generic MiscFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep MiscFlags :: Type -> Type Source #

Generic ParFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ParFlags :: Type -> Type Source #

Generic ProfFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ProfFlags :: Type -> Type Source #

Generic RTSFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep RTSFlags :: Type -> Type Source #

Generic TickyFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep TickyFlags :: Type -> Type Source #

Generic TraceFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep TraceFlags :: Type -> Type Source #

Generic SrcLoc 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SrcLoc :: Type -> Type Source #

Generic GCDetails 
Instance details

Defined in GHC.Stats

Associated Types

type Rep GCDetails :: Type -> Type Source #

Generic RTSStats 
Instance details

Defined in GHC.Stats

Associated Types

type Rep RTSStats :: Type -> Type Source #

Generic GeneralCategory 
Instance details

Defined in GHC.Generics

Associated Types

type Rep GeneralCategory :: Type -> Type Source #

Generic SHA256Digest Source # 
Instance details

Defined in Dhall.Crypto

Associated Types

type Rep SHA256Digest :: Type -> Type Source #

Generic CharacterSet Source # 
Instance details

Defined in Dhall.Pretty.Internal

Associated Types

type Rep CharacterSet :: Type -> Type Source #

Generic Src Source # 
Instance details

Defined in Dhall.Src

Associated Types

type Rep Src :: Type -> Type Source #

Methods

from :: Src -> Rep Src x Source #

to :: Rep Src x -> Src Source #

Generic Const Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep Const :: Type -> Type Source #

Methods

from :: Const -> Rep Const x Source #

to :: Rep Const x -> Const Source #

Generic DhallDouble Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep DhallDouble :: Type -> Type Source #

Generic Directory Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep Directory :: Type -> Type Source #

Generic File Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep File :: Type -> Type Source #

Methods

from :: File -> Rep File x Source #

to :: Rep File x -> File Source #

Generic FilePrefix Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep FilePrefix :: Type -> Type Source #

Generic Import Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep Import :: Type -> Type Source #

Generic ImportHashed Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep ImportHashed :: Type -> Type Source #

Generic ImportMode Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep ImportMode :: Type -> Type Source #

Generic ImportType Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep ImportType :: Type -> Type Source #

Generic Scheme Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep Scheme :: Type -> Type Source #

Generic URL Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep URL :: Type -> Type Source #

Methods

from :: URL -> Rep URL x Source #

to :: Rep URL x -> URL Source #

Generic Var Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep Var :: Type -> Type Source #

Methods

from :: Var -> Rep Var x Source #

to :: Rep Var x -> Var Source #

Generic WithComponent Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep WithComponent :: Type -> Type Source #

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type Source #

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension :: Type -> Type Source #

Generic Ordering 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type Source #

Generic Half 
Instance details

Defined in Numeric.Half.Internal

Associated Types

type Rep Half :: Type -> Type Source #

Methods

from :: Half -> Rep Half x Source #

to :: Rep Half x -> Half Source #

Generic IP 
Instance details

Defined in Data.IP.Addr

Associated Types

type Rep IP :: Type -> Type Source #

Methods

from :: IP -> Rep IP x Source #

to :: Rep IP x -> IP Source #

Generic IPv4 
Instance details

Defined in Data.IP.Addr

Associated Types

type Rep IPv4 :: Type -> Type Source #

Methods

from :: IPv4 -> Rep IPv4 x Source #

to :: Rep IPv4 x -> IPv4 Source #

Generic IPv6 
Instance details

Defined in Data.IP.Addr

Associated Types

type Rep IPv6 :: Type -> Type Source #

Methods

from :: IPv6 -> Rep IPv6 x Source #

to :: Rep IPv6 x -> IPv6 Source #

Generic IPRange 
Instance details

Defined in Data.IP.Range

Associated Types

type Rep IPRange :: Type -> Type Source #

Methods

from :: IPRange -> Rep IPRange x Source #

to :: Rep IPRange x -> IPRange Source #

Generic InvalidPosException 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep InvalidPosException :: Type -> Type Source #

Methods

from :: InvalidPosException -> Rep InvalidPosException x Source #

to :: Rep InvalidPosException x -> InvalidPosException Source #

Generic Pos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep Pos :: Type -> Type Source #

Methods

from :: Pos -> Rep Pos x Source #

to :: Rep Pos x -> Pos Source #

Generic SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep SourcePos :: Type -> Type Source #

Methods

from :: SourcePos -> Rep SourcePos x Source #

to :: Rep SourcePos x -> SourcePos Source #

Generic URI 
Instance details

Defined in Network.URI

Associated Types

type Rep URI :: Type -> Type Source #

Methods

from :: URI -> Rep URI x Source #

to :: Rep URI x -> URI Source #

Generic URIAuth 
Instance details

Defined in Network.URI

Associated Types

type Rep URIAuth :: Type -> Type Source #

Methods

from :: URIAuth -> Rep URIAuth x Source #

to :: Rep URIAuth x -> URIAuth Source #

Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode :: Type -> Type Source #

Methods

from :: Mode -> Rep Mode x Source #

to :: Rep Mode x -> Mode Source #

Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Style :: Type -> Type Source #

Methods

from :: Style -> Rep Style x Source #

to :: Rep Style x -> Style Source #

Generic TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep TextDetails :: Type -> Type Source #

Generic Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Associated Types

type Rep Doc :: Type -> Type Source #

Methods

from :: Doc -> Rep Doc x Source #

to :: Rep Doc x -> Doc Source #

Generic ColorOptions 
Instance details

Defined in Text.Pretty.Simple.Internal.Color

Associated Types

type Rep ColorOptions :: Type -> Type Source #

Methods

from :: ColorOptions -> Rep ColorOptions x Source #

to :: Rep ColorOptions x -> ColorOptions Source #

Generic Style 
Instance details

Defined in Text.Pretty.Simple.Internal.Color

Associated Types

type Rep Style :: Type -> Type Source #

Methods

from :: Style -> Rep Style x Source #

to :: Rep Style x -> Style Source #

Generic Expr 
Instance details

Defined in Text.Pretty.Simple.Internal.Expr

Associated Types

type Rep Expr :: Type -> Type Source #

Methods

from :: Expr -> Rep Expr x Source #

to :: Rep Expr x -> Expr Source #

Generic CheckColorTty 
Instance details

Defined in Text.Pretty.Simple.Internal.Printer

Associated Types

type Rep CheckColorTty :: Type -> Type Source #

Methods

from :: CheckColorTty -> Rep CheckColorTty x Source #

to :: Rep CheckColorTty x -> CheckColorTty Source #

Generic OutputOptions 
Instance details

Defined in Text.Pretty.Simple.Internal.Printer

Associated Types

type Rep OutputOptions :: Type -> Type Source #

Methods

from :: OutputOptions -> Rep OutputOptions x Source #

to :: Rep OutputOptions x -> OutputOptions Source #

Generic StringOutputStyle 
Instance details

Defined in Text.Pretty.Simple.Internal.Printer

Associated Types

type Rep StringOutputStyle :: Type -> Type Source #

Methods

from :: StringOutputStyle -> Rep StringOutputStyle x Source #

to :: Rep StringOutputStyle x -> StringOutputStyle Source #

Generic AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookup :: Type -> Type Source #

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget :: Type -> Type Source #

Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bang :: Type -> Type Source #

Methods

from :: Bang -> Rep Bang x Source #

to :: Rep Bang x -> Bang Source #

Generic Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Body :: Type -> Type Source #

Methods

from :: Body -> Rep Body x Source #

to :: Rep Body x -> Body Source #

Generic Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bytes :: Type -> Type Source #

Methods

from :: Bytes -> Rep Bytes x Source #

to :: Rep Bytes x -> Bytes Source #

Generic Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Callconv :: Type -> Type Source #

Generic Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Clause :: Type -> Type Source #

Generic Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Con :: Type -> Type Source #

Methods

from :: Con -> Rep Con x Source #

to :: Rep Con x -> Con Source #

Generic Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Dec :: Type -> Type Source #

Methods

from :: Dec -> Rep Dec x Source #

to :: Rep Dec x -> Dec Source #

Generic DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecidedStrictness :: Type -> Type Source #

Generic DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause :: Type -> Type Source #

Generic DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy :: Type -> Type Source #

Generic DocLoc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DocLoc :: Type -> Type Source #

Generic Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Exp :: Type -> Type Source #

Methods

from :: Exp -> Rep Exp x Source #

to :: Rep Exp x -> Exp Source #

Generic FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FamilyResultSig :: Type -> Type Source #

Generic Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Fixity :: Type -> Type Source #

Generic FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FixityDirection :: Type -> Type Source #

Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Foreign :: Type -> Type Source #

Generic FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FunDep :: Type -> Type Source #

Generic Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Guard :: Type -> Type Source #

Methods

from :: Guard -> Rep Guard x Source #

to :: Rep Guard x -> Guard Source #

Generic Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Info :: Type -> Type Source #

Methods

from :: Info -> Rep Info x Source #

to :: Rep Info x -> Info Source #

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnn :: Type -> Type Source #

Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Inline :: Type -> Type Source #

Generic Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Lit :: Type -> Type Source #

Methods

from :: Lit -> Rep Lit x Source #

to :: Rep Lit x -> Lit Source #

Generic Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Loc :: Type -> Type Source #

Methods

from :: Loc -> Rep Loc x Source #

to :: Rep Loc x -> Loc Source #

Generic Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Match :: Type -> Type Source #

Methods

from :: Match -> Rep Match x Source #

to :: Rep Match x -> Match Source #

Generic ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModName :: Type -> Type Source #

Generic Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Module :: Type -> Type Source #

Generic ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleInfo :: Type -> Type Source #

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name :: Type -> Type Source #

Methods

from :: Name -> Rep Name x Source #

to :: Rep Name x -> Name Source #

Generic NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameFlavour :: Type -> Type Source #

Generic NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameSpace :: Type -> Type Source #

Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccName :: Type -> Type Source #

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: Type -> Type Source #

Generic Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pat :: Type -> Type Source #

Methods

from :: Pat -> Rep Pat x Source #

to :: Rep Pat x -> Pat Source #

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgs :: Type -> Type Source #

Generic PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDir :: Type -> Type Source #

Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Phases :: Type -> Type Source #

Generic PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PkgName :: Type -> Type Source #

Generic Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pragma :: Type -> Type Source #

Generic Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Range :: Type -> Type Source #

Methods

from :: Range -> Rep Range x Source #

to :: Rep Range x -> Range Source #

Generic Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Role :: Type -> Type Source #

Methods

from :: Role -> Rep Role x Source #

to :: Rep Role x -> Role Source #

Generic RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleBndr :: Type -> Type Source #

Generic RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleMatch :: Type -> Type Source #

Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Safety :: Type -> Type Source #

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictness :: Type -> Type Source #

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness :: Type -> Type Source #

Generic Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Specificity :: Type -> Type Source #

Generic Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Stmt :: Type -> Type Source #

Methods

from :: Stmt -> Rep Stmt x Source #

to :: Rep Stmt x -> Stmt Source #

Generic TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyLit :: Type -> Type Source #

Methods

from :: TyLit -> Rep TyLit x Source #

to :: Rep TyLit x -> TyLit Source #

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TySynEqn :: Type -> Type Source #

Generic Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Type :: Type -> Type Source #

Methods

from :: Type -> Rep Type x Source #

to :: Rep Type x -> Type Source #

Generic TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeFamilyHead :: Type -> Type Source #

Generic CompressionLevel 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep CompressionLevel :: Type -> Type Source #

Methods

from :: CompressionLevel -> Rep CompressionLevel x Source #

to :: Rep CompressionLevel x -> CompressionLevel Source #

Generic CompressionStrategy 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep CompressionStrategy :: Type -> Type Source #

Methods

from :: CompressionStrategy -> Rep CompressionStrategy x Source #

to :: Rep CompressionStrategy x -> CompressionStrategy Source #

Generic Format 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep Format :: Type -> Type Source #

Methods

from :: Format -> Rep Format x Source #

to :: Rep Format x -> Format Source #

Generic MemoryLevel 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep MemoryLevel :: Type -> Type Source #

Methods

from :: MemoryLevel -> Rep MemoryLevel x Source #

to :: Rep MemoryLevel x -> MemoryLevel Source #

Generic Method 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep Method :: Type -> Type Source #

Methods

from :: Method -> Rep Method x Source #

to :: Rep Method x -> Method Source #

Generic WindowBits 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep WindowBits :: Type -> Type Source #

Methods

from :: WindowBits -> Rep WindowBits x Source #

to :: Rep WindowBits x -> WindowBits Source #

Generic () 
Instance details

Defined in GHC.Generics

Associated Types

type Rep () :: Type -> Type Source #

Methods

from :: () -> Rep () x Source #

to :: Rep () x -> () Source #

Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type Source #

Methods

from :: Bool -> Rep Bool x Source #

to :: Rep Bool x -> Bool Source #

Generic (ZipList a) 
Instance details

Defined in Control.Applicative

Associated Types

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

Methods

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

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

Generic (Complex a) 
Instance details

Defined in Data.Complex

Associated Types

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

Methods

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

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

Generic (Identity a) 
Instance details

Defined in Data.Functor.Identity

Associated Types

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

Methods

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

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

Generic (First a) 
Instance details

Defined in Data.Monoid

Associated Types

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

Methods

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

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

Generic (Last a) 
Instance details

Defined in Data.Monoid

Associated Types

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

Methods

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

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

Generic (Down a) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (First a) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (Last a) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (Max a) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (Min a) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (WrappedMonoid m) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Generic (Dual a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Endo a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Product a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Par1 p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Digit a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

Methods

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

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

Generic (Elem a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

Methods

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

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

Generic (FingerTree a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

Methods

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

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

Generic (Node a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

Methods

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

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

Generic (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

Methods

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

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

Generic (ViewR a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

Methods

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

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

Generic (Tree a) 
Instance details

Defined in Data.Tree

Associated Types

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

Methods

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

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

Generic (Fix f) 
Instance details

Defined in Data.Fix

Associated Types

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

Methods

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

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

Generic (Set a) Source # 
Instance details

Defined in Dhall.Set

Associated Types

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

Methods

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

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

Generic (FieldSelection s) Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep (FieldSelection s) :: Type -> Type Source #

Generic (HistoriedResponse body) 
Instance details

Defined in Network.HTTP.Client

Associated Types

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

Methods

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

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

Generic (AddrRange a) 
Instance details

Defined in Data.IP.Range

Associated Types

type Rep (AddrRange a) :: Type -> Type Source #

Methods

from :: AddrRange a -> Rep (AddrRange a) x Source #

to :: Rep (AddrRange a) x -> AddrRange a Source #

Generic (ErrorFancy e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

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

Methods

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

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

Generic (ErrorItem t) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

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

Methods

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

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

Generic (PosState s) 
Instance details

Defined in Text.Megaparsec.State

Associated Types

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

Methods

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

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

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

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

Methods

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

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

Generic (CommaSeparated a) 
Instance details

Defined in Text.Pretty.Simple.Internal.Expr

Associated Types

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

Methods

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

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

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

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

Methods

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

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

Generic (SimpleDocStream ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

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

Generic (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Associated Types

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

Methods

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

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

Generic (TyVarBndr flag) 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep (TyVarBndr flag) :: Type -> Type Source #

Methods

from :: TyVarBndr flag -> Rep (TyVarBndr flag) x Source #

to :: Rep (TyVarBndr flag) x -> TyVarBndr flag Source #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Maybe a) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a) :: Type -> Type Source #

Methods

from :: (a) -> Rep (a) x Source #

to :: Rep (a) x -> (a) Source #

Generic [a] 
Instance details

Defined in GHC.Generics

Associated Types

type Rep [a] :: Type -> Type Source #

Methods

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

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

Generic (WrappedMonad m a) 
Instance details

Defined in Control.Applicative

Associated Types

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

Methods

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

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

Generic (Either a b) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Arg a b) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (U1 p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (V1 p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Map k v) Source # 
Instance details

Defined in Dhall.Map

Associated Types

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

Methods

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

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

Generic (Binding s a) Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

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

Methods

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

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

Generic (Chunks s a) Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

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

Methods

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

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

Generic (Expr s a) Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

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

Methods

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

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

Generic (FunctionBinding s a) Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep (FunctionBinding s a) :: Type -> Type Source #

Generic (PreferAnnotation s a) Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep (PreferAnnotation s a) :: Type -> Type Source #

Generic (RecordField s a) Source # 
Instance details

Defined in Dhall.Syntax

Associated Types

type Rep (RecordField s a) :: Type -> Type Source #

Methods

from :: RecordField s a -> Rep (RecordField s a) x Source #

to :: Rep (RecordField s a) x -> RecordField s a Source #

Generic (ParseError s e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

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

Methods

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

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

Generic (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

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

Methods

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

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

Generic (State s e) 
Instance details

Defined in Text.Megaparsec.State

Associated Types

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

Methods

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

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

Generic (Either a b) 
Instance details

Defined in Data.Strict.Either

Associated Types

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

Methods

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

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

Generic (These a b) 
Instance details

Defined in Data.Strict.These

Associated Types

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

Methods

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

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

Generic (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Associated Types

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

Methods

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

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

Generic (These a b) 
Instance details

Defined in Data.These

Associated Types

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

Methods

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

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

Generic (a, b) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (WrappedArrow a b c) 
Instance details

Defined in Control.Applicative

Associated Types

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

Methods

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

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

Generic (Kleisli m a b) 
Instance details

Defined in Control.Arrow

Associated Types

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

Methods

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

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

Generic (Const a b) 
Instance details

Defined in Data.Functor.Const

Associated Types

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

Methods

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

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

Generic (Ap f a) 
Instance details

Defined in Data.Monoid

Associated Types

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

Methods

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

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

Generic (Alt f a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Rec1 f p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (URec Char p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (URec Double p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (URec Int p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (URec Word p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Join p a) 
Instance details

Defined in Data.Bifunctor.Join

Associated Types

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

Methods

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

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

Generic (Tagged s b) 
Instance details

Defined in Data.Tagged

Associated Types

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

Methods

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

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

Generic (These1 f g a) 
Instance details

Defined in Data.Functor.These

Associated Types

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

Methods

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

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

Generic (a, b, c) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Product f g a) 
Instance details

Defined in Data.Functor.Product

Associated Types

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

Methods

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

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

Generic (Sum f g a) 
Instance details

Defined in Data.Functor.Sum

Associated Types

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

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (K1 i c p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Compose f g a) 
Instance details

Defined in Data.Functor.Compose

Associated Types

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

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (M1 i c f p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Clown f a b) 
Instance details

Defined in Data.Bifunctor.Clown

Associated Types

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

Methods

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

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

Generic (Flip p a b) 
Instance details

Defined in Data.Bifunctor.Flip

Associated Types

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

Methods

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

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

Generic (Joker g a b) 
Instance details

Defined in Data.Bifunctor.Joker

Associated Types

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

Methods

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

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

Generic (WrappedBifunctor p a b) 
Instance details

Defined in Data.Bifunctor.Wrapped

Associated Types

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

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Product f g a b) 
Instance details

Defined in Data.Bifunctor.Product

Associated Types

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

Methods

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

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

Generic (Sum p q a b) 
Instance details

Defined in Data.Bifunctor.Sum

Associated Types

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

Methods

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

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

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 Source #

Methods

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

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

Generic (Tannen f p a b) 
Instance details

Defined in Data.Bifunctor.Tannen

Associated Types

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

Methods

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

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

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 Source #

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

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 Source #

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

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

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j) :: Type -> Type Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j) -> Rep (a, b, c, d, e, f, g, h, i, j) x Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j) x -> (a, b, c, d, e, f, g, h, i, j) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k) :: Type -> Type Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k) -> Rep (a, b, c, d, e, f, g, h, i, j, k) x Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k) x -> (a, b, c, d, e, f, g, h, i, j, k) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l) :: Type -> Type Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l) x Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l) x -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) :: Type -> Type Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: Type -> Type Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

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 Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #