dhall-1.1.0: A configuration language guaranteed to terminate

Safe HaskellNone
LanguageHaskell98

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

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 : Integer │  ❰1❱ is an expression that has type ❰Integer❱, 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

Instances

Functor Type Source # 

Methods

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

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

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 Integer)
[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.

Methods

auto :: Type a Source #

auto :: (Generic a, GenericInterpret (Rep a)) => Type a 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 

bool :: Type Bool Source #

Decode a Bool

>>> input bool "True"
True

natural :: Type Natural Source #

Decode a Natural

>>> input natural "+42"
42

integer :: Type Integer Source #

Decode an Integer

>>> input integer "42"
42

double :: Type Double Source #

Decode a Double

>>> input double "42.0"
42.0

text :: Type Text Source #

Decode Text

>>> input text "\"Test\""
"Test"

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

Decode a Maybe

>>> input (maybe integer) "[1] : Optional Integer"
Just 1

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

Decode a Vector

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

Re-exports

data Natural :: * #

Type representing arbitrary-precision non-negative integers.

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

Since: 4.8.0.0

Instances

Enum Natural 
Eq Natural 

Methods

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

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

Integral Natural 
Data Natural 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Natural -> c Natural #

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

toConstr :: Natural -> Constr #

dataTypeOf :: Natural -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Natural 
Ord Natural 
Read Natural 
Real Natural 
Show Natural 
Ix Natural 
Lift Natural 

Methods

lift :: Natural -> Q Exp #

Bits Natural 
Hashable Natural 

Methods

hashWithSalt :: Int -> Natural -> Int #

hash :: Natural -> Int #

Interpret Natural Source # 

data Text :: * #

Instances

Hashable Text 

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Ixed Text 
Buildable Text 

Methods

build :: Text -> Builder #

Interpret Text Source # 

Methods

auto :: Type Text Source #

Monad m => Stream Text m Char 

Methods

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

type Item Text 
type Item Text = Char
type Index Text 
type IxValue Text 

data Vector a :: * -> * #

Boxed vectors, supporting efficient slicing.

Instances

Monad Vector 

Methods

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

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

return :: a -> Vector a #

fail :: String -> Vector a #

Functor Vector 

Methods

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

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

Applicative Vector 

Methods

pure :: a -> Vector a #

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

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

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

Foldable Vector 

Methods

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

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

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

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

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

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

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

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

toList :: Vector a -> [a] #

null :: Vector a -> Bool #

length :: Vector a -> Int #

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

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

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

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

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

Traversable Vector 

Methods

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

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

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

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

Alternative Vector 

Methods

empty :: Vector a #

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

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

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

MonadPlus Vector 

Methods

mzero :: Vector a #

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

Vector Vector a 

Methods

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

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

basicLength :: Vector a -> Int #

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

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

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

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

IsList (Vector a) 

Associated Types

type Item (Vector a) :: * #

Methods

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

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

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

Eq a => Eq (Vector a) 

Methods

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

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

Data a => Data (Vector a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) #

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

toConstr :: Vector a -> Constr #

dataTypeOf :: Vector a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Vector a) 

Methods

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

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

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

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

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

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

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

Read a => Read (Vector a) 
Show a => Show (Vector a) 

Methods

showsPrec :: Int -> Vector a -> ShowS #

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

Monoid (Vector a) 

Methods

mempty :: Vector a #

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

mconcat :: [Vector a] -> Vector a #

NFData a => NFData (Vector a) 

Methods

rnf :: Vector a -> () #

Ixed (Vector a) 

Methods

ix :: Index (Vector a) -> Traversal' (Vector a) (IxValue (Vector a)) #

Wrapped (Vector a) 

Associated Types

type Unwrapped (Vector a) :: * #

Methods

_Wrapped' :: Iso' (Vector a) (Unwrapped (Vector a)) #

Interpret a => Interpret (Vector a) Source # 

Methods

auto :: Type (Vector a) Source #

(~) * t (Vector a') => Rewrapped (Vector a) t 
type Mutable Vector 
type Item (Vector a) 
type Item (Vector a) = a
type Index (Vector a) 
type Index (Vector a) = Int
type IxValue (Vector a) 
type IxValue (Vector a) = a
type Unwrapped (Vector a) 
type Unwrapped (Vector a) = [a]

class Generic a #

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

Minimal complete definition

from, to

Instances

Generic Bool 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering 

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic Exp 

Associated Types

type Rep Exp :: * -> * #

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

Generic Match 

Associated Types

type Rep Match :: * -> * #

Methods

from :: Match -> Rep Match x #

to :: Rep Match x -> Match #

Generic Clause 

Associated Types

type Rep Clause :: * -> * #

Methods

from :: Clause -> Rep Clause x #

to :: Rep Clause x -> Clause #

Generic Pat 

Associated Types

type Rep Pat :: * -> * #

Methods

from :: Pat -> Rep Pat x #

to :: Rep Pat x -> Pat #

Generic Type 

Associated Types

type Rep Type :: * -> * #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Generic Dec 

Associated Types

type Rep Dec :: * -> * #

Methods

from :: Dec -> Rep Dec x #

to :: Rep Dec x -> Dec #

Generic Name 

Associated Types

type Rep Name :: * -> * #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Generic FunDep 

Associated Types

type Rep FunDep :: * -> * #

Methods

from :: FunDep -> Rep FunDep x #

to :: Rep FunDep x -> FunDep #

Generic TyVarBndr 

Associated Types

type Rep TyVarBndr :: * -> * #

Generic InjectivityAnn 

Associated Types

type Rep InjectivityAnn :: * -> * #

Generic Overlap 

Associated Types

type Rep Overlap :: * -> * #

Methods

from :: Overlap -> Rep Overlap x #

to :: Rep Overlap x -> Overlap #

Generic () 

Associated Types

type Rep () :: * -> * #

Methods

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

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

Generic Void 

Associated Types

type Rep Void :: * -> * #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Generic Version 

Associated Types

type Rep Version :: * -> * #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic ExitCode 

Associated Types

type Rep ExitCode :: * -> * #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic All 

Associated Types

type Rep All :: * -> * #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any 

Associated Types

type Rep Any :: * -> * #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Fixity 

Associated Types

type Rep Fixity :: * -> * #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity 

Associated Types

type Rep Associativity :: * -> * #

Generic SourceUnpackedness 
Generic SourceStrictness 
Generic DecidedStrictness 
Generic Extension 

Associated Types

type Rep Extension :: * -> * #

Generic URI 

Associated Types

type Rep URI :: * -> * #

Methods

from :: URI -> Rep URI x #

to :: Rep URI x -> URI #

Generic Con 

Associated Types

type Rep Con :: * -> * #

Methods

from :: Con -> Rep Con x #

to :: Rep Con x -> Con #

Generic Doc 

Associated Types

type Rep Doc :: * -> * #

Methods

from :: Doc -> Rep Doc x #

to :: Rep Doc x -> Doc #

Generic TextDetails 

Associated Types

type Rep TextDetails :: * -> * #

Generic Style 

Associated Types

type Rep Style :: * -> * #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

Generic Mode 

Associated Types

type Rep Mode :: * -> * #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

Generic WindowBits 

Associated Types

type Rep WindowBits :: * -> * #

Generic ModName 

Associated Types

type Rep ModName :: * -> * #

Methods

from :: ModName -> Rep ModName x #

to :: Rep ModName x -> ModName #

Generic PkgName 

Associated Types

type Rep PkgName :: * -> * #

Methods

from :: PkgName -> Rep PkgName x #

to :: Rep PkgName x -> PkgName #

Generic Module 

Associated Types

type Rep Module :: * -> * #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Generic OccName 

Associated Types

type Rep OccName :: * -> * #

Methods

from :: OccName -> Rep OccName x #

to :: Rep OccName x -> OccName #

Generic NameFlavour 

Associated Types

type Rep NameFlavour :: * -> * #

Generic NameSpace 

Associated Types

type Rep NameSpace :: * -> * #

Generic Loc 

Associated Types

type Rep Loc :: * -> * #

Methods

from :: Loc -> Rep Loc x #

to :: Rep Loc x -> Loc #

Generic Info 

Associated Types

type Rep Info :: * -> * #

Methods

from :: Info -> Rep Info x #

to :: Rep Info x -> Info #

Generic ModuleInfo 

Associated Types

type Rep ModuleInfo :: * -> * #

Generic Fixity 

Associated Types

type Rep Fixity :: * -> * #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic FixityDirection 
Generic Lit 

Associated Types

type Rep Lit :: * -> * #

Methods

from :: Lit -> Rep Lit x #

to :: Rep Lit x -> Lit #

Generic Body 

Associated Types

type Rep Body :: * -> * #

Methods

from :: Body -> Rep Body x #

to :: Rep Body x -> Body #

Generic Guard 

Associated Types

type Rep Guard :: * -> * #

Methods

from :: Guard -> Rep Guard x #

to :: Rep Guard x -> Guard #

Generic Stmt 

Associated Types

type Rep Stmt :: * -> * #

Methods

from :: Stmt -> Rep Stmt x #

to :: Rep Stmt x -> Stmt #

Generic Range 

Associated Types

type Rep Range :: * -> * #

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

Generic TypeFamilyHead 

Associated Types

type Rep TypeFamilyHead :: * -> * #

Generic TySynEqn 

Associated Types

type Rep TySynEqn :: * -> * #

Methods

from :: TySynEqn -> Rep TySynEqn x #

to :: Rep TySynEqn x -> TySynEqn #

Generic FamFlavour 

Associated Types

type Rep FamFlavour :: * -> * #

Generic Foreign 

Associated Types

type Rep Foreign :: * -> * #

Methods

from :: Foreign -> Rep Foreign x #

to :: Rep Foreign x -> Foreign #

Generic Callconv 

Associated Types

type Rep Callconv :: * -> * #

Methods

from :: Callconv -> Rep Callconv x #

to :: Rep Callconv x -> Callconv #

Generic Safety 

Associated Types

type Rep Safety :: * -> * #

Methods

from :: Safety -> Rep Safety x #

to :: Rep Safety x -> Safety #

Generic Pragma 

Associated Types

type Rep Pragma :: * -> * #

Methods

from :: Pragma -> Rep Pragma x #

to :: Rep Pragma x -> Pragma #

Generic Inline 

Associated Types

type Rep Inline :: * -> * #

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Generic RuleMatch 

Associated Types

type Rep RuleMatch :: * -> * #

Generic Phases 

Associated Types

type Rep Phases :: * -> * #

Methods

from :: Phases -> Rep Phases x #

to :: Rep Phases x -> Phases #

Generic RuleBndr 

Associated Types

type Rep RuleBndr :: * -> * #

Methods

from :: RuleBndr -> Rep RuleBndr x #

to :: Rep RuleBndr x -> RuleBndr #

Generic AnnTarget 

Associated Types

type Rep AnnTarget :: * -> * #

Generic SourceUnpackedness 
Generic SourceStrictness 
Generic DecidedStrictness 
Generic Bang 

Associated Types

type Rep Bang :: * -> * #

Methods

from :: Bang -> Rep Bang x #

to :: Rep Bang x -> Bang #

Generic FamilyResultSig 
Generic TyLit 

Associated Types

type Rep TyLit :: * -> * #

Methods

from :: TyLit -> Rep TyLit x #

to :: Rep TyLit x -> TyLit #

Generic Role 

Associated Types

type Rep Role :: * -> * #

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Generic AnnLookup 

Associated Types

type Rep AnnLookup :: * -> * #

Generic Strand 

Associated Types

type Rep Strand :: * -> * #

Methods

from :: Strand -> Rep Strand x #

to :: Rep Strand x -> Strand #

Generic Caret 

Associated Types

type Rep Caret :: * -> * #

Methods

from :: Caret -> Rep Caret x #

to :: Rep Caret x -> Caret #

Generic Span 

Associated Types

type Rep Span :: * -> * #

Methods

from :: Span -> Rep Span x #

to :: Rep Span x -> Span #

Generic Fixit 

Associated Types

type Rep Fixit :: * -> * #

Methods

from :: Fixit -> Rep Fixit x #

to :: Rep Fixit x -> Fixit #

Generic Delta 

Associated Types

type Rep Delta :: * -> * #

Methods

from :: Delta -> Rep Delta x #

to :: Rep Delta x -> Delta #

Generic Format 

Associated Types

type Rep Format :: * -> * #

Methods

from :: Format -> Rep Format x #

to :: Rep Format x -> Format #

Generic Method 

Associated Types

type Rep Method :: * -> * #

Methods

from :: Method -> Rep Method x #

to :: Rep Method x -> Method #

Generic CompressionLevel 
Generic MemoryLevel 

Associated Types

type Rep MemoryLevel :: * -> * #

Generic CompressionStrategy 
Generic [a] 

Associated Types

type Rep [a] :: * -> * #

Methods

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

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

Generic (Maybe a) 

Associated Types

type Rep (Maybe a) :: * -> * #

Methods

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

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

Generic (V1 p) 

Associated Types

type Rep (V1 p) :: * -> * #

Methods

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

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

Generic (U1 p) 

Associated Types

type Rep (U1 p) :: * -> * #

Methods

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

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

Generic (Par1 p) 

Associated Types

type Rep (Par1 p) :: * -> * #

Methods

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

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

Generic (Identity a) 

Associated Types

type Rep (Identity a) :: * -> * #

Methods

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

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

Generic (Min a) 

Associated Types

type Rep (Min a) :: * -> * #

Methods

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

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

Generic (Max a) 

Associated Types

type Rep (Max a) :: * -> * #

Methods

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

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

Generic (First a) 

Associated Types

type Rep (First a) :: * -> * #

Methods

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

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

Generic (Last a) 

Associated Types

type Rep (Last a) :: * -> * #

Methods

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

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

Generic (WrappedMonoid m) 

Associated Types

type Rep (WrappedMonoid m) :: * -> * #

Generic (Option a) 

Associated Types

type Rep (Option a) :: * -> * #

Methods

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

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

Generic (NonEmpty a) 

Associated Types

type Rep (NonEmpty a) :: * -> * #

Methods

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

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

Generic (Complex a) 

Associated Types

type Rep (Complex a) :: * -> * #

Methods

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

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

Generic (ZipList a) 

Associated Types

type Rep (ZipList a) :: * -> * #

Methods

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

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

Generic (Dual a) 

Associated Types

type Rep (Dual a) :: * -> * #

Methods

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

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

Generic (Endo a) 

Associated Types

type Rep (Endo a) :: * -> * #

Methods

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

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

Generic (Sum a) 

Associated Types

type Rep (Sum a) :: * -> * #

Methods

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

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

Generic (Product a) 

Associated Types

type Rep (Product a) :: * -> * #

Methods

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

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

Generic (First a) 

Associated Types

type Rep (First a) :: * -> * #

Methods

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

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

Generic (Last a) 

Associated Types

type Rep (Last a) :: * -> * #

Methods

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

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

Generic (HistoriedResponse body) 

Associated Types

type Rep (HistoriedResponse body) :: * -> * #

Methods

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

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

Generic (Doc a) 

Associated Types

type Rep (Doc a) :: * -> * #

Methods

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

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

Generic (Careted a) 

Associated Types

type Rep (Careted a) :: * -> * #

Methods

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

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

Generic (Spanned a) 

Associated Types

type Rep (Spanned a) :: * -> * #

Methods

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

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

Generic (Either a b) 

Associated Types

type Rep (Either a b) :: * -> * #

Methods

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

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

Generic (Rec1 f p) 

Associated Types

type Rep (Rec1 f p) :: * -> * #

Methods

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

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

Generic (URec Char p) 

Associated Types

type Rep (URec Char p) :: * -> * #

Methods

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

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

Generic (URec Double p) 

Associated Types

type Rep (URec Double p) :: * -> * #

Methods

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

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

Generic (URec Float p) 

Associated Types

type Rep (URec Float p) :: * -> * #

Methods

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

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

Generic (URec Int p) 

Associated Types

type Rep (URec Int p) :: * -> * #

Methods

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

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

Generic (URec Word p) 

Associated Types

type Rep (URec Word p) :: * -> * #

Methods

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

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

Generic (URec (Ptr ()) p) 

Associated Types

type Rep (URec (Ptr ()) p) :: * -> * #

Methods

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

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

Generic (a, b) 

Associated Types

type Rep (a, b) :: * -> * #

Methods

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

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

Generic (Arg a b) 

Associated Types

type Rep (Arg a b) :: * -> * #

Methods

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

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

Generic (WrappedMonad m a) 

Associated Types

type Rep (WrappedMonad m a) :: * -> * #

Methods

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

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

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

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

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

Generic (K1 i c p) 

Associated Types

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

Methods

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

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

Generic ((:+:) f g p) 

Associated Types

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

Methods

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

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

Generic ((:*:) f g p) 

Associated Types

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

Methods

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

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

Generic ((:.:) f g p) 

Associated Types

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

Methods

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

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

Generic (a, b, c) 

Associated Types

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

Methods

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

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

Generic (WrappedArrow a b c) 

Associated Types

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

Methods

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

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

Generic (Const k a b) 

Associated Types

type Rep (Const k a b) :: * -> * #

Methods

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

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

Generic (Alt k f a) 

Associated Types

type Rep (Alt k f a) :: * -> * #

Methods

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

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

Generic (Join k p a) 

Associated Types

type Rep (Join k p a) :: * -> * #

Methods

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

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

Generic (Tagged k s b) 

Associated Types

type Rep (Tagged k s b) :: * -> * #

Methods

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

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

Generic (M1 i c f p) 

Associated Types

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

Methods

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

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

Generic (a, b, c, d) 

Associated Types

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

Methods

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

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

Generic (Product k f g a) 

Associated Types

type Rep (Product k f g a) :: * -> * #

Methods

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

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

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

Associated Types

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

Methods

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

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

Generic (Compose k1 k f g a) 

Associated Types

type Rep (Compose k1 k f g a) :: * -> * #

Methods

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

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

Generic (WrappedBifunctor k1 k p a b) 

Associated Types

type Rep (WrappedBifunctor k1 k p a b) :: * -> * #

Methods

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

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

Generic (Joker k1 k g a b) 

Associated Types

type Rep (Joker k1 k g a b) :: * -> * #

Methods

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

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

Generic (Flip k k1 p a b) 

Associated Types

type Rep (Flip k k1 p a b) :: * -> * #

Methods

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

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

Generic (Clown k1 k f a b) 

Associated Types

type Rep (Clown k1 k f a b) :: * -> * #

Methods

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

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

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

Associated Types

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

Methods

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

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

Generic (Product k1 k f g a b) 

Associated Types

type Rep (Product k1 k f g a b) :: * -> * #

Methods

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

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

Generic (Sum k1 k p q a b) 

Associated Types

type Rep (Sum k1 k p q a b) :: * -> * #

Methods

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

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

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

Associated Types

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

Methods

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

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

Generic (Tannen k2 k1 k f p a b) 

Associated Types

type Rep (Tannen k2 k1 k f p a b) :: * -> * #

Methods

from :: Tannen k2 k1 k f p a b -> Rep (Tannen k2 k1 k f p a b) x #

to :: Rep (Tannen k2 k1 k f p a b) x -> Tannen k2 k1 k f p a b #

Generic (Biff k3 k2 k1 k p f g a b) 

Associated Types

type Rep (Biff k3 k2 k1 k p f g a b) :: * -> * #

Methods

from :: Biff k3 k2 k1 k p f g a b -> Rep (Biff k3 k2 k1 k p f g a b) x #

to :: Rep (Biff k3 k2 k1 k p f g a b) x -> Biff k3 k2 k1 k p f g a b #