singletons-2.4: A framework for generating singleton types

Copyright(C) 2013 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRichard Eisenberg (rae@cs.brynmawr.edu)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.TH

Contents

Description

This module contains everything you need to derive your own singletons via Template Haskell.

TURN ON -XScopedTypeVariables IN YOUR MODULE IF YOU WANT THIS TO WORK.

Synopsis

Primary Template Haskell generation functions

singletons :: DsMonad q => q [Dec] -> q [Dec] Source #

Make promoted and singleton versions of all declarations given, retaining the original declarations. See https://github.com/goldfirere/singletons/blob/master/README.md for further explanation.

singletonsOnly :: DsMonad q => q [Dec] -> q [Dec] Source #

Make promoted and singleton versions of all declarations given, discarding the original declarations. Note that a singleton based on a datatype needs the original datatype, so this will fail if it sees any datatype declarations. Classes, instances, and functions are all fine.

genSingletons :: DsMonad q => [Name] -> q [Dec] Source #

Generate singleton definitions from a type that is already defined. For example, the singletons package itself uses

$(genSingletons [''Bool, ''Maybe, ''Either, ''[]])

to generate singletons for Prelude types.

promote :: DsMonad q => q [Dec] -> q [Dec] Source #

Promote every declaration given to the type level, retaining the originals.

promoteOnly :: DsMonad q => q [Dec] -> q [Dec] Source #

Promote each declaration, discarding the originals. Note that a promoted datatype uses the same definition as an original datatype, so this will not work with datatypes. Classes, instances, and functions are all fine.

genDefunSymbols :: DsMonad q => [Name] -> q [Dec] Source #

Generate defunctionalization symbols for existing type family

genPromotions :: DsMonad q => [Name] -> q [Dec] Source #

Generate promoted definitions from a type that is already defined. This is generally only useful with classes.

Functions to generate equality instances

promoteEqInstances :: DsMonad q => [Name] -> q [Dec] Source #

Produce instances for (==) (type-level equality) from the given types

promoteEqInstance :: DsMonad q => Name -> q [Dec] Source #

Produce an instance for (==) (type-level equality) from the given type

singEqInstances :: DsMonad q => [Name] -> q [Dec] Source #

Create instances of SEq and type-level (==) for each type in the list

singEqInstance :: DsMonad q => Name -> q [Dec] Source #

Create instance of SEq and type-level (==) for the given type

singEqInstancesOnly :: DsMonad q => [Name] -> q [Dec] Source #

Create instances of SEq (only -- no instance for (==), which SEq generally relies on) for each type in the list

singEqInstanceOnly :: DsMonad q => Name -> q [Dec] Source #

Create instances of SEq (only -- no instance for (==), which SEq generally relies on) for the given type

singDecideInstances :: DsMonad q => [Name] -> q [Dec] Source #

Create instances of SDecide for each type in the list.

singDecideInstance :: DsMonad q => Name -> q [Dec] Source #

Create instance of SDecide for the given type.

Functions to generate Ord instances

promoteOrdInstances :: DsMonad q => [Name] -> q [Dec] Source #

Produce instances for POrd from the given types

promoteOrdInstance :: DsMonad q => Name -> q [Dec] Source #

Produce an instance for POrd from the given type

singOrdInstances :: DsMonad q => [Name] -> q [Dec] Source #

Create instances of SOrd for the given types

singOrdInstance :: DsMonad q => Name -> q [Dec] Source #

Create instance of SOrd for the given type

Functions to generate Bounded instances

promoteBoundedInstances :: DsMonad q => [Name] -> q [Dec] Source #

Produce instances for PBounded from the given types

promoteBoundedInstance :: DsMonad q => Name -> q [Dec] Source #

Produce an instance for PBounded from the given type

singBoundedInstances :: DsMonad q => [Name] -> q [Dec] Source #

Create instances of SBounded for the given types

singBoundedInstance :: DsMonad q => Name -> q [Dec] Source #

Create instance of SBounded for the given type

Functions to generate Enum instances

promoteEnumInstances :: DsMonad q => [Name] -> q [Dec] Source #

Produce instances for PEnum from the given types

promoteEnumInstance :: DsMonad q => Name -> q [Dec] Source #

Produce an instance for PEnum from the given type

singEnumInstances :: DsMonad q => [Name] -> q [Dec] Source #

Create instances of SEnum for the given types

singEnumInstance :: DsMonad q => Name -> q [Dec] Source #

Create instance of SEnum for the given type

Functions to generate Show instances

promoteShowInstances :: DsMonad q => [Name] -> q [Dec] Source #

Produce instances for PShow from the given types

promoteShowInstance :: DsMonad q => Name -> q [Dec] Source #

Produce an instance for PShow from the given type

singShowInstances :: DsMonad q => [Name] -> q [Dec] Source #

Create instances of SShow for the given types

(Not to be confused with showSingInstances.)

singShowInstance :: DsMonad q => Name -> q [Dec] Source #

Create instance of SShow for the given type

(Not to be confused with showShowInstance.)

Utility functions

cases Source #

Arguments

:: DsMonad q 
=> Name

The head of the type of the scrutinee. (Like ''Maybe or ''Bool.)

-> q Exp

The scrutinee, in a Template Haskell quote

-> q Exp

The body, in a Template Haskell quote

-> q Exp 

The function cases generates a case expression where each right-hand side is identical. This may be useful if the type-checker requires knowledge of which constructor is used to satisfy equality or type-class constraints, but where each constructor is treated the same.

sCases Source #

Arguments

:: DsMonad q 
=> Name

The head of the type the scrutinee's type is based on. (Like ''Maybe or ''Bool.)

-> q Exp

The scrutinee, in a Template Haskell quote

-> q Exp

The body, in a Template Haskell quote

-> q Exp 

The function sCases generates a case expression where each right-hand side is identical. This may be useful if the type-checker requires knowledge of which constructor is used to satisfy equality or type-class constraints, but where each constructor is treated the same. For sCases, unlike cases, the scrutinee is a singleton. But make sure to pass in the name of the original datatype, preferring ''Maybe over ''SMaybe.

Basic singleton definitions

data family Sing (a :: k) Source #

The singleton kind-indexed data family.

Instances
data Sing (z :: Bool) Source # 
Instance details
data Sing (z :: Bool) where
data Sing (z :: Ordering) Source # 
Instance details
data Sing (z :: Ordering) where
data Sing (a :: Type) Source # 
Instance details
data Sing (a :: Type) = STypeRep (TypeRep a)
data Sing (n :: Nat) Source # 
Instance details
data Sing (n :: Nat) where
data Sing (n :: Symbol) Source # 
Instance details
data Sing (n :: Symbol) where
data Sing (z :: ()) Source # 
Instance details
data Sing (z :: ()) where
data Sing (z :: Void) Source # 
Instance details
data Sing (z :: Void)
data Sing (z :: [a]) Source # 
Instance details
data Sing (z :: [a]) where
data Sing (z :: Maybe a) Source # 
Instance details
data Sing (z :: Maybe a) where
data Sing (z :: NonEmpty a) Source # 
Instance details
data Sing (z :: NonEmpty a) where
data Sing (z :: Either a b) Source # 
Instance details
data Sing (z :: Either a b) where
data Sing (z :: (a, b)) Source # 
Instance details
data Sing (z :: (a, b)) where
data Sing (f :: k1 ~> k2) Source # 
Instance details
data Sing (f :: k1 ~> k2) = SLambda {}
data Sing (z :: (a, b, c)) Source # 
Instance details
data Sing (z :: (a, b, c)) where
data Sing (z :: (a, b, c, d)) Source # 
Instance details
data Sing (z :: (a, b, c, d)) where
data Sing (z :: (a, b, c, d, e)) Source # 
Instance details
data Sing (z :: (a, b, c, d, e)) where
data Sing (z :: (a, b, c, d, e, f)) Source # 
Instance details
data Sing (z :: (a, b, c, d, e, f)) where
data Sing (z :: (a, b, c, d, e, f, g)) Source # 
Instance details
data Sing (z :: (a, b, c, d, e, f, g)) where

Auxiliary definitions

These definitions might be mentioned in code generated by Template Haskell, so they must be in scope.

class PEq a Source #

The promoted analogue of Eq. If you supply no definition for '(==)', then it defaults to a use of '(DTE.==)', from Data.Type.Equality.

Associated Types

type (x :: a) == (y :: a) :: Bool infix 4 Source #

type (x :: a) /= (y :: a) :: Bool infix 4 Source #

Instances
PEq Bool Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq Ordering Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq () Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq Void Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq [a] Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (Maybe a) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (NonEmpty a) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (Either a b) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (a, b) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (a, b, c) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (a, b, c, d) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (a, b, c, d, e) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (a, b, c, d, e, f) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (a, b, c, d, e, f, g) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

type family If (cond :: Bool) (tru :: k) (fls :: k) :: k where ... #

Type-level If. If True a b ==> a; If False a b ==> b

Equations

If True (tru :: k) (fls :: k) = tru 
If False (tru :: k) (fls :: k) = fls 

sIf :: Sing a -> Sing b -> Sing c -> Sing (If a b c) Source #

Conditional over singletons

type family (a :: Bool) && (b :: Bool) :: Bool where ... infixr 3 #

Type-level "and"

Equations

False && a = False 
True && a = a 
a && False = False 
a && True = a 
a && a = a 

(%&&) :: Sing a -> Sing b -> Sing (a && b) infixr 3 Source #

Conjunction of singletons

class SEq k where Source #

The singleton analogue of Eq. Unlike the definition for Eq, it is required that instances define a body for '(%==)'. You may also supply a body for '(%/=)'.

Minimal complete definition

(%==)

Methods

(%==) :: forall (a :: k) (b :: k). Sing a -> Sing b -> Sing (a == b) infix 4 Source #

Boolean equality on singletons

(%/=) :: forall (a :: k) (b :: k). Sing a -> Sing b -> Sing (a /= b) infix 4 Source #

Boolean disequality on singletons

(%/=) :: forall (a :: k) (b :: k). (a /= b) ~ Not (a == b) => Sing a -> Sing b -> Sing (a /= b) infix 4 Source #

Boolean disequality on singletons

Instances
SEq Bool Source # 
Instance details

Methods

(%==) :: Sing a -> Sing b -> Sing (a == b) Source #

(%/=) :: Sing a -> Sing b -> Sing (a /= b) Source #

SEq Ordering Source # 
Instance details

Methods

(%==) :: Sing a -> Sing b -> Sing (a == b) Source #

(%/=) :: Sing a -> Sing b -> Sing (a /= b) Source #

SEq () Source # 
Instance details

Methods

(%==) :: Sing a -> Sing b -> Sing (a == b) Source #

(%/=) :: Sing a -> Sing b -> Sing (a /= b) Source #

SEq Void Source # 
Instance details

Methods

(%==) :: Sing a -> Sing b -> Sing (a == b) Source #

(%/=) :: Sing a -> Sing b -> Sing (a /= b) Source #

(SEq a, SEq [a]) => SEq [a] Source # 
Instance details

Methods

(%==) :: Sing a0 -> Sing b -> Sing (a0 == b) Source #

(%/=) :: Sing a0 -> Sing b -> Sing (a0 /= b) Source #

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

Methods

(%==) :: Sing a0 -> Sing b -> Sing (a0 == b) Source #

(%/=) :: Sing a0 -> Sing b -> Sing (a0 /= b) Source #

(SEq a, SEq [a]) => SEq (NonEmpty a) Source # 
Instance details

Methods

(%==) :: Sing a0 -> Sing b -> Sing (a0 == b) Source #

(%/=) :: Sing a0 -> Sing b -> Sing (a0 /= b) Source #

(SEq a, SEq b) => SEq (Either a b) Source # 
Instance details

Methods

(%==) :: Sing a0 -> Sing b0 -> Sing (a0 == b0) Source #

(%/=) :: Sing a0 -> Sing b0 -> Sing (a0 /= b0) Source #

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

Methods

(%==) :: Sing a0 -> Sing b0 -> Sing (a0 == b0) Source #

(%/=) :: Sing a0 -> Sing b0 -> Sing (a0 /= b0) Source #

(SEq a, SEq b, SEq c) => SEq (a, b, c) Source # 
Instance details

Methods

(%==) :: Sing a0 -> Sing b0 -> Sing (a0 == b0) Source #

(%/=) :: Sing a0 -> Sing b0 -> Sing (a0 /= b0) Source #

(SEq a, SEq b, SEq c, SEq d) => SEq (a, b, c, d) Source # 
Instance details

Methods

(%==) :: Sing a0 -> Sing b0 -> Sing (a0 == b0) Source #

(%/=) :: Sing a0 -> Sing b0 -> Sing (a0 /= b0) Source #

(SEq a, SEq b, SEq c, SEq d, SEq e) => SEq (a, b, c, d, e) Source # 
Instance details

Methods

(%==) :: Sing a0 -> Sing b0 -> Sing (a0 == b0) Source #

(%/=) :: Sing a0 -> Sing b0 -> Sing (a0 /= b0) Source #

(SEq a, SEq b, SEq c, SEq d, SEq e, SEq f) => SEq (a, b, c, d, e, f) Source # 
Instance details

Methods

(%==) :: Sing a0 -> Sing b0 -> Sing (a0 == b0) Source #

(%/=) :: Sing a0 -> Sing b0 -> Sing (a0 /= b0) Source #

(SEq a, SEq b, SEq c, SEq d, SEq e, SEq f, SEq g) => SEq (a, b, c, d, e, f, g) Source # 
Instance details

Methods

(%==) :: Sing a0 -> Sing b0 -> Sing (a0 == b0) Source #

(%/=) :: Sing a0 -> Sing b0 -> Sing (a0 /= b0) Source #

class PEq a => POrd (a :: Type) Source #

Associated Types

type Compare (arg :: a) (arg :: a) :: Ordering Source #

type (arg :: a) < (arg :: a) :: Bool Source #

type (arg :: a) <= (arg :: a) :: Bool Source #

type (arg :: a) > (arg :: a) :: Bool Source #

type (arg :: a) >= (arg :: a) :: Bool Source #

type Max (arg :: a) (arg :: a) :: a Source #

type Min (arg :: a) (arg :: a) :: a Source #

Instances
POrd Bool Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd Ordering Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd () Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd Void Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd [a] Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (Maybe a) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (NonEmpty a) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (Either a b) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (a, b) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (a, b, c) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (a, b, c, d) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (a, b, c, d, e) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (a, b, c, d, e, f) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (a, b, c, d, e, f, g) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

class SEq a => SOrd a where Source #

Methods

sCompare :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t :: Ordering) Source #

(%<) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t :: Bool) infix 4 Source #

(%<=) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t :: Bool) infix 4 Source #

(%>) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t :: Bool) infix 4 Source #

(%>=) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t :: Bool) infix 4 Source #

sMax :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t :: a) Source #

sMin :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t :: a) Source #

sCompare :: forall (t :: a) (t :: a). ((Apply (Apply CompareSym0 t) t :: Ordering) ~ Apply (Apply Compare_6989586621679304673Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t :: Ordering) Source #

(%<) :: forall (t :: a) (t :: a). ((Apply (Apply (<@#@$) t) t :: Bool) ~ Apply (Apply TFHelper_6989586621679304706Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t :: Bool) infix 4 Source #

(%<=) :: forall (t :: a) (t :: a). ((Apply (Apply (<=@#@$) t) t :: Bool) ~ Apply (Apply TFHelper_6989586621679304739Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t :: Bool) infix 4 Source #

(%>) :: forall (t :: a) (t :: a). ((Apply (Apply (>@#@$) t) t :: Bool) ~ Apply (Apply TFHelper_6989586621679304772Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t :: Bool) infix 4 Source #

(%>=) :: forall (t :: a) (t :: a). ((Apply (Apply (>=@#@$) t) t :: Bool) ~ Apply (Apply TFHelper_6989586621679304805Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t :: Bool) infix 4 Source #

sMax :: forall (t :: a) (t :: a). ((Apply (Apply MaxSym0 t) t :: a) ~ Apply (Apply Max_6989586621679304838Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t :: a) Source #

sMin :: forall (t :: a) (t :: a). ((Apply (Apply MinSym0 t) t :: a) ~ Apply (Apply Min_6989586621679304871Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t :: a) Source #

Instances
SOrd Bool Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

SOrd Ordering Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

SOrd () Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

SOrd Void Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

(SOrd a, SOrd [a]) => SOrd [a] Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

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

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

(SOrd a, SOrd [a]) => SOrd (NonEmpty a) Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

(SOrd a, SOrd b) => SOrd (Either a b) Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

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

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

(SOrd a, SOrd b, SOrd c) => SOrd (a, b, c) Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

(SOrd a, SOrd b, SOrd c, SOrd d) => SOrd (a, b, c, d) Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

(SOrd a, SOrd b, SOrd c, SOrd d, SOrd e) => SOrd (a, b, c, d, e) Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

(SOrd a, SOrd b, SOrd c, SOrd d, SOrd e, SOrd f) => SOrd (a, b, c, d, e, f) Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

(SOrd a, SOrd b, SOrd c, SOrd d, SOrd e, SOrd f, SOrd g) => SOrd (a, b, c, d, e, f, g) Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

type family ThenCmp (a :: Ordering) (a :: Ordering) :: Ordering where ... Source #

Equations

ThenCmp EQ x = x 
ThenCmp LT _ = LTSym0 
ThenCmp GT _ = GTSym0 

sThenCmp :: forall (t :: Ordering) (t :: Ordering). Sing t -> Sing t -> Sing (Apply (Apply ThenCmpSym0 t) t :: Ordering) Source #

type family Foldl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #

Equations

Foldl f z0 xs0 = Apply (Apply (Let6989586621679259311LgoSym3 f z0 xs0) z0) xs0 

sFoldl :: forall (t :: TyFun b (TyFun a b -> Type) -> Type) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source #

class SDecide k where Source #

Members of the SDecide "kind" class support decidable equality. Instances of this class are generated alongside singleton definitions for datatypes that derive an Eq instance.

Minimal complete definition

(%~)

Methods

(%~) :: forall (a :: k) (b :: k). Sing a -> Sing b -> Decision (a :~: b) infix 4 Source #

Compute a proof or disproof of equality, given two singletons.

data (a :: k) :~: (b :: k) :: forall k. k -> k -> * where infix 4 #

Propositional equality. If a :~: b is inhabited by some terminating value, then the type a is the same as the type b. To use this equality in practice, pattern-match on the a :~: b to get out the Refl constructor; in the body of the pattern-match, the compiler knows that a ~ b.

Since: 4.7.0.0

Constructors

Refl :: a :~: a 
Instances
TestCoercion ((:~:) a :: k -> *)

Since: 4.7.0.0

Instance details

Methods

testCoercion :: (a :~: a0) -> (a :~: b) -> Maybe (Coercion a0 b) #

TestEquality ((:~:) a :: k -> *)

Since: 4.7.0.0

Instance details

Methods

testEquality :: (a :~: a0) -> (a :~: b) -> Maybe (a0 :~: b) #

a ~ b => Bounded (a :~: b)

Since: 4.7.0.0

Instance details

Methods

minBound :: a :~: b #

maxBound :: a :~: b #

a ~ b => Enum (a :~: b)

Since: 4.7.0.0

Instance details

Methods

succ :: (a :~: b) -> a :~: b #

pred :: (a :~: b) -> a :~: b #

toEnum :: Int -> a :~: b #

fromEnum :: (a :~: b) -> Int #

enumFrom :: (a :~: b) -> [a :~: b] #

enumFromThen :: (a :~: b) -> (a :~: b) -> [a :~: b] #

enumFromTo :: (a :~: b) -> (a :~: b) -> [a :~: b] #

enumFromThenTo :: (a :~: b) -> (a :~: b) -> (a :~: b) -> [a :~: b] #

Eq (a :~: b) 
Instance details

Methods

(==) :: (a :~: b) -> (a :~: b) -> Bool #

(/=) :: (a :~: b) -> (a :~: b) -> Bool #

(a ~ b, Data a) => Data (a :~: b)

Since: 4.7.0.0

Instance details

Methods

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

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

toConstr :: (a :~: b) -> Constr #

dataTypeOf :: (a :~: b) -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (a :~: b) 
Instance details

Methods

compare :: (a :~: b) -> (a :~: b) -> Ordering #

(<) :: (a :~: b) -> (a :~: b) -> Bool #

(<=) :: (a :~: b) -> (a :~: b) -> Bool #

(>) :: (a :~: b) -> (a :~: b) -> Bool #

(>=) :: (a :~: b) -> (a :~: b) -> Bool #

max :: (a :~: b) -> (a :~: b) -> a :~: b #

min :: (a :~: b) -> (a :~: b) -> a :~: b #

a ~ b => Read (a :~: b)

Since: 4.7.0.0

Instance details

Methods

readsPrec :: Int -> ReadS (a :~: b) #

readList :: ReadS [a :~: b] #

readPrec :: ReadPrec (a :~: b) #

readListPrec :: ReadPrec [a :~: b] #

Show (a :~: b) 
Instance details

Methods

showsPrec :: Int -> (a :~: b) -> ShowS #

show :: (a :~: b) -> String #

showList :: [a :~: b] -> ShowS #

data Void :: * #

Uninhabited data type

Since: 4.8.0.0

Instances
Eq Void

Since: 4.8.0.0

Instance details

Methods

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

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

Data Void

Since: 4.8.0.0

Instance details

Methods

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

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

toConstr :: Void -> Constr #

dataTypeOf :: Void -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Void

Since: 4.8.0.0

Instance details

Methods

compare :: Void -> Void -> Ordering #

(<) :: Void -> Void -> Bool #

(<=) :: Void -> Void -> Bool #

(>) :: Void -> Void -> Bool #

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

max :: Void -> Void -> Void #

min :: Void -> Void -> Void #

Read Void

Reading a Void value is always a parse error, considering Void as a data type with no constructors.

Since: 4.8.0.0

Instance details
Show Void

Since: 4.8.0.0

Instance details

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Ix Void

Since: 4.8.0.0

Instance details

Methods

range :: (Void, Void) -> [Void] #

index :: (Void, Void) -> Void -> Int #

unsafeIndex :: (Void, Void) -> Void -> Int

inRange :: (Void, Void) -> Void -> Bool #

rangeSize :: (Void, Void) -> Int #

unsafeRangeSize :: (Void, Void) -> Int

Generic Void 
Instance details

Associated Types

type Rep Void :: * -> * #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Semigroup Void

Since: 4.9.0.0

Instance details

Methods

(<>) :: Void -> Void -> Void #

sconcat :: NonEmpty Void -> Void #

stimes :: Integral b => b -> Void -> Void #

Exception Void

Since: 4.8.0.0

Instance details
PEq Void Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

SEq Void Source # 
Instance details

Methods

(%==) :: Sing a -> Sing b -> Sing (a == b) Source #

(%/=) :: Sing a -> Sing b -> Sing (a /= b) Source #

SOrd Void Source # 
Instance details

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

(%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source #

(%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source #

(%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source #

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

POrd Void Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

ShowSing Void Source # 
Instance details

Methods

showsSingPrec :: Int -> Sing a -> ShowS Source #

SShow Void Source # 
Instance details
PShow Void Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

SuppressUnusedWarnings (AbsurdSym0 :: TyFun Void a6989586621679285232 -> *) Source # 
Instance details
type Rep Void

Since: 4.8.0.0

Instance details
type Rep Void = D1 (MetaData "Void" "Data.Void" "base" False) (V1 :: * -> *)
type Demote Void Source # 
Instance details
data Sing (z :: Void) Source # 
Instance details
data Sing (z :: Void)
type Show_ (arg :: Void) Source # 
Instance details
type Show_ (arg :: Void)
type (a :: Void) == (b :: Void) Source # 
Instance details
type (a :: Void) == (b :: Void)
type (x :: Void) /= (y :: Void) Source # 
Instance details
type (x :: Void) /= (y :: Void) = Not (x == y)
type Compare (a1 :: Void) (a2 :: Void) Source # 
Instance details
type Compare (a1 :: Void) (a2 :: Void)
type (arg1 :: Void) < (arg2 :: Void) Source # 
Instance details
type (arg1 :: Void) < (arg2 :: Void)
type (arg1 :: Void) <= (arg2 :: Void) Source # 
Instance details
type (arg1 :: Void) <= (arg2 :: Void)
type (arg1 :: Void) > (arg2 :: Void) Source # 
Instance details
type (arg1 :: Void) > (arg2 :: Void)
type (arg1 :: Void) >= (arg2 :: Void) Source # 
Instance details
type (arg1 :: Void) >= (arg2 :: Void)
type Max (arg1 :: Void) (arg2 :: Void) Source # 
Instance details
type Max (arg1 :: Void) (arg2 :: Void)
type Min (arg1 :: Void) (arg2 :: Void) Source # 
Instance details
type Min (arg1 :: Void) (arg2 :: Void)
type ShowList (arg1 :: [Void]) arg2 Source # 
Instance details
type ShowList (arg1 :: [Void]) arg2
type ShowsPrec a1 (a2 :: Void) a3 Source # 
Instance details
type ShowsPrec a1 (a2 :: Void) a3
type Apply (AbsurdSym0 :: TyFun Void k2 -> *) (l :: Void) Source # 
Instance details
type Apply (AbsurdSym0 :: TyFun Void k2 -> *) (l :: Void) = (Absurd l :: k2)

type Refuted a = a -> Void Source #

Because we can never create a value of type Void, a function that type-checks at a -> Void shows that objects of type a can never exist. Thus, we say that a is Refuted

data Decision a Source #

A Decision about a type a is either a proof of existence or a proof that a cannot exist.

Constructors

Proved a

Witness for a

Disproved (Refuted a)

Proof that no a exists

class PBounded (a :: Type) Source #

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

Instances
PBounded Bool Source # 
Instance details

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded Ordering Source # 
Instance details

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded () Source # 
Instance details

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (a, b) Source # 
Instance details

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (a, b, c) Source # 
Instance details

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (a, b, c, d) Source # 
Instance details

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (a, b, c, d, e) Source # 
Instance details

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (a, b, c, d, e, f) Source # 
Instance details

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (a, b, c, d, e, f, g) Source # 
Instance details

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

class SBounded a where Source #

Minimal complete definition

sMinBound, sMaxBound

Instances
SBounded Bool Source # 
Instance details
SBounded Ordering Source # 
Instance details
SBounded () Source # 
Instance details
(SBounded a, SBounded b) => SBounded (a, b) Source # 
Instance details
(SBounded a, SBounded b, SBounded c) => SBounded (a, b, c) Source # 
Instance details
(SBounded a, SBounded b, SBounded c, SBounded d) => SBounded (a, b, c, d) Source # 
Instance details
(SBounded a, SBounded b, SBounded c, SBounded d, SBounded e) => SBounded (a, b, c, d, e) Source # 
Instance details
(SBounded a, SBounded b, SBounded c, SBounded d, SBounded e, SBounded f) => SBounded (a, b, c, d, e, f) Source # 
Instance details
(SBounded a, SBounded b, SBounded c, SBounded d, SBounded e, SBounded f, SBounded g) => SBounded (a, b, c, d, e, f, g) Source # 
Instance details

class PEnum (a :: Type) Source #

Associated Types

type ToEnum (arg :: Nat) :: a Source #

type FromEnum (arg :: a) :: Nat Source #

Instances
PEnum Bool Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

type EnumFromThenTo arg arg arg :: [a] Source #

PEnum Ordering Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

type EnumFromThenTo arg arg arg :: [a] Source #

PEnum Nat Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

type EnumFromThenTo arg arg arg :: [a] Source #

PEnum () Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

type EnumFromThenTo arg arg arg :: [a] Source #

class SEnum a where Source #

Minimal complete definition

sToEnum, sFromEnum

Methods

sToEnum :: forall (t :: Nat). Sing t -> Sing (Apply ToEnumSym0 t :: a) Source #

sFromEnum :: forall (t :: a). Sing t -> Sing (Apply FromEnumSym0 t :: Nat) Source #

Instances
SEnum Bool Source # 
Instance details
SEnum Ordering Source # 
Instance details
SEnum Nat Source # 
Instance details
SEnum () Source # 
Instance details

class PShow (a :: Type) Source #

Associated Types

type ShowsPrec (arg :: Nat) (arg :: a) (arg :: Symbol) :: Symbol Source #

type Show_ (arg :: a) :: Symbol Source #

type ShowList (arg :: [a]) (arg :: Symbol) :: Symbol Source #

Instances
PShow Bool Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow Ordering Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow Nat Source #

Note that this instance is really, really slow, since it uses an inefficient, inductive definition of division behind the hood.

Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow Symbol Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow () Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow Void Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow [a] Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Maybe a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (NonEmpty a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Either a b) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (a, b) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (a, b, c) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (a, b, c, d) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (a, b, c, d, e) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (a, b, c, d, e, f) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (a, b, c, d, e, f, g) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

class SShow a where Source #

Methods

sShowsPrec :: forall (t :: Nat) (t :: a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t :: Symbol) Source #

sShow_ :: forall (t :: a). Sing t -> Sing (Apply Show_Sym0 t :: Symbol) Source #

sShowList :: forall (t :: [a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t :: Symbol) Source #

sShowsPrec :: forall (t :: Nat) (t :: a) (t :: Symbol). ((Apply (Apply (Apply ShowsPrecSym0 t) t) t :: Symbol) ~ Apply (Apply (Apply ShowsPrec_6989586621679674410Sym0 t) t) t) => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t :: Symbol) Source #

sShow_ :: forall (t :: a). ((Apply Show_Sym0 t :: Symbol) ~ Apply Show__6989586621679674430Sym0 t) => Sing t -> Sing (Apply Show_Sym0 t :: Symbol) Source #

sShowList :: forall (t :: [a]) (t :: Symbol). ((Apply (Apply ShowListSym0 t) t :: Symbol) ~ Apply (Apply ShowList_6989586621679674448Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t :: Symbol) Source #

Instances
SShow Bool Source # 
Instance details
SShow Ordering Source # 
Instance details
SShow Nat Source # 
Instance details
SShow Symbol Source # 
Instance details
SShow () Source # 
Instance details
SShow Void Source # 
Instance details
SShow a => SShow [a] Source # 
Instance details
SShow a => SShow (Maybe a) Source # 
Instance details
(SShow a, SShow [a]) => SShow (NonEmpty a) Source # 
Instance details
(SShow a, SShow b) => SShow (Either a b) Source # 
Instance details
(SShow a, SShow b) => SShow (a, b) Source # 
Instance details
(SShow a, SShow b, SShow c) => SShow (a, b, c) Source # 
Instance details
(SShow a, SShow b, SShow c, SShow d) => SShow (a, b, c, d) Source # 
Instance details
(SShow a, SShow b, SShow c, SShow d, SShow e) => SShow (a, b, c, d, e) Source # 
Instance details
(SShow a, SShow b, SShow c, SShow d, SShow e, SShow f) => SShow (a, b, c, d, e, f) Source # 
Instance details
(SShow a, SShow b, SShow c, SShow d, SShow e, SShow f, SShow g) => SShow (a, b, c, d, e, f, g) Source # 
Instance details

type family ShowString (a :: Symbol) (a :: Symbol) :: Symbol where ... Source #

Equations

ShowString a_6989586621679674203 a_6989586621679674205 = Apply (Apply (<>@#@$) a_6989586621679674203) a_6989586621679674205 

sShowString :: forall (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowStringSym0 t) t :: Symbol) Source #

type family ShowParen (a :: Bool) (a :: TyFun Symbol Symbol -> Type) (a :: Symbol) :: Symbol where ... Source #

Equations

ShowParen b p a_6989586621679674255 = Apply (Case_6989586621679674260 b p a_6989586621679674255 b) a_6989586621679674255 

sShowParen :: forall (t :: Bool) (t :: TyFun Symbol Symbol -> Type) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowParenSym0 t) t) t :: Symbol) Source #

type family ShowSpace (a :: Symbol) :: Symbol where ... Source #

Equations

ShowSpace a_6989586621679674185 = Apply (Apply Lambda_6989586621679674192Sym0 a_6989586621679674185) a_6989586621679674185 

sShowSpace :: forall (t :: Symbol). Sing t -> Sing (Apply ShowSpaceSym0 t :: Symbol) Source #

type family ShowChar (a :: Symbol) (a :: Symbol) :: Symbol where ... Source #

Equations

ShowChar a_6989586621679674225 a_6989586621679674227 = Apply (Apply (<>@#@$) a_6989586621679674225) a_6989586621679674227 

sShowChar :: forall (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowCharSym0 t) t :: Symbol) Source #

type family ShowCommaSpace (a :: Symbol) :: Symbol where ... Source #

Equations

ShowCommaSpace a_6989586621679674218 = Apply (Apply ShowStringSym0 ", ") a_6989586621679674218 

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

Equations

(f :. g) a_6989586621679420075 = Apply (Apply (Apply (Apply Lambda_6989586621679420080Sym0 f) g) a_6989586621679420075) a_6989586621679420075 

(%.) :: forall (t :: TyFun b c -> Type) (t :: TyFun a b -> Type) (t :: a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (.@#@$) t) t) t :: c) infixr 9 Source #

data SomeSing k where Source #

An existentially-quantified singleton. This type is useful when you want a singleton type, but there is no way of knowing, at compile-time, what the type index will be. To make use of this type, you will generally have to use a pattern-match:

foo :: Bool -> ...
foo b = case toSing b of
          SomeSing sb -> {- fancy dependently-typed code with sb -}

An example like the one above may be easier to write using withSomeSing.

Constructors

SomeSing :: Sing (a :: k) -> SomeSing k 

type family Error (str :: k0) :: k where ... Source #

The promotion of error. This version is more poly-kinded for easier use.

sError :: Sing (str :: Symbol) -> a Source #

The singleton for error

data ErrorSym0 (l :: TyFun k06989586621679378680 k6989586621679378681) Source #

Instances
SuppressUnusedWarnings (ErrorSym0 :: TyFun k06989586621679378680 k6989586621679378681 -> *) Source # 
Instance details
type Apply (ErrorSym0 :: TyFun k0 k2 -> *) (l :: k0) Source # 
Instance details
type Apply (ErrorSym0 :: TyFun k0 k2 -> *) (l :: k0) = (Error l :: k2)

type ErrorSym1 (t :: k06989586621679378680) = Error t Source #

type family Undefined :: k where ... Source #

The promotion of undefined.

sUndefined :: a Source #

The singleton for undefined.

data (==@#@$) (l :: TyFun a6989586621679292214 (TyFun a6989586621679292214 Bool -> Type)) Source #

Instances
SuppressUnusedWarnings ((==@#@$) :: TyFun a6989586621679292214 (TyFun a6989586621679292214 Bool -> Type) -> *) Source # 
Instance details
type Apply ((==@#@$) :: TyFun a6989586621679292214 (TyFun a6989586621679292214 Bool -> Type) -> *) (l :: a6989586621679292214) Source # 
Instance details
type Apply ((==@#@$) :: TyFun a6989586621679292214 (TyFun a6989586621679292214 Bool -> Type) -> *) (l :: a6989586621679292214) = (==@#@$$) l

data (l :: a6989586621679292214) ==@#@$$ (l :: TyFun a6989586621679292214 Bool) Source #

Instances
SuppressUnusedWarnings ((==@#@$$) :: a6989586621679292214 -> TyFun a6989586621679292214 Bool -> *) Source # 
Instance details
type Apply ((==@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) Source # 
Instance details
type Apply ((==@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) = l1 == l2

type (==@#@$$$) (t :: a6989586621679292214) (t :: a6989586621679292214) = (==) t t Source #

data (>@#@$) (l :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type)) Source #

Instances
SuppressUnusedWarnings ((>@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) Source # 
Instance details
type Apply ((>@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) (l :: a6989586621679303258) Source # 
Instance details
type Apply ((>@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) (l :: a6989586621679303258) = (>@#@$$) l

data (l :: a6989586621679303258) >@#@$$ (l :: TyFun a6989586621679303258 Bool) Source #

Instances
SuppressUnusedWarnings ((>@#@$$) :: a6989586621679303258 -> TyFun a6989586621679303258 Bool -> *) Source # 
Instance details
type Apply ((>@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) Source # 
Instance details
type Apply ((>@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) = l1 > l2

type (>@#@$$$) (t :: a6989586621679303258) (t :: a6989586621679303258) = (>) t t Source #

type LTSym0 = LT Source #

type EQSym0 = EQ Source #

type GTSym0 = GT Source #

type Tuple0Sym0 = '() Source #

data Tuple2Sym0 (l :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple2Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> Type) -> *) Source # 
Instance details
type Apply (Tuple2Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> Type) -> *) (l :: a3530822107858468865) Source # 
Instance details
type Apply (Tuple2Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> Type) -> *) (l :: a3530822107858468865) = (Tuple2Sym1 l :: TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> *)

data Tuple2Sym1 (l :: a3530822107858468865) (l :: TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866)) Source #

Instances
SuppressUnusedWarnings (Tuple2Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> *) Source # 
Instance details
type Apply (Tuple2Sym1 l1 :: TyFun k1 (k2, k1) -> *) (l2 :: k1) Source # 
Instance details
type Apply (Tuple2Sym1 l1 :: TyFun k1 (k2, k1) -> *) (l2 :: k1) = (,) l1 l2

type Tuple2Sym2 (t :: a3530822107858468865) (t :: b3530822107858468866) = '(t, t) Source #

data Tuple3Sym0 (l :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple3Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple3Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> Type) -> *) (l :: a3530822107858468865) Source # 
Instance details
type Apply (Tuple3Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> Type) -> *) (l :: a3530822107858468865) = (Tuple3Sym1 l :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> *)

data Tuple3Sym1 (l :: a3530822107858468865) (l :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple3Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> *) Source # 
Instance details
type Apply (Tuple3Sym1 l1 :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> *) (l2 :: b3530822107858468866) Source # 
Instance details
type Apply (Tuple3Sym1 l1 :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> *) (l2 :: b3530822107858468866) = (Tuple3Sym2 l1 l2 :: TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> *)

data Tuple3Sym2 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867)) Source #

Instances
SuppressUnusedWarnings (Tuple3Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> *) Source # 
Instance details
type Apply (Tuple3Sym2 l1 l2 :: TyFun k3 (k2, k1, k3) -> *) (l3 :: k3) Source # 
Instance details
type Apply (Tuple3Sym2 l1 l2 :: TyFun k3 (k2, k1, k3) -> *) (l3 :: k3) = (,,) l1 l2 l3

type Tuple3Sym3 (t :: a3530822107858468865) (t :: b3530822107858468866) (t :: c3530822107858468867) = '(t, t, t) Source #

data Tuple4Sym0 (l :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple4Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple4Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> Type) -> *) (l :: a3530822107858468865) Source # 
Instance details
type Apply (Tuple4Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> Type) -> *) (l :: a3530822107858468865) = (Tuple4Sym1 l :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> *)

data Tuple4Sym1 (l :: a3530822107858468865) (l :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple4Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple4Sym1 l1 :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> *) (l2 :: b3530822107858468866) Source # 
Instance details
type Apply (Tuple4Sym1 l1 :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> *) (l2 :: b3530822107858468866) = (Tuple4Sym2 l1 l2 :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> *)

data Tuple4Sym2 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple4Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> *) Source # 
Instance details
type Apply (Tuple4Sym2 l1 l2 :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> *) (l3 :: c3530822107858468867) Source # 
Instance details
type Apply (Tuple4Sym2 l1 l2 :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> *) (l3 :: c3530822107858468867) = (Tuple4Sym3 l1 l2 l3 :: TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> *)

data Tuple4Sym3 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: c3530822107858468867) (l :: TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868)) Source #

Instances
SuppressUnusedWarnings (Tuple4Sym3 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> *) Source # 
Instance details
type Apply (Tuple4Sym3 l1 l2 l3 :: TyFun k4 (k2, k1, k3, k4) -> *) (l4 :: k4) Source # 
Instance details
type Apply (Tuple4Sym3 l1 l2 l3 :: TyFun k4 (k2, k1, k3, k4) -> *) (l4 :: k4) = (,,,) l1 l2 l3 l4

type Tuple4Sym4 (t :: a3530822107858468865) (t :: b3530822107858468866) (t :: c3530822107858468867) (t :: d3530822107858468868) = '(t, t, t, t) Source #

data Tuple5Sym0 (l :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple5Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple5Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> Type) -> *) (l :: a3530822107858468865) Source # 
Instance details
type Apply (Tuple5Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> Type) -> *) (l :: a3530822107858468865) = (Tuple5Sym1 l :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> *)

data Tuple5Sym1 (l :: a3530822107858468865) (l :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple5Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple5Sym1 l1 :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> *) (l2 :: b3530822107858468866) Source # 
Instance details
type Apply (Tuple5Sym1 l1 :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> *) (l2 :: b3530822107858468866) = (Tuple5Sym2 l1 l2 :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> *)

data Tuple5Sym2 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple5Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple5Sym2 l1 l2 :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> *) (l3 :: c3530822107858468867) Source # 
Instance details
type Apply (Tuple5Sym2 l1 l2 :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> *) (l3 :: c3530822107858468867) = (Tuple5Sym3 l1 l2 l3 :: TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> *)

data Tuple5Sym3 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: c3530822107858468867) (l :: TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple5Sym3 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> *) Source # 
Instance details
type Apply (Tuple5Sym3 l1 l2 l3 :: TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> *) (l4 :: d3530822107858468868) Source # 
Instance details
type Apply (Tuple5Sym3 l1 l2 l3 :: TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> *) (l4 :: d3530822107858468868) = (Tuple5Sym4 l1 l2 l3 l4 :: TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> *)

data Tuple5Sym4 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: c3530822107858468867) (l :: d3530822107858468868) (l :: TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869)) Source #

Instances
SuppressUnusedWarnings (Tuple5Sym4 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> *) Source # 
Instance details
type Apply (Tuple5Sym4 l1 l2 l3 l4 :: TyFun k5 (k2, k1, k3, k4, k5) -> *) (l5 :: k5) Source # 
Instance details
type Apply (Tuple5Sym4 l1 l2 l3 l4 :: TyFun k5 (k2, k1, k3, k4, k5) -> *) (l5 :: k5) = (,,,,) l1 l2 l3 l4 l5

type Tuple5Sym5 (t :: a3530822107858468865) (t :: b3530822107858468866) (t :: c3530822107858468867) (t :: d3530822107858468868) (t :: e3530822107858468869) = '(t, t, t, t, t) Source #

data Tuple6Sym0 (l :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple6Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple6Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: a3530822107858468865) Source # 
Instance details
type Apply (Tuple6Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: a3530822107858468865) = (Tuple6Sym1 l :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> *)

data Tuple6Sym1 (l :: a3530822107858468865) (l :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple6Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple6Sym1 l1 :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: b3530822107858468866) Source # 
Instance details
type Apply (Tuple6Sym1 l1 :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: b3530822107858468866) = (Tuple6Sym2 l1 l2 :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> *)

data Tuple6Sym2 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple6Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple6Sym2 l1 l2 :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> *) (l3 :: c3530822107858468867) Source # 
Instance details
type Apply (Tuple6Sym2 l1 l2 :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> *) (l3 :: c3530822107858468867) = (Tuple6Sym3 l1 l2 l3 :: TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> *)

data Tuple6Sym3 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: c3530822107858468867) (l :: TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple6Sym3 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple6Sym3 l1 l2 l3 :: TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> *) (l4 :: d3530822107858468868) Source # 
Instance details
type Apply (Tuple6Sym3 l1 l2 l3 :: TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> *) (l4 :: d3530822107858468868) = (Tuple6Sym4 l1 l2 l3 l4 :: TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> *)

data Tuple6Sym4 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: c3530822107858468867) (l :: d3530822107858468868) (l :: TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple6Sym4 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> *) Source # 
Instance details
type Apply (Tuple6Sym4 l1 l2 l3 l4 :: TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> *) (l5 :: e3530822107858468869) Source # 
Instance details
type Apply (Tuple6Sym4 l1 l2 l3 l4 :: TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> *) (l5 :: e3530822107858468869) = (Tuple6Sym5 l1 l2 l3 l4 l5 :: TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> *)

data Tuple6Sym5 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: c3530822107858468867) (l :: d3530822107858468868) (l :: e3530822107858468869) (l :: TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870)) Source #

Instances
SuppressUnusedWarnings (Tuple6Sym5 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> e3530822107858468869 -> TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> *) Source # 
Instance details
type Apply (Tuple6Sym5 l1 l2 l3 l4 l5 :: TyFun k6 (k2, k1, k3, k4, k5, k6) -> *) (l6 :: k6) Source # 
Instance details
type Apply (Tuple6Sym5 l1 l2 l3 l4 l5 :: TyFun k6 (k2, k1, k3, k4, k5, k6) -> *) (l6 :: k6) = (,,,,,) l1 l2 l3 l4 l5 l6

type Tuple6Sym6 (t :: a3530822107858468865) (t :: b3530822107858468866) (t :: c3530822107858468867) (t :: d3530822107858468868) (t :: e3530822107858468869) (t :: f3530822107858468870) = '(t, t, t, t, t, t) Source #

data Tuple7Sym0 (l :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple7Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple7Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: a3530822107858468865) Source # 
Instance details
type Apply (Tuple7Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: a3530822107858468865) = (Tuple7Sym1 l :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> *)

data Tuple7Sym1 (l :: a3530822107858468865) (l :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple7Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple7Sym1 l1 :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: b3530822107858468866) Source # 
Instance details
type Apply (Tuple7Sym1 l1 :: TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: b3530822107858468866) = (Tuple7Sym2 l1 l2 :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> *)

data Tuple7Sym2 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple7Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple7Sym2 l1 l2 :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> *) (l3 :: c3530822107858468867) Source # 
Instance details
type Apply (Tuple7Sym2 l1 l2 :: TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> *) (l3 :: c3530822107858468867) = (Tuple7Sym3 l1 l2 l3 :: TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> *)

data Tuple7Sym3 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: c3530822107858468867) (l :: TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple7Sym3 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple7Sym3 l1 l2 l3 :: TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> *) (l4 :: d3530822107858468868) Source # 
Instance details
type Apply (Tuple7Sym3 l1 l2 l3 :: TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> *) (l4 :: d3530822107858468868) = (Tuple7Sym4 l1 l2 l3 l4 :: TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> *)

data Tuple7Sym4 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: c3530822107858468867) (l :: d3530822107858468868) (l :: TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple7Sym4 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> *) Source # 
Instance details
type Apply (Tuple7Sym4 l1 l2 l3 l4 :: TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> *) (l5 :: e3530822107858468869) Source # 
Instance details
type Apply (Tuple7Sym4 l1 l2 l3 l4 :: TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> *) (l5 :: e3530822107858468869) = (Tuple7Sym5 l1 l2 l3 l4 l5 :: TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> *)

data Tuple7Sym5 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: c3530822107858468867) (l :: d3530822107858468868) (l :: e3530822107858468869) (l :: TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type)) Source #

Instances
SuppressUnusedWarnings (Tuple7Sym5 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> e3530822107858468869 -> TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> *) Source # 
Instance details
type Apply (Tuple7Sym5 l1 l2 l3 l4 l5 :: TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> *) (l6 :: f3530822107858468870) Source # 
Instance details
type Apply (Tuple7Sym5 l1 l2 l3 l4 l5 :: TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> *) (l6 :: f3530822107858468870) = (Tuple7Sym6 l1 l2 l3 l4 l5 l6 :: TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> *)

data Tuple7Sym6 (l :: a3530822107858468865) (l :: b3530822107858468866) (l :: c3530822107858468867) (l :: d3530822107858468868) (l :: e3530822107858468869) (l :: f3530822107858468870) (l :: TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871)) Source #

Instances
SuppressUnusedWarnings (Tuple7Sym6 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> e3530822107858468869 -> f3530822107858468870 -> TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> *) Source # 
Instance details
type Apply (Tuple7Sym6 l1 l2 l3 l4 l5 l6 :: TyFun k7 (k2, k1, k3, k4, k5, k6, k7) -> *) (l7 :: k7) Source # 
Instance details
type Apply (Tuple7Sym6 l1 l2 l3 l4 l5 l6 :: TyFun k7 (k2, k1, k3, k4, k5, k6, k7) -> *) (l7 :: k7) = (,,,,,,) l1 l2 l3 l4 l5 l6 l7

type Tuple7Sym7 (t :: a3530822107858468865) (t :: b3530822107858468866) (t :: c3530822107858468867) (t :: d3530822107858468868) (t :: e3530822107858468869) (t :: f3530822107858468870) (t :: g3530822107858468871) = '(t, t, t, t, t, t, t) Source #

data CompareSym0 (l :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Ordering -> Type)) Source #

Instances
SuppressUnusedWarnings (CompareSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Ordering -> Type) -> *) Source # 
Instance details
type Apply (CompareSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Ordering -> Type) -> *) (l :: a6989586621679303258) Source # 
Instance details
type Apply (CompareSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Ordering -> Type) -> *) (l :: a6989586621679303258) = CompareSym1 l

data CompareSym1 (l :: a6989586621679303258) (l :: TyFun a6989586621679303258 Ordering) Source #

Instances
SuppressUnusedWarnings (CompareSym1 :: a6989586621679303258 -> TyFun a6989586621679303258 Ordering -> *) Source # 
Instance details
type Apply (CompareSym1 l1 :: TyFun a Ordering -> *) (l2 :: a) Source # 
Instance details
type Apply (CompareSym1 l1 :: TyFun a Ordering -> *) (l2 :: a) = Compare l1 l2

type CompareSym2 (t :: a6989586621679303258) (t :: a6989586621679303258) = Compare t t Source #

data ThenCmpSym1 (l :: Ordering) (l :: TyFun Ordering Ordering) Source #

Instances
SuppressUnusedWarnings ThenCmpSym1 Source # 
Instance details
type Apply (ThenCmpSym1 l1 :: TyFun Ordering Ordering -> *) (l2 :: Ordering) Source # 
Instance details
type Apply (ThenCmpSym1 l1 :: TyFun Ordering Ordering -> *) (l2 :: Ordering) = ThenCmp l1 l2

type ThenCmpSym2 (t :: Ordering) (t :: Ordering) = ThenCmp t t Source #

data FoldlSym0 (l :: TyFun (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (FoldlSym0 :: TyFun (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> Type) -> *) Source # 
Instance details
type Apply (FoldlSym0 :: TyFun (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> Type) -> *) (l :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) Source # 
Instance details
type Apply (FoldlSym0 :: TyFun (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> Type) -> *) (l :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) = FoldlSym1 l

data FoldlSym1 (l :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (l :: TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type)) Source #

Instances
SuppressUnusedWarnings (FoldlSym1 :: (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) -> TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> *) Source # 
Instance details
type Apply (FoldlSym1 l1 :: TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> *) (l2 :: b6989586621679259259) Source # 
Instance details
type Apply (FoldlSym1 l1 :: TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> *) (l2 :: b6989586621679259259) = FoldlSym2 l1 l2

data FoldlSym2 (l :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (l :: b6989586621679259259) (l :: TyFun [a6989586621679259258] b6989586621679259259) Source #

Instances
SuppressUnusedWarnings (FoldlSym2 :: (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) -> b6989586621679259259 -> TyFun [a6989586621679259258] b6989586621679259259 -> *) Source # 
Instance details
type Apply (FoldlSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) Source # 
Instance details
type Apply (FoldlSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) = Foldl l1 l2 l3

type FoldlSym3 (t :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (t :: b6989586621679259259) (t :: [a6989586621679259258]) = Foldl t t t Source #

data ShowsPrecSym0 (l :: TyFun Nat (TyFun a6989586621679672338 (TyFun Symbol Symbol -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ShowsPrecSym0 :: TyFun Nat (TyFun a6989586621679672338 (TyFun Symbol Symbol -> Type) -> Type) -> *) Source # 
Instance details
type Apply (ShowsPrecSym0 :: TyFun Nat (TyFun a6989586621679672338 (TyFun Symbol Symbol -> Type) -> Type) -> *) (l :: Nat) Source # 
Instance details
type Apply (ShowsPrecSym0 :: TyFun Nat (TyFun a6989586621679672338 (TyFun Symbol Symbol -> Type) -> Type) -> *) (l :: Nat) = (ShowsPrecSym1 l :: TyFun a6989586621679672338 (TyFun Symbol Symbol -> Type) -> *)

data ShowsPrecSym1 (l :: Nat) (l :: TyFun a6989586621679672338 (TyFun Symbol Symbol -> Type)) Source #

Instances
SuppressUnusedWarnings (ShowsPrecSym1 :: Nat -> TyFun a6989586621679672338 (TyFun Symbol Symbol -> Type) -> *) Source # 
Instance details
type Apply (ShowsPrecSym1 l1 :: TyFun a6989586621679672338 (TyFun Symbol Symbol -> Type) -> *) (l2 :: a6989586621679672338) Source # 
Instance details
type Apply (ShowsPrecSym1 l1 :: TyFun a6989586621679672338 (TyFun Symbol Symbol -> Type) -> *) (l2 :: a6989586621679672338) = ShowsPrecSym2 l1 l2

data ShowsPrecSym2 (l :: Nat) (l :: a6989586621679672338) (l :: TyFun Symbol Symbol) Source #

Instances
SuppressUnusedWarnings (ShowsPrecSym2 :: Nat -> a6989586621679672338 -> TyFun Symbol Symbol -> *) Source # 
Instance details
type Apply (ShowsPrecSym2 l1 l2 :: TyFun Symbol Symbol -> *) (l3 :: Symbol) Source # 
Instance details
type Apply (ShowsPrecSym2 l1 l2 :: TyFun Symbol Symbol -> *) (l3 :: Symbol) = ShowsPrec l1 l2 l3

type ShowsPrecSym3 (t :: Nat) (t :: a6989586621679672338) (t :: Symbol) = ShowsPrec t t t Source #

data ShowStringSym1 (l :: Symbol) (l :: TyFun Symbol Symbol) Source #

Instances
SuppressUnusedWarnings ShowStringSym1 Source # 
Instance details
type Apply (ShowStringSym1 l1 :: TyFun Symbol Symbol -> *) (l2 :: Symbol) Source # 
Instance details
type Apply (ShowStringSym1 l1 :: TyFun Symbol Symbol -> *) (l2 :: Symbol) = ShowString l1 l2

type ShowStringSym2 (t :: Symbol) (t :: Symbol) = ShowString t t Source #

data ShowParenSym2 (l :: Bool) (l :: TyFun Symbol Symbol -> Type) (l :: TyFun Symbol Symbol) Source #

Instances
SuppressUnusedWarnings ShowParenSym2 Source # 
Instance details
type Apply (ShowParenSym2 l1 l2 :: TyFun Symbol Symbol -> *) (l3 :: Symbol) Source # 
Instance details
type Apply (ShowParenSym2 l1 l2 :: TyFun Symbol Symbol -> *) (l3 :: Symbol) = ShowParen l1 l2 l3

data ShowSpaceSym0 (l :: TyFun Symbol Symbol) Source #

Instances
SuppressUnusedWarnings ShowSpaceSym0 Source # 
Instance details
type Apply ShowSpaceSym0 (l :: Symbol) Source # 
Instance details

data ShowCharSym0 (l :: TyFun Symbol (TyFun Symbol Symbol -> Type)) Source #

Instances
SuppressUnusedWarnings ShowCharSym0 Source # 
Instance details
type Apply ShowCharSym0 (l :: Symbol) Source # 
Instance details

data ShowCharSym1 (l :: Symbol) (l :: TyFun Symbol Symbol) Source #

Instances
SuppressUnusedWarnings ShowCharSym1 Source # 
Instance details
type Apply (ShowCharSym1 l1 :: TyFun Symbol Symbol -> *) (l2 :: Symbol) Source # 
Instance details
type Apply (ShowCharSym1 l1 :: TyFun Symbol Symbol -> *) (l2 :: Symbol) = ShowChar l1 l2

type ShowCharSym2 (t :: Symbol) (t :: Symbol) = ShowChar t t Source #

data (.@#@$) (l :: TyFun (TyFun b6989586621679419898 c6989586621679419899 -> Type) (TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings ((.@#@$) :: TyFun (TyFun b6989586621679419898 c6989586621679419899 -> Type) (TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> Type) -> *) Source # 
Instance details
type Apply ((.@#@$) :: TyFun (TyFun b6989586621679419898 c6989586621679419899 -> Type) (TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> Type) -> *) (l :: TyFun b6989586621679419898 c6989586621679419899 -> Type) Source # 
Instance details
type Apply ((.@#@$) :: TyFun (TyFun b6989586621679419898 c6989586621679419899 -> Type) (TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> Type) -> *) (l :: TyFun b6989586621679419898 c6989586621679419899 -> Type) = ((.@#@$$) l :: TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> *)

data (l :: TyFun b6989586621679419898 c6989586621679419899 -> Type) .@#@$$ (l :: TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type)) Source #

Instances
SuppressUnusedWarnings ((.@#@$$) :: (TyFun b6989586621679419898 c6989586621679419899 -> Type) -> TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> *) Source # 
Instance details
type Apply ((.@#@$$) l1 :: TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> *) (l2 :: TyFun a6989586621679419900 b6989586621679419898 -> Type) Source # 
Instance details
type Apply ((.@#@$$) l1 :: TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> *) (l2 :: TyFun a6989586621679419900 b6989586621679419898 -> Type) = l1 .@#@$$$ l2

data ((l :: TyFun b6989586621679419898 c6989586621679419899 -> Type) .@#@$$$ (l :: TyFun a6989586621679419900 b6989586621679419898 -> Type)) (l :: TyFun a6989586621679419900 c6989586621679419899) Source #

Instances
SuppressUnusedWarnings ((.@#@$$$) :: (TyFun b6989586621679419898 c6989586621679419899 -> Type) -> (TyFun a6989586621679419900 b6989586621679419898 -> Type) -> TyFun a6989586621679419900 c6989586621679419899 -> *) Source # 
Instance details
type Apply (l1 .@#@$$$ l2 :: TyFun a c -> *) (l3 :: a) Source # 
Instance details
type Apply (l1 .@#@$$$ l2 :: TyFun a c -> *) (l3 :: a) = (l1 :. l2) l3

type (.@#@$$$$) (t :: TyFun b6989586621679419898 c6989586621679419899 -> Type) (t :: TyFun a6989586621679419900 b6989586621679419898 -> Type) (t :: a6989586621679419900) = (:.) t t t Source #

data (:@#@$) (l :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type)) Source #

Instances
SuppressUnusedWarnings ((:@#@$) :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type) -> *) Source # 
Instance details
type Apply ((:@#@$) :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type) -> *) (l :: a3530822107858468865) Source # 
Instance details
type Apply ((:@#@$) :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type) -> *) (l :: a3530822107858468865) = (:@#@$$) l

data (l :: a3530822107858468865) :@#@$$ (l :: TyFun [a3530822107858468865] [a3530822107858468865]) Source #

Instances
SuppressUnusedWarnings ((:@#@$$) :: a3530822107858468865 -> TyFun [a3530822107858468865] [a3530822107858468865] -> *) Source # 
Instance details
type Apply ((:@#@$$) l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details
type Apply ((:@#@$$) l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = l1 ': l2

type (:@#@$$$) (t :: a3530822107858468865) (t :: [a3530822107858468865]) = (:) t t Source #

class SuppressUnusedWarnings (t :: k) where Source #

This class (which users should never see) is to be instantiated in order to use an otherwise-unused data constructor, such as the "kind-inference" data constructor for defunctionalization symbols.

Minimal complete definition

suppressUnusedWarnings

Instances
SuppressUnusedWarnings ShowParenSym2 Source # 
Instance details
SuppressUnusedWarnings (&&@#@$$) Source # 
Instance details
SuppressUnusedWarnings (||@#@$$) Source # 
Instance details
SuppressUnusedWarnings ShowParenSym1 Source # 
Instance details
SuppressUnusedWarnings ThenCmpSym1 Source # 
Instance details
SuppressUnusedWarnings (~>@#@$$) Source # 
Instance details
SuppressUnusedWarnings (^@#@$$) Source # 
Instance details
SuppressUnusedWarnings DivSym1 Source # 
Instance details
SuppressUnusedWarnings ModSym1 Source # 
Instance details
SuppressUnusedWarnings QuotSym1 Source # 
Instance details
SuppressUnusedWarnings RemSym1 Source # 
Instance details
SuppressUnusedWarnings QuotRemSym1 Source # 
Instance details
SuppressUnusedWarnings DivModSym1 Source # 
Instance details
SuppressUnusedWarnings (<>@#@$$) Source # 
Instance details
SuppressUnusedWarnings ShowCharSym1 Source # 
Instance details
SuppressUnusedWarnings ShowStringSym1 Source # 
Instance details
SuppressUnusedWarnings NotSym0 Source # 
Instance details
SuppressUnusedWarnings (&&@#@$) Source # 
Instance details
SuppressUnusedWarnings (||@#@$) Source # 
Instance details
SuppressUnusedWarnings ShowParenSym0 Source # 
Instance details
SuppressUnusedWarnings AndSym0 Source # 
Instance details
SuppressUnusedWarnings OrSym0 Source # 
Instance details
SuppressUnusedWarnings UnlinesSym0 Source # 
Instance details
SuppressUnusedWarnings UnwordsSym0 Source # 
Instance details
SuppressUnusedWarnings ThenCmpSym0 Source # 
Instance details
SuppressUnusedWarnings (~>@#@$) Source # 
Instance details
SuppressUnusedWarnings DemoteSym0 Source # 
Instance details
SuppressUnusedWarnings (^@#@$) Source # 
Instance details
SuppressUnusedWarnings DivSym0 Source # 
Instance details
SuppressUnusedWarnings ModSym0 Source # 
Instance details
SuppressUnusedWarnings QuotSym0 Source # 
Instance details
SuppressUnusedWarnings RemSym0 Source # 
Instance details
SuppressUnusedWarnings QuotRemSym0 Source # 
Instance details
SuppressUnusedWarnings DivModSym0 Source # 
Instance details
SuppressUnusedWarnings KnownNatSym0 Source # 
Instance details
SuppressUnusedWarnings Log2Sym0 Source # 
Instance details
SuppressUnusedWarnings ShowCharSym0 Source # 
Instance details
SuppressUnusedWarnings ShowStringSym0 Source # 
Instance details
SuppressUnusedWarnings (<>@#@$) Source # 
Instance details
SuppressUnusedWarnings KnownSymbolSym0 Source # 
Instance details
SuppressUnusedWarnings ShowCommaSpaceSym0 Source # 
Instance details
SuppressUnusedWarnings ShowSpaceSym0 Source # 
Instance details
SuppressUnusedWarnings XorSym0 Source # 
Instance details
SuppressUnusedWarnings (NubBySym1 :: (TyFun a6989586621679442418 (TyFun a6989586621679442418 Bool -> Type) -> Type) -> TyFun [a6989586621679442418] [a6989586621679442418] -> *) Source # 
Instance details
SuppressUnusedWarnings (PartitionSym1 :: (TyFun a6989586621679442427 Bool -> Type) -> TyFun [a6989586621679442427] ([a6989586621679442427], [a6989586621679442427]) -> *) Source # 
Instance details
SuppressUnusedWarnings (BreakSym1 :: (TyFun a6989586621679442439 Bool -> Type) -> TyFun [a6989586621679442439] ([a6989586621679442439], [a6989586621679442439]) -> *) Source # 
Instance details
SuppressUnusedWarnings (SpanSym1 :: (TyFun a6989586621679442440 Bool -> Type) -> TyFun [a6989586621679442440] ([a6989586621679442440], [a6989586621679442440]) -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupBySym1 :: (TyFun a6989586621679442430 (TyFun a6989586621679442430 Bool -> Type) -> Type) -> TyFun [a6989586621679442430] [[a6989586621679442430]] -> *) Source # 
Instance details
SuppressUnusedWarnings (DropWhileSym1 :: (TyFun a6989586621679442442 Bool -> Type) -> TyFun [a6989586621679442442] [a6989586621679442442] -> *) Source # 
Instance details
SuppressUnusedWarnings (TakeWhileSym1 :: (TyFun a6989586621679442443 Bool -> Type) -> TyFun [a6989586621679442443] [a6989586621679442443] -> *) Source # 
Instance details
SuppressUnusedWarnings (FilterSym1 :: (TyFun a6989586621679442451 Bool -> Type) -> TyFun [a6989586621679442451] [a6989586621679442451] -> *) Source # 
Instance details
SuppressUnusedWarnings (FindSym1 :: (TyFun a6989586621679442450 Bool -> Type) -> TyFun [a6989586621679442450] (Maybe a6989586621679442450) -> *) Source # 
Instance details
SuppressUnusedWarnings (InsertBySym1 :: (TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) -> TyFun a6989586621679442454 (TyFun [a6989586621679442454] [a6989586621679442454] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (InsertBySym2 :: (TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) -> a6989586621679442454 -> TyFun [a6989586621679442454] [a6989586621679442454] -> *) Source # 
Instance details
SuppressUnusedWarnings (SortBySym1 :: (TyFun a6989586621679442455 (TyFun a6989586621679442455 Ordering -> Type) -> Type) -> TyFun [a6989586621679442455] [a6989586621679442455] -> *) Source # 
Instance details
SuppressUnusedWarnings (DeleteBySym1 :: (TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) -> TyFun a6989586621679442457 (TyFun [a6989586621679442457] [a6989586621679442457] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (DeleteBySym2 :: (TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) -> a6989586621679442457 -> TyFun [a6989586621679442457] [a6989586621679442457] -> *) Source # 
Instance details
SuppressUnusedWarnings (DeleteFirstsBySym2 :: (TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) -> [a6989586621679442456] -> TyFun [a6989586621679442456] [a6989586621679442456] -> *) Source # 
Instance details
SuppressUnusedWarnings (DeleteFirstsBySym1 :: (TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) -> TyFun [a6989586621679442456] (TyFun [a6989586621679442456] [a6989586621679442456] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (UnionBySym2 :: (TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) -> [a6989586621679442416] -> TyFun [a6989586621679442416] [a6989586621679442416] -> *) Source # 
Instance details
SuppressUnusedWarnings (UnionBySym1 :: (TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) -> TyFun [a6989586621679442416] (TyFun [a6989586621679442416] [a6989586621679442416] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (FindIndicesSym1 :: (TyFun a6989586621679442446 Bool -> Type) -> TyFun [a6989586621679442446] [Nat] -> *) Source # 
Instance details
SuppressUnusedWarnings (FindIndexSym1 :: (TyFun a6989586621679442447 Bool -> Type) -> TyFun [a6989586621679442447] (Maybe Nat) -> *) Source # 
Instance details
SuppressUnusedWarnings (Scanr1Sym1 :: (TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) -> TyFun [a6989586621679442514] [a6989586621679442514] -> *) Source # 
Instance details
SuppressUnusedWarnings (Scanl1Sym1 :: (TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) -> TyFun [a6989586621679442517] [a6989586621679442517] -> *) Source # 
Instance details
SuppressUnusedWarnings (AnySym1 :: (TyFun a6989586621679442520 Bool -> Type) -> TyFun [a6989586621679442520] Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (IntersectBySym2 :: (TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) -> [a6989586621679442444] -> TyFun [a6989586621679442444] [a6989586621679442444] -> *) Source # 
Instance details
SuppressUnusedWarnings (IntersectBySym1 :: (TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) -> TyFun [a6989586621679442444] (TyFun [a6989586621679442444] [a6989586621679442444] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (AllSym1 :: (TyFun a6989586621679442521 Bool -> Type) -> TyFun [a6989586621679442521] Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (Foldr1Sym1 :: (TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) -> TyFun [a6989586621679442525] a6989586621679442525 -> *) Source # 
Instance details
SuppressUnusedWarnings (Foldl1Sym1 :: (TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) -> TyFun [a6989586621679442527] a6989586621679442527 -> *) Source # 
Instance details
SuppressUnusedWarnings (MaximumBySym1 :: (TyFun a6989586621679442453 (TyFun a6989586621679442453 Ordering -> Type) -> Type) -> TyFun [a6989586621679442453] a6989586621679442453 -> *) Source # 
Instance details
SuppressUnusedWarnings (MinimumBySym1 :: (TyFun a6989586621679442452 (TyFun a6989586621679442452 Ordering -> Type) -> Type) -> TyFun [a6989586621679442452] a6989586621679442452 -> *) Source # 
Instance details
SuppressUnusedWarnings (Foldl1'Sym1 :: (TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) -> TyFun [a6989586621679442526] a6989586621679442526 -> *) Source # 
Instance details
SuppressUnusedWarnings (DropWhileEndSym1 :: (TyFun a6989586621679442441 Bool -> Type) -> TyFun [a6989586621679442441] [a6989586621679442441] -> *) Source # 
Instance details
SuppressUnusedWarnings (ShowListWithSym2 :: (TyFun a6989586621679672322 (TyFun Symbol Symbol -> Type) -> Type) -> [a6989586621679672322] -> TyFun Symbol Symbol -> *) Source # 
Instance details
SuppressUnusedWarnings (ShowListWithSym1 :: (TyFun a6989586621679672322 (TyFun Symbol Symbol -> Type) -> Type) -> TyFun [a6989586621679672322] (TyFun Symbol Symbol -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (NubBySym1 :: (TyFun a6989586621679768146 (TyFun a6989586621679768146 Bool -> Type) -> Type) -> TyFun (NonEmpty a6989586621679768146) (NonEmpty a6989586621679768146) -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupBySym1 :: (TyFun a6989586621679768167 (TyFun a6989586621679768167 Bool -> Type) -> Type) -> TyFun [a6989586621679768167] [NonEmpty a6989586621679768167] -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupBy1Sym1 :: (TyFun a6989586621679768161 (TyFun a6989586621679768161 Bool -> Type) -> Type) -> TyFun (NonEmpty a6989586621679768161) (NonEmpty (NonEmpty a6989586621679768161)) -> *) Source # 
Instance details
SuppressUnusedWarnings (TakeWhileSym1 :: (TyFun a6989586621679768174 Bool -> Type) -> TyFun (NonEmpty a6989586621679768174) [a6989586621679768174] -> *) Source # 
Instance details
SuppressUnusedWarnings (DropWhileSym1 :: (TyFun a6989586621679768173 Bool -> Type) -> TyFun (NonEmpty a6989586621679768173) [a6989586621679768173] -> *) Source # 
Instance details
SuppressUnusedWarnings (SpanSym1 :: (TyFun a6989586621679768172 Bool -> Type) -> TyFun (NonEmpty a6989586621679768172) ([a6989586621679768172], [a6989586621679768172]) -> *) Source # 
Instance details
SuppressUnusedWarnings (BreakSym1 :: (TyFun a6989586621679768171 Bool -> Type) -> TyFun (NonEmpty a6989586621679768171) ([a6989586621679768171], [a6989586621679768171]) -> *) Source # 
Instance details
SuppressUnusedWarnings (FilterSym1 :: (TyFun a6989586621679768170 Bool -> Type) -> TyFun (NonEmpty a6989586621679768170) [a6989586621679768170] -> *) Source # 
Instance details
SuppressUnusedWarnings (PartitionSym1 :: (TyFun a6989586621679768169 Bool -> Type) -> TyFun (NonEmpty a6989586621679768169) ([a6989586621679768169], [a6989586621679768169]) -> *) Source # 
Instance details
SuppressUnusedWarnings (SortBySym1 :: (TyFun a6989586621679768144 (TyFun a6989586621679768144 Ordering -> Type) -> Type) -> TyFun (NonEmpty a6989586621679768144) (NonEmpty a6989586621679768144) -> *) Source # 
Instance details
SuppressUnusedWarnings (Scanl1Sym1 :: (TyFun a6989586621679768181 (TyFun a6989586621679768181 a6989586621679768181 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679768181) (NonEmpty a6989586621679768181) -> *) Source # 
Instance details
SuppressUnusedWarnings (Scanr1Sym1 :: (TyFun a6989586621679768180 (TyFun a6989586621679768180 a6989586621679768180 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679768180) (NonEmpty a6989586621679768180) -> *) Source # 
Instance details
SuppressUnusedWarnings (UntilSym2 :: (TyFun a6989586621679958924 Bool -> Type) -> (TyFun a6989586621679958924 a6989586621679958924 -> Type) -> TyFun a6989586621679958924 a6989586621679958924 -> *) Source # 
Instance details
SuppressUnusedWarnings (UntilSym1 :: (TyFun a6989586621679958924 Bool -> Type) -> TyFun (TyFun a6989586621679958924 a6989586621679958924 -> Type) (TyFun a6989586621679958924 a6989586621679958924 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((++@#@$$) :: [a6989586621679419904] -> TyFun [a6989586621679419904] [a6989586621679419904] -> *) Source # 
Instance details
SuppressUnusedWarnings ((!!@#@$$) :: [a6989586621679442420] -> TyFun Nat a6989586621679442420 -> *) Source # 
Instance details
SuppressUnusedWarnings (UnionSym1 :: [a6989586621679442415] -> TyFun [a6989586621679442415] [a6989586621679442415] -> *) Source # 
Instance details
SuppressUnusedWarnings ((\\@#@$$) :: [a6989586621679442458] -> TyFun [a6989586621679442458] [a6989586621679442458] -> *) Source # 
Instance details
SuppressUnusedWarnings (IsPrefixOfSym1 :: [a6989586621679442503] -> TyFun [a6989586621679442503] Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (IsInfixOfSym1 :: [a6989586621679442501] -> TyFun [a6989586621679442501] Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (IntersectSym1 :: [a6989586621679442445] -> TyFun [a6989586621679442445] [a6989586621679442445] -> *) Source # 
Instance details
SuppressUnusedWarnings (IntercalateSym1 :: [a6989586621679442534] -> TyFun [[a6989586621679442534]] [a6989586621679442534] -> *) Source # 
Instance details
SuppressUnusedWarnings (IsSuffixOfSym1 :: [a6989586621679442502] -> TyFun [a6989586621679442502] Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (ShowListSym1 :: [a6989586621679672338] -> TyFun Symbol Symbol -> *) Source # 
Instance details
SuppressUnusedWarnings (IsPrefixOfSym1 :: [a6989586621679768156] -> TyFun (NonEmpty a6989586621679768156) Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (StripPrefixSym1 :: [a6989586621679922315] -> TyFun [a6989586621679922315] (Maybe [a6989586621679922315]) -> *) Source # 
Instance details
SuppressUnusedWarnings (ShowsPrecSym2 :: Nat -> a6989586621679672338 -> TyFun Symbol Symbol -> *) Source # 
Instance details
SuppressUnusedWarnings (DropSym1 :: Nat -> TyFun [a6989586621679442437] [a6989586621679442437] -> *) Source # 
Instance details
SuppressUnusedWarnings (TakeSym1 :: Nat -> TyFun [a6989586621679442438] [a6989586621679442438] -> *) Source # 
Instance details
SuppressUnusedWarnings (SplitAtSym1 :: Nat -> TyFun [a6989586621679442436] ([a6989586621679442436], [a6989586621679442436]) -> *) Source # 
Instance details
SuppressUnusedWarnings (ReplicateSym1 :: Nat -> TyFun a6989586621679442422 [a6989586621679442422] -> *) Source # 
Instance details
SuppressUnusedWarnings (ShowsPrecSym1 :: Nat -> TyFun a6989586621679672338 (TyFun Symbol Symbol -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (TakeSym1 :: Nat -> TyFun (NonEmpty a6989586621679768177) [a6989586621679768177] -> *) Source # 
Instance details
SuppressUnusedWarnings (DropSym1 :: Nat -> TyFun (NonEmpty a6989586621679768176) [a6989586621679768176] -> *) Source # 
Instance details
SuppressUnusedWarnings (SplitAtSym1 :: Nat -> TyFun (NonEmpty a6989586621679768175) ([a6989586621679768175], [a6989586621679768175]) -> *) Source # 
Instance details
SuppressUnusedWarnings ((:@#@$$) :: a3530822107858468865 -> TyFun [a3530822107858468865] [a3530822107858468865] -> *) Source # 
Instance details
SuppressUnusedWarnings ((:|@#@$$) :: a6989586621679067178 -> TyFun [a6989586621679067178] (NonEmpty a6989586621679067178) -> *) Source # 
Instance details
SuppressUnusedWarnings (Bool_Sym2 :: a6989586621679289682 -> a6989586621679289682 -> TyFun Bool a6989586621679289682 -> *) Source # 
Instance details
SuppressUnusedWarnings (Bool_Sym1 :: a6989586621679289682 -> TyFun a6989586621679289682 (TyFun Bool a6989586621679289682 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((==@#@$$) :: a6989586621679292214 -> TyFun a6989586621679292214 Bool -> *) Source # 
Instance details
SuppressUnusedWarnings ((/=@#@$$) :: a6989586621679292214 -> TyFun a6989586621679292214 Bool -> *) Source # 
Instance details
SuppressUnusedWarnings ((<=@#@$$) :: a6989586621679303258 -> TyFun a6989586621679303258 Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (CompareSym1 :: a6989586621679303258 -> TyFun a6989586621679303258 Ordering -> *) Source # 
Instance details
SuppressUnusedWarnings (MinSym1 :: a6989586621679303258 -> TyFun a6989586621679303258 a6989586621679303258 -> *) Source # 
Instance details
SuppressUnusedWarnings (MaxSym1 :: a6989586621679303258 -> TyFun a6989586621679303258 a6989586621679303258 -> *) Source # 
Instance details
SuppressUnusedWarnings ((>=@#@$$) :: a6989586621679303258 -> TyFun a6989586621679303258 Bool -> *) Source # 
Instance details
SuppressUnusedWarnings ((>@#@$$) :: a6989586621679303258 -> TyFun a6989586621679303258 Bool -> *) Source # 
Instance details
SuppressUnusedWarnings ((<@#@$$) :: a6989586621679303258 -> TyFun a6989586621679303258 Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (FromMaybeSym1 :: a6989586621679404427 -> TyFun (Maybe a6989586621679404427) a6989586621679404427 -> *) Source # 
Instance details
SuppressUnusedWarnings ((-@#@$$) :: a6989586621679412530 -> TyFun a6989586621679412530 a6989586621679412530 -> *) Source # 
Instance details
SuppressUnusedWarnings ((+@#@$$) :: a6989586621679412530 -> TyFun a6989586621679412530 a6989586621679412530 -> *) Source # 
Instance details
SuppressUnusedWarnings ((*@#@$$) :: a6989586621679412530 -> TyFun a6989586621679412530 a6989586621679412530 -> *) Source # 
Instance details
SuppressUnusedWarnings (SubtractSym1 :: a6989586621679414803 -> TyFun a6989586621679414803 a6989586621679414803 -> *) Source # 
Instance details
SuppressUnusedWarnings (AsTypeOfSym1 :: a6989586621679419894 -> TyFun a6989586621679419894 a6989586621679419894 -> *) Source # 
Instance details
SuppressUnusedWarnings (InsertSym1 :: a6989586621679442432 -> TyFun [a6989586621679442432] [a6989586621679442432] -> *) Source # 
Instance details
SuppressUnusedWarnings (DeleteSym1 :: a6989586621679442459 -> TyFun [a6989586621679442459] [a6989586621679442459] -> *) Source # 
Instance details
SuppressUnusedWarnings (ElemIndicesSym1 :: a6989586621679442448 -> TyFun [a6989586621679442448] [Nat] -> *) Source # 
Instance details
SuppressUnusedWarnings (ElemIndexSym1 :: a6989586621679442449 -> TyFun [a6989586621679442449] (Maybe Nat) -> *) Source # 
Instance details
SuppressUnusedWarnings (NotElemSym1 :: a6989586621679442499 -> TyFun [a6989586621679442499] Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (ElemSym1 :: a6989586621679442500 -> TyFun [a6989586621679442500] Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (IntersperseSym1 :: a6989586621679442535 -> TyFun [a6989586621679442535] [a6989586621679442535] -> *) Source # 
Instance details
SuppressUnusedWarnings (ShowsSym1 :: a6989586621679672323 -> TyFun Symbol Symbol -> *) Source # 
Instance details
SuppressUnusedWarnings (IntersperseSym1 :: a6989586621679768179 -> TyFun (NonEmpty a6989586621679768179) (NonEmpty a6989586621679768179) -> *) Source # 
Instance details
SuppressUnusedWarnings (InsertSym1 :: a6989586621679768186 -> TyFun [a6989586621679768186] (NonEmpty a6989586621679768186) -> *) Source # 
Instance details
SuppressUnusedWarnings ((<|@#@$$) :: a6989586621679768197 -> TyFun (NonEmpty a6989586621679768197) (NonEmpty a6989586621679768197) -> *) Source # 
Instance details
SuppressUnusedWarnings (ConsSym1 :: a6989586621679768196 -> TyFun (NonEmpty a6989586621679768196) (NonEmpty a6989586621679768196) -> *) Source # 
Instance details
SuppressUnusedWarnings (EnumFromThenToSym1 :: a6989586621679843221 -> TyFun a6989586621679843221 (TyFun a6989586621679843221 [a6989586621679843221] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (EnumFromThenToSym2 :: a6989586621679843221 -> a6989586621679843221 -> TyFun a6989586621679843221 [a6989586621679843221] -> *) Source # 
Instance details
SuppressUnusedWarnings (EnumFromToSym1 :: a6989586621679843221 -> TyFun a6989586621679843221 [a6989586621679843221] -> *) Source # 
Instance details
SuppressUnusedWarnings (SameKindSym1 :: k6989586621679026622 -> TyFun k6989586621679026622 Constraint -> *) Source # 
Instance details
SuppressUnusedWarnings ((!!@#@$$) :: NonEmpty a6989586621679768155 -> TyFun Nat a6989586621679768155 -> *) Source # 
Instance details
SuppressUnusedWarnings (NubBySym0 :: TyFun (TyFun a6989586621679442418 (TyFun a6989586621679442418 Bool -> Type) -> Type) (TyFun [a6989586621679442418] [a6989586621679442418] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (PartitionSym0 :: TyFun (TyFun a6989586621679442427 Bool -> Type) (TyFun [a6989586621679442427] ([a6989586621679442427], [a6989586621679442427]) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (BreakSym0 :: TyFun (TyFun a6989586621679442439 Bool -> Type) (TyFun [a6989586621679442439] ([a6989586621679442439], [a6989586621679442439]) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (SpanSym0 :: TyFun (TyFun a6989586621679442440 Bool -> Type) (TyFun [a6989586621679442440] ([a6989586621679442440], [a6989586621679442440]) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupBySym0 :: TyFun (TyFun a6989586621679442430 (TyFun a6989586621679442430 Bool -> Type) -> Type) (TyFun [a6989586621679442430] [[a6989586621679442430]] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (DropWhileSym0 :: TyFun (TyFun a6989586621679442442 Bool -> Type) (TyFun [a6989586621679442442] [a6989586621679442442] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (TyFun a6989586621679442443 Bool -> Type) (TyFun [a6989586621679442443] [a6989586621679442443] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (FilterSym0 :: TyFun (TyFun a6989586621679442451 Bool -> Type) (TyFun [a6989586621679442451] [a6989586621679442451] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (FindSym0 :: TyFun (TyFun a6989586621679442450 Bool -> Type) (TyFun [a6989586621679442450] (Maybe a6989586621679442450) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (InsertBySym0 :: TyFun (TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) (TyFun a6989586621679442454 (TyFun [a6989586621679442454] [a6989586621679442454] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (SortBySym0 :: TyFun (TyFun a6989586621679442455 (TyFun a6989586621679442455 Ordering -> Type) -> Type) (TyFun [a6989586621679442455] [a6989586621679442455] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (DeleteBySym0 :: TyFun (TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) (TyFun a6989586621679442457 (TyFun [a6989586621679442457] [a6989586621679442457] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) (TyFun [a6989586621679442456] (TyFun [a6989586621679442456] [a6989586621679442456] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (UnionBySym0 :: TyFun (TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) (TyFun [a6989586621679442416] (TyFun [a6989586621679442416] [a6989586621679442416] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (TyFun a6989586621679442446 Bool -> Type) (TyFun [a6989586621679442446] [Nat] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (FindIndexSym0 :: TyFun (TyFun a6989586621679442447 Bool -> Type) (TyFun [a6989586621679442447] (Maybe Nat) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) (TyFun [a6989586621679442514] [a6989586621679442514] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) (TyFun [a6989586621679442517] [a6989586621679442517] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (AnySym0 :: TyFun (TyFun a6989586621679442520 Bool -> Type) (TyFun [a6989586621679442520] Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (IntersectBySym0 :: TyFun (TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) (TyFun [a6989586621679442444] (TyFun [a6989586621679442444] [a6989586621679442444] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (AllSym0 :: TyFun (TyFun a6989586621679442521 Bool -> Type) (TyFun [a6989586621679442521] Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) (TyFun [a6989586621679442525] a6989586621679442525 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) (TyFun [a6989586621679442527] a6989586621679442527 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MaximumBySym0 :: TyFun (TyFun a6989586621679442453 (TyFun a6989586621679442453 Ordering -> Type) -> Type) (TyFun [a6989586621679442453] a6989586621679442453 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MinimumBySym0 :: TyFun (TyFun a6989586621679442452 (TyFun a6989586621679442452 Ordering -> Type) -> Type) (TyFun [a6989586621679442452] a6989586621679442452 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) (TyFun [a6989586621679442526] a6989586621679442526 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (TyFun a6989586621679442441 Bool -> Type) (TyFun [a6989586621679442441] [a6989586621679442441] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ShowListWithSym0 :: TyFun (TyFun a6989586621679672322 (TyFun Symbol Symbol -> Type) -> Type) (TyFun [a6989586621679672322] (TyFun Symbol Symbol -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (NubBySym0 :: TyFun (TyFun a6989586621679768146 (TyFun a6989586621679768146 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679768146) (NonEmpty a6989586621679768146) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupBySym0 :: TyFun (TyFun a6989586621679768167 (TyFun a6989586621679768167 Bool -> Type) -> Type) (TyFun [a6989586621679768167] [NonEmpty a6989586621679768167] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupBy1Sym0 :: TyFun (TyFun a6989586621679768161 (TyFun a6989586621679768161 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679768161) (NonEmpty (NonEmpty a6989586621679768161)) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (TyFun a6989586621679768174 Bool -> Type) (TyFun (NonEmpty a6989586621679768174) [a6989586621679768174] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (DropWhileSym0 :: TyFun (TyFun a6989586621679768173 Bool -> Type) (TyFun (NonEmpty a6989586621679768173) [a6989586621679768173] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (SpanSym0 :: TyFun (TyFun a6989586621679768172 Bool -> Type) (TyFun (NonEmpty a6989586621679768172) ([a6989586621679768172], [a6989586621679768172]) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (BreakSym0 :: TyFun (TyFun a6989586621679768171 Bool -> Type) (TyFun (NonEmpty a6989586621679768171) ([a6989586621679768171], [a6989586621679768171]) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (FilterSym0 :: TyFun (TyFun a6989586621679768170 Bool -> Type) (TyFun (NonEmpty a6989586621679768170) [a6989586621679768170] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (PartitionSym0 :: TyFun (TyFun a6989586621679768169 Bool -> Type) (TyFun (NonEmpty a6989586621679768169) ([a6989586621679768169], [a6989586621679768169]) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (SortBySym0 :: TyFun (TyFun a6989586621679768144 (TyFun a6989586621679768144 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679768144) (NonEmpty a6989586621679768144) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (TyFun a6989586621679768181 (TyFun a6989586621679768181 a6989586621679768181 -> Type) -> Type) (TyFun (NonEmpty a6989586621679768181) (NonEmpty a6989586621679768181) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (TyFun a6989586621679768180 (TyFun a6989586621679768180 a6989586621679768180 -> Type) -> Type) (TyFun (NonEmpty a6989586621679768180) (NonEmpty a6989586621679768180) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (UntilSym0 :: TyFun (TyFun a6989586621679958924 Bool -> Type) (TyFun (TyFun a6989586621679958924 a6989586621679958924 -> Type) (TyFun a6989586621679958924 a6989586621679958924 -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ConcatSym0 :: TyFun [[a6989586621679442524]] [a6989586621679442524] -> *) Source # 
Instance details
SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a6989586621679442421]] [[a6989586621679442421]] -> *) Source # 
Instance details
SuppressUnusedWarnings (CatMaybesSym0 :: TyFun [Maybe a6989586621679404424] [a6989586621679404424] -> *) Source # 
Instance details
SuppressUnusedWarnings (ListToMaybeSym0 :: TyFun [a6989586621679404425] (Maybe a6989586621679404425) -> *) Source # 
Instance details
SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679419904] (TyFun [a6989586621679419904] [a6989586621679419904] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((!!@#@$) :: TyFun [a6989586621679442420] (TyFun Nat a6989586621679442420 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (LengthSym0 :: TyFun [a6989586621679442423] Nat -> *) Source # 
Instance details
SuppressUnusedWarnings (ProductSym0 :: TyFun [a6989586621679442424] a6989586621679442424 -> *) Source # 
Instance details
SuppressUnusedWarnings (SumSym0 :: TyFun [a6989586621679442425] a6989586621679442425 -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621679442435] [[a6989586621679442435]] -> *) Source # 
Instance details
SuppressUnusedWarnings (SortSym0 :: TyFun [a6989586621679442431] [a6989586621679442431] -> *) Source # 
Instance details
SuppressUnusedWarnings (UnionSym0 :: TyFun [a6989586621679442415] (TyFun [a6989586621679442415] [a6989586621679442415] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((\\@#@$) :: TyFun [a6989586621679442458] (TyFun [a6989586621679442458] [a6989586621679442458] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (NubSym0 :: TyFun [a6989586621679442419] [a6989586621679442419] -> *) Source # 
Instance details
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679442503] (TyFun [a6989586621679442503] Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621679442504] [[a6989586621679442504]] -> *) Source # 
Instance details
SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621679442505] [[a6989586621679442505]] -> *) Source # 
Instance details
SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a6989586621679442501] (TyFun [a6989586621679442501] Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (IntersectSym0 :: TyFun [a6989586621679442445] (TyFun [a6989586621679442445] [a6989586621679442445] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MaximumSym0 :: TyFun [a6989586621679442434] a6989586621679442434 -> *) Source # 
Instance details
SuppressUnusedWarnings (MinimumSym0 :: TyFun [a6989586621679442433] a6989586621679442433 -> *) Source # 
Instance details
SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a6989586621679442530] [[a6989586621679442530]] -> *) Source # 
Instance details
SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a6989586621679442533] [[a6989586621679442533]] -> *) Source # 
Instance details
SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a6989586621679442534] (TyFun [[a6989586621679442534]] [a6989586621679442534] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ReverseSym0 :: TyFun [a6989586621679442536] [a6989586621679442536] -> *) Source # 
Instance details
SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679442502] (TyFun [a6989586621679442502] Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (NullSym0 :: TyFun [a6989586621679442537] Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (InitSym0 :: TyFun [a6989586621679442538] [a6989586621679442538] -> *) Source # 
Instance details
SuppressUnusedWarnings (TailSym0 :: TyFun [a6989586621679442539] [a6989586621679442539] -> *) Source # 
Instance details
SuppressUnusedWarnings (LastSym0 :: TyFun [a6989586621679442540] a6989586621679442540 -> *) Source # 
Instance details
SuppressUnusedWarnings (HeadSym0 :: TyFun [a6989586621679442541] a6989586621679442541 -> *) Source # 
Instance details
SuppressUnusedWarnings (ShowListSym0 :: TyFun [a6989586621679672338] (TyFun Symbol Symbol -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679768156] (TyFun (NonEmpty a6989586621679768156) Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621679768168] [NonEmpty a6989586621679768168] -> *) Source # 
Instance details
SuppressUnusedWarnings (FromListSym0 :: TyFun [a6989586621679768194] (NonEmpty a6989586621679768194) -> *) Source # 
Instance details
SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621679768188] (NonEmpty [a6989586621679768188]) -> *) Source # 
Instance details
SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621679768187] (NonEmpty [a6989586621679768187]) -> *) Source # 
Instance details
SuppressUnusedWarnings (NonEmpty_Sym0 :: TyFun [a6989586621679768205] (Maybe (NonEmpty a6989586621679768205)) -> *) Source # 
Instance details
SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a6989586621679922315] (TyFun [a6989586621679922315] (Maybe [a6989586621679922315]) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MaybeToListSym0 :: TyFun (Maybe a6989586621679404426) [a6989586621679404426] -> *) Source # 
Instance details
SuppressUnusedWarnings (FromJustSym0 :: TyFun (Maybe a6989586621679404428) a6989586621679404428 -> *) Source # 
Instance details
SuppressUnusedWarnings (IsNothingSym0 :: TyFun (Maybe a6989586621679404429) Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (IsJustSym0 :: TyFun (Maybe a6989586621679404430) Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (DropSym0 :: TyFun Nat (TyFun [a6989586621679442437] [a6989586621679442437] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (TakeSym0 :: TyFun Nat (TyFun [a6989586621679442438] [a6989586621679442438] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat (TyFun [a6989586621679442436] ([a6989586621679442436], [a6989586621679442436]) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ReplicateSym0 :: TyFun Nat (TyFun a6989586621679442422 [a6989586621679442422] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ShowsPrecSym0 :: TyFun Nat (TyFun a6989586621679672338 (TyFun Symbol Symbol -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (TakeSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679768177) [a6989586621679768177] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (DropSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679768176) [a6989586621679768176] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679768175) ([a6989586621679768175], [a6989586621679768175]) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (FromIntegerSym0 :: TyFun Nat a6989586621679412530 -> *) Source # 
Instance details
SuppressUnusedWarnings (ToEnumSym0 :: TyFun Nat a6989586621679843221 -> *) Source # 
Instance details
SuppressUnusedWarnings (FromStringSym0 :: TyFun Symbol a6989586621679411866 -> *) Source # 
Instance details
SuppressUnusedWarnings (JustSym0 :: TyFun a3530822107858468865 (Maybe a3530822107858468865) -> *) Source # 
Instance details
SuppressUnusedWarnings ((:@#@$) :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((:|@#@$) :: TyFun a6989586621679067178 (TyFun [a6989586621679067178] (NonEmpty a6989586621679067178) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Bool_Sym0 :: TyFun a6989586621679289682 (TyFun a6989586621679289682 (TyFun Bool a6989586621679289682 -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((==@#@$) :: TyFun a6989586621679292214 (TyFun a6989586621679292214 Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((/=@#@$) :: TyFun a6989586621679292214 (TyFun a6989586621679292214 Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((<=@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (CompareSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Ordering -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MinSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 a6989586621679303258 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MaxSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 a6989586621679303258 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((>=@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((>@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((<@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (FromMaybeSym0 :: TyFun a6989586621679404427 (TyFun (Maybe a6989586621679404427) a6989586621679404427 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (NegateSym0 :: TyFun a6989586621679412530 a6989586621679412530 -> *) Source # 
Instance details
SuppressUnusedWarnings ((-@#@$) :: TyFun a6989586621679412530 (TyFun a6989586621679412530 a6989586621679412530 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((+@#@$) :: TyFun a6989586621679412530 (TyFun a6989586621679412530 a6989586621679412530 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (SignumSym0 :: TyFun a6989586621679412530 a6989586621679412530 -> *) Source # 
Instance details
SuppressUnusedWarnings (AbsSym0 :: TyFun a6989586621679412530 a6989586621679412530 -> *) Source # 
Instance details
SuppressUnusedWarnings ((*@#@$) :: TyFun a6989586621679412530 (TyFun a6989586621679412530 a6989586621679412530 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (SubtractSym0 :: TyFun a6989586621679414803 (TyFun a6989586621679414803 a6989586621679414803 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (AsTypeOfSym0 :: TyFun a6989586621679419894 (TyFun a6989586621679419894 a6989586621679419894 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (IdSym0 :: TyFun a6989586621679419903 a6989586621679419903 -> *) Source # 
Instance details
SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621679442432 (TyFun [a6989586621679442432] [a6989586621679442432] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (DeleteSym0 :: TyFun a6989586621679442459 (TyFun [a6989586621679442459] [a6989586621679442459] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a6989586621679442448 (TyFun [a6989586621679442448] [Nat] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679442449 (TyFun [a6989586621679442449] (Maybe Nat) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621679442499 (TyFun [a6989586621679442499] Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621679442500 (TyFun [a6989586621679442500] Bool -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679442535 (TyFun [a6989586621679442535] [a6989586621679442535] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Show_Sym0 :: TyFun a6989586621679672338 Symbol -> *) Source # 
Instance details
SuppressUnusedWarnings (ShowsSym0 :: TyFun a6989586621679672323 (TyFun Symbol Symbol -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679768179 (TyFun (NonEmpty a6989586621679768179) (NonEmpty a6989586621679768179) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621679768186 (TyFun [a6989586621679768186] (NonEmpty a6989586621679768186) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((<|@#@$) :: TyFun a6989586621679768197 (TyFun (NonEmpty a6989586621679768197) (NonEmpty a6989586621679768197) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ConsSym0 :: TyFun a6989586621679768196 (TyFun (NonEmpty a6989586621679768196) (NonEmpty a6989586621679768196) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (EnumFromThenToSym0 :: TyFun a6989586621679843221 (TyFun a6989586621679843221 (TyFun a6989586621679843221 [a6989586621679843221] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (EnumFromToSym0 :: TyFun a6989586621679843221 (TyFun a6989586621679843221 [a6989586621679843221] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (FromEnumSym0 :: TyFun a6989586621679843221 Nat -> *) Source # 
Instance details
SuppressUnusedWarnings (PredSym0 :: TyFun a6989586621679843221 a6989586621679843221 -> *) Source # 
Instance details
SuppressUnusedWarnings (SuccSym0 :: TyFun a6989586621679843221 a6989586621679843221 -> *) Source # 
Instance details
SuppressUnusedWarnings (SameKindSym0 :: TyFun k6989586621679026622 (TyFun k6989586621679026622 Constraint -> *) -> *) Source # 
Instance details
SuppressUnusedWarnings (KindOfSym0 :: TyFun k6989586621679026625 * -> *) Source # 
Instance details
SuppressUnusedWarnings (AbsurdSym0 :: TyFun Void a6989586621679285232 -> *) Source # 
Instance details
SuppressUnusedWarnings (NubSym0 :: TyFun (NonEmpty a6989586621679768147) (NonEmpty a6989586621679768147) -> *) Source # 
Instance details
SuppressUnusedWarnings ((!!@#@$) :: TyFun (NonEmpty a6989586621679768155) (TyFun Nat a6989586621679768155 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Group1Sym0 :: TyFun (NonEmpty a6989586621679768162) (NonEmpty (NonEmpty a6989586621679768162)) -> *) Source # 
Instance details
SuppressUnusedWarnings (ToListSym0 :: TyFun (NonEmpty a6989586621679768193) [a6989586621679768193] -> *) Source # 
Instance details
SuppressUnusedWarnings (ReverseSym0 :: TyFun (NonEmpty a6989586621679768178) (NonEmpty a6989586621679768178) -> *) Source # 
Instance details
SuppressUnusedWarnings (SortSym0 :: TyFun (NonEmpty a6989586621679768195) (NonEmpty a6989586621679768195) -> *) Source # 
Instance details
SuppressUnusedWarnings (InitSym0 :: TyFun (NonEmpty a6989586621679768198) [a6989586621679768198] -> *) Source # 
Instance details
SuppressUnusedWarnings (LastSym0 :: TyFun (NonEmpty a6989586621679768199) a6989586621679768199 -> *) Source # 
Instance details
SuppressUnusedWarnings (TailSym0 :: TyFun (NonEmpty a6989586621679768200) [a6989586621679768200] -> *) Source # 
Instance details
SuppressUnusedWarnings (HeadSym0 :: TyFun (NonEmpty a6989586621679768201) a6989586621679768201 -> *) Source # 
Instance details
SuppressUnusedWarnings (UnconsSym0 :: TyFun (NonEmpty a6989586621679768204) (a6989586621679768204, Maybe (NonEmpty a6989586621679768204)) -> *) Source # 
Instance details
SuppressUnusedWarnings (LengthSym0 :: TyFun (NonEmpty a6989586621679768208) Nat -> *) Source # 
Instance details
SuppressUnusedWarnings (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a6989586621679768145)) (NonEmpty (NonEmpty a6989586621679768145)) -> *) Source # 
Instance details
SuppressUnusedWarnings (FoldlSym2 :: (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) -> b6989586621679259259 -> TyFun [a6989586621679259258] b6989586621679259259 -> *) Source # 
Instance details
SuppressUnusedWarnings (FoldlSym1 :: (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) -> TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ComparingSym2 :: (TyFun b6989586621679303248 a6989586621679303247 -> Type) -> b6989586621679303248 -> TyFun b6989586621679303248 Ordering -> *) Source # 
Instance details
SuppressUnusedWarnings (ComparingSym1 :: (TyFun b6989586621679303248 a6989586621679303247 -> Type) -> TyFun b6989586621679303248 (TyFun b6989586621679303248 Ordering -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MapMaybeSym1 :: (TyFun a6989586621679404422 (Maybe b6989586621679404423) -> Type) -> TyFun [a6989586621679404422] [b6989586621679404423] -> *) Source # 
Instance details
SuppressUnusedWarnings (($!@#@$$) :: (TyFun a6989586621679419890 b6989586621679419891 -> Type) -> TyFun a6989586621679419890 b6989586621679419891 -> *) Source # 
Instance details
SuppressUnusedWarnings (($@#@$$) :: (TyFun a6989586621679419892 b6989586621679419893 -> Type) -> TyFun a6989586621679419892 b6989586621679419893 -> *) Source # 
Instance details
SuppressUnusedWarnings (MapSym1 :: (TyFun a6989586621679419905 b6989586621679419906 -> Type) -> TyFun [a6989586621679419905] [b6989586621679419906] -> *) Source # 
Instance details
SuppressUnusedWarnings (FoldrSym2 :: (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) -> b6989586621679419908 -> TyFun [a6989586621679419907] b6989586621679419908 -> *) Source # 
Instance details
SuppressUnusedWarnings (FoldrSym1 :: (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) -> TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (UnfoldrSym1 :: (TyFun b6989586621679442506 (Maybe (a6989586621679442507, b6989586621679442506)) -> Type) -> TyFun b6989586621679442506 [a6989586621679442507] -> *) Source # 
Instance details
SuppressUnusedWarnings (ScanrSym1 :: (TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) -> TyFun b6989586621679442516 (TyFun [a6989586621679442515] [b6989586621679442516] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ScanrSym2 :: (TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) -> b6989586621679442516 -> TyFun [a6989586621679442515] [b6989586621679442516] -> *) Source # 
Instance details
SuppressUnusedWarnings (ScanlSym1 :: (TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) -> TyFun b6989586621679442518 (TyFun [a6989586621679442519] [b6989586621679442518] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ScanlSym2 :: (TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) -> b6989586621679442518 -> TyFun [a6989586621679442519] [b6989586621679442518] -> *) Source # 
Instance details
SuppressUnusedWarnings (ConcatMapSym1 :: (TyFun a6989586621679442522 [b6989586621679442523] -> Type) -> TyFun [a6989586621679442522] [b6989586621679442523] -> *) Source # 
Instance details
SuppressUnusedWarnings (Foldl'Sym2 :: (TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) -> b6989586621679442529 -> TyFun [a6989586621679442528] b6989586621679442529 -> *) Source # 
Instance details
SuppressUnusedWarnings (Foldl'Sym1 :: (TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) -> TyFun b6989586621679442529 (TyFun [a6989586621679442528] b6989586621679442529 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupWithSym1 :: (TyFun a6989586621679768166 b6989586621679768165 -> Type) -> TyFun [a6989586621679768166] [NonEmpty a6989586621679768166] -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupAllWithSym1 :: (TyFun a6989586621679768164 b6989586621679768163 -> Type) -> TyFun [a6989586621679768164] [NonEmpty a6989586621679768164] -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupWith1Sym1 :: (TyFun a6989586621679768160 b6989586621679768159 -> Type) -> TyFun (NonEmpty a6989586621679768160) (NonEmpty (NonEmpty a6989586621679768160)) -> *) Source # 
Instance details
SuppressUnusedWarnings (MapSym1 :: (TyFun a6989586621679768189 b6989586621679768190 -> Type) -> TyFun (NonEmpty a6989586621679768189) (NonEmpty b6989586621679768190) -> *) Source # 
Instance details
SuppressUnusedWarnings (SortWithSym1 :: (TyFun a6989586621679768143 o6989586621679768142 -> Type) -> TyFun (NonEmpty a6989586621679768143) (NonEmpty a6989586621679768143) -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupAllWith1Sym1 :: (TyFun a6989586621679768158 b6989586621679768157 -> Type) -> TyFun (NonEmpty a6989586621679768158) (NonEmpty (NonEmpty a6989586621679768158)) -> *) Source # 
Instance details
SuppressUnusedWarnings (ScanlSym2 :: (TyFun b6989586621679768184 (TyFun a6989586621679768185 b6989586621679768184 -> Type) -> Type) -> b6989586621679768184 -> TyFun [a6989586621679768185] (NonEmpty b6989586621679768184) -> *) Source # 
Instance details
SuppressUnusedWarnings (ScanlSym1 :: (TyFun b6989586621679768184 (TyFun a6989586621679768185 b6989586621679768184 -> Type) -> Type) -> TyFun b6989586621679768184 (TyFun [a6989586621679768185] (NonEmpty b6989586621679768184) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ScanrSym2 :: (TyFun a6989586621679768182 (TyFun b6989586621679768183 b6989586621679768183 -> Type) -> Type) -> b6989586621679768183 -> TyFun [a6989586621679768182] (NonEmpty b6989586621679768183) -> *) Source # 
Instance details
SuppressUnusedWarnings (ScanrSym1 :: (TyFun a6989586621679768182 (TyFun b6989586621679768183 b6989586621679768183 -> Type) -> Type) -> TyFun b6989586621679768183 (TyFun [a6989586621679768182] (NonEmpty b6989586621679768183) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (UnfoldrSym1 :: (TyFun a6989586621679768202 (b6989586621679768203, Maybe a6989586621679768202) -> Type) -> TyFun a6989586621679768202 (NonEmpty b6989586621679768203) -> *) Source # 
Instance details
SuppressUnusedWarnings (UnfoldSym1 :: (TyFun a6989586621679768206 (b6989586621679768207, Maybe a6989586621679768206) -> Type) -> TyFun a6989586621679768206 (NonEmpty b6989586621679768207) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipSym1 :: [a6989586621679442497] -> TyFun [b6989586621679442498] [(a6989586621679442497, b6989586621679442498)] -> *) Source # 
Instance details
SuppressUnusedWarnings (GenericIndexSym1 :: [a6989586621679922260] -> TyFun i6989586621679922259 a6989586621679922260 -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple2Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> *) Source # 
Instance details
SuppressUnusedWarnings (Maybe_Sym2 :: b6989586621679403309 -> (TyFun a6989586621679403310 b6989586621679403309 -> Type) -> TyFun (Maybe a6989586621679403310) b6989586621679403309 -> *) Source # 
Instance details
SuppressUnusedWarnings (Maybe_Sym1 :: b6989586621679403309 -> TyFun (TyFun a6989586621679403310 b6989586621679403309 -> Type) (TyFun (Maybe a6989586621679403310) b6989586621679403309 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (SeqSym1 :: a6989586621679419888 -> TyFun b6989586621679419889 b6989586621679419889 -> *) Source # 
Instance details
SuppressUnusedWarnings (ConstSym1 :: a6989586621679419901 -> TyFun b6989586621679419902 a6989586621679419901 -> *) Source # 
Instance details
SuppressUnusedWarnings (LookupSym1 :: a6989586621679442428 -> TyFun [(a6989586621679442428, b6989586621679442429)] (Maybe b6989586621679442429) -> *) Source # 
Instance details
SuppressUnusedWarnings ((&@#@$$) :: a6989586621679759158 -> TyFun (TyFun a6989586621679759158 b6989586621679759159 -> Type) b6989586621679759159 -> *) Source # 
Instance details
SuppressUnusedWarnings (GenericReplicateSym1 :: i6989586621679922257 -> TyFun a6989586621679922258 [a6989586621679922258] -> *) Source # 
Instance details
SuppressUnusedWarnings (GenericSplitAtSym1 :: i6989586621679922261 -> TyFun [a6989586621679922262] ([a6989586621679922262], [a6989586621679922262]) -> *) Source # 
Instance details
SuppressUnusedWarnings (GenericDropSym1 :: i6989586621679922263 -> TyFun [a6989586621679922264] [a6989586621679922264] -> *) Source # 
Instance details
SuppressUnusedWarnings (GenericTakeSym1 :: i6989586621679922265 -> TyFun [a6989586621679922266] [a6989586621679922266] -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipSym1 :: NonEmpty a6989586621679768153 -> TyFun (NonEmpty b6989586621679768154) (NonEmpty (a6989586621679768153, b6989586621679768154)) -> *) Source # 
Instance details
SuppressUnusedWarnings (ApplySym1 :: (k16989586621679024775 ~> k26989586621679024776) -> TyFun k16989586621679024775 k26989586621679024776 -> *) Source # 
Instance details
SuppressUnusedWarnings ((@@@#@$$) :: (k16989586621679030856 ~> k6989586621679030855) -> TyFun k16989586621679030856 k6989586621679030855 -> *) Source # 
Instance details
SuppressUnusedWarnings (FoldlSym0 :: TyFun (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ComparingSym0 :: TyFun (TyFun b6989586621679303248 a6989586621679303247 -> Type) (TyFun b6989586621679303248 (TyFun b6989586621679303248 Ordering -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MapMaybeSym0 :: TyFun (TyFun a6989586621679404422 (Maybe b6989586621679404423) -> Type) (TyFun [a6989586621679404422] [b6989586621679404423] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (($!@#@$) :: TyFun (TyFun a6989586621679419890 b6989586621679419891 -> Type) (TyFun a6989586621679419890 b6989586621679419891 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (($@#@$) :: TyFun (TyFun a6989586621679419892 b6989586621679419893 -> Type) (TyFun a6989586621679419892 b6989586621679419893 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MapSym0 :: TyFun (TyFun a6989586621679419905 b6989586621679419906 -> Type) (TyFun [a6989586621679419905] [b6989586621679419906] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (FoldrSym0 :: TyFun (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (TyFun b6989586621679442506 (Maybe (a6989586621679442507, b6989586621679442506)) -> Type) (TyFun b6989586621679442506 [a6989586621679442507] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ScanrSym0 :: TyFun (TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) (TyFun b6989586621679442516 (TyFun [a6989586621679442515] [b6989586621679442516] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ScanlSym0 :: TyFun (TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) (TyFun b6989586621679442518 (TyFun [a6989586621679442519] [b6989586621679442518] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (TyFun a6989586621679442522 [b6989586621679442523] -> Type) (TyFun [a6989586621679442522] [b6989586621679442523] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) (TyFun b6989586621679442529 (TyFun [a6989586621679442528] b6989586621679442529 -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupWithSym0 :: TyFun (TyFun a6989586621679768166 b6989586621679768165 -> Type) (TyFun [a6989586621679768166] [NonEmpty a6989586621679768166] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupAllWithSym0 :: TyFun (TyFun a6989586621679768164 b6989586621679768163 -> Type) (TyFun [a6989586621679768164] [NonEmpty a6989586621679768164] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupWith1Sym0 :: TyFun (TyFun a6989586621679768160 b6989586621679768159 -> Type) (TyFun (NonEmpty a6989586621679768160) (NonEmpty (NonEmpty a6989586621679768160)) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MapSym0 :: TyFun (TyFun a6989586621679768189 b6989586621679768190 -> Type) (TyFun (NonEmpty a6989586621679768189) (NonEmpty b6989586621679768190) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (SortWithSym0 :: TyFun (TyFun a6989586621679768143 o6989586621679768142 -> Type) (TyFun (NonEmpty a6989586621679768143) (NonEmpty a6989586621679768143) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GroupAllWith1Sym0 :: TyFun (TyFun a6989586621679768158 b6989586621679768157 -> Type) (TyFun (NonEmpty a6989586621679768158) (NonEmpty (NonEmpty a6989586621679768158)) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ScanlSym0 :: TyFun (TyFun b6989586621679768184 (TyFun a6989586621679768185 b6989586621679768184 -> Type) -> Type) (TyFun b6989586621679768184 (TyFun [a6989586621679768185] (NonEmpty b6989586621679768184) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ScanrSym0 :: TyFun (TyFun a6989586621679768182 (TyFun b6989586621679768183 b6989586621679768183 -> Type) -> Type) (TyFun b6989586621679768183 (TyFun [a6989586621679768182] (NonEmpty b6989586621679768183) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (TyFun a6989586621679768202 (b6989586621679768203, Maybe a6989586621679768202) -> Type) (TyFun a6989586621679768202 (NonEmpty b6989586621679768203) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (UnfoldSym0 :: TyFun (TyFun a6989586621679768206 (b6989586621679768207, Maybe a6989586621679768206) -> Type) (TyFun a6989586621679768206 (NonEmpty b6989586621679768207) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (RightsSym0 :: TyFun [Either a6989586621679913273 b6989586621679913274] [b6989586621679913274] -> *) Source # 
Instance details
SuppressUnusedWarnings (LeftsSym0 :: TyFun [Either a6989586621679913275 b6989586621679913276] [a6989586621679913275] -> *) Source # 
Instance details
SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a6989586621679442485, b6989586621679442486)] ([a6989586621679442485], [b6989586621679442486]) -> *) Source # 
Instance details
SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a6989586621679442414] i6989586621679442413 -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipSym0 :: TyFun [a6989586621679442497] (TyFun [b6989586621679442498] [(a6989586621679442497, b6989586621679442498)] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GenericIndexSym0 :: TyFun [a6989586621679922260] (TyFun i6989586621679922259 a6989586621679922260 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (IsRightSym0 :: TyFun (Either a6989586621679913267 b6989586621679913268) Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (IsLeftSym0 :: TyFun (Either a6989586621679913269 b6989586621679913270) Bool -> *) Source # 
Instance details
SuppressUnusedWarnings (SwapSym0 :: TyFun (a6989586621679285916, b6989586621679285917) (b6989586621679285917, a6989586621679285916) -> *) Source # 
Instance details
SuppressUnusedWarnings (SndSym0 :: TyFun (a6989586621679285924, b6989586621679285925) b6989586621679285925 -> *) Source # 
Instance details
SuppressUnusedWarnings (FstSym0 :: TyFun (a6989586621679285926, b6989586621679285927) a6989586621679285926 -> *) Source # 
Instance details
SuppressUnusedWarnings (LeftSym0 :: TyFun a6989586621679082339 (Either a6989586621679082339 b6989586621679082340) -> *) Source # 
Instance details
SuppressUnusedWarnings (RightSym0 :: TyFun b6989586621679082340 (Either a6989586621679082339 b6989586621679082340) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple2Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ErrorSym0 :: TyFun k06989586621679378680 k6989586621679378681 -> *) Source # 
Instance details
SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b6989586621679403309 (TyFun (TyFun a6989586621679403310 b6989586621679403309 -> Type) (TyFun (Maybe a6989586621679403310) b6989586621679403309 -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (SeqSym0 :: TyFun a6989586621679419888 (TyFun b6989586621679419889 b6989586621679419889 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ConstSym0 :: TyFun a6989586621679419901 (TyFun b6989586621679419902 a6989586621679419901 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679442428 (TyFun [(a6989586621679442428, b6989586621679442429)] (Maybe b6989586621679442429) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((&@#@$) :: TyFun a6989586621679759158 (TyFun (TyFun a6989586621679759158 b6989586621679759159 -> Type) b6989586621679759159 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GenericReplicateSym0 :: TyFun i6989586621679922257 (TyFun a6989586621679922258 [a6989586621679922258] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GenericSplitAtSym0 :: TyFun i6989586621679922261 (TyFun [a6989586621679922262] ([a6989586621679922262], [a6989586621679922262]) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GenericDropSym0 :: TyFun i6989586621679922263 (TyFun [a6989586621679922264] [a6989586621679922264] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (GenericTakeSym0 :: TyFun i6989586621679922265 (TyFun [a6989586621679922266] [a6989586621679922266] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (UnzipSym0 :: TyFun (NonEmpty (a6989586621679768148, b6989586621679768149)) (NonEmpty a6989586621679768148, NonEmpty b6989586621679768149) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipSym0 :: TyFun (NonEmpty a6989586621679768153) (TyFun (NonEmpty b6989586621679768154) (NonEmpty (a6989586621679768153, b6989586621679768154)) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ApplySym0 :: TyFun (k16989586621679024775 ~> k26989586621679024776) (TyFun k16989586621679024775 k26989586621679024776 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((@@@#@$) :: TyFun (k16989586621679030856 ~> k6989586621679030855) (TyFun k16989586621679030856 k6989586621679030855 -> *) -> *) Source # 
Instance details
SuppressUnusedWarnings (CurrySym2 :: (TyFun (a6989586621679285921, b6989586621679285922) c6989586621679285923 -> Type) -> a6989586621679285921 -> TyFun b6989586621679285922 c6989586621679285923 -> *) Source # 
Instance details
SuppressUnusedWarnings (CurrySym1 :: (TyFun (a6989586621679285921, b6989586621679285922) c6989586621679285923 -> Type) -> TyFun a6989586621679285921 (TyFun b6989586621679285922 c6989586621679285923 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (UncurrySym1 :: (TyFun a6989586621679285918 (TyFun b6989586621679285919 c6989586621679285920 -> Type) -> Type) -> TyFun (a6989586621679285918, b6989586621679285919) c6989586621679285920 -> *) Source # 
Instance details
SuppressUnusedWarnings (FlipSym2 :: (TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) -> b6989586621679419896 -> TyFun a6989586621679419895 c6989586621679419897 -> *) Source # 
Instance details
SuppressUnusedWarnings (FlipSym1 :: (TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) -> TyFun b6989586621679419896 (TyFun a6989586621679419895 c6989586621679419897 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((.@#@$$$) :: (TyFun b6989586621679419898 c6989586621679419899 -> Type) -> (TyFun a6989586621679419900 b6989586621679419898 -> Type) -> TyFun a6989586621679419900 c6989586621679419899 -> *) Source # 
Instance details
SuppressUnusedWarnings ((.@#@$$) :: (TyFun b6989586621679419898 c6989586621679419899 -> Type) -> TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWithSym1 :: (TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) -> TyFun [a6989586621679442491] (TyFun [b6989586621679442492] [c6989586621679442493] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWithSym2 :: (TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) -> [a6989586621679442491] -> TyFun [b6989586621679442492] [c6989586621679442493] -> *) Source # 
Instance details
SuppressUnusedWarnings (MapAccumRSym1 :: (TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) -> TyFun acc6989586621679442508 (TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MapAccumRSym2 :: (TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) -> acc6989586621679442508 -> TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> *) Source # 
Instance details
SuppressUnusedWarnings (MapAccumLSym1 :: (TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) -> TyFun acc6989586621679442511 (TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MapAccumLSym2 :: (TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) -> acc6989586621679442511 -> TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> *) Source # 
Instance details
SuppressUnusedWarnings (OnSym3 :: (TyFun b6989586621679759160 (TyFun b6989586621679759160 c6989586621679759161 -> Type) -> Type) -> (TyFun a6989586621679759162 b6989586621679759160 -> Type) -> a6989586621679759162 -> TyFun a6989586621679759162 c6989586621679759161 -> *) Source # 
Instance details
SuppressUnusedWarnings (OnSym2 :: (TyFun b6989586621679759160 (TyFun b6989586621679759160 c6989586621679759161 -> Type) -> Type) -> (TyFun a6989586621679759162 b6989586621679759160 -> Type) -> TyFun a6989586621679759162 (TyFun a6989586621679759162 c6989586621679759161 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (OnSym1 :: (TyFun b6989586621679759160 (TyFun b6989586621679759160 c6989586621679759161 -> Type) -> Type) -> TyFun (TyFun a6989586621679759162 b6989586621679759160 -> Type) (TyFun a6989586621679759162 (TyFun a6989586621679759162 c6989586621679759161 -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWithSym2 :: (TyFun a6989586621679768150 (TyFun b6989586621679768151 c6989586621679768152 -> Type) -> Type) -> NonEmpty a6989586621679768150 -> TyFun (NonEmpty b6989586621679768151) (NonEmpty c6989586621679768152) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWithSym1 :: (TyFun a6989586621679768150 (TyFun b6989586621679768151 c6989586621679768152 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679768150) (TyFun (NonEmpty b6989586621679768151) (NonEmpty c6989586621679768152) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Either_Sym2 :: (TyFun a6989586621679912139 c6989586621679912140 -> Type) -> (TyFun b6989586621679912141 c6989586621679912140 -> Type) -> TyFun (Either a6989586621679912139 b6989586621679912141) c6989586621679912140 -> *) Source # 
Instance details
SuppressUnusedWarnings (Either_Sym1 :: (TyFun a6989586621679912139 c6989586621679912140 -> Type) -> TyFun (TyFun b6989586621679912141 c6989586621679912140 -> Type) (TyFun (Either a6989586621679912139 b6989586621679912141) c6989586621679912140 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip3Sym1 :: [a6989586621679442494] -> TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip3Sym2 :: [a6989586621679442494] -> [b6989586621679442495] -> TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple3Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple3Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (CurrySym0 :: TyFun (TyFun (a6989586621679285921, b6989586621679285922) c6989586621679285923 -> Type) (TyFun a6989586621679285921 (TyFun b6989586621679285922 c6989586621679285923 -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (UncurrySym0 :: TyFun (TyFun a6989586621679285918 (TyFun b6989586621679285919 c6989586621679285920 -> Type) -> Type) (TyFun (a6989586621679285918, b6989586621679285919) c6989586621679285920 -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (FlipSym0 :: TyFun (TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) (TyFun b6989586621679419896 (TyFun a6989586621679419895 c6989586621679419897 -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings ((.@#@$) :: TyFun (TyFun b6989586621679419898 c6989586621679419899 -> Type) (TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWithSym0 :: TyFun (TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) (TyFun [a6989586621679442491] (TyFun [b6989586621679442492] [c6989586621679442493] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) (TyFun acc6989586621679442508 (TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) (TyFun acc6989586621679442511 (TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (OnSym0 :: TyFun (TyFun b6989586621679759160 (TyFun b6989586621679759160 c6989586621679759161 -> Type) -> Type) (TyFun (TyFun a6989586621679759162 b6989586621679759160 -> Type) (TyFun a6989586621679759162 (TyFun a6989586621679759162 c6989586621679759161 -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWithSym0 :: TyFun (TyFun a6989586621679768150 (TyFun b6989586621679768151 c6989586621679768152 -> Type) -> Type) (TyFun (NonEmpty a6989586621679768150) (TyFun (NonEmpty b6989586621679768151) (NonEmpty c6989586621679768152) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Either_Sym0 :: TyFun (TyFun a6989586621679912139 c6989586621679912140 -> Type) (TyFun (TyFun b6989586621679912141 c6989586621679912140 -> Type) (TyFun (Either a6989586621679912139 b6989586621679912141) c6989586621679912140 -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a6989586621679442482, b6989586621679442483, c6989586621679442484)] ([a6989586621679442482], [b6989586621679442483], [c6989586621679442484]) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a6989586621679442494] (TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple3Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith3Sym1 :: (TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) -> TyFun [a6989586621679442487] (TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith3Sym2 :: (TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) -> [a6989586621679442487] -> TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith3Sym3 :: (TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) -> [a6989586621679442487] -> [b6989586621679442488] -> TyFun [c6989586621679442489] [d6989586621679442490] -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip4Sym3 :: [a6989586621679922311] -> [b6989586621679922312] -> [c6989586621679922313] -> TyFun [d6989586621679922314] [(a6989586621679922311, b6989586621679922312, c6989586621679922313, d6989586621679922314)] -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip4Sym2 :: [a6989586621679922311] -> [b6989586621679922312] -> TyFun [c6989586621679922313] (TyFun [d6989586621679922314] [(a6989586621679922311, b6989586621679922312, c6989586621679922313, d6989586621679922314)] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip4Sym1 :: [a6989586621679922311] -> TyFun [b6989586621679922312] (TyFun [c6989586621679922313] (TyFun [d6989586621679922314] [(a6989586621679922311, b6989586621679922312, c6989586621679922313, d6989586621679922314)] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple4Sym3 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple4Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple4Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (TyFun [a6989586621679442487] (TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a6989586621679442478, b6989586621679442479, c6989586621679442480, d6989586621679442481)] ([a6989586621679442478], [b6989586621679442479], [c6989586621679442480], [d6989586621679442481]) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a6989586621679922311] (TyFun [b6989586621679922312] (TyFun [c6989586621679922313] (TyFun [d6989586621679922314] [(a6989586621679922311, b6989586621679922312, c6989586621679922313, d6989586621679922314)] -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple4Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith4Sym1 :: (TyFun a6989586621679922288 (TyFun b6989586621679922289 (TyFun c6989586621679922290 (TyFun d6989586621679922291 e6989586621679922292 -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679922288] (TyFun [b6989586621679922289] (TyFun [c6989586621679922290] (TyFun [d6989586621679922291] [e6989586621679922292] -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith4Sym2 :: (TyFun a6989586621679922288 (TyFun b6989586621679922289 (TyFun c6989586621679922290 (TyFun d6989586621679922291 e6989586621679922292 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922288] -> TyFun [b6989586621679922289] (TyFun [c6989586621679922290] (TyFun [d6989586621679922291] [e6989586621679922292] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith4Sym3 :: (TyFun a6989586621679922288 (TyFun b6989586621679922289 (TyFun c6989586621679922290 (TyFun d6989586621679922291 e6989586621679922292 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922288] -> [b6989586621679922289] -> TyFun [c6989586621679922290] (TyFun [d6989586621679922291] [e6989586621679922292] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith4Sym4 :: (TyFun a6989586621679922288 (TyFun b6989586621679922289 (TyFun c6989586621679922290 (TyFun d6989586621679922291 e6989586621679922292 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922288] -> [b6989586621679922289] -> [c6989586621679922290] -> TyFun [d6989586621679922291] [e6989586621679922292] -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip5Sym4 :: [a6989586621679922306] -> [b6989586621679922307] -> [c6989586621679922308] -> [d6989586621679922309] -> TyFun [e6989586621679922310] [(a6989586621679922306, b6989586621679922307, c6989586621679922308, d6989586621679922309, e6989586621679922310)] -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip5Sym3 :: [a6989586621679922306] -> [b6989586621679922307] -> [c6989586621679922308] -> TyFun [d6989586621679922309] (TyFun [e6989586621679922310] [(a6989586621679922306, b6989586621679922307, c6989586621679922308, d6989586621679922309, e6989586621679922310)] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip5Sym2 :: [a6989586621679922306] -> [b6989586621679922307] -> TyFun [c6989586621679922308] (TyFun [d6989586621679922309] (TyFun [e6989586621679922310] [(a6989586621679922306, b6989586621679922307, c6989586621679922308, d6989586621679922309, e6989586621679922310)] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip5Sym1 :: [a6989586621679922306] -> TyFun [b6989586621679922307] (TyFun [c6989586621679922308] (TyFun [d6989586621679922309] (TyFun [e6989586621679922310] [(a6989586621679922306, b6989586621679922307, c6989586621679922308, d6989586621679922309, e6989586621679922310)] -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple5Sym4 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple5Sym3 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple5Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple5Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (TyFun a6989586621679922288 (TyFun b6989586621679922289 (TyFun c6989586621679922290 (TyFun d6989586621679922291 e6989586621679922292 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679922288] (TyFun [b6989586621679922289] (TyFun [c6989586621679922290] (TyFun [d6989586621679922291] [e6989586621679922292] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a6989586621679442473, b6989586621679442474, c6989586621679442475, d6989586621679442476, e6989586621679442477)] ([a6989586621679442473], [b6989586621679442474], [c6989586621679442475], [d6989586621679442476], [e6989586621679442477]) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a6989586621679922306] (TyFun [b6989586621679922307] (TyFun [c6989586621679922308] (TyFun [d6989586621679922309] (TyFun [e6989586621679922310] [(a6989586621679922306, b6989586621679922307, c6989586621679922308, d6989586621679922309, e6989586621679922310)] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple5Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith5Sym1 :: (TyFun a6989586621679922282 (TyFun b6989586621679922283 (TyFun c6989586621679922284 (TyFun d6989586621679922285 (TyFun e6989586621679922286 f6989586621679922287 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679922282] (TyFun [b6989586621679922283] (TyFun [c6989586621679922284] (TyFun [d6989586621679922285] (TyFun [e6989586621679922286] [f6989586621679922287] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith5Sym2 :: (TyFun a6989586621679922282 (TyFun b6989586621679922283 (TyFun c6989586621679922284 (TyFun d6989586621679922285 (TyFun e6989586621679922286 f6989586621679922287 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922282] -> TyFun [b6989586621679922283] (TyFun [c6989586621679922284] (TyFun [d6989586621679922285] (TyFun [e6989586621679922286] [f6989586621679922287] -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith5Sym3 :: (TyFun a6989586621679922282 (TyFun b6989586621679922283 (TyFun c6989586621679922284 (TyFun d6989586621679922285 (TyFun e6989586621679922286 f6989586621679922287 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922282] -> [b6989586621679922283] -> TyFun [c6989586621679922284] (TyFun [d6989586621679922285] (TyFun [e6989586621679922286] [f6989586621679922287] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith5Sym4 :: (TyFun a6989586621679922282 (TyFun b6989586621679922283 (TyFun c6989586621679922284 (TyFun d6989586621679922285 (TyFun e6989586621679922286 f6989586621679922287 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922282] -> [b6989586621679922283] -> [c6989586621679922284] -> TyFun [d6989586621679922285] (TyFun [e6989586621679922286] [f6989586621679922287] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith5Sym5 :: (TyFun a6989586621679922282 (TyFun b6989586621679922283 (TyFun c6989586621679922284 (TyFun d6989586621679922285 (TyFun e6989586621679922286 f6989586621679922287 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922282] -> [b6989586621679922283] -> [c6989586621679922284] -> [d6989586621679922285] -> TyFun [e6989586621679922286] [f6989586621679922287] -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip6Sym5 :: [a6989586621679922300] -> [b6989586621679922301] -> [c6989586621679922302] -> [d6989586621679922303] -> [e6989586621679922304] -> TyFun [f6989586621679922305] [(a6989586621679922300, b6989586621679922301, c6989586621679922302, d6989586621679922303, e6989586621679922304, f6989586621679922305)] -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip6Sym4 :: [a6989586621679922300] -> [b6989586621679922301] -> [c6989586621679922302] -> [d6989586621679922303] -> TyFun [e6989586621679922304] (TyFun [f6989586621679922305] [(a6989586621679922300, b6989586621679922301, c6989586621679922302, d6989586621679922303, e6989586621679922304, f6989586621679922305)] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip6Sym3 :: [a6989586621679922300] -> [b6989586621679922301] -> [c6989586621679922302] -> TyFun [d6989586621679922303] (TyFun [e6989586621679922304] (TyFun [f6989586621679922305] [(a6989586621679922300, b6989586621679922301, c6989586621679922302, d6989586621679922303, e6989586621679922304, f6989586621679922305)] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip6Sym2 :: [a6989586621679922300] -> [b6989586621679922301] -> TyFun [c6989586621679922302] (TyFun [d6989586621679922303] (TyFun [e6989586621679922304] (TyFun [f6989586621679922305] [(a6989586621679922300, b6989586621679922301, c6989586621679922302, d6989586621679922303, e6989586621679922304, f6989586621679922305)] -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip6Sym1 :: [a6989586621679922300] -> TyFun [b6989586621679922301] (TyFun [c6989586621679922302] (TyFun [d6989586621679922303] (TyFun [e6989586621679922304] (TyFun [f6989586621679922305] [(a6989586621679922300, b6989586621679922301, c6989586621679922302, d6989586621679922303, e6989586621679922304, f6989586621679922305)] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple6Sym5 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> e3530822107858468869 -> TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple6Sym4 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple6Sym3 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple6Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple6Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (TyFun a6989586621679922282 (TyFun b6989586621679922283 (TyFun c6989586621679922284 (TyFun d6989586621679922285 (TyFun e6989586621679922286 f6989586621679922287 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679922282] (TyFun [b6989586621679922283] (TyFun [c6989586621679922284] (TyFun [d6989586621679922285] (TyFun [e6989586621679922286] [f6989586621679922287] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a6989586621679442467, b6989586621679442468, c6989586621679442469, d6989586621679442470, e6989586621679442471, f6989586621679442472)] ([a6989586621679442467], [b6989586621679442468], [c6989586621679442469], [d6989586621679442470], [e6989586621679442471], [f6989586621679442472]) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a6989586621679922300] (TyFun [b6989586621679922301] (TyFun [c6989586621679922302] (TyFun [d6989586621679922303] (TyFun [e6989586621679922304] (TyFun [f6989586621679922305] [(a6989586621679922300, b6989586621679922301, c6989586621679922302, d6989586621679922303, e6989586621679922304, f6989586621679922305)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple6Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith6Sym1 :: (TyFun a6989586621679922275 (TyFun b6989586621679922276 (TyFun c6989586621679922277 (TyFun d6989586621679922278 (TyFun e6989586621679922279 (TyFun f6989586621679922280 g6989586621679922281 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679922275] (TyFun [b6989586621679922276] (TyFun [c6989586621679922277] (TyFun [d6989586621679922278] (TyFun [e6989586621679922279] (TyFun [f6989586621679922280] [g6989586621679922281] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith6Sym2 :: (TyFun a6989586621679922275 (TyFun b6989586621679922276 (TyFun c6989586621679922277 (TyFun d6989586621679922278 (TyFun e6989586621679922279 (TyFun f6989586621679922280 g6989586621679922281 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922275] -> TyFun [b6989586621679922276] (TyFun [c6989586621679922277] (TyFun [d6989586621679922278] (TyFun [e6989586621679922279] (TyFun [f6989586621679922280] [g6989586621679922281] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith6Sym3 :: (TyFun a6989586621679922275 (TyFun b6989586621679922276 (TyFun c6989586621679922277 (TyFun d6989586621679922278 (TyFun e6989586621679922279 (TyFun f6989586621679922280 g6989586621679922281 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922275] -> [b6989586621679922276] -> TyFun [c6989586621679922277] (TyFun [d6989586621679922278] (TyFun [e6989586621679922279] (TyFun [f6989586621679922280] [g6989586621679922281] -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith6Sym4 :: (TyFun a6989586621679922275 (TyFun b6989586621679922276 (TyFun c6989586621679922277 (TyFun d6989586621679922278 (TyFun e6989586621679922279 (TyFun f6989586621679922280 g6989586621679922281 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922275] -> [b6989586621679922276] -> [c6989586621679922277] -> TyFun [d6989586621679922278] (TyFun [e6989586621679922279] (TyFun [f6989586621679922280] [g6989586621679922281] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith6Sym5 :: (TyFun a6989586621679922275 (TyFun b6989586621679922276 (TyFun c6989586621679922277 (TyFun d6989586621679922278 (TyFun e6989586621679922279 (TyFun f6989586621679922280 g6989586621679922281 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922275] -> [b6989586621679922276] -> [c6989586621679922277] -> [d6989586621679922278] -> TyFun [e6989586621679922279] (TyFun [f6989586621679922280] [g6989586621679922281] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith6Sym6 :: (TyFun a6989586621679922275 (TyFun b6989586621679922276 (TyFun c6989586621679922277 (TyFun d6989586621679922278 (TyFun e6989586621679922279 (TyFun f6989586621679922280 g6989586621679922281 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922275] -> [b6989586621679922276] -> [c6989586621679922277] -> [d6989586621679922278] -> [e6989586621679922279] -> TyFun [f6989586621679922280] [g6989586621679922281] -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip7Sym6 :: [a6989586621679922293] -> [b6989586621679922294] -> [c6989586621679922295] -> [d6989586621679922296] -> [e6989586621679922297] -> [f6989586621679922298] -> TyFun [g6989586621679922299] [(a6989586621679922293, b6989586621679922294, c6989586621679922295, d6989586621679922296, e6989586621679922297, f6989586621679922298, g6989586621679922299)] -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip7Sym5 :: [a6989586621679922293] -> [b6989586621679922294] -> [c6989586621679922295] -> [d6989586621679922296] -> [e6989586621679922297] -> TyFun [f6989586621679922298] (TyFun [g6989586621679922299] [(a6989586621679922293, b6989586621679922294, c6989586621679922295, d6989586621679922296, e6989586621679922297, f6989586621679922298, g6989586621679922299)] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip7Sym4 :: [a6989586621679922293] -> [b6989586621679922294] -> [c6989586621679922295] -> [d6989586621679922296] -> TyFun [e6989586621679922297] (TyFun [f6989586621679922298] (TyFun [g6989586621679922299] [(a6989586621679922293, b6989586621679922294, c6989586621679922295, d6989586621679922296, e6989586621679922297, f6989586621679922298, g6989586621679922299)] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip7Sym3 :: [a6989586621679922293] -> [b6989586621679922294] -> [c6989586621679922295] -> TyFun [d6989586621679922296] (TyFun [e6989586621679922297] (TyFun [f6989586621679922298] (TyFun [g6989586621679922299] [(a6989586621679922293, b6989586621679922294, c6989586621679922295, d6989586621679922296, e6989586621679922297, f6989586621679922298, g6989586621679922299)] -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip7Sym2 :: [a6989586621679922293] -> [b6989586621679922294] -> TyFun [c6989586621679922295] (TyFun [d6989586621679922296] (TyFun [e6989586621679922297] (TyFun [f6989586621679922298] (TyFun [g6989586621679922299] [(a6989586621679922293, b6989586621679922294, c6989586621679922295, d6989586621679922296, e6989586621679922297, f6989586621679922298, g6989586621679922299)] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip7Sym1 :: [a6989586621679922293] -> TyFun [b6989586621679922294] (TyFun [c6989586621679922295] (TyFun [d6989586621679922296] (TyFun [e6989586621679922297] (TyFun [f6989586621679922298] (TyFun [g6989586621679922299] [(a6989586621679922293, b6989586621679922294, c6989586621679922295, d6989586621679922296, e6989586621679922297, f6989586621679922298, g6989586621679922299)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple7Sym6 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> e3530822107858468869 -> f3530822107858468870 -> TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple7Sym5 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> e3530822107858468869 -> TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple7Sym4 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple7Sym3 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple7Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple7Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (TyFun a6989586621679922275 (TyFun b6989586621679922276 (TyFun c6989586621679922277 (TyFun d6989586621679922278 (TyFun e6989586621679922279 (TyFun f6989586621679922280 g6989586621679922281 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679922275] (TyFun [b6989586621679922276] (TyFun [c6989586621679922277] (TyFun [d6989586621679922278] (TyFun [e6989586621679922279] (TyFun [f6989586621679922280] [g6989586621679922281] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a6989586621679442460, b6989586621679442461, c6989586621679442462, d6989586621679442463, e6989586621679442464, f6989586621679442465, g6989586621679442466)] ([a6989586621679442460], [b6989586621679442461], [c6989586621679442462], [d6989586621679442463], [e6989586621679442464], [f6989586621679442465], [g6989586621679442466]) -> *) Source # 
Instance details
SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a6989586621679922293] (TyFun [b6989586621679922294] (TyFun [c6989586621679922295] (TyFun [d6989586621679922296] (TyFun [e6989586621679922297] (TyFun [f6989586621679922298] (TyFun [g6989586621679922299] [(a6989586621679922293, b6989586621679922294, c6989586621679922295, d6989586621679922296, e6989586621679922297, f6989586621679922298, g6989586621679922299)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (Tuple7Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith7Sym1 :: (TyFun a6989586621679922267 (TyFun b6989586621679922268 (TyFun c6989586621679922269 (TyFun d6989586621679922270 (TyFun e6989586621679922271 (TyFun f6989586621679922272 (TyFun g6989586621679922273 h6989586621679922274 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679922267] (TyFun [b6989586621679922268] (TyFun [c6989586621679922269] (TyFun [d6989586621679922270] (TyFun [e6989586621679922271] (TyFun [f6989586621679922272] (TyFun [g6989586621679922273] [h6989586621679922274] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith7Sym2 :: (TyFun a6989586621679922267 (TyFun b6989586621679922268 (TyFun c6989586621679922269 (TyFun d6989586621679922270 (TyFun e6989586621679922271 (TyFun f6989586621679922272 (TyFun g6989586621679922273 h6989586621679922274 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922267] -> TyFun [b6989586621679922268] (TyFun [c6989586621679922269] (TyFun [d6989586621679922270] (TyFun [e6989586621679922271] (TyFun [f6989586621679922272] (TyFun [g6989586621679922273] [h6989586621679922274] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith7Sym3 :: (TyFun a6989586621679922267 (TyFun b6989586621679922268 (TyFun c6989586621679922269 (TyFun d6989586621679922270 (TyFun e6989586621679922271 (TyFun f6989586621679922272 (TyFun g6989586621679922273 h6989586621679922274 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922267] -> [b6989586621679922268] -> TyFun [c6989586621679922269] (TyFun [d6989586621679922270] (TyFun [e6989586621679922271] (TyFun [f6989586621679922272] (TyFun [g6989586621679922273] [h6989586621679922274] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith7Sym4 :: (TyFun a6989586621679922267 (TyFun b6989586621679922268 (TyFun c6989586621679922269 (TyFun d6989586621679922270 (TyFun e6989586621679922271 (TyFun f6989586621679922272 (TyFun g6989586621679922273 h6989586621679922274 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922267] -> [b6989586621679922268] -> [c6989586621679922269] -> TyFun [d6989586621679922270] (TyFun [e6989586621679922271] (TyFun [f6989586621679922272] (TyFun [g6989586621679922273] [h6989586621679922274] -> Type) -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith7Sym5 :: (TyFun a6989586621679922267 (TyFun b6989586621679922268 (TyFun c6989586621679922269 (TyFun d6989586621679922270 (TyFun e6989586621679922271 (TyFun f6989586621679922272 (TyFun g6989586621679922273 h6989586621679922274 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922267] -> [b6989586621679922268] -> [c6989586621679922269] -> [d6989586621679922270] -> TyFun [e6989586621679922271] (TyFun [f6989586621679922272] (TyFun [g6989586621679922273] [h6989586621679922274] -> Type) -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith7Sym6 :: (TyFun a6989586621679922267 (TyFun b6989586621679922268 (TyFun c6989586621679922269 (TyFun d6989586621679922270 (TyFun e6989586621679922271 (TyFun f6989586621679922272 (TyFun g6989586621679922273 h6989586621679922274 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922267] -> [b6989586621679922268] -> [c6989586621679922269] -> [d6989586621679922270] -> [e6989586621679922271] -> TyFun [f6989586621679922272] (TyFun [g6989586621679922273] [h6989586621679922274] -> Type) -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith7Sym7 :: (TyFun a6989586621679922267 (TyFun b6989586621679922268 (TyFun c6989586621679922269 (TyFun d6989586621679922270 (TyFun e6989586621679922271 (TyFun f6989586621679922272 (TyFun g6989586621679922273 h6989586621679922274 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679922267] -> [b6989586621679922268] -> [c6989586621679922269] -> [d6989586621679922270] -> [e6989586621679922271] -> [f6989586621679922272] -> TyFun [g6989586621679922273] [h6989586621679922274] -> *) Source # 
Instance details
SuppressUnusedWarnings (ZipWith7Sym0 :: TyFun (TyFun a6989586621679922267 (TyFun b6989586621679922268 (TyFun c6989586621679922269 (TyFun d6989586621679922270 (TyFun e6989586621679922271 (TyFun f6989586621679922272 (TyFun g6989586621679922273 h6989586621679922274 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679922267] (TyFun [b6989586621679922268] (TyFun [c6989586621679922269] (TyFun [d6989586621679922270] (TyFun [e6989586621679922271] (TyFun [f6989586621679922272] (TyFun [g6989586621679922273] [h6989586621679922274] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details