singletons-2.4.1: 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
SDecide k => TestCoercion (Sing :: k -> *) # 
Instance details

Defined in Data.Singletons.Decide

Methods

testCoercion :: Sing a -> Sing b -> Maybe (Coercion a b) #

SDecide k => TestEquality (Sing :: k -> *) # 
Instance details

Defined in Data.Singletons.Decide

Methods

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

Show (SSymbol s) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> SSymbol s -> ShowS #

show :: SSymbol s -> String #

showList :: [SSymbol s] -> ShowS #

Show (SNat n) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> SNat n -> ShowS #

show :: SNat n -> String #

showList :: [SNat n] -> ShowS #

Eq (Sing a) # 
Instance details

Defined in Data.Singletons.TypeRepStar

Methods

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

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

Ord (Sing a) # 
Instance details

Defined in Data.Singletons.TypeRepStar

Methods

compare :: Sing a -> Sing a -> Ordering #

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

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

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

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

max :: Sing a -> Sing a -> Sing a #

min :: Sing a -> Sing a -> Sing a #

Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing [a]) => Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing a => Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b) => Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing a) # 
Instance details

Defined in Data.Singletons.TypeRepStar

Methods

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

show :: Sing a -> String #

showList :: [Sing a] -> ShowS #

Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b) => Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c) => Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d) => Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e) => Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f) => Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f, ShowSing g) => Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing [a]) => Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

data Sing (z :: Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: Bool) where
data Sing (z :: Ordering) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: Ordering) where
data Sing (a :: Type) Source # 
Instance details

Defined in Data.Singletons.TypeRepStar

data Sing (a :: Type) = STypeRep (TypeRep a)
data Sing (n :: Nat) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

data Sing (n :: Nat) where
data Sing (n :: Symbol) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

data Sing (n :: Symbol) where
data Sing (z :: ()) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: ()) where
data Sing (z :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: Void)
data Sing (z :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: [a]) where
data Sing (z :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: Maybe a) where
data Sing (z :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: NonEmpty a) where
data Sing (z :: Either a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: Either a b) where
data Sing (z :: (a, b)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: (a, b)) where
data Sing (f :: k1 ~> k2) Source # 
Instance details

Defined in Data.Singletons.Internal

data Sing (f :: k1 ~> k2) = SLambda {}
data Sing (z :: (a, b, c)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: (a, b, c)) where
data Sing (z :: (a, b, c, d)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: (a, b, c, d)) where
data Sing (z :: (a, b, c, d, e)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: (a, b, c, d, e)) where
data Sing (z :: (a, b, c, d, e, f)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: (a, b, c, d, e, f)) where
data Sing (z :: (a, b, c, d, e, f, g)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq Type Source # 
Instance details

Defined in Data.Singletons.TypeRepStar

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq Nat Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq Symbol Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq () Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq [a] Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (Either a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (a, b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

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

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

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

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

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

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

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

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

Methods

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

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

SEq Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

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

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

SEq Type Source # 
Instance details

Defined in Data.Singletons.TypeRepStar

Methods

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

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

SEq Nat Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

Methods

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

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

SEq Symbol Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

Methods

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

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

SEq () Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

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

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

SEq Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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 Nat Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

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 Symbol Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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_6989586621679325222Sym0 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_6989586621679325255Sym0 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_6989586621679325288Sym0 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_6989586621679325321Sym0 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_6989586621679325354Sym0 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_6989586621679325387Sym0 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_6989586621679325420Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t :: a) Source #

Instances
SOrd Bool Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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 Nat Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

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 Symbol Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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 (Let6989586621679273532LgoSym3 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.

Instances
SDecide Bool Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a -> Sing b -> Decision (a :~: b) Source #

SDecide Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a -> Sing b -> Decision (a :~: b) Source #

SDecide Type Source # 
Instance details

Defined in Data.Singletons.TypeRepStar

Methods

(%~) :: Sing a -> Sing b -> Decision (a :~: b) Source #

SDecide Nat Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

Methods

(%~) :: Sing a -> Sing b -> Decision (a :~: b) Source #

SDecide Symbol Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

Methods

(%~) :: Sing a -> Sing b -> Decision (a :~: b) Source #

SDecide () Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a -> Sing b -> Decision (a :~: b) Source #

SDecide Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a -> Sing b -> Decision (a :~: b) Source #

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

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a0 -> Sing b -> Decision (a0 :~: b) Source #

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

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a0 -> Sing b -> Decision (a0 :~: b) Source #

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

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a0 -> Sing b -> Decision (a0 :~: b) Source #

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

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a0 -> Sing b0 -> Decision (a0 :~: b0) Source #

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

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a0 -> Sing b0 -> Decision (a0 :~: b0) Source #

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

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a0 -> Sing b0 -> Decision (a0 :~: b0) Source #

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

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a0 -> Sing b0 -> Decision (a0 :~: b0) Source #

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

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a0 -> Sing b0 -> Decision (a0 :~: b0) Source #

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

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a0 -> Sing b0 -> Decision (a0 :~: b0) Source #

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

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a0 -> Sing b0 -> Decision (a0 :~: b0) Source #

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: base-4.7.0.0

Constructors

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

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Coercion

Methods

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

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

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

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

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

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

minBound :: a :~: b #

maxBound :: a :~: b #

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

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

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

Defined in Data.Type.Equality

Methods

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

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

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

Since: base-4.7.0.0

Instance details

Defined in Data.Data

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

Defined in Data.Type.Equality

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: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

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

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

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

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

Show (a :~: b) 
Instance details

Defined in Data.Type.Equality

Methods

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

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

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

data Void #

Uninhabited data type

Since: base-4.8.0.0

Instances
Eq Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Methods

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

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

Data Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

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: base-4.8.0.0

Instance details

Defined in Data.Void

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: base-4.8.0.0

Instance details

Defined in Data.Void

Show Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Ix Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

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

Defined in Data.Void

Associated Types

type Rep Void :: * -> * #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Semigroup Void

Since: base-4.9.0.0

Instance details

Defined in Data.Void

Methods

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

sconcat :: NonEmpty Void -> Void #

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

Exception Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

SingKind Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

Associated Types

type Demote Void = (r :: *) Source #

SDecide Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

(%~) :: Sing a -> Sing b -> Decision (a :~: b) Source #

PEq Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

SEq Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

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

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

SOrd Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.ShowSing

Methods

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

SShow Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

PShow Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

Show (Sing z) # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

SuppressUnusedWarnings (AbsurdSym0 :: TyFun Void a6989586621679303847 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Void

type Rep Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

type Rep Void = D1 (MetaData "Void" "Data.Void" "base" False) (V1 :: * -> *)
type Demote Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (z :: Void)
type Show_ (arg :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Show_ (arg :: Void)
type (a :: Void) == (b :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

type (a :: Void) == (b :: Void)
type (x :: Void) /= (y :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

type (x :: Void) /= (y :: Void) = Not (x == y)
type Compare (a1 :: Void) (a2 :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Compare (a1 :: Void) (a2 :: Void)
type (arg1 :: Void) < (arg2 :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type (arg1 :: Void) < (arg2 :: Void)
type (arg1 :: Void) <= (arg2 :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type (arg1 :: Void) <= (arg2 :: Void)
type (arg1 :: Void) > (arg2 :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type (arg1 :: Void) > (arg2 :: Void)
type (arg1 :: Void) >= (arg2 :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type (arg1 :: Void) >= (arg2 :: Void)
type Max (arg1 :: Void) (arg2 :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Max (arg1 :: Void) (arg2 :: Void)
type Min (arg1 :: Void) (arg2 :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Min (arg1 :: Void) (arg2 :: Void)
type ShowList (arg1 :: [Void]) arg2 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type ShowList (arg1 :: [Void]) arg2
type ShowsPrec a1 (a2 :: Void) a3 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type ShowsPrec a1 (a2 :: Void) a3
type Apply (AbsurdSym0 :: TyFun Void k2 -> *) (l :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Void

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

Defined in Data.Singletons.Prelude.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded () Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (a, b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

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

Defined in Data.Singletons.Prelude.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

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

Defined in Data.Singletons.Prelude.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

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

Defined in Data.Singletons.Prelude.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

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

Defined in Data.Singletons.Prelude.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

SBounded Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

SBounded () Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

(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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

SEnum Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

SEnum Nat Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

SEnum () Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow () Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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_6989586621679731952Sym0 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__6989586621679731972Sym0 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_6989586621679731990Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t :: Symbol) Source #

Instances
SShow Bool Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SShow Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SShow Nat Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SShow Symbol Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SShow () Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SShow Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

(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

Defined in Data.Singletons.Prelude.Show

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

Equations

ShowString a_6989586621679731745 a_6989586621679731747 = Apply (Apply (<>@#@$) a_6989586621679731745) a_6989586621679731747 

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_6989586621679731797 = Apply (Case_6989586621679731802 b p a_6989586621679731797 b) a_6989586621679731797 

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_6989586621679731727 = Apply (Apply Lambda_6989586621679731734Sym0 a_6989586621679731727) a_6989586621679731727 

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_6989586621679731767 a_6989586621679731769 = Apply (Apply (<>@#@$) a_6989586621679731767) a_6989586621679731769 

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_6989586621679731760 = Apply (Apply ShowStringSym0 ", ") a_6989586621679731760 

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

Equations

(f :. g) a_6989586621679448640 = Apply (Apply (Apply (Apply Lambda_6989586621679448645Sym0 f) g) a_6989586621679448640) a_6989586621679448640 

(%.) :: 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 
Instances
SBounded k => Bounded (SomeSing k) # 
Instance details

Defined in Data.Singletons

(SEnum k, SingKind k) => Enum (SomeSing k) # 
Instance details

Defined in Data.Singletons

SEq k => Eq (SomeSing k) # 
Instance details

Defined in Data.Singletons

Methods

(==) :: SomeSing k -> SomeSing k -> Bool #

(/=) :: SomeSing k -> SomeSing k -> Bool #

SNum k => Num (SomeSing k) # 
Instance details

Defined in Data.Singletons

SOrd k => Ord (SomeSing k) # 
Instance details

Defined in Data.Singletons

Methods

compare :: SomeSing k -> SomeSing k -> Ordering #

(<) :: SomeSing k -> SomeSing k -> Bool #

(<=) :: SomeSing k -> SomeSing k -> Bool #

(>) :: SomeSing k -> SomeSing k -> Bool #

(>=) :: SomeSing k -> SomeSing k -> Bool #

max :: SomeSing k -> SomeSing k -> SomeSing k #

min :: SomeSing k -> SomeSing k -> SomeSing k #

ShowSing k => Show (SomeSing k) # 
Instance details

Defined in Data.Singletons

Methods

showsPrec :: Int -> SomeSing k -> ShowS #

show :: SomeSing k -> String #

showList :: [SomeSing k] -> ShowS #

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

Instances
SuppressUnusedWarnings (ErrorSym0 :: TyFun k06989586621679403140 k6989586621679403141 -> *) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Apply (ErrorSym0 :: TyFun k0 k2 -> *) (l :: k0) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Apply (ErrorSym0 :: TyFun k0 k2 -> *) (l :: k0) = (Error l :: k2)

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

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

The promotion of undefined.

sUndefined :: a Source #

The singleton for undefined.

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

Instances
SuppressUnusedWarnings ((==@#@$) :: TyFun a6989586621679311772 (TyFun a6989586621679311772 Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

type Apply ((==@#@$) :: TyFun a6989586621679311772 (TyFun a6989586621679311772 Bool -> Type) -> *) (l :: a6989586621679311772) = (==@#@$$) l

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

Instances
SuppressUnusedWarnings ((==@#@$$) :: a6989586621679311772 -> TyFun a6989586621679311772 Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

type Apply ((==@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) = l1 == l2

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

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

Instances
SuppressUnusedWarnings ((>@#@$) :: TyFun a6989586621679323527 (TyFun a6989586621679323527 Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>@#@$) :: TyFun a6989586621679323527 (TyFun a6989586621679323527 Bool -> Type) -> *) (l :: a6989586621679323527) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>@#@$) :: TyFun a6989586621679323527 (TyFun a6989586621679323527 Bool -> Type) -> *) (l :: a6989586621679323527) = (>@#@$$) l

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

Instances
SuppressUnusedWarnings ((>@#@$$) :: a6989586621679323527 -> TyFun a6989586621679323527 Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

type Apply ((>@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) = l1 > l2

type (>@#@$$$) (t :: a6989586621679323527) (t :: a6989586621679323527) = (>) 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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

type Apply (Tuple2Sym1 l1 :: TyFun k1 (k2, k1) -> *) (l2 :: k1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

type Apply (Tuple3Sym2 l1 l2 :: TyFun k3 (k2, k1, k3) -> *) (l3 :: k3) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

type Apply (Tuple4Sym3 l1 l2 l3 :: TyFun k4 (k2, k1, k3, k4) -> *) (l4 :: k4) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

type Apply (Tuple5Sym4 l1 l2 l3 l4 :: TyFun k5 (k2, k1, k3, k4, k5) -> *) (l5 :: k5) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

type Apply (Tuple6Sym5 l1 l2 l3 l4 l5 :: TyFun k6 (k2, k1, k3, k4, k5, k6) -> *) (l6 :: k6) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

type Apply (Tuple7Sym6 l1 l2 l3 l4 l5 l6 :: TyFun k7 (k2, k1, k3, k4, k5, k6, k7) -> *) (l7 :: k7) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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 a6989586621679323527 (TyFun a6989586621679323527 Ordering -> Type)) Source #

Instances
SuppressUnusedWarnings (CompareSym0 :: TyFun a6989586621679323527 (TyFun a6989586621679323527 Ordering -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (CompareSym0 :: TyFun a6989586621679323527 (TyFun a6989586621679323527 Ordering -> Type) -> *) (l :: a6989586621679323527) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (CompareSym0 :: TyFun a6989586621679323527 (TyFun a6989586621679323527 Ordering -> Type) -> *) (l :: a6989586621679323527) = CompareSym1 l

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

Instances
SuppressUnusedWarnings (CompareSym1 :: a6989586621679323527 -> TyFun a6989586621679323527 Ordering -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (CompareSym1 l1 :: TyFun a Ordering -> *) (l2 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (CompareSym1 l1 :: TyFun a Ordering -> *) (l2 :: a) = Compare l1 l2

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

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

Instances
SuppressUnusedWarnings ThenCmpSym1 Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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 b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (FoldlSym0 :: TyFun (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (FoldlSym0 :: TyFun (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> Type) -> *) (l :: TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (FoldlSym0 :: TyFun (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> Type) -> *) (l :: TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) = FoldlSym1 l

data FoldlSym1 (l :: TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (l :: TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type)) Source #

Instances
SuppressUnusedWarnings (FoldlSym1 :: (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) -> TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (FoldlSym1 l1 :: TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> *) (l2 :: b6989586621679273480) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (FoldlSym1 l1 :: TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> *) (l2 :: b6989586621679273480) = FoldlSym2 l1 l2

data FoldlSym2 (l :: TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (l :: b6989586621679273480) (l :: TyFun [a6989586621679273479] b6989586621679273480) Source #

Instances
SuppressUnusedWarnings (FoldlSym2 :: (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) -> b6989586621679273480 -> TyFun [a6989586621679273479] b6989586621679273480 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (FoldlSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (FoldlSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) = Foldl l1 l2 l3

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

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

Instances
SuppressUnusedWarnings (ShowsPrecSym0 :: TyFun Nat (TyFun a6989586621679729880 (TyFun Symbol Symbol -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrecSym0 :: TyFun Nat (TyFun a6989586621679729880 (TyFun Symbol Symbol -> Type) -> Type) -> *) (l :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrecSym0 :: TyFun Nat (TyFun a6989586621679729880 (TyFun Symbol Symbol -> Type) -> Type) -> *) (l :: Nat) = (ShowsPrecSym1 l :: TyFun a6989586621679729880 (TyFun Symbol Symbol -> Type) -> *)

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

Instances
SuppressUnusedWarnings (ShowsPrecSym1 :: Nat -> TyFun a6989586621679729880 (TyFun Symbol Symbol -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrecSym1 l1 :: TyFun a6989586621679729880 (TyFun Symbol Symbol -> Type) -> *) (l2 :: a6989586621679729880) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrecSym1 l1 :: TyFun a6989586621679729880 (TyFun Symbol Symbol -> Type) -> *) (l2 :: a6989586621679729880) = ShowsPrecSym2 l1 l2

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

Instances
SuppressUnusedWarnings (ShowsPrecSym2 :: Nat -> a6989586621679729880 -> TyFun Symbol Symbol -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrecSym2 l1 l2 :: TyFun Symbol Symbol -> *) (l3 :: Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrecSym2 l1 l2 :: TyFun Symbol Symbol -> *) (l3 :: Symbol) = ShowsPrec l1 l2 l3

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

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

Instances
SuppressUnusedWarnings ShowStringSym1 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

type Apply (ShowParenSym2 l1 l2 :: TyFun Symbol Symbol -> *) (l3 :: Symbol) = ShowParen l1 l2 l3

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

Instances
SuppressUnusedWarnings ShowCharSym1 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Show

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 b6989586621679448463 c6989586621679448464 -> Type) (TyFun (TyFun a6989586621679448465 b6989586621679448463 -> Type) (TyFun a6989586621679448465 c6989586621679448464 -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings ((.@#@$) :: TyFun (TyFun b6989586621679448463 c6989586621679448464 -> Type) (TyFun (TyFun a6989586621679448465 b6989586621679448463 -> Type) (TyFun a6989586621679448465 c6989586621679448464 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((.@#@$) :: TyFun (TyFun b6989586621679448463 c6989586621679448464 -> Type) (TyFun (TyFun a6989586621679448465 b6989586621679448463 -> Type) (TyFun a6989586621679448465 c6989586621679448464 -> Type) -> Type) -> *) (l :: TyFun b6989586621679448463 c6989586621679448464 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((.@#@$) :: TyFun (TyFun b6989586621679448463 c6989586621679448464 -> Type) (TyFun (TyFun a6989586621679448465 b6989586621679448463 -> Type) (TyFun a6989586621679448465 c6989586621679448464 -> Type) -> Type) -> *) (l :: TyFun b6989586621679448463 c6989586621679448464 -> Type) = ((.@#@$$) l :: TyFun (TyFun a6989586621679448465 b6989586621679448463 -> Type) (TyFun a6989586621679448465 c6989586621679448464 -> Type) -> *)

data (l :: TyFun b6989586621679448463 c6989586621679448464 -> Type) .@#@$$ (l :: TyFun (TyFun a6989586621679448465 b6989586621679448463 -> Type) (TyFun a6989586621679448465 c6989586621679448464 -> Type)) Source #

Instances
SuppressUnusedWarnings ((.@#@$$) :: (TyFun b6989586621679448463 c6989586621679448464 -> Type) -> TyFun (TyFun a6989586621679448465 b6989586621679448463 -> Type) (TyFun a6989586621679448465 c6989586621679448464 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((.@#@$$) l1 :: TyFun (TyFun a6989586621679448465 b6989586621679448463 -> Type) (TyFun a6989586621679448465 c6989586621679448464 -> Type) -> *) (l2 :: TyFun a6989586621679448465 b6989586621679448463 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((.@#@$$) l1 :: TyFun (TyFun a6989586621679448465 b6989586621679448463 -> Type) (TyFun a6989586621679448465 c6989586621679448464 -> Type) -> *) (l2 :: TyFun a6989586621679448465 b6989586621679448463 -> Type) = l1 .@#@$$$ l2

data ((l :: TyFun b6989586621679448463 c6989586621679448464 -> Type) .@#@$$$ (l :: TyFun a6989586621679448465 b6989586621679448463 -> Type)) (l :: TyFun a6989586621679448465 c6989586621679448464) Source #

Instances
SuppressUnusedWarnings ((.@#@$$$) :: (TyFun b6989586621679448463 c6989586621679448464 -> Type) -> (TyFun a6989586621679448465 b6989586621679448463 -> Type) -> TyFun a6989586621679448465 c6989586621679448464 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (l1 .@#@$$$ l2 :: TyFun a c -> *) (l3 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (l1 .@#@$$$ l2 :: TyFun a c -> *) (l3 :: a) = (l1 :. l2) l3

type (.@#@$$$$) (t :: TyFun b6989586621679448463 c6989586621679448464 -> Type) (t :: TyFun a6989586621679448465 b6989586621679448463 -> Type) (t :: a6989586621679448465) = (:.) t t t Source #

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

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (&&@#@$$) Source # 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (||@#@$$) Source # 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings ShowParenSym1 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings ThenCmpSym1 Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (~>@#@$$) Source # 
Instance details

Defined in Data.Singletons

SuppressUnusedWarnings (^@#@$$) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

SuppressUnusedWarnings DivSym1 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings ModSym1 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings QuotSym1 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings RemSym1 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings QuotRemSym1 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings DivModSym1 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings (<>@#@$$) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

SuppressUnusedWarnings ShowCharSym1 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings ShowStringSym1 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings NotSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (&&@#@$) Source # 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (||@#@$) Source # 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings ShowParenSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings AndSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings OrSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings UnlinesSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings UnwordsSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings ThenCmpSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (~>@#@$) Source # 
Instance details

Defined in Data.Singletons

SuppressUnusedWarnings DemoteSym0 Source # 
Instance details

Defined in Data.Singletons

SuppressUnusedWarnings (^@#@$) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

SuppressUnusedWarnings DivSym0 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings ModSym0 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings QuotSym0 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings RemSym0 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings QuotRemSym0 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings DivModSym0 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings KnownNatSym0 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings Log2Sym0 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings ShowCharSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings ShowStringSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (<>@#@$) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

SuppressUnusedWarnings KnownSymbolSym0 Source # 
Instance details

Defined in Data.Singletons.TypeLits

SuppressUnusedWarnings ShowCommaSpaceSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings ShowSpaceSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings XorSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (NubBySym1 :: (TyFun a6989586621679472919 (TyFun a6989586621679472919 Bool -> Type) -> Type) -> TyFun [a6989586621679472919] [a6989586621679472919] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (PartitionSym1 :: (TyFun a6989586621679472928 Bool -> Type) -> TyFun [a6989586621679472928] ([a6989586621679472928], [a6989586621679472928]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (BreakSym1 :: (TyFun a6989586621679472940 Bool -> Type) -> TyFun [a6989586621679472940] ([a6989586621679472940], [a6989586621679472940]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (SpanSym1 :: (TyFun a6989586621679472941 Bool -> Type) -> TyFun [a6989586621679472941] ([a6989586621679472941], [a6989586621679472941]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (GroupBySym1 :: (TyFun a6989586621679472931 (TyFun a6989586621679472931 Bool -> Type) -> Type) -> TyFun [a6989586621679472931] [[a6989586621679472931]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (DropWhileSym1 :: (TyFun a6989586621679472943 Bool -> Type) -> TyFun [a6989586621679472943] [a6989586621679472943] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (TakeWhileSym1 :: (TyFun a6989586621679472944 Bool -> Type) -> TyFun [a6989586621679472944] [a6989586621679472944] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (FilterSym1 :: (TyFun a6989586621679472952 Bool -> Type) -> TyFun [a6989586621679472952] [a6989586621679472952] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (FindSym1 :: (TyFun a6989586621679472951 Bool -> Type) -> TyFun [a6989586621679472951] (Maybe a6989586621679472951) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (InsertBySym1 :: (TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) -> TyFun a6989586621679472955 (TyFun [a6989586621679472955] [a6989586621679472955] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (InsertBySym2 :: (TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) -> a6989586621679472955 -> TyFun [a6989586621679472955] [a6989586621679472955] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (SortBySym1 :: (TyFun a6989586621679472956 (TyFun a6989586621679472956 Ordering -> Type) -> Type) -> TyFun [a6989586621679472956] [a6989586621679472956] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (DeleteBySym1 :: (TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) -> TyFun a6989586621679472958 (TyFun [a6989586621679472958] [a6989586621679472958] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (DeleteBySym2 :: (TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) -> a6989586621679472958 -> TyFun [a6989586621679472958] [a6989586621679472958] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (DeleteFirstsBySym2 :: (TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) -> [a6989586621679472957] -> TyFun [a6989586621679472957] [a6989586621679472957] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (DeleteFirstsBySym1 :: (TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) -> TyFun [a6989586621679472957] (TyFun [a6989586621679472957] [a6989586621679472957] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (UnionBySym2 :: (TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) -> [a6989586621679472917] -> TyFun [a6989586621679472917] [a6989586621679472917] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (UnionBySym1 :: (TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) -> TyFun [a6989586621679472917] (TyFun [a6989586621679472917] [a6989586621679472917] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (FindIndicesSym1 :: (TyFun a6989586621679472947 Bool -> Type) -> TyFun [a6989586621679472947] [Nat] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (FindIndexSym1 :: (TyFun a6989586621679472948 Bool -> Type) -> TyFun [a6989586621679472948] (Maybe Nat) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Scanr1Sym1 :: (TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) -> TyFun [a6989586621679473015] [a6989586621679473015] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Scanl1Sym1 :: (TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) -> TyFun [a6989586621679473018] [a6989586621679473018] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (AnySym1 :: (TyFun a6989586621679473021 Bool -> Type) -> TyFun [a6989586621679473021] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IntersectBySym2 :: (TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) -> [a6989586621679472945] -> TyFun [a6989586621679472945] [a6989586621679472945] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IntersectBySym1 :: (TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) -> TyFun [a6989586621679472945] (TyFun [a6989586621679472945] [a6989586621679472945] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (AllSym1 :: (TyFun a6989586621679473022 Bool -> Type) -> TyFun [a6989586621679473022] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Foldr1Sym1 :: (TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) -> TyFun [a6989586621679473026] a6989586621679473026 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Foldl1Sym1 :: (TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) -> TyFun [a6989586621679473028] a6989586621679473028 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (MaximumBySym1 :: (TyFun a6989586621679472954 (TyFun a6989586621679472954 Ordering -> Type) -> Type) -> TyFun [a6989586621679472954] a6989586621679472954 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (MinimumBySym1 :: (TyFun a6989586621679472953 (TyFun a6989586621679472953 Ordering -> Type) -> Type) -> TyFun [a6989586621679472953] a6989586621679472953 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Foldl1'Sym1 :: (TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) -> TyFun [a6989586621679473027] a6989586621679473027 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (DropWhileEndSym1 :: (TyFun a6989586621679472942 Bool -> Type) -> TyFun [a6989586621679472942] [a6989586621679472942] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ShowListWithSym2 :: (TyFun a6989586621679729864 (TyFun Symbol Symbol -> Type) -> Type) -> [a6989586621679729864] -> TyFun Symbol Symbol -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (ShowListWithSym1 :: (TyFun a6989586621679729864 (TyFun Symbol Symbol -> Type) -> Type) -> TyFun [a6989586621679729864] (TyFun Symbol Symbol -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (NubBySym1 :: (TyFun a6989586621679833967 (TyFun a6989586621679833967 Bool -> Type) -> Type) -> TyFun (NonEmpty a6989586621679833967) (NonEmpty a6989586621679833967) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupBySym1 :: (TyFun a6989586621679833988 (TyFun a6989586621679833988 Bool -> Type) -> Type) -> TyFun [a6989586621679833988] [NonEmpty a6989586621679833988] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupBy1Sym1 :: (TyFun a6989586621679833982 (TyFun a6989586621679833982 Bool -> Type) -> Type) -> TyFun (NonEmpty a6989586621679833982) (NonEmpty (NonEmpty a6989586621679833982)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (TakeWhileSym1 :: (TyFun a6989586621679833995 Bool -> Type) -> TyFun (NonEmpty a6989586621679833995) [a6989586621679833995] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (DropWhileSym1 :: (TyFun a6989586621679833994 Bool -> Type) -> TyFun (NonEmpty a6989586621679833994) [a6989586621679833994] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SpanSym1 :: (TyFun a6989586621679833993 Bool -> Type) -> TyFun (NonEmpty a6989586621679833993) ([a6989586621679833993], [a6989586621679833993]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (BreakSym1 :: (TyFun a6989586621679833992 Bool -> Type) -> TyFun (NonEmpty a6989586621679833992) ([a6989586621679833992], [a6989586621679833992]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (FilterSym1 :: (TyFun a6989586621679833991 Bool -> Type) -> TyFun (NonEmpty a6989586621679833991) [a6989586621679833991] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (PartitionSym1 :: (TyFun a6989586621679833990 Bool -> Type) -> TyFun (NonEmpty a6989586621679833990) ([a6989586621679833990], [a6989586621679833990]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SortBySym1 :: (TyFun a6989586621679833965 (TyFun a6989586621679833965 Ordering -> Type) -> Type) -> TyFun (NonEmpty a6989586621679833965) (NonEmpty a6989586621679833965) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (Scanl1Sym1 :: (TyFun a6989586621679834002 (TyFun a6989586621679834002 a6989586621679834002 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679834002) (NonEmpty a6989586621679834002) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (Scanr1Sym1 :: (TyFun a6989586621679834001 (TyFun a6989586621679834001 a6989586621679834001 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679834001) (NonEmpty a6989586621679834001) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (UntilSym2 :: (TyFun a6989586621680044097 Bool -> Type) -> (TyFun a6989586621680044097 a6989586621680044097 -> Type) -> TyFun a6989586621680044097 a6989586621680044097 -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.Base

SuppressUnusedWarnings (UntilSym1 :: (TyFun a6989586621680044097 Bool -> Type) -> TyFun (TyFun a6989586621680044097 a6989586621680044097 -> Type) (TyFun a6989586621680044097 a6989586621680044097 -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.Base

SuppressUnusedWarnings ((++@#@$$) :: [a6989586621679448469] -> TyFun [a6989586621679448469] [a6989586621679448469] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings ((!!@#@$$) :: [a6989586621679472921] -> TyFun Nat a6989586621679472921 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (UnionSym1 :: [a6989586621679472916] -> TyFun [a6989586621679472916] [a6989586621679472916] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings ((\\@#@$$) :: [a6989586621679472959] -> TyFun [a6989586621679472959] [a6989586621679472959] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IsPrefixOfSym1 :: [a6989586621679473004] -> TyFun [a6989586621679473004] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IsInfixOfSym1 :: [a6989586621679473002] -> TyFun [a6989586621679473002] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IntersectSym1 :: [a6989586621679472946] -> TyFun [a6989586621679472946] [a6989586621679472946] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IntercalateSym1 :: [a6989586621679473035] -> TyFun [[a6989586621679473035]] [a6989586621679473035] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IsSuffixOfSym1 :: [a6989586621679473003] -> TyFun [a6989586621679473003] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ShowListSym1 :: [a6989586621679729880] -> TyFun Symbol Symbol -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (IsPrefixOfSym1 :: [a6989586621679833977] -> TyFun (NonEmpty a6989586621679833977) Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (StripPrefixSym1 :: [a6989586621680003314] -> TyFun [a6989586621680003314] (Maybe [a6989586621680003314]) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ShowsPrecSym2 :: Nat -> a6989586621679729880 -> TyFun Symbol Symbol -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (DropSym1 :: Nat -> TyFun [a6989586621679472938] [a6989586621679472938] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (TakeSym1 :: Nat -> TyFun [a6989586621679472939] [a6989586621679472939] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (SplitAtSym1 :: Nat -> TyFun [a6989586621679472937] ([a6989586621679472937], [a6989586621679472937]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ReplicateSym1 :: Nat -> TyFun a6989586621679472923 [a6989586621679472923] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ShowsPrecSym1 :: Nat -> TyFun a6989586621679729880 (TyFun Symbol Symbol -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (TakeSym1 :: Nat -> TyFun (NonEmpty a6989586621679833998) [a6989586621679833998] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (DropSym1 :: Nat -> TyFun (NonEmpty a6989586621679833997) [a6989586621679833997] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SplitAtSym1 :: Nat -> TyFun (NonEmpty a6989586621679833996) ([a6989586621679833996], [a6989586621679833996]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings ((:@#@$$) :: a3530822107858468865 -> TyFun [a3530822107858468865] [a3530822107858468865] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings ((:|@#@$$) :: a6989586621679068306 -> TyFun [a6989586621679068306] (NonEmpty a6989586621679068306) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Bool_Sym2 :: a6989586621679308852 -> a6989586621679308852 -> TyFun Bool a6989586621679308852 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (Bool_Sym1 :: a6989586621679308852 -> TyFun a6989586621679308852 (TyFun Bool a6989586621679308852 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings ((==@#@$$) :: a6989586621679311772 -> TyFun a6989586621679311772 Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings ((/=@#@$$) :: a6989586621679311772 -> TyFun a6989586621679311772 Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings ((<=@#@$$) :: a6989586621679323527 -> TyFun a6989586621679323527 Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (CompareSym1 :: a6989586621679323527 -> TyFun a6989586621679323527 Ordering -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (MinSym1 :: a6989586621679323527 -> TyFun a6989586621679323527 a6989586621679323527 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (MaxSym1 :: a6989586621679323527 -> TyFun a6989586621679323527 a6989586621679323527 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>=@#@$$) :: a6989586621679323527 -> TyFun a6989586621679323527 Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>@#@$$) :: a6989586621679323527 -> TyFun a6989586621679323527 Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((<@#@$$) :: a6989586621679323527 -> TyFun a6989586621679323527 Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (FromMaybeSym1 :: a6989586621679430982 -> TyFun (Maybe a6989586621679430982) a6989586621679430982 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings ((-@#@$$) :: a6989586621679440260 -> TyFun a6989586621679440260 a6989586621679440260 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Num

SuppressUnusedWarnings ((+@#@$$) :: a6989586621679440260 -> TyFun a6989586621679440260 a6989586621679440260 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Num

SuppressUnusedWarnings ((*@#@$$) :: a6989586621679440260 -> TyFun a6989586621679440260 a6989586621679440260 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Num

SuppressUnusedWarnings (SubtractSym1 :: a6989586621679442533 -> TyFun a6989586621679442533 a6989586621679442533 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Num

SuppressUnusedWarnings (AsTypeOfSym1 :: a6989586621679448459 -> TyFun a6989586621679448459 a6989586621679448459 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (InsertSym1 :: a6989586621679472933 -> TyFun [a6989586621679472933] [a6989586621679472933] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (DeleteSym1 :: a6989586621679472960 -> TyFun [a6989586621679472960] [a6989586621679472960] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ElemIndicesSym1 :: a6989586621679472949 -> TyFun [a6989586621679472949] [Nat] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ElemIndexSym1 :: a6989586621679472950 -> TyFun [a6989586621679472950] (Maybe Nat) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (NotElemSym1 :: a6989586621679473000 -> TyFun [a6989586621679473000] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ElemSym1 :: a6989586621679473001 -> TyFun [a6989586621679473001] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IntersperseSym1 :: a6989586621679473036 -> TyFun [a6989586621679473036] [a6989586621679473036] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ShowsSym1 :: a6989586621679729865 -> TyFun Symbol Symbol -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (IntersperseSym1 :: a6989586621679834000 -> TyFun (NonEmpty a6989586621679834000) (NonEmpty a6989586621679834000) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (InsertSym1 :: a6989586621679834007 -> TyFun [a6989586621679834007] (NonEmpty a6989586621679834007) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings ((<|@#@$$) :: a6989586621679834018 -> TyFun (NonEmpty a6989586621679834018) (NonEmpty a6989586621679834018) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ConsSym1 :: a6989586621679834017 -> TyFun (NonEmpty a6989586621679834017) (NonEmpty a6989586621679834017) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (EnumFromThenToSym1 :: a6989586621679916796 -> TyFun a6989586621679916796 (TyFun a6989586621679916796 [a6989586621679916796] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (EnumFromThenToSym2 :: a6989586621679916796 -> a6989586621679916796 -> TyFun a6989586621679916796 [a6989586621679916796] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (EnumFromToSym1 :: a6989586621679916796 -> TyFun a6989586621679916796 [a6989586621679916796] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (SameKindSym1 :: k6989586621679027070 -> TyFun k6989586621679027070 Constraint -> *) Source # 
Instance details

Defined in Data.Singletons

SuppressUnusedWarnings ((!!@#@$$) :: NonEmpty a6989586621679833976 -> TyFun Nat a6989586621679833976 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (NubBySym0 :: TyFun (TyFun a6989586621679472919 (TyFun a6989586621679472919 Bool -> Type) -> Type) (TyFun [a6989586621679472919] [a6989586621679472919] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (PartitionSym0 :: TyFun (TyFun a6989586621679472928 Bool -> Type) (TyFun [a6989586621679472928] ([a6989586621679472928], [a6989586621679472928]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (BreakSym0 :: TyFun (TyFun a6989586621679472940 Bool -> Type) (TyFun [a6989586621679472940] ([a6989586621679472940], [a6989586621679472940]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (SpanSym0 :: TyFun (TyFun a6989586621679472941 Bool -> Type) (TyFun [a6989586621679472941] ([a6989586621679472941], [a6989586621679472941]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (GroupBySym0 :: TyFun (TyFun a6989586621679472931 (TyFun a6989586621679472931 Bool -> Type) -> Type) (TyFun [a6989586621679472931] [[a6989586621679472931]] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (DropWhileSym0 :: TyFun (TyFun a6989586621679472943 Bool -> Type) (TyFun [a6989586621679472943] [a6989586621679472943] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (TyFun a6989586621679472944 Bool -> Type) (TyFun [a6989586621679472944] [a6989586621679472944] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (FilterSym0 :: TyFun (TyFun a6989586621679472952 Bool -> Type) (TyFun [a6989586621679472952] [a6989586621679472952] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (FindSym0 :: TyFun (TyFun a6989586621679472951 Bool -> Type) (TyFun [a6989586621679472951] (Maybe a6989586621679472951) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (InsertBySym0 :: TyFun (TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) (TyFun a6989586621679472955 (TyFun [a6989586621679472955] [a6989586621679472955] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (SortBySym0 :: TyFun (TyFun a6989586621679472956 (TyFun a6989586621679472956 Ordering -> Type) -> Type) (TyFun [a6989586621679472956] [a6989586621679472956] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (DeleteBySym0 :: TyFun (TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) (TyFun a6989586621679472958 (TyFun [a6989586621679472958] [a6989586621679472958] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) (TyFun [a6989586621679472957] (TyFun [a6989586621679472957] [a6989586621679472957] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (UnionBySym0 :: TyFun (TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) (TyFun [a6989586621679472917] (TyFun [a6989586621679472917] [a6989586621679472917] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (TyFun a6989586621679472947 Bool -> Type) (TyFun [a6989586621679472947] [Nat] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (FindIndexSym0 :: TyFun (TyFun a6989586621679472948 Bool -> Type) (TyFun [a6989586621679472948] (Maybe Nat) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) (TyFun [a6989586621679473015] [a6989586621679473015] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) (TyFun [a6989586621679473018] [a6989586621679473018] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (AnySym0 :: TyFun (TyFun a6989586621679473021 Bool -> Type) (TyFun [a6989586621679473021] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IntersectBySym0 :: TyFun (TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) (TyFun [a6989586621679472945] (TyFun [a6989586621679472945] [a6989586621679472945] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (AllSym0 :: TyFun (TyFun a6989586621679473022 Bool -> Type) (TyFun [a6989586621679473022] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) (TyFun [a6989586621679473026] a6989586621679473026 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) (TyFun [a6989586621679473028] a6989586621679473028 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (MaximumBySym0 :: TyFun (TyFun a6989586621679472954 (TyFun a6989586621679472954 Ordering -> Type) -> Type) (TyFun [a6989586621679472954] a6989586621679472954 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (MinimumBySym0 :: TyFun (TyFun a6989586621679472953 (TyFun a6989586621679472953 Ordering -> Type) -> Type) (TyFun [a6989586621679472953] a6989586621679472953 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) (TyFun [a6989586621679473027] a6989586621679473027 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (TyFun a6989586621679472942 Bool -> Type) (TyFun [a6989586621679472942] [a6989586621679472942] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ShowListWithSym0 :: TyFun (TyFun a6989586621679729864 (TyFun Symbol Symbol -> Type) -> Type) (TyFun [a6989586621679729864] (TyFun Symbol Symbol -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (NubBySym0 :: TyFun (TyFun a6989586621679833967 (TyFun a6989586621679833967 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679833967) (NonEmpty a6989586621679833967) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupBySym0 :: TyFun (TyFun a6989586621679833988 (TyFun a6989586621679833988 Bool -> Type) -> Type) (TyFun [a6989586621679833988] [NonEmpty a6989586621679833988] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupBy1Sym0 :: TyFun (TyFun a6989586621679833982 (TyFun a6989586621679833982 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679833982) (NonEmpty (NonEmpty a6989586621679833982)) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (TyFun a6989586621679833995 Bool -> Type) (TyFun (NonEmpty a6989586621679833995) [a6989586621679833995] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (DropWhileSym0 :: TyFun (TyFun a6989586621679833994 Bool -> Type) (TyFun (NonEmpty a6989586621679833994) [a6989586621679833994] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SpanSym0 :: TyFun (TyFun a6989586621679833993 Bool -> Type) (TyFun (NonEmpty a6989586621679833993) ([a6989586621679833993], [a6989586621679833993]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (BreakSym0 :: TyFun (TyFun a6989586621679833992 Bool -> Type) (TyFun (NonEmpty a6989586621679833992) ([a6989586621679833992], [a6989586621679833992]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (FilterSym0 :: TyFun (TyFun a6989586621679833991 Bool -> Type) (TyFun (NonEmpty a6989586621679833991) [a6989586621679833991] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (PartitionSym0 :: TyFun (TyFun a6989586621679833990 Bool -> Type) (TyFun (NonEmpty a6989586621679833990) ([a6989586621679833990], [a6989586621679833990]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SortBySym0 :: TyFun (TyFun a6989586621679833965 (TyFun a6989586621679833965 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679833965) (NonEmpty a6989586621679833965) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (TyFun a6989586621679834002 (TyFun a6989586621679834002 a6989586621679834002 -> Type) -> Type) (TyFun (NonEmpty a6989586621679834002) (NonEmpty a6989586621679834002) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (TyFun a6989586621679834001 (TyFun a6989586621679834001 a6989586621679834001 -> Type) -> Type) (TyFun (NonEmpty a6989586621679834001) (NonEmpty a6989586621679834001) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (UntilSym0 :: TyFun (TyFun a6989586621680044097 Bool -> Type) (TyFun (TyFun a6989586621680044097 a6989586621680044097 -> Type) (TyFun a6989586621680044097 a6989586621680044097 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.Base

SuppressUnusedWarnings (ConcatSym0 :: TyFun [[a6989586621679473025]] [a6989586621679473025] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a6989586621679472922]] [[a6989586621679472922]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (CatMaybesSym0 :: TyFun [Maybe a6989586621679430979] [a6989586621679430979] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (ListToMaybeSym0 :: TyFun [a6989586621679430980] (Maybe a6989586621679430980) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679448469] (TyFun [a6989586621679448469] [a6989586621679448469] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings ((!!@#@$) :: TyFun [a6989586621679472921] (TyFun Nat a6989586621679472921 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (LengthSym0 :: TyFun [a6989586621679472924] Nat -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ProductSym0 :: TyFun [a6989586621679472925] a6989586621679472925 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (SumSym0 :: TyFun [a6989586621679472926] a6989586621679472926 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621679472936] [[a6989586621679472936]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (SortSym0 :: TyFun [a6989586621679472932] [a6989586621679472932] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (UnionSym0 :: TyFun [a6989586621679472916] (TyFun [a6989586621679472916] [a6989586621679472916] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings ((\\@#@$) :: TyFun [a6989586621679472959] (TyFun [a6989586621679472959] [a6989586621679472959] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (NubSym0 :: TyFun [a6989586621679472920] [a6989586621679472920] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679473004] (TyFun [a6989586621679473004] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621679473005] [[a6989586621679473005]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621679473006] [[a6989586621679473006]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a6989586621679473002] (TyFun [a6989586621679473002] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IntersectSym0 :: TyFun [a6989586621679472946] (TyFun [a6989586621679472946] [a6989586621679472946] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (MaximumSym0 :: TyFun [a6989586621679472935] a6989586621679472935 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (MinimumSym0 :: TyFun [a6989586621679472934] a6989586621679472934 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a6989586621679473031] [[a6989586621679473031]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a6989586621679473034] [[a6989586621679473034]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a6989586621679473035] (TyFun [[a6989586621679473035]] [a6989586621679473035] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ReverseSym0 :: TyFun [a6989586621679473037] [a6989586621679473037] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679473003] (TyFun [a6989586621679473003] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (NullSym0 :: TyFun [a6989586621679473038] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (InitSym0 :: TyFun [a6989586621679473039] [a6989586621679473039] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (TailSym0 :: TyFun [a6989586621679473040] [a6989586621679473040] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (LastSym0 :: TyFun [a6989586621679473041] a6989586621679473041 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (HeadSym0 :: TyFun [a6989586621679473042] a6989586621679473042 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ShowListSym0 :: TyFun [a6989586621679729880] (TyFun Symbol Symbol -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679833977] (TyFun (NonEmpty a6989586621679833977) Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621679833989] [NonEmpty a6989586621679833989] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (FromListSym0 :: TyFun [a6989586621679834015] (NonEmpty a6989586621679834015) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621679834009] (NonEmpty [a6989586621679834009]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621679834008] (NonEmpty [a6989586621679834008]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (NonEmpty_Sym0 :: TyFun [a6989586621679834026] (Maybe (NonEmpty a6989586621679834026)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a6989586621680003314] (TyFun [a6989586621680003314] (Maybe [a6989586621680003314]) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (MaybeToListSym0 :: TyFun (Maybe a6989586621679430981) [a6989586621679430981] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (FromJustSym0 :: TyFun (Maybe a6989586621679430983) a6989586621679430983 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (IsNothingSym0 :: TyFun (Maybe a6989586621679430984) Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (IsJustSym0 :: TyFun (Maybe a6989586621679430985) Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (DropSym0 :: TyFun Nat (TyFun [a6989586621679472938] [a6989586621679472938] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (TakeSym0 :: TyFun Nat (TyFun [a6989586621679472939] [a6989586621679472939] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat (TyFun [a6989586621679472937] ([a6989586621679472937], [a6989586621679472937]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ReplicateSym0 :: TyFun Nat (TyFun a6989586621679472923 [a6989586621679472923] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ShowsPrecSym0 :: TyFun Nat (TyFun a6989586621679729880 (TyFun Symbol Symbol -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (TakeSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679833998) [a6989586621679833998] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (DropSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679833997) [a6989586621679833997] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679833996) ([a6989586621679833996], [a6989586621679833996]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (FromIntegerSym0 :: TyFun Nat a6989586621679440260 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Num

SuppressUnusedWarnings (ToEnumSym0 :: TyFun Nat a6989586621679916796 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (FromStringSym0 :: TyFun Symbol a6989586621679439496 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.IsString

SuppressUnusedWarnings (JustSym0 :: TyFun a3530822107858468865 (Maybe a3530822107858468865) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings ((:@#@$) :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings ((:|@#@$) :: TyFun a6989586621679068306 (TyFun [a6989586621679068306] (NonEmpty a6989586621679068306) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Bool_Sym0 :: TyFun a6989586621679308852 (TyFun a6989586621679308852 (TyFun Bool a6989586621679308852 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings ((==@#@$) :: TyFun a6989586621679311772 (TyFun a6989586621679311772 Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings ((/=@#@$) :: TyFun a6989586621679311772 (TyFun a6989586621679311772 Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings ((<=@#@$) :: TyFun a6989586621679323527 (TyFun a6989586621679323527 Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (CompareSym0 :: TyFun a6989586621679323527 (TyFun a6989586621679323527 Ordering -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (MinSym0 :: TyFun a6989586621679323527 (TyFun a6989586621679323527 a6989586621679323527 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (MaxSym0 :: TyFun a6989586621679323527 (TyFun a6989586621679323527 a6989586621679323527 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>=@#@$) :: TyFun a6989586621679323527 (TyFun a6989586621679323527 Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>@#@$) :: TyFun a6989586621679323527 (TyFun a6989586621679323527 Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((<@#@$) :: TyFun a6989586621679323527 (TyFun a6989586621679323527 Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (FromMaybeSym0 :: TyFun a6989586621679430982 (TyFun (Maybe a6989586621679430982) a6989586621679430982 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (NegateSym0 :: TyFun a6989586621679440260 a6989586621679440260 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Num

SuppressUnusedWarnings ((-@#@$) :: TyFun a6989586621679440260 (TyFun a6989586621679440260 a6989586621679440260 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Num

SuppressUnusedWarnings ((+@#@$) :: TyFun a6989586621679440260 (TyFun a6989586621679440260 a6989586621679440260 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Num

SuppressUnusedWarnings (SignumSym0 :: TyFun a6989586621679440260 a6989586621679440260 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Num

SuppressUnusedWarnings (AbsSym0 :: TyFun a6989586621679440260 a6989586621679440260 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Num

SuppressUnusedWarnings ((*@#@$) :: TyFun a6989586621679440260 (TyFun a6989586621679440260 a6989586621679440260 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Num

SuppressUnusedWarnings (SubtractSym0 :: TyFun a6989586621679442533 (TyFun a6989586621679442533 a6989586621679442533 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Num

SuppressUnusedWarnings (AsTypeOfSym0 :: TyFun a6989586621679448459 (TyFun a6989586621679448459 a6989586621679448459 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (IdSym0 :: TyFun a6989586621679448468 a6989586621679448468 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621679472933 (TyFun [a6989586621679472933] [a6989586621679472933] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (DeleteSym0 :: TyFun a6989586621679472960 (TyFun [a6989586621679472960] [a6989586621679472960] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a6989586621679472949 (TyFun [a6989586621679472949] [Nat] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679472950 (TyFun [a6989586621679472950] (Maybe Nat) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621679473000 (TyFun [a6989586621679473000] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621679473001 (TyFun [a6989586621679473001] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679473036 (TyFun [a6989586621679473036] [a6989586621679473036] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Show_Sym0 :: TyFun a6989586621679729880 Symbol -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (ShowsSym0 :: TyFun a6989586621679729865 (TyFun Symbol Symbol -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679834000 (TyFun (NonEmpty a6989586621679834000) (NonEmpty a6989586621679834000) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621679834007 (TyFun [a6989586621679834007] (NonEmpty a6989586621679834007) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings ((<|@#@$) :: TyFun a6989586621679834018 (TyFun (NonEmpty a6989586621679834018) (NonEmpty a6989586621679834018) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ConsSym0 :: TyFun a6989586621679834017 (TyFun (NonEmpty a6989586621679834017) (NonEmpty a6989586621679834017) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (EnumFromThenToSym0 :: TyFun a6989586621679916796 (TyFun a6989586621679916796 (TyFun a6989586621679916796 [a6989586621679916796] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (EnumFromToSym0 :: TyFun a6989586621679916796 (TyFun a6989586621679916796 [a6989586621679916796] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (FromEnumSym0 :: TyFun a6989586621679916796 Nat -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (PredSym0 :: TyFun a6989586621679916796 a6989586621679916796 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (SuccSym0 :: TyFun a6989586621679916796 a6989586621679916796 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (SameKindSym0 :: TyFun k6989586621679027070 (TyFun k6989586621679027070 Constraint -> *) -> *) Source # 
Instance details

Defined in Data.Singletons

SuppressUnusedWarnings (KindOfSym0 :: TyFun k6989586621679027073 * -> *) Source # 
Instance details

Defined in Data.Singletons

SuppressUnusedWarnings (AbsurdSym0 :: TyFun Void a6989586621679303847 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Void

SuppressUnusedWarnings (NubSym0 :: TyFun (NonEmpty a6989586621679833968) (NonEmpty a6989586621679833968) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings ((!!@#@$) :: TyFun (NonEmpty a6989586621679833976) (TyFun Nat a6989586621679833976 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (Group1Sym0 :: TyFun (NonEmpty a6989586621679833983) (NonEmpty (NonEmpty a6989586621679833983)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ToListSym0 :: TyFun (NonEmpty a6989586621679834014) [a6989586621679834014] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ReverseSym0 :: TyFun (NonEmpty a6989586621679833999) (NonEmpty a6989586621679833999) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SortSym0 :: TyFun (NonEmpty a6989586621679834016) (NonEmpty a6989586621679834016) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (InitSym0 :: TyFun (NonEmpty a6989586621679834019) [a6989586621679834019] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (LastSym0 :: TyFun (NonEmpty a6989586621679834020) a6989586621679834020 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (TailSym0 :: TyFun (NonEmpty a6989586621679834021) [a6989586621679834021] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (HeadSym0 :: TyFun (NonEmpty a6989586621679834022) a6989586621679834022 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (UnconsSym0 :: TyFun (NonEmpty a6989586621679834025) (a6989586621679834025, Maybe (NonEmpty a6989586621679834025)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (LengthSym0 :: TyFun (NonEmpty a6989586621679834029) Nat -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a6989586621679833966)) (NonEmpty (NonEmpty a6989586621679833966)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (FoldlSym2 :: (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) -> b6989586621679273480 -> TyFun [a6989586621679273479] b6989586621679273480 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (FoldlSym1 :: (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) -> TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (ComparingSym2 :: (TyFun b6989586621679323517 a6989586621679323516 -> Type) -> b6989586621679323517 -> TyFun b6989586621679323517 Ordering -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (ComparingSym1 :: (TyFun b6989586621679323517 a6989586621679323516 -> Type) -> TyFun b6989586621679323517 (TyFun b6989586621679323517 Ordering -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (MapMaybeSym1 :: (TyFun a6989586621679430977 (Maybe b6989586621679430978) -> Type) -> TyFun [a6989586621679430977] [b6989586621679430978] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (($!@#@$$) :: (TyFun a6989586621679448455 b6989586621679448456 -> Type) -> TyFun a6989586621679448455 b6989586621679448456 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (($@#@$$) :: (TyFun a6989586621679448457 b6989586621679448458 -> Type) -> TyFun a6989586621679448457 b6989586621679448458 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (MapSym1 :: (TyFun a6989586621679448470 b6989586621679448471 -> Type) -> TyFun [a6989586621679448470] [b6989586621679448471] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (FoldrSym2 :: (TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) -> b6989586621679448473 -> TyFun [a6989586621679448472] b6989586621679448473 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (FoldrSym1 :: (TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) -> TyFun b6989586621679448473 (TyFun [a6989586621679448472] b6989586621679448473 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (UnfoldrSym1 :: (TyFun b6989586621679473007 (Maybe (a6989586621679473008, b6989586621679473007)) -> Type) -> TyFun b6989586621679473007 [a6989586621679473008] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ScanrSym1 :: (TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) -> TyFun b6989586621679473017 (TyFun [a6989586621679473016] [b6989586621679473017] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ScanrSym2 :: (TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) -> b6989586621679473017 -> TyFun [a6989586621679473016] [b6989586621679473017] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ScanlSym1 :: (TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) -> TyFun b6989586621679473019 (TyFun [a6989586621679473020] [b6989586621679473019] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ScanlSym2 :: (TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) -> b6989586621679473019 -> TyFun [a6989586621679473020] [b6989586621679473019] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ConcatMapSym1 :: (TyFun a6989586621679473023 [b6989586621679473024] -> Type) -> TyFun [a6989586621679473023] [b6989586621679473024] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Foldl'Sym2 :: (TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) -> b6989586621679473030 -> TyFun [a6989586621679473029] b6989586621679473030 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Foldl'Sym1 :: (TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) -> TyFun b6989586621679473030 (TyFun [a6989586621679473029] b6989586621679473030 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (GroupWithSym1 :: (TyFun a6989586621679833987 b6989586621679833986 -> Type) -> TyFun [a6989586621679833987] [NonEmpty a6989586621679833987] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupAllWithSym1 :: (TyFun a6989586621679833985 b6989586621679833984 -> Type) -> TyFun [a6989586621679833985] [NonEmpty a6989586621679833985] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupWith1Sym1 :: (TyFun a6989586621679833981 b6989586621679833980 -> Type) -> TyFun (NonEmpty a6989586621679833981) (NonEmpty (NonEmpty a6989586621679833981)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (MapSym1 :: (TyFun a6989586621679834010 b6989586621679834011 -> Type) -> TyFun (NonEmpty a6989586621679834010) (NonEmpty b6989586621679834011) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SortWithSym1 :: (TyFun a6989586621679833964 o6989586621679833963 -> Type) -> TyFun (NonEmpty a6989586621679833964) (NonEmpty a6989586621679833964) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupAllWith1Sym1 :: (TyFun a6989586621679833979 b6989586621679833978 -> Type) -> TyFun (NonEmpty a6989586621679833979) (NonEmpty (NonEmpty a6989586621679833979)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ScanlSym2 :: (TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) -> b6989586621679834005 -> TyFun [a6989586621679834006] (NonEmpty b6989586621679834005) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ScanlSym1 :: (TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) -> TyFun b6989586621679834005 (TyFun [a6989586621679834006] (NonEmpty b6989586621679834005) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ScanrSym2 :: (TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) -> b6989586621679834004 -> TyFun [a6989586621679834003] (NonEmpty b6989586621679834004) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ScanrSym1 :: (TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) -> TyFun b6989586621679834004 (TyFun [a6989586621679834003] (NonEmpty b6989586621679834004) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (UnfoldrSym1 :: (TyFun a6989586621679834023 (b6989586621679834024, Maybe a6989586621679834023) -> Type) -> TyFun a6989586621679834023 (NonEmpty b6989586621679834024) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (UnfoldSym1 :: (TyFun a6989586621679834027 (b6989586621679834028, Maybe a6989586621679834027) -> Type) -> TyFun a6989586621679834027 (NonEmpty b6989586621679834028) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ZipSym1 :: [a6989586621679472998] -> TyFun [b6989586621679472999] [(a6989586621679472998, b6989586621679472999)] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (GenericIndexSym1 :: [a6989586621680003259] -> TyFun i6989586621680003258 a6989586621680003259 -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Tuple2Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Maybe_Sym2 :: b6989586621679429864 -> (TyFun a6989586621679429865 b6989586621679429864 -> Type) -> TyFun (Maybe a6989586621679429865) b6989586621679429864 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (Maybe_Sym1 :: b6989586621679429864 -> TyFun (TyFun a6989586621679429865 b6989586621679429864 -> Type) (TyFun (Maybe a6989586621679429865) b6989586621679429864 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (SeqSym1 :: a6989586621679448453 -> TyFun b6989586621679448454 b6989586621679448454 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (ConstSym1 :: a6989586621679448466 -> TyFun b6989586621679448467 a6989586621679448466 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (LookupSym1 :: a6989586621679472929 -> TyFun [(a6989586621679472929, b6989586621679472930)] (Maybe b6989586621679472930) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings ((&@#@$$) :: a6989586621679824150 -> TyFun (TyFun a6989586621679824150 b6989586621679824151 -> Type) b6989586621679824151 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

SuppressUnusedWarnings (GenericReplicateSym1 :: i6989586621680003256 -> TyFun a6989586621680003257 [a6989586621680003257] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (GenericSplitAtSym1 :: i6989586621680003260 -> TyFun [a6989586621680003261] ([a6989586621680003261], [a6989586621680003261]) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (GenericDropSym1 :: i6989586621680003262 -> TyFun [a6989586621680003263] [a6989586621680003263] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (GenericTakeSym1 :: i6989586621680003264 -> TyFun [a6989586621680003265] [a6989586621680003265] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipSym1 :: NonEmpty a6989586621679833974 -> TyFun (NonEmpty b6989586621679833975) (NonEmpty (a6989586621679833974, b6989586621679833975)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ApplySym1 :: (k16989586621679025209 ~> k26989586621679025210) -> TyFun k16989586621679025209 k26989586621679025210 -> *) Source # 
Instance details

Defined in Data.Singletons

SuppressUnusedWarnings ((@@@#@$$) :: (k16989586621679031304 ~> k6989586621679031303) -> TyFun k16989586621679031304 k6989586621679031303 -> *) Source # 
Instance details

Defined in Data.Singletons

SuppressUnusedWarnings (FoldlSym0 :: TyFun (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (ComparingSym0 :: TyFun (TyFun b6989586621679323517 a6989586621679323516 -> Type) (TyFun b6989586621679323517 (TyFun b6989586621679323517 Ordering -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (MapMaybeSym0 :: TyFun (TyFun a6989586621679430977 (Maybe b6989586621679430978) -> Type) (TyFun [a6989586621679430977] [b6989586621679430978] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (($!@#@$) :: TyFun (TyFun a6989586621679448455 b6989586621679448456 -> Type) (TyFun a6989586621679448455 b6989586621679448456 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (($@#@$) :: TyFun (TyFun a6989586621679448457 b6989586621679448458 -> Type) (TyFun a6989586621679448457 b6989586621679448458 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (MapSym0 :: TyFun (TyFun a6989586621679448470 b6989586621679448471 -> Type) (TyFun [a6989586621679448470] [b6989586621679448471] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (FoldrSym0 :: TyFun (TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) (TyFun b6989586621679448473 (TyFun [a6989586621679448472] b6989586621679448473 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (TyFun b6989586621679473007 (Maybe (a6989586621679473008, b6989586621679473007)) -> Type) (TyFun b6989586621679473007 [a6989586621679473008] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ScanrSym0 :: TyFun (TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) (TyFun b6989586621679473017 (TyFun [a6989586621679473016] [b6989586621679473017] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ScanlSym0 :: TyFun (TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) (TyFun b6989586621679473019 (TyFun [a6989586621679473020] [b6989586621679473019] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (TyFun a6989586621679473023 [b6989586621679473024] -> Type) (TyFun [a6989586621679473023] [b6989586621679473024] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) (TyFun b6989586621679473030 (TyFun [a6989586621679473029] b6989586621679473030 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (GroupWithSym0 :: TyFun (TyFun a6989586621679833987 b6989586621679833986 -> Type) (TyFun [a6989586621679833987] [NonEmpty a6989586621679833987] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupAllWithSym0 :: TyFun (TyFun a6989586621679833985 b6989586621679833984 -> Type) (TyFun [a6989586621679833985] [NonEmpty a6989586621679833985] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupWith1Sym0 :: TyFun (TyFun a6989586621679833981 b6989586621679833980 -> Type) (TyFun (NonEmpty a6989586621679833981) (NonEmpty (NonEmpty a6989586621679833981)) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (MapSym0 :: TyFun (TyFun a6989586621679834010 b6989586621679834011 -> Type) (TyFun (NonEmpty a6989586621679834010) (NonEmpty b6989586621679834011) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SortWithSym0 :: TyFun (TyFun a6989586621679833964 o6989586621679833963 -> Type) (TyFun (NonEmpty a6989586621679833964) (NonEmpty a6989586621679833964) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupAllWith1Sym0 :: TyFun (TyFun a6989586621679833979 b6989586621679833978 -> Type) (TyFun (NonEmpty a6989586621679833979) (NonEmpty (NonEmpty a6989586621679833979)) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ScanlSym0 :: TyFun (TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) (TyFun b6989586621679834005 (TyFun [a6989586621679834006] (NonEmpty b6989586621679834005) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ScanrSym0 :: TyFun (TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) (TyFun b6989586621679834004 (TyFun [a6989586621679834003] (NonEmpty b6989586621679834004) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (TyFun a6989586621679834023 (b6989586621679834024, Maybe a6989586621679834023) -> Type) (TyFun a6989586621679834023 (NonEmpty b6989586621679834024) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (UnfoldSym0 :: TyFun (TyFun a6989586621679834027 (b6989586621679834028, Maybe a6989586621679834027) -> Type) (TyFun a6989586621679834027 (NonEmpty b6989586621679834028) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (RightsSym0 :: TyFun [Either a6989586621679993351 b6989586621679993352] [b6989586621679993352] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Either

SuppressUnusedWarnings (LeftsSym0 :: TyFun [Either a6989586621679993353 b6989586621679993354] [a6989586621679993353] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Either

SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a6989586621679472986, b6989586621679472987)] ([a6989586621679472986], [b6989586621679472987]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a6989586621679472915] i6989586621679472914 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ZipSym0 :: TyFun [a6989586621679472998] (TyFun [b6989586621679472999] [(a6989586621679472998, b6989586621679472999)] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (GenericIndexSym0 :: TyFun [a6989586621680003259] (TyFun i6989586621680003258 a6989586621680003259 -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (IsRightSym0 :: TyFun (Either a6989586621679993345 b6989586621679993346) Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Either

SuppressUnusedWarnings (IsLeftSym0 :: TyFun (Either a6989586621679993347 b6989586621679993348) Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Either

SuppressUnusedWarnings (SwapSym0 :: TyFun (a6989586621679304593, b6989586621679304594) (b6989586621679304594, a6989586621679304593) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Tuple

SuppressUnusedWarnings (SndSym0 :: TyFun (a6989586621679304601, b6989586621679304602) b6989586621679304602 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Tuple

SuppressUnusedWarnings (FstSym0 :: TyFun (a6989586621679304603, b6989586621679304604) a6989586621679304603 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Tuple

SuppressUnusedWarnings (LeftSym0 :: TyFun a6989586621679084181 (Either a6989586621679084181 b6989586621679084182) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (RightSym0 :: TyFun b6989586621679084182 (Either a6989586621679084181 b6989586621679084182) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Tuple2Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (ErrorSym0 :: TyFun k06989586621679403140 k6989586621679403141 -> *) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b6989586621679429864 (TyFun (TyFun a6989586621679429865 b6989586621679429864 -> Type) (TyFun (Maybe a6989586621679429865) b6989586621679429864 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (SeqSym0 :: TyFun a6989586621679448453 (TyFun b6989586621679448454 b6989586621679448454 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (ConstSym0 :: TyFun a6989586621679448466 (TyFun b6989586621679448467 a6989586621679448466 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679472929 (TyFun [(a6989586621679472929, b6989586621679472930)] (Maybe b6989586621679472930) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings ((&@#@$) :: TyFun a6989586621679824150 (TyFun (TyFun a6989586621679824150 b6989586621679824151 -> Type) b6989586621679824151 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

SuppressUnusedWarnings (GenericReplicateSym0 :: TyFun i6989586621680003256 (TyFun a6989586621680003257 [a6989586621680003257] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (GenericSplitAtSym0 :: TyFun i6989586621680003260 (TyFun [a6989586621680003261] ([a6989586621680003261], [a6989586621680003261]) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (GenericDropSym0 :: TyFun i6989586621680003262 (TyFun [a6989586621680003263] [a6989586621680003263] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (GenericTakeSym0 :: TyFun i6989586621680003264 (TyFun [a6989586621680003265] [a6989586621680003265] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (UnzipSym0 :: TyFun (NonEmpty (a6989586621679833969, b6989586621679833970)) (NonEmpty a6989586621679833969, NonEmpty b6989586621679833970) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ZipSym0 :: TyFun (NonEmpty a6989586621679833974) (TyFun (NonEmpty b6989586621679833975) (NonEmpty (a6989586621679833974, b6989586621679833975)) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ApplySym0 :: TyFun (k16989586621679025209 ~> k26989586621679025210) (TyFun k16989586621679025209 k26989586621679025210 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons

SuppressUnusedWarnings ((@@@#@$) :: TyFun (k16989586621679031304 ~> k6989586621679031303) (TyFun k16989586621679031304 k6989586621679031303 -> *) -> *) Source # 
Instance details

Defined in Data.Singletons

SuppressUnusedWarnings (CurrySym2 :: (TyFun (a6989586621679304598, b6989586621679304599) c6989586621679304600 -> Type) -> a6989586621679304598 -> TyFun b6989586621679304599 c6989586621679304600 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Tuple

SuppressUnusedWarnings (CurrySym1 :: (TyFun (a6989586621679304598, b6989586621679304599) c6989586621679304600 -> Type) -> TyFun a6989586621679304598 (TyFun b6989586621679304599 c6989586621679304600 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Tuple

SuppressUnusedWarnings (UncurrySym1 :: (TyFun a6989586621679304595 (TyFun b6989586621679304596 c6989586621679304597 -> Type) -> Type) -> TyFun (a6989586621679304595, b6989586621679304596) c6989586621679304597 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Tuple

SuppressUnusedWarnings (FlipSym2 :: (TyFun a6989586621679448460 (TyFun b6989586621679448461 c6989586621679448462 -> Type) -> Type) -> b6989586621679448461 -> TyFun a6989586621679448460 c6989586621679448462 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (FlipSym1 :: (TyFun a6989586621679448460 (TyFun b6989586621679448461 c6989586621679448462 -> Type) -> Type) -> TyFun b6989586621679448461 (TyFun a6989586621679448460 c6989586621679448462 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings ((.@#@$$$) :: (TyFun b6989586621679448463 c6989586621679448464 -> Type) -> (TyFun a6989586621679448465 b6989586621679448463 -> Type) -> TyFun a6989586621679448465 c6989586621679448464 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings ((.@#@$$) :: (TyFun b6989586621679448463 c6989586621679448464 -> Type) -> TyFun (TyFun a6989586621679448465 b6989586621679448463 -> Type) (TyFun a6989586621679448465 c6989586621679448464 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (ZipWithSym1 :: (TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) -> TyFun [a6989586621679472992] (TyFun [b6989586621679472993] [c6989586621679472994] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ZipWithSym2 :: (TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) -> [a6989586621679472992] -> TyFun [b6989586621679472993] [c6989586621679472994] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (MapAccumRSym1 :: (TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) -> TyFun acc6989586621679473009 (TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (MapAccumRSym2 :: (TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) -> acc6989586621679473009 -> TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (MapAccumLSym1 :: (TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) -> TyFun acc6989586621679473012 (TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (MapAccumLSym2 :: (TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) -> acc6989586621679473012 -> TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (OnSym3 :: (TyFun b6989586621679824152 (TyFun b6989586621679824152 c6989586621679824153 -> Type) -> Type) -> (TyFun a6989586621679824154 b6989586621679824152 -> Type) -> a6989586621679824154 -> TyFun a6989586621679824154 c6989586621679824153 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

SuppressUnusedWarnings (OnSym2 :: (TyFun b6989586621679824152 (TyFun b6989586621679824152 c6989586621679824153 -> Type) -> Type) -> (TyFun a6989586621679824154 b6989586621679824152 -> Type) -> TyFun a6989586621679824154 (TyFun a6989586621679824154 c6989586621679824153 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

SuppressUnusedWarnings (OnSym1 :: (TyFun b6989586621679824152 (TyFun b6989586621679824152 c6989586621679824153 -> Type) -> Type) -> TyFun (TyFun a6989586621679824154 b6989586621679824152 -> Type) (TyFun a6989586621679824154 (TyFun a6989586621679824154 c6989586621679824153 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

SuppressUnusedWarnings (ZipWithSym2 :: (TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) -> NonEmpty a6989586621679833971 -> TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ZipWithSym1 :: (TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679833971) (TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (Either_Sym2 :: (TyFun a6989586621679992217 c6989586621679992218 -> Type) -> (TyFun b6989586621679992219 c6989586621679992218 -> Type) -> TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Either

SuppressUnusedWarnings (Either_Sym1 :: (TyFun a6989586621679992217 c6989586621679992218 -> Type) -> TyFun (TyFun b6989586621679992219 c6989586621679992218 -> Type) (TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Either

SuppressUnusedWarnings (Zip3Sym1 :: [a6989586621679472995] -> TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Zip3Sym2 :: [a6989586621679472995] -> [b6989586621679472996] -> TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Tuple3Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Tuple3Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (CurrySym0 :: TyFun (TyFun (a6989586621679304598, b6989586621679304599) c6989586621679304600 -> Type) (TyFun a6989586621679304598 (TyFun b6989586621679304599 c6989586621679304600 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Tuple

SuppressUnusedWarnings (UncurrySym0 :: TyFun (TyFun a6989586621679304595 (TyFun b6989586621679304596 c6989586621679304597 -> Type) -> Type) (TyFun (a6989586621679304595, b6989586621679304596) c6989586621679304597 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Tuple

SuppressUnusedWarnings (FlipSym0 :: TyFun (TyFun a6989586621679448460 (TyFun b6989586621679448461 c6989586621679448462 -> Type) -> Type) (TyFun b6989586621679448461 (TyFun a6989586621679448460 c6989586621679448462 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings ((.@#@$) :: TyFun (TyFun b6989586621679448463 c6989586621679448464 -> Type) (TyFun (TyFun a6989586621679448465 b6989586621679448463 -> Type) (TyFun a6989586621679448465 c6989586621679448464 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (ZipWithSym0 :: TyFun (TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) (TyFun [a6989586621679472992] (TyFun [b6989586621679472993] [c6989586621679472994] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) (TyFun acc6989586621679473009 (TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) (TyFun acc6989586621679473012 (TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (OnSym0 :: TyFun (TyFun b6989586621679824152 (TyFun b6989586621679824152 c6989586621679824153 -> Type) -> Type) (TyFun (TyFun a6989586621679824154 b6989586621679824152 -> Type) (TyFun a6989586621679824154 (TyFun a6989586621679824154 c6989586621679824153 -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

SuppressUnusedWarnings (ZipWithSym0 :: TyFun (TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) (TyFun (NonEmpty a6989586621679833971) (TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (Either_Sym0 :: TyFun (TyFun a6989586621679992217 c6989586621679992218 -> Type) (TyFun (TyFun b6989586621679992219 c6989586621679992218 -> Type) (TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Either

SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a6989586621679472983, b6989586621679472984, c6989586621679472985)] ([a6989586621679472983], [b6989586621679472984], [c6989586621679472985]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a6989586621679472995] (TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Tuple3Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (ZipWith3Sym1 :: (TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) -> TyFun [a6989586621679472988] (TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ZipWith3Sym2 :: (TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) -> [a6989586621679472988] -> TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (ZipWith3Sym3 :: (TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) -> [a6989586621679472988] -> [b6989586621679472989] -> TyFun [c6989586621679472990] [d6989586621679472991] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Zip4Sym3 :: [a6989586621680003310] -> [b6989586621680003311] -> [c6989586621680003312] -> TyFun [d6989586621680003313] [(a6989586621680003310, b6989586621680003311, c6989586621680003312, d6989586621680003313)] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip4Sym2 :: [a6989586621680003310] -> [b6989586621680003311] -> TyFun [c6989586621680003312] (TyFun [d6989586621680003313] [(a6989586621680003310, b6989586621680003311, c6989586621680003312, d6989586621680003313)] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip4Sym1 :: [a6989586621680003310] -> TyFun [b6989586621680003311] (TyFun [c6989586621680003312] (TyFun [d6989586621680003313] [(a6989586621680003310, b6989586621680003311, c6989586621680003312, d6989586621680003313)] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Tuple4Sym3 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Tuple4Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Tuple4Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (TyFun [a6989586621679472988] (TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a6989586621679472979, b6989586621679472980, c6989586621679472981, d6989586621679472982)] ([a6989586621679472979], [b6989586621679472980], [c6989586621679472981], [d6989586621679472982]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a6989586621680003310] (TyFun [b6989586621680003311] (TyFun [c6989586621680003312] (TyFun [d6989586621680003313] [(a6989586621680003310, b6989586621680003311, c6989586621680003312, d6989586621680003313)] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Tuple4Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (ZipWith4Sym1 :: (TyFun a6989586621680003287 (TyFun b6989586621680003288 (TyFun c6989586621680003289 (TyFun d6989586621680003290 e6989586621680003291 -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621680003287] (TyFun [b6989586621680003288] (TyFun [c6989586621680003289] (TyFun [d6989586621680003290] [e6989586621680003291] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith4Sym2 :: (TyFun a6989586621680003287 (TyFun b6989586621680003288 (TyFun c6989586621680003289 (TyFun d6989586621680003290 e6989586621680003291 -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003287] -> TyFun [b6989586621680003288] (TyFun [c6989586621680003289] (TyFun [d6989586621680003290] [e6989586621680003291] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith4Sym3 :: (TyFun a6989586621680003287 (TyFun b6989586621680003288 (TyFun c6989586621680003289 (TyFun d6989586621680003290 e6989586621680003291 -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003287] -> [b6989586621680003288] -> TyFun [c6989586621680003289] (TyFun [d6989586621680003290] [e6989586621680003291] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith4Sym4 :: (TyFun a6989586621680003287 (TyFun b6989586621680003288 (TyFun c6989586621680003289 (TyFun d6989586621680003290 e6989586621680003291 -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003287] -> [b6989586621680003288] -> [c6989586621680003289] -> TyFun [d6989586621680003290] [e6989586621680003291] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip5Sym4 :: [a6989586621680003305] -> [b6989586621680003306] -> [c6989586621680003307] -> [d6989586621680003308] -> TyFun [e6989586621680003309] [(a6989586621680003305, b6989586621680003306, c6989586621680003307, d6989586621680003308, e6989586621680003309)] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip5Sym3 :: [a6989586621680003305] -> [b6989586621680003306] -> [c6989586621680003307] -> TyFun [d6989586621680003308] (TyFun [e6989586621680003309] [(a6989586621680003305, b6989586621680003306, c6989586621680003307, d6989586621680003308, e6989586621680003309)] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip5Sym2 :: [a6989586621680003305] -> [b6989586621680003306] -> TyFun [c6989586621680003307] (TyFun [d6989586621680003308] (TyFun [e6989586621680003309] [(a6989586621680003305, b6989586621680003306, c6989586621680003307, d6989586621680003308, e6989586621680003309)] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip5Sym1 :: [a6989586621680003305] -> TyFun [b6989586621680003306] (TyFun [c6989586621680003307] (TyFun [d6989586621680003308] (TyFun [e6989586621680003309] [(a6989586621680003305, b6989586621680003306, c6989586621680003307, d6989586621680003308, e6989586621680003309)] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Tuple5Sym4 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Tuple5Sym3 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Tuple5Sym2 :: a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Tuple5Sym1 :: a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (TyFun a6989586621680003287 (TyFun b6989586621680003288 (TyFun c6989586621680003289 (TyFun d6989586621680003290 e6989586621680003291 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621680003287] (TyFun [b6989586621680003288] (TyFun [c6989586621680003289] (TyFun [d6989586621680003290] [e6989586621680003291] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a6989586621679472974, b6989586621679472975, c6989586621679472976, d6989586621679472977, e6989586621679472978)] ([a6989586621679472974], [b6989586621679472975], [c6989586621679472976], [d6989586621679472977], [e6989586621679472978]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a6989586621680003305] (TyFun [b6989586621680003306] (TyFun [c6989586621680003307] (TyFun [d6989586621680003308] (TyFun [e6989586621680003309] [(a6989586621680003305, b6989586621680003306, c6989586621680003307, d6989586621680003308, e6989586621680003309)] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Tuple5Sym0 :: TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (ZipWith5Sym1 :: (TyFun a6989586621680003281 (TyFun b6989586621680003282 (TyFun c6989586621680003283 (TyFun d6989586621680003284 (TyFun e6989586621680003285 f6989586621680003286 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621680003281] (TyFun [b6989586621680003282] (TyFun [c6989586621680003283] (TyFun [d6989586621680003284] (TyFun [e6989586621680003285] [f6989586621680003286] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith5Sym2 :: (TyFun a6989586621680003281 (TyFun b6989586621680003282 (TyFun c6989586621680003283 (TyFun d6989586621680003284 (TyFun e6989586621680003285 f6989586621680003286 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003281] -> TyFun [b6989586621680003282] (TyFun [c6989586621680003283] (TyFun [d6989586621680003284] (TyFun [e6989586621680003285] [f6989586621680003286] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith5Sym3 :: (TyFun a6989586621680003281 (TyFun b6989586621680003282 (TyFun c6989586621680003283 (TyFun d6989586621680003284 (TyFun e6989586621680003285 f6989586621680003286 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003281] -> [b6989586621680003282] -> TyFun [c6989586621680003283] (TyFun [d6989586621680003284] (TyFun [e6989586621680003285] [f6989586621680003286] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith5Sym4 :: (TyFun a6989586621680003281 (TyFun b6989586621680003282 (TyFun c6989586621680003283 (TyFun d6989586621680003284 (TyFun e6989586621680003285 f6989586621680003286 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003281] -> [b6989586621680003282] -> [c6989586621680003283] -> TyFun [d6989586621680003284] (TyFun [e6989586621680003285] [f6989586621680003286] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith5Sym5 :: (TyFun a6989586621680003281 (TyFun b6989586621680003282 (TyFun c6989586621680003283 (TyFun d6989586621680003284 (TyFun e6989586621680003285 f6989586621680003286 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003281] -> [b6989586621680003282] -> [c6989586621680003283] -> [d6989586621680003284] -> TyFun [e6989586621680003285] [f6989586621680003286] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip6Sym5 :: [a6989586621680003299] -> [b6989586621680003300] -> [c6989586621680003301] -> [d6989586621680003302] -> [e6989586621680003303] -> TyFun [f6989586621680003304] [(a6989586621680003299, b6989586621680003300, c6989586621680003301, d6989586621680003302, e6989586621680003303, f6989586621680003304)] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip6Sym4 :: [a6989586621680003299] -> [b6989586621680003300] -> [c6989586621680003301] -> [d6989586621680003302] -> TyFun [e6989586621680003303] (TyFun [f6989586621680003304] [(a6989586621680003299, b6989586621680003300, c6989586621680003301, d6989586621680003302, e6989586621680003303, f6989586621680003304)] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip6Sym3 :: [a6989586621680003299] -> [b6989586621680003300] -> [c6989586621680003301] -> TyFun [d6989586621680003302] (TyFun [e6989586621680003303] (TyFun [f6989586621680003304] [(a6989586621680003299, b6989586621680003300, c6989586621680003301, d6989586621680003302, e6989586621680003303, f6989586621680003304)] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip6Sym2 :: [a6989586621680003299] -> [b6989586621680003300] -> TyFun [c6989586621680003301] (TyFun [d6989586621680003302] (TyFun [e6989586621680003303] (TyFun [f6989586621680003304] [(a6989586621680003299, b6989586621680003300, c6989586621680003301, d6989586621680003302, e6989586621680003303, f6989586621680003304)] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip6Sym1 :: [a6989586621680003299] -> TyFun [b6989586621680003300] (TyFun [c6989586621680003301] (TyFun [d6989586621680003302] (TyFun [e6989586621680003303] (TyFun [f6989586621680003304] [(a6989586621680003299, b6989586621680003300, c6989586621680003301, d6989586621680003302, e6989586621680003303, f6989586621680003304)] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Tuple6Sym5 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> e3530822107858468869 -> TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Tuple6Sym4 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Tuple6Sym3 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.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

Defined in Data.Singletons.Prelude.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

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (TyFun a6989586621680003281 (TyFun b6989586621680003282 (TyFun c6989586621680003283 (TyFun d6989586621680003284 (TyFun e6989586621680003285 f6989586621680003286 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621680003281] (TyFun [b6989586621680003282] (TyFun [c6989586621680003283] (TyFun [d6989586621680003284] (TyFun [e6989586621680003285] [f6989586621680003286] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a6989586621679472968, b6989586621679472969, c6989586621679472970, d6989586621679472971, e6989586621679472972, f6989586621679472973)] ([a6989586621679472968], [b6989586621679472969], [c6989586621679472970], [d6989586621679472971], [e6989586621679472972], [f6989586621679472973]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a6989586621680003299] (TyFun [b6989586621680003300] (TyFun [c6989586621680003301] (TyFun [d6989586621680003302] (TyFun [e6989586621680003303] (TyFun [f6989586621680003304] [(a6989586621680003299, b6989586621680003300, c6989586621680003301, d6989586621680003302, e6989586621680003303, f6989586621680003304)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

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

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (ZipWith6Sym1 :: (TyFun a6989586621680003274 (TyFun b6989586621680003275 (TyFun c6989586621680003276 (TyFun d6989586621680003277 (TyFun e6989586621680003278 (TyFun f6989586621680003279 g6989586621680003280 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621680003274] (TyFun [b6989586621680003275] (TyFun [c6989586621680003276] (TyFun [d6989586621680003277] (TyFun [e6989586621680003278] (TyFun [f6989586621680003279] [g6989586621680003280] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith6Sym2 :: (TyFun a6989586621680003274 (TyFun b6989586621680003275 (TyFun c6989586621680003276 (TyFun d6989586621680003277 (TyFun e6989586621680003278 (TyFun f6989586621680003279 g6989586621680003280 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003274] -> TyFun [b6989586621680003275] (TyFun [c6989586621680003276] (TyFun [d6989586621680003277] (TyFun [e6989586621680003278] (TyFun [f6989586621680003279] [g6989586621680003280] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith6Sym3 :: (TyFun a6989586621680003274 (TyFun b6989586621680003275 (TyFun c6989586621680003276 (TyFun d6989586621680003277 (TyFun e6989586621680003278 (TyFun f6989586621680003279 g6989586621680003280 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003274] -> [b6989586621680003275] -> TyFun [c6989586621680003276] (TyFun [d6989586621680003277] (TyFun [e6989586621680003278] (TyFun [f6989586621680003279] [g6989586621680003280] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith6Sym4 :: (TyFun a6989586621680003274 (TyFun b6989586621680003275 (TyFun c6989586621680003276 (TyFun d6989586621680003277 (TyFun e6989586621680003278 (TyFun f6989586621680003279 g6989586621680003280 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003274] -> [b6989586621680003275] -> [c6989586621680003276] -> TyFun [d6989586621680003277] (TyFun [e6989586621680003278] (TyFun [f6989586621680003279] [g6989586621680003280] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith6Sym5 :: (TyFun a6989586621680003274 (TyFun b6989586621680003275 (TyFun c6989586621680003276 (TyFun d6989586621680003277 (TyFun e6989586621680003278 (TyFun f6989586621680003279 g6989586621680003280 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003274] -> [b6989586621680003275] -> [c6989586621680003276] -> [d6989586621680003277] -> TyFun [e6989586621680003278] (TyFun [f6989586621680003279] [g6989586621680003280] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith6Sym6 :: (TyFun a6989586621680003274 (TyFun b6989586621680003275 (TyFun c6989586621680003276 (TyFun d6989586621680003277 (TyFun e6989586621680003278 (TyFun f6989586621680003279 g6989586621680003280 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003274] -> [b6989586621680003275] -> [c6989586621680003276] -> [d6989586621680003277] -> [e6989586621680003278] -> TyFun [f6989586621680003279] [g6989586621680003280] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip7Sym6 :: [a6989586621680003292] -> [b6989586621680003293] -> [c6989586621680003294] -> [d6989586621680003295] -> [e6989586621680003296] -> [f6989586621680003297] -> TyFun [g6989586621680003298] [(a6989586621680003292, b6989586621680003293, c6989586621680003294, d6989586621680003295, e6989586621680003296, f6989586621680003297, g6989586621680003298)] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip7Sym5 :: [a6989586621680003292] -> [b6989586621680003293] -> [c6989586621680003294] -> [d6989586621680003295] -> [e6989586621680003296] -> TyFun [f6989586621680003297] (TyFun [g6989586621680003298] [(a6989586621680003292, b6989586621680003293, c6989586621680003294, d6989586621680003295, e6989586621680003296, f6989586621680003297, g6989586621680003298)] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip7Sym4 :: [a6989586621680003292] -> [b6989586621680003293] -> [c6989586621680003294] -> [d6989586621680003295] -> TyFun [e6989586621680003296] (TyFun [f6989586621680003297] (TyFun [g6989586621680003298] [(a6989586621680003292, b6989586621680003293, c6989586621680003294, d6989586621680003295, e6989586621680003296, f6989586621680003297, g6989586621680003298)] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip7Sym3 :: [a6989586621680003292] -> [b6989586621680003293] -> [c6989586621680003294] -> TyFun [d6989586621680003295] (TyFun [e6989586621680003296] (TyFun [f6989586621680003297] (TyFun [g6989586621680003298] [(a6989586621680003292, b6989586621680003293, c6989586621680003294, d6989586621680003295, e6989586621680003296, f6989586621680003297, g6989586621680003298)] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip7Sym2 :: [a6989586621680003292] -> [b6989586621680003293] -> TyFun [c6989586621680003294] (TyFun [d6989586621680003295] (TyFun [e6989586621680003296] (TyFun [f6989586621680003297] (TyFun [g6989586621680003298] [(a6989586621680003292, b6989586621680003293, c6989586621680003294, d6989586621680003295, e6989586621680003296, f6989586621680003297, g6989586621680003298)] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Zip7Sym1 :: [a6989586621680003292] -> TyFun [b6989586621680003293] (TyFun [c6989586621680003294] (TyFun [d6989586621680003295] (TyFun [e6989586621680003296] (TyFun [f6989586621680003297] (TyFun [g6989586621680003298] [(a6989586621680003292, b6989586621680003293, c6989586621680003294, d6989586621680003295, e6989586621680003296, f6989586621680003297, g6989586621680003298)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Tuple7Sym6 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> e3530822107858468869 -> f3530822107858468870 -> TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (Tuple7Sym5 :: a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> e3530822107858468869 -> TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.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

Defined in Data.Singletons.Prelude.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

Defined in Data.Singletons.Prelude.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

Defined in Data.Singletons.Prelude.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

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (TyFun a6989586621680003274 (TyFun b6989586621680003275 (TyFun c6989586621680003276 (TyFun d6989586621680003277 (TyFun e6989586621680003278 (TyFun f6989586621680003279 g6989586621680003280 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621680003274] (TyFun [b6989586621680003275] (TyFun [c6989586621680003276] (TyFun [d6989586621680003277] (TyFun [e6989586621680003278] (TyFun [f6989586621680003279] [g6989586621680003280] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a6989586621679472961, b6989586621679472962, c6989586621679472963, d6989586621679472964, e6989586621679472965, f6989586621679472966, g6989586621679472967)] ([a6989586621679472961], [b6989586621679472962], [c6989586621679472963], [d6989586621679472964], [e6989586621679472965], [f6989586621679472966], [g6989586621679472967]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a6989586621680003292] (TyFun [b6989586621680003293] (TyFun [c6989586621680003294] (TyFun [d6989586621680003295] (TyFun [e6989586621680003296] (TyFun [f6989586621680003297] (TyFun [g6989586621680003298] [(a6989586621680003292, b6989586621680003293, c6989586621680003294, d6989586621680003295, e6989586621680003296, f6989586621680003297, g6989586621680003298)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

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

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (ZipWith7Sym1 :: (TyFun a6989586621680003266 (TyFun b6989586621680003267 (TyFun c6989586621680003268 (TyFun d6989586621680003269 (TyFun e6989586621680003270 (TyFun f6989586621680003271 (TyFun g6989586621680003272 h6989586621680003273 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621680003266] (TyFun [b6989586621680003267] (TyFun [c6989586621680003268] (TyFun [d6989586621680003269] (TyFun [e6989586621680003270] (TyFun [f6989586621680003271] (TyFun [g6989586621680003272] [h6989586621680003273] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith7Sym2 :: (TyFun a6989586621680003266 (TyFun b6989586621680003267 (TyFun c6989586621680003268 (TyFun d6989586621680003269 (TyFun e6989586621680003270 (TyFun f6989586621680003271 (TyFun g6989586621680003272 h6989586621680003273 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003266] -> TyFun [b6989586621680003267] (TyFun [c6989586621680003268] (TyFun [d6989586621680003269] (TyFun [e6989586621680003270] (TyFun [f6989586621680003271] (TyFun [g6989586621680003272] [h6989586621680003273] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith7Sym3 :: (TyFun a6989586621680003266 (TyFun b6989586621680003267 (TyFun c6989586621680003268 (TyFun d6989586621680003269 (TyFun e6989586621680003270 (TyFun f6989586621680003271 (TyFun g6989586621680003272 h6989586621680003273 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003266] -> [b6989586621680003267] -> TyFun [c6989586621680003268] (TyFun [d6989586621680003269] (TyFun [e6989586621680003270] (TyFun [f6989586621680003271] (TyFun [g6989586621680003272] [h6989586621680003273] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith7Sym4 :: (TyFun a6989586621680003266 (TyFun b6989586621680003267 (TyFun c6989586621680003268 (TyFun d6989586621680003269 (TyFun e6989586621680003270 (TyFun f6989586621680003271 (TyFun g6989586621680003272 h6989586621680003273 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003266] -> [b6989586621680003267] -> [c6989586621680003268] -> TyFun [d6989586621680003269] (TyFun [e6989586621680003270] (TyFun [f6989586621680003271] (TyFun [g6989586621680003272] [h6989586621680003273] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith7Sym5 :: (TyFun a6989586621680003266 (TyFun b6989586621680003267 (TyFun c6989586621680003268 (TyFun d6989586621680003269 (TyFun e6989586621680003270 (TyFun f6989586621680003271 (TyFun g6989586621680003272 h6989586621680003273 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003266] -> [b6989586621680003267] -> [c6989586621680003268] -> [d6989586621680003269] -> TyFun [e6989586621680003270] (TyFun [f6989586621680003271] (TyFun [g6989586621680003272] [h6989586621680003273] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith7Sym6 :: (TyFun a6989586621680003266 (TyFun b6989586621680003267 (TyFun c6989586621680003268 (TyFun d6989586621680003269 (TyFun e6989586621680003270 (TyFun f6989586621680003271 (TyFun g6989586621680003272 h6989586621680003273 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003266] -> [b6989586621680003267] -> [c6989586621680003268] -> [d6989586621680003269] -> [e6989586621680003270] -> TyFun [f6989586621680003271] (TyFun [g6989586621680003272] [h6989586621680003273] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith7Sym7 :: (TyFun a6989586621680003266 (TyFun b6989586621680003267 (TyFun c6989586621680003268 (TyFun d6989586621680003269 (TyFun e6989586621680003270 (TyFun f6989586621680003271 (TyFun g6989586621680003272 h6989586621680003273 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680003266] -> [b6989586621680003267] -> [c6989586621680003268] -> [d6989586621680003269] -> [e6989586621680003270] -> [f6989586621680003271] -> TyFun [g6989586621680003272] [h6989586621680003273] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

SuppressUnusedWarnings (ZipWith7Sym0 :: TyFun (TyFun a6989586621680003266 (TyFun b6989586621680003267 (TyFun c6989586621680003268 (TyFun d6989586621680003269 (TyFun e6989586621680003270 (TyFun f6989586621680003271 (TyFun g6989586621680003272 h6989586621680003273 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621680003266] (TyFun [b6989586621680003267] (TyFun [c6989586621680003268] (TyFun [d6989586621680003269] (TyFun [e6989586621680003270] (TyFun [f6989586621680003271] (TyFun [g6989586621680003272] [h6989586621680003273] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List