dhall-1.19.1: A configuration language guaranteed to terminate

Safe HaskellNone
LanguageHaskell2010

Dhall

Contents

Description

Please read the Dhall.Tutorial module, which contains a tutorial explaining how to use the language, the compiler, and this library

Synopsis

Input

input Source #

Arguments

:: Type a

The type of value to decode from Dhall to Haskell

-> Text

The Dhall program

-> IO a

The decoded value in Haskell

Type-check and evaluate a Dhall program, decoding the result into Haskell

The first argument determines the type of value that you decode:

>>> input integer "+2"
2
>>> input (vector double) "[1.0, 2.0]"
[1.0,2.0]

Use auto to automatically select which type to decode based on the inferred return type:

>>> input auto "True" :: IO Bool
True

This uses the settings from defaultInputSettings.

inputWithSettings Source #

Arguments

:: InputSettings 
-> Type a

The type of value to decode from Dhall to Haskell

-> Text

The Dhall program

-> IO a

The decoded value in Haskell

Extend input with a root directory to resolve imports relative to, a file to mention in errors as the source, a custom typing context, and a custom normalization process.

Since: 1.16

inputFile Source #

Arguments

:: Type a

The type of value to decode from Dhall to Haskell

-> FilePath

The path to the Dhall program.

-> IO a

The decoded value in Haskell.

Type-check and evaluate a Dhall program that is read from the file-system.

This uses the settings from defaultEvaluateSettings.

Since: 1.16

inputFileWithSettings Source #

Arguments

:: EvaluateSettings 
-> Type a

The type of value to decode from Dhall to Haskell

-> FilePath

The path to the Dhall program.

-> IO a

The decoded value in Haskell.

Extend inputFile with a custom typing context and a custom normalization process.

Since: 1.16

inputExpr Source #

Arguments

:: Text

The Dhall program

-> IO (Expr Src X)

The fully normalized AST

Similar to input, but without interpreting the Dhall Expr into a Haskell type.

Uses the settings from defaultInputSettings.

inputExprWithSettings Source #

Arguments

:: InputSettings 
-> Text

The Dhall program

-> IO (Expr Src X)

The fully normalized AST

Extend inputExpr with a root directory to resolve imports relative to, a file to mention in errors as the source, a custom typing context, and a custom normalization process.

Since: 1.16

rootDirectory :: Functor f => LensLike' f InputSettings FilePath Source #

Access the directory to resolve imports relative to.

Since: 1.16

sourceName :: Functor f => LensLike' f InputSettings FilePath Source #

Access the name of the source to report locations from; this is only used in error messages, so it's okay if this is a best guess or something symbolic.

Since: 1.16

startingContext :: (Functor f, HasEvaluateSettings s) => LensLike' f s (Context (Expr Src X)) Source #

Access the starting context used for evaluation and type-checking.

Since: 1.16

normalizer :: (Functor f, HasEvaluateSettings s) => LensLike' f s (ReifiedNormalizer X) Source #

Access the custom normalizer.

Since: 1.16

standardVersion :: (Functor f, HasEvaluateSettings s) => LensLike' f s StandardVersion Source #

Access the standard version (used primarily when encoding or decoding Dhall expressions to and from a binary representation)

Since: 1.17

defaultInputSettings :: InputSettings Source #

Default input settings: resolves imports relative to . (the current working directory), report errors as coming from (input), and default evaluation settings from defaultEvaluateSettings.

Since: 1.16

defaultEvaluateSettings :: EvaluateSettings Source #

Default evaluation settings: no extra entries in the initial context, and no special normalizer behaviour.

Since: 1.16

class HasEvaluateSettings s Source #

Since: 1.16

Minimal complete definition

evaluateSettings

detailed :: IO a -> IO a Source #

Use this to provide more detailed error messages

> input auto "True" :: IO Integer
 *** Exception: Error: Expression doesn't match annotation

 True : Integer

 (input):1:1
> detailed (input auto "True") :: IO Integer
 *** Exception: Error: Expression doesn't match annotation

 Explanation: You can annotate an expression with its type or kind using the
 ❰:❱ symbol, like this:


     ┌───────┐
     │ x : t │  ❰x❱ is an expression and ❰t❱ is the annotated type or kind of ❰x❱
     └───────┘

 The type checker verifies that the expression's type or kind matches the
 provided annotation

 For example, all of the following are valid annotations that the type checker
 accepts:


     ┌─────────────┐
     │ 1 : Natural │  ❰1❱ is an expression that has type ❰Natural❱, so the type
     └─────────────┘  checker accepts the annotation


     ┌───────────────────────┐
     │ Natural/even 2 : Bool │  ❰Natural/even 2❱ has type ❰Bool❱, so the type
     └───────────────────────┘  checker accepts the annotation


     ┌────────────────────┐
     │ List : Type → Type │  ❰List❱ is an expression that has kind ❰Type → Type❱,
     └────────────────────┘  so the type checker accepts the annotation


     ┌──────────────────┐
     │ List Text : Type │  ❰List Text❱ is an expression that has kind ❰Type❱, so
     └──────────────────┘  the type checker accepts the annotation


 However, the following annotations are not valid and the type checker will
 reject them:


     ┌──────────┐
     │ 1 : Text │  The type checker rejects this because ❰1❱ does not have type
     └──────────┘  ❰Text❱


     ┌─────────────┐
     │ List : Type │  ❰List❱ does not have kind ❰Type❱
     └─────────────┘


 You or the interpreter annotated this expression:

 ↳ True

 ... with this type or kind:

 ↳ Integer

 ... but the inferred type or kind of the expression is actually:

 ↳ Bool

 Some common reasons why you might get this error:

 ● The Haskell Dhall interpreter implicitly inserts a top-level annotation
   matching the expected type

   For example, if you run the following Haskell code:


     ┌───────────────────────────────┐
     │ >>> input auto "1" :: IO Text │
     └───────────────────────────────┘


   ... then the interpreter will actually type check the following annotated
   expression:


     ┌──────────┐
     │ 1 : Text │
     └──────────┘


   ... and then type-checking will fail

 ────────────────────────────────────────────────────────────────────────────────

 True : Integer

 (input):1:1

Types

data Type a Source #

A (Type a) represents a way to marshal a value of type 'a' from Dhall into Haskell

You can produce Types either explicitly:

example :: Type (Vector Text)
example = vector text

... or implicitly using auto:

example :: Type (Vector Text)
example = auto

You can consume Types using the input function:

input :: Type a -> Text -> IO a

Constructors

Type 

Fields

Instances
Functor Type Source # 
Instance details

Defined in Dhall

Methods

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

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

newtype RecordType a Source #

The RecordType applicative functor allows you to build a Type parser from a Dhall record.

For example, let's take the following Haskell data type:

data Project = Project
  { projectName :: Text
  , projectDescription :: Text
  , projectStars :: Natural
  }

And assume that we have the following Dhall record that we would like to parse as a Project:

{ name =
    "dhall-haskell"
, description =
    "A configuration language guaranteed to terminate"
, stars =
    289
}

Our parser has type Type Project, but we can't build that out of any smaller parsers, as Types cannot be combined (they are only Functors). However, we can use a RecordType to build a Type for Project:

project :: Type Project
project =
  record
    ( Project <$> field "name" string
              <*> field "description" string
              <*> field "stars" natural
    )

Constructors

RecordType (Product (Const (Map Text (Expr Src X))) (Compose ((->) (Expr Src X)) Maybe) a) 
Instances
Functor RecordType Source # 
Instance details

Defined in Dhall

Methods

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

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

Applicative RecordType Source # 
Instance details

Defined in Dhall

data InputType a Source #

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

Constructors

InputType 

Fields

Instances
Contravariant InputType Source # 
Instance details

Defined in Dhall

Methods

contramap :: (a -> b) -> InputType b -> InputType a Source #

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

class Interpret a where Source #

Any value that implements Interpret can be automatically decoded based on the inferred return type of input

>>> input auto "[1, 2, 3]" :: IO (Vector Natural)
[1,2,3]

This class auto-generates a default implementation for records that implement Generic. This does not auto-generate an instance for recursive types.

Minimal complete definition

Nothing

Instances
Interpret Bool Source # 
Instance details

Defined in Dhall

Interpret Double Source # 
Instance details

Defined in Dhall

Interpret Integer Source # 
Instance details

Defined in Dhall

Interpret Natural Source # 
Instance details

Defined in Dhall

Interpret Text Source # 
Instance details

Defined in Dhall

Interpret Scientific Source # 
Instance details

Defined in Dhall

Methods

autoWith :: InterpretOptions -> Type Scientific Source #

Interpret Text Source # 
Instance details

Defined in Dhall

Interpret [Char] Source # 
Instance details

Defined in Dhall

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

Defined in Dhall

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

Defined in Dhall

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

Defined in Dhall

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

Defined in Dhall

(Inject a, Interpret b) => Interpret (a -> b) Source # 
Instance details

Defined in Dhall

Methods

autoWith :: InterpretOptions -> Type (a -> b) Source #

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

Defined in Dhall

Methods

autoWith :: InterpretOptions -> Type (a, b) Source #

data InvalidType Source #

Every Type must obey the contract that if an expression's type matches the the expected type then the extract function must succeed. If not, then this exception is thrown

This exception indicates that an invalid Type was provided to the input function

Constructors

InvalidType 

auto :: Interpret a => Type a Source #

Use the default options for interpreting a configuration file

auto = autoWith defaultInterpretOptions

genericAuto :: (Generic a, GenericInterpret (Rep a)) => Type a Source #

genericAuto is the default implementation for auto if you derive Interpret. The difference is that you can use genericAuto without having to explicitly provide an Interpret instance for a type as long as the type derives Generic

data InterpretOptions Source #

Use these options to tweak how Dhall derives a generic implementation of Interpret

Constructors

InterpretOptions 

Fields

  • fieldModifier :: Text -> Text

    Function used to transform Haskell field names into their corresponding Dhall field names

  • constructorModifier :: Text -> Text

    Function used to transform Haskell constructor names into their corresponding Dhall alternative names

defaultInterpretOptions :: InterpretOptions Source #

Default interpret options, which you can tweak or override, like this:

autoWith
    (defaultInterpretOptions { fieldModifier = Data.Text.Lazy.dropWhile (== '_') })

bool :: Type Bool Source #

Decode a Expr

>>> input bool "True"
True

natural :: Type Natural Source #

Decode a Expr

>>> input natural "42"
42

integer :: Type Integer Source #

Decode an Expr

>>> input integer "+42"
42

scientific :: Type Scientific Source #

Decode a Scientific

>>> input scientific "1e100"
1.0e100

double :: Type Double Source #

Decode a Expr

>>> input double "42.0"
42.0

lazyText :: Type Text Source #

Decode lazy Expr

>>> input lazyText "\"Test\""
"Test"

strictText :: Type Text Source #

Decode strict Expr

>>> input strictText "\"Test\""
"Test"

maybe :: Type a -> Type (Maybe a) Source #

Decode a Maybe

>>> input (maybe natural) "Some 1"
Just 1

sequence :: Type a -> Type (Seq a) Source #

Decode a Seq - >>> input (sequence natural) "[1, 2, 3]" fromList [1,2,3]

list :: Type a -> Type [a] Source #

Decode a list

>>> input (list natural) "[1, 2, 3]"
[1,2,3]

vector :: Type a -> Type (Vector a) Source #

Decode a Vector

>>> input (vector natural) "[1, 2, 3]"
[1,2,3]

unit :: Type () Source #

Decode () from an empty record.

>>> input unit "{=}"  -- GHC doesn't print the result if it is ()

string :: Type String Source #

Decode a String

>>> input string "\"ABC\""
"ABC"

pair :: Type a -> Type b -> Type (a, b) Source #

Given a pair of Types, decode a tuple-record into their pairing.

>>> input (pair natural bool) "{ _1 = 42, _2 = False }"
(42,False)

record :: RecordType a -> Type a Source #

Run a RecordType parser to build a Type parser.

field :: Text -> Type a -> RecordType a Source #

Parse a single field of a record.

class GenericInterpret f where Source #

This is the underlying class that powers the Interpret class's support for automatically deriving a generic implementation

Instances
GenericInterpret (V1 :: Type -> Type) Source # 
Instance details

Defined in Dhall

GenericInterpret (U1 :: Type -> Type) Source # 
Instance details

Defined in Dhall

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

Defined in Dhall

Methods

genericAutoWith :: InterpretOptions -> State Int (Type ((M1 C c f :+: (g :+: h)) a)) Source #

(Constructor c1, Constructor c2, GenericInterpret f1, GenericInterpret f2) => GenericInterpret (M1 C c1 f1 :+: M1 C c2 f2) Source # 
Instance details

Defined in Dhall

Methods

genericAutoWith :: InterpretOptions -> State Int (Type ((M1 C c1 f1 :+: M1 C c2 f2) a)) Source #

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

Defined in Dhall

Methods

genericAutoWith :: InterpretOptions -> State Int (Type (((f :+: g) :+: (h :+: i)) a)) Source #

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

Defined in Dhall

Methods

genericAutoWith :: InterpretOptions -> State Int (Type (((f :+: g) :+: M1 C c h) a)) Source #

(GenericInterpret f, GenericInterpret g) => GenericInterpret (f :*: g) Source # 
Instance details

Defined in Dhall

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

Defined in Dhall

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

Defined in Dhall

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

Defined in Dhall

class GenericInject f where Source #

This is the underlying class that powers the Interpret class's support for automatically deriving a generic implementation

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

Defined in Dhall

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

Defined in Dhall

(Constructor c1, Constructor c2, GenericInject f1, GenericInject f2) => GenericInject (M1 C c1 f1 :+: M1 C c2 f2) Source # 
Instance details

Defined in Dhall

Methods

genericInjectWith :: InterpretOptions -> State Int (InputType ((M1 C c1 f1 :+: M1 C c2 f2) a)) Source #

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

Defined in Dhall

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

Defined in Dhall

(GenericInject f, GenericInject g) => GenericInject (f :*: g) Source # 
Instance details

Defined in Dhall

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

Defined in Dhall

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

Defined in Dhall

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

Defined in Dhall

class Inject a where Source #

This class is used by Interpret instance for functions:

instance (Inject a, Interpret b) => Interpret (a -> b)

You can convert Dhall functions with "simple" inputs (i.e. instances of this class) into Haskell functions. This works by:

  • Marshaling the input to the Haskell function into a Dhall expression (i.e. x :: Expr Src X)
  • Applying the Dhall function (i.e. f :: Expr Src X) to the Dhall input (i.e. App f x)
  • Normalizing the syntax tree (i.e. normalize (App f x))
  • Marshaling the resulting Dhall expression back into a Haskell value

Minimal complete definition

Nothing

Instances
Inject Bool Source # 
Instance details

Defined in Dhall

Inject Double Source # 
Instance details

Defined in Dhall

Inject Int Source # 
Instance details

Defined in Dhall

Inject Integer Source # 
Instance details

Defined in Dhall

Inject Natural Source # 
Instance details

Defined in Dhall

Inject Word8 Source # 
Instance details

Defined in Dhall

Inject Word16 Source # 
Instance details

Defined in Dhall

Inject Word32 Source # 
Instance details

Defined in Dhall

Inject Word64 Source # 
Instance details

Defined in Dhall

Inject () Source # 
Instance details

Defined in Dhall

Inject Text Source # 
Instance details

Defined in Dhall

Inject Text Source # 
Instance details

Defined in Dhall

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

Defined in Dhall

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

Defined in Dhall

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

Defined in Dhall

Inject a => Inject (Set a) Source # 
Instance details

Defined in Dhall

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

Defined in Dhall

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

Defined in Dhall

inject :: Inject a => InputType a Source #

Use the default options for injecting a value

inject = inject defaultInterpretOptions

newtype RecordInputType a Source #

Constructors

RecordInputType (Map Text (InputType a)) 
Instances
Contravariant RecordInputType Source # 
Instance details

Defined in Dhall

Divisible RecordInputType Source # 
Instance details

Defined in Dhall

Miscellaneous

rawInput Source #

Arguments

:: Alternative f 
=> Type a

The type of value to decode from Dhall to Haskell

-> Expr s X

a closed form Dhall program, which evaluates to the expected type

-> f a

The decoded value in Haskell

Use this function to extract Haskell values directly from Dhall AST. The intended use case is to allow easy extraction of Dhall values for making the function normalizeWith easier to use.

For other use cases, use input from Dhall module. It will give you a much better user experience.

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

This is an infix alias for contramap.

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

The RecordInputType divisible (contravariant) functor allows you to build an InputType injector for a Dhall record.

For example, let's take the following Haskell data type:

data Project = Project
  { projectName :: Text
  , projectDescription :: Text
  , projectStars :: Natural
  }

And assume that we have the following Dhall record that we would like to parse as a Project:

{ name =
    "dhall-haskell"
, description =
    "A configuration language guaranteed to terminate"
, stars =
    289
}

Our injector has type InputType Project, but we can't build that out of any smaller injectors, as InputTypes cannot be combined (they are only Contravariants). However, we can use an InputRecordType to build an InputType for Project:

injectProject :: InputType Project
injectProject =
  inputRecord
    (  adapt >$< inputFieldWith "name" inject
             >*< inputFieldWith "description" inject
             >*< inputFieldWith "stars" inject
    )
  where
    adapt (Project{..}) = (projectName, (projectDescription, projectStars))

Or, since we are simply using the Inject instance to inject each field, we could write

injectProject :: InputType Project
injectProject =
  inputRecord
    (  adapt >$< inputField "name"
             >*< inputField "description"
             >*< inputField "stars"
    )
  where
    adapt (Project{..}) = (projectName, (projectDescription, projectStars))

Infix divided

Re-exports

data Natural Source #

Type representing arbitrary-precision non-negative integers.

>>> 2^100 :: Natural
1267650600228229401496703205376

Operations whose result would be negative throw (Underflow :: ArithException),

>>> -1 :: Natural
*** Exception: arithmetic underflow

Since: base-4.8.0.0

Instances
Enum Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Enum

Eq Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Natural

Integral Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

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

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

Ord Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Natural

Read Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Read

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

Ix Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Arr

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Natural -> Q Exp Source #

Pretty Natural 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Natural -> Doc ann

prettyList :: [Natural] -> Doc ann

Hashable Natural 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Natural -> Int

hash :: Natural -> Int

Subtractive Natural 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Natural :: Type

Methods

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

Serialise Natural 
Instance details

Defined in Codec.Serialise.Class

Inject Natural Source # 
Instance details

Defined in Dhall

Interpret Natural Source # 
Instance details

Defined in Dhall

type Difference Natural 
Instance details

Defined in Basement.Numerical.Subtractive

type Difference Natural = Maybe Natural

data Seq a Source #

General-purpose finite sequences.

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

fail :: String -> 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 #

MonadFix Seq

Since: containers-0.5.11

Instance details

Defined in Data.Sequence.Internal

Methods

mfix :: (a -> 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 #

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 #

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 #

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 #

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 #

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 #

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 #

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)

IsList (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Item (Seq a) :: Type Source #

Methods

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

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

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

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 #

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

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 #

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 #

a ~ Char => IsString (Seq a)

Since: containers-0.5.7

Instance details

Defined in Data.Sequence.Internal

Methods

fromString :: String -> 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 #

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 #

NFData a => NFData (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

rnf :: Seq a -> () Source #

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]

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

Defined in Dhall

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

Defined in Dhall

type Item (Seq a) 
Instance details

Defined in Data.Sequence.Internal

type Item (Seq a) = a

data Text Source #

A space efficient, packed, unboxed Unicode text type.

Instances
Stream Text 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token Text :: Type Source #

type Tokens Text :: Type Source #

Pretty Text 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Text -> Doc ann

prettyList :: [Text] -> Doc ann

Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int

hash :: Text -> Int

Chunk Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem Text :: Type

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]

Serialise Text 
Instance details

Defined in Codec.Serialise.Class

Inject Text Source # 
Instance details

Defined in Dhall

Interpret Text Source # 
Instance details

Defined in Dhall

MonadParsec Void Text Parser Source # 
Instance details

Defined in Dhall.Parser.Combinators

Monad m => Stream Text m Char 
Instance details

Defined in Text.Parsec.Prim

Methods

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

type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char
type Tokens Text 
Instance details

Defined in Text.Megaparsec.Stream

type Token Text 
Instance details

Defined in Text.Megaparsec.Stream

type Token Text = Char
type State Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State Text = Buffer
type ChunkElem Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type ChunkElem Text = Char

data Vector a Source #

Boxed vectors, supporting efficient slicing.

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

fail :: String -> 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 #

MonadFail Vector 
Instance details

Defined in Data.Vector

Methods

fail :: String -> 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 #

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 #

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 #

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 #

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 #

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 #

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 #

MonadPlus Vector 
Instance details

Defined in Data.Vector

Methods

mzero :: Vector a Source #

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

Vector Vector a 
Instance details

Defined in Data.Vector

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) a -> m (Vector a) Source #

basicUnsafeThaw :: PrimMonad m => Vector a -> m (Mutable Vector (PrimState m) a) Source #

basicLength :: Vector a -> Int Source #

basicUnsafeSlice :: Int -> Int -> Vector a -> Vector a Source #

basicUnsafeIndexM :: Monad m => Vector a -> Int -> m a Source #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) a -> Vector a -> m () Source #

elemseq :: Vector a -> a -> b -> b Source #

IsList (Vector a) 
Instance details

Defined in Data.Vector

Associated Types

type Item (Vector a) :: Type Source #

Methods

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

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

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

Eq a => Eq (Vector a) 
Instance details

Defined in Data.Vector

Methods

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

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

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

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 #

Read a => Read (Vector a) 
Instance details

Defined in Data.Vector

Show a => Show (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 #

Monoid (Vector a) 
Instance details

Defined in Data.Vector

NFData a => NFData (Vector a) 
Instance details

Defined in Data.Vector

Methods

rnf :: Vector a -> () Source #

Serialise a => Serialise (Vector a) 
Instance details

Defined in Codec.Serialise.Class

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

Defined in Dhall

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

Defined in Dhall

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

Defined in GHC.Generics

Associated Types

type Rep Ordering :: 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 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 Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Clause :: 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 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 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 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 FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FunDep :: Type -> Type Source #

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnn :: Type -> Type Source #

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: Type -> Type 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 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 Version 
Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type Source #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type 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 Fixity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type Source #

Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type Source #

Generic SourceUnpackedness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type Source #

Generic SourceStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type Source #

Generic DecidedStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type Source #

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension :: Type -> Type Source #

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type 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 InvalidPosException 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep InvalidPosException :: Type -> Type Source #

Generic SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep SourcePos :: 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 TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep TextDetails :: Type -> Type 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 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 ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModName :: Type -> Type Source #

Generic PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PkgName :: Type -> Type Source #

Generic Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Module :: Type -> Type Source #

Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccName :: Type -> Type 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 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 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 ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleInfo :: 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 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 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 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 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 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 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 TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeFamilyHead :: Type -> Type Source #

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TySynEqn :: Type -> Type Source #

Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Foreign :: Type -> Type Source #

Generic Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Callconv :: Type -> Type Source #

Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Safety :: Type -> Type Source #

Generic Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pragma :: Type -> Type Source #

Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Inline :: Type -> Type Source #

Generic RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleMatch :: Type -> Type Source #

Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Phases :: Type -> Type Source #

Generic RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleBndr :: Type -> Type Source #

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget :: Type -> Type Source #

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness :: Type -> Type Source #

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictness :: Type -> Type Source #

Generic DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecidedStrictness :: 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 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 PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDir :: Type -> Type Source #

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgs :: Type -> Type Source #

Generic TyVarBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyVarBndr :: Type -> Type Source #

Generic FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FamilyResultSig :: Type -> Type 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 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 AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookup :: Type -> Type Source #

Generic Var Source # 
Instance details

Defined in Dhall.Core

Associated Types

type Rep Var :: Type -> Type Source #

Methods

from :: Var -> Rep Var x Source #

to :: Rep Var x -> Var Source #

Generic Const Source # 
Instance details

Defined in Dhall.Core

Associated Types

type Rep Const :: Type -> Type Source #

Methods

from :: Const -> Rep Const x Source #

to :: Rep Const x -> Const Source #

Generic Import Source # 
Instance details

Defined in Dhall.Core

Associated Types

type Rep Import :: Type -> Type Source #

Generic ImportHashed Source # 
Instance details

Defined in Dhall.Core

Associated Types

type Rep ImportHashed :: Type -> Type Source #

Generic ImportMode Source # 
Instance details

Defined in Dhall.Core

Associated Types

type Rep ImportMode :: Type -> Type Source #

Generic ImportType Source # 
Instance details

Defined in Dhall.Core

Associated Types

type Rep ImportType :: Type -> Type Source #

Generic URL Source # 
Instance details

Defined in Dhall.Core

Associated Types

type Rep URL :: Type -> Type Source #

Methods

from :: URL -> Rep URL x Source #

to :: Rep URL x -> URL Source #

Generic Scheme Source # 
Instance details

Defined in Dhall.Core

Associated Types

type Rep Scheme :: Type -> Type Source #

Generic FilePrefix Source # 
Instance details

Defined in Dhall.Core

Associated Types

type Rep FilePrefix :: Type -> Type Source #

Generic File Source # 
Instance details

Defined in Dhall.Core

Associated Types

type Rep File :: Type -> Type Source #

Methods

from :: File -> Rep File x Source #

to :: Rep File x -> File Source #

Generic Directory Source # 
Instance details

Defined in Dhall.Core

Associated Types

type Rep Directory :: Type -> Type Source #

Generic Half 
Instance details

Defined in Numeric.Half

Associated Types

type Rep Half :: Type -> Type Source #

Methods

from :: Half -> Rep Half x Source #

to :: Rep Half x -> Half 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 [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 (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 (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 (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 (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 (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 (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 (WrappedMonoid m) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Generic (Option a) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

to :: Rep (Option a) x -> Option a 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 (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 (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 (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 (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 (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 (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 (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 (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 (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 (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 (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 (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 (HistoriedResponse body) 
Instance details

Defined in Network.HTTP.Client

Associated Types

type Rep (HistoriedResponse body) :: Type -> Type 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 (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 (State s) 
Instance details

Defined in Text.Megaparsec.State

Associated Types

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

Methods

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

to :: Rep (State s) x -> State s 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 (Doc ann) 
Instance details

Defined in Data.Text.Prettyprint.Doc.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 Data.Text.Prettyprint.Doc.Internal

Associated Types

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

Methods

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

to :: Rep (SimpleDocStream ann) x -> SimpleDocStream ann 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 (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 (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 (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 (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 (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 (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 (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 (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 #

Generic (Expr s a) Source # 
Instance details

Defined in Dhall.Core

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 (Chunks s a) Source # 
Instance details

Defined in Dhall.Core

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 (Binding s a) Source # 
Instance details

Defined in Dhall.Core

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