singletons-2.2: A framework for generating singleton types

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

Data.Singletons.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] #

Make promoted and singleton versions of all declarations given, retaining the original declarations. See http://www.cis.upenn.edu/~eir/packages/singletons/README.html for further explanation.

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

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

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

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

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

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

Generate defunctionalization symbols for existing type family

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

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

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

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

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

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

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

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

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

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

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

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

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

Create instances of SDecide for each type in the list.

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

Create instance of SDecide for the given type.

Functions to generate Ord instances

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

Produce instances for POrd from the given types

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

Produce an instance for POrd from the given type

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

Create instances of SOrd for the given types

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

Create instance of SOrd for the given type

Functions to generate Bounded instances

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

Produce instances for PBounded from the given types

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

Produce an instance for PBounded from the given type

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

Create instances of SBounded for the given types

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

Create instance of SBounded for the given type

Functions to generate Enum instances

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

Produce instances for PEnum from the given types

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

Produce an instance for PEnum from the given type

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

Create instances of SEnum for the given types

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

Create instance of SEnum for the given type

Utility functions

cases #

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 #

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

The singleton kind-indexed data family.

Instances

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

Auxiliary definitions

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

class kproxy ~ Proxy => PEq kproxy #

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

Associated Types

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

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

Instances

PEq Bool (Proxy * Bool) # 

Associated Types

type ((Proxy * Bool) :== (x :: Proxy * Bool)) (y :: Proxy * Bool) :: Bool #

type ((Proxy * Bool) :/= (x :: Proxy * Bool)) (y :: Proxy * Bool) :: Bool #

PEq Ordering (Proxy * Ordering) # 

Associated Types

type ((Proxy * Ordering) :== (x :: Proxy * Ordering)) (y :: Proxy * Ordering) :: Bool #

type ((Proxy * Ordering) :/= (x :: Proxy * Ordering)) (y :: Proxy * Ordering) :: Bool #

PEq () (Proxy * ()) # 

Associated Types

type ((Proxy * ()) :== (x :: Proxy * ())) (y :: Proxy * ()) :: Bool #

type ((Proxy * ()) :/= (x :: Proxy * ())) (y :: Proxy * ()) :: Bool #

PEq [k0] (Proxy * [k0]) # 

Associated Types

type ((Proxy * [k0]) :== (x :: Proxy * [k0])) (y :: Proxy * [k0]) :: Bool #

type ((Proxy * [k0]) :/= (x :: Proxy * [k0])) (y :: Proxy * [k0]) :: Bool #

PEq (Maybe k0) (Proxy * (Maybe k0)) # 

Associated Types

type ((Proxy * (Maybe k0)) :== (x :: Proxy * (Maybe k0))) (y :: Proxy * (Maybe k0)) :: Bool #

type ((Proxy * (Maybe k0)) :/= (x :: Proxy * (Maybe k0))) (y :: Proxy * (Maybe k0)) :: Bool #

PEq (NonEmpty k0) (Proxy * (NonEmpty k0)) # 

Associated Types

type ((Proxy * (NonEmpty k0)) :== (x :: Proxy * (NonEmpty k0))) (y :: Proxy * (NonEmpty k0)) :: Bool #

type ((Proxy * (NonEmpty k0)) :/= (x :: Proxy * (NonEmpty k0))) (y :: Proxy * (NonEmpty k0)) :: Bool #

PEq (Either k0 k1) (Proxy * (Either k0 k1)) # 

Associated Types

type ((Proxy * (Either k0 k1)) :== (x :: Proxy * (Either k0 k1))) (y :: Proxy * (Either k0 k1)) :: Bool #

type ((Proxy * (Either k0 k1)) :/= (x :: Proxy * (Either k0 k1))) (y :: Proxy * (Either k0 k1)) :: Bool #

PEq (k0, k1) (Proxy * (k0, k1)) # 

Associated Types

type ((Proxy * (k0, k1)) :== (x :: Proxy * (k0, k1))) (y :: Proxy * (k0, k1)) :: Bool #

type ((Proxy * (k0, k1)) :/= (x :: Proxy * (k0, k1))) (y :: Proxy * (k0, k1)) :: Bool #

PEq (k0, k1, k2) (Proxy * (k0, k1, k2)) # 

Associated Types

type ((Proxy * (k0, k1, k2)) :== (x :: Proxy * (k0, k1, k2))) (y :: Proxy * (k0, k1, k2)) :: Bool #

type ((Proxy * (k0, k1, k2)) :/= (x :: Proxy * (k0, k1, k2))) (y :: Proxy * (k0, k1, k2)) :: Bool #

PEq (k0, k1, k2, k3) (Proxy * (k0, k1, k2, k3)) # 

Associated Types

type ((Proxy * (k0, k1, k2, k3)) :== (x :: Proxy * (k0, k1, k2, k3))) (y :: Proxy * (k0, k1, k2, k3)) :: Bool #

type ((Proxy * (k0, k1, k2, k3)) :/= (x :: Proxy * (k0, k1, k2, k3))) (y :: Proxy * (k0, k1, k2, k3)) :: Bool #

PEq (k0, k1, k2, k3, k4) (Proxy * (k0, k1, k2, k3, k4)) # 

Associated Types

type ((Proxy * (k0, k1, k2, k3, k4)) :== (x :: Proxy * (k0, k1, k2, k3, k4))) (y :: Proxy * (k0, k1, k2, k3, k4)) :: Bool #

type ((Proxy * (k0, k1, k2, k3, k4)) :/= (x :: Proxy * (k0, k1, k2, k3, k4))) (y :: Proxy * (k0, k1, k2, k3, k4)) :: Bool #

PEq (k0, k1, k2, k3, k4, k5) (Proxy * (k0, k1, k2, k3, k4, k5)) # 

Associated Types

type ((Proxy * (k0, k1, k2, k3, k4, k5)) :== (x :: Proxy * (k0, k1, k2, k3, k4, k5))) (y :: Proxy * (k0, k1, k2, k3, k4, k5)) :: Bool #

type ((Proxy * (k0, k1, k2, k3, k4, k5)) :/= (x :: Proxy * (k0, k1, k2, k3, k4, k5))) (y :: Proxy * (k0, k1, k2, k3, k4, k5)) :: Bool #

PEq (k0, k1, k2, k3, k4, k5, k6) (Proxy * (k0, k1, k2, k3, k4, k5, k6)) # 

Associated Types

type ((Proxy * (k0, k1, k2, k3, k4, k5, k6)) :== (x :: Proxy * (k0, k1, k2, k3, k4, k5, k6))) (y :: Proxy * (k0, k1, k2, k3, k4, k5, k6)) :: Bool #

type ((Proxy * (k0, k1, k2, k3, k4, k5, k6)) :/= (x :: Proxy * (k0, k1, k2, k3, k4, k5, k6))) (y :: Proxy * (k0, k1, k2, k3, k4, k5, k6)) :: Bool #

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

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

Equations

If k True tru fls = tru 
If k False tru fls = fls 

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

Conditional over singletons

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

Equations

False :&& _z_6989586621679546512 = FalseSym0 
True :&& x = x 

class SEq k where #

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 b. Sing a -> Sing b -> Sing (a :== b) infix 4 #

Boolean equality on singletons

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

Boolean disequality on singletons

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

Boolean disequality on singletons

Instances

SEq Bool # 

Methods

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

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

SEq Ordering # 

Methods

(%:==) :: Sing Ordering a -> Sing Ordering b -> Sing Bool ((Ordering :== a) b) #

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

SEq () # 

Methods

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

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

SEq a0 => SEq [a0] # 

Methods

(%:==) :: Sing [a0] a -> Sing [a0] b -> Sing Bool (([a0] :== a) b) #

(%:/=) :: Sing [a0] a -> Sing [a0] b -> Sing Bool (([a0] :/= a) b) #

SEq a0 => SEq (Maybe a0) # 

Methods

(%:==) :: Sing (Maybe a0) a -> Sing (Maybe a0) b -> Sing Bool ((Maybe a0 :== a) b) #

(%:/=) :: Sing (Maybe a0) a -> Sing (Maybe a0) b -> Sing Bool ((Maybe a0 :/= a) b) #

SEq a0 => SEq (NonEmpty a0) # 

Methods

(%:==) :: Sing (NonEmpty a0) a -> Sing (NonEmpty a0) b -> Sing Bool ((NonEmpty a0 :== a) b) #

(%:/=) :: Sing (NonEmpty a0) a -> Sing (NonEmpty a0) b -> Sing Bool ((NonEmpty a0 :/= a) b) #

(SEq a0, SEq b0) => SEq (Either a0 b0) # 

Methods

(%:==) :: Sing (Either a0 b0) a -> Sing (Either a0 b0) b -> Sing Bool ((Either a0 b0 :== a) b) #

(%:/=) :: Sing (Either a0 b0) a -> Sing (Either a0 b0) b -> Sing Bool ((Either a0 b0 :/= a) b) #

(SEq a0, SEq b0) => SEq (a0, b0) # 

Methods

(%:==) :: Sing (a0, b0) a -> Sing (a0, b0) b -> Sing Bool (((a0, b0) :== a) b) #

(%:/=) :: Sing (a0, b0) a -> Sing (a0, b0) b -> Sing Bool (((a0, b0) :/= a) b) #

(SEq a0, SEq b0, SEq c0) => SEq (a0, b0, c0) # 

Methods

(%:==) :: Sing (a0, b0, c0) a -> Sing (a0, b0, c0) b -> Sing Bool (((a0, b0, c0) :== a) b) #

(%:/=) :: Sing (a0, b0, c0) a -> Sing (a0, b0, c0) b -> Sing Bool (((a0, b0, c0) :/= a) b) #

(SEq a0, SEq b0, SEq c0, SEq d0) => SEq (a0, b0, c0, d0) # 

Methods

(%:==) :: Sing (a0, b0, c0, d0) a -> Sing (a0, b0, c0, d0) b -> Sing Bool (((a0, b0, c0, d0) :== a) b) #

(%:/=) :: Sing (a0, b0, c0, d0) a -> Sing (a0, b0, c0, d0) b -> Sing Bool (((a0, b0, c0, d0) :/= a) b) #

(SEq a0, SEq b0, SEq c0, SEq d0, SEq e0) => SEq (a0, b0, c0, d0, e0) # 

Methods

(%:==) :: Sing (a0, b0, c0, d0, e0) a -> Sing (a0, b0, c0, d0, e0) b -> Sing Bool (((a0, b0, c0, d0, e0) :== a) b) #

(%:/=) :: Sing (a0, b0, c0, d0, e0) a -> Sing (a0, b0, c0, d0, e0) b -> Sing Bool (((a0, b0, c0, d0, e0) :/= a) b) #

(SEq a0, SEq b0, SEq c0, SEq d0, SEq e0, SEq f0) => SEq (a0, b0, c0, d0, e0, f0) # 

Methods

(%:==) :: Sing (a0, b0, c0, d0, e0, f0) a -> Sing (a0, b0, c0, d0, e0, f0) b -> Sing Bool (((a0, b0, c0, d0, e0, f0) :== a) b) #

(%:/=) :: Sing (a0, b0, c0, d0, e0, f0) a -> Sing (a0, b0, c0, d0, e0, f0) b -> Sing Bool (((a0, b0, c0, d0, e0, f0) :/= a) b) #

(SEq a0, SEq b0, SEq c0, SEq d0, SEq e0, SEq f0, SEq g0) => SEq (a0, b0, c0, d0, e0, f0, g0) # 

Methods

(%:==) :: Sing (a0, b0, c0, d0, e0, f0, g0) a -> Sing (a0, b0, c0, d0, e0, f0, g0) b -> Sing Bool (((a0, b0, c0, d0, e0, f0, g0) :== a) b) #

(%:/=) :: Sing (a0, b0, c0, d0, e0, f0, g0) a -> Sing (a0, b0, c0, d0, e0, f0, g0) b -> Sing Bool (((a0, b0, c0, d0, e0, f0, g0) :/= a) b) #

class (PEq (Proxy :: Proxy a), kproxy ~ Proxy) => POrd kproxy #

Associated Types

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

type (arg :: a) :< (arg :: a) :: Bool infix 4 #

type (arg :: a) :<= (arg :: a) :: Bool infix 4 #

type (arg :: a) :> (arg :: a) :: Bool infix 4 #

type (arg :: a) :>= (arg :: a) :: Bool infix 4 #

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

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

Instances

POrd Bool (Proxy * Bool) # 

Associated Types

type Compare (Proxy * Bool) (arg :: Proxy * Bool) (arg :: Proxy * Bool) :: Ordering #

type ((Proxy * Bool) :< (arg :: Proxy * Bool)) (arg :: Proxy * Bool) :: Bool #

type ((Proxy * Bool) :<= (arg :: Proxy * Bool)) (arg :: Proxy * Bool) :: Bool #

type ((Proxy * Bool) :> (arg :: Proxy * Bool)) (arg :: Proxy * Bool) :: Bool #

type ((Proxy * Bool) :>= (arg :: Proxy * Bool)) (arg :: Proxy * Bool) :: Bool #

type Max (Proxy * Bool) (arg :: Proxy * Bool) (arg :: Proxy * Bool) :: a #

type Min (Proxy * Bool) (arg :: Proxy * Bool) (arg :: Proxy * Bool) :: a #

POrd Ordering (Proxy * Ordering) # 

Associated Types

type Compare (Proxy * Ordering) (arg :: Proxy * Ordering) (arg :: Proxy * Ordering) :: Ordering #

type ((Proxy * Ordering) :< (arg :: Proxy * Ordering)) (arg :: Proxy * Ordering) :: Bool #

type ((Proxy * Ordering) :<= (arg :: Proxy * Ordering)) (arg :: Proxy * Ordering) :: Bool #

type ((Proxy * Ordering) :> (arg :: Proxy * Ordering)) (arg :: Proxy * Ordering) :: Bool #

type ((Proxy * Ordering) :>= (arg :: Proxy * Ordering)) (arg :: Proxy * Ordering) :: Bool #

type Max (Proxy * Ordering) (arg :: Proxy * Ordering) (arg :: Proxy * Ordering) :: a #

type Min (Proxy * Ordering) (arg :: Proxy * Ordering) (arg :: Proxy * Ordering) :: a #

POrd () (Proxy * ()) # 

Associated Types

type Compare (Proxy * ()) (arg :: Proxy * ()) (arg :: Proxy * ()) :: Ordering #

type ((Proxy * ()) :< (arg :: Proxy * ())) (arg :: Proxy * ()) :: Bool #

type ((Proxy * ()) :<= (arg :: Proxy * ())) (arg :: Proxy * ()) :: Bool #

type ((Proxy * ()) :> (arg :: Proxy * ())) (arg :: Proxy * ()) :: Bool #

type ((Proxy * ()) :>= (arg :: Proxy * ())) (arg :: Proxy * ()) :: Bool #

type Max (Proxy * ()) (arg :: Proxy * ()) (arg :: Proxy * ()) :: a #

type Min (Proxy * ()) (arg :: Proxy * ()) (arg :: Proxy * ()) :: a #

POrd [a0] (Proxy * [a0]) # 

Associated Types

type Compare (Proxy * [a0]) (arg :: Proxy * [a0]) (arg :: Proxy * [a0]) :: Ordering #

type ((Proxy * [a0]) :< (arg :: Proxy * [a0])) (arg :: Proxy * [a0]) :: Bool #

type ((Proxy * [a0]) :<= (arg :: Proxy * [a0])) (arg :: Proxy * [a0]) :: Bool #

type ((Proxy * [a0]) :> (arg :: Proxy * [a0])) (arg :: Proxy * [a0]) :: Bool #

type ((Proxy * [a0]) :>= (arg :: Proxy * [a0])) (arg :: Proxy * [a0]) :: Bool #

type Max (Proxy * [a0]) (arg :: Proxy * [a0]) (arg :: Proxy * [a0]) :: a #

type Min (Proxy * [a0]) (arg :: Proxy * [a0]) (arg :: Proxy * [a0]) :: a #

POrd (Maybe a0) (Proxy * (Maybe a0)) # 

Associated Types

type Compare (Proxy * (Maybe a0)) (arg :: Proxy * (Maybe a0)) (arg :: Proxy * (Maybe a0)) :: Ordering #

type ((Proxy * (Maybe a0)) :< (arg :: Proxy * (Maybe a0))) (arg :: Proxy * (Maybe a0)) :: Bool #

type ((Proxy * (Maybe a0)) :<= (arg :: Proxy * (Maybe a0))) (arg :: Proxy * (Maybe a0)) :: Bool #

type ((Proxy * (Maybe a0)) :> (arg :: Proxy * (Maybe a0))) (arg :: Proxy * (Maybe a0)) :: Bool #

type ((Proxy * (Maybe a0)) :>= (arg :: Proxy * (Maybe a0))) (arg :: Proxy * (Maybe a0)) :: Bool #

type Max (Proxy * (Maybe a0)) (arg :: Proxy * (Maybe a0)) (arg :: Proxy * (Maybe a0)) :: a #

type Min (Proxy * (Maybe a0)) (arg :: Proxy * (Maybe a0)) (arg :: Proxy * (Maybe a0)) :: a #

POrd (NonEmpty a0) (Proxy * (NonEmpty a0)) # 

Associated Types

type Compare (Proxy * (NonEmpty a0)) (arg :: Proxy * (NonEmpty a0)) (arg :: Proxy * (NonEmpty a0)) :: Ordering #

type ((Proxy * (NonEmpty a0)) :< (arg :: Proxy * (NonEmpty a0))) (arg :: Proxy * (NonEmpty a0)) :: Bool #

type ((Proxy * (NonEmpty a0)) :<= (arg :: Proxy * (NonEmpty a0))) (arg :: Proxy * (NonEmpty a0)) :: Bool #

type ((Proxy * (NonEmpty a0)) :> (arg :: Proxy * (NonEmpty a0))) (arg :: Proxy * (NonEmpty a0)) :: Bool #

type ((Proxy * (NonEmpty a0)) :>= (arg :: Proxy * (NonEmpty a0))) (arg :: Proxy * (NonEmpty a0)) :: Bool #

type Max (Proxy * (NonEmpty a0)) (arg :: Proxy * (NonEmpty a0)) (arg :: Proxy * (NonEmpty a0)) :: a #

type Min (Proxy * (NonEmpty a0)) (arg :: Proxy * (NonEmpty a0)) (arg :: Proxy * (NonEmpty a0)) :: a #

POrd (Either a0 b0) (Proxy * (Either a0 b0)) # 

Associated Types

type Compare (Proxy * (Either a0 b0)) (arg :: Proxy * (Either a0 b0)) (arg :: Proxy * (Either a0 b0)) :: Ordering #

type ((Proxy * (Either a0 b0)) :< (arg :: Proxy * (Either a0 b0))) (arg :: Proxy * (Either a0 b0)) :: Bool #

type ((Proxy * (Either a0 b0)) :<= (arg :: Proxy * (Either a0 b0))) (arg :: Proxy * (Either a0 b0)) :: Bool #

type ((Proxy * (Either a0 b0)) :> (arg :: Proxy * (Either a0 b0))) (arg :: Proxy * (Either a0 b0)) :: Bool #

type ((Proxy * (Either a0 b0)) :>= (arg :: Proxy * (Either a0 b0))) (arg :: Proxy * (Either a0 b0)) :: Bool #

type Max (Proxy * (Either a0 b0)) (arg :: Proxy * (Either a0 b0)) (arg :: Proxy * (Either a0 b0)) :: a #

type Min (Proxy * (Either a0 b0)) (arg :: Proxy * (Either a0 b0)) (arg :: Proxy * (Either a0 b0)) :: a #

POrd (a0, b0) (Proxy * (a0, b0)) # 

Associated Types

type Compare (Proxy * (a0, b0)) (arg :: Proxy * (a0, b0)) (arg :: Proxy * (a0, b0)) :: Ordering #

type ((Proxy * (a0, b0)) :< (arg :: Proxy * (a0, b0))) (arg :: Proxy * (a0, b0)) :: Bool #

type ((Proxy * (a0, b0)) :<= (arg :: Proxy * (a0, b0))) (arg :: Proxy * (a0, b0)) :: Bool #

type ((Proxy * (a0, b0)) :> (arg :: Proxy * (a0, b0))) (arg :: Proxy * (a0, b0)) :: Bool #

type ((Proxy * (a0, b0)) :>= (arg :: Proxy * (a0, b0))) (arg :: Proxy * (a0, b0)) :: Bool #

type Max (Proxy * (a0, b0)) (arg :: Proxy * (a0, b0)) (arg :: Proxy * (a0, b0)) :: a #

type Min (Proxy * (a0, b0)) (arg :: Proxy * (a0, b0)) (arg :: Proxy * (a0, b0)) :: a #

POrd (a0, b0, c0) (Proxy * (a0, b0, c0)) # 

Associated Types

type Compare (Proxy * (a0, b0, c0)) (arg :: Proxy * (a0, b0, c0)) (arg :: Proxy * (a0, b0, c0)) :: Ordering #

type ((Proxy * (a0, b0, c0)) :< (arg :: Proxy * (a0, b0, c0))) (arg :: Proxy * (a0, b0, c0)) :: Bool #

type ((Proxy * (a0, b0, c0)) :<= (arg :: Proxy * (a0, b0, c0))) (arg :: Proxy * (a0, b0, c0)) :: Bool #

type ((Proxy * (a0, b0, c0)) :> (arg :: Proxy * (a0, b0, c0))) (arg :: Proxy * (a0, b0, c0)) :: Bool #

type ((Proxy * (a0, b0, c0)) :>= (arg :: Proxy * (a0, b0, c0))) (arg :: Proxy * (a0, b0, c0)) :: Bool #

type Max (Proxy * (a0, b0, c0)) (arg :: Proxy * (a0, b0, c0)) (arg :: Proxy * (a0, b0, c0)) :: a #

type Min (Proxy * (a0, b0, c0)) (arg :: Proxy * (a0, b0, c0)) (arg :: Proxy * (a0, b0, c0)) :: a #

POrd (a0, b0, c0, d0) (Proxy * (a0, b0, c0, d0)) # 

Associated Types

type Compare (Proxy * (a0, b0, c0, d0)) (arg :: Proxy * (a0, b0, c0, d0)) (arg :: Proxy * (a0, b0, c0, d0)) :: Ordering #

type ((Proxy * (a0, b0, c0, d0)) :< (arg :: Proxy * (a0, b0, c0, d0))) (arg :: Proxy * (a0, b0, c0, d0)) :: Bool #

type ((Proxy * (a0, b0, c0, d0)) :<= (arg :: Proxy * (a0, b0, c0, d0))) (arg :: Proxy * (a0, b0, c0, d0)) :: Bool #

type ((Proxy * (a0, b0, c0, d0)) :> (arg :: Proxy * (a0, b0, c0, d0))) (arg :: Proxy * (a0, b0, c0, d0)) :: Bool #

type ((Proxy * (a0, b0, c0, d0)) :>= (arg :: Proxy * (a0, b0, c0, d0))) (arg :: Proxy * (a0, b0, c0, d0)) :: Bool #

type Max (Proxy * (a0, b0, c0, d0)) (arg :: Proxy * (a0, b0, c0, d0)) (arg :: Proxy * (a0, b0, c0, d0)) :: a #

type Min (Proxy * (a0, b0, c0, d0)) (arg :: Proxy * (a0, b0, c0, d0)) (arg :: Proxy * (a0, b0, c0, d0)) :: a #

POrd (a0, b0, c0, d0, e0) (Proxy * (a0, b0, c0, d0, e0)) # 

Associated Types

type Compare (Proxy * (a0, b0, c0, d0, e0)) (arg :: Proxy * (a0, b0, c0, d0, e0)) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: Ordering #

type ((Proxy * (a0, b0, c0, d0, e0)) :< (arg :: Proxy * (a0, b0, c0, d0, e0))) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: Bool #

type ((Proxy * (a0, b0, c0, d0, e0)) :<= (arg :: Proxy * (a0, b0, c0, d0, e0))) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: Bool #

type ((Proxy * (a0, b0, c0, d0, e0)) :> (arg :: Proxy * (a0, b0, c0, d0, e0))) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: Bool #

type ((Proxy * (a0, b0, c0, d0, e0)) :>= (arg :: Proxy * (a0, b0, c0, d0, e0))) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: Bool #

type Max (Proxy * (a0, b0, c0, d0, e0)) (arg :: Proxy * (a0, b0, c0, d0, e0)) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: a #

type Min (Proxy * (a0, b0, c0, d0, e0)) (arg :: Proxy * (a0, b0, c0, d0, e0)) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: a #

POrd (a0, b0, c0, d0, e0, f0) (Proxy * (a0, b0, c0, d0, e0, f0)) # 

Associated Types

type Compare (Proxy * (a0, b0, c0, d0, e0, f0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: Ordering #

type ((Proxy * (a0, b0, c0, d0, e0, f0)) :< (arg :: Proxy * (a0, b0, c0, d0, e0, f0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: Bool #

type ((Proxy * (a0, b0, c0, d0, e0, f0)) :<= (arg :: Proxy * (a0, b0, c0, d0, e0, f0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: Bool #

type ((Proxy * (a0, b0, c0, d0, e0, f0)) :> (arg :: Proxy * (a0, b0, c0, d0, e0, f0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: Bool #

type ((Proxy * (a0, b0, c0, d0, e0, f0)) :>= (arg :: Proxy * (a0, b0, c0, d0, e0, f0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: Bool #

type Max (Proxy * (a0, b0, c0, d0, e0, f0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: a #

type Min (Proxy * (a0, b0, c0, d0, e0, f0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: a #

POrd (a0, b0, c0, d0, e0, f0, g0) (Proxy * (a0, b0, c0, d0, e0, f0, g0)) # 

Associated Types

type Compare (Proxy * (a0, b0, c0, d0, e0, f0, g0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: Ordering #

type ((Proxy * (a0, b0, c0, d0, e0, f0, g0)) :< (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: Bool #

type ((Proxy * (a0, b0, c0, d0, e0, f0, g0)) :<= (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: Bool #

type ((Proxy * (a0, b0, c0, d0, e0, f0, g0)) :> (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: Bool #

type ((Proxy * (a0, b0, c0, d0, e0, f0, g0)) :>= (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: Bool #

type Max (Proxy * (a0, b0, c0, d0, e0, f0, g0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: a #

type Min (Proxy * (a0, b0, c0, d0, e0, f0, g0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: a #

class SEq a => SOrd a where #

Methods

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

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

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

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

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

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

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

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

(%:<) :: forall t t. (Apply (Apply (:<$) t) t ~ Apply (Apply TFHelper_6989586621679588852Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply (:<$) t) t :: Bool) infix 4 #

(%:<=) :: forall t t. (Apply (Apply (:<=$) t) t ~ Apply (Apply TFHelper_6989586621679588885Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply (:<=$) t) t :: Bool) infix 4 #

(%:>) :: forall t t. (Apply (Apply (:>$) t) t ~ Apply (Apply TFHelper_6989586621679588918Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply (:>$) t) t :: Bool) infix 4 #

(%:>=) :: forall t t. (Apply (Apply (:>=$) t) t ~ Apply (Apply TFHelper_6989586621679588951Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply (:>=$) t) t :: Bool) infix 4 #

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

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

Instances

SOrd Bool # 
SOrd Ordering # 
SOrd () # 

Methods

sCompare :: Sing () t -> Sing () t -> Sing Ordering (Apply () Ordering (Apply () (TyFun () Ordering -> Type) (CompareSym0 ()) t) t) #

(%:<) :: Sing () t -> Sing () t -> Sing Bool (Apply () Bool (Apply () (TyFun () Bool -> Type) ((:<$) ()) t) t) #

(%:<=) :: Sing () t -> Sing () t -> Sing Bool (Apply () Bool (Apply () (TyFun () Bool -> Type) ((:<=$) ()) t) t) #

(%:>) :: Sing () t -> Sing () t -> Sing Bool (Apply () Bool (Apply () (TyFun () Bool -> Type) ((:>$) ()) t) t) #

(%:>=) :: Sing () t -> Sing () t -> Sing Bool (Apply () Bool (Apply () (TyFun () Bool -> Type) ((:>=$) ()) t) t) #

sMax :: Sing () t -> Sing () t -> Sing () (Apply () () (Apply () (TyFun () () -> Type) (MaxSym0 ()) t) t) #

sMin :: Sing () t -> Sing () t -> Sing () (Apply () () (Apply () (TyFun () () -> Type) (MinSym0 ()) t) t) #

(SOrd a0, SOrd [a0]) => SOrd [a0] # 

Methods

sCompare :: Sing [a0] t -> Sing [a0] t -> Sing Ordering (Apply [a0] Ordering (Apply [a0] (TyFun [a0] Ordering -> Type) (CompareSym0 [a0]) t) t) #

(%:<) :: Sing [a0] t -> Sing [a0] t -> Sing Bool (Apply [a0] Bool (Apply [a0] (TyFun [a0] Bool -> Type) ((:<$) [a0]) t) t) #

(%:<=) :: Sing [a0] t -> Sing [a0] t -> Sing Bool (Apply [a0] Bool (Apply [a0] (TyFun [a0] Bool -> Type) ((:<=$) [a0]) t) t) #

(%:>) :: Sing [a0] t -> Sing [a0] t -> Sing Bool (Apply [a0] Bool (Apply [a0] (TyFun [a0] Bool -> Type) ((:>$) [a0]) t) t) #

(%:>=) :: Sing [a0] t -> Sing [a0] t -> Sing Bool (Apply [a0] Bool (Apply [a0] (TyFun [a0] Bool -> Type) ((:>=$) [a0]) t) t) #

sMax :: Sing [a0] t -> Sing [a0] t -> Sing [a0] (Apply [a0] [a0] (Apply [a0] (TyFun [a0] [a0] -> Type) (MaxSym0 [a0]) t) t) #

sMin :: Sing [a0] t -> Sing [a0] t -> Sing [a0] (Apply [a0] [a0] (Apply [a0] (TyFun [a0] [a0] -> Type) (MinSym0 [a0]) t) t) #

SOrd a0 => SOrd (Maybe a0) # 

Methods

sCompare :: Sing (Maybe a0) t -> Sing (Maybe a0) t -> Sing Ordering (Apply (Maybe a0) Ordering (Apply (Maybe a0) (TyFun (Maybe a0) Ordering -> Type) (CompareSym0 (Maybe a0)) t) t) #

(%:<) :: Sing (Maybe a0) t -> Sing (Maybe a0) t -> Sing Bool (Apply (Maybe a0) Bool (Apply (Maybe a0) (TyFun (Maybe a0) Bool -> Type) ((:<$) (Maybe a0)) t) t) #

(%:<=) :: Sing (Maybe a0) t -> Sing (Maybe a0) t -> Sing Bool (Apply (Maybe a0) Bool (Apply (Maybe a0) (TyFun (Maybe a0) Bool -> Type) ((:<=$) (Maybe a0)) t) t) #

(%:>) :: Sing (Maybe a0) t -> Sing (Maybe a0) t -> Sing Bool (Apply (Maybe a0) Bool (Apply (Maybe a0) (TyFun (Maybe a0) Bool -> Type) ((:>$) (Maybe a0)) t) t) #

(%:>=) :: Sing (Maybe a0) t -> Sing (Maybe a0) t -> Sing Bool (Apply (Maybe a0) Bool (Apply (Maybe a0) (TyFun (Maybe a0) Bool -> Type) ((:>=$) (Maybe a0)) t) t) #

sMax :: Sing (Maybe a0) t -> Sing (Maybe a0) t -> Sing (Maybe a0) (Apply (Maybe a0) (Maybe a0) (Apply (Maybe a0) (TyFun (Maybe a0) (Maybe a0) -> Type) (MaxSym0 (Maybe a0)) t) t) #

sMin :: Sing (Maybe a0) t -> Sing (Maybe a0) t -> Sing (Maybe a0) (Apply (Maybe a0) (Maybe a0) (Apply (Maybe a0) (TyFun (Maybe a0) (Maybe a0) -> Type) (MinSym0 (Maybe a0)) t) t) #

(SOrd a0, SOrd [a0]) => SOrd (NonEmpty a0) # 

Methods

sCompare :: Sing (NonEmpty a0) t -> Sing (NonEmpty a0) t -> Sing Ordering (Apply (NonEmpty a0) Ordering (Apply (NonEmpty a0) (TyFun (NonEmpty a0) Ordering -> Type) (CompareSym0 (NonEmpty a0)) t) t) #

(%:<) :: Sing (NonEmpty a0) t -> Sing (NonEmpty a0) t -> Sing Bool (Apply (NonEmpty a0) Bool (Apply (NonEmpty a0) (TyFun (NonEmpty a0) Bool -> Type) ((:<$) (NonEmpty a0)) t) t) #

(%:<=) :: Sing (NonEmpty a0) t -> Sing (NonEmpty a0) t -> Sing Bool (Apply (NonEmpty a0) Bool (Apply (NonEmpty a0) (TyFun (NonEmpty a0) Bool -> Type) ((:<=$) (NonEmpty a0)) t) t) #

(%:>) :: Sing (NonEmpty a0) t -> Sing (NonEmpty a0) t -> Sing Bool (Apply (NonEmpty a0) Bool (Apply (NonEmpty a0) (TyFun (NonEmpty a0) Bool -> Type) ((:>$) (NonEmpty a0)) t) t) #

(%:>=) :: Sing (NonEmpty a0) t -> Sing (NonEmpty a0) t -> Sing Bool (Apply (NonEmpty a0) Bool (Apply (NonEmpty a0) (TyFun (NonEmpty a0) Bool -> Type) ((:>=$) (NonEmpty a0)) t) t) #

sMax :: Sing (NonEmpty a0) t -> Sing (NonEmpty a0) t -> Sing (NonEmpty a0) (Apply (NonEmpty a0) (NonEmpty a0) (Apply (NonEmpty a0) (TyFun (NonEmpty a0) (NonEmpty a0) -> Type) (MaxSym0 (NonEmpty a0)) t) t) #

sMin :: Sing (NonEmpty a0) t -> Sing (NonEmpty a0) t -> Sing (NonEmpty a0) (Apply (NonEmpty a0) (NonEmpty a0) (Apply (NonEmpty a0) (TyFun (NonEmpty a0) (NonEmpty a0) -> Type) (MinSym0 (NonEmpty a0)) t) t) #

(SOrd a0, SOrd b0) => SOrd (Either a0 b0) # 

Methods

sCompare :: Sing (Either a0 b0) t -> Sing (Either a0 b0) t -> Sing Ordering (Apply (Either a0 b0) Ordering (Apply (Either a0 b0) (TyFun (Either a0 b0) Ordering -> Type) (CompareSym0 (Either a0 b0)) t) t) #

(%:<) :: Sing (Either a0 b0) t -> Sing (Either a0 b0) t -> Sing Bool (Apply (Either a0 b0) Bool (Apply (Either a0 b0) (TyFun (Either a0 b0) Bool -> Type) ((:<$) (Either a0 b0)) t) t) #

(%:<=) :: Sing (Either a0 b0) t -> Sing (Either a0 b0) t -> Sing Bool (Apply (Either a0 b0) Bool (Apply (Either a0 b0) (TyFun (Either a0 b0) Bool -> Type) ((:<=$) (Either a0 b0)) t) t) #

(%:>) :: Sing (Either a0 b0) t -> Sing (Either a0 b0) t -> Sing Bool (Apply (Either a0 b0) Bool (Apply (Either a0 b0) (TyFun (Either a0 b0) Bool -> Type) ((:>$) (Either a0 b0)) t) t) #

(%:>=) :: Sing (Either a0 b0) t -> Sing (Either a0 b0) t -> Sing Bool (Apply (Either a0 b0) Bool (Apply (Either a0 b0) (TyFun (Either a0 b0) Bool -> Type) ((:>=$) (Either a0 b0)) t) t) #

sMax :: Sing (Either a0 b0) t -> Sing (Either a0 b0) t -> Sing (Either a0 b0) (Apply (Either a0 b0) (Either a0 b0) (Apply (Either a0 b0) (TyFun (Either a0 b0) (Either a0 b0) -> Type) (MaxSym0 (Either a0 b0)) t) t) #

sMin :: Sing (Either a0 b0) t -> Sing (Either a0 b0) t -> Sing (Either a0 b0) (Apply (Either a0 b0) (Either a0 b0) (Apply (Either a0 b0) (TyFun (Either a0 b0) (Either a0 b0) -> Type) (MinSym0 (Either a0 b0)) t) t) #

(SOrd a0, SOrd b0) => SOrd (a0, b0) # 

Methods

sCompare :: Sing (a0, b0) t -> Sing (a0, b0) t -> Sing Ordering (Apply (a0, b0) Ordering (Apply (a0, b0) (TyFun (a0, b0) Ordering -> Type) (CompareSym0 (a0, b0)) t) t) #

(%:<) :: Sing (a0, b0) t -> Sing (a0, b0) t -> Sing Bool (Apply (a0, b0) Bool (Apply (a0, b0) (TyFun (a0, b0) Bool -> Type) ((:<$) (a0, b0)) t) t) #

(%:<=) :: Sing (a0, b0) t -> Sing (a0, b0) t -> Sing Bool (Apply (a0, b0) Bool (Apply (a0, b0) (TyFun (a0, b0) Bool -> Type) ((:<=$) (a0, b0)) t) t) #

(%:>) :: Sing (a0, b0) t -> Sing (a0, b0) t -> Sing Bool (Apply (a0, b0) Bool (Apply (a0, b0) (TyFun (a0, b0) Bool -> Type) ((:>$) (a0, b0)) t) t) #

(%:>=) :: Sing (a0, b0) t -> Sing (a0, b0) t -> Sing Bool (Apply (a0, b0) Bool (Apply (a0, b0) (TyFun (a0, b0) Bool -> Type) ((:>=$) (a0, b0)) t) t) #

sMax :: Sing (a0, b0) t -> Sing (a0, b0) t -> Sing (a0, b0) (Apply (a0, b0) (a0, b0) (Apply (a0, b0) (TyFun (a0, b0) (a0, b0) -> Type) (MaxSym0 (a0, b0)) t) t) #

sMin :: Sing (a0, b0) t -> Sing (a0, b0) t -> Sing (a0, b0) (Apply (a0, b0) (a0, b0) (Apply (a0, b0) (TyFun (a0, b0) (a0, b0) -> Type) (MinSym0 (a0, b0)) t) t) #

(SOrd a0, SOrd b0, SOrd c0) => SOrd (a0, b0, c0) # 

Methods

sCompare :: Sing (a0, b0, c0) t -> Sing (a0, b0, c0) t -> Sing Ordering (Apply (a0, b0, c0) Ordering (Apply (a0, b0, c0) (TyFun (a0, b0, c0) Ordering -> Type) (CompareSym0 (a0, b0, c0)) t) t) #

(%:<) :: Sing (a0, b0, c0) t -> Sing (a0, b0, c0) t -> Sing Bool (Apply (a0, b0, c0) Bool (Apply (a0, b0, c0) (TyFun (a0, b0, c0) Bool -> Type) ((:<$) (a0, b0, c0)) t) t) #

(%:<=) :: Sing (a0, b0, c0) t -> Sing (a0, b0, c0) t -> Sing Bool (Apply (a0, b0, c0) Bool (Apply (a0, b0, c0) (TyFun (a0, b0, c0) Bool -> Type) ((:<=$) (a0, b0, c0)) t) t) #

(%:>) :: Sing (a0, b0, c0) t -> Sing (a0, b0, c0) t -> Sing Bool (Apply (a0, b0, c0) Bool (Apply (a0, b0, c0) (TyFun (a0, b0, c0) Bool -> Type) ((:>$) (a0, b0, c0)) t) t) #

(%:>=) :: Sing (a0, b0, c0) t -> Sing (a0, b0, c0) t -> Sing Bool (Apply (a0, b0, c0) Bool (Apply (a0, b0, c0) (TyFun (a0, b0, c0) Bool -> Type) ((:>=$) (a0, b0, c0)) t) t) #

sMax :: Sing (a0, b0, c0) t -> Sing (a0, b0, c0) t -> Sing (a0, b0, c0) (Apply (a0, b0, c0) (a0, b0, c0) (Apply (a0, b0, c0) (TyFun (a0, b0, c0) (a0, b0, c0) -> Type) (MaxSym0 (a0, b0, c0)) t) t) #

sMin :: Sing (a0, b0, c0) t -> Sing (a0, b0, c0) t -> Sing (a0, b0, c0) (Apply (a0, b0, c0) (a0, b0, c0) (Apply (a0, b0, c0) (TyFun (a0, b0, c0) (a0, b0, c0) -> Type) (MinSym0 (a0, b0, c0)) t) t) #

(SOrd a0, SOrd b0, SOrd c0, SOrd d0) => SOrd (a0, b0, c0, d0) # 

Methods

sCompare :: Sing (a0, b0, c0, d0) t -> Sing (a0, b0, c0, d0) t -> Sing Ordering (Apply (a0, b0, c0, d0) Ordering (Apply (a0, b0, c0, d0) (TyFun (a0, b0, c0, d0) Ordering -> Type) (CompareSym0 (a0, b0, c0, d0)) t) t) #

(%:<) :: Sing (a0, b0, c0, d0) t -> Sing (a0, b0, c0, d0) t -> Sing Bool (Apply (a0, b0, c0, d0) Bool (Apply (a0, b0, c0, d0) (TyFun (a0, b0, c0, d0) Bool -> Type) ((:<$) (a0, b0, c0, d0)) t) t) #

(%:<=) :: Sing (a0, b0, c0, d0) t -> Sing (a0, b0, c0, d0) t -> Sing Bool (Apply (a0, b0, c0, d0) Bool (Apply (a0, b0, c0, d0) (TyFun (a0, b0, c0, d0) Bool -> Type) ((:<=$) (a0, b0, c0, d0)) t) t) #

(%:>) :: Sing (a0, b0, c0, d0) t -> Sing (a0, b0, c0, d0) t -> Sing Bool (Apply (a0, b0, c0, d0) Bool (Apply (a0, b0, c0, d0) (TyFun (a0, b0, c0, d0) Bool -> Type) ((:>$) (a0, b0, c0, d0)) t) t) #

(%:>=) :: Sing (a0, b0, c0, d0) t -> Sing (a0, b0, c0, d0) t -> Sing Bool (Apply (a0, b0, c0, d0) Bool (Apply (a0, b0, c0, d0) (TyFun (a0, b0, c0, d0) Bool -> Type) ((:>=$) (a0, b0, c0, d0)) t) t) #

sMax :: Sing (a0, b0, c0, d0) t -> Sing (a0, b0, c0, d0) t -> Sing (a0, b0, c0, d0) (Apply (a0, b0, c0, d0) (a0, b0, c0, d0) (Apply (a0, b0, c0, d0) (TyFun (a0, b0, c0, d0) (a0, b0, c0, d0) -> Type) (MaxSym0 (a0, b0, c0, d0)) t) t) #

sMin :: Sing (a0, b0, c0, d0) t -> Sing (a0, b0, c0, d0) t -> Sing (a0, b0, c0, d0) (Apply (a0, b0, c0, d0) (a0, b0, c0, d0) (Apply (a0, b0, c0, d0) (TyFun (a0, b0, c0, d0) (a0, b0, c0, d0) -> Type) (MinSym0 (a0, b0, c0, d0)) t) t) #

(SOrd a0, SOrd b0, SOrd c0, SOrd d0, SOrd e0) => SOrd (a0, b0, c0, d0, e0) # 

Methods

sCompare :: Sing (a0, b0, c0, d0, e0) t -> Sing (a0, b0, c0, d0, e0) t -> Sing Ordering (Apply (a0, b0, c0, d0, e0) Ordering (Apply (a0, b0, c0, d0, e0) (TyFun (a0, b0, c0, d0, e0) Ordering -> Type) (CompareSym0 (a0, b0, c0, d0, e0)) t) t) #

(%:<) :: Sing (a0, b0, c0, d0, e0) t -> Sing (a0, b0, c0, d0, e0) t -> Sing Bool (Apply (a0, b0, c0, d0, e0) Bool (Apply (a0, b0, c0, d0, e0) (TyFun (a0, b0, c0, d0, e0) Bool -> Type) ((:<$) (a0, b0, c0, d0, e0)) t) t) #

(%:<=) :: Sing (a0, b0, c0, d0, e0) t -> Sing (a0, b0, c0, d0, e0) t -> Sing Bool (Apply (a0, b0, c0, d0, e0) Bool (Apply (a0, b0, c0, d0, e0) (TyFun (a0, b0, c0, d0, e0) Bool -> Type) ((:<=$) (a0, b0, c0, d0, e0)) t) t) #

(%:>) :: Sing (a0, b0, c0, d0, e0) t -> Sing (a0, b0, c0, d0, e0) t -> Sing Bool (Apply (a0, b0, c0, d0, e0) Bool (Apply (a0, b0, c0, d0, e0) (TyFun (a0, b0, c0, d0, e0) Bool -> Type) ((:>$) (a0, b0, c0, d0, e0)) t) t) #

(%:>=) :: Sing (a0, b0, c0, d0, e0) t -> Sing (a0, b0, c0, d0, e0) t -> Sing Bool (Apply (a0, b0, c0, d0, e0) Bool (Apply (a0, b0, c0, d0, e0) (TyFun (a0, b0, c0, d0, e0) Bool -> Type) ((:>=$) (a0, b0, c0, d0, e0)) t) t) #

sMax :: Sing (a0, b0, c0, d0, e0) t -> Sing (a0, b0, c0, d0, e0) t -> Sing (a0, b0, c0, d0, e0) (Apply (a0, b0, c0, d0, e0) (a0, b0, c0, d0, e0) (Apply (a0, b0, c0, d0, e0) (TyFun (a0, b0, c0, d0, e0) (a0, b0, c0, d0, e0) -> Type) (MaxSym0 (a0, b0, c0, d0, e0)) t) t) #

sMin :: Sing (a0, b0, c0, d0, e0) t -> Sing (a0, b0, c0, d0, e0) t -> Sing (a0, b0, c0, d0, e0) (Apply (a0, b0, c0, d0, e0) (a0, b0, c0, d0, e0) (Apply (a0, b0, c0, d0, e0) (TyFun (a0, b0, c0, d0, e0) (a0, b0, c0, d0, e0) -> Type) (MinSym0 (a0, b0, c0, d0, e0)) t) t) #

(SOrd a0, SOrd b0, SOrd c0, SOrd d0, SOrd e0, SOrd f0) => SOrd (a0, b0, c0, d0, e0, f0) # 

Methods

sCompare :: Sing (a0, b0, c0, d0, e0, f0) t -> Sing (a0, b0, c0, d0, e0, f0) t -> Sing Ordering (Apply (a0, b0, c0, d0, e0, f0) Ordering (Apply (a0, b0, c0, d0, e0, f0) (TyFun (a0, b0, c0, d0, e0, f0) Ordering -> Type) (CompareSym0 (a0, b0, c0, d0, e0, f0)) t) t) #

(%:<) :: Sing (a0, b0, c0, d0, e0, f0) t -> Sing (a0, b0, c0, d0, e0, f0) t -> Sing Bool (Apply (a0, b0, c0, d0, e0, f0) Bool (Apply (a0, b0, c0, d0, e0, f0) (TyFun (a0, b0, c0, d0, e0, f0) Bool -> Type) ((:<$) (a0, b0, c0, d0, e0, f0)) t) t) #

(%:<=) :: Sing (a0, b0, c0, d0, e0, f0) t -> Sing (a0, b0, c0, d0, e0, f0) t -> Sing Bool (Apply (a0, b0, c0, d0, e0, f0) Bool (Apply (a0, b0, c0, d0, e0, f0) (TyFun (a0, b0, c0, d0, e0, f0) Bool -> Type) ((:<=$) (a0, b0, c0, d0, e0, f0)) t) t) #

(%:>) :: Sing (a0, b0, c0, d0, e0, f0) t -> Sing (a0, b0, c0, d0, e0, f0) t -> Sing Bool (Apply (a0, b0, c0, d0, e0, f0) Bool (Apply (a0, b0, c0, d0, e0, f0) (TyFun (a0, b0, c0, d0, e0, f0) Bool -> Type) ((:>$) (a0, b0, c0, d0, e0, f0)) t) t) #

(%:>=) :: Sing (a0, b0, c0, d0, e0, f0) t -> Sing (a0, b0, c0, d0, e0, f0) t -> Sing Bool (Apply (a0, b0, c0, d0, e0, f0) Bool (Apply (a0, b0, c0, d0, e0, f0) (TyFun (a0, b0, c0, d0, e0, f0) Bool -> Type) ((:>=$) (a0, b0, c0, d0, e0, f0)) t) t) #

sMax :: Sing (a0, b0, c0, d0, e0, f0) t -> Sing (a0, b0, c0, d0, e0, f0) t -> Sing (a0, b0, c0, d0, e0, f0) (Apply (a0, b0, c0, d0, e0, f0) (a0, b0, c0, d0, e0, f0) (Apply (a0, b0, c0, d0, e0, f0) (TyFun (a0, b0, c0, d0, e0, f0) (a0, b0, c0, d0, e0, f0) -> Type) (MaxSym0 (a0, b0, c0, d0, e0, f0)) t) t) #

sMin :: Sing (a0, b0, c0, d0, e0, f0) t -> Sing (a0, b0, c0, d0, e0, f0) t -> Sing (a0, b0, c0, d0, e0, f0) (Apply (a0, b0, c0, d0, e0, f0) (a0, b0, c0, d0, e0, f0) (Apply (a0, b0, c0, d0, e0, f0) (TyFun (a0, b0, c0, d0, e0, f0) (a0, b0, c0, d0, e0, f0) -> Type) (MinSym0 (a0, b0, c0, d0, e0, f0)) t) t) #

(SOrd a0, SOrd b0, SOrd c0, SOrd d0, SOrd e0, SOrd f0, SOrd g0) => SOrd (a0, b0, c0, d0, e0, f0, g0) # 

Methods

sCompare :: Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing Ordering (Apply (a0, b0, c0, d0, e0, f0, g0) Ordering (Apply (a0, b0, c0, d0, e0, f0, g0) (TyFun (a0, b0, c0, d0, e0, f0, g0) Ordering -> Type) (CompareSym0 (a0, b0, c0, d0, e0, f0, g0)) t) t) #

(%:<) :: Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing Bool (Apply (a0, b0, c0, d0, e0, f0, g0) Bool (Apply (a0, b0, c0, d0, e0, f0, g0) (TyFun (a0, b0, c0, d0, e0, f0, g0) Bool -> Type) ((:<$) (a0, b0, c0, d0, e0, f0, g0)) t) t) #

(%:<=) :: Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing Bool (Apply (a0, b0, c0, d0, e0, f0, g0) Bool (Apply (a0, b0, c0, d0, e0, f0, g0) (TyFun (a0, b0, c0, d0, e0, f0, g0) Bool -> Type) ((:<=$) (a0, b0, c0, d0, e0, f0, g0)) t) t) #

(%:>) :: Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing Bool (Apply (a0, b0, c0, d0, e0, f0, g0) Bool (Apply (a0, b0, c0, d0, e0, f0, g0) (TyFun (a0, b0, c0, d0, e0, f0, g0) Bool -> Type) ((:>$) (a0, b0, c0, d0, e0, f0, g0)) t) t) #

(%:>=) :: Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing Bool (Apply (a0, b0, c0, d0, e0, f0, g0) Bool (Apply (a0, b0, c0, d0, e0, f0, g0) (TyFun (a0, b0, c0, d0, e0, f0, g0) Bool -> Type) ((:>=$) (a0, b0, c0, d0, e0, f0, g0)) t) t) #

sMax :: Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing (a0, b0, c0, d0, e0, f0, g0) (Apply (a0, b0, c0, d0, e0, f0, g0) (a0, b0, c0, d0, e0, f0, g0) (Apply (a0, b0, c0, d0, e0, f0, g0) (TyFun (a0, b0, c0, d0, e0, f0, g0) (a0, b0, c0, d0, e0, f0, g0) -> Type) (MaxSym0 (a0, b0, c0, d0, e0, f0, g0)) t) t) #

sMin :: Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing (a0, b0, c0, d0, e0, f0, g0) t -> Sing (a0, b0, c0, d0, e0, f0, g0) (Apply (a0, b0, c0, d0, e0, f0, g0) (a0, b0, c0, d0, e0, f0, g0) (Apply (a0, b0, c0, d0, e0, f0, g0) (TyFun (a0, b0, c0, d0, e0, f0, g0) (a0, b0, c0, d0, e0, f0, g0) -> Type) (MinSym0 (a0, b0, c0, d0, e0, f0, g0)) t) t) #

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

Equations

ThenCmp EQ x = x 
ThenCmp LT _z_6989586621679595891 = LTSym0 
ThenCmp GT _z_6989586621679595894 = GTSym0 

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

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

Equations

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

sFoldl :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) #

type family Any k :: k where ... #

The type constructor Any is type to which you can unsafely coerce any lifted type, and back.

  • It is lifted, and hence represented by a pointer
  • It does not claim to be a data type, and that's important for the code generator, because the code gen may enter a data value but never enters a function value.

It's also used to instantiate un-constrained type variables after type checking. For example, length has type

length :: forall a. [a] -> Int

and the list datacon for the empty list has type

[] :: forall a. [a]

In order to compose these two terms as length [] a type application is required, but there is no constraint on the choice. In this situation GHC uses Any:

length (Any *) ([] (Any *))

Above, we print kinds explicitly, as if with -fprint-explicit-kinds.

Note that Any is kind polymorphic; its kind is thus forall k. k.

class SDecide k where #

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 b. Sing a -> Sing b -> Decision (a :~: b) #

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

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

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

Since: 4.7.0.0

Constructors

Refl :: (:~:) k a a 

Instances

Category k ((:~:) k) 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

TestCoercion k ((:~:) k a) 

Methods

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

TestEquality k ((:~:) k a) 

Methods

testEquality :: f a -> f b -> Maybe (((k :~: a) :~: a) b) #

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

Methods

minBound :: (k :~: a) b #

maxBound :: (k :~: a) b #

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

Methods

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

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

toEnum :: Int -> (k :~: a) b #

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

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

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

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

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

Eq ((:~:) k a b) 

Methods

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

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

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

Methods

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

gunfold :: (forall c r. Data c => c (c -> 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 c. Data c => c -> c) -> (* :~: 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 ((:~:) k a b) 

Methods

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

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

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

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

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

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

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

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

Methods

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

readList :: ReadS [(k :~: a) b] #

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

readListPrec :: ReadPrec [(k :~: a) b] #

Show ((:~:) k a b) 

Methods

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

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

showList :: [(k :~: a) b] -> ShowS #

data Void :: * #

Uninhabited data type

Since: 4.8.0.0

Instances

Eq Void 

Methods

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

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

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 

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.

Show Void 

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Ix 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 

Associated Types

type Rep Void :: * -> * #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Semigroup Void 

Methods

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

sconcat :: NonEmpty Void -> Void #

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

Exception Void 
type Rep Void 
type Rep Void = D1 (MetaData "Void" "Data.Void" "base" False) V1

type Refuted a = a -> Void #

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 #

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

data Proxy k t :: forall k. k -> * #

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Monad (Proxy *) 

Methods

(>>=) :: Proxy * a -> (a -> Proxy * b) -> Proxy * b #

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

return :: a -> Proxy * a #

fail :: String -> Proxy * a #

Functor (Proxy *) 

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b #

(<$) :: a -> Proxy * b -> Proxy * a #

Applicative (Proxy *) 

Methods

pure :: a -> Proxy * a #

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

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

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

Foldable (Proxy *) 

Methods

fold :: Monoid m => Proxy * m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy * a -> m #

foldr :: (a -> b -> b) -> b -> Proxy * a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy * a -> b #

foldl :: (b -> a -> b) -> b -> Proxy * a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy * a -> b #

foldr1 :: (a -> a -> a) -> Proxy * a -> a #

foldl1 :: (a -> a -> a) -> Proxy * a -> a #

toList :: Proxy * a -> [a] #

null :: Proxy * a -> Bool #

length :: Proxy * a -> Int #

elem :: Eq a => a -> Proxy * a -> Bool #

maximum :: Ord a => Proxy * a -> a #

minimum :: Ord a => Proxy * a -> a #

sum :: Num a => Proxy * a -> a #

product :: Num a => Proxy * a -> a #

Traversable (Proxy *) 

Methods

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

sequenceA :: Applicative f => Proxy * (f a) -> f (Proxy * a) #

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

sequence :: Monad m => Proxy * (m a) -> m (Proxy * a) #

Generic1 (Proxy *) 

Associated Types

type Rep1 (Proxy * :: * -> *) :: * -> * #

Methods

from1 :: Proxy * a -> Rep1 (Proxy *) a #

to1 :: Rep1 (Proxy *) a -> Proxy * a #

Eq1 (Proxy *)

Since: 4.9.0.0

Methods

liftEq :: (a -> b -> Bool) -> Proxy * a -> Proxy * b -> Bool #

Ord1 (Proxy *)

Since: 4.9.0.0

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy * a -> Proxy * b -> Ordering #

Read1 (Proxy *)

Since: 4.9.0.0

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy * a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy * a] #

Show1 (Proxy *)

Since: 4.9.0.0

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy * a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy * a] -> ShowS #

Alternative (Proxy *) 

Methods

empty :: Proxy * a #

(<|>) :: Proxy * a -> Proxy * a -> Proxy * a #

some :: Proxy * a -> Proxy * [a] #

many :: Proxy * a -> Proxy * [a] #

MonadPlus (Proxy *) 

Methods

mzero :: Proxy * a #

mplus :: Proxy * a -> Proxy * a -> Proxy * a #

Bounded (Proxy k s) 

Methods

minBound :: Proxy k s #

maxBound :: Proxy k s #

Enum (Proxy k s) 

Methods

succ :: Proxy k s -> Proxy k s #

pred :: Proxy k s -> Proxy k s #

toEnum :: Int -> Proxy k s #

fromEnum :: Proxy k s -> Int #

enumFrom :: Proxy k s -> [Proxy k s] #

enumFromThen :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromTo :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromThenTo :: Proxy k s -> Proxy k s -> Proxy k s -> [Proxy k s] #

Eq (Proxy k s) 

Methods

(==) :: Proxy k s -> Proxy k s -> Bool #

(/=) :: Proxy k s -> Proxy k s -> Bool #

Data t => Data (Proxy * t) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy * t -> c (Proxy * t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy * t) #

toConstr :: Proxy * t -> Constr #

dataTypeOf :: Proxy * t -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Proxy * t -> Proxy * t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy * t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy * t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Proxy * t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy * t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) #

Ord (Proxy k s) 

Methods

compare :: Proxy k s -> Proxy k s -> Ordering #

(<) :: Proxy k s -> Proxy k s -> Bool #

(<=) :: Proxy k s -> Proxy k s -> Bool #

(>) :: Proxy k s -> Proxy k s -> Bool #

(>=) :: Proxy k s -> Proxy k s -> Bool #

max :: Proxy k s -> Proxy k s -> Proxy k s #

min :: Proxy k s -> Proxy k s -> Proxy k s #

Read (Proxy k s) 
Show (Proxy k s) 

Methods

showsPrec :: Int -> Proxy k s -> ShowS #

show :: Proxy k s -> String #

showList :: [Proxy k s] -> ShowS #

Ix (Proxy k s) 

Methods

range :: (Proxy k s, Proxy k s) -> [Proxy k s] #

index :: (Proxy k s, Proxy k s) -> Proxy k s -> Int #

unsafeIndex :: (Proxy k s, Proxy k s) -> Proxy k s -> Int

inRange :: (Proxy k s, Proxy k s) -> Proxy k s -> Bool #

rangeSize :: (Proxy k s, Proxy k s) -> Int #

unsafeRangeSize :: (Proxy k s, Proxy k s) -> Int

Generic (Proxy k t) 

Associated Types

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

Methods

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

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

Semigroup (Proxy k s) 

Methods

(<>) :: Proxy k s -> Proxy k s -> Proxy k s #

sconcat :: NonEmpty (Proxy k s) -> Proxy k s #

stimes :: Integral b => b -> Proxy k s -> Proxy k s #

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

type Rep1 (Proxy *) 
type Rep1 (Proxy *) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)
type Rep (Proxy k t) 
type Rep (Proxy k t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)

data SomeSing k where #

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

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

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

Constructors

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

type family Error (str :: k0) :: k #

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

data ErrorSym0 l #

Instances

SuppressUnusedWarnings (TyFun k06989586621679675033 k6989586621679675035 -> *) (ErrorSym0 k06989586621679675033 k6989586621679675035) # 

Methods

suppressUnusedWarnings :: Proxy (ErrorSym0 k06989586621679675033 k6989586621679675035) t -> () #

type Apply k06989586621679675033 k2 (ErrorSym0 k06989586621679675033 k2) l0 # 
type Apply k06989586621679675033 k2 (ErrorSym0 k06989586621679675033 k2) l0 = ErrorSym1 k2 k06989586621679675033 l0

type TrueSym0 = True #

type LTSym0 = LT #

type EQSym0 = EQ #

type GTSym0 = GT #

type Tuple0Sym0 = '() #

data Tuple2Sym0 l #

Instances

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun b3530822107858468867 (a3530822107858468866, b3530822107858468867) -> Type) -> *) (Tuple2Sym0 a3530822107858468866 b3530822107858468867) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple2Sym0 a3530822107858468866 b3530822107858468867) t -> () #

type Apply a3530822107858468866 (TyFun b3530822107858468867 (a3530822107858468866, b3530822107858468867) -> Type) (Tuple2Sym0 a3530822107858468866 b3530822107858468867) l0 # 
type Apply a3530822107858468866 (TyFun b3530822107858468867 (a3530822107858468866, b3530822107858468867) -> Type) (Tuple2Sym0 a3530822107858468866 b3530822107858468867) l0 = Tuple2Sym1 b3530822107858468867 a3530822107858468866 l0

data Tuple2Sym1 l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> TyFun b3530822107858468867 (a3530822107858468866, b3530822107858468867) -> *) (Tuple2Sym1 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple2Sym1 b3530822107858468867 a3530822107858468866) t -> () #

type Apply b3530822107858468867 (a3530822107858468866, b3530822107858468867) (Tuple2Sym1 b3530822107858468867 a3530822107858468866 l0) l1 # 
type Apply b3530822107858468867 (a3530822107858468866, b3530822107858468867) (Tuple2Sym1 b3530822107858468867 a3530822107858468866 l0) l1 = Tuple2Sym2 b3530822107858468867 a3530822107858468866 l0 l1

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

data Tuple3Sym0 l #

Instances

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (a3530822107858468866, b3530822107858468867, c3530822107858468868) -> Type) -> Type) -> *) (Tuple3Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868) t -> () #

type Apply a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (a3530822107858468866, b3530822107858468867, c3530822107858468868) -> Type) -> Type) (Tuple3Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868) l0 # 
type Apply a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (a3530822107858468866, b3530822107858468867, c3530822107858468868) -> Type) -> Type) (Tuple3Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868) l0 = Tuple3Sym1 b3530822107858468867 c3530822107858468868 a3530822107858468866 l0

data Tuple3Sym1 l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> TyFun b3530822107858468867 (TyFun c3530822107858468868 (a3530822107858468866, b3530822107858468867, c3530822107858468868) -> Type) -> *) (Tuple3Sym1 b3530822107858468867 c3530822107858468868 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym1 b3530822107858468867 c3530822107858468868 a3530822107858468866) t -> () #

type Apply b3530822107858468867 (TyFun c3530822107858468868 (a3530822107858468866, b3530822107858468867, c3530822107858468868) -> Type) (Tuple3Sym1 b3530822107858468867 c3530822107858468868 a3530822107858468866 l0) l1 # 
type Apply b3530822107858468867 (TyFun c3530822107858468868 (a3530822107858468866, b3530822107858468867, c3530822107858468868) -> Type) (Tuple3Sym1 b3530822107858468867 c3530822107858468868 a3530822107858468866 l0) l1 = Tuple3Sym2 c3530822107858468868 b3530822107858468867 a3530822107858468866 l0 l1

data Tuple3Sym2 l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> TyFun c3530822107858468868 (a3530822107858468866, b3530822107858468867, c3530822107858468868) -> *) (Tuple3Sym2 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym2 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

type Apply c3530822107858468868 (a3530822107858468866, b3530822107858468867, c3530822107858468868) (Tuple3Sym2 c3530822107858468868 b3530822107858468867 a3530822107858468866 l1 l0) l2 # 
type Apply c3530822107858468868 (a3530822107858468866, b3530822107858468867, c3530822107858468868) (Tuple3Sym2 c3530822107858468868 b3530822107858468867 a3530822107858468866 l1 l0) l2 = Tuple3Sym3 c3530822107858468868 b3530822107858468867 a3530822107858468866 l1 l0 l2

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

data Tuple4Sym0 l #

Instances

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> Type) -> Type) -> Type) -> *) (Tuple4Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869) t -> () #

type Apply a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> Type) -> Type) -> Type) (Tuple4Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869) l0 # 
type Apply a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> Type) -> Type) -> Type) (Tuple4Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869) l0 = Tuple4Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 a3530822107858468866 l0

data Tuple4Sym1 l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> Type) -> Type) -> *) (Tuple4Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 a3530822107858468866) t -> () #

type Apply b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> Type) -> Type) (Tuple4Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 a3530822107858468866 l0) l1 # 
type Apply b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> Type) -> Type) (Tuple4Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 a3530822107858468866 l0) l1 = Tuple4Sym2 c3530822107858468868 d3530822107858468869 b3530822107858468867 a3530822107858468866 l0 l1

data Tuple4Sym2 l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> TyFun c3530822107858468868 (TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> Type) -> *) (Tuple4Sym2 c3530822107858468868 d3530822107858468869 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym2 c3530822107858468868 d3530822107858468869 b3530822107858468867 a3530822107858468866) t -> () #

type Apply c3530822107858468868 (TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> Type) (Tuple4Sym2 c3530822107858468868 d3530822107858468869 b3530822107858468867 a3530822107858468866 l1 l0) l2 # 
type Apply c3530822107858468868 (TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> Type) (Tuple4Sym2 c3530822107858468868 d3530822107858468869 b3530822107858468867 a3530822107858468866 l1 l0) l2 = Tuple4Sym3 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l1 l0 l2

data Tuple4Sym3 l l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> *) (Tuple4Sym3 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym3 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

type Apply d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) (Tuple4Sym3 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l2 l1 l0) l3 # 
type Apply d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) (Tuple4Sym3 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l2 l1 l0) l3 = Tuple4Sym4 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l2 l1 l0 l3

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

data Tuple5Sym0 l #

Instances

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple5Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870) t -> () #

type Apply a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> Type) -> Type) -> Type) (Tuple5Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870) l0 # 
type Apply a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> Type) -> Type) -> Type) (Tuple5Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870) l0 = Tuple5Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 a3530822107858468866 l0

data Tuple5Sym1 l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> Type) -> Type) -> *) (Tuple5Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 a3530822107858468866) t -> () #

type Apply b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> Type) -> Type) (Tuple5Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 a3530822107858468866 l0) l1 # 
type Apply b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> Type) -> Type) (Tuple5Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 a3530822107858468866 l0) l1 = Tuple5Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 b3530822107858468867 a3530822107858468866 l0 l1

data Tuple5Sym2 l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> Type) -> *) (Tuple5Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 b3530822107858468867 a3530822107858468866) t -> () #

type Apply c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> Type) (Tuple5Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 b3530822107858468867 a3530822107858468866 l1 l0) l2 # 
type Apply c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> Type) (Tuple5Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 b3530822107858468867 a3530822107858468866 l1 l0) l2 = Tuple5Sym3 d3530822107858468869 e3530822107858468870 c3530822107858468868 b3530822107858468867 a3530822107858468866 l1 l0 l2

data Tuple5Sym3 l l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> *) (Tuple5Sym3 d3530822107858468869 e3530822107858468870 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym3 d3530822107858468869 e3530822107858468870 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

type Apply d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) (Tuple5Sym3 d3530822107858468869 e3530822107858468870 c3530822107858468868 b3530822107858468867 a3530822107858468866 l2 l1 l0) l3 # 
type Apply d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) (Tuple5Sym3 d3530822107858468869 e3530822107858468870 c3530822107858468868 b3530822107858468867 a3530822107858468866 l2 l1 l0) l3 = Tuple5Sym4 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l2 l1 l0 l3

data Tuple5Sym4 l l l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> d3530822107858468869 -> TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> *) (Tuple5Sym4 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym4 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

type Apply e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) (Tuple5Sym4 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l3 l2 l1 l0) l4 # 
type Apply e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) (Tuple5Sym4 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l3 l2 l1 l0) l4 = Tuple5Sym5 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l3 l2 l1 l0 l4

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

data Tuple6Sym0 l #

Instances

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple6Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871) t -> () #

type Apply a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple6Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871) l0 # 
type Apply a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple6Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871) l0 = Tuple6Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 a3530822107858468866 l0

data Tuple6Sym1 l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple6Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 a3530822107858468866) t -> () #

type Apply b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> Type) -> Type) (Tuple6Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 a3530822107858468866 l0) l1 # 
type Apply b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> Type) -> Type) (Tuple6Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 a3530822107858468866 l0) l1 = Tuple6Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 b3530822107858468867 a3530822107858468866 l0 l1

data Tuple6Sym2 l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> Type) -> *) (Tuple6Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 b3530822107858468867 a3530822107858468866) t -> () #

type Apply c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> Type) (Tuple6Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 b3530822107858468867 a3530822107858468866 l1 l0) l2 # 
type Apply c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> Type) (Tuple6Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 b3530822107858468867 a3530822107858468866 l1 l0) l2 = Tuple6Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 c3530822107858468868 b3530822107858468867 a3530822107858468866 l1 l0 l2

data Tuple6Sym3 l l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> *) (Tuple6Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

type Apply d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) (Tuple6Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 c3530822107858468868 b3530822107858468867 a3530822107858468866 l2 l1 l0) l3 # 
type Apply d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) (Tuple6Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 c3530822107858468868 b3530822107858468867 a3530822107858468866 l2 l1 l0) l3 = Tuple6Sym4 e3530822107858468870 f3530822107858468871 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l2 l1 l0 l3

data Tuple6Sym4 l l l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> d3530822107858468869 -> TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> *) (Tuple6Sym4 e3530822107858468870 f3530822107858468871 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym4 e3530822107858468870 f3530822107858468871 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

type Apply e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) (Tuple6Sym4 e3530822107858468870 f3530822107858468871 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l3 l2 l1 l0) l4 # 
type Apply e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) (Tuple6Sym4 e3530822107858468870 f3530822107858468871 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l3 l2 l1 l0) l4 = Tuple6Sym5 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l3 l2 l1 l0 l4

data Tuple6Sym5 l l l l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> d3530822107858468869 -> e3530822107858468870 -> TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> *) (Tuple6Sym5 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym5 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

type Apply f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) (Tuple6Sym5 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l4 l3 l2 l1 l0) l5 # 
type Apply f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) (Tuple6Sym5 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l4 l3 l2 l1 l0) l5 = Tuple6Sym6 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l4 l3 l2 l1 l0 l5

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

data Tuple7Sym0 l #

Instances

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872) t -> () #

type Apply a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872) l0 # 
type Apply a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872) l0 = Tuple7Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 a3530822107858468866 l0

data Tuple7Sym1 l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 a3530822107858468866) t -> () #

type Apply b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 a3530822107858468866 l0) l1 # 
type Apply b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 a3530822107858468866 l0) l1 = Tuple7Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 b3530822107858468867 a3530822107858468866 l0 l1

data Tuple7Sym2 l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 b3530822107858468867 a3530822107858468866) t -> () #

type Apply c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 b3530822107858468867 a3530822107858468866 l1 l0) l2 # 
type Apply c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 b3530822107858468867 a3530822107858468866 l1 l0) l2 = Tuple7Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 c3530822107858468868 b3530822107858468867 a3530822107858468866 l1 l0 l2

data Tuple7Sym3 l l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> *) (Tuple7Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

type Apply d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) (Tuple7Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 c3530822107858468868 b3530822107858468867 a3530822107858468866 l2 l1 l0) l3 # 
type Apply d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) (Tuple7Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 c3530822107858468868 b3530822107858468867 a3530822107858468866 l2 l1 l0) l3 = Tuple7Sym4 e3530822107858468870 f3530822107858468871 g3530822107858468872 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l2 l1 l0 l3

data Tuple7Sym4 l l l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> d3530822107858468869 -> TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> *) (Tuple7Sym4 e3530822107858468870 f3530822107858468871 g3530822107858468872 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym4 e3530822107858468870 f3530822107858468871 g3530822107858468872 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

type Apply e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) (Tuple7Sym4 e3530822107858468870 f3530822107858468871 g3530822107858468872 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l3 l2 l1 l0) l4 # 
type Apply e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) (Tuple7Sym4 e3530822107858468870 f3530822107858468871 g3530822107858468872 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l3 l2 l1 l0) l4 = Tuple7Sym5 f3530822107858468871 g3530822107858468872 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l3 l2 l1 l0 l4

data Tuple7Sym5 l l l l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> d3530822107858468869 -> e3530822107858468870 -> TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> *) (Tuple7Sym5 f3530822107858468871 g3530822107858468872 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym5 f3530822107858468871 g3530822107858468872 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

type Apply f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) (Tuple7Sym5 f3530822107858468871 g3530822107858468872 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l4 l3 l2 l1 l0) l5 # 
type Apply f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) (Tuple7Sym5 f3530822107858468871 g3530822107858468872 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l4 l3 l2 l1 l0) l5 = Tuple7Sym6 g3530822107858468872 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l4 l3 l2 l1 l0 l5

data Tuple7Sym6 l l l l l l l #

Instances

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> d3530822107858468869 -> e3530822107858468870 -> f3530822107858468871 -> TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> *) (Tuple7Sym6 g3530822107858468872 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym6 g3530822107858468872 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

type Apply g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) (Tuple7Sym6 g3530822107858468872 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l5 l4 l3 l2 l1 l0) l6 # 
type Apply g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) (Tuple7Sym6 g3530822107858468872 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l5 l4 l3 l2 l1 l0) l6 = Tuple7Sym7 g3530822107858468872 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866 l5 l4 l3 l2 l1 l0 l6

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

data CompareSym0 l #

Instances

SuppressUnusedWarnings (TyFun a6989586621679586420 (TyFun a6989586621679586420 Ordering -> Type) -> *) (CompareSym0 a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy (CompareSym0 a6989586621679586420) t -> () #

type Apply a6989586621679586420 (TyFun a6989586621679586420 Ordering -> Type) (CompareSym0 a6989586621679586420) l0 # 
type Apply a6989586621679586420 (TyFun a6989586621679586420 Ordering -> Type) (CompareSym0 a6989586621679586420) l0 = CompareSym1 a6989586621679586420 l0

data FoldlSym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679509136 (TyFun a6989586621679509135 b6989586621679509136 -> Type) -> Type) (TyFun b6989586621679509136 (TyFun [a6989586621679509135] b6989586621679509136 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679509135 b6989586621679509136) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym0 a6989586621679509135 b6989586621679509136) t -> () #

type Apply (TyFun b6989586621679509136 (TyFun a6989586621679509135 b6989586621679509136 -> Type) -> Type) (TyFun b6989586621679509136 (TyFun [a6989586621679509135] b6989586621679509136 -> Type) -> Type) (FoldlSym0 a6989586621679509135 b6989586621679509136) l0 # 
type Apply (TyFun b6989586621679509136 (TyFun a6989586621679509135 b6989586621679509136 -> Type) -> Type) (TyFun b6989586621679509136 (TyFun [a6989586621679509135] b6989586621679509136 -> Type) -> Type) (FoldlSym0 a6989586621679509135 b6989586621679509136) l0 = FoldlSym1 a6989586621679509135 b6989586621679509136 l0

class SuppressUnusedWarnings t where #

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

Methods

suppressUnusedWarnings :: Proxy t -> () #

Instances

SuppressUnusedWarnings (Bool -> TyFun Bool Bool -> *) (:&&$$) # 
SuppressUnusedWarnings (Bool -> TyFun Bool Bool -> *) (:||$$) # 
SuppressUnusedWarnings (Ordering -> TyFun Ordering Ordering -> *) ThenCmpSym1 # 
SuppressUnusedWarnings (Nat -> TyFun Nat Nat -> *) (:^$$) # 
SuppressUnusedWarnings (TyFun Bool Bool -> *) NotSym0 # 
SuppressUnusedWarnings (TyFun Bool (TyFun Bool Bool -> Type) -> *) (:&&$) # 
SuppressUnusedWarnings (TyFun Bool (TyFun Bool Bool -> Type) -> *) (:||$) # 
SuppressUnusedWarnings (TyFun [Bool] Bool -> *) AndSym0 # 
SuppressUnusedWarnings (TyFun [Bool] Bool -> *) OrSym0 # 
SuppressUnusedWarnings (TyFun Ordering (TyFun Ordering Ordering -> Type) -> *) ThenCmpSym0 # 
SuppressUnusedWarnings (TyFun Nat (TyFun Nat Nat -> *) -> *) (:^$) # 
SuppressUnusedWarnings ((TyFun a6989586621679785711 Bool -> Type) -> TyFun [a6989586621679785711] Bool -> *) (Any_Sym1 a6989586621679785711) # 

Methods

suppressUnusedWarnings :: Proxy (Any_Sym1 a6989586621679785711) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796316 Bool -> Type) -> TyFun [a6989586621679796316] [a6989586621679796316] -> *) (DropWhileEndSym1 a6989586621679796316) # 

Methods

suppressUnusedWarnings :: Proxy (DropWhileEndSym1 a6989586621679796316) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796400 (TyFun a6989586621679796400 a6989586621679796400 -> Type) -> Type) -> TyFun [a6989586621679796400] a6989586621679796400 -> *) (Foldl1'Sym1 a6989586621679796400) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl1'Sym1 a6989586621679796400) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796327 (TyFun a6989586621679796327 Ordering -> Type) -> Type) -> TyFun [a6989586621679796327] a6989586621679796327 -> *) (MinimumBySym1 a6989586621679796327) # 

Methods

suppressUnusedWarnings :: Proxy (MinimumBySym1 a6989586621679796327) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796328 (TyFun a6989586621679796328 Ordering -> Type) -> Type) -> TyFun [a6989586621679796328] a6989586621679796328 -> *) (MaximumBySym1 a6989586621679796328) # 

Methods

suppressUnusedWarnings :: Proxy (MaximumBySym1 a6989586621679796328) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796401 (TyFun a6989586621679796401 a6989586621679796401 -> Type) -> Type) -> TyFun [a6989586621679796401] a6989586621679796401 -> *) (Foldl1Sym1 a6989586621679796401) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl1Sym1 a6989586621679796401) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796399 (TyFun a6989586621679796399 a6989586621679796399 -> Type) -> Type) -> TyFun [a6989586621679796399] a6989586621679796399 -> *) (Foldr1Sym1 a6989586621679796399) # 

Methods

suppressUnusedWarnings :: Proxy (Foldr1Sym1 a6989586621679796399) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796395 Bool -> Type) -> TyFun [a6989586621679796395] Bool -> *) (AllSym1 a6989586621679796395) # 

Methods

suppressUnusedWarnings :: Proxy (AllSym1 a6989586621679796395) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796392 (TyFun a6989586621679796392 a6989586621679796392 -> Type) -> Type) -> TyFun [a6989586621679796392] [a6989586621679796392] -> *) (Scanl1Sym1 a6989586621679796392) # 

Methods

suppressUnusedWarnings :: Proxy (Scanl1Sym1 a6989586621679796392) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796389 (TyFun a6989586621679796389 a6989586621679796389 -> Type) -> Type) -> TyFun [a6989586621679796389] [a6989586621679796389] -> *) (Scanr1Sym1 a6989586621679796389) # 

Methods

suppressUnusedWarnings :: Proxy (Scanr1Sym1 a6989586621679796389) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796322 Bool -> Type) -> TyFun [a6989586621679796322] (Maybe Nat) -> *) (FindIndexSym1 a6989586621679796322) # 

Methods

suppressUnusedWarnings :: Proxy (FindIndexSym1 a6989586621679796322) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796321 Bool -> Type) -> TyFun [a6989586621679796321] [Nat] -> *) (FindIndicesSym1 a6989586621679796321) # 

Methods

suppressUnusedWarnings :: Proxy (FindIndicesSym1 a6989586621679796321) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796291 (TyFun a6989586621679796291 Bool -> Type) -> Type) -> TyFun [a6989586621679796291] (TyFun [a6989586621679796291] [a6989586621679796291] -> Type) -> *) (UnionBySym1 a6989586621679796291) # 

Methods

suppressUnusedWarnings :: Proxy (UnionBySym1 a6989586621679796291) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796291 (TyFun a6989586621679796291 Bool -> Type) -> Type) -> [a6989586621679796291] -> TyFun [a6989586621679796291] [a6989586621679796291] -> *) (UnionBySym2 a6989586621679796291) # 

Methods

suppressUnusedWarnings :: Proxy (UnionBySym2 a6989586621679796291) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796331 (TyFun a6989586621679796331 Bool -> Type) -> Type) -> TyFun [a6989586621679796331] (TyFun [a6989586621679796331] [a6989586621679796331] -> Type) -> *) (DeleteFirstsBySym1 a6989586621679796331) # 

Methods

suppressUnusedWarnings :: Proxy (DeleteFirstsBySym1 a6989586621679796331) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796331 (TyFun a6989586621679796331 Bool -> Type) -> Type) -> [a6989586621679796331] -> TyFun [a6989586621679796331] [a6989586621679796331] -> *) (DeleteFirstsBySym2 a6989586621679796331) # 

Methods

suppressUnusedWarnings :: Proxy (DeleteFirstsBySym2 a6989586621679796331) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796332 (TyFun a6989586621679796332 Bool -> Type) -> Type) -> TyFun a6989586621679796332 (TyFun [a6989586621679796332] [a6989586621679796332] -> Type) -> *) (DeleteBySym1 a6989586621679796332) # 

Methods

suppressUnusedWarnings :: Proxy (DeleteBySym1 a6989586621679796332) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796332 (TyFun a6989586621679796332 Bool -> Type) -> Type) -> a6989586621679796332 -> TyFun [a6989586621679796332] [a6989586621679796332] -> *) (DeleteBySym2 a6989586621679796332) # 

Methods

suppressUnusedWarnings :: Proxy (DeleteBySym2 a6989586621679796332) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796330 (TyFun a6989586621679796330 Ordering -> Type) -> Type) -> TyFun [a6989586621679796330] [a6989586621679796330] -> *) (SortBySym1 a6989586621679796330) # 

Methods

suppressUnusedWarnings :: Proxy (SortBySym1 a6989586621679796330) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796329 (TyFun a6989586621679796329 Ordering -> Type) -> Type) -> TyFun a6989586621679796329 (TyFun [a6989586621679796329] [a6989586621679796329] -> Type) -> *) (InsertBySym1 a6989586621679796329) # 

Methods

suppressUnusedWarnings :: Proxy (InsertBySym1 a6989586621679796329) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796329 (TyFun a6989586621679796329 Ordering -> Type) -> Type) -> a6989586621679796329 -> TyFun [a6989586621679796329] [a6989586621679796329] -> *) (InsertBySym2 a6989586621679796329) # 

Methods

suppressUnusedWarnings :: Proxy (InsertBySym2 a6989586621679796329) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796319 (TyFun a6989586621679796319 Bool -> Type) -> Type) -> TyFun [a6989586621679796319] (TyFun [a6989586621679796319] [a6989586621679796319] -> Type) -> *) (IntersectBySym1 a6989586621679796319) # 

Methods

suppressUnusedWarnings :: Proxy (IntersectBySym1 a6989586621679796319) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796319 (TyFun a6989586621679796319 Bool -> Type) -> Type) -> [a6989586621679796319] -> TyFun [a6989586621679796319] [a6989586621679796319] -> *) (IntersectBySym2 a6989586621679796319) # 

Methods

suppressUnusedWarnings :: Proxy (IntersectBySym2 a6989586621679796319) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796325 Bool -> Type) -> TyFun [a6989586621679796325] (Maybe a6989586621679796325) -> *) (FindSym1 a6989586621679796325) # 

Methods

suppressUnusedWarnings :: Proxy (FindSym1 a6989586621679796325) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796326 Bool -> Type) -> TyFun [a6989586621679796326] [a6989586621679796326] -> *) (FilterSym1 a6989586621679796326) # 

Methods

suppressUnusedWarnings :: Proxy (FilterSym1 a6989586621679796326) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796318 Bool -> Type) -> TyFun [a6989586621679796318] [a6989586621679796318] -> *) (TakeWhileSym1 a6989586621679796318) # 

Methods

suppressUnusedWarnings :: Proxy (TakeWhileSym1 a6989586621679796318) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796317 Bool -> Type) -> TyFun [a6989586621679796317] [a6989586621679796317] -> *) (DropWhileSym1 a6989586621679796317) # 

Methods

suppressUnusedWarnings :: Proxy (DropWhileSym1 a6989586621679796317) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796305 (TyFun a6989586621679796305 Bool -> Type) -> Type) -> TyFun [a6989586621679796305] [[a6989586621679796305]] -> *) (GroupBySym1 a6989586621679796305) # 

Methods

suppressUnusedWarnings :: Proxy (GroupBySym1 a6989586621679796305) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796315 Bool -> Type) -> TyFun [a6989586621679796315] ([a6989586621679796315], [a6989586621679796315]) -> *) (SpanSym1 a6989586621679796315) # 

Methods

suppressUnusedWarnings :: Proxy (SpanSym1 a6989586621679796315) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796314 Bool -> Type) -> TyFun [a6989586621679796314] ([a6989586621679796314], [a6989586621679796314]) -> *) (BreakSym1 a6989586621679796314) # 

Methods

suppressUnusedWarnings :: Proxy (BreakSym1 a6989586621679796314) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796302 Bool -> Type) -> TyFun [a6989586621679796302] ([a6989586621679796302], [a6989586621679796302]) -> *) (PartitionSym1 a6989586621679796302) # 

Methods

suppressUnusedWarnings :: Proxy (PartitionSym1 a6989586621679796302) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796293 (TyFun a6989586621679796293 Bool -> Type) -> Type) -> TyFun [a6989586621679796293] [a6989586621679796293] -> *) (NubBySym1 a6989586621679796293) # 

Methods

suppressUnusedWarnings :: Proxy (NubBySym1 a6989586621679796293) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680073211 Bool -> Type) -> TyFun (TyFun a6989586621680073211 a6989586621680073211 -> Type) (TyFun a6989586621680073211 a6989586621680073211 -> Type) -> *) (UntilSym1 a6989586621680073211) # 

Methods

suppressUnusedWarnings :: Proxy (UntilSym1 a6989586621680073211) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680073211 Bool -> Type) -> (TyFun a6989586621680073211 a6989586621680073211 -> Type) -> TyFun a6989586621680073211 a6989586621680073211 -> *) (UntilSym2 a6989586621680073211) # 

Methods

suppressUnusedWarnings :: Proxy (UntilSym2 a6989586621680073211) t -> () #

SuppressUnusedWarnings ([a6989586621679550102] -> TyFun [a6989586621679550102] [a6989586621679550102] -> *) ((:++$$) a6989586621679550102) # 

Methods

suppressUnusedWarnings :: Proxy ((:++$$) a6989586621679550102) t -> () #

SuppressUnusedWarnings ([a6989586621679796377] -> TyFun [a6989586621679796377] Bool -> *) (IsSuffixOfSym1 a6989586621679796377) # 

Methods

suppressUnusedWarnings :: Proxy (IsSuffixOfSym1 a6989586621679796377) t -> () #

SuppressUnusedWarnings ([a6989586621679796408] -> TyFun [[a6989586621679796408]] [a6989586621679796408] -> *) (IntercalateSym1 a6989586621679796408) # 

Methods

suppressUnusedWarnings :: Proxy (IntercalateSym1 a6989586621679796408) t -> () #

SuppressUnusedWarnings ([a6989586621679796376] -> TyFun [a6989586621679796376] Bool -> *) (IsInfixOfSym1 a6989586621679796376) # 

Methods

suppressUnusedWarnings :: Proxy (IsInfixOfSym1 a6989586621679796376) t -> () #

SuppressUnusedWarnings ([a6989586621679796378] -> TyFun [a6989586621679796378] Bool -> *) (IsPrefixOfSym1 a6989586621679796378) # 

Methods

suppressUnusedWarnings :: Proxy (IsPrefixOfSym1 a6989586621679796378) t -> () #

SuppressUnusedWarnings ([a6989586621679796333] -> TyFun [a6989586621679796333] [a6989586621679796333] -> *) ((:\\$$) a6989586621679796333) # 

Methods

suppressUnusedWarnings :: Proxy ((:\\$$) a6989586621679796333) t -> () #

SuppressUnusedWarnings ([a6989586621679796290] -> TyFun [a6989586621679796290] [a6989586621679796290] -> *) (UnionSym1 a6989586621679796290) # 

Methods

suppressUnusedWarnings :: Proxy (UnionSym1 a6989586621679796290) t -> () #

SuppressUnusedWarnings ([a6989586621679796320] -> TyFun [a6989586621679796320] [a6989586621679796320] -> *) (IntersectSym1 a6989586621679796320) # 

Methods

suppressUnusedWarnings :: Proxy (IntersectSym1 a6989586621679796320) t -> () #

SuppressUnusedWarnings ([a6989586621679796295] -> TyFun Nat a6989586621679796295 -> *) ((:!!$$) a6989586621679796295) # 

Methods

suppressUnusedWarnings :: Proxy ((:!!$$) a6989586621679796295) t -> () #

SuppressUnusedWarnings ([a6989586621680051561] -> TyFun [a6989586621680051561] (Maybe [a6989586621680051561]) -> *) (StripPrefixSym1 a6989586621680051561) # 

Methods

suppressUnusedWarnings :: Proxy (StripPrefixSym1 a6989586621680051561) t -> () #

SuppressUnusedWarnings (Nat -> TyFun [a6989586621679796311] ([a6989586621679796311], [a6989586621679796311]) -> *) (SplitAtSym1 a6989586621679796311) # 

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym1 a6989586621679796311) t -> () #

SuppressUnusedWarnings (Nat -> TyFun [a6989586621679796313] [a6989586621679796313] -> *) (TakeSym1 a6989586621679796313) # 

Methods

suppressUnusedWarnings :: Proxy (TakeSym1 a6989586621679796313) t -> () #

SuppressUnusedWarnings (Nat -> TyFun [a6989586621679796312] [a6989586621679796312] -> *) (DropSym1 a6989586621679796312) # 

Methods

suppressUnusedWarnings :: Proxy (DropSym1 a6989586621679796312) t -> () #

SuppressUnusedWarnings (Nat -> TyFun a6989586621679796297 [a6989586621679796297] -> *) (ReplicateSym1 a6989586621679796297) # 

Methods

suppressUnusedWarnings :: Proxy (ReplicateSym1 a6989586621679796297) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> TyFun [a3530822107858468866] [a3530822107858468866] -> *) ((:$$) a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy ((:$$) a3530822107858468866) t -> () #

SuppressUnusedWarnings (a6989586621679545776 -> TyFun a6989586621679545776 (TyFun Bool a6989586621679545776 -> Type) -> *) (Bool_Sym1 a6989586621679545776) # 

Methods

suppressUnusedWarnings :: Proxy (Bool_Sym1 a6989586621679545776) t -> () #

SuppressUnusedWarnings (a6989586621679545776 -> a6989586621679545776 -> TyFun Bool a6989586621679545776 -> *) (Bool_Sym2 a6989586621679545776) # 

Methods

suppressUnusedWarnings :: Proxy (Bool_Sym2 a6989586621679545776) t -> () #

SuppressUnusedWarnings (a6989586621679550092 -> TyFun a6989586621679550092 a6989586621679550092 -> *) (AsTypeOfSym1 a6989586621679550092) # 

Methods

suppressUnusedWarnings :: Proxy (AsTypeOfSym1 a6989586621679550092) t -> () #

SuppressUnusedWarnings (a6989586621679561203 -> TyFun a6989586621679561203 Bool -> *) ((:/=$$) a6989586621679561203) # 

Methods

suppressUnusedWarnings :: Proxy ((:/=$$) a6989586621679561203) t -> () #

SuppressUnusedWarnings (a6989586621679561203 -> TyFun a6989586621679561203 Bool -> *) ((:==$$) a6989586621679561203) # 

Methods

suppressUnusedWarnings :: Proxy ((:==$$) a6989586621679561203) t -> () #

SuppressUnusedWarnings (a6989586621679586420 -> TyFun a6989586621679586420 a6989586621679586420 -> *) (MinSym1 a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy (MinSym1 a6989586621679586420) t -> () #

SuppressUnusedWarnings (a6989586621679586420 -> TyFun a6989586621679586420 a6989586621679586420 -> *) (MaxSym1 a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy (MaxSym1 a6989586621679586420) t -> () #

SuppressUnusedWarnings (a6989586621679586420 -> TyFun a6989586621679586420 Bool -> *) ((:>=$$) a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy ((:>=$$) a6989586621679586420) t -> () #

SuppressUnusedWarnings (a6989586621679586420 -> TyFun a6989586621679586420 Bool -> *) ((:>$$) a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy ((:>$$) a6989586621679586420) t -> () #

SuppressUnusedWarnings (a6989586621679586420 -> TyFun a6989586621679586420 Bool -> *) ((:<=$$) a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy ((:<=$$) a6989586621679586420) t -> () #

SuppressUnusedWarnings (a6989586621679586420 -> TyFun a6989586621679586420 Bool -> *) ((:<$$) a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy ((:<$$) a6989586621679586420) t -> () #

SuppressUnusedWarnings (a6989586621679586420 -> TyFun a6989586621679586420 Ordering -> *) (CompareSym1 a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy (CompareSym1 a6989586621679586420) t -> () #

SuppressUnusedWarnings (a6989586621679685236 -> TyFun a6989586621679685236 a6989586621679685236 -> *) ((:*$$) a6989586621679685236) # 

Methods

suppressUnusedWarnings :: Proxy ((:*$$) a6989586621679685236) t -> () #

SuppressUnusedWarnings (a6989586621679685236 -> TyFun a6989586621679685236 a6989586621679685236 -> *) ((:-$$) a6989586621679685236) # 

Methods

suppressUnusedWarnings :: Proxy ((:-$$) a6989586621679685236) t -> () #

SuppressUnusedWarnings (a6989586621679685236 -> TyFun a6989586621679685236 a6989586621679685236 -> *) ((:+$$) a6989586621679685236) # 

Methods

suppressUnusedWarnings :: Proxy ((:+$$) a6989586621679685236) t -> () #

SuppressUnusedWarnings (a6989586621679687552 -> TyFun a6989586621679687552 a6989586621679687552 -> *) (SubtractSym1 a6989586621679687552) # 

Methods

suppressUnusedWarnings :: Proxy (SubtractSym1 a6989586621679687552) t -> () #

SuppressUnusedWarnings (a6989586621679697496 -> TyFun a6989586621679697496 (TyFun a6989586621679697496 [a6989586621679697496] -> Type) -> *) (EnumFromThenToSym1 a6989586621679697496) # 

Methods

suppressUnusedWarnings :: Proxy (EnumFromThenToSym1 a6989586621679697496) t -> () #

SuppressUnusedWarnings (a6989586621679697496 -> a6989586621679697496 -> TyFun a6989586621679697496 [a6989586621679697496] -> *) (EnumFromThenToSym2 a6989586621679697496) # 

Methods

suppressUnusedWarnings :: Proxy (EnumFromThenToSym2 a6989586621679697496) t -> () #

SuppressUnusedWarnings (a6989586621679697496 -> TyFun a6989586621679697496 [a6989586621679697496] -> *) (EnumFromToSym1 a6989586621679697496) # 

Methods

suppressUnusedWarnings :: Proxy (EnumFromToSym1 a6989586621679697496) t -> () #

SuppressUnusedWarnings (a6989586621679771947 -> TyFun (Maybe a6989586621679771947) a6989586621679771947 -> *) (FromMaybeSym1 a6989586621679771947) # 

Methods

suppressUnusedWarnings :: Proxy (FromMaybeSym1 a6989586621679771947) t -> () #

SuppressUnusedWarnings (a6989586621679796409 -> TyFun [a6989586621679796409] [a6989586621679796409] -> *) (IntersperseSym1 a6989586621679796409) # 

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym1 a6989586621679796409) t -> () #

SuppressUnusedWarnings (a6989586621679796375 -> TyFun [a6989586621679796375] Bool -> *) (ElemSym1 a6989586621679796375) # 

Methods

suppressUnusedWarnings :: Proxy (ElemSym1 a6989586621679796375) t -> () #

SuppressUnusedWarnings (a6989586621679796374 -> TyFun [a6989586621679796374] Bool -> *) (NotElemSym1 a6989586621679796374) # 

Methods

suppressUnusedWarnings :: Proxy (NotElemSym1 a6989586621679796374) t -> () #

SuppressUnusedWarnings (a6989586621679796324 -> TyFun [a6989586621679796324] (Maybe Nat) -> *) (ElemIndexSym1 a6989586621679796324) # 

Methods

suppressUnusedWarnings :: Proxy (ElemIndexSym1 a6989586621679796324) t -> () #

SuppressUnusedWarnings (a6989586621679796323 -> TyFun [a6989586621679796323] [Nat] -> *) (ElemIndicesSym1 a6989586621679796323) # 

Methods

suppressUnusedWarnings :: Proxy (ElemIndicesSym1 a6989586621679796323) t -> () #

SuppressUnusedWarnings (a6989586621679796334 -> TyFun [a6989586621679796334] [a6989586621679796334] -> *) (DeleteSym1 a6989586621679796334) # 

Methods

suppressUnusedWarnings :: Proxy (DeleteSym1 a6989586621679796334) t -> () #

SuppressUnusedWarnings (a6989586621679796307 -> TyFun [a6989586621679796307] [a6989586621679796307] -> *) (InsertSym1 a6989586621679796307) # 

Methods

suppressUnusedWarnings :: Proxy (InsertSym1 a6989586621679796307) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679785711 Bool -> Type) (TyFun [a6989586621679785711] Bool -> Type) -> *) (Any_Sym0 a6989586621679785711) # 

Methods

suppressUnusedWarnings :: Proxy (Any_Sym0 a6989586621679785711) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796316 Bool -> Type) (TyFun [a6989586621679796316] [a6989586621679796316] -> Type) -> *) (DropWhileEndSym0 a6989586621679796316) # 

Methods

suppressUnusedWarnings :: Proxy (DropWhileEndSym0 a6989586621679796316) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796400 (TyFun a6989586621679796400 a6989586621679796400 -> Type) -> Type) (TyFun [a6989586621679796400] a6989586621679796400 -> Type) -> *) (Foldl1'Sym0 a6989586621679796400) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl1'Sym0 a6989586621679796400) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796327 (TyFun a6989586621679796327 Ordering -> Type) -> Type) (TyFun [a6989586621679796327] a6989586621679796327 -> Type) -> *) (MinimumBySym0 a6989586621679796327) # 

Methods

suppressUnusedWarnings :: Proxy (MinimumBySym0 a6989586621679796327) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796328 (TyFun a6989586621679796328 Ordering -> Type) -> Type) (TyFun [a6989586621679796328] a6989586621679796328 -> Type) -> *) (MaximumBySym0 a6989586621679796328) # 

Methods

suppressUnusedWarnings :: Proxy (MaximumBySym0 a6989586621679796328) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796401 (TyFun a6989586621679796401 a6989586621679796401 -> Type) -> Type) (TyFun [a6989586621679796401] a6989586621679796401 -> Type) -> *) (Foldl1Sym0 a6989586621679796401) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl1Sym0 a6989586621679796401) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796399 (TyFun a6989586621679796399 a6989586621679796399 -> Type) -> Type) (TyFun [a6989586621679796399] a6989586621679796399 -> Type) -> *) (Foldr1Sym0 a6989586621679796399) # 

Methods

suppressUnusedWarnings :: Proxy (Foldr1Sym0 a6989586621679796399) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796395 Bool -> Type) (TyFun [a6989586621679796395] Bool -> Type) -> *) (AllSym0 a6989586621679796395) # 

Methods

suppressUnusedWarnings :: Proxy (AllSym0 a6989586621679796395) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796392 (TyFun a6989586621679796392 a6989586621679796392 -> Type) -> Type) (TyFun [a6989586621679796392] [a6989586621679796392] -> Type) -> *) (Scanl1Sym0 a6989586621679796392) # 

Methods

suppressUnusedWarnings :: Proxy (Scanl1Sym0 a6989586621679796392) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796389 (TyFun a6989586621679796389 a6989586621679796389 -> Type) -> Type) (TyFun [a6989586621679796389] [a6989586621679796389] -> Type) -> *) (Scanr1Sym0 a6989586621679796389) # 

Methods

suppressUnusedWarnings :: Proxy (Scanr1Sym0 a6989586621679796389) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796322 Bool -> Type) (TyFun [a6989586621679796322] (Maybe Nat) -> Type) -> *) (FindIndexSym0 a6989586621679796322) # 

Methods

suppressUnusedWarnings :: Proxy (FindIndexSym0 a6989586621679796322) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796321 Bool -> Type) (TyFun [a6989586621679796321] [Nat] -> Type) -> *) (FindIndicesSym0 a6989586621679796321) # 

Methods

suppressUnusedWarnings :: Proxy (FindIndicesSym0 a6989586621679796321) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796291 (TyFun a6989586621679796291 Bool -> Type) -> Type) (TyFun [a6989586621679796291] (TyFun [a6989586621679796291] [a6989586621679796291] -> Type) -> Type) -> *) (UnionBySym0 a6989586621679796291) # 

Methods

suppressUnusedWarnings :: Proxy (UnionBySym0 a6989586621679796291) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796331 (TyFun a6989586621679796331 Bool -> Type) -> Type) (TyFun [a6989586621679796331] (TyFun [a6989586621679796331] [a6989586621679796331] -> Type) -> Type) -> *) (DeleteFirstsBySym0 a6989586621679796331) # 

Methods

suppressUnusedWarnings :: Proxy (DeleteFirstsBySym0 a6989586621679796331) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796332 (TyFun a6989586621679796332 Bool -> Type) -> Type) (TyFun a6989586621679796332 (TyFun [a6989586621679796332] [a6989586621679796332] -> Type) -> Type) -> *) (DeleteBySym0 a6989586621679796332) # 

Methods

suppressUnusedWarnings :: Proxy (DeleteBySym0 a6989586621679796332) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796330 (TyFun a6989586621679796330 Ordering -> Type) -> Type) (TyFun [a6989586621679796330] [a6989586621679796330] -> Type) -> *) (SortBySym0 a6989586621679796330) # 

Methods

suppressUnusedWarnings :: Proxy (SortBySym0 a6989586621679796330) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796329 (TyFun a6989586621679796329 Ordering -> Type) -> Type) (TyFun a6989586621679796329 (TyFun [a6989586621679796329] [a6989586621679796329] -> Type) -> Type) -> *) (InsertBySym0 a6989586621679796329) # 

Methods

suppressUnusedWarnings :: Proxy (InsertBySym0 a6989586621679796329) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796319 (TyFun a6989586621679796319 Bool -> Type) -> Type) (TyFun [a6989586621679796319] (TyFun [a6989586621679796319] [a6989586621679796319] -> Type) -> Type) -> *) (IntersectBySym0 a6989586621679796319) # 

Methods

suppressUnusedWarnings :: Proxy (IntersectBySym0 a6989586621679796319) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796325 Bool -> Type) (TyFun [a6989586621679796325] (Maybe a6989586621679796325) -> Type) -> *) (FindSym0 a6989586621679796325) # 

Methods

suppressUnusedWarnings :: Proxy (FindSym0 a6989586621679796325) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796326 Bool -> Type) (TyFun [a6989586621679796326] [a6989586621679796326] -> Type) -> *) (FilterSym0 a6989586621679796326) # 

Methods

suppressUnusedWarnings :: Proxy (FilterSym0 a6989586621679796326) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796318 Bool -> Type) (TyFun [a6989586621679796318] [a6989586621679796318] -> Type) -> *) (TakeWhileSym0 a6989586621679796318) # 

Methods

suppressUnusedWarnings :: Proxy (TakeWhileSym0 a6989586621679796318) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796317 Bool -> Type) (TyFun [a6989586621679796317] [a6989586621679796317] -> Type) -> *) (DropWhileSym0 a6989586621679796317) # 

Methods

suppressUnusedWarnings :: Proxy (DropWhileSym0 a6989586621679796317) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796305 (TyFun a6989586621679796305 Bool -> Type) -> Type) (TyFun [a6989586621679796305] [[a6989586621679796305]] -> Type) -> *) (GroupBySym0 a6989586621679796305) # 

Methods

suppressUnusedWarnings :: Proxy (GroupBySym0 a6989586621679796305) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796315 Bool -> Type) (TyFun [a6989586621679796315] ([a6989586621679796315], [a6989586621679796315]) -> Type) -> *) (SpanSym0 a6989586621679796315) # 

Methods

suppressUnusedWarnings :: Proxy (SpanSym0 a6989586621679796315) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796314 Bool -> Type) (TyFun [a6989586621679796314] ([a6989586621679796314], [a6989586621679796314]) -> Type) -> *) (BreakSym0 a6989586621679796314) # 

Methods

suppressUnusedWarnings :: Proxy (BreakSym0 a6989586621679796314) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796302 Bool -> Type) (TyFun [a6989586621679796302] ([a6989586621679796302], [a6989586621679796302]) -> Type) -> *) (PartitionSym0 a6989586621679796302) # 

Methods

suppressUnusedWarnings :: Proxy (PartitionSym0 a6989586621679796302) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796293 (TyFun a6989586621679796293 Bool -> Type) -> Type) (TyFun [a6989586621679796293] [a6989586621679796293] -> Type) -> *) (NubBySym0 a6989586621679796293) # 

Methods

suppressUnusedWarnings :: Proxy (NubBySym0 a6989586621679796293) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621680073211 Bool -> Type) (TyFun (TyFun a6989586621680073211 a6989586621680073211 -> Type) (TyFun a6989586621680073211 a6989586621680073211 -> Type) -> Type) -> *) (UntilSym0 a6989586621680073211) # 

Methods

suppressUnusedWarnings :: Proxy (UntilSym0 a6989586621680073211) t -> () #

SuppressUnusedWarnings (TyFun [[a6989586621679796296]] [[a6989586621679796296]] -> *) (TransposeSym0 a6989586621679796296) # 

Methods

suppressUnusedWarnings :: Proxy (TransposeSym0 a6989586621679796296) t -> () #

SuppressUnusedWarnings (TyFun [[a6989586621679796398]] [a6989586621679796398] -> *) (ConcatSym0 a6989586621679796398) # 

Methods

suppressUnusedWarnings :: Proxy (ConcatSym0 a6989586621679796398) t -> () #

SuppressUnusedWarnings (TyFun [Maybe a6989586621679771944] [a6989586621679771944] -> *) (CatMaybesSym0 a6989586621679771944) # 

Methods

suppressUnusedWarnings :: Proxy (CatMaybesSym0 a6989586621679771944) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679550102] (TyFun [a6989586621679550102] [a6989586621679550102] -> Type) -> *) ((:++$) a6989586621679550102) # 

Methods

suppressUnusedWarnings :: Proxy ((:++$) a6989586621679550102) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679771945] (Maybe a6989586621679771945) -> *) (ListToMaybeSym0 a6989586621679771945) # 

Methods

suppressUnusedWarnings :: Proxy (ListToMaybeSym0 a6989586621679771945) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796415] a6989586621679796415 -> *) (HeadSym0 a6989586621679796415) # 

Methods

suppressUnusedWarnings :: Proxy (HeadSym0 a6989586621679796415) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796414] a6989586621679796414 -> *) (LastSym0 a6989586621679796414) # 

Methods

suppressUnusedWarnings :: Proxy (LastSym0 a6989586621679796414) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796413] [a6989586621679796413] -> *) (TailSym0 a6989586621679796413) # 

Methods

suppressUnusedWarnings :: Proxy (TailSym0 a6989586621679796413) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796412] [a6989586621679796412] -> *) (InitSym0 a6989586621679796412) # 

Methods

suppressUnusedWarnings :: Proxy (InitSym0 a6989586621679796412) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796411] Bool -> *) (NullSym0 a6989586621679796411) # 

Methods

suppressUnusedWarnings :: Proxy (NullSym0 a6989586621679796411) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796377] (TyFun [a6989586621679796377] Bool -> Type) -> *) (IsSuffixOfSym0 a6989586621679796377) # 

Methods

suppressUnusedWarnings :: Proxy (IsSuffixOfSym0 a6989586621679796377) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796410] [a6989586621679796410] -> *) (ReverseSym0 a6989586621679796410) # 

Methods

suppressUnusedWarnings :: Proxy (ReverseSym0 a6989586621679796410) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796408] (TyFun [[a6989586621679796408]] [a6989586621679796408] -> Type) -> *) (IntercalateSym0 a6989586621679796408) # 

Methods

suppressUnusedWarnings :: Proxy (IntercalateSym0 a6989586621679796408) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796407] [[a6989586621679796407]] -> *) (SubsequencesSym0 a6989586621679796407) # 

Methods

suppressUnusedWarnings :: Proxy (SubsequencesSym0 a6989586621679796407) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796404] [[a6989586621679796404]] -> *) (PermutationsSym0 a6989586621679796404) # 

Methods

suppressUnusedWarnings :: Proxy (PermutationsSym0 a6989586621679796404) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796308] a6989586621679796308 -> *) (MinimumSym0 a6989586621679796308) # 

Methods

suppressUnusedWarnings :: Proxy (MinimumSym0 a6989586621679796308) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796309] a6989586621679796309 -> *) (MaximumSym0 a6989586621679796309) # 

Methods

suppressUnusedWarnings :: Proxy (MaximumSym0 a6989586621679796309) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796380] [[a6989586621679796380]] -> *) (InitsSym0 a6989586621679796380) # 

Methods

suppressUnusedWarnings :: Proxy (InitsSym0 a6989586621679796380) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796376] (TyFun [a6989586621679796376] Bool -> Type) -> *) (IsInfixOfSym0 a6989586621679796376) # 

Methods

suppressUnusedWarnings :: Proxy (IsInfixOfSym0 a6989586621679796376) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796379] [[a6989586621679796379]] -> *) (TailsSym0 a6989586621679796379) # 

Methods

suppressUnusedWarnings :: Proxy (TailsSym0 a6989586621679796379) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796378] (TyFun [a6989586621679796378] Bool -> Type) -> *) (IsPrefixOfSym0 a6989586621679796378) # 

Methods

suppressUnusedWarnings :: Proxy (IsPrefixOfSym0 a6989586621679796378) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796294] [a6989586621679796294] -> *) (NubSym0 a6989586621679796294) # 

Methods

suppressUnusedWarnings :: Proxy (NubSym0 a6989586621679796294) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796333] (TyFun [a6989586621679796333] [a6989586621679796333] -> Type) -> *) ((:\\$) a6989586621679796333) # 

Methods

suppressUnusedWarnings :: Proxy ((:\\$) a6989586621679796333) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796290] (TyFun [a6989586621679796290] [a6989586621679796290] -> Type) -> *) (UnionSym0 a6989586621679796290) # 

Methods

suppressUnusedWarnings :: Proxy (UnionSym0 a6989586621679796290) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796306] [a6989586621679796306] -> *) (SortSym0 a6989586621679796306) # 

Methods

suppressUnusedWarnings :: Proxy (SortSym0 a6989586621679796306) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796320] (TyFun [a6989586621679796320] [a6989586621679796320] -> Type) -> *) (IntersectSym0 a6989586621679796320) # 

Methods

suppressUnusedWarnings :: Proxy (IntersectSym0 a6989586621679796320) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796310] [[a6989586621679796310]] -> *) (GroupSym0 a6989586621679796310) # 

Methods

suppressUnusedWarnings :: Proxy (GroupSym0 a6989586621679796310) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796300] a6989586621679796300 -> *) (SumSym0 a6989586621679796300) # 

Methods

suppressUnusedWarnings :: Proxy (SumSym0 a6989586621679796300) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796299] a6989586621679796299 -> *) (ProductSym0 a6989586621679796299) # 

Methods

suppressUnusedWarnings :: Proxy (ProductSym0 a6989586621679796299) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796298] Nat -> *) (LengthSym0 a6989586621679796298) # 

Methods

suppressUnusedWarnings :: Proxy (LengthSym0 a6989586621679796298) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796295] (TyFun Nat a6989586621679796295 -> Type) -> *) ((:!!$) a6989586621679796295) # 

Methods

suppressUnusedWarnings :: Proxy ((:!!$) a6989586621679796295) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621680051561] (TyFun [a6989586621680051561] (Maybe [a6989586621680051561]) -> Type) -> *) (StripPrefixSym0 a6989586621680051561) # 

Methods

suppressUnusedWarnings :: Proxy (StripPrefixSym0 a6989586621680051561) t -> () #

SuppressUnusedWarnings (TyFun (Maybe a6989586621679771950) Bool -> *) (IsJustSym0 a6989586621679771950) # 

Methods

suppressUnusedWarnings :: Proxy (IsJustSym0 a6989586621679771950) t -> () #

SuppressUnusedWarnings (TyFun (Maybe a6989586621679771949) Bool -> *) (IsNothingSym0 a6989586621679771949) # 

Methods

suppressUnusedWarnings :: Proxy (IsNothingSym0 a6989586621679771949) t -> () #

SuppressUnusedWarnings (TyFun (Maybe a6989586621679771948) a6989586621679771948 -> *) (FromJustSym0 a6989586621679771948) # 

Methods

suppressUnusedWarnings :: Proxy (FromJustSym0 a6989586621679771948) t -> () #

SuppressUnusedWarnings (TyFun (Maybe a6989586621679771946) [a6989586621679771946] -> *) (MaybeToListSym0 a6989586621679771946) # 

Methods

suppressUnusedWarnings :: Proxy (MaybeToListSym0 a6989586621679771946) t -> () #

SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679796311] ([a6989586621679796311], [a6989586621679796311]) -> Type) -> *) (SplitAtSym0 a6989586621679796311) # 

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym0 a6989586621679796311) t -> () #

SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679796313] [a6989586621679796313] -> Type) -> *) (TakeSym0 a6989586621679796313) # 

Methods

suppressUnusedWarnings :: Proxy (TakeSym0 a6989586621679796313) t -> () #

SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679796312] [a6989586621679796312] -> Type) -> *) (DropSym0 a6989586621679796312) # 

Methods

suppressUnusedWarnings :: Proxy (DropSym0 a6989586621679796312) t -> () #

SuppressUnusedWarnings (TyFun Nat (TyFun a6989586621679796297 [a6989586621679796297] -> Type) -> *) (ReplicateSym0 a6989586621679796297) # 

Methods

suppressUnusedWarnings :: Proxy (ReplicateSym0 a6989586621679796297) t -> () #

SuppressUnusedWarnings (TyFun Nat a6989586621679685236 -> *) (FromIntegerSym0 a6989586621679685236) # 

Methods

suppressUnusedWarnings :: Proxy (FromIntegerSym0 a6989586621679685236) t -> () #

SuppressUnusedWarnings (TyFun Nat a6989586621679697496 -> *) (ToEnumSym0 a6989586621679697496) # 

Methods

suppressUnusedWarnings :: Proxy (ToEnumSym0 a6989586621679697496) t -> () #

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun [a3530822107858468866] [a3530822107858468866] -> Type) -> *) ((:$) a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy ((:$) a3530822107858468866) t -> () #

SuppressUnusedWarnings (TyFun a3530822107858468866 (Maybe a3530822107858468866) -> *) (JustSym0 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (JustSym0 a3530822107858468866) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679545776 (TyFun a6989586621679545776 (TyFun Bool a6989586621679545776 -> Type) -> Type) -> *) (Bool_Sym0 a6989586621679545776) # 

Methods

suppressUnusedWarnings :: Proxy (Bool_Sym0 a6989586621679545776) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679550101 a6989586621679550101 -> *) (IdSym0 a6989586621679550101) # 

Methods

suppressUnusedWarnings :: Proxy (IdSym0 a6989586621679550101) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679550092 (TyFun a6989586621679550092 a6989586621679550092 -> Type) -> *) (AsTypeOfSym0 a6989586621679550092) # 

Methods

suppressUnusedWarnings :: Proxy (AsTypeOfSym0 a6989586621679550092) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679561203 (TyFun a6989586621679561203 Bool -> Type) -> *) ((:/=$) a6989586621679561203) # 

Methods

suppressUnusedWarnings :: Proxy ((:/=$) a6989586621679561203) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679561203 (TyFun a6989586621679561203 Bool -> Type) -> *) ((:==$) a6989586621679561203) # 

Methods

suppressUnusedWarnings :: Proxy ((:==$) a6989586621679561203) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679586420 (TyFun a6989586621679586420 a6989586621679586420 -> Type) -> *) (MinSym0 a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy (MinSym0 a6989586621679586420) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679586420 (TyFun a6989586621679586420 a6989586621679586420 -> Type) -> *) (MaxSym0 a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy (MaxSym0 a6989586621679586420) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679586420 (TyFun a6989586621679586420 Bool -> Type) -> *) ((:>=$) a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy ((:>=$) a6989586621679586420) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679586420 (TyFun a6989586621679586420 Bool -> Type) -> *) ((:>$) a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy ((:>$) a6989586621679586420) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679586420 (TyFun a6989586621679586420 Bool -> Type) -> *) ((:<=$) a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy ((:<=$) a6989586621679586420) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679586420 (TyFun a6989586621679586420 Bool -> Type) -> *) ((:<$) a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy ((:<$) a6989586621679586420) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679586420 (TyFun a6989586621679586420 Ordering -> Type) -> *) (CompareSym0 a6989586621679586420) # 

Methods

suppressUnusedWarnings :: Proxy (CompareSym0 a6989586621679586420) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679685236 a6989586621679685236 -> *) (SignumSym0 a6989586621679685236) # 

Methods

suppressUnusedWarnings :: Proxy (SignumSym0 a6989586621679685236) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679685236 a6989586621679685236 -> *) (AbsSym0 a6989586621679685236) # 

Methods

suppressUnusedWarnings :: Proxy (AbsSym0 a6989586621679685236) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679685236 a6989586621679685236 -> *) (NegateSym0 a6989586621679685236) # 

Methods

suppressUnusedWarnings :: Proxy (NegateSym0 a6989586621679685236) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679685236 (TyFun a6989586621679685236 a6989586621679685236 -> Type) -> *) ((:*$) a6989586621679685236) # 

Methods

suppressUnusedWarnings :: Proxy ((:*$) a6989586621679685236) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679685236 (TyFun a6989586621679685236 a6989586621679685236 -> Type) -> *) ((:-$) a6989586621679685236) # 

Methods

suppressUnusedWarnings :: Proxy ((:-$) a6989586621679685236) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679685236 (TyFun a6989586621679685236 a6989586621679685236 -> Type) -> *) ((:+$) a6989586621679685236) # 

Methods

suppressUnusedWarnings :: Proxy ((:+$) a6989586621679685236) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679687552 (TyFun a6989586621679687552 a6989586621679687552 -> Type) -> *) (SubtractSym0 a6989586621679687552) # 

Methods

suppressUnusedWarnings :: Proxy (SubtractSym0 a6989586621679687552) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679697496 (TyFun a6989586621679697496 (TyFun a6989586621679697496 [a6989586621679697496] -> Type) -> Type) -> *) (EnumFromThenToSym0 a6989586621679697496) # 

Methods

suppressUnusedWarnings :: Proxy (EnumFromThenToSym0 a6989586621679697496) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679697496 (TyFun a6989586621679697496 [a6989586621679697496] -> Type) -> *) (EnumFromToSym0 a6989586621679697496) # 

Methods

suppressUnusedWarnings :: Proxy (EnumFromToSym0 a6989586621679697496) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679697496 Nat -> *) (FromEnumSym0 a6989586621679697496) # 

Methods

suppressUnusedWarnings :: Proxy (FromEnumSym0 a6989586621679697496) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679697496 a6989586621679697496 -> *) (PredSym0 a6989586621679697496) # 

Methods

suppressUnusedWarnings :: Proxy (PredSym0 a6989586621679697496) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679697496 a6989586621679697496 -> *) (SuccSym0 a6989586621679697496) # 

Methods

suppressUnusedWarnings :: Proxy (SuccSym0 a6989586621679697496) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679771947 (TyFun (Maybe a6989586621679771947) a6989586621679771947 -> Type) -> *) (FromMaybeSym0 a6989586621679771947) # 

Methods

suppressUnusedWarnings :: Proxy (FromMaybeSym0 a6989586621679771947) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679796409 (TyFun [a6989586621679796409] [a6989586621679796409] -> Type) -> *) (IntersperseSym0 a6989586621679796409) # 

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym0 a6989586621679796409) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679796375 (TyFun [a6989586621679796375] Bool -> Type) -> *) (ElemSym0 a6989586621679796375) # 

Methods

suppressUnusedWarnings :: Proxy (ElemSym0 a6989586621679796375) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679796374 (TyFun [a6989586621679796374] Bool -> Type) -> *) (NotElemSym0 a6989586621679796374) # 

Methods

suppressUnusedWarnings :: Proxy (NotElemSym0 a6989586621679796374) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679796324 (TyFun [a6989586621679796324] (Maybe Nat) -> Type) -> *) (ElemIndexSym0 a6989586621679796324) # 

Methods

suppressUnusedWarnings :: Proxy (ElemIndexSym0 a6989586621679796324) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679796323 (TyFun [a6989586621679796323] [Nat] -> Type) -> *) (ElemIndicesSym0 a6989586621679796323) # 

Methods

suppressUnusedWarnings :: Proxy (ElemIndicesSym0 a6989586621679796323) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679796334 (TyFun [a6989586621679796334] [a6989586621679796334] -> Type) -> *) (DeleteSym0 a6989586621679796334) # 

Methods

suppressUnusedWarnings :: Proxy (DeleteSym0 a6989586621679796334) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679796307 (TyFun [a6989586621679796307] [a6989586621679796307] -> Type) -> *) (InsertSym0 a6989586621679796307) # 

Methods

suppressUnusedWarnings :: Proxy (InsertSym0 a6989586621679796307) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679509136 (TyFun a6989586621679509135 b6989586621679509136 -> Type) -> Type) -> TyFun b6989586621679509136 (TyFun [a6989586621679509135] b6989586621679509136 -> Type) -> *) (FoldlSym1 a6989586621679509135 b6989586621679509136) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym1 a6989586621679509135 b6989586621679509136) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679509136 (TyFun a6989586621679509135 b6989586621679509136 -> Type) -> Type) -> b6989586621679509136 -> TyFun [a6989586621679509135] b6989586621679509136 -> *) (FoldlSym2 a6989586621679509135 b6989586621679509136) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym2 a6989586621679509135 b6989586621679509136) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679550105 (TyFun b6989586621679550106 b6989586621679550106 -> Type) -> Type) -> TyFun b6989586621679550106 (TyFun [a6989586621679550105] b6989586621679550106 -> Type) -> *) (FoldrSym1 a6989586621679550105 b6989586621679550106) # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym1 a6989586621679550105 b6989586621679550106) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679550105 (TyFun b6989586621679550106 b6989586621679550106 -> Type) -> Type) -> b6989586621679550106 -> TyFun [a6989586621679550105] b6989586621679550106 -> *) (FoldrSym2 a6989586621679550105 b6989586621679550106) # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym2 a6989586621679550105 b6989586621679550106) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679550103 b6989586621679550104 -> Type) -> TyFun [a6989586621679550103] [b6989586621679550104] -> *) (MapSym1 a6989586621679550103 b6989586621679550104) # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a6989586621679550103 b6989586621679550104) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679771942 (Maybe b6989586621679771943) -> Type) -> TyFun [a6989586621679771942] [b6989586621679771943] -> *) (MapMaybeSym1 a6989586621679771942 b6989586621679771943) # 

Methods

suppressUnusedWarnings :: Proxy (MapMaybeSym1 a6989586621679771942 b6989586621679771943) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679796403 (TyFun a6989586621679796402 b6989586621679796403 -> Type) -> Type) -> TyFun b6989586621679796403 (TyFun [a6989586621679796402] b6989586621679796403 -> Type) -> *) (Foldl'Sym1 a6989586621679796402 b6989586621679796403) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym1 a6989586621679796402 b6989586621679796403) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679796403 (TyFun a6989586621679796402 b6989586621679796403 -> Type) -> Type) -> b6989586621679796403 -> TyFun [a6989586621679796402] b6989586621679796403 -> *) (Foldl'Sym2 a6989586621679796402 b6989586621679796403) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym2 a6989586621679796402 b6989586621679796403) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796396 [b6989586621679796397] -> Type) -> TyFun [a6989586621679796396] [b6989586621679796397] -> *) (ConcatMapSym1 a6989586621679796396 b6989586621679796397) # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym1 a6989586621679796396 b6989586621679796397) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679796393 (TyFun a6989586621679796394 b6989586621679796393 -> Type) -> Type) -> TyFun b6989586621679796393 (TyFun [a6989586621679796394] [b6989586621679796393] -> Type) -> *) (ScanlSym1 a6989586621679796394 b6989586621679796393) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a6989586621679796394 b6989586621679796393) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679796393 (TyFun a6989586621679796394 b6989586621679796393 -> Type) -> Type) -> b6989586621679796393 -> TyFun [a6989586621679796394] [b6989586621679796393] -> *) (ScanlSym2 a6989586621679796394 b6989586621679796393) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a6989586621679796394 b6989586621679796393) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796390 (TyFun b6989586621679796391 b6989586621679796391 -> Type) -> Type) -> TyFun b6989586621679796391 (TyFun [a6989586621679796390] [b6989586621679796391] -> Type) -> *) (ScanrSym1 a6989586621679796390 b6989586621679796391) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a6989586621679796390 b6989586621679796391) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796390 (TyFun b6989586621679796391 b6989586621679796391 -> Type) -> Type) -> b6989586621679796391 -> TyFun [a6989586621679796390] [b6989586621679796391] -> *) (ScanrSym2 a6989586621679796390 b6989586621679796391) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a6989586621679796390 b6989586621679796391) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679796381 (Maybe (a6989586621679796382, b6989586621679796381)) -> Type) -> TyFun b6989586621679796381 [a6989586621679796382] -> *) (UnfoldrSym1 a6989586621679796382 b6989586621679796381) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 a6989586621679796382 b6989586621679796381) t -> () #

SuppressUnusedWarnings ([a6989586621679796372] -> TyFun [b6989586621679796373] [(a6989586621679796372, b6989586621679796373)] -> *) (ZipSym1 b6989586621679796373 a6989586621679796372) # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 b6989586621679796373 a6989586621679796372) t -> () #

SuppressUnusedWarnings ([a6989586621680051506] -> TyFun i6989586621680051505 a6989586621680051506 -> *) (GenericIndexSym1 i6989586621680051505 a6989586621680051506) # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym1 i6989586621680051505 a6989586621680051506) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> TyFun b3530822107858468867 (a3530822107858468866, b3530822107858468867) -> *) (Tuple2Sym1 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple2Sym1 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a6989586621679550099 -> TyFun b6989586621679550100 a6989586621679550099 -> *) (ConstSym1 b6989586621679550100 a6989586621679550099) # 

Methods

suppressUnusedWarnings :: Proxy (ConstSym1 b6989586621679550100 a6989586621679550099) t -> () #

SuppressUnusedWarnings (a6989586621679550090 -> TyFun b6989586621679550091 b6989586621679550091 -> *) (SeqSym1 b6989586621679550091 a6989586621679550090) # 

Methods

suppressUnusedWarnings :: Proxy (SeqSym1 b6989586621679550091 a6989586621679550090) t -> () #

SuppressUnusedWarnings (b6989586621679770696 -> TyFun (TyFun a6989586621679770697 b6989586621679770696 -> Type) (TyFun (Maybe a6989586621679770697) b6989586621679770696 -> Type) -> *) (Maybe_Sym1 a6989586621679770697 b6989586621679770696) # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym1 a6989586621679770697 b6989586621679770696) t -> () #

SuppressUnusedWarnings (b6989586621679770696 -> (TyFun a6989586621679770697 b6989586621679770696 -> Type) -> TyFun (Maybe a6989586621679770697) b6989586621679770696 -> *) (Maybe_Sym2 a6989586621679770697 b6989586621679770696) # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym2 a6989586621679770697 b6989586621679770696) t -> () #

SuppressUnusedWarnings (a6989586621679796303 -> TyFun [(a6989586621679796303, b6989586621679796304)] (Maybe b6989586621679796304) -> *) (LookupSym1 b6989586621679796304 a6989586621679796303) # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym1 b6989586621679796304 a6989586621679796303) t -> () #

SuppressUnusedWarnings (i6989586621680051511 -> TyFun [a6989586621680051512] [a6989586621680051512] -> *) (GenericTakeSym1 a6989586621680051512 i6989586621680051511) # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym1 a6989586621680051512 i6989586621680051511) t -> () #

SuppressUnusedWarnings (i6989586621680051509 -> TyFun [a6989586621680051510] [a6989586621680051510] -> *) (GenericDropSym1 a6989586621680051510 i6989586621680051509) # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym1 a6989586621680051510 i6989586621680051509) t -> () #

SuppressUnusedWarnings (i6989586621680051507 -> TyFun [a6989586621680051508] ([a6989586621680051508], [a6989586621680051508]) -> *) (GenericSplitAtSym1 a6989586621680051508 i6989586621680051507) # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym1 a6989586621680051508 i6989586621680051507) t -> () #

SuppressUnusedWarnings (i6989586621680051503 -> TyFun a6989586621680051504 [a6989586621680051504] -> *) (GenericReplicateSym1 a6989586621680051504 i6989586621680051503) # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym1 a6989586621680051504 i6989586621680051503) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679509136 (TyFun a6989586621679509135 b6989586621679509136 -> Type) -> Type) (TyFun b6989586621679509136 (TyFun [a6989586621679509135] b6989586621679509136 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679509135 b6989586621679509136) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym0 a6989586621679509135 b6989586621679509136) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679550105 (TyFun b6989586621679550106 b6989586621679550106 -> Type) -> Type) (TyFun b6989586621679550106 (TyFun [a6989586621679550105] b6989586621679550106 -> Type) -> Type) -> *) (FoldrSym0 a6989586621679550105 b6989586621679550106) # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym0 a6989586621679550105 b6989586621679550106) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679550103 b6989586621679550104 -> Type) (TyFun [a6989586621679550103] [b6989586621679550104] -> Type) -> *) (MapSym0 a6989586621679550103 b6989586621679550104) # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a6989586621679550103 b6989586621679550104) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679771942 (Maybe b6989586621679771943) -> Type) (TyFun [a6989586621679771942] [b6989586621679771943] -> Type) -> *) (MapMaybeSym0 a6989586621679771942 b6989586621679771943) # 

Methods

suppressUnusedWarnings :: Proxy (MapMaybeSym0 a6989586621679771942 b6989586621679771943) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679796403 (TyFun a6989586621679796402 b6989586621679796403 -> Type) -> Type) (TyFun b6989586621679796403 (TyFun [a6989586621679796402] b6989586621679796403 -> Type) -> Type) -> *) (Foldl'Sym0 a6989586621679796402 b6989586621679796403) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym0 a6989586621679796402 b6989586621679796403) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796396 [b6989586621679796397] -> Type) (TyFun [a6989586621679796396] [b6989586621679796397] -> Type) -> *) (ConcatMapSym0 a6989586621679796396 b6989586621679796397) # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym0 a6989586621679796396 b6989586621679796397) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679796393 (TyFun a6989586621679796394 b6989586621679796393 -> Type) -> Type) (TyFun b6989586621679796393 (TyFun [a6989586621679796394] [b6989586621679796393] -> Type) -> Type) -> *) (ScanlSym0 a6989586621679796394 b6989586621679796393) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a6989586621679796394 b6989586621679796393) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796390 (TyFun b6989586621679796391 b6989586621679796391 -> Type) -> Type) (TyFun b6989586621679796391 (TyFun [a6989586621679796390] [b6989586621679796391] -> Type) -> Type) -> *) (ScanrSym0 a6989586621679796390 b6989586621679796391) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a6989586621679796390 b6989586621679796391) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679796381 (Maybe (a6989586621679796382, b6989586621679796381)) -> Type) (TyFun b6989586621679796381 [a6989586621679796382] -> Type) -> *) (UnfoldrSym0 b6989586621679796381 a6989586621679796382) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 b6989586621679796381 a6989586621679796382) t -> () #

SuppressUnusedWarnings (TyFun [Either a6989586621679762510 b6989586621679762511] [a6989586621679762510] -> *) (LeftsSym0 b6989586621679762511 a6989586621679762510) # 

Methods

suppressUnusedWarnings :: Proxy (LeftsSym0 b6989586621679762511 a6989586621679762510) t -> () #

SuppressUnusedWarnings (TyFun [Either a6989586621679762508 b6989586621679762509] [b6989586621679762509] -> *) (RightsSym0 a6989586621679762508 b6989586621679762509) # 

Methods

suppressUnusedWarnings :: Proxy (RightsSym0 a6989586621679762508 b6989586621679762509) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679796360, b6989586621679796361)] ([a6989586621679796360], [b6989586621679796361]) -> *) (UnzipSym0 a6989586621679796360 b6989586621679796361) # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a6989586621679796360 b6989586621679796361) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796372] (TyFun [b6989586621679796373] [(a6989586621679796372, b6989586621679796373)] -> Type) -> *) (ZipSym0 a6989586621679796372 b6989586621679796373) # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a6989586621679796372 b6989586621679796373) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796289] i6989586621679796288 -> *) (GenericLengthSym0 a6989586621679796289 i6989586621679796288) # 

Methods

suppressUnusedWarnings :: Proxy (GenericLengthSym0 a6989586621679796289 i6989586621679796288) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621680051506] (TyFun i6989586621680051505 a6989586621680051506 -> Type) -> *) (GenericIndexSym0 i6989586621680051505 a6989586621680051506) # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym0 i6989586621680051505 a6989586621680051506) t -> () #

SuppressUnusedWarnings (TyFun (Either a6989586621679762504 b6989586621679762505) Bool -> *) (IsLeftSym0 a6989586621679762504 b6989586621679762505) # 

Methods

suppressUnusedWarnings :: Proxy (IsLeftSym0 a6989586621679762504 b6989586621679762505) t -> () #

SuppressUnusedWarnings (TyFun (Either a6989586621679762502 b6989586621679762503) Bool -> *) (IsRightSym0 a6989586621679762502 b6989586621679762503) # 

Methods

suppressUnusedWarnings :: Proxy (IsRightSym0 a6989586621679762502 b6989586621679762503) t -> () #

SuppressUnusedWarnings (TyFun (a6989586621679781816, b6989586621679781817) a6989586621679781816 -> *) (FstSym0 b6989586621679781817 a6989586621679781816) # 

Methods

suppressUnusedWarnings :: Proxy (FstSym0 b6989586621679781817 a6989586621679781816) t -> () #

SuppressUnusedWarnings (TyFun (a6989586621679781814, b6989586621679781815) b6989586621679781815 -> *) (SndSym0 a6989586621679781814 b6989586621679781815) # 

Methods

suppressUnusedWarnings :: Proxy (SndSym0 a6989586621679781814 b6989586621679781815) t -> () #

SuppressUnusedWarnings (TyFun (a6989586621679781806, b6989586621679781807) (b6989586621679781807, a6989586621679781806) -> *) (SwapSym0 b6989586621679781807 a6989586621679781806) # 

Methods

suppressUnusedWarnings :: Proxy (SwapSym0 b6989586621679781807 a6989586621679781806) t -> () #

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun b3530822107858468867 (a3530822107858468866, b3530822107858468867) -> Type) -> *) (Tuple2Sym0 a3530822107858468866 b3530822107858468867) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple2Sym0 a3530822107858468866 b3530822107858468867) t -> () #

SuppressUnusedWarnings (TyFun b6989586621679054094 (Either a6989586621679054093 b6989586621679054094) -> *) (RightSym0 a6989586621679054093 b6989586621679054094) # 

Methods

suppressUnusedWarnings :: Proxy (RightSym0 a6989586621679054093 b6989586621679054094) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679054093 (Either a6989586621679054093 b6989586621679054094) -> *) (LeftSym0 a6989586621679054093 b6989586621679054094) # 

Methods

suppressUnusedWarnings :: Proxy (LeftSym0 a6989586621679054093 b6989586621679054094) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679550099 (TyFun b6989586621679550100 a6989586621679550099 -> Type) -> *) (ConstSym0 b6989586621679550100 a6989586621679550099) # 

Methods

suppressUnusedWarnings :: Proxy (ConstSym0 b6989586621679550100 a6989586621679550099) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679550090 (TyFun b6989586621679550091 b6989586621679550091 -> Type) -> *) (SeqSym0 a6989586621679550090 b6989586621679550091) # 

Methods

suppressUnusedWarnings :: Proxy (SeqSym0 a6989586621679550090 b6989586621679550091) t -> () #

SuppressUnusedWarnings (TyFun k06989586621679675033 k6989586621679675035 -> *) (ErrorSym0 k06989586621679675033 k6989586621679675035) # 

Methods

suppressUnusedWarnings :: Proxy (ErrorSym0 k06989586621679675033 k6989586621679675035) t -> () #

SuppressUnusedWarnings (TyFun b6989586621679770696 (TyFun (TyFun a6989586621679770697 b6989586621679770696 -> Type) (TyFun (Maybe a6989586621679770697) b6989586621679770696 -> Type) -> Type) -> *) (Maybe_Sym0 a6989586621679770697 b6989586621679770696) # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym0 a6989586621679770697 b6989586621679770696) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679796303 (TyFun [(a6989586621679796303, b6989586621679796304)] (Maybe b6989586621679796304) -> Type) -> *) (LookupSym0 a6989586621679796303 b6989586621679796304) # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym0 a6989586621679796303 b6989586621679796304) t -> () #

SuppressUnusedWarnings (TyFun i6989586621680051511 (TyFun [a6989586621680051512] [a6989586621680051512] -> Type) -> *) (GenericTakeSym0 i6989586621680051511 a6989586621680051512) # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym0 i6989586621680051511 a6989586621680051512) t -> () #

SuppressUnusedWarnings (TyFun i6989586621680051509 (TyFun [a6989586621680051510] [a6989586621680051510] -> Type) -> *) (GenericDropSym0 i6989586621680051509 a6989586621680051510) # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym0 i6989586621680051509 a6989586621680051510) t -> () #

SuppressUnusedWarnings (TyFun i6989586621680051507 (TyFun [a6989586621680051508] ([a6989586621680051508], [a6989586621680051508]) -> Type) -> *) (GenericSplitAtSym0 i6989586621680051507 a6989586621680051508) # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym0 i6989586621680051507 a6989586621680051508) t -> () #

SuppressUnusedWarnings (TyFun i6989586621680051503 (TyFun a6989586621680051504 [a6989586621680051504] -> Type) -> *) (GenericReplicateSym0 i6989586621680051503 a6989586621680051504) # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym0 i6989586621680051503 a6989586621680051504) t -> () #

SuppressUnusedWarnings ((TyFun (a6989586621679781811, b6989586621679781812) c6989586621679781813 -> Type) -> TyFun a6989586621679781811 (TyFun b6989586621679781812 c6989586621679781813 -> Type) -> *) (CurrySym1 a6989586621679781811 b6989586621679781812 c6989586621679781813) # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym1 a6989586621679781811 b6989586621679781812 c6989586621679781813) t -> () #

SuppressUnusedWarnings ((TyFun (a6989586621679781811, b6989586621679781812) c6989586621679781813 -> Type) -> a6989586621679781811 -> TyFun b6989586621679781812 c6989586621679781813 -> *) (CurrySym2 a6989586621679781811 b6989586621679781812 c6989586621679781813) # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym2 a6989586621679781811 b6989586621679781812 c6989586621679781813) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679550096 c6989586621679550097 -> Type) -> TyFun (TyFun a6989586621679550098 b6989586621679550096 -> Type) (TyFun a6989586621679550098 c6989586621679550097 -> Type) -> *) ((:.$$) a6989586621679550098 b6989586621679550096 c6989586621679550097) # 

Methods

suppressUnusedWarnings :: Proxy ((a6989586621679550098 :.$$ b6989586621679550096) c6989586621679550097) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679550096 c6989586621679550097 -> Type) -> (TyFun a6989586621679550098 b6989586621679550096 -> Type) -> TyFun a6989586621679550098 c6989586621679550097 -> *) ((:.$$$) a6989586621679550098 b6989586621679550096 c6989586621679550097) # 

Methods

suppressUnusedWarnings :: Proxy ((a6989586621679550098 :.$$$ b6989586621679550096) c6989586621679550097) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679550093 (TyFun b6989586621679550094 c6989586621679550095 -> Type) -> Type) -> TyFun b6989586621679550094 (TyFun a6989586621679550093 c6989586621679550095 -> Type) -> *) (FlipSym1 a6989586621679550093 b6989586621679550094 c6989586621679550095) # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym1 a6989586621679550093 b6989586621679550094 c6989586621679550095) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679550093 (TyFun b6989586621679550094 c6989586621679550095 -> Type) -> Type) -> b6989586621679550094 -> TyFun a6989586621679550093 c6989586621679550095 -> *) (FlipSym2 a6989586621679550093 b6989586621679550094 c6989586621679550095) # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym2 a6989586621679550093 b6989586621679550094 c6989586621679550095) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679761240 c6989586621679761241 -> Type) -> TyFun (TyFun b6989586621679761242 c6989586621679761241 -> Type) (TyFun (Either a6989586621679761240 b6989586621679761242) c6989586621679761241 -> Type) -> *) (Either_Sym1 b6989586621679761242 a6989586621679761240 c6989586621679761241) # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym1 b6989586621679761242 a6989586621679761240 c6989586621679761241) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679761240 c6989586621679761241 -> Type) -> (TyFun b6989586621679761242 c6989586621679761241 -> Type) -> TyFun (Either a6989586621679761240 b6989586621679761242) c6989586621679761241 -> *) (Either_Sym2 b6989586621679761242 a6989586621679761240 c6989586621679761241) # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym2 b6989586621679761242 a6989586621679761240 c6989586621679761241) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679781808 (TyFun b6989586621679781809 c6989586621679781810 -> Type) -> Type) -> TyFun (a6989586621679781808, b6989586621679781809) c6989586621679781810 -> *) (UncurrySym1 a6989586621679781808 b6989586621679781809 c6989586621679781810) # 

Methods

suppressUnusedWarnings :: Proxy (UncurrySym1 a6989586621679781808 b6989586621679781809 c6989586621679781810) t -> () #

SuppressUnusedWarnings ((TyFun acc6989586621679796386 (TyFun x6989586621679796387 (acc6989586621679796386, y6989586621679796388) -> Type) -> Type) -> TyFun acc6989586621679796386 (TyFun [x6989586621679796387] (acc6989586621679796386, [y6989586621679796388]) -> Type) -> *) (MapAccumLSym1 x6989586621679796387 acc6989586621679796386 y6989586621679796388) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym1 x6989586621679796387 acc6989586621679796386 y6989586621679796388) t -> () #

SuppressUnusedWarnings ((TyFun acc6989586621679796386 (TyFun x6989586621679796387 (acc6989586621679796386, y6989586621679796388) -> Type) -> Type) -> acc6989586621679796386 -> TyFun [x6989586621679796387] (acc6989586621679796386, [y6989586621679796388]) -> *) (MapAccumLSym2 x6989586621679796387 acc6989586621679796386 y6989586621679796388) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym2 x6989586621679796387 acc6989586621679796386 y6989586621679796388) t -> () #

SuppressUnusedWarnings ((TyFun acc6989586621679796383 (TyFun x6989586621679796384 (acc6989586621679796383, y6989586621679796385) -> Type) -> Type) -> TyFun acc6989586621679796383 (TyFun [x6989586621679796384] (acc6989586621679796383, [y6989586621679796385]) -> Type) -> *) (MapAccumRSym1 x6989586621679796384 acc6989586621679796383 y6989586621679796385) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym1 x6989586621679796384 acc6989586621679796383 y6989586621679796385) t -> () #

SuppressUnusedWarnings ((TyFun acc6989586621679796383 (TyFun x6989586621679796384 (acc6989586621679796383, y6989586621679796385) -> Type) -> Type) -> acc6989586621679796383 -> TyFun [x6989586621679796384] (acc6989586621679796383, [y6989586621679796385]) -> *) (MapAccumRSym2 x6989586621679796384 acc6989586621679796383 y6989586621679796385) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym2 x6989586621679796384 acc6989586621679796383 y6989586621679796385) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796366 (TyFun b6989586621679796367 c6989586621679796368 -> Type) -> Type) -> TyFun [a6989586621679796366] (TyFun [b6989586621679796367] [c6989586621679796368] -> Type) -> *) (ZipWithSym1 a6989586621679796366 b6989586621679796367 c6989586621679796368) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a6989586621679796366 b6989586621679796367 c6989586621679796368) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796366 (TyFun b6989586621679796367 c6989586621679796368 -> Type) -> Type) -> [a6989586621679796366] -> TyFun [b6989586621679796367] [c6989586621679796368] -> *) (ZipWithSym2 a6989586621679796366 b6989586621679796367 c6989586621679796368) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a6989586621679796366 b6989586621679796367 c6989586621679796368) t -> () #

SuppressUnusedWarnings ([a6989586621679796369] -> TyFun [b6989586621679796370] (TyFun [c6989586621679796371] [(a6989586621679796369, b6989586621679796370, c6989586621679796371)] -> Type) -> *) (Zip3Sym1 b6989586621679796370 c6989586621679796371 a6989586621679796369) # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym1 b6989586621679796370 c6989586621679796371 a6989586621679796369) t -> () #

SuppressUnusedWarnings ([a6989586621679796369] -> [b6989586621679796370] -> TyFun [c6989586621679796371] [(a6989586621679796369, b6989586621679796370, c6989586621679796371)] -> *) (Zip3Sym2 c6989586621679796371 b6989586621679796370 a6989586621679796369) # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym2 c6989586621679796371 b6989586621679796370 a6989586621679796369) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> TyFun b3530822107858468867 (TyFun c3530822107858468868 (a3530822107858468866, b3530822107858468867, c3530822107858468868) -> Type) -> *) (Tuple3Sym1 b3530822107858468867 c3530822107858468868 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym1 b3530822107858468867 c3530822107858468868 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> TyFun c3530822107858468868 (a3530822107858468866, b3530822107858468867, c3530822107858468868) -> *) (Tuple3Sym2 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym2 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (TyFun (TyFun (a6989586621679781811, b6989586621679781812) c6989586621679781813 -> Type) (TyFun a6989586621679781811 (TyFun b6989586621679781812 c6989586621679781813 -> Type) -> Type) -> *) (CurrySym0 a6989586621679781811 b6989586621679781812 c6989586621679781813) # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym0 a6989586621679781811 b6989586621679781812 c6989586621679781813) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679550096 c6989586621679550097 -> Type) (TyFun (TyFun a6989586621679550098 b6989586621679550096 -> Type) (TyFun a6989586621679550098 c6989586621679550097 -> Type) -> Type) -> *) ((:.$) b6989586621679550096 a6989586621679550098 c6989586621679550097) # 

Methods

suppressUnusedWarnings :: Proxy ((b6989586621679550096 :.$ a6989586621679550098) c6989586621679550097) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679550093 (TyFun b6989586621679550094 c6989586621679550095 -> Type) -> Type) (TyFun b6989586621679550094 (TyFun a6989586621679550093 c6989586621679550095 -> Type) -> Type) -> *) (FlipSym0 b6989586621679550094 a6989586621679550093 c6989586621679550095) # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym0 b6989586621679550094 a6989586621679550093 c6989586621679550095) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679761240 c6989586621679761241 -> Type) (TyFun (TyFun b6989586621679761242 c6989586621679761241 -> Type) (TyFun (Either a6989586621679761240 b6989586621679761242) c6989586621679761241 -> Type) -> Type) -> *) (Either_Sym0 a6989586621679761240 b6989586621679761242 c6989586621679761241) # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym0 a6989586621679761240 b6989586621679761242 c6989586621679761241) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679781808 (TyFun b6989586621679781809 c6989586621679781810 -> Type) -> Type) (TyFun (a6989586621679781808, b6989586621679781809) c6989586621679781810 -> Type) -> *) (UncurrySym0 a6989586621679781808 b6989586621679781809 c6989586621679781810) # 

Methods

suppressUnusedWarnings :: Proxy (UncurrySym0 a6989586621679781808 b6989586621679781809 c6989586621679781810) t -> () #

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679796386 (TyFun x6989586621679796387 (acc6989586621679796386, y6989586621679796388) -> Type) -> Type) (TyFun acc6989586621679796386 (TyFun [x6989586621679796387] (acc6989586621679796386, [y6989586621679796388]) -> Type) -> Type) -> *) (MapAccumLSym0 x6989586621679796387 acc6989586621679796386 y6989586621679796388) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym0 x6989586621679796387 acc6989586621679796386 y6989586621679796388) t -> () #

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679796383 (TyFun x6989586621679796384 (acc6989586621679796383, y6989586621679796385) -> Type) -> Type) (TyFun acc6989586621679796383 (TyFun [x6989586621679796384] (acc6989586621679796383, [y6989586621679796385]) -> Type) -> Type) -> *) (MapAccumRSym0 x6989586621679796384 acc6989586621679796383 y6989586621679796385) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym0 x6989586621679796384 acc6989586621679796383 y6989586621679796385) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796366 (TyFun b6989586621679796367 c6989586621679796368 -> Type) -> Type) (TyFun [a6989586621679796366] (TyFun [b6989586621679796367] [c6989586621679796368] -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679796366 b6989586621679796367 c6989586621679796368) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a6989586621679796366 b6989586621679796367 c6989586621679796368) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679796357, b6989586621679796358, c6989586621679796359)] ([a6989586621679796357], [b6989586621679796358], [c6989586621679796359]) -> *) (Unzip3Sym0 a6989586621679796357 b6989586621679796358 c6989586621679796359) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip3Sym0 a6989586621679796357 b6989586621679796358 c6989586621679796359) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679796369] (TyFun [b6989586621679796370] (TyFun [c6989586621679796371] [(a6989586621679796369, b6989586621679796370, c6989586621679796371)] -> Type) -> Type) -> *) (Zip3Sym0 a6989586621679796369 b6989586621679796370 c6989586621679796371) # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym0 a6989586621679796369 b6989586621679796370 c6989586621679796371) t -> () #

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (a3530822107858468866, b3530822107858468867, c3530822107858468868) -> Type) -> Type) -> *) (Tuple3Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796362 (TyFun b6989586621679796363 (TyFun c6989586621679796364 d6989586621679796365 -> Type) -> Type) -> Type) -> TyFun [a6989586621679796362] (TyFun [b6989586621679796363] (TyFun [c6989586621679796364] [d6989586621679796365] -> Type) -> Type) -> *) (ZipWith3Sym1 a6989586621679796362 b6989586621679796363 c6989586621679796364 d6989586621679796365) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym1 a6989586621679796362 b6989586621679796363 c6989586621679796364 d6989586621679796365) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796362 (TyFun b6989586621679796363 (TyFun c6989586621679796364 d6989586621679796365 -> Type) -> Type) -> Type) -> [a6989586621679796362] -> TyFun [b6989586621679796363] (TyFun [c6989586621679796364] [d6989586621679796365] -> Type) -> *) (ZipWith3Sym2 a6989586621679796362 b6989586621679796363 c6989586621679796364 d6989586621679796365) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym2 a6989586621679796362 b6989586621679796363 c6989586621679796364 d6989586621679796365) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679796362 (TyFun b6989586621679796363 (TyFun c6989586621679796364 d6989586621679796365 -> Type) -> Type) -> Type) -> [a6989586621679796362] -> [b6989586621679796363] -> TyFun [c6989586621679796364] [d6989586621679796365] -> *) (ZipWith3Sym3 a6989586621679796362 b6989586621679796363 c6989586621679796364 d6989586621679796365) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym3 a6989586621679796362 b6989586621679796363 c6989586621679796364 d6989586621679796365) t -> () #

SuppressUnusedWarnings ([a6989586621680051557] -> TyFun [b6989586621680051558] (TyFun [c6989586621680051559] (TyFun [d6989586621680051560] [(a6989586621680051557, b6989586621680051558, c6989586621680051559, d6989586621680051560)] -> Type) -> Type) -> *) (Zip4Sym1 b6989586621680051558 c6989586621680051559 d6989586621680051560 a6989586621680051557) # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym1 b6989586621680051558 c6989586621680051559 d6989586621680051560 a6989586621680051557) t -> () #

SuppressUnusedWarnings ([a6989586621680051557] -> [b6989586621680051558] -> TyFun [c6989586621680051559] (TyFun [d6989586621680051560] [(a6989586621680051557, b6989586621680051558, c6989586621680051559, d6989586621680051560)] -> Type) -> *) (Zip4Sym2 c6989586621680051559 d6989586621680051560 b6989586621680051558 a6989586621680051557) # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym2 c6989586621680051559 d6989586621680051560 b6989586621680051558 a6989586621680051557) t -> () #

SuppressUnusedWarnings ([a6989586621680051557] -> [b6989586621680051558] -> [c6989586621680051559] -> TyFun [d6989586621680051560] [(a6989586621680051557, b6989586621680051558, c6989586621680051559, d6989586621680051560)] -> *) (Zip4Sym3 d6989586621680051560 c6989586621680051559 b6989586621680051558 a6989586621680051557) # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym3 d6989586621680051560 c6989586621680051559 b6989586621680051558 a6989586621680051557) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> Type) -> Type) -> *) (Tuple4Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> TyFun c3530822107858468868 (TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> Type) -> *) (Tuple4Sym2 c3530822107858468868 d3530822107858468869 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym2 c3530822107858468868 d3530822107858468869 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> *) (Tuple4Sym3 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym3 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679796362 (TyFun b6989586621679796363 (TyFun c6989586621679796364 d6989586621679796365 -> Type) -> Type) -> Type) (TyFun [a6989586621679796362] (TyFun [b6989586621679796363] (TyFun [c6989586621679796364] [d6989586621679796365] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a6989586621679796362 b6989586621679796363 c6989586621679796364 d6989586621679796365) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym0 a6989586621679796362 b6989586621679796363 c6989586621679796364 d6989586621679796365) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679796353, b6989586621679796354, c6989586621679796355, d6989586621679796356)] ([a6989586621679796353], [b6989586621679796354], [c6989586621679796355], [d6989586621679796356]) -> *) (Unzip4Sym0 a6989586621679796353 b6989586621679796354 c6989586621679796355 d6989586621679796356) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip4Sym0 a6989586621679796353 b6989586621679796354 c6989586621679796355 d6989586621679796356) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621680051557] (TyFun [b6989586621680051558] (TyFun [c6989586621680051559] (TyFun [d6989586621680051560] [(a6989586621680051557, b6989586621680051558, c6989586621680051559, d6989586621680051560)] -> Type) -> Type) -> Type) -> *) (Zip4Sym0 a6989586621680051557 b6989586621680051558 c6989586621680051559 d6989586621680051560) # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym0 a6989586621680051557 b6989586621680051558 c6989586621680051559 d6989586621680051560) t -> () #

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869) -> Type) -> Type) -> Type) -> *) (Tuple4Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051534 (TyFun b6989586621680051535 (TyFun c6989586621680051536 (TyFun d6989586621680051537 e6989586621680051538 -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621680051534] (TyFun [b6989586621680051535] (TyFun [c6989586621680051536] (TyFun [d6989586621680051537] [e6989586621680051538] -> Type) -> Type) -> Type) -> *) (ZipWith4Sym1 a6989586621680051534 b6989586621680051535 c6989586621680051536 d6989586621680051537 e6989586621680051538) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym1 a6989586621680051534 b6989586621680051535 c6989586621680051536 d6989586621680051537 e6989586621680051538) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051534 (TyFun b6989586621680051535 (TyFun c6989586621680051536 (TyFun d6989586621680051537 e6989586621680051538 -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051534] -> TyFun [b6989586621680051535] (TyFun [c6989586621680051536] (TyFun [d6989586621680051537] [e6989586621680051538] -> Type) -> Type) -> *) (ZipWith4Sym2 a6989586621680051534 b6989586621680051535 c6989586621680051536 d6989586621680051537 e6989586621680051538) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym2 a6989586621680051534 b6989586621680051535 c6989586621680051536 d6989586621680051537 e6989586621680051538) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051534 (TyFun b6989586621680051535 (TyFun c6989586621680051536 (TyFun d6989586621680051537 e6989586621680051538 -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051534] -> [b6989586621680051535] -> TyFun [c6989586621680051536] (TyFun [d6989586621680051537] [e6989586621680051538] -> Type) -> *) (ZipWith4Sym3 a6989586621680051534 b6989586621680051535 c6989586621680051536 d6989586621680051537 e6989586621680051538) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym3 a6989586621680051534 b6989586621680051535 c6989586621680051536 d6989586621680051537 e6989586621680051538) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051534 (TyFun b6989586621680051535 (TyFun c6989586621680051536 (TyFun d6989586621680051537 e6989586621680051538 -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051534] -> [b6989586621680051535] -> [c6989586621680051536] -> TyFun [d6989586621680051537] [e6989586621680051538] -> *) (ZipWith4Sym4 a6989586621680051534 b6989586621680051535 c6989586621680051536 d6989586621680051537 e6989586621680051538) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym4 a6989586621680051534 b6989586621680051535 c6989586621680051536 d6989586621680051537 e6989586621680051538) t -> () #

SuppressUnusedWarnings ([a6989586621680051552] -> TyFun [b6989586621680051553] (TyFun [c6989586621680051554] (TyFun [d6989586621680051555] (TyFun [e6989586621680051556] [(a6989586621680051552, b6989586621680051553, c6989586621680051554, d6989586621680051555, e6989586621680051556)] -> Type) -> Type) -> Type) -> *) (Zip5Sym1 b6989586621680051553 c6989586621680051554 d6989586621680051555 e6989586621680051556 a6989586621680051552) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym1 b6989586621680051553 c6989586621680051554 d6989586621680051555 e6989586621680051556 a6989586621680051552) t -> () #

SuppressUnusedWarnings ([a6989586621680051552] -> [b6989586621680051553] -> TyFun [c6989586621680051554] (TyFun [d6989586621680051555] (TyFun [e6989586621680051556] [(a6989586621680051552, b6989586621680051553, c6989586621680051554, d6989586621680051555, e6989586621680051556)] -> Type) -> Type) -> *) (Zip5Sym2 c6989586621680051554 d6989586621680051555 e6989586621680051556 b6989586621680051553 a6989586621680051552) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym2 c6989586621680051554 d6989586621680051555 e6989586621680051556 b6989586621680051553 a6989586621680051552) t -> () #

SuppressUnusedWarnings ([a6989586621680051552] -> [b6989586621680051553] -> [c6989586621680051554] -> TyFun [d6989586621680051555] (TyFun [e6989586621680051556] [(a6989586621680051552, b6989586621680051553, c6989586621680051554, d6989586621680051555, e6989586621680051556)] -> Type) -> *) (Zip5Sym3 d6989586621680051555 e6989586621680051556 c6989586621680051554 b6989586621680051553 a6989586621680051552) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym3 d6989586621680051555 e6989586621680051556 c6989586621680051554 b6989586621680051553 a6989586621680051552) t -> () #

SuppressUnusedWarnings ([a6989586621680051552] -> [b6989586621680051553] -> [c6989586621680051554] -> [d6989586621680051555] -> TyFun [e6989586621680051556] [(a6989586621680051552, b6989586621680051553, c6989586621680051554, d6989586621680051555, e6989586621680051556)] -> *) (Zip5Sym4 e6989586621680051556 d6989586621680051555 c6989586621680051554 b6989586621680051553 a6989586621680051552) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym4 e6989586621680051556 d6989586621680051555 c6989586621680051554 b6989586621680051553 a6989586621680051552) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> Type) -> Type) -> *) (Tuple5Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> Type) -> *) (Tuple5Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> *) (Tuple5Sym3 d3530822107858468869 e3530822107858468870 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym3 d3530822107858468869 e3530822107858468870 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> d3530822107858468869 -> TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> *) (Tuple5Sym4 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym4 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621680051534 (TyFun b6989586621680051535 (TyFun c6989586621680051536 (TyFun d6989586621680051537 e6989586621680051538 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621680051534] (TyFun [b6989586621680051535] (TyFun [c6989586621680051536] (TyFun [d6989586621680051537] [e6989586621680051538] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith4Sym0 a6989586621680051534 b6989586621680051535 c6989586621680051536 d6989586621680051537 e6989586621680051538) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym0 a6989586621680051534 b6989586621680051535 c6989586621680051536 d6989586621680051537 e6989586621680051538) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679796348, b6989586621679796349, c6989586621679796350, d6989586621679796351, e6989586621679796352)] ([a6989586621679796348], [b6989586621679796349], [c6989586621679796350], [d6989586621679796351], [e6989586621679796352]) -> *) (Unzip5Sym0 a6989586621679796348 b6989586621679796349 c6989586621679796350 d6989586621679796351 e6989586621679796352) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip5Sym0 a6989586621679796348 b6989586621679796349 c6989586621679796350 d6989586621679796351 e6989586621679796352) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621680051552] (TyFun [b6989586621680051553] (TyFun [c6989586621680051554] (TyFun [d6989586621680051555] (TyFun [e6989586621680051556] [(a6989586621680051552, b6989586621680051553, c6989586621680051554, d6989586621680051555, e6989586621680051556)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip5Sym0 a6989586621680051552 b6989586621680051553 c6989586621680051554 d6989586621680051555 e6989586621680051556) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym0 a6989586621680051552 b6989586621680051553 c6989586621680051554 d6989586621680051555 e6989586621680051556) t -> () #

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple5Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051528 (TyFun b6989586621680051529 (TyFun c6989586621680051530 (TyFun d6989586621680051531 (TyFun e6989586621680051532 f6989586621680051533 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621680051528] (TyFun [b6989586621680051529] (TyFun [c6989586621680051530] (TyFun [d6989586621680051531] (TyFun [e6989586621680051532] [f6989586621680051533] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym1 a6989586621680051528 b6989586621680051529 c6989586621680051530 d6989586621680051531 e6989586621680051532 f6989586621680051533) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym1 a6989586621680051528 b6989586621680051529 c6989586621680051530 d6989586621680051531 e6989586621680051532 f6989586621680051533) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051528 (TyFun b6989586621680051529 (TyFun c6989586621680051530 (TyFun d6989586621680051531 (TyFun e6989586621680051532 f6989586621680051533 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051528] -> TyFun [b6989586621680051529] (TyFun [c6989586621680051530] (TyFun [d6989586621680051531] (TyFun [e6989586621680051532] [f6989586621680051533] -> Type) -> Type) -> Type) -> *) (ZipWith5Sym2 a6989586621680051528 b6989586621680051529 c6989586621680051530 d6989586621680051531 e6989586621680051532 f6989586621680051533) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym2 a6989586621680051528 b6989586621680051529 c6989586621680051530 d6989586621680051531 e6989586621680051532 f6989586621680051533) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051528 (TyFun b6989586621680051529 (TyFun c6989586621680051530 (TyFun d6989586621680051531 (TyFun e6989586621680051532 f6989586621680051533 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051528] -> [b6989586621680051529] -> TyFun [c6989586621680051530] (TyFun [d6989586621680051531] (TyFun [e6989586621680051532] [f6989586621680051533] -> Type) -> Type) -> *) (ZipWith5Sym3 a6989586621680051528 b6989586621680051529 c6989586621680051530 d6989586621680051531 e6989586621680051532 f6989586621680051533) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym3 a6989586621680051528 b6989586621680051529 c6989586621680051530 d6989586621680051531 e6989586621680051532 f6989586621680051533) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051528 (TyFun b6989586621680051529 (TyFun c6989586621680051530 (TyFun d6989586621680051531 (TyFun e6989586621680051532 f6989586621680051533 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051528] -> [b6989586621680051529] -> [c6989586621680051530] -> TyFun [d6989586621680051531] (TyFun [e6989586621680051532] [f6989586621680051533] -> Type) -> *) (ZipWith5Sym4 a6989586621680051528 b6989586621680051529 c6989586621680051530 d6989586621680051531 e6989586621680051532 f6989586621680051533) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym4 a6989586621680051528 b6989586621680051529 c6989586621680051530 d6989586621680051531 e6989586621680051532 f6989586621680051533) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051528 (TyFun b6989586621680051529 (TyFun c6989586621680051530 (TyFun d6989586621680051531 (TyFun e6989586621680051532 f6989586621680051533 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051528] -> [b6989586621680051529] -> [c6989586621680051530] -> [d6989586621680051531] -> TyFun [e6989586621680051532] [f6989586621680051533] -> *) (ZipWith5Sym5 a6989586621680051528 b6989586621680051529 c6989586621680051530 d6989586621680051531 e6989586621680051532 f6989586621680051533) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym5 a6989586621680051528 b6989586621680051529 c6989586621680051530 d6989586621680051531 e6989586621680051532 f6989586621680051533) t -> () #

SuppressUnusedWarnings ([a6989586621680051546] -> TyFun [b6989586621680051547] (TyFun [c6989586621680051548] (TyFun [d6989586621680051549] (TyFun [e6989586621680051550] (TyFun [f6989586621680051551] [(a6989586621680051546, b6989586621680051547, c6989586621680051548, d6989586621680051549, e6989586621680051550, f6989586621680051551)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym1 b6989586621680051547 c6989586621680051548 d6989586621680051549 e6989586621680051550 f6989586621680051551 a6989586621680051546) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym1 b6989586621680051547 c6989586621680051548 d6989586621680051549 e6989586621680051550 f6989586621680051551 a6989586621680051546) t -> () #

SuppressUnusedWarnings ([a6989586621680051546] -> [b6989586621680051547] -> TyFun [c6989586621680051548] (TyFun [d6989586621680051549] (TyFun [e6989586621680051550] (TyFun [f6989586621680051551] [(a6989586621680051546, b6989586621680051547, c6989586621680051548, d6989586621680051549, e6989586621680051550, f6989586621680051551)] -> Type) -> Type) -> Type) -> *) (Zip6Sym2 c6989586621680051548 d6989586621680051549 e6989586621680051550 f6989586621680051551 b6989586621680051547 a6989586621680051546) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym2 c6989586621680051548 d6989586621680051549 e6989586621680051550 f6989586621680051551 b6989586621680051547 a6989586621680051546) t -> () #

SuppressUnusedWarnings ([a6989586621680051546] -> [b6989586621680051547] -> [c6989586621680051548] -> TyFun [d6989586621680051549] (TyFun [e6989586621680051550] (TyFun [f6989586621680051551] [(a6989586621680051546, b6989586621680051547, c6989586621680051548, d6989586621680051549, e6989586621680051550, f6989586621680051551)] -> Type) -> Type) -> *) (Zip6Sym3 d6989586621680051549 e6989586621680051550 f6989586621680051551 c6989586621680051548 b6989586621680051547 a6989586621680051546) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym3 d6989586621680051549 e6989586621680051550 f6989586621680051551 c6989586621680051548 b6989586621680051547 a6989586621680051546) t -> () #

SuppressUnusedWarnings ([a6989586621680051546] -> [b6989586621680051547] -> [c6989586621680051548] -> [d6989586621680051549] -> TyFun [e6989586621680051550] (TyFun [f6989586621680051551] [(a6989586621680051546, b6989586621680051547, c6989586621680051548, d6989586621680051549, e6989586621680051550, f6989586621680051551)] -> Type) -> *) (Zip6Sym4 e6989586621680051550 f6989586621680051551 d6989586621680051549 c6989586621680051548 b6989586621680051547 a6989586621680051546) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym4 e6989586621680051550 f6989586621680051551 d6989586621680051549 c6989586621680051548 b6989586621680051547 a6989586621680051546) t -> () #

SuppressUnusedWarnings ([a6989586621680051546] -> [b6989586621680051547] -> [c6989586621680051548] -> [d6989586621680051549] -> [e6989586621680051550] -> TyFun [f6989586621680051551] [(a6989586621680051546, b6989586621680051547, c6989586621680051548, d6989586621680051549, e6989586621680051550, f6989586621680051551)] -> *) (Zip6Sym5 f6989586621680051551 e6989586621680051550 d6989586621680051549 c6989586621680051548 b6989586621680051547 a6989586621680051546) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym5 f6989586621680051551 e6989586621680051550 d6989586621680051549 c6989586621680051548 b6989586621680051547 a6989586621680051546) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple6Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> Type) -> *) (Tuple6Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> *) (Tuple6Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> d3530822107858468869 -> TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> *) (Tuple6Sym4 e3530822107858468870 f3530822107858468871 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym4 e3530822107858468870 f3530822107858468871 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> d3530822107858468869 -> e3530822107858468870 -> TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> *) (Tuple6Sym5 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym5 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621680051528 (TyFun b6989586621680051529 (TyFun c6989586621680051530 (TyFun d6989586621680051531 (TyFun e6989586621680051532 f6989586621680051533 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621680051528] (TyFun [b6989586621680051529] (TyFun [c6989586621680051530] (TyFun [d6989586621680051531] (TyFun [e6989586621680051532] [f6989586621680051533] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym0 a6989586621680051528 b6989586621680051529 c6989586621680051530 d6989586621680051531 e6989586621680051532 f6989586621680051533) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym0 a6989586621680051528 b6989586621680051529 c6989586621680051530 d6989586621680051531 e6989586621680051532 f6989586621680051533) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679796342, b6989586621679796343, c6989586621679796344, d6989586621679796345, e6989586621679796346, f6989586621679796347)] ([a6989586621679796342], [b6989586621679796343], [c6989586621679796344], [d6989586621679796345], [e6989586621679796346], [f6989586621679796347]) -> *) (Unzip6Sym0 a6989586621679796342 b6989586621679796343 c6989586621679796344 d6989586621679796345 e6989586621679796346 f6989586621679796347) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip6Sym0 a6989586621679796342 b6989586621679796343 c6989586621679796344 d6989586621679796345 e6989586621679796346 f6989586621679796347) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621680051546] (TyFun [b6989586621680051547] (TyFun [c6989586621680051548] (TyFun [d6989586621680051549] (TyFun [e6989586621680051550] (TyFun [f6989586621680051551] [(a6989586621680051546, b6989586621680051547, c6989586621680051548, d6989586621680051549, e6989586621680051550, f6989586621680051551)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym0 a6989586621680051546 b6989586621680051547 c6989586621680051548 d6989586621680051549 e6989586621680051550 f6989586621680051551) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym0 a6989586621680051546 b6989586621680051547 c6989586621680051548 d6989586621680051549 e6989586621680051550 f6989586621680051551) t -> () #

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple6Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051521 (TyFun b6989586621680051522 (TyFun c6989586621680051523 (TyFun d6989586621680051524 (TyFun e6989586621680051525 (TyFun f6989586621680051526 g6989586621680051527 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621680051521] (TyFun [b6989586621680051522] (TyFun [c6989586621680051523] (TyFun [d6989586621680051524] (TyFun [e6989586621680051525] (TyFun [f6989586621680051526] [g6989586621680051527] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym1 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym1 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051521 (TyFun b6989586621680051522 (TyFun c6989586621680051523 (TyFun d6989586621680051524 (TyFun e6989586621680051525 (TyFun f6989586621680051526 g6989586621680051527 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051521] -> TyFun [b6989586621680051522] (TyFun [c6989586621680051523] (TyFun [d6989586621680051524] (TyFun [e6989586621680051525] (TyFun [f6989586621680051526] [g6989586621680051527] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym2 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym2 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051521 (TyFun b6989586621680051522 (TyFun c6989586621680051523 (TyFun d6989586621680051524 (TyFun e6989586621680051525 (TyFun f6989586621680051526 g6989586621680051527 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051521] -> [b6989586621680051522] -> TyFun [c6989586621680051523] (TyFun [d6989586621680051524] (TyFun [e6989586621680051525] (TyFun [f6989586621680051526] [g6989586621680051527] -> Type) -> Type) -> Type) -> *) (ZipWith6Sym3 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym3 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051521 (TyFun b6989586621680051522 (TyFun c6989586621680051523 (TyFun d6989586621680051524 (TyFun e6989586621680051525 (TyFun f6989586621680051526 g6989586621680051527 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051521] -> [b6989586621680051522] -> [c6989586621680051523] -> TyFun [d6989586621680051524] (TyFun [e6989586621680051525] (TyFun [f6989586621680051526] [g6989586621680051527] -> Type) -> Type) -> *) (ZipWith6Sym4 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym4 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051521 (TyFun b6989586621680051522 (TyFun c6989586621680051523 (TyFun d6989586621680051524 (TyFun e6989586621680051525 (TyFun f6989586621680051526 g6989586621680051527 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051521] -> [b6989586621680051522] -> [c6989586621680051523] -> [d6989586621680051524] -> TyFun [e6989586621680051525] (TyFun [f6989586621680051526] [g6989586621680051527] -> Type) -> *) (ZipWith6Sym5 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym5 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051521 (TyFun b6989586621680051522 (TyFun c6989586621680051523 (TyFun d6989586621680051524 (TyFun e6989586621680051525 (TyFun f6989586621680051526 g6989586621680051527 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051521] -> [b6989586621680051522] -> [c6989586621680051523] -> [d6989586621680051524] -> [e6989586621680051525] -> TyFun [f6989586621680051526] [g6989586621680051527] -> *) (ZipWith6Sym6 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym6 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) t -> () #

SuppressUnusedWarnings ([a6989586621680051539] -> TyFun [b6989586621680051540] (TyFun [c6989586621680051541] (TyFun [d6989586621680051542] (TyFun [e6989586621680051543] (TyFun [f6989586621680051544] (TyFun [g6989586621680051545] [(a6989586621680051539, b6989586621680051540, c6989586621680051541, d6989586621680051542, e6989586621680051543, f6989586621680051544, g6989586621680051545)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym1 b6989586621680051540 c6989586621680051541 d6989586621680051542 e6989586621680051543 f6989586621680051544 g6989586621680051545 a6989586621680051539) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym1 b6989586621680051540 c6989586621680051541 d6989586621680051542 e6989586621680051543 f6989586621680051544 g6989586621680051545 a6989586621680051539) t -> () #

SuppressUnusedWarnings ([a6989586621680051539] -> [b6989586621680051540] -> TyFun [c6989586621680051541] (TyFun [d6989586621680051542] (TyFun [e6989586621680051543] (TyFun [f6989586621680051544] (TyFun [g6989586621680051545] [(a6989586621680051539, b6989586621680051540, c6989586621680051541, d6989586621680051542, e6989586621680051543, f6989586621680051544, g6989586621680051545)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym2 c6989586621680051541 d6989586621680051542 e6989586621680051543 f6989586621680051544 g6989586621680051545 b6989586621680051540 a6989586621680051539) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym2 c6989586621680051541 d6989586621680051542 e6989586621680051543 f6989586621680051544 g6989586621680051545 b6989586621680051540 a6989586621680051539) t -> () #

SuppressUnusedWarnings ([a6989586621680051539] -> [b6989586621680051540] -> [c6989586621680051541] -> TyFun [d6989586621680051542] (TyFun [e6989586621680051543] (TyFun [f6989586621680051544] (TyFun [g6989586621680051545] [(a6989586621680051539, b6989586621680051540, c6989586621680051541, d6989586621680051542, e6989586621680051543, f6989586621680051544, g6989586621680051545)] -> Type) -> Type) -> Type) -> *) (Zip7Sym3 d6989586621680051542 e6989586621680051543 f6989586621680051544 g6989586621680051545 c6989586621680051541 b6989586621680051540 a6989586621680051539) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym3 d6989586621680051542 e6989586621680051543 f6989586621680051544 g6989586621680051545 c6989586621680051541 b6989586621680051540 a6989586621680051539) t -> () #

SuppressUnusedWarnings ([a6989586621680051539] -> [b6989586621680051540] -> [c6989586621680051541] -> [d6989586621680051542] -> TyFun [e6989586621680051543] (TyFun [f6989586621680051544] (TyFun [g6989586621680051545] [(a6989586621680051539, b6989586621680051540, c6989586621680051541, d6989586621680051542, e6989586621680051543, f6989586621680051544, g6989586621680051545)] -> Type) -> Type) -> *) (Zip7Sym4 e6989586621680051543 f6989586621680051544 g6989586621680051545 d6989586621680051542 c6989586621680051541 b6989586621680051540 a6989586621680051539) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym4 e6989586621680051543 f6989586621680051544 g6989586621680051545 d6989586621680051542 c6989586621680051541 b6989586621680051540 a6989586621680051539) t -> () #

SuppressUnusedWarnings ([a6989586621680051539] -> [b6989586621680051540] -> [c6989586621680051541] -> [d6989586621680051542] -> [e6989586621680051543] -> TyFun [f6989586621680051544] (TyFun [g6989586621680051545] [(a6989586621680051539, b6989586621680051540, c6989586621680051541, d6989586621680051542, e6989586621680051543, f6989586621680051544, g6989586621680051545)] -> Type) -> *) (Zip7Sym5 f6989586621680051544 g6989586621680051545 e6989586621680051543 d6989586621680051542 c6989586621680051541 b6989586621680051540 a6989586621680051539) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym5 f6989586621680051544 g6989586621680051545 e6989586621680051543 d6989586621680051542 c6989586621680051541 b6989586621680051540 a6989586621680051539) t -> () #

SuppressUnusedWarnings ([a6989586621680051539] -> [b6989586621680051540] -> [c6989586621680051541] -> [d6989586621680051542] -> [e6989586621680051543] -> [f6989586621680051544] -> TyFun [g6989586621680051545] [(a6989586621680051539, b6989586621680051540, c6989586621680051541, d6989586621680051542, e6989586621680051543, f6989586621680051544, g6989586621680051545)] -> *) (Zip7Sym6 g6989586621680051545 f6989586621680051544 e6989586621680051543 d6989586621680051542 c6989586621680051541 b6989586621680051540 a6989586621680051539) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym6 g6989586621680051545 f6989586621680051544 e6989586621680051543 d6989586621680051542 c6989586621680051541 b6989586621680051540 a6989586621680051539) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym1 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym2 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> *) (Tuple7Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym3 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> d3530822107858468869 -> TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> *) (Tuple7Sym4 e3530822107858468870 f3530822107858468871 g3530822107858468872 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym4 e3530822107858468870 f3530822107858468871 g3530822107858468872 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> d3530822107858468869 -> e3530822107858468870 -> TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> *) (Tuple7Sym5 f3530822107858468871 g3530822107858468872 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym5 f3530822107858468871 g3530822107858468872 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (a3530822107858468866 -> b3530822107858468867 -> c3530822107858468868 -> d3530822107858468869 -> e3530822107858468870 -> f3530822107858468871 -> TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> *) (Tuple7Sym6 g3530822107858468872 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym6 g3530822107858468872 f3530822107858468871 e3530822107858468870 d3530822107858468869 c3530822107858468868 b3530822107858468867 a3530822107858468866) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621680051521 (TyFun b6989586621680051522 (TyFun c6989586621680051523 (TyFun d6989586621680051524 (TyFun e6989586621680051525 (TyFun f6989586621680051526 g6989586621680051527 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621680051521] (TyFun [b6989586621680051522] (TyFun [c6989586621680051523] (TyFun [d6989586621680051524] (TyFun [e6989586621680051525] (TyFun [f6989586621680051526] [g6989586621680051527] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym0 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym0 a6989586621680051521 b6989586621680051522 c6989586621680051523 d6989586621680051524 e6989586621680051525 f6989586621680051526 g6989586621680051527) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679796335, b6989586621679796336, c6989586621679796337, d6989586621679796338, e6989586621679796339, f6989586621679796340, g6989586621679796341)] ([a6989586621679796335], [b6989586621679796336], [c6989586621679796337], [d6989586621679796338], [e6989586621679796339], [f6989586621679796340], [g6989586621679796341]) -> *) (Unzip7Sym0 a6989586621679796335 b6989586621679796336 c6989586621679796337 d6989586621679796338 e6989586621679796339 f6989586621679796340 g6989586621679796341) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip7Sym0 a6989586621679796335 b6989586621679796336 c6989586621679796337 d6989586621679796338 e6989586621679796339 f6989586621679796340 g6989586621679796341) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621680051539] (TyFun [b6989586621680051540] (TyFun [c6989586621680051541] (TyFun [d6989586621680051542] (TyFun [e6989586621680051543] (TyFun [f6989586621680051544] (TyFun [g6989586621680051545] [(a6989586621680051539, b6989586621680051540, c6989586621680051541, d6989586621680051542, e6989586621680051543, f6989586621680051544, g6989586621680051545)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym0 a6989586621680051539 b6989586621680051540 c6989586621680051541 d6989586621680051542 e6989586621680051543 f6989586621680051544 g6989586621680051545) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym0 a6989586621680051539 b6989586621680051540 c6989586621680051541 d6989586621680051542 e6989586621680051543 f6989586621680051544 g6989586621680051545) t -> () #

SuppressUnusedWarnings (TyFun a3530822107858468866 (TyFun b3530822107858468867 (TyFun c3530822107858468868 (TyFun d3530822107858468869 (TyFun e3530822107858468870 (TyFun f3530822107858468871 (TyFun g3530822107858468872 (a3530822107858468866, b3530822107858468867, c3530822107858468868, d3530822107858468869, e3530822107858468870, f3530822107858468871, g3530822107858468872) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym0 a3530822107858468866 b3530822107858468867 c3530822107858468868 d3530822107858468869 e3530822107858468870 f3530822107858468871 g3530822107858468872) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051513 (TyFun b6989586621680051514 (TyFun c6989586621680051515 (TyFun d6989586621680051516 (TyFun e6989586621680051517 (TyFun f6989586621680051518 (TyFun g6989586621680051519 h6989586621680051520 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621680051513] (TyFun [b6989586621680051514] (TyFun [c6989586621680051515] (TyFun [d6989586621680051516] (TyFun [e6989586621680051517] (TyFun [f6989586621680051518] (TyFun [g6989586621680051519] [h6989586621680051520] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym1 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym1 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051513 (TyFun b6989586621680051514 (TyFun c6989586621680051515 (TyFun d6989586621680051516 (TyFun e6989586621680051517 (TyFun f6989586621680051518 (TyFun g6989586621680051519 h6989586621680051520 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051513] -> TyFun [b6989586621680051514] (TyFun [c6989586621680051515] (TyFun [d6989586621680051516] (TyFun [e6989586621680051517] (TyFun [f6989586621680051518] (TyFun [g6989586621680051519] [h6989586621680051520] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym2 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym2 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051513 (TyFun b6989586621680051514 (TyFun c6989586621680051515 (TyFun d6989586621680051516 (TyFun e6989586621680051517 (TyFun f6989586621680051518 (TyFun g6989586621680051519 h6989586621680051520 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051513] -> [b6989586621680051514] -> TyFun [c6989586621680051515] (TyFun [d6989586621680051516] (TyFun [e6989586621680051517] (TyFun [f6989586621680051518] (TyFun [g6989586621680051519] [h6989586621680051520] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym3 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym3 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051513 (TyFun b6989586621680051514 (TyFun c6989586621680051515 (TyFun d6989586621680051516 (TyFun e6989586621680051517 (TyFun f6989586621680051518 (TyFun g6989586621680051519 h6989586621680051520 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051513] -> [b6989586621680051514] -> [c6989586621680051515] -> TyFun [d6989586621680051516] (TyFun [e6989586621680051517] (TyFun [f6989586621680051518] (TyFun [g6989586621680051519] [h6989586621680051520] -> Type) -> Type) -> Type) -> *) (ZipWith7Sym4 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym4 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051513 (TyFun b6989586621680051514 (TyFun c6989586621680051515 (TyFun d6989586621680051516 (TyFun e6989586621680051517 (TyFun f6989586621680051518 (TyFun g6989586621680051519 h6989586621680051520 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051513] -> [b6989586621680051514] -> [c6989586621680051515] -> [d6989586621680051516] -> TyFun [e6989586621680051517] (TyFun [f6989586621680051518] (TyFun [g6989586621680051519] [h6989586621680051520] -> Type) -> Type) -> *) (ZipWith7Sym5 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym5 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051513 (TyFun b6989586621680051514 (TyFun c6989586621680051515 (TyFun d6989586621680051516 (TyFun e6989586621680051517 (TyFun f6989586621680051518 (TyFun g6989586621680051519 h6989586621680051520 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051513] -> [b6989586621680051514] -> [c6989586621680051515] -> [d6989586621680051516] -> [e6989586621680051517] -> TyFun [f6989586621680051518] (TyFun [g6989586621680051519] [h6989586621680051520] -> Type) -> *) (ZipWith7Sym6 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym6 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621680051513 (TyFun b6989586621680051514 (TyFun c6989586621680051515 (TyFun d6989586621680051516 (TyFun e6989586621680051517 (TyFun f6989586621680051518 (TyFun g6989586621680051519 h6989586621680051520 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621680051513] -> [b6989586621680051514] -> [c6989586621680051515] -> [d6989586621680051516] -> [e6989586621680051517] -> [f6989586621680051518] -> TyFun [g6989586621680051519] [h6989586621680051520] -> *) (ZipWith7Sym7 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym7 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621680051513 (TyFun b6989586621680051514 (TyFun c6989586621680051515 (TyFun d6989586621680051516 (TyFun e6989586621680051517 (TyFun f6989586621680051518 (TyFun g6989586621680051519 h6989586621680051520 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621680051513] (TyFun [b6989586621680051514] (TyFun [c6989586621680051515] (TyFun [d6989586621680051516] (TyFun [e6989586621680051517] (TyFun [f6989586621680051518] (TyFun [g6989586621680051519] [h6989586621680051520] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym0 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym0 a6989586621680051513 b6989586621680051514 c6989586621680051515 d6989586621680051516 e6989586621680051517 f6989586621680051518 g6989586621680051519 h6989586621680051520) t -> () #