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_6989586621679479432 = 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_6989586621679515916Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t :: Ordering) #

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

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

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

(%:>=) :: forall t t. (Apply (Apply (:>=$) t) t ~ Apply (Apply TFHelper_6989586621679516048Sym0 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_6989586621679516081Sym0 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_6989586621679516114Sym0 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_6989586621679522988 = LTSym0 
ThenCmp GT _z_6989586621679522991 = 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 (Let6989586621679448376LgoSym3 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 k06989586621679591922 k6989586621679591924 -> *) (ErrorSym0 k06989586621679591922 k6989586621679591924) # 

Methods

suppressUnusedWarnings :: Proxy (ErrorSym0 k06989586621679591922 k6989586621679591924) t -> () #

type Apply k06989586621679591922 k2 (ErrorSym0 k06989586621679591922 k2) l0 # 
type Apply k06989586621679591922 k2 (ErrorSym0 k06989586621679591922 k2) l0 = ErrorSym1 k2 k06989586621679591922 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 a6989586621679513517 (TyFun a6989586621679513517 Ordering -> Type) -> *) (CompareSym0 a6989586621679513517) # 

Methods

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

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

data FoldlSym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679448348 (TyFun a6989586621679448347 b6989586621679448348 -> Type) -> Type) (TyFun b6989586621679448348 (TyFun [a6989586621679448347] b6989586621679448348 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679448347 b6989586621679448348) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym0 a6989586621679448347 b6989586621679448348) t -> () #

type Apply (TyFun b6989586621679448348 (TyFun a6989586621679448347 b6989586621679448348 -> Type) -> Type) (TyFun b6989586621679448348 (TyFun [a6989586621679448347] b6989586621679448348 -> Type) -> Type) (FoldlSym0 a6989586621679448347 b6989586621679448348) l0 # 
type Apply (TyFun b6989586621679448348 (TyFun a6989586621679448347 b6989586621679448348 -> Type) -> Type) (TyFun b6989586621679448348 (TyFun [a6989586621679448347] b6989586621679448348 -> Type) -> Type) (FoldlSym0 a6989586621679448347 b6989586621679448348) l0 = FoldlSym1 a6989586621679448347 b6989586621679448348 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 a6989586621679689467 Bool -> Type) -> TyFun [a6989586621679689467] Bool -> *) (Any_Sym1 a6989586621679689467) # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy (NullSym0 a6989586621679700167) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700133] (TyFun [a6989586621679700133] Bool -> Type) -> *) (IsSuffixOfSym0 a6989586621679700133) # 

Methods

suppressUnusedWarnings :: Proxy (IsSuffixOfSym0 a6989586621679700133) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700166] [a6989586621679700166] -> *) (ReverseSym0 a6989586621679700166) # 

Methods

suppressUnusedWarnings :: Proxy (ReverseSym0 a6989586621679700166) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700164] (TyFun [[a6989586621679700164]] [a6989586621679700164] -> Type) -> *) (IntercalateSym0 a6989586621679700164) # 

Methods

suppressUnusedWarnings :: Proxy (IntercalateSym0 a6989586621679700164) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700163] [[a6989586621679700163]] -> *) (SubsequencesSym0 a6989586621679700163) # 

Methods

suppressUnusedWarnings :: Proxy (SubsequencesSym0 a6989586621679700163) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700160] [[a6989586621679700160]] -> *) (PermutationsSym0 a6989586621679700160) # 

Methods

suppressUnusedWarnings :: Proxy (PermutationsSym0 a6989586621679700160) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700064] a6989586621679700064 -> *) (MinimumSym0 a6989586621679700064) # 

Methods

suppressUnusedWarnings :: Proxy (MinimumSym0 a6989586621679700064) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700065] a6989586621679700065 -> *) (MaximumSym0 a6989586621679700065) # 

Methods

suppressUnusedWarnings :: Proxy (MaximumSym0 a6989586621679700065) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700136] [[a6989586621679700136]] -> *) (InitsSym0 a6989586621679700136) # 

Methods

suppressUnusedWarnings :: Proxy (InitsSym0 a6989586621679700136) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700132] (TyFun [a6989586621679700132] Bool -> Type) -> *) (IsInfixOfSym0 a6989586621679700132) # 

Methods

suppressUnusedWarnings :: Proxy (IsInfixOfSym0 a6989586621679700132) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700135] [[a6989586621679700135]] -> *) (TailsSym0 a6989586621679700135) # 

Methods

suppressUnusedWarnings :: Proxy (TailsSym0 a6989586621679700135) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700134] (TyFun [a6989586621679700134] Bool -> Type) -> *) (IsPrefixOfSym0 a6989586621679700134) # 

Methods

suppressUnusedWarnings :: Proxy (IsPrefixOfSym0 a6989586621679700134) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700050] [a6989586621679700050] -> *) (NubSym0 a6989586621679700050) # 

Methods

suppressUnusedWarnings :: Proxy (NubSym0 a6989586621679700050) t -> () #

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

Methods

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

SuppressUnusedWarnings (TyFun [a6989586621679700046] (TyFun [a6989586621679700046] [a6989586621679700046] -> Type) -> *) (UnionSym0 a6989586621679700046) # 

Methods

suppressUnusedWarnings :: Proxy (UnionSym0 a6989586621679700046) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700062] [a6989586621679700062] -> *) (SortSym0 a6989586621679700062) # 

Methods

suppressUnusedWarnings :: Proxy (SortSym0 a6989586621679700062) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700076] (TyFun [a6989586621679700076] [a6989586621679700076] -> Type) -> *) (IntersectSym0 a6989586621679700076) # 

Methods

suppressUnusedWarnings :: Proxy (IntersectSym0 a6989586621679700076) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700066] [[a6989586621679700066]] -> *) (GroupSym0 a6989586621679700066) # 

Methods

suppressUnusedWarnings :: Proxy (GroupSym0 a6989586621679700066) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700056] a6989586621679700056 -> *) (SumSym0 a6989586621679700056) # 

Methods

suppressUnusedWarnings :: Proxy (SumSym0 a6989586621679700056) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700055] a6989586621679700055 -> *) (ProductSym0 a6989586621679700055) # 

Methods

suppressUnusedWarnings :: Proxy (ProductSym0 a6989586621679700055) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700054] Nat -> *) (LengthSym0 a6989586621679700054) # 

Methods

suppressUnusedWarnings :: Proxy (LengthSym0 a6989586621679700054) t -> () #

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

Methods

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

SuppressUnusedWarnings (TyFun [a6989586621679923077] (TyFun [a6989586621679923077] (Maybe [a6989586621679923077]) -> Type) -> *) (StripPrefixSym0 a6989586621679923077) # 

Methods

suppressUnusedWarnings :: Proxy (StripPrefixSym0 a6989586621679923077) t -> () #

SuppressUnusedWarnings (TyFun (Maybe a6989586621679677401) Bool -> *) (IsJustSym0 a6989586621679677401) # 

Methods

suppressUnusedWarnings :: Proxy (IsJustSym0 a6989586621679677401) t -> () #

SuppressUnusedWarnings (TyFun (Maybe a6989586621679677400) Bool -> *) (IsNothingSym0 a6989586621679677400) # 

Methods

suppressUnusedWarnings :: Proxy (IsNothingSym0 a6989586621679677400) t -> () #

SuppressUnusedWarnings (TyFun (Maybe a6989586621679677399) a6989586621679677399 -> *) (FromJustSym0 a6989586621679677399) # 

Methods

suppressUnusedWarnings :: Proxy (FromJustSym0 a6989586621679677399) t -> () #

SuppressUnusedWarnings (TyFun (Maybe a6989586621679677397) [a6989586621679677397] -> *) (MaybeToListSym0 a6989586621679677397) # 

Methods

suppressUnusedWarnings :: Proxy (MaybeToListSym0 a6989586621679677397) t -> () #

SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679700067] ([a6989586621679700067], [a6989586621679700067]) -> Type) -> *) (SplitAtSym0 a6989586621679700067) # 

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym0 a6989586621679700067) t -> () #

SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679700069] [a6989586621679700069] -> Type) -> *) (TakeSym0 a6989586621679700069) # 

Methods

suppressUnusedWarnings :: Proxy (TakeSym0 a6989586621679700069) t -> () #

SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679700068] [a6989586621679700068] -> Type) -> *) (DropSym0 a6989586621679700068) # 

Methods

suppressUnusedWarnings :: Proxy (DropSym0 a6989586621679700068) t -> () #

SuppressUnusedWarnings (TyFun Nat (TyFun a6989586621679700053 [a6989586621679700053] -> Type) -> *) (ReplicateSym0 a6989586621679700053) # 

Methods

suppressUnusedWarnings :: Proxy (ReplicateSym0 a6989586621679700053) t -> () #

SuppressUnusedWarnings (TyFun Nat a6989586621679601146 -> *) (FromIntegerSym0 a6989586621679601146) # 

Methods

suppressUnusedWarnings :: Proxy (FromIntegerSym0 a6989586621679601146) t -> () #

SuppressUnusedWarnings (TyFun Nat a6989586621679612097 -> *) (ToEnumSym0 a6989586621679612097) # 

Methods

suppressUnusedWarnings :: Proxy (ToEnumSym0 a6989586621679612097) 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 a6989586621679478696 (TyFun a6989586621679478696 (TyFun Bool a6989586621679478696 -> Type) -> Type) -> *) (Bool_Sym0 a6989586621679478696) # 

Methods

suppressUnusedWarnings :: Proxy (Bool_Sym0 a6989586621679478696) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679482535 a6989586621679482535 -> *) (IdSym0 a6989586621679482535) # 

Methods

suppressUnusedWarnings :: Proxy (IdSym0 a6989586621679482535) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679482526 (TyFun a6989586621679482526 a6989586621679482526 -> Type) -> *) (AsTypeOfSym0 a6989586621679482526) # 

Methods

suppressUnusedWarnings :: Proxy (AsTypeOfSym0 a6989586621679482526) t -> () #

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun a6989586621679513517 (TyFun a6989586621679513517 a6989586621679513517 -> Type) -> *) (MinSym0 a6989586621679513517) # 

Methods

suppressUnusedWarnings :: Proxy (MinSym0 a6989586621679513517) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679513517 (TyFun a6989586621679513517 a6989586621679513517 -> Type) -> *) (MaxSym0 a6989586621679513517) # 

Methods

suppressUnusedWarnings :: Proxy (MaxSym0 a6989586621679513517) t -> () #

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

Methods

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

SuppressUnusedWarnings (TyFun a6989586621679513517 (TyFun a6989586621679513517 Bool -> Type) -> *) ((:>$) a6989586621679513517) # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun a6989586621679601146 a6989586621679601146 -> *) (SignumSym0 a6989586621679601146) # 

Methods

suppressUnusedWarnings :: Proxy (SignumSym0 a6989586621679601146) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679601146 a6989586621679601146 -> *) (AbsSym0 a6989586621679601146) # 

Methods

suppressUnusedWarnings :: Proxy (AbsSym0 a6989586621679601146) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679601146 a6989586621679601146 -> *) (NegateSym0 a6989586621679601146) # 

Methods

suppressUnusedWarnings :: Proxy (NegateSym0 a6989586621679601146) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679601146 (TyFun a6989586621679601146 a6989586621679601146 -> Type) -> *) ((:*$) a6989586621679601146) # 

Methods

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

SuppressUnusedWarnings (TyFun a6989586621679601146 (TyFun a6989586621679601146 a6989586621679601146 -> Type) -> *) ((:-$) a6989586621679601146) # 

Methods

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

SuppressUnusedWarnings (TyFun a6989586621679601146 (TyFun a6989586621679601146 a6989586621679601146 -> Type) -> *) ((:+$) a6989586621679601146) # 

Methods

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

SuppressUnusedWarnings (TyFun a6989586621679603462 (TyFun a6989586621679603462 a6989586621679603462 -> Type) -> *) (SubtractSym0 a6989586621679603462) # 

Methods

suppressUnusedWarnings :: Proxy (SubtractSym0 a6989586621679603462) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679612097 (TyFun a6989586621679612097 (TyFun a6989586621679612097 [a6989586621679612097] -> Type) -> Type) -> *) (EnumFromThenToSym0 a6989586621679612097) # 

Methods

suppressUnusedWarnings :: Proxy (EnumFromThenToSym0 a6989586621679612097) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679612097 (TyFun a6989586621679612097 [a6989586621679612097] -> Type) -> *) (EnumFromToSym0 a6989586621679612097) # 

Methods

suppressUnusedWarnings :: Proxy (EnumFromToSym0 a6989586621679612097) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679612097 Nat -> *) (FromEnumSym0 a6989586621679612097) # 

Methods

suppressUnusedWarnings :: Proxy (FromEnumSym0 a6989586621679612097) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679612097 a6989586621679612097 -> *) (PredSym0 a6989586621679612097) # 

Methods

suppressUnusedWarnings :: Proxy (PredSym0 a6989586621679612097) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679612097 a6989586621679612097 -> *) (SuccSym0 a6989586621679612097) # 

Methods

suppressUnusedWarnings :: Proxy (SuccSym0 a6989586621679612097) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679677398 (TyFun (Maybe a6989586621679677398) a6989586621679677398 -> Type) -> *) (FromMaybeSym0 a6989586621679677398) # 

Methods

suppressUnusedWarnings :: Proxy (FromMaybeSym0 a6989586621679677398) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679700165 (TyFun [a6989586621679700165] [a6989586621679700165] -> Type) -> *) (IntersperseSym0 a6989586621679700165) # 

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym0 a6989586621679700165) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679700131 (TyFun [a6989586621679700131] Bool -> Type) -> *) (ElemSym0 a6989586621679700131) # 

Methods

suppressUnusedWarnings :: Proxy (ElemSym0 a6989586621679700131) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679700130 (TyFun [a6989586621679700130] Bool -> Type) -> *) (NotElemSym0 a6989586621679700130) # 

Methods

suppressUnusedWarnings :: Proxy (NotElemSym0 a6989586621679700130) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679700080 (TyFun [a6989586621679700080] (Maybe Nat) -> Type) -> *) (ElemIndexSym0 a6989586621679700080) # 

Methods

suppressUnusedWarnings :: Proxy (ElemIndexSym0 a6989586621679700080) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679700079 (TyFun [a6989586621679700079] [Nat] -> Type) -> *) (ElemIndicesSym0 a6989586621679700079) # 

Methods

suppressUnusedWarnings :: Proxy (ElemIndicesSym0 a6989586621679700079) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679700090 (TyFun [a6989586621679700090] [a6989586621679700090] -> Type) -> *) (DeleteSym0 a6989586621679700090) # 

Methods

suppressUnusedWarnings :: Proxy (DeleteSym0 a6989586621679700090) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679700063 (TyFun [a6989586621679700063] [a6989586621679700063] -> Type) -> *) (InsertSym0 a6989586621679700063) # 

Methods

suppressUnusedWarnings :: Proxy (InsertSym0 a6989586621679700063) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679448348 (TyFun a6989586621679448347 b6989586621679448348 -> Type) -> Type) -> TyFun b6989586621679448348 (TyFun [a6989586621679448347] b6989586621679448348 -> Type) -> *) (FoldlSym1 a6989586621679448347 b6989586621679448348) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym1 a6989586621679448347 b6989586621679448348) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679448348 (TyFun a6989586621679448347 b6989586621679448348 -> Type) -> Type) -> b6989586621679448348 -> TyFun [a6989586621679448347] b6989586621679448348 -> *) (FoldlSym2 a6989586621679448347 b6989586621679448348) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym2 a6989586621679448347 b6989586621679448348) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679482539 (TyFun b6989586621679482540 b6989586621679482540 -> Type) -> Type) -> TyFun b6989586621679482540 (TyFun [a6989586621679482539] b6989586621679482540 -> Type) -> *) (FoldrSym1 a6989586621679482539 b6989586621679482540) # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym1 a6989586621679482539 b6989586621679482540) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679482539 (TyFun b6989586621679482540 b6989586621679482540 -> Type) -> Type) -> b6989586621679482540 -> TyFun [a6989586621679482539] b6989586621679482540 -> *) (FoldrSym2 a6989586621679482539 b6989586621679482540) # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym2 a6989586621679482539 b6989586621679482540) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679482537 b6989586621679482538 -> Type) -> TyFun [a6989586621679482537] [b6989586621679482538] -> *) (MapSym1 a6989586621679482537 b6989586621679482538) # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a6989586621679482537 b6989586621679482538) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679677393 (Maybe b6989586621679677394) -> Type) -> TyFun [a6989586621679677393] [b6989586621679677394] -> *) (MapMaybeSym1 a6989586621679677393 b6989586621679677394) # 

Methods

suppressUnusedWarnings :: Proxy (MapMaybeSym1 a6989586621679677393 b6989586621679677394) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679700159 (TyFun a6989586621679700158 b6989586621679700159 -> Type) -> Type) -> TyFun b6989586621679700159 (TyFun [a6989586621679700158] b6989586621679700159 -> Type) -> *) (Foldl'Sym1 a6989586621679700158 b6989586621679700159) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym1 a6989586621679700158 b6989586621679700159) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679700159 (TyFun a6989586621679700158 b6989586621679700159 -> Type) -> Type) -> b6989586621679700159 -> TyFun [a6989586621679700158] b6989586621679700159 -> *) (Foldl'Sym2 a6989586621679700158 b6989586621679700159) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym2 a6989586621679700158 b6989586621679700159) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679700152 [b6989586621679700153] -> Type) -> TyFun [a6989586621679700152] [b6989586621679700153] -> *) (ConcatMapSym1 a6989586621679700152 b6989586621679700153) # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym1 a6989586621679700152 b6989586621679700153) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679700149 (TyFun a6989586621679700150 b6989586621679700149 -> Type) -> Type) -> TyFun b6989586621679700149 (TyFun [a6989586621679700150] [b6989586621679700149] -> Type) -> *) (ScanlSym1 a6989586621679700150 b6989586621679700149) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a6989586621679700150 b6989586621679700149) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679700149 (TyFun a6989586621679700150 b6989586621679700149 -> Type) -> Type) -> b6989586621679700149 -> TyFun [a6989586621679700150] [b6989586621679700149] -> *) (ScanlSym2 a6989586621679700150 b6989586621679700149) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a6989586621679700150 b6989586621679700149) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679700146 (TyFun b6989586621679700147 b6989586621679700147 -> Type) -> Type) -> TyFun b6989586621679700147 (TyFun [a6989586621679700146] [b6989586621679700147] -> Type) -> *) (ScanrSym1 a6989586621679700146 b6989586621679700147) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a6989586621679700146 b6989586621679700147) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679700146 (TyFun b6989586621679700147 b6989586621679700147 -> Type) -> Type) -> b6989586621679700147 -> TyFun [a6989586621679700146] [b6989586621679700147] -> *) (ScanrSym2 a6989586621679700146 b6989586621679700147) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a6989586621679700146 b6989586621679700147) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679700137 (Maybe (a6989586621679700138, b6989586621679700137)) -> Type) -> TyFun b6989586621679700137 [a6989586621679700138] -> *) (UnfoldrSym1 a6989586621679700138 b6989586621679700137) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 a6989586621679700138 b6989586621679700137) t -> () #

SuppressUnusedWarnings ([a6989586621679700128] -> TyFun [b6989586621679700129] [(a6989586621679700128, b6989586621679700129)] -> *) (ZipSym1 b6989586621679700129 a6989586621679700128) # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 b6989586621679700129 a6989586621679700128) t -> () #

SuppressUnusedWarnings ([a6989586621679923022] -> TyFun i6989586621679923021 a6989586621679923022 -> *) (GenericIndexSym1 i6989586621679923021 a6989586621679923022) # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym1 i6989586621679923021 a6989586621679923022) t -> () #

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

Methods

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

SuppressUnusedWarnings (a6989586621679482533 -> TyFun b6989586621679482534 a6989586621679482533 -> *) (ConstSym1 b6989586621679482534 a6989586621679482533) # 

Methods

suppressUnusedWarnings :: Proxy (ConstSym1 b6989586621679482534 a6989586621679482533) t -> () #

SuppressUnusedWarnings (a6989586621679482524 -> TyFun b6989586621679482525 b6989586621679482525 -> *) (SeqSym1 b6989586621679482525 a6989586621679482524) # 

Methods

suppressUnusedWarnings :: Proxy (SeqSym1 b6989586621679482525 a6989586621679482524) t -> () #

SuppressUnusedWarnings (b6989586621679676147 -> TyFun (TyFun a6989586621679676148 b6989586621679676147 -> Type) (TyFun (Maybe a6989586621679676148) b6989586621679676147 -> Type) -> *) (Maybe_Sym1 a6989586621679676148 b6989586621679676147) # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym1 a6989586621679676148 b6989586621679676147) t -> () #

SuppressUnusedWarnings (b6989586621679676147 -> (TyFun a6989586621679676148 b6989586621679676147 -> Type) -> TyFun (Maybe a6989586621679676148) b6989586621679676147 -> *) (Maybe_Sym2 a6989586621679676148 b6989586621679676147) # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym2 a6989586621679676148 b6989586621679676147) t -> () #

SuppressUnusedWarnings (a6989586621679700059 -> TyFun [(a6989586621679700059, b6989586621679700060)] (Maybe b6989586621679700060) -> *) (LookupSym1 b6989586621679700060 a6989586621679700059) # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym1 b6989586621679700060 a6989586621679700059) t -> () #

SuppressUnusedWarnings (i6989586621679923027 -> TyFun [a6989586621679923028] [a6989586621679923028] -> *) (GenericTakeSym1 a6989586621679923028 i6989586621679923027) # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym1 a6989586621679923028 i6989586621679923027) t -> () #

SuppressUnusedWarnings (i6989586621679923025 -> TyFun [a6989586621679923026] [a6989586621679923026] -> *) (GenericDropSym1 a6989586621679923026 i6989586621679923025) # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym1 a6989586621679923026 i6989586621679923025) t -> () #

SuppressUnusedWarnings (i6989586621679923023 -> TyFun [a6989586621679923024] ([a6989586621679923024], [a6989586621679923024]) -> *) (GenericSplitAtSym1 a6989586621679923024 i6989586621679923023) # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym1 a6989586621679923024 i6989586621679923023) t -> () #

SuppressUnusedWarnings (i6989586621679923019 -> TyFun a6989586621679923020 [a6989586621679923020] -> *) (GenericReplicateSym1 a6989586621679923020 i6989586621679923019) # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym1 a6989586621679923020 i6989586621679923019) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679448348 (TyFun a6989586621679448347 b6989586621679448348 -> Type) -> Type) (TyFun b6989586621679448348 (TyFun [a6989586621679448347] b6989586621679448348 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679448347 b6989586621679448348) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym0 a6989586621679448347 b6989586621679448348) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679482539 (TyFun b6989586621679482540 b6989586621679482540 -> Type) -> Type) (TyFun b6989586621679482540 (TyFun [a6989586621679482539] b6989586621679482540 -> Type) -> Type) -> *) (FoldrSym0 a6989586621679482539 b6989586621679482540) # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym0 a6989586621679482539 b6989586621679482540) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679482537 b6989586621679482538 -> Type) (TyFun [a6989586621679482537] [b6989586621679482538] -> Type) -> *) (MapSym0 a6989586621679482537 b6989586621679482538) # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a6989586621679482537 b6989586621679482538) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679677393 (Maybe b6989586621679677394) -> Type) (TyFun [a6989586621679677393] [b6989586621679677394] -> Type) -> *) (MapMaybeSym0 a6989586621679677393 b6989586621679677394) # 

Methods

suppressUnusedWarnings :: Proxy (MapMaybeSym0 a6989586621679677393 b6989586621679677394) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679700159 (TyFun a6989586621679700158 b6989586621679700159 -> Type) -> Type) (TyFun b6989586621679700159 (TyFun [a6989586621679700158] b6989586621679700159 -> Type) -> Type) -> *) (Foldl'Sym0 a6989586621679700158 b6989586621679700159) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym0 a6989586621679700158 b6989586621679700159) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679700152 [b6989586621679700153] -> Type) (TyFun [a6989586621679700152] [b6989586621679700153] -> Type) -> *) (ConcatMapSym0 a6989586621679700152 b6989586621679700153) # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym0 a6989586621679700152 b6989586621679700153) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679700149 (TyFun a6989586621679700150 b6989586621679700149 -> Type) -> Type) (TyFun b6989586621679700149 (TyFun [a6989586621679700150] [b6989586621679700149] -> Type) -> Type) -> *) (ScanlSym0 a6989586621679700150 b6989586621679700149) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a6989586621679700150 b6989586621679700149) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679700146 (TyFun b6989586621679700147 b6989586621679700147 -> Type) -> Type) (TyFun b6989586621679700147 (TyFun [a6989586621679700146] [b6989586621679700147] -> Type) -> Type) -> *) (ScanrSym0 a6989586621679700146 b6989586621679700147) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a6989586621679700146 b6989586621679700147) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679700137 (Maybe (a6989586621679700138, b6989586621679700137)) -> Type) (TyFun b6989586621679700137 [a6989586621679700138] -> Type) -> *) (UnfoldrSym0 b6989586621679700137 a6989586621679700138) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 b6989586621679700137 a6989586621679700138) t -> () #

SuppressUnusedWarnings (TyFun [Either a6989586621679668933 b6989586621679668934] [a6989586621679668933] -> *) (LeftsSym0 b6989586621679668934 a6989586621679668933) # 

Methods

suppressUnusedWarnings :: Proxy (LeftsSym0 b6989586621679668934 a6989586621679668933) t -> () #

SuppressUnusedWarnings (TyFun [Either a6989586621679668931 b6989586621679668932] [b6989586621679668932] -> *) (RightsSym0 a6989586621679668931 b6989586621679668932) # 

Methods

suppressUnusedWarnings :: Proxy (RightsSym0 a6989586621679668931 b6989586621679668932) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679700116, b6989586621679700117)] ([a6989586621679700116], [b6989586621679700117]) -> *) (UnzipSym0 a6989586621679700116 b6989586621679700117) # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a6989586621679700116 b6989586621679700117) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700128] (TyFun [b6989586621679700129] [(a6989586621679700128, b6989586621679700129)] -> Type) -> *) (ZipSym0 a6989586621679700128 b6989586621679700129) # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a6989586621679700128 b6989586621679700129) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700045] i6989586621679700044 -> *) (GenericLengthSym0 a6989586621679700045 i6989586621679700044) # 

Methods

suppressUnusedWarnings :: Proxy (GenericLengthSym0 a6989586621679700045 i6989586621679700044) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679923022] (TyFun i6989586621679923021 a6989586621679923022 -> Type) -> *) (GenericIndexSym0 i6989586621679923021 a6989586621679923022) # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym0 i6989586621679923021 a6989586621679923022) t -> () #

SuppressUnusedWarnings (TyFun (Either a6989586621679668927 b6989586621679668928) Bool -> *) (IsLeftSym0 a6989586621679668927 b6989586621679668928) # 

Methods

suppressUnusedWarnings :: Proxy (IsLeftSym0 a6989586621679668927 b6989586621679668928) t -> () #

SuppressUnusedWarnings (TyFun (Either a6989586621679668925 b6989586621679668926) Bool -> *) (IsRightSym0 a6989586621679668925 b6989586621679668926) # 

Methods

suppressUnusedWarnings :: Proxy (IsRightSym0 a6989586621679668925 b6989586621679668926) t -> () #

SuppressUnusedWarnings (TyFun (a6989586621679686056, b6989586621679686057) a6989586621679686056 -> *) (FstSym0 b6989586621679686057 a6989586621679686056) # 

Methods

suppressUnusedWarnings :: Proxy (FstSym0 b6989586621679686057 a6989586621679686056) t -> () #

SuppressUnusedWarnings (TyFun (a6989586621679686054, b6989586621679686055) b6989586621679686055 -> *) (SndSym0 a6989586621679686054 b6989586621679686055) # 

Methods

suppressUnusedWarnings :: Proxy (SndSym0 a6989586621679686054 b6989586621679686055) t -> () #

SuppressUnusedWarnings (TyFun (a6989586621679686046, b6989586621679686047) (b6989586621679686047, a6989586621679686046) -> *) (SwapSym0 b6989586621679686047 a6989586621679686046) # 

Methods

suppressUnusedWarnings :: Proxy (SwapSym0 b6989586621679686047 a6989586621679686046) t -> () #

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

Methods

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

SuppressUnusedWarnings (TyFun b6989586621679054101 (Either a6989586621679054100 b6989586621679054101) -> *) (RightSym0 a6989586621679054100 b6989586621679054101) # 

Methods

suppressUnusedWarnings :: Proxy (RightSym0 a6989586621679054100 b6989586621679054101) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679054100 (Either a6989586621679054100 b6989586621679054101) -> *) (LeftSym0 a6989586621679054100 b6989586621679054101) # 

Methods

suppressUnusedWarnings :: Proxy (LeftSym0 a6989586621679054100 b6989586621679054101) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679482533 (TyFun b6989586621679482534 a6989586621679482533 -> Type) -> *) (ConstSym0 b6989586621679482534 a6989586621679482533) # 

Methods

suppressUnusedWarnings :: Proxy (ConstSym0 b6989586621679482534 a6989586621679482533) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679482524 (TyFun b6989586621679482525 b6989586621679482525 -> Type) -> *) (SeqSym0 a6989586621679482524 b6989586621679482525) # 

Methods

suppressUnusedWarnings :: Proxy (SeqSym0 a6989586621679482524 b6989586621679482525) t -> () #

SuppressUnusedWarnings (TyFun k06989586621679591922 k6989586621679591924 -> *) (ErrorSym0 k06989586621679591922 k6989586621679591924) # 

Methods

suppressUnusedWarnings :: Proxy (ErrorSym0 k06989586621679591922 k6989586621679591924) t -> () #

SuppressUnusedWarnings (TyFun b6989586621679676147 (TyFun (TyFun a6989586621679676148 b6989586621679676147 -> Type) (TyFun (Maybe a6989586621679676148) b6989586621679676147 -> Type) -> Type) -> *) (Maybe_Sym0 a6989586621679676148 b6989586621679676147) # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym0 a6989586621679676148 b6989586621679676147) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679700059 (TyFun [(a6989586621679700059, b6989586621679700060)] (Maybe b6989586621679700060) -> Type) -> *) (LookupSym0 a6989586621679700059 b6989586621679700060) # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym0 a6989586621679700059 b6989586621679700060) t -> () #

SuppressUnusedWarnings (TyFun i6989586621679923027 (TyFun [a6989586621679923028] [a6989586621679923028] -> Type) -> *) (GenericTakeSym0 i6989586621679923027 a6989586621679923028) # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym0 i6989586621679923027 a6989586621679923028) t -> () #

SuppressUnusedWarnings (TyFun i6989586621679923025 (TyFun [a6989586621679923026] [a6989586621679923026] -> Type) -> *) (GenericDropSym0 i6989586621679923025 a6989586621679923026) # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym0 i6989586621679923025 a6989586621679923026) t -> () #

SuppressUnusedWarnings (TyFun i6989586621679923023 (TyFun [a6989586621679923024] ([a6989586621679923024], [a6989586621679923024]) -> Type) -> *) (GenericSplitAtSym0 i6989586621679923023 a6989586621679923024) # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym0 i6989586621679923023 a6989586621679923024) t -> () #

SuppressUnusedWarnings (TyFun i6989586621679923019 (TyFun a6989586621679923020 [a6989586621679923020] -> Type) -> *) (GenericReplicateSym0 i6989586621679923019 a6989586621679923020) # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym0 i6989586621679923019 a6989586621679923020) t -> () #

SuppressUnusedWarnings ((TyFun (a6989586621679686051, b6989586621679686052) c6989586621679686053 -> Type) -> TyFun a6989586621679686051 (TyFun b6989586621679686052 c6989586621679686053 -> Type) -> *) (CurrySym1 a6989586621679686051 b6989586621679686052 c6989586621679686053) # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym1 a6989586621679686051 b6989586621679686052 c6989586621679686053) t -> () #

SuppressUnusedWarnings ((TyFun (a6989586621679686051, b6989586621679686052) c6989586621679686053 -> Type) -> a6989586621679686051 -> TyFun b6989586621679686052 c6989586621679686053 -> *) (CurrySym2 a6989586621679686051 b6989586621679686052 c6989586621679686053) # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym2 a6989586621679686051 b6989586621679686052 c6989586621679686053) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679482530 c6989586621679482531 -> Type) -> TyFun (TyFun a6989586621679482532 b6989586621679482530 -> Type) (TyFun a6989586621679482532 c6989586621679482531 -> Type) -> *) ((:.$$) a6989586621679482532 b6989586621679482530 c6989586621679482531) # 

Methods

suppressUnusedWarnings :: Proxy ((a6989586621679482532 :.$$ b6989586621679482530) c6989586621679482531) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679482530 c6989586621679482531 -> Type) -> (TyFun a6989586621679482532 b6989586621679482530 -> Type) -> TyFun a6989586621679482532 c6989586621679482531 -> *) ((:.$$$) a6989586621679482532 b6989586621679482530 c6989586621679482531) # 

Methods

suppressUnusedWarnings :: Proxy ((a6989586621679482532 :.$$$ b6989586621679482530) c6989586621679482531) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679482527 (TyFun b6989586621679482528 c6989586621679482529 -> Type) -> Type) -> TyFun b6989586621679482528 (TyFun a6989586621679482527 c6989586621679482529 -> Type) -> *) (FlipSym1 a6989586621679482527 b6989586621679482528 c6989586621679482529) # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym1 a6989586621679482527 b6989586621679482528 c6989586621679482529) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679482527 (TyFun b6989586621679482528 c6989586621679482529 -> Type) -> Type) -> b6989586621679482528 -> TyFun a6989586621679482527 c6989586621679482529 -> *) (FlipSym2 a6989586621679482527 b6989586621679482528 c6989586621679482529) # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym2 a6989586621679482527 b6989586621679482528 c6989586621679482529) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679667663 c6989586621679667664 -> Type) -> TyFun (TyFun b6989586621679667665 c6989586621679667664 -> Type) (TyFun (Either a6989586621679667663 b6989586621679667665) c6989586621679667664 -> Type) -> *) (Either_Sym1 b6989586621679667665 a6989586621679667663 c6989586621679667664) # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym1 b6989586621679667665 a6989586621679667663 c6989586621679667664) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679667663 c6989586621679667664 -> Type) -> (TyFun b6989586621679667665 c6989586621679667664 -> Type) -> TyFun (Either a6989586621679667663 b6989586621679667665) c6989586621679667664 -> *) (Either_Sym2 b6989586621679667665 a6989586621679667663 c6989586621679667664) # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym2 b6989586621679667665 a6989586621679667663 c6989586621679667664) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679686048 (TyFun b6989586621679686049 c6989586621679686050 -> Type) -> Type) -> TyFun (a6989586621679686048, b6989586621679686049) c6989586621679686050 -> *) (UncurrySym1 a6989586621679686048 b6989586621679686049 c6989586621679686050) # 

Methods

suppressUnusedWarnings :: Proxy (UncurrySym1 a6989586621679686048 b6989586621679686049 c6989586621679686050) t -> () #

SuppressUnusedWarnings ((TyFun acc6989586621679700142 (TyFun x6989586621679700143 (acc6989586621679700142, y6989586621679700144) -> Type) -> Type) -> TyFun acc6989586621679700142 (TyFun [x6989586621679700143] (acc6989586621679700142, [y6989586621679700144]) -> Type) -> *) (MapAccumLSym1 x6989586621679700143 acc6989586621679700142 y6989586621679700144) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym1 x6989586621679700143 acc6989586621679700142 y6989586621679700144) t -> () #

SuppressUnusedWarnings ((TyFun acc6989586621679700142 (TyFun x6989586621679700143 (acc6989586621679700142, y6989586621679700144) -> Type) -> Type) -> acc6989586621679700142 -> TyFun [x6989586621679700143] (acc6989586621679700142, [y6989586621679700144]) -> *) (MapAccumLSym2 x6989586621679700143 acc6989586621679700142 y6989586621679700144) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym2 x6989586621679700143 acc6989586621679700142 y6989586621679700144) t -> () #

SuppressUnusedWarnings ((TyFun acc6989586621679700139 (TyFun x6989586621679700140 (acc6989586621679700139, y6989586621679700141) -> Type) -> Type) -> TyFun acc6989586621679700139 (TyFun [x6989586621679700140] (acc6989586621679700139, [y6989586621679700141]) -> Type) -> *) (MapAccumRSym1 x6989586621679700140 acc6989586621679700139 y6989586621679700141) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym1 x6989586621679700140 acc6989586621679700139 y6989586621679700141) t -> () #

SuppressUnusedWarnings ((TyFun acc6989586621679700139 (TyFun x6989586621679700140 (acc6989586621679700139, y6989586621679700141) -> Type) -> Type) -> acc6989586621679700139 -> TyFun [x6989586621679700140] (acc6989586621679700139, [y6989586621679700141]) -> *) (MapAccumRSym2 x6989586621679700140 acc6989586621679700139 y6989586621679700141) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym2 x6989586621679700140 acc6989586621679700139 y6989586621679700141) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679700122 (TyFun b6989586621679700123 c6989586621679700124 -> Type) -> Type) -> TyFun [a6989586621679700122] (TyFun [b6989586621679700123] [c6989586621679700124] -> Type) -> *) (ZipWithSym1 a6989586621679700122 b6989586621679700123 c6989586621679700124) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a6989586621679700122 b6989586621679700123 c6989586621679700124) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679700122 (TyFun b6989586621679700123 c6989586621679700124 -> Type) -> Type) -> [a6989586621679700122] -> TyFun [b6989586621679700123] [c6989586621679700124] -> *) (ZipWithSym2 a6989586621679700122 b6989586621679700123 c6989586621679700124) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a6989586621679700122 b6989586621679700123 c6989586621679700124) t -> () #

SuppressUnusedWarnings ([a6989586621679700125] -> TyFun [b6989586621679700126] (TyFun [c6989586621679700127] [(a6989586621679700125, b6989586621679700126, c6989586621679700127)] -> Type) -> *) (Zip3Sym1 b6989586621679700126 c6989586621679700127 a6989586621679700125) # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym1 b6989586621679700126 c6989586621679700127 a6989586621679700125) t -> () #

SuppressUnusedWarnings ([a6989586621679700125] -> [b6989586621679700126] -> TyFun [c6989586621679700127] [(a6989586621679700125, b6989586621679700126, c6989586621679700127)] -> *) (Zip3Sym2 c6989586621679700127 b6989586621679700126 a6989586621679700125) # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym2 c6989586621679700127 b6989586621679700126 a6989586621679700125) 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 (a6989586621679686051, b6989586621679686052) c6989586621679686053 -> Type) (TyFun a6989586621679686051 (TyFun b6989586621679686052 c6989586621679686053 -> Type) -> Type) -> *) (CurrySym0 a6989586621679686051 b6989586621679686052 c6989586621679686053) # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym0 a6989586621679686051 b6989586621679686052 c6989586621679686053) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679482530 c6989586621679482531 -> Type) (TyFun (TyFun a6989586621679482532 b6989586621679482530 -> Type) (TyFun a6989586621679482532 c6989586621679482531 -> Type) -> Type) -> *) ((:.$) b6989586621679482530 a6989586621679482532 c6989586621679482531) # 

Methods

suppressUnusedWarnings :: Proxy ((b6989586621679482530 :.$ a6989586621679482532) c6989586621679482531) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679482527 (TyFun b6989586621679482528 c6989586621679482529 -> Type) -> Type) (TyFun b6989586621679482528 (TyFun a6989586621679482527 c6989586621679482529 -> Type) -> Type) -> *) (FlipSym0 b6989586621679482528 a6989586621679482527 c6989586621679482529) # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym0 b6989586621679482528 a6989586621679482527 c6989586621679482529) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679667663 c6989586621679667664 -> Type) (TyFun (TyFun b6989586621679667665 c6989586621679667664 -> Type) (TyFun (Either a6989586621679667663 b6989586621679667665) c6989586621679667664 -> Type) -> Type) -> *) (Either_Sym0 a6989586621679667663 b6989586621679667665 c6989586621679667664) # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym0 a6989586621679667663 b6989586621679667665 c6989586621679667664) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679686048 (TyFun b6989586621679686049 c6989586621679686050 -> Type) -> Type) (TyFun (a6989586621679686048, b6989586621679686049) c6989586621679686050 -> Type) -> *) (UncurrySym0 a6989586621679686048 b6989586621679686049 c6989586621679686050) # 

Methods

suppressUnusedWarnings :: Proxy (UncurrySym0 a6989586621679686048 b6989586621679686049 c6989586621679686050) t -> () #

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679700142 (TyFun x6989586621679700143 (acc6989586621679700142, y6989586621679700144) -> Type) -> Type) (TyFun acc6989586621679700142 (TyFun [x6989586621679700143] (acc6989586621679700142, [y6989586621679700144]) -> Type) -> Type) -> *) (MapAccumLSym0 x6989586621679700143 acc6989586621679700142 y6989586621679700144) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym0 x6989586621679700143 acc6989586621679700142 y6989586621679700144) t -> () #

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679700139 (TyFun x6989586621679700140 (acc6989586621679700139, y6989586621679700141) -> Type) -> Type) (TyFun acc6989586621679700139 (TyFun [x6989586621679700140] (acc6989586621679700139, [y6989586621679700141]) -> Type) -> Type) -> *) (MapAccumRSym0 x6989586621679700140 acc6989586621679700139 y6989586621679700141) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym0 x6989586621679700140 acc6989586621679700139 y6989586621679700141) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679700122 (TyFun b6989586621679700123 c6989586621679700124 -> Type) -> Type) (TyFun [a6989586621679700122] (TyFun [b6989586621679700123] [c6989586621679700124] -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679700122 b6989586621679700123 c6989586621679700124) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a6989586621679700122 b6989586621679700123 c6989586621679700124) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679700113, b6989586621679700114, c6989586621679700115)] ([a6989586621679700113], [b6989586621679700114], [c6989586621679700115]) -> *) (Unzip3Sym0 a6989586621679700113 b6989586621679700114 c6989586621679700115) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip3Sym0 a6989586621679700113 b6989586621679700114 c6989586621679700115) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679700125] (TyFun [b6989586621679700126] (TyFun [c6989586621679700127] [(a6989586621679700125, b6989586621679700126, c6989586621679700127)] -> Type) -> Type) -> *) (Zip3Sym0 a6989586621679700125 b6989586621679700126 c6989586621679700127) # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym0 a6989586621679700125 b6989586621679700126 c6989586621679700127) 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 a6989586621679700118 (TyFun b6989586621679700119 (TyFun c6989586621679700120 d6989586621679700121 -> Type) -> Type) -> Type) -> TyFun [a6989586621679700118] (TyFun [b6989586621679700119] (TyFun [c6989586621679700120] [d6989586621679700121] -> Type) -> Type) -> *) (ZipWith3Sym1 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym1 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679700118 (TyFun b6989586621679700119 (TyFun c6989586621679700120 d6989586621679700121 -> Type) -> Type) -> Type) -> [a6989586621679700118] -> TyFun [b6989586621679700119] (TyFun [c6989586621679700120] [d6989586621679700121] -> Type) -> *) (ZipWith3Sym2 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym2 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679700118 (TyFun b6989586621679700119 (TyFun c6989586621679700120 d6989586621679700121 -> Type) -> Type) -> Type) -> [a6989586621679700118] -> [b6989586621679700119] -> TyFun [c6989586621679700120] [d6989586621679700121] -> *) (ZipWith3Sym3 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym3 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) t -> () #

SuppressUnusedWarnings ([a6989586621679923073] -> TyFun [b6989586621679923074] (TyFun [c6989586621679923075] (TyFun [d6989586621679923076] [(a6989586621679923073, b6989586621679923074, c6989586621679923075, d6989586621679923076)] -> Type) -> Type) -> *) (Zip4Sym1 b6989586621679923074 c6989586621679923075 d6989586621679923076 a6989586621679923073) # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym1 b6989586621679923074 c6989586621679923075 d6989586621679923076 a6989586621679923073) t -> () #

SuppressUnusedWarnings ([a6989586621679923073] -> [b6989586621679923074] -> TyFun [c6989586621679923075] (TyFun [d6989586621679923076] [(a6989586621679923073, b6989586621679923074, c6989586621679923075, d6989586621679923076)] -> Type) -> *) (Zip4Sym2 c6989586621679923075 d6989586621679923076 b6989586621679923074 a6989586621679923073) # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym2 c6989586621679923075 d6989586621679923076 b6989586621679923074 a6989586621679923073) t -> () #

SuppressUnusedWarnings ([a6989586621679923073] -> [b6989586621679923074] -> [c6989586621679923075] -> TyFun [d6989586621679923076] [(a6989586621679923073, b6989586621679923074, c6989586621679923075, d6989586621679923076)] -> *) (Zip4Sym3 d6989586621679923076 c6989586621679923075 b6989586621679923074 a6989586621679923073) # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym3 d6989586621679923076 c6989586621679923075 b6989586621679923074 a6989586621679923073) 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 a6989586621679700118 (TyFun b6989586621679700119 (TyFun c6989586621679700120 d6989586621679700121 -> Type) -> Type) -> Type) (TyFun [a6989586621679700118] (TyFun [b6989586621679700119] (TyFun [c6989586621679700120] [d6989586621679700121] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym0 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679700109, b6989586621679700110, c6989586621679700111, d6989586621679700112)] ([a6989586621679700109], [b6989586621679700110], [c6989586621679700111], [d6989586621679700112]) -> *) (Unzip4Sym0 a6989586621679700109 b6989586621679700110 c6989586621679700111 d6989586621679700112) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip4Sym0 a6989586621679700109 b6989586621679700110 c6989586621679700111 d6989586621679700112) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679923073] (TyFun [b6989586621679923074] (TyFun [c6989586621679923075] (TyFun [d6989586621679923076] [(a6989586621679923073, b6989586621679923074, c6989586621679923075, d6989586621679923076)] -> Type) -> Type) -> Type) -> *) (Zip4Sym0 a6989586621679923073 b6989586621679923074 c6989586621679923075 d6989586621679923076) # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym0 a6989586621679923073 b6989586621679923074 c6989586621679923075 d6989586621679923076) 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 a6989586621679923050 (TyFun b6989586621679923051 (TyFun c6989586621679923052 (TyFun d6989586621679923053 e6989586621679923054 -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679923050] (TyFun [b6989586621679923051] (TyFun [c6989586621679923052] (TyFun [d6989586621679923053] [e6989586621679923054] -> Type) -> Type) -> Type) -> *) (ZipWith4Sym1 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym1 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923050 (TyFun b6989586621679923051 (TyFun c6989586621679923052 (TyFun d6989586621679923053 e6989586621679923054 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923050] -> TyFun [b6989586621679923051] (TyFun [c6989586621679923052] (TyFun [d6989586621679923053] [e6989586621679923054] -> Type) -> Type) -> *) (ZipWith4Sym2 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym2 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923050 (TyFun b6989586621679923051 (TyFun c6989586621679923052 (TyFun d6989586621679923053 e6989586621679923054 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923050] -> [b6989586621679923051] -> TyFun [c6989586621679923052] (TyFun [d6989586621679923053] [e6989586621679923054] -> Type) -> *) (ZipWith4Sym3 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym3 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923050 (TyFun b6989586621679923051 (TyFun c6989586621679923052 (TyFun d6989586621679923053 e6989586621679923054 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923050] -> [b6989586621679923051] -> [c6989586621679923052] -> TyFun [d6989586621679923053] [e6989586621679923054] -> *) (ZipWith4Sym4 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym4 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) t -> () #

SuppressUnusedWarnings ([a6989586621679923068] -> TyFun [b6989586621679923069] (TyFun [c6989586621679923070] (TyFun [d6989586621679923071] (TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> Type) -> Type) -> Type) -> *) (Zip5Sym1 b6989586621679923069 c6989586621679923070 d6989586621679923071 e6989586621679923072 a6989586621679923068) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym1 b6989586621679923069 c6989586621679923070 d6989586621679923071 e6989586621679923072 a6989586621679923068) t -> () #

SuppressUnusedWarnings ([a6989586621679923068] -> [b6989586621679923069] -> TyFun [c6989586621679923070] (TyFun [d6989586621679923071] (TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> Type) -> Type) -> *) (Zip5Sym2 c6989586621679923070 d6989586621679923071 e6989586621679923072 b6989586621679923069 a6989586621679923068) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym2 c6989586621679923070 d6989586621679923071 e6989586621679923072 b6989586621679923069 a6989586621679923068) t -> () #

SuppressUnusedWarnings ([a6989586621679923068] -> [b6989586621679923069] -> [c6989586621679923070] -> TyFun [d6989586621679923071] (TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> Type) -> *) (Zip5Sym3 d6989586621679923071 e6989586621679923072 c6989586621679923070 b6989586621679923069 a6989586621679923068) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym3 d6989586621679923071 e6989586621679923072 c6989586621679923070 b6989586621679923069 a6989586621679923068) t -> () #

SuppressUnusedWarnings ([a6989586621679923068] -> [b6989586621679923069] -> [c6989586621679923070] -> [d6989586621679923071] -> TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> *) (Zip5Sym4 e6989586621679923072 d6989586621679923071 c6989586621679923070 b6989586621679923069 a6989586621679923068) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym4 e6989586621679923072 d6989586621679923071 c6989586621679923070 b6989586621679923069 a6989586621679923068) 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 a6989586621679923050 (TyFun b6989586621679923051 (TyFun c6989586621679923052 (TyFun d6989586621679923053 e6989586621679923054 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679923050] (TyFun [b6989586621679923051] (TyFun [c6989586621679923052] (TyFun [d6989586621679923053] [e6989586621679923054] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith4Sym0 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym0 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679700104, b6989586621679700105, c6989586621679700106, d6989586621679700107, e6989586621679700108)] ([a6989586621679700104], [b6989586621679700105], [c6989586621679700106], [d6989586621679700107], [e6989586621679700108]) -> *) (Unzip5Sym0 a6989586621679700104 b6989586621679700105 c6989586621679700106 d6989586621679700107 e6989586621679700108) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip5Sym0 a6989586621679700104 b6989586621679700105 c6989586621679700106 d6989586621679700107 e6989586621679700108) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679923068] (TyFun [b6989586621679923069] (TyFun [c6989586621679923070] (TyFun [d6989586621679923071] (TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip5Sym0 a6989586621679923068 b6989586621679923069 c6989586621679923070 d6989586621679923071 e6989586621679923072) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym0 a6989586621679923068 b6989586621679923069 c6989586621679923070 d6989586621679923071 e6989586621679923072) 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 a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679923044] (TyFun [b6989586621679923045] (TyFun [c6989586621679923046] (TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym1 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym1 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923044] -> TyFun [b6989586621679923045] (TyFun [c6989586621679923046] (TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> Type) -> Type) -> *) (ZipWith5Sym2 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym2 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923044] -> [b6989586621679923045] -> TyFun [c6989586621679923046] (TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> Type) -> *) (ZipWith5Sym3 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym3 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923044] -> [b6989586621679923045] -> [c6989586621679923046] -> TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> *) (ZipWith5Sym4 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym4 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923044] -> [b6989586621679923045] -> [c6989586621679923046] -> [d6989586621679923047] -> TyFun [e6989586621679923048] [f6989586621679923049] -> *) (ZipWith5Sym5 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym5 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) t -> () #

SuppressUnusedWarnings ([a6989586621679923062] -> TyFun [b6989586621679923063] (TyFun [c6989586621679923064] (TyFun [d6989586621679923065] (TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym1 b6989586621679923063 c6989586621679923064 d6989586621679923065 e6989586621679923066 f6989586621679923067 a6989586621679923062) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym1 b6989586621679923063 c6989586621679923064 d6989586621679923065 e6989586621679923066 f6989586621679923067 a6989586621679923062) t -> () #

SuppressUnusedWarnings ([a6989586621679923062] -> [b6989586621679923063] -> TyFun [c6989586621679923064] (TyFun [d6989586621679923065] (TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> Type) -> Type) -> *) (Zip6Sym2 c6989586621679923064 d6989586621679923065 e6989586621679923066 f6989586621679923067 b6989586621679923063 a6989586621679923062) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym2 c6989586621679923064 d6989586621679923065 e6989586621679923066 f6989586621679923067 b6989586621679923063 a6989586621679923062) t -> () #

SuppressUnusedWarnings ([a6989586621679923062] -> [b6989586621679923063] -> [c6989586621679923064] -> TyFun [d6989586621679923065] (TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> Type) -> *) (Zip6Sym3 d6989586621679923065 e6989586621679923066 f6989586621679923067 c6989586621679923064 b6989586621679923063 a6989586621679923062) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym3 d6989586621679923065 e6989586621679923066 f6989586621679923067 c6989586621679923064 b6989586621679923063 a6989586621679923062) t -> () #

SuppressUnusedWarnings ([a6989586621679923062] -> [b6989586621679923063] -> [c6989586621679923064] -> [d6989586621679923065] -> TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> *) (Zip6Sym4 e6989586621679923066 f6989586621679923067 d6989586621679923065 c6989586621679923064 b6989586621679923063 a6989586621679923062) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym4 e6989586621679923066 f6989586621679923067 d6989586621679923065 c6989586621679923064 b6989586621679923063 a6989586621679923062) t -> () #

SuppressUnusedWarnings ([a6989586621679923062] -> [b6989586621679923063] -> [c6989586621679923064] -> [d6989586621679923065] -> [e6989586621679923066] -> TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> *) (Zip6Sym5 f6989586621679923067 e6989586621679923066 d6989586621679923065 c6989586621679923064 b6989586621679923063 a6989586621679923062) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym5 f6989586621679923067 e6989586621679923066 d6989586621679923065 c6989586621679923064 b6989586621679923063 a6989586621679923062) 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 a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679923044] (TyFun [b6989586621679923045] (TyFun [c6989586621679923046] (TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym0 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym0 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679700098, b6989586621679700099, c6989586621679700100, d6989586621679700101, e6989586621679700102, f6989586621679700103)] ([a6989586621679700098], [b6989586621679700099], [c6989586621679700100], [d6989586621679700101], [e6989586621679700102], [f6989586621679700103]) -> *) (Unzip6Sym0 a6989586621679700098 b6989586621679700099 c6989586621679700100 d6989586621679700101 e6989586621679700102 f6989586621679700103) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip6Sym0 a6989586621679700098 b6989586621679700099 c6989586621679700100 d6989586621679700101 e6989586621679700102 f6989586621679700103) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679923062] (TyFun [b6989586621679923063] (TyFun [c6989586621679923064] (TyFun [d6989586621679923065] (TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym0 a6989586621679923062 b6989586621679923063 c6989586621679923064 d6989586621679923065 e6989586621679923066 f6989586621679923067) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym0 a6989586621679923062 b6989586621679923063 c6989586621679923064 d6989586621679923065 e6989586621679923066 f6989586621679923067) 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 a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679923037] (TyFun [b6989586621679923038] (TyFun [c6989586621679923039] (TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym1 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym1 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923037] -> TyFun [b6989586621679923038] (TyFun [c6989586621679923039] (TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym2 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym2 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923037] -> [b6989586621679923038] -> TyFun [c6989586621679923039] (TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> Type) -> *) (ZipWith6Sym3 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym3 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923037] -> [b6989586621679923038] -> [c6989586621679923039] -> TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> *) (ZipWith6Sym4 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym4 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923037] -> [b6989586621679923038] -> [c6989586621679923039] -> [d6989586621679923040] -> TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> *) (ZipWith6Sym5 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym5 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923037] -> [b6989586621679923038] -> [c6989586621679923039] -> [d6989586621679923040] -> [e6989586621679923041] -> TyFun [f6989586621679923042] [g6989586621679923043] -> *) (ZipWith6Sym6 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym6 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) t -> () #

SuppressUnusedWarnings ([a6989586621679923055] -> TyFun [b6989586621679923056] (TyFun [c6989586621679923057] (TyFun [d6989586621679923058] (TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym1 b6989586621679923056 c6989586621679923057 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061 a6989586621679923055) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym1 b6989586621679923056 c6989586621679923057 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061 a6989586621679923055) t -> () #

SuppressUnusedWarnings ([a6989586621679923055] -> [b6989586621679923056] -> TyFun [c6989586621679923057] (TyFun [d6989586621679923058] (TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym2 c6989586621679923057 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061 b6989586621679923056 a6989586621679923055) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym2 c6989586621679923057 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061 b6989586621679923056 a6989586621679923055) t -> () #

SuppressUnusedWarnings ([a6989586621679923055] -> [b6989586621679923056] -> [c6989586621679923057] -> TyFun [d6989586621679923058] (TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> Type) -> *) (Zip7Sym3 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061 c6989586621679923057 b6989586621679923056 a6989586621679923055) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym3 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061 c6989586621679923057 b6989586621679923056 a6989586621679923055) t -> () #

SuppressUnusedWarnings ([a6989586621679923055] -> [b6989586621679923056] -> [c6989586621679923057] -> [d6989586621679923058] -> TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> *) (Zip7Sym4 e6989586621679923059 f6989586621679923060 g6989586621679923061 d6989586621679923058 c6989586621679923057 b6989586621679923056 a6989586621679923055) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym4 e6989586621679923059 f6989586621679923060 g6989586621679923061 d6989586621679923058 c6989586621679923057 b6989586621679923056 a6989586621679923055) t -> () #

SuppressUnusedWarnings ([a6989586621679923055] -> [b6989586621679923056] -> [c6989586621679923057] -> [d6989586621679923058] -> [e6989586621679923059] -> TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> *) (Zip7Sym5 f6989586621679923060 g6989586621679923061 e6989586621679923059 d6989586621679923058 c6989586621679923057 b6989586621679923056 a6989586621679923055) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym5 f6989586621679923060 g6989586621679923061 e6989586621679923059 d6989586621679923058 c6989586621679923057 b6989586621679923056 a6989586621679923055) t -> () #

SuppressUnusedWarnings ([a6989586621679923055] -> [b6989586621679923056] -> [c6989586621679923057] -> [d6989586621679923058] -> [e6989586621679923059] -> [f6989586621679923060] -> TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> *) (Zip7Sym6 g6989586621679923061 f6989586621679923060 e6989586621679923059 d6989586621679923058 c6989586621679923057 b6989586621679923056 a6989586621679923055) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym6 g6989586621679923061 f6989586621679923060 e6989586621679923059 d6989586621679923058 c6989586621679923057 b6989586621679923056 a6989586621679923055) 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 a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679923037] (TyFun [b6989586621679923038] (TyFun [c6989586621679923039] (TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym0 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym0 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679700091, b6989586621679700092, c6989586621679700093, d6989586621679700094, e6989586621679700095, f6989586621679700096, g6989586621679700097)] ([a6989586621679700091], [b6989586621679700092], [c6989586621679700093], [d6989586621679700094], [e6989586621679700095], [f6989586621679700096], [g6989586621679700097]) -> *) (Unzip7Sym0 a6989586621679700091 b6989586621679700092 c6989586621679700093 d6989586621679700094 e6989586621679700095 f6989586621679700096 g6989586621679700097) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip7Sym0 a6989586621679700091 b6989586621679700092 c6989586621679700093 d6989586621679700094 e6989586621679700095 f6989586621679700096 g6989586621679700097) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679923055] (TyFun [b6989586621679923056] (TyFun [c6989586621679923057] (TyFun [d6989586621679923058] (TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym0 a6989586621679923055 b6989586621679923056 c6989586621679923057 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym0 a6989586621679923055 b6989586621679923056 c6989586621679923057 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061) 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 a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679923029] (TyFun [b6989586621679923030] (TyFun [c6989586621679923031] (TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym1 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym1 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923029] -> TyFun [b6989586621679923030] (TyFun [c6989586621679923031] (TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym2 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym2 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923029] -> [b6989586621679923030] -> TyFun [c6989586621679923031] (TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym3 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym3 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923029] -> [b6989586621679923030] -> [c6989586621679923031] -> TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> *) (ZipWith7Sym4 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym4 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923029] -> [b6989586621679923030] -> [c6989586621679923031] -> [d6989586621679923032] -> TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> *) (ZipWith7Sym5 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym5 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923029] -> [b6989586621679923030] -> [c6989586621679923031] -> [d6989586621679923032] -> [e6989586621679923033] -> TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> *) (ZipWith7Sym6 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym6 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923029] -> [b6989586621679923030] -> [c6989586621679923031] -> [d6989586621679923032] -> [e6989586621679923033] -> [f6989586621679923034] -> TyFun [g6989586621679923035] [h6989586621679923036] -> *) (ZipWith7Sym7 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym7 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679923029] (TyFun [b6989586621679923030] (TyFun [c6989586621679923031] (TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym0 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym0 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) t -> () #