singletons-2.2: A framework for generating singleton types

Copyright(C) 2013 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRichard Eisenberg (eir@cis.upenn.edu)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Prelude.Tuple

Contents

Description

Defines functions and datatypes relating to the singleton for tuples, including a singletons version of all the definitions in Data.Tuple.

Because many of these definitions are produced by Template Haskell, it is not possible to create proper Haddock documentation. Please look up the corresponding operation in Data.Tuple. Also, please excuse the apparent repeated variable names. This is due to an interaction between Template Haskell and Haddock.

Synopsis

Singleton definitions

See Sing for more info.

data family Sing (a :: k) Source #

The singleton kind-indexed data family.

Instances

data Sing Bool Source # 
data Sing Bool where
data Sing Ordering Source # 
data Sing * Source # 
data Sing * where
data Sing Nat Source # 
data Sing Nat where
data Sing Symbol Source # 
data Sing Symbol where
data Sing () Source # 
data Sing () where
data Sing [a0] Source # 
data Sing [a0] where
data Sing (Maybe a0) Source # 
data Sing (Maybe a0) where
data Sing (NonEmpty a0) Source # 
data Sing (NonEmpty a0) where
data Sing (Either a0 b0) Source # 
data Sing (Either a0 b0) where
data Sing (a0, b0) Source # 
data Sing (a0, b0) where
data Sing ((~>) k1 k2) Source # 
data Sing ((~>) k1 k2) = SLambda {}
data Sing (a0, b0, c0) Source # 
data Sing (a0, b0, c0) where
data Sing (a0, b0, c0, d0) Source # 
data Sing (a0, b0, c0, d0) where
data Sing (a0, b0, c0, d0, e0) Source # 
data Sing (a0, b0, c0, d0, e0) where
data Sing (a0, b0, c0, d0, e0, f0) Source # 
data Sing (a0, b0, c0, d0, e0, f0) where
data Sing (a0, b0, c0, d0, e0, f0, g0) Source # 
data Sing (a0, b0, c0, d0, e0, f0, g0) where

type STuple0 = (Sing :: () -> Type) Source #

type STuple2 = (Sing :: (a, b) -> Type) Source #

type STuple3 = (Sing :: (a, b, c) -> Type) Source #

type STuple4 = (Sing :: (a, b, c, d) -> Type) Source #

type STuple5 = (Sing :: (a, b, c, d, e) -> Type) Source #

type STuple6 = (Sing :: (a, b, c, d, e, f) -> Type) Source #

type STuple7 = (Sing :: (a, b, c, d, e, f, g) -> Type) Source #

Singletons from Data.Tuple

type family Fst (a :: (a, b)) :: a where ... Source #

Equations

Fst '(x, _z_1627840782) = x 

sFst :: forall t. Sing t -> Sing (Apply FstSym0 t :: a) Source #

type family Snd (a :: (a, b)) :: b where ... Source #

Equations

Snd '(_z_1627840773, y) = y 

sSnd :: forall t. Sing t -> Sing (Apply SndSym0 t :: b) Source #

type family Curry (a :: TyFun (a, b) c -> Type) (a :: a) (a :: b) :: c where ... Source #

Equations

Curry f x y = Apply f (Apply (Apply Tuple2Sym0 x) y) 

sCurry :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply CurrySym0 t) t) t :: c) Source #

type family Uncurry (a :: TyFun a (TyFun b c -> Type) -> Type) (a :: (a, b)) :: c where ... Source #

Equations

Uncurry f p = Apply (Apply f (Apply FstSym0 p)) (Apply SndSym0 p) 

sUncurry :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply UncurrySym0 t) t :: c) Source #

type family Swap (a :: (a, b)) :: (b, a) where ... Source #

Equations

Swap '(a, b) = Apply (Apply Tuple2Sym0 b) a 

sSwap :: forall t. Sing t -> Sing (Apply SwapSym0 t :: (b, a)) Source #

Defunctionalization symbols

type Tuple0Sym0 = '() Source #

data Tuple2Sym0 l Source #

Instances

SuppressUnusedWarnings (TyFun a822083586 (TyFun b822083587 (a822083586, b822083587) -> Type) -> *) (Tuple2Sym0 a822083586 b822083587) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple2Sym0 a822083586 b822083587) t -> () Source #

type Apply a822083586 (TyFun b822083587 (a822083586, b822083587) -> Type) (Tuple2Sym0 a822083586 b822083587) l0 Source # 
type Apply a822083586 (TyFun b822083587 (a822083586, b822083587) -> Type) (Tuple2Sym0 a822083586 b822083587) l0 = Tuple2Sym1 b822083587 a822083586 l0

data Tuple2Sym1 l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> TyFun b822083587 (a822083586, b822083587) -> *) (Tuple2Sym1 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple2Sym1 b822083587 a822083586) t -> () Source #

type Apply b822083587 (a822083586, b822083587) (Tuple2Sym1 b822083587 a822083586 l1) l0 Source # 
type Apply b822083587 (a822083586, b822083587) (Tuple2Sym1 b822083587 a822083586 l1) l0 = Tuple2Sym2 a822083586 b822083587 l1 l0

type Tuple2Sym2 t t = '(t, t) Source #

data Tuple3Sym0 l Source #

Instances

SuppressUnusedWarnings (TyFun a822083586 (TyFun b822083587 (TyFun c822083588 (a822083586, b822083587, c822083588) -> Type) -> Type) -> *) (Tuple3Sym0 a822083586 b822083587 c822083588) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym0 a822083586 b822083587 c822083588) t -> () Source #

type Apply a822083586 (TyFun b822083587 (TyFun c822083588 (a822083586, b822083587, c822083588) -> Type) -> Type) (Tuple3Sym0 a822083586 b822083587 c822083588) l0 Source # 
type Apply a822083586 (TyFun b822083587 (TyFun c822083588 (a822083586, b822083587, c822083588) -> Type) -> Type) (Tuple3Sym0 a822083586 b822083587 c822083588) l0 = Tuple3Sym1 b822083587 c822083588 a822083586 l0

data Tuple3Sym1 l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> TyFun b822083587 (TyFun c822083588 (a822083586, b822083587, c822083588) -> Type) -> *) (Tuple3Sym1 b822083587 c822083588 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym1 b822083587 c822083588 a822083586) t -> () Source #

type Apply b822083587 (TyFun c822083588 (a822083586, b822083587, c822083588) -> Type) (Tuple3Sym1 b822083587 c822083588 a822083586 l1) l0 Source # 
type Apply b822083587 (TyFun c822083588 (a822083586, b822083587, c822083588) -> Type) (Tuple3Sym1 b822083587 c822083588 a822083586 l1) l0 = Tuple3Sym2 c822083588 b822083587 a822083586 l1 l0

data Tuple3Sym2 l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> TyFun c822083588 (a822083586, b822083587, c822083588) -> *) (Tuple3Sym2 c822083588 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym2 c822083588 b822083587 a822083586) t -> () Source #

type Apply c822083588 (a822083586, b822083587, c822083588) (Tuple3Sym2 c822083588 b822083587 a822083586 l1 l2) l0 Source # 
type Apply c822083588 (a822083586, b822083587, c822083588) (Tuple3Sym2 c822083588 b822083587 a822083586 l1 l2) l0 = Tuple3Sym3 a822083586 b822083587 c822083588 l1 l2 l0

type Tuple3Sym3 t t t = '(t, t, t) Source #

data Tuple4Sym0 l Source #

Instances

SuppressUnusedWarnings (TyFun a822083586 (TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (a822083586, b822083587, c822083588, d822083589) -> Type) -> Type) -> Type) -> *) (Tuple4Sym0 a822083586 b822083587 c822083588 d822083589) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym0 a822083586 b822083587 c822083588 d822083589) t -> () Source #

type Apply a822083586 (TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (a822083586, b822083587, c822083588, d822083589) -> Type) -> Type) -> Type) (Tuple4Sym0 a822083586 b822083587 c822083588 d822083589) l0 Source # 
type Apply a822083586 (TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (a822083586, b822083587, c822083588, d822083589) -> Type) -> Type) -> Type) (Tuple4Sym0 a822083586 b822083587 c822083588 d822083589) l0 = Tuple4Sym1 b822083587 c822083588 d822083589 a822083586 l0

data Tuple4Sym1 l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (a822083586, b822083587, c822083588, d822083589) -> Type) -> Type) -> *) (Tuple4Sym1 b822083587 c822083588 d822083589 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym1 b822083587 c822083588 d822083589 a822083586) t -> () Source #

type Apply b822083587 (TyFun c822083588 (TyFun d822083589 (a822083586, b822083587, c822083588, d822083589) -> Type) -> Type) (Tuple4Sym1 b822083587 c822083588 d822083589 a822083586 l1) l0 Source # 
type Apply b822083587 (TyFun c822083588 (TyFun d822083589 (a822083586, b822083587, c822083588, d822083589) -> Type) -> Type) (Tuple4Sym1 b822083587 c822083588 d822083589 a822083586 l1) l0 = Tuple4Sym2 c822083588 d822083589 b822083587 a822083586 l1 l0

data Tuple4Sym2 l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> TyFun c822083588 (TyFun d822083589 (a822083586, b822083587, c822083588, d822083589) -> Type) -> *) (Tuple4Sym2 c822083588 d822083589 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym2 c822083588 d822083589 b822083587 a822083586) t -> () Source #

type Apply c822083588 (TyFun d822083589 (a822083586, b822083587, c822083588, d822083589) -> Type) (Tuple4Sym2 c822083588 d822083589 b822083587 a822083586 l1 l2) l0 Source # 
type Apply c822083588 (TyFun d822083589 (a822083586, b822083587, c822083588, d822083589) -> Type) (Tuple4Sym2 c822083588 d822083589 b822083587 a822083586 l1 l2) l0 = Tuple4Sym3 d822083589 c822083588 b822083587 a822083586 l1 l2 l0

data Tuple4Sym3 l l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> c822083588 -> TyFun d822083589 (a822083586, b822083587, c822083588, d822083589) -> *) (Tuple4Sym3 d822083589 c822083588 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym3 d822083589 c822083588 b822083587 a822083586) t -> () Source #

type Apply d822083589 (a822083586, b822083587, c822083588, d822083589) (Tuple4Sym3 d822083589 c822083588 b822083587 a822083586 l1 l2 l3) l0 Source # 
type Apply d822083589 (a822083586, b822083587, c822083588, d822083589) (Tuple4Sym3 d822083589 c822083588 b822083587 a822083586 l1 l2 l3) l0 = Tuple4Sym4 a822083586 b822083587 c822083588 d822083589 l1 l2 l3 l0

type Tuple4Sym4 t t t t = '(t, t, t, t) Source #

data Tuple5Sym0 l Source #

Instances

SuppressUnusedWarnings (TyFun a822083586 (TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple5Sym0 a822083586 b822083587 c822083588 d822083589 e822083590) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym0 a822083586 b822083587 c822083588 d822083589 e822083590) t -> () Source #

type Apply a822083586 (TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> Type) -> Type) -> Type) -> Type) (Tuple5Sym0 a822083586 b822083587 c822083588 d822083589 e822083590) l0 Source # 
type Apply a822083586 (TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> Type) -> Type) -> Type) -> Type) (Tuple5Sym0 a822083586 b822083587 c822083588 d822083589 e822083590) l0 = Tuple5Sym1 b822083587 c822083588 d822083589 e822083590 a822083586 l0

data Tuple5Sym1 l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> Type) -> Type) -> Type) -> *) (Tuple5Sym1 b822083587 c822083588 d822083589 e822083590 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym1 b822083587 c822083588 d822083589 e822083590 a822083586) t -> () Source #

type Apply b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> Type) -> Type) -> Type) (Tuple5Sym1 b822083587 c822083588 d822083589 e822083590 a822083586 l1) l0 Source # 
type Apply b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> Type) -> Type) -> Type) (Tuple5Sym1 b822083587 c822083588 d822083589 e822083590 a822083586 l1) l0 = Tuple5Sym2 c822083588 d822083589 e822083590 b822083587 a822083586 l1 l0

data Tuple5Sym2 l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> Type) -> Type) -> *) (Tuple5Sym2 c822083588 d822083589 e822083590 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym2 c822083588 d822083589 e822083590 b822083587 a822083586) t -> () Source #

type Apply c822083588 (TyFun d822083589 (TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> Type) -> Type) (Tuple5Sym2 c822083588 d822083589 e822083590 b822083587 a822083586 l1 l2) l0 Source # 
type Apply c822083588 (TyFun d822083589 (TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> Type) -> Type) (Tuple5Sym2 c822083588 d822083589 e822083590 b822083587 a822083586 l1 l2) l0 = Tuple5Sym3 d822083589 e822083590 c822083588 b822083587 a822083586 l1 l2 l0

data Tuple5Sym3 l l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> c822083588 -> TyFun d822083589 (TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> Type) -> *) (Tuple5Sym3 d822083589 e822083590 c822083588 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym3 d822083589 e822083590 c822083588 b822083587 a822083586) t -> () Source #

type Apply d822083589 (TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> Type) (Tuple5Sym3 d822083589 e822083590 c822083588 b822083587 a822083586 l1 l2 l3) l0 Source # 
type Apply d822083589 (TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> Type) (Tuple5Sym3 d822083589 e822083590 c822083588 b822083587 a822083586 l1 l2 l3) l0 = Tuple5Sym4 e822083590 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l0

data Tuple5Sym4 l l l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> c822083588 -> d822083589 -> TyFun e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) -> *) (Tuple5Sym4 e822083590 d822083589 c822083588 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym4 e822083590 d822083589 c822083588 b822083587 a822083586) t -> () Source #

type Apply e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) (Tuple5Sym4 e822083590 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4) l0 Source # 
type Apply e822083590 (a822083586, b822083587, c822083588, d822083589, e822083590) (Tuple5Sym4 e822083590 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4) l0 = Tuple5Sym5 a822083586 b822083587 c822083588 d822083589 e822083590 l1 l2 l3 l4 l0

type Tuple5Sym5 t t t t t = '(t, t, t, t, t) Source #

data Tuple6Sym0 l Source #

Instances

SuppressUnusedWarnings (TyFun a822083586 (TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple6Sym0 a822083586 b822083587 c822083588 d822083589 e822083590 f822083591) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym0 a822083586 b822083587 c822083588 d822083589 e822083590 f822083591) t -> () Source #

type Apply a822083586 (TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple6Sym0 a822083586 b822083587 c822083588 d822083589 e822083590 f822083591) l0 Source # 
type Apply a822083586 (TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple6Sym0 a822083586 b822083587 c822083588 d822083589 e822083590 f822083591) l0 = Tuple6Sym1 b822083587 c822083588 d822083589 e822083590 f822083591 a822083586 l0

data Tuple6Sym1 l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple6Sym1 b822083587 c822083588 d822083589 e822083590 f822083591 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym1 b822083587 c822083588 d822083589 e822083590 f822083591 a822083586) t -> () Source #

type Apply b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> Type) -> Type) -> Type) (Tuple6Sym1 b822083587 c822083588 d822083589 e822083590 f822083591 a822083586 l1) l0 Source # 
type Apply b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> Type) -> Type) -> Type) (Tuple6Sym1 b822083587 c822083588 d822083589 e822083590 f822083591 a822083586 l1) l0 = Tuple6Sym2 c822083588 d822083589 e822083590 f822083591 b822083587 a822083586 l1 l0

data Tuple6Sym2 l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> Type) -> Type) -> *) (Tuple6Sym2 c822083588 d822083589 e822083590 f822083591 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym2 c822083588 d822083589 e822083590 f822083591 b822083587 a822083586) t -> () Source #

type Apply c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> Type) -> Type) (Tuple6Sym2 c822083588 d822083589 e822083590 f822083591 b822083587 a822083586 l1 l2) l0 Source # 
type Apply c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> Type) -> Type) (Tuple6Sym2 c822083588 d822083589 e822083590 f822083591 b822083587 a822083586 l1 l2) l0 = Tuple6Sym3 d822083589 e822083590 f822083591 c822083588 b822083587 a822083586 l1 l2 l0

data Tuple6Sym3 l l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> c822083588 -> TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> Type) -> *) (Tuple6Sym3 d822083589 e822083590 f822083591 c822083588 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym3 d822083589 e822083590 f822083591 c822083588 b822083587 a822083586) t -> () Source #

type Apply d822083589 (TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> Type) (Tuple6Sym3 d822083589 e822083590 f822083591 c822083588 b822083587 a822083586 l1 l2 l3) l0 Source # 
type Apply d822083589 (TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> Type) (Tuple6Sym3 d822083589 e822083590 f822083591 c822083588 b822083587 a822083586 l1 l2 l3) l0 = Tuple6Sym4 e822083590 f822083591 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l0

data Tuple6Sym4 l l l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> c822083588 -> d822083589 -> TyFun e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) -> *) (Tuple6Sym4 e822083590 f822083591 d822083589 c822083588 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym4 e822083590 f822083591 d822083589 c822083588 b822083587 a822083586) t -> () Source #

type Apply e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) (Tuple6Sym4 e822083590 f822083591 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4) l0 Source # 
type Apply e822083590 (TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> Type) (Tuple6Sym4 e822083590 f822083591 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4) l0 = Tuple6Sym5 f822083591 e822083590 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4 l0

data Tuple6Sym5 l l l l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> c822083588 -> d822083589 -> e822083590 -> TyFun f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) -> *) (Tuple6Sym5 f822083591 e822083590 d822083589 c822083588 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym5 f822083591 e822083590 d822083589 c822083588 b822083587 a822083586) t -> () Source #

type Apply f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) (Tuple6Sym5 f822083591 e822083590 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4 l5) l0 Source # 
type Apply f822083591 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591) (Tuple6Sym5 f822083591 e822083590 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4 l5) l0 = Tuple6Sym6 a822083586 b822083587 c822083588 d822083589 e822083590 f822083591 l1 l2 l3 l4 l5 l0

type Tuple6Sym6 t t t t t t = '(t, t, t, t, t, t) Source #

data Tuple7Sym0 l Source #

Instances

SuppressUnusedWarnings (TyFun a822083586 (TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym0 a822083586 b822083587 c822083588 d822083589 e822083590 f822083591 g822083592) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym0 a822083586 b822083587 c822083588 d822083589 e822083590 f822083591 g822083592) t -> () Source #

type Apply a822083586 (TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym0 a822083586 b822083587 c822083588 d822083589 e822083590 f822083591 g822083592) l0 Source # 
type Apply a822083586 (TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym0 a822083586 b822083587 c822083588 d822083589 e822083590 f822083591 g822083592) l0 = Tuple7Sym1 b822083587 c822083588 d822083589 e822083590 f822083591 g822083592 a822083586 l0

data Tuple7Sym1 l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> TyFun b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym1 b822083587 c822083588 d822083589 e822083590 f822083591 g822083592 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym1 b822083587 c822083588 d822083589 e822083590 f822083591 g822083592 a822083586) t -> () Source #

type Apply b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym1 b822083587 c822083588 d822083589 e822083590 f822083591 g822083592 a822083586 l1) l0 Source # 
type Apply b822083587 (TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym1 b822083587 c822083588 d822083589 e822083590 f822083591 g822083592 a822083586 l1) l0 = Tuple7Sym2 c822083588 d822083589 e822083590 f822083591 g822083592 b822083587 a822083586 l1 l0

data Tuple7Sym2 l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> TyFun c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym2 c822083588 d822083589 e822083590 f822083591 g822083592 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym2 c822083588 d822083589 e822083590 f822083591 g822083592 b822083587 a822083586) t -> () Source #

type Apply c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym2 c822083588 d822083589 e822083590 f822083591 g822083592 b822083587 a822083586 l1 l2) l0 Source # 
type Apply c822083588 (TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym2 c822083588 d822083589 e822083590 f822083591 g822083592 b822083587 a822083586 l1 l2) l0 = Tuple7Sym3 d822083589 e822083590 f822083591 g822083592 c822083588 b822083587 a822083586 l1 l2 l0

data Tuple7Sym3 l l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> c822083588 -> TyFun d822083589 (TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> Type) -> *) (Tuple7Sym3 d822083589 e822083590 f822083591 g822083592 c822083588 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym3 d822083589 e822083590 f822083591 g822083592 c822083588 b822083587 a822083586) t -> () Source #

type Apply d822083589 (TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> Type) (Tuple7Sym3 d822083589 e822083590 f822083591 g822083592 c822083588 b822083587 a822083586 l1 l2 l3) l0 Source # 
type Apply d822083589 (TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> Type) (Tuple7Sym3 d822083589 e822083590 f822083591 g822083592 c822083588 b822083587 a822083586 l1 l2 l3) l0 = Tuple7Sym4 e822083590 f822083591 g822083592 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l0

data Tuple7Sym4 l l l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> c822083588 -> d822083589 -> TyFun e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) -> *) (Tuple7Sym4 e822083590 f822083591 g822083592 d822083589 c822083588 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym4 e822083590 f822083591 g822083592 d822083589 c822083588 b822083587 a822083586) t -> () Source #

type Apply e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) (Tuple7Sym4 e822083590 f822083591 g822083592 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4) l0 Source # 
type Apply e822083590 (TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> Type) (Tuple7Sym4 e822083590 f822083591 g822083592 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4) l0 = Tuple7Sym5 f822083591 g822083592 e822083590 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4 l0

data Tuple7Sym5 l l l l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> c822083588 -> d822083589 -> e822083590 -> TyFun f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) -> *) (Tuple7Sym5 f822083591 g822083592 e822083590 d822083589 c822083588 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym5 f822083591 g822083592 e822083590 d822083589 c822083588 b822083587 a822083586) t -> () Source #

type Apply f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) (Tuple7Sym5 f822083591 g822083592 e822083590 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4 l5) l0 Source # 
type Apply f822083591 (TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> Type) (Tuple7Sym5 f822083591 g822083592 e822083590 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4 l5) l0 = Tuple7Sym6 g822083592 f822083591 e822083590 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4 l5 l0

data Tuple7Sym6 l l l l l l l Source #

Instances

SuppressUnusedWarnings (a822083586 -> b822083587 -> c822083588 -> d822083589 -> e822083590 -> f822083591 -> TyFun g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) -> *) (Tuple7Sym6 g822083592 f822083591 e822083590 d822083589 c822083588 b822083587 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym6 g822083592 f822083591 e822083590 d822083589 c822083588 b822083587 a822083586) t -> () Source #

type Apply g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) (Tuple7Sym6 g822083592 f822083591 e822083590 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4 l5 l6) l0 Source # 
type Apply g822083592 (a822083586, b822083587, c822083588, d822083589, e822083590, f822083591, g822083592) (Tuple7Sym6 g822083592 f822083591 e822083590 d822083589 c822083588 b822083587 a822083586 l1 l2 l3 l4 l5 l6) l0 = Tuple7Sym7 a822083586 b822083587 c822083588 d822083589 e822083590 f822083591 g822083592 l1 l2 l3 l4 l5 l6 l0

type Tuple7Sym7 t t t t t t t = '(t, t, t, t, t, t, t) Source #

data FstSym0 l Source #

Instances

SuppressUnusedWarnings (TyFun (a1627840729, b1627840730) a1627840729 -> *) (FstSym0 b1627840730 a1627840729) Source # 

Methods

suppressUnusedWarnings :: Proxy (FstSym0 b1627840730 a1627840729) t -> () Source #

type Apply (a1627840729, b1627840730) a1627840729 (FstSym0 b1627840730 a1627840729) l0 Source # 
type Apply (a1627840729, b1627840730) a1627840729 (FstSym0 b1627840730 a1627840729) l0 = FstSym1 a1627840729 b1627840730 l0

type FstSym1 t = Fst t Source #

data SndSym0 l Source #

Instances

SuppressUnusedWarnings (TyFun (a1627840727, b1627840728) b1627840728 -> *) (SndSym0 a1627840727 b1627840728) Source # 

Methods

suppressUnusedWarnings :: Proxy (SndSym0 a1627840727 b1627840728) t -> () Source #

type Apply (a1627840727, b1627840728) b1627840728 (SndSym0 a1627840727 b1627840728) l0 Source # 
type Apply (a1627840727, b1627840728) b1627840728 (SndSym0 a1627840727 b1627840728) l0 = SndSym1 a1627840727 b1627840728 l0

type SndSym1 t = Snd t Source #

data CurrySym0 l Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun (a1627840724, b1627840725) c1627840726 -> Type) (TyFun a1627840724 (TyFun b1627840725 c1627840726 -> Type) -> Type) -> *) (CurrySym0 a1627840724 b1627840725 c1627840726) Source # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym0 a1627840724 b1627840725 c1627840726) t -> () Source #

type Apply (TyFun (a1627840724, b1627840725) c1627840726 -> Type) (TyFun a1627840724 (TyFun b1627840725 c1627840726 -> Type) -> Type) (CurrySym0 a1627840724 b1627840725 c1627840726) l0 Source # 
type Apply (TyFun (a1627840724, b1627840725) c1627840726 -> Type) (TyFun a1627840724 (TyFun b1627840725 c1627840726 -> Type) -> Type) (CurrySym0 a1627840724 b1627840725 c1627840726) l0 = CurrySym1 a1627840724 b1627840725 c1627840726 l0

data CurrySym1 l l Source #

Instances

SuppressUnusedWarnings ((TyFun (a1627840724, b1627840725) c1627840726 -> Type) -> TyFun a1627840724 (TyFun b1627840725 c1627840726 -> Type) -> *) (CurrySym1 a1627840724 b1627840725 c1627840726) Source # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym1 a1627840724 b1627840725 c1627840726) t -> () Source #

type Apply a1627840724 (TyFun b1627840725 c1627840726 -> Type) (CurrySym1 a1627840724 b1627840725 c1627840726 l1) l0 Source # 
type Apply a1627840724 (TyFun b1627840725 c1627840726 -> Type) (CurrySym1 a1627840724 b1627840725 c1627840726 l1) l0 = CurrySym2 a1627840724 b1627840725 c1627840726 l1 l0

data CurrySym2 l l l Source #

Instances

SuppressUnusedWarnings ((TyFun (a1627840724, b1627840725) c1627840726 -> Type) -> a1627840724 -> TyFun b1627840725 c1627840726 -> *) (CurrySym2 a1627840724 b1627840725 c1627840726) Source # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym2 a1627840724 b1627840725 c1627840726) t -> () Source #

type Apply b1627840725 c1627840726 (CurrySym2 a1627840724 b1627840725 c1627840726 l1 l2) l0 Source # 
type Apply b1627840725 c1627840726 (CurrySym2 a1627840724 b1627840725 c1627840726 l1 l2) l0 = CurrySym3 a1627840724 b1627840725 c1627840726 l1 l2 l0

type CurrySym3 t t t = Curry t t t Source #

data UncurrySym0 l Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a1627840721 (TyFun b1627840722 c1627840723 -> Type) -> Type) (TyFun (a1627840721, b1627840722) c1627840723 -> Type) -> *) (UncurrySym0 a1627840721 b1627840722 c1627840723) Source # 

Methods

suppressUnusedWarnings :: Proxy (UncurrySym0 a1627840721 b1627840722 c1627840723) t -> () Source #

type Apply (TyFun a1627840721 (TyFun b1627840722 c1627840723 -> Type) -> Type) (TyFun (a1627840721, b1627840722) c1627840723 -> Type) (UncurrySym0 a1627840721 b1627840722 c1627840723) l0 Source # 
type Apply (TyFun a1627840721 (TyFun b1627840722 c1627840723 -> Type) -> Type) (TyFun (a1627840721, b1627840722) c1627840723 -> Type) (UncurrySym0 a1627840721 b1627840722 c1627840723) l0 = UncurrySym1 a1627840721 b1627840722 c1627840723 l0

data UncurrySym1 l l Source #

Instances

SuppressUnusedWarnings ((TyFun a1627840721 (TyFun b1627840722 c1627840723 -> Type) -> Type) -> TyFun (a1627840721, b1627840722) c1627840723 -> *) (UncurrySym1 a1627840721 b1627840722 c1627840723) Source # 

Methods

suppressUnusedWarnings :: Proxy (UncurrySym1 a1627840721 b1627840722 c1627840723) t -> () Source #

type Apply (a1627840721, b1627840722) c1627840723 (UncurrySym1 a1627840721 b1627840722 c1627840723 l1) l0 Source # 
type Apply (a1627840721, b1627840722) c1627840723 (UncurrySym1 a1627840721 b1627840722 c1627840723 l1) l0 = UncurrySym2 a1627840721 b1627840722 c1627840723 l1 l0

type UncurrySym2 t t = Uncurry t t Source #

data SwapSym0 l Source #

Instances

SuppressUnusedWarnings (TyFun (a1627840719, b1627840720) (b1627840720, a1627840719) -> *) (SwapSym0 b1627840720 a1627840719) Source # 

Methods

suppressUnusedWarnings :: Proxy (SwapSym0 b1627840720 a1627840719) t -> () Source #

type Apply (a1627840719, b1627840720) (b1627840720, a1627840719) (SwapSym0 b1627840720 a1627840719) l0 Source # 
type Apply (a1627840719, b1627840720) (b1627840720, a1627840719) (SwapSym0 b1627840720 a1627840719) l0 = SwapSym1 a1627840719 b1627840720 l0

type SwapSym1 t = Swap t Source #