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

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

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

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

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

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

to generate singletons for Prelude types.

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

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

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

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

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

Generate defunctionalization symbols for existing type family

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

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

Functions to generate equality instances

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

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

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

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

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

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

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

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

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

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

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

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

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

Create instances of SDecide for each type in the list.

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

Create instance of SDecide for the given type.

Functions to generate Ord instances

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

Produce instances for POrd from the given types

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

Produce an instance for POrd from the given type

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

Create instances of SOrd for the given types

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

Create instance of SOrd for the given type

Functions to generate Bounded instances

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

Produce instances for PBounded from the given types

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

Produce an instance for PBounded from the given type

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

Create instances of SBounded for the given types

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

Create instance of SBounded for the given type

Functions to generate Enum instances

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

Produce instances for PEnum from the given types

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

Produce an instance for PEnum from the given type

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

Create instances of SEnum for the given types

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

Create instance of SEnum for the given type

Utility functions

cases Source #

Arguments

:: DsMonad q 
=> Name

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

-> q Exp

The scrutinee, in a Template Haskell quote

-> q Exp

The body, in a Template Haskell quote

-> q Exp 

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

sCases Source #

Arguments

:: DsMonad q 
=> Name

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

-> q Exp

The scrutinee, in a Template Haskell quote

-> q Exp

The body, in a Template Haskell quote

-> q Exp 

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

Basic singleton definitions

data family Sing (a :: k) Source #

The singleton kind-indexed data family.

Instances

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

Auxiliary definitions

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

class kproxy ~ Proxy => PEq kproxy Source #

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

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

Instances

PEq Bool (Proxy * Bool) Source # 

Associated Types

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

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

PEq Ordering (Proxy * Ordering) Source # 

Associated Types

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

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

PEq () (Proxy * ()) Source # 

Associated Types

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

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

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

Associated Types

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

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

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

Associated Types

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

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

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

Associated Types

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

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

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

Associated Types

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

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

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

Associated Types

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

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

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

Associated Types

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

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

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

Associated Types

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

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

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

Associated Types

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

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

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

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

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

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

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

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

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

Conditional over singletons

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

Equations

False :&& _z_1627658356 = FalseSym0 
True :&& x = x 

class SEq k where Source #

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

Minimal complete definition

(%:==)

Methods

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

Boolean equality on singletons

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

Boolean disequality on singletons

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

Boolean disequality on singletons

Instances

SEq Bool Source # 

Methods

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

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

SEq Ordering Source # 
SEq () Source # 

Methods

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

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

SEq a0 => SEq [a0] Source # 

Methods

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

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

SEq a0 => SEq (Maybe a0) Source # 

Methods

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

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

SEq a0 => SEq (NonEmpty a0) Source # 

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

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

(%:/=) :: 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) Source #

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

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

(%:/=) :: 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) Source #

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

Associated Types

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

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

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

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

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

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

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

Instances

POrd Bool (Proxy * Bool) Source # 

Associated Types

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

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

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

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

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

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

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

POrd Ordering (Proxy * Ordering) Source # 

Associated Types

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

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

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

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

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

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

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

POrd () (Proxy * ()) Source # 

Associated Types

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

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

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

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

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

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

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

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

Associated Types

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

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

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

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

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

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

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

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

Associated Types

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

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

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

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

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

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

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

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

Associated Types

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

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

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

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

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

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

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

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

Associated Types

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

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

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

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

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

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

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

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

Associated Types

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

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

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

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

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

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

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

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

Associated Types

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

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

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

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

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

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

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

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

Associated Types

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

class SEq a => SOrd a where Source #

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Instances

SOrd Bool Source # 
SOrd Ordering Source # 
SOrd () Source # 

Methods

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

SOrd a0 => SOrd (Maybe a0) Source # 

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

(%:<) :: 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) Source #

(%:<=) :: 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) Source #

(%:>) :: 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) Source #

(%:>=) :: 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) Source #

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

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

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

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

(%:<) :: 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) Source #

(%:<=) :: 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) Source #

(%:>) :: 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) Source #

(%:>=) :: 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) Source #

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

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

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

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

(%:<) :: 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) Source #

(%:<=) :: 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) Source #

(%:>) :: 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) Source #

(%:>=) :: 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) Source #

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

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

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

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

(%:<) :: 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) Source #

(%:<=) :: 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) Source #

(%:>) :: 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) Source #

(%:>=) :: 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) Source #

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

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

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

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

(%:<) :: 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) Source #

(%:<=) :: 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) Source #

(%:>) :: 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) Source #

(%:>=) :: 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) Source #

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

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

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

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

(%:<) :: 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) Source #

(%:<=) :: 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) Source #

(%:>) :: 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) Source #

(%:>=) :: 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) Source #

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

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

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

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

(%:<) :: 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) Source #

(%:<=) :: 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) Source #

(%:>) :: 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) Source #

(%:>=) :: 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) Source #

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

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

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

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

(%:<) :: 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) Source #

(%:<=) :: 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) Source #

(%:>) :: 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) Source #

(%:>=) :: 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) Source #

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

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

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

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

(%:<) :: 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) Source #

(%:<=) :: 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) Source #

(%:>) :: 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) Source #

(%:>=) :: 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) Source #

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

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

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

Equations

ThenCmp EQ x = x 
ThenCmp LT _z_1627690200 = LTSym0 
ThenCmp GT _z_1627690203 = GTSym0 

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

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

Equations

Foldl f z0 xs0 = Apply (Apply (Let1627619941LgoSym3 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) Source #

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

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

Minimal complete definition

(%~)

Methods

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

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

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

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

data Decision a Source #

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

Constructors

Proved a

Witness for a

Disproved (Refuted a)

Proof that no a exists

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

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

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

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

Constructors

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

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

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

data ErrorSym0 l Source #

Instances

SuppressUnusedWarnings (TyFun k01627810588 k1627810590 -> *) (ErrorSym0 k01627810588 k1627810590) Source # 

Methods

suppressUnusedWarnings :: Proxy (ErrorSym0 k01627810588 k1627810590) t -> () Source #

type Apply k01627810588 k2 (ErrorSym0 k01627810588 k2) l0 Source # 
type Apply k01627810588 k2 (ErrorSym0 k01627810588 k2) l0 = ErrorSym1 k01627810588 k2 l0

type LTSym0 = LT Source #

type EQSym0 = EQ Source #

type GTSym0 = GT Source #

type Tuple0Sym0 = '() Source #

data Tuple2Sym0 l Source #

Instances

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

Methods

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

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

data Tuple2Sym1 l l Source #

Instances

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

Methods

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

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

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

data Tuple3Sym0 l Source #

Instances

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

Methods

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

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

data Tuple3Sym1 l l Source #

Instances

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

Methods

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

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

data Tuple3Sym2 l l l Source #

Instances

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

Methods

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

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

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

data Tuple4Sym0 l Source #

Instances

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

Methods

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

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

data Tuple4Sym1 l l Source #

Instances

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

Methods

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

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

data Tuple4Sym2 l l l Source #

Instances

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

Methods

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

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

data Tuple4Sym3 l l l l Source #

Instances

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

Methods

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

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

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

data Tuple5Sym0 l Source #

Instances

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

Methods

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

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

data Tuple5Sym1 l l Source #

Instances

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

Methods

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

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

data Tuple5Sym2 l l l Source #

Instances

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

Methods

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

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

data Tuple5Sym3 l l l l Source #

Instances

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

Methods

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

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

data Tuple5Sym4 l l l l l Source #

Instances

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

Methods

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

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

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

data Tuple6Sym0 l Source #

Instances

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

Methods

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

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

data Tuple6Sym1 l l Source #

Instances

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

Methods

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

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

data Tuple6Sym2 l l l Source #

Instances

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

Methods

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

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

data Tuple6Sym3 l l l l Source #

Instances

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

Methods

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

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

data Tuple6Sym4 l l l l l Source #

Instances

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

Methods

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

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

data Tuple6Sym5 l l l l l l Source #

Instances

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

Methods

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

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

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

data Tuple7Sym0 l Source #

Instances

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

Methods

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

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

data Tuple7Sym1 l l Source #

Instances

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

Methods

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

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

data Tuple7Sym2 l l l Source #

Instances

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

Methods

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

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

data Tuple7Sym3 l l l l Source #

Instances

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

Methods

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

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

data Tuple7Sym4 l l l l l Source #

Instances

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

Methods

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

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

data Tuple7Sym5 l l l l l l Source #

Instances

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

Methods

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

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

data Tuple7Sym6 l l l l l l l Source #

Instances

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

Methods

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

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

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

data CompareSym0 l Source #

Instances

SuppressUnusedWarnings (TyFun a1627682221 (TyFun a1627682221 Ordering -> Type) -> *) (CompareSym0 a1627682221) Source # 

Methods

suppressUnusedWarnings :: Proxy (CompareSym0 a1627682221) t -> () Source #

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

data FoldlSym0 l Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun b1627619913 (TyFun a1627619912 b1627619913 -> Type) -> Type) (TyFun b1627619913 (TyFun [a1627619912] b1627619913 -> Type) -> Type) -> *) (FoldlSym0 a1627619912 b1627619913) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym0 a1627619912 b1627619913) t -> () Source #

type Apply (TyFun b1627619913 (TyFun a1627619912 b1627619913 -> Type) -> Type) (TyFun b1627619913 (TyFun [a1627619912] b1627619913 -> Type) -> Type) (FoldlSym0 a1627619912 b1627619913) l0 Source # 
type Apply (TyFun b1627619913 (TyFun a1627619912 b1627619913 -> Type) -> Type) (TyFun b1627619913 (TyFun [a1627619912] b1627619913 -> Type) -> Type) (FoldlSym0 a1627619912 b1627619913) l0 = FoldlSym1 a1627619912 b1627619913 l0

class SuppressUnusedWarnings t where Source #

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

Minimal complete definition

suppressUnusedWarnings

Instances

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

Methods

suppressUnusedWarnings :: Proxy (UntilSym1 a1627845465) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627845465 Bool -> Type) -> (TyFun a1627845465 a1627845465 -> Type) -> TyFun a1627845465 a1627845465 -> *) (UntilSym2 a1627845465) Source # 

Methods

suppressUnusedWarnings :: Proxy (UntilSym2 a1627845465) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627942712 Bool -> Type) -> TyFun [a1627942712] Bool -> *) (Any_Sym1 a1627942712) Source # 

Methods

suppressUnusedWarnings :: Proxy (Any_Sym1 a1627942712) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DropWhileEndSym1 a1627953310) t -> () Source #

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy (MinimumBySym1 a1627953321) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (MaximumBySym1 a1627953322) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Foldl1Sym1 a1627953395) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Foldr1Sym1 a1627953393) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (AllSym1 a1627953389) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Scanl1Sym1 a1627953386) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Scanr1Sym1 a1627953383) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (FindIndexSym1 a1627953316) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (FindIndicesSym1 a1627953315) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (UnionBySym1 a1627953285) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (UnionBySym2 a1627953285) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DeleteFirstsBySym1 a1627953325) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DeleteFirstsBySym2 a1627953325) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DeleteBySym1 a1627953326) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DeleteBySym2 a1627953326) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (SortBySym1 a1627953324) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (InsertBySym1 a1627953323) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (InsertBySym2 a1627953323) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (IntersectBySym1 a1627953313) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (IntersectBySym2 a1627953313) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (FindSym1 a1627953319) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (FilterSym1 a1627953320) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (TakeWhileSym1 a1627953312) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DropWhileSym1 a1627953311) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (GroupBySym1 a1627953299) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (SpanSym1 a1627953309) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (BreakSym1 a1627953308) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (PartitionSym1 a1627953296) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (NubBySym1 a1627953287) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy ((:++$$) a1627796654) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (IsSuffixOfSym1 a1627953371) t -> () Source #

SuppressUnusedWarnings ([a1627953402] -> TyFun [[a1627953402]] [a1627953402] -> *) (IntercalateSym1 a1627953402) Source # 

Methods

suppressUnusedWarnings :: Proxy (IntercalateSym1 a1627953402) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (IsInfixOfSym1 a1627953370) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (IsPrefixOfSym1 a1627953372) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy ((:\\$$) a1627953327) t -> () Source #

SuppressUnusedWarnings ([a1627953284] -> TyFun [a1627953284] [a1627953284] -> *) (UnionSym1 a1627953284) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnionSym1 a1627953284) t -> () Source #

SuppressUnusedWarnings ([a1627953314] -> TyFun [a1627953314] [a1627953314] -> *) (IntersectSym1 a1627953314) Source # 

Methods

suppressUnusedWarnings :: Proxy (IntersectSym1 a1627953314) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy ((:!!$$) a1627953289) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (StripPrefixSym1 a1628251687) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym1 a1627953305) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (TakeSym1 a1627953307) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DropSym1 a1627953306) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (ReplicateSym1 a1627953291) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy ((:$$) a822083586) t -> () Source #

SuppressUnusedWarnings (a1627657621 -> TyFun a1627657621 (TyFun Bool a1627657621 -> Type) -> *) (Bool_Sym1 a1627657621) Source # 

Methods

suppressUnusedWarnings :: Proxy (Bool_Sym1 a1627657621) t -> () Source #

SuppressUnusedWarnings (a1627657621 -> a1627657621 -> TyFun Bool a1627657621 -> *) (Bool_Sym2 a1627657621) Source # 

Methods

suppressUnusedWarnings :: Proxy (Bool_Sym2 a1627657621) t -> () Source #

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy ((:==$$) a1627662065) t -> () Source #

SuppressUnusedWarnings (a1627682221 -> TyFun a1627682221 a1627682221 -> *) (MinSym1 a1627682221) Source # 

Methods

suppressUnusedWarnings :: Proxy (MinSym1 a1627682221) t -> () Source #

SuppressUnusedWarnings (a1627682221 -> TyFun a1627682221 a1627682221 -> *) (MaxSym1 a1627682221) Source # 

Methods

suppressUnusedWarnings :: Proxy (MaxSym1 a1627682221) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy ((:>=$$) a1627682221) t -> () Source #

SuppressUnusedWarnings (a1627682221 -> TyFun a1627682221 Bool -> *) ((:>$$) a1627682221) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:>$$) a1627682221) t -> () Source #

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy ((:<$$) a1627682221) t -> () Source #

SuppressUnusedWarnings (a1627682221 -> TyFun a1627682221 Ordering -> *) (CompareSym1 a1627682221) Source # 

Methods

suppressUnusedWarnings :: Proxy (CompareSym1 a1627682221) t -> () Source #

SuppressUnusedWarnings (a1627796644 -> TyFun a1627796644 a1627796644 -> *) (AsTypeOfSym1 a1627796644) Source # 

Methods

suppressUnusedWarnings :: Proxy (AsTypeOfSym1 a1627796644) t -> () Source #

SuppressUnusedWarnings (a1627817219 -> TyFun a1627817219 a1627817219 -> *) ((:*$$) a1627817219) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:*$$) a1627817219) t -> () Source #

SuppressUnusedWarnings (a1627817219 -> TyFun a1627817219 a1627817219 -> *) ((:-$$) a1627817219) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:-$$) a1627817219) t -> () Source #

SuppressUnusedWarnings (a1627817219 -> TyFun a1627817219 a1627817219 -> *) ((:+$$) a1627817219) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:+$$) a1627817219) t -> () Source #

SuppressUnusedWarnings (a1627819601 -> TyFun a1627819601 a1627819601 -> *) (SubtractSym1 a1627819601) Source # 

Methods

suppressUnusedWarnings :: Proxy (SubtractSym1 a1627819601) t -> () Source #

SuppressUnusedWarnings (a1627849033 -> TyFun (Maybe a1627849033) a1627849033 -> *) (FromMaybeSym1 a1627849033) Source # 

Methods

suppressUnusedWarnings :: Proxy (FromMaybeSym1 a1627849033) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (EnumFromThenToSym1 a1627864213) t -> () Source #

SuppressUnusedWarnings (a1627864213 -> a1627864213 -> TyFun a1627864213 [a1627864213] -> *) (EnumFromThenToSym2 a1627864213) Source # 

Methods

suppressUnusedWarnings :: Proxy (EnumFromThenToSym2 a1627864213) t -> () Source #

SuppressUnusedWarnings (a1627864213 -> TyFun a1627864213 [a1627864213] -> *) (EnumFromToSym1 a1627864213) Source # 

Methods

suppressUnusedWarnings :: Proxy (EnumFromToSym1 a1627864213) t -> () Source #

SuppressUnusedWarnings (a1627953403 -> TyFun [a1627953403] [a1627953403] -> *) (IntersperseSym1 a1627953403) Source # 

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym1 a1627953403) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (ElemSym1 a1627953369) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (NotElemSym1 a1627953368) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (ElemIndexSym1 a1627953318) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (ElemIndicesSym1 a1627953317) t -> () Source #

SuppressUnusedWarnings (a1627953328 -> TyFun [a1627953328] [a1627953328] -> *) (DeleteSym1 a1627953328) Source # 

Methods

suppressUnusedWarnings :: Proxy (DeleteSym1 a1627953328) t -> () Source #

SuppressUnusedWarnings (a1627953301 -> TyFun [a1627953301] [a1627953301] -> *) (InsertSym1 a1627953301) Source # 

Methods

suppressUnusedWarnings :: Proxy (InsertSym1 a1627953301) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a1627845465 Bool -> Type) (TyFun (TyFun a1627845465 a1627845465 -> Type) (TyFun a1627845465 a1627845465 -> Type) -> Type) -> *) (UntilSym0 a1627845465) Source # 

Methods

suppressUnusedWarnings :: Proxy (UntilSym0 a1627845465) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Any_Sym0 a1627942712) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DropWhileEndSym0 a1627953310) t -> () Source #

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy (MinimumBySym0 a1627953321) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (MaximumBySym0 a1627953322) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Foldl1Sym0 a1627953395) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Foldr1Sym0 a1627953393) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (AllSym0 a1627953389) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Scanl1Sym0 a1627953386) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Scanr1Sym0 a1627953383) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (FindIndexSym0 a1627953316) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (FindIndicesSym0 a1627953315) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (UnionBySym0 a1627953285) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DeleteFirstsBySym0 a1627953325) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DeleteBySym0 a1627953326) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (SortBySym0 a1627953324) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (InsertBySym0 a1627953323) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (IntersectBySym0 a1627953313) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (FindSym0 a1627953319) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (FilterSym0 a1627953320) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (TakeWhileSym0 a1627953312) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DropWhileSym0 a1627953311) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (GroupBySym0 a1627953299) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (SpanSym0 a1627953309) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (BreakSym0 a1627953308) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (PartitionSym0 a1627953296) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (NubBySym0 a1627953287) t -> () Source #

SuppressUnusedWarnings (TyFun [[a1627953290]] [[a1627953290]] -> *) (TransposeSym0 a1627953290) Source # 

Methods

suppressUnusedWarnings :: Proxy (TransposeSym0 a1627953290) t -> () Source #

SuppressUnusedWarnings (TyFun [[a1627953392]] [a1627953392] -> *) (ConcatSym0 a1627953392) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConcatSym0 a1627953392) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (CatMaybesSym0 a1627849030) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy ((:++$) a1627796654) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (ListToMaybeSym0 a1627849031) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953409] a1627953409 -> *) (HeadSym0 a1627953409) Source # 

Methods

suppressUnusedWarnings :: Proxy (HeadSym0 a1627953409) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953408] a1627953408 -> *) (LastSym0 a1627953408) Source # 

Methods

suppressUnusedWarnings :: Proxy (LastSym0 a1627953408) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953407] [a1627953407] -> *) (TailSym0 a1627953407) Source # 

Methods

suppressUnusedWarnings :: Proxy (TailSym0 a1627953407) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953406] [a1627953406] -> *) (InitSym0 a1627953406) Source # 

Methods

suppressUnusedWarnings :: Proxy (InitSym0 a1627953406) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (NullSym0 a1627953405) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (IsSuffixOfSym0 a1627953371) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953404] [a1627953404] -> *) (ReverseSym0 a1627953404) Source # 

Methods

suppressUnusedWarnings :: Proxy (ReverseSym0 a1627953404) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (IntercalateSym0 a1627953402) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953401] [[a1627953401]] -> *) (SubsequencesSym0 a1627953401) Source # 

Methods

suppressUnusedWarnings :: Proxy (SubsequencesSym0 a1627953401) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953398] [[a1627953398]] -> *) (PermutationsSym0 a1627953398) Source # 

Methods

suppressUnusedWarnings :: Proxy (PermutationsSym0 a1627953398) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953302] a1627953302 -> *) (MinimumSym0 a1627953302) Source # 

Methods

suppressUnusedWarnings :: Proxy (MinimumSym0 a1627953302) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953303] a1627953303 -> *) (MaximumSym0 a1627953303) Source # 

Methods

suppressUnusedWarnings :: Proxy (MaximumSym0 a1627953303) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953374] [[a1627953374]] -> *) (InitsSym0 a1627953374) Source # 

Methods

suppressUnusedWarnings :: Proxy (InitsSym0 a1627953374) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (IsInfixOfSym0 a1627953370) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953373] [[a1627953373]] -> *) (TailsSym0 a1627953373) Source # 

Methods

suppressUnusedWarnings :: Proxy (TailsSym0 a1627953373) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (IsPrefixOfSym0 a1627953372) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953288] [a1627953288] -> *) (NubSym0 a1627953288) Source # 

Methods

suppressUnusedWarnings :: Proxy (NubSym0 a1627953288) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy ((:\\$) a1627953327) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (UnionSym0 a1627953284) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953300] [a1627953300] -> *) (SortSym0 a1627953300) Source # 

Methods

suppressUnusedWarnings :: Proxy (SortSym0 a1627953300) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (IntersectSym0 a1627953314) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953304] [[a1627953304]] -> *) (GroupSym0 a1627953304) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupSym0 a1627953304) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953294] a1627953294 -> *) (SumSym0 a1627953294) Source # 

Methods

suppressUnusedWarnings :: Proxy (SumSym0 a1627953294) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953293] a1627953293 -> *) (ProductSym0 a1627953293) Source # 

Methods

suppressUnusedWarnings :: Proxy (ProductSym0 a1627953293) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (LengthSym0 a1627953292) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy ((:!!$) a1627953289) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (StripPrefixSym0 a1628251687) t -> () Source #

SuppressUnusedWarnings (TyFun (Maybe a1627849036) Bool -> *) (IsJustSym0 a1627849036) Source # 

Methods

suppressUnusedWarnings :: Proxy (IsJustSym0 a1627849036) t -> () Source #

SuppressUnusedWarnings (TyFun (Maybe a1627849035) Bool -> *) (IsNothingSym0 a1627849035) Source # 

Methods

suppressUnusedWarnings :: Proxy (IsNothingSym0 a1627849035) t -> () Source #

SuppressUnusedWarnings (TyFun (Maybe a1627849034) a1627849034 -> *) (FromJustSym0 a1627849034) Source # 

Methods

suppressUnusedWarnings :: Proxy (FromJustSym0 a1627849034) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (MaybeToListSym0 a1627849032) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym0 a1627953305) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (TakeSym0 a1627953307) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DropSym0 a1627953306) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (ReplicateSym0 a1627953291) t -> () Source #

SuppressUnusedWarnings (TyFun Nat a1627817219 -> *) (FromIntegerSym0 a1627817219) Source # 

Methods

suppressUnusedWarnings :: Proxy (FromIntegerSym0 a1627817219) t -> () Source #

SuppressUnusedWarnings (TyFun Nat a1627864213 -> *) (ToEnumSym0 a1627864213) Source # 

Methods

suppressUnusedWarnings :: Proxy (ToEnumSym0 a1627864213) t -> () Source #

SuppressUnusedWarnings (TyFun a822083586 (TyFun [a822083586] [a822083586] -> Type) -> *) ((:$) a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:$) a822083586) t -> () Source #

SuppressUnusedWarnings (TyFun a822083586 (Maybe a822083586) -> *) (JustSym0 a822083586) Source # 

Methods

suppressUnusedWarnings :: Proxy (JustSym0 a822083586) t -> () Source #

SuppressUnusedWarnings (TyFun a1627657621 (TyFun a1627657621 (TyFun Bool a1627657621 -> Type) -> Type) -> *) (Bool_Sym0 a1627657621) Source # 

Methods

suppressUnusedWarnings :: Proxy (Bool_Sym0 a1627657621) t -> () Source #

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy ((:==$) a1627662065) t -> () Source #

SuppressUnusedWarnings (TyFun a1627682221 (TyFun a1627682221 a1627682221 -> Type) -> *) (MinSym0 a1627682221) Source # 

Methods

suppressUnusedWarnings :: Proxy (MinSym0 a1627682221) t -> () Source #

SuppressUnusedWarnings (TyFun a1627682221 (TyFun a1627682221 a1627682221 -> Type) -> *) (MaxSym0 a1627682221) Source # 

Methods

suppressUnusedWarnings :: Proxy (MaxSym0 a1627682221) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy ((:>=$) a1627682221) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy ((:>$) a1627682221) t -> () Source #

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy ((:<$) a1627682221) t -> () Source #

SuppressUnusedWarnings (TyFun a1627682221 (TyFun a1627682221 Ordering -> Type) -> *) (CompareSym0 a1627682221) Source # 

Methods

suppressUnusedWarnings :: Proxy (CompareSym0 a1627682221) t -> () Source #

SuppressUnusedWarnings (TyFun a1627796653 a1627796653 -> *) (IdSym0 a1627796653) Source # 

Methods

suppressUnusedWarnings :: Proxy (IdSym0 a1627796653) t -> () Source #

SuppressUnusedWarnings (TyFun a1627796644 (TyFun a1627796644 a1627796644 -> Type) -> *) (AsTypeOfSym0 a1627796644) Source # 

Methods

suppressUnusedWarnings :: Proxy (AsTypeOfSym0 a1627796644) t -> () Source #

SuppressUnusedWarnings (TyFun a1627817219 a1627817219 -> *) (SignumSym0 a1627817219) Source # 

Methods

suppressUnusedWarnings :: Proxy (SignumSym0 a1627817219) t -> () Source #

SuppressUnusedWarnings (TyFun a1627817219 a1627817219 -> *) (AbsSym0 a1627817219) Source # 

Methods

suppressUnusedWarnings :: Proxy (AbsSym0 a1627817219) t -> () Source #

SuppressUnusedWarnings (TyFun a1627817219 a1627817219 -> *) (NegateSym0 a1627817219) Source # 

Methods

suppressUnusedWarnings :: Proxy (NegateSym0 a1627817219) t -> () Source #

SuppressUnusedWarnings (TyFun a1627817219 (TyFun a1627817219 a1627817219 -> Type) -> *) ((:*$) a1627817219) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:*$) a1627817219) t -> () Source #

SuppressUnusedWarnings (TyFun a1627817219 (TyFun a1627817219 a1627817219 -> Type) -> *) ((:-$) a1627817219) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:-$) a1627817219) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy ((:+$) a1627817219) t -> () Source #

SuppressUnusedWarnings (TyFun a1627819601 (TyFun a1627819601 a1627819601 -> Type) -> *) (SubtractSym0 a1627819601) Source # 

Methods

suppressUnusedWarnings :: Proxy (SubtractSym0 a1627819601) t -> () Source #

SuppressUnusedWarnings (TyFun a1627849033 (TyFun (Maybe a1627849033) a1627849033 -> Type) -> *) (FromMaybeSym0 a1627849033) Source # 

Methods

suppressUnusedWarnings :: Proxy (FromMaybeSym0 a1627849033) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (EnumFromThenToSym0 a1627864213) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (EnumFromToSym0 a1627864213) t -> () Source #

SuppressUnusedWarnings (TyFun a1627864213 Nat -> *) (FromEnumSym0 a1627864213) Source # 

Methods

suppressUnusedWarnings :: Proxy (FromEnumSym0 a1627864213) t -> () Source #

SuppressUnusedWarnings (TyFun a1627864213 a1627864213 -> *) (PredSym0 a1627864213) Source # 

Methods

suppressUnusedWarnings :: Proxy (PredSym0 a1627864213) t -> () Source #

SuppressUnusedWarnings (TyFun a1627864213 a1627864213 -> *) (SuccSym0 a1627864213) Source # 

Methods

suppressUnusedWarnings :: Proxy (SuccSym0 a1627864213) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym0 a1627953403) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (ElemSym0 a1627953369) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (NotElemSym0 a1627953368) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (ElemIndexSym0 a1627953318) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (ElemIndicesSym0 a1627953317) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DeleteSym0 a1627953328) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (InsertSym0 a1627953301) t -> () Source #

SuppressUnusedWarnings ((TyFun b1627619913 (TyFun a1627619912 b1627619913 -> Type) -> Type) -> TyFun b1627619913 (TyFun [a1627619912] b1627619913 -> Type) -> *) (FoldlSym1 a1627619912 b1627619913) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym1 a1627619912 b1627619913) t -> () Source #

SuppressUnusedWarnings ((TyFun b1627619913 (TyFun a1627619912 b1627619913 -> Type) -> Type) -> b1627619913 -> TyFun [a1627619912] b1627619913 -> *) (FoldlSym2 a1627619912 b1627619913) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym2 a1627619912 b1627619913) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627796657 (TyFun b1627796658 b1627796658 -> Type) -> Type) -> TyFun b1627796658 (TyFun [a1627796657] b1627796658 -> Type) -> *) (FoldrSym1 a1627796657 b1627796658) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym1 a1627796657 b1627796658) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627796657 (TyFun b1627796658 b1627796658 -> Type) -> Type) -> b1627796658 -> TyFun [a1627796657] b1627796658 -> *) (FoldrSym2 a1627796657 b1627796658) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym2 a1627796657 b1627796658) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627796655 b1627796656 -> Type) -> TyFun [a1627796655] [b1627796656] -> *) (MapSym1 a1627796655 b1627796656) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a1627796655 b1627796656) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627849028 (Maybe b1627849029) -> Type) -> TyFun [a1627849028] [b1627849029] -> *) (MapMaybeSym1 a1627849028 b1627849029) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapMaybeSym1 a1627849028 b1627849029) t -> () Source #

SuppressUnusedWarnings ((TyFun b1627953397 (TyFun a1627953396 b1627953397 -> Type) -> Type) -> TyFun b1627953397 (TyFun [a1627953396] b1627953397 -> Type) -> *) (Foldl'Sym1 a1627953396 b1627953397) Source # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym1 a1627953396 b1627953397) t -> () Source #

SuppressUnusedWarnings ((TyFun b1627953397 (TyFun a1627953396 b1627953397 -> Type) -> Type) -> b1627953397 -> TyFun [a1627953396] b1627953397 -> *) (Foldl'Sym2 a1627953396 b1627953397) Source # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym2 a1627953396 b1627953397) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627953390 [b1627953391] -> Type) -> TyFun [a1627953390] [b1627953391] -> *) (ConcatMapSym1 a1627953390 b1627953391) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym1 a1627953390 b1627953391) t -> () Source #

SuppressUnusedWarnings ((TyFun b1627953387 (TyFun a1627953388 b1627953387 -> Type) -> Type) -> TyFun b1627953387 (TyFun [a1627953388] [b1627953387] -> Type) -> *) (ScanlSym1 a1627953388 b1627953387) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a1627953388 b1627953387) t -> () Source #

SuppressUnusedWarnings ((TyFun b1627953387 (TyFun a1627953388 b1627953387 -> Type) -> Type) -> b1627953387 -> TyFun [a1627953388] [b1627953387] -> *) (ScanlSym2 a1627953388 b1627953387) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a1627953388 b1627953387) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627953384 (TyFun b1627953385 b1627953385 -> Type) -> Type) -> TyFun b1627953385 (TyFun [a1627953384] [b1627953385] -> Type) -> *) (ScanrSym1 a1627953384 b1627953385) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a1627953384 b1627953385) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627953384 (TyFun b1627953385 b1627953385 -> Type) -> Type) -> b1627953385 -> TyFun [a1627953384] [b1627953385] -> *) (ScanrSym2 a1627953384 b1627953385) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a1627953384 b1627953385) t -> () Source #

SuppressUnusedWarnings ((TyFun b1627953375 (Maybe (a1627953376, b1627953375)) -> Type) -> TyFun b1627953375 [a1627953376] -> *) (UnfoldrSym1 a1627953376 b1627953375) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 a1627953376 b1627953375) t -> () Source #

SuppressUnusedWarnings ([a1627953366] -> TyFun [b1627953367] [(a1627953366, b1627953367)] -> *) (ZipSym1 b1627953367 a1627953366) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 b1627953367 a1627953366) t -> () Source #

SuppressUnusedWarnings ([a1628251632] -> TyFun i1628251631 a1628251632 -> *) (GenericIndexSym1 i1628251631 a1628251632) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym1 i1628251631 a1628251632) t -> () Source #

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

Methods

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

SuppressUnusedWarnings (a1627796651 -> TyFun b1627796652 a1627796651 -> *) (ConstSym1 b1627796652 a1627796651) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConstSym1 b1627796652 a1627796651) t -> () Source #

SuppressUnusedWarnings (a1627796642 -> TyFun b1627796643 b1627796643 -> *) (SeqSym1 b1627796643 a1627796642) Source # 

Methods

suppressUnusedWarnings :: Proxy (SeqSym1 b1627796643 a1627796642) t -> () Source #

SuppressUnusedWarnings (b1627847771 -> TyFun (TyFun a1627847772 b1627847771 -> Type) (TyFun (Maybe a1627847772) b1627847771 -> Type) -> *) (Maybe_Sym1 a1627847772 b1627847771) Source # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym1 a1627847772 b1627847771) t -> () Source #

SuppressUnusedWarnings (b1627847771 -> (TyFun a1627847772 b1627847771 -> Type) -> TyFun (Maybe a1627847772) b1627847771 -> *) (Maybe_Sym2 a1627847772 b1627847771) Source # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym2 a1627847772 b1627847771) t -> () Source #

SuppressUnusedWarnings (a1627953297 -> TyFun [(a1627953297, b1627953298)] (Maybe b1627953298) -> *) (LookupSym1 b1627953298 a1627953297) Source # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym1 b1627953298 a1627953297) t -> () Source #

SuppressUnusedWarnings (i1628251637 -> TyFun [a1628251638] [a1628251638] -> *) (GenericTakeSym1 a1628251638 i1628251637) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym1 a1628251638 i1628251637) t -> () Source #

SuppressUnusedWarnings (i1628251635 -> TyFun [a1628251636] [a1628251636] -> *) (GenericDropSym1 a1628251636 i1628251635) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym1 a1628251636 i1628251635) t -> () Source #

SuppressUnusedWarnings (i1628251633 -> TyFun [a1628251634] ([a1628251634], [a1628251634]) -> *) (GenericSplitAtSym1 a1628251634 i1628251633) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym1 a1628251634 i1628251633) t -> () Source #

SuppressUnusedWarnings (i1628251629 -> TyFun a1628251630 [a1628251630] -> *) (GenericReplicateSym1 a1628251630 i1628251629) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym1 a1628251630 i1628251629) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun b1627619913 (TyFun a1627619912 b1627619913 -> Type) -> Type) (TyFun b1627619913 (TyFun [a1627619912] b1627619913 -> Type) -> Type) -> *) (FoldlSym0 a1627619912 b1627619913) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym0 a1627619912 b1627619913) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a1627796657 (TyFun b1627796658 b1627796658 -> Type) -> Type) (TyFun b1627796658 (TyFun [a1627796657] b1627796658 -> Type) -> Type) -> *) (FoldrSym0 a1627796657 b1627796658) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym0 a1627796657 b1627796658) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a1627796655 b1627796656 -> Type) (TyFun [a1627796655] [b1627796656] -> Type) -> *) (MapSym0 a1627796655 b1627796656) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a1627796655 b1627796656) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a1627849028 (Maybe b1627849029) -> Type) (TyFun [a1627849028] [b1627849029] -> Type) -> *) (MapMaybeSym0 a1627849028 b1627849029) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapMaybeSym0 a1627849028 b1627849029) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun b1627953397 (TyFun a1627953396 b1627953397 -> Type) -> Type) (TyFun b1627953397 (TyFun [a1627953396] b1627953397 -> Type) -> Type) -> *) (Foldl'Sym0 a1627953396 b1627953397) Source # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym0 a1627953396 b1627953397) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a1627953390 [b1627953391] -> Type) (TyFun [a1627953390] [b1627953391] -> Type) -> *) (ConcatMapSym0 a1627953390 b1627953391) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym0 a1627953390 b1627953391) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun b1627953387 (TyFun a1627953388 b1627953387 -> Type) -> Type) (TyFun b1627953387 (TyFun [a1627953388] [b1627953387] -> Type) -> Type) -> *) (ScanlSym0 a1627953388 b1627953387) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a1627953388 b1627953387) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a1627953384 (TyFun b1627953385 b1627953385 -> Type) -> Type) (TyFun b1627953385 (TyFun [a1627953384] [b1627953385] -> Type) -> Type) -> *) (ScanrSym0 a1627953384 b1627953385) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a1627953384 b1627953385) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun b1627953375 (Maybe (a1627953376, b1627953375)) -> Type) (TyFun b1627953375 [a1627953376] -> Type) -> *) (UnfoldrSym0 b1627953375 a1627953376) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 b1627953375 a1627953376) t -> () Source #

SuppressUnusedWarnings (TyFun [Either a1627830454 b1627830455] [a1627830454] -> *) (LeftsSym0 b1627830455 a1627830454) Source # 

Methods

suppressUnusedWarnings :: Proxy (LeftsSym0 b1627830455 a1627830454) t -> () Source #

SuppressUnusedWarnings (TyFun [Either a1627830452 b1627830453] [b1627830453] -> *) (RightsSym0 a1627830452 b1627830453) Source # 

Methods

suppressUnusedWarnings :: Proxy (RightsSym0 a1627830452 b1627830453) t -> () Source #

SuppressUnusedWarnings (TyFun [(a1627953354, b1627953355)] ([a1627953354], [b1627953355]) -> *) (UnzipSym0 a1627953354 b1627953355) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a1627953354 b1627953355) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953366] (TyFun [b1627953367] [(a1627953366, b1627953367)] -> Type) -> *) (ZipSym0 a1627953366 b1627953367) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a1627953366 b1627953367) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953283] i1627953282 -> *) (GenericLengthSym0 a1627953283 i1627953282) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericLengthSym0 a1627953283 i1627953282) t -> () Source #

SuppressUnusedWarnings (TyFun [a1628251632] (TyFun i1628251631 a1628251632 -> Type) -> *) (GenericIndexSym0 i1628251631 a1628251632) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym0 i1628251631 a1628251632) t -> () Source #

SuppressUnusedWarnings (TyFun (Either a1627830448 b1627830449) Bool -> *) (IsLeftSym0 a1627830448 b1627830449) Source # 

Methods

suppressUnusedWarnings :: Proxy (IsLeftSym0 a1627830448 b1627830449) t -> () Source #

SuppressUnusedWarnings (TyFun (Either a1627830446 b1627830447) Bool -> *) (IsRightSym0 a1627830446 b1627830447) Source # 

Methods

suppressUnusedWarnings :: Proxy (IsRightSym0 a1627830446 b1627830447) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun b1627437721 (Either a1627437720 b1627437721) -> *) (RightSym0 a1627437720 b1627437721) Source # 

Methods

suppressUnusedWarnings :: Proxy (RightSym0 a1627437720 b1627437721) t -> () Source #

SuppressUnusedWarnings (TyFun a1627437720 (Either a1627437720 b1627437721) -> *) (LeftSym0 a1627437720 b1627437721) Source # 

Methods

suppressUnusedWarnings :: Proxy (LeftSym0 a1627437720 b1627437721) t -> () Source #

SuppressUnusedWarnings (TyFun a1627796651 (TyFun b1627796652 a1627796651 -> Type) -> *) (ConstSym0 b1627796652 a1627796651) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConstSym0 b1627796652 a1627796651) t -> () Source #

SuppressUnusedWarnings (TyFun a1627796642 (TyFun b1627796643 b1627796643 -> Type) -> *) (SeqSym0 a1627796642 b1627796643) Source # 

Methods

suppressUnusedWarnings :: Proxy (SeqSym0 a1627796642 b1627796643) t -> () Source #

SuppressUnusedWarnings (TyFun k01627810588 k1627810590 -> *) (ErrorSym0 k01627810588 k1627810590) Source # 

Methods

suppressUnusedWarnings :: Proxy (ErrorSym0 k01627810588 k1627810590) t -> () Source #

SuppressUnusedWarnings (TyFun b1627847771 (TyFun (TyFun a1627847772 b1627847771 -> Type) (TyFun (Maybe a1627847772) b1627847771 -> Type) -> Type) -> *) (Maybe_Sym0 a1627847772 b1627847771) Source # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym0 a1627847772 b1627847771) t -> () Source #

SuppressUnusedWarnings (TyFun a1627953297 (TyFun [(a1627953297, b1627953298)] (Maybe b1627953298) -> Type) -> *) (LookupSym0 a1627953297 b1627953298) Source # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym0 a1627953297 b1627953298) t -> () Source #

SuppressUnusedWarnings (TyFun i1628251637 (TyFun [a1628251638] [a1628251638] -> Type) -> *) (GenericTakeSym0 i1628251637 a1628251638) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym0 i1628251637 a1628251638) t -> () Source #

SuppressUnusedWarnings (TyFun i1628251635 (TyFun [a1628251636] [a1628251636] -> Type) -> *) (GenericDropSym0 i1628251635 a1628251636) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym0 i1628251635 a1628251636) t -> () Source #

SuppressUnusedWarnings (TyFun i1628251633 (TyFun [a1628251634] ([a1628251634], [a1628251634]) -> Type) -> *) (GenericSplitAtSym0 i1628251633 a1628251634) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym0 i1628251633 a1628251634) t -> () Source #

SuppressUnusedWarnings (TyFun i1628251629 (TyFun a1628251630 [a1628251630] -> Type) -> *) (GenericReplicateSym0 i1628251629 a1628251630) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym0 i1628251629 a1628251630) t -> () Source #

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

Methods

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

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

Methods

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

SuppressUnusedWarnings ((TyFun b1627796648 c1627796649 -> Type) -> TyFun (TyFun a1627796650 b1627796648 -> Type) (TyFun a1627796650 c1627796649 -> Type) -> *) ((:.$$) a1627796650 b1627796648 c1627796649) Source # 

Methods

suppressUnusedWarnings :: Proxy ((a1627796650 :.$$ b1627796648) c1627796649) t -> () Source #

SuppressUnusedWarnings ((TyFun b1627796648 c1627796649 -> Type) -> (TyFun a1627796650 b1627796648 -> Type) -> TyFun a1627796650 c1627796649 -> *) ((:.$$$) a1627796650 b1627796648 c1627796649) Source # 

Methods

suppressUnusedWarnings :: Proxy ((a1627796650 :.$$$ b1627796648) c1627796649) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627796645 (TyFun b1627796646 c1627796647 -> Type) -> Type) -> TyFun b1627796646 (TyFun a1627796645 c1627796647 -> Type) -> *) (FlipSym1 a1627796645 b1627796646 c1627796647) Source # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym1 a1627796645 b1627796646 c1627796647) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627796645 (TyFun b1627796646 c1627796647 -> Type) -> Type) -> b1627796646 -> TyFun a1627796645 c1627796647 -> *) (FlipSym2 a1627796645 b1627796646 c1627796647) Source # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym2 a1627796645 b1627796646 c1627796647) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627829180 c1627829181 -> Type) -> TyFun (TyFun b1627829182 c1627829181 -> Type) (TyFun (Either a1627829180 b1627829182) c1627829181 -> Type) -> *) (Either_Sym1 b1627829182 a1627829180 c1627829181) Source # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym1 b1627829182 a1627829180 c1627829181) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627829180 c1627829181 -> Type) -> (TyFun b1627829182 c1627829181 -> Type) -> TyFun (Either a1627829180 b1627829182) c1627829181 -> *) (Either_Sym2 b1627829182 a1627829180 c1627829181) Source # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym2 b1627829182 a1627829180 c1627829181) t -> () Source #

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

Methods

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

SuppressUnusedWarnings ((TyFun acc1627953380 (TyFun x1627953381 (acc1627953380, y1627953382) -> Type) -> Type) -> TyFun acc1627953380 (TyFun [x1627953381] (acc1627953380, [y1627953382]) -> Type) -> *) (MapAccumLSym1 x1627953381 acc1627953380 y1627953382) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym1 x1627953381 acc1627953380 y1627953382) t -> () Source #

SuppressUnusedWarnings ((TyFun acc1627953380 (TyFun x1627953381 (acc1627953380, y1627953382) -> Type) -> Type) -> acc1627953380 -> TyFun [x1627953381] (acc1627953380, [y1627953382]) -> *) (MapAccumLSym2 x1627953381 acc1627953380 y1627953382) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym2 x1627953381 acc1627953380 y1627953382) t -> () Source #

SuppressUnusedWarnings ((TyFun acc1627953377 (TyFun x1627953378 (acc1627953377, y1627953379) -> Type) -> Type) -> TyFun acc1627953377 (TyFun [x1627953378] (acc1627953377, [y1627953379]) -> Type) -> *) (MapAccumRSym1 x1627953378 acc1627953377 y1627953379) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym1 x1627953378 acc1627953377 y1627953379) t -> () Source #

SuppressUnusedWarnings ((TyFun acc1627953377 (TyFun x1627953378 (acc1627953377, y1627953379) -> Type) -> Type) -> acc1627953377 -> TyFun [x1627953378] (acc1627953377, [y1627953379]) -> *) (MapAccumRSym2 x1627953378 acc1627953377 y1627953379) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym2 x1627953378 acc1627953377 y1627953379) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627953360 (TyFun b1627953361 c1627953362 -> Type) -> Type) -> TyFun [a1627953360] (TyFun [b1627953361] [c1627953362] -> Type) -> *) (ZipWithSym1 a1627953360 b1627953361 c1627953362) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a1627953360 b1627953361 c1627953362) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627953360 (TyFun b1627953361 c1627953362 -> Type) -> Type) -> [a1627953360] -> TyFun [b1627953361] [c1627953362] -> *) (ZipWithSym2 a1627953360 b1627953361 c1627953362) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a1627953360 b1627953361 c1627953362) t -> () Source #

SuppressUnusedWarnings ([a1627953363] -> TyFun [b1627953364] (TyFun [c1627953365] [(a1627953363, b1627953364, c1627953365)] -> Type) -> *) (Zip3Sym1 b1627953364 c1627953365 a1627953363) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym1 b1627953364 c1627953365 a1627953363) t -> () Source #

SuppressUnusedWarnings ([a1627953363] -> [b1627953364] -> TyFun [c1627953365] [(a1627953363, b1627953364, c1627953365)] -> *) (Zip3Sym2 c1627953365 b1627953364 a1627953363) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym2 c1627953365 b1627953364 a1627953363) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun (TyFun b1627796648 c1627796649 -> Type) (TyFun (TyFun a1627796650 b1627796648 -> Type) (TyFun a1627796650 c1627796649 -> Type) -> Type) -> *) ((:.$) b1627796648 a1627796650 c1627796649) Source # 

Methods

suppressUnusedWarnings :: Proxy ((b1627796648 :.$ a1627796650) c1627796649) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a1627796645 (TyFun b1627796646 c1627796647 -> Type) -> Type) (TyFun b1627796646 (TyFun a1627796645 c1627796647 -> Type) -> Type) -> *) (FlipSym0 b1627796646 a1627796645 c1627796647) Source # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym0 b1627796646 a1627796645 c1627796647) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a1627829180 c1627829181 -> Type) (TyFun (TyFun b1627829182 c1627829181 -> Type) (TyFun (Either a1627829180 b1627829182) c1627829181 -> Type) -> Type) -> *) (Either_Sym0 a1627829180 b1627829182 c1627829181) Source # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym0 a1627829180 b1627829182 c1627829181) t -> () Source #

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

Methods

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

SuppressUnusedWarnings (TyFun (TyFun acc1627953380 (TyFun x1627953381 (acc1627953380, y1627953382) -> Type) -> Type) (TyFun acc1627953380 (TyFun [x1627953381] (acc1627953380, [y1627953382]) -> Type) -> Type) -> *) (MapAccumLSym0 x1627953381 acc1627953380 y1627953382) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym0 x1627953381 acc1627953380 y1627953382) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun acc1627953377 (TyFun x1627953378 (acc1627953377, y1627953379) -> Type) -> Type) (TyFun acc1627953377 (TyFun [x1627953378] (acc1627953377, [y1627953379]) -> Type) -> Type) -> *) (MapAccumRSym0 x1627953378 acc1627953377 y1627953379) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym0 x1627953378 acc1627953377 y1627953379) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a1627953360 (TyFun b1627953361 c1627953362 -> Type) -> Type) (TyFun [a1627953360] (TyFun [b1627953361] [c1627953362] -> Type) -> Type) -> *) (ZipWithSym0 a1627953360 b1627953361 c1627953362) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a1627953360 b1627953361 c1627953362) t -> () Source #

SuppressUnusedWarnings (TyFun [(a1627953351, b1627953352, c1627953353)] ([a1627953351], [b1627953352], [c1627953353]) -> *) (Unzip3Sym0 a1627953351 b1627953352 c1627953353) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip3Sym0 a1627953351 b1627953352 c1627953353) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953363] (TyFun [b1627953364] (TyFun [c1627953365] [(a1627953363, b1627953364, c1627953365)] -> Type) -> Type) -> *) (Zip3Sym0 a1627953363 b1627953364 c1627953365) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym0 a1627953363 b1627953364 c1627953365) t -> () Source #

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

Methods

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

SuppressUnusedWarnings ((TyFun a1627953356 (TyFun b1627953357 (TyFun c1627953358 d1627953359 -> Type) -> Type) -> Type) -> TyFun [a1627953356] (TyFun [b1627953357] (TyFun [c1627953358] [d1627953359] -> Type) -> Type) -> *) (ZipWith3Sym1 a1627953356 b1627953357 c1627953358 d1627953359) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym1 a1627953356 b1627953357 c1627953358 d1627953359) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627953356 (TyFun b1627953357 (TyFun c1627953358 d1627953359 -> Type) -> Type) -> Type) -> [a1627953356] -> TyFun [b1627953357] (TyFun [c1627953358] [d1627953359] -> Type) -> *) (ZipWith3Sym2 a1627953356 b1627953357 c1627953358 d1627953359) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym2 a1627953356 b1627953357 c1627953358 d1627953359) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627953356 (TyFun b1627953357 (TyFun c1627953358 d1627953359 -> Type) -> Type) -> Type) -> [a1627953356] -> [b1627953357] -> TyFun [c1627953358] [d1627953359] -> *) (ZipWith3Sym3 a1627953356 b1627953357 c1627953358 d1627953359) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym3 a1627953356 b1627953357 c1627953358 d1627953359) t -> () Source #

SuppressUnusedWarnings ([a1628251683] -> TyFun [b1628251684] (TyFun [c1628251685] (TyFun [d1628251686] [(a1628251683, b1628251684, c1628251685, d1628251686)] -> Type) -> Type) -> *) (Zip4Sym1 b1628251684 c1628251685 d1628251686 a1628251683) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym1 b1628251684 c1628251685 d1628251686 a1628251683) t -> () Source #

SuppressUnusedWarnings ([a1628251683] -> [b1628251684] -> TyFun [c1628251685] (TyFun [d1628251686] [(a1628251683, b1628251684, c1628251685, d1628251686)] -> Type) -> *) (Zip4Sym2 c1628251685 d1628251686 b1628251684 a1628251683) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym2 c1628251685 d1628251686 b1628251684 a1628251683) t -> () Source #

SuppressUnusedWarnings ([a1628251683] -> [b1628251684] -> [c1628251685] -> TyFun [d1628251686] [(a1628251683, b1628251684, c1628251685, d1628251686)] -> *) (Zip4Sym3 d1628251686 c1628251685 b1628251684 a1628251683) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym3 d1628251686 c1628251685 b1628251684 a1628251683) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun (TyFun a1627953356 (TyFun b1627953357 (TyFun c1627953358 d1627953359 -> Type) -> Type) -> Type) (TyFun [a1627953356] (TyFun [b1627953357] (TyFun [c1627953358] [d1627953359] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a1627953356 b1627953357 c1627953358 d1627953359) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym0 a1627953356 b1627953357 c1627953358 d1627953359) t -> () Source #

SuppressUnusedWarnings (TyFun [(a1627953347, b1627953348, c1627953349, d1627953350)] ([a1627953347], [b1627953348], [c1627953349], [d1627953350]) -> *) (Unzip4Sym0 a1627953347 b1627953348 c1627953349 d1627953350) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip4Sym0 a1627953347 b1627953348 c1627953349 d1627953350) t -> () Source #

SuppressUnusedWarnings (TyFun [a1628251683] (TyFun [b1628251684] (TyFun [c1628251685] (TyFun [d1628251686] [(a1628251683, b1628251684, c1628251685, d1628251686)] -> Type) -> Type) -> Type) -> *) (Zip4Sym0 a1628251683 b1628251684 c1628251685 d1628251686) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym0 a1628251683 b1628251684 c1628251685 d1628251686) t -> () Source #

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

Methods

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

SuppressUnusedWarnings ((TyFun a1628251660 (TyFun b1628251661 (TyFun c1628251662 (TyFun d1628251663 e1628251664 -> Type) -> Type) -> Type) -> Type) -> TyFun [a1628251660] (TyFun [b1628251661] (TyFun [c1628251662] (TyFun [d1628251663] [e1628251664] -> Type) -> Type) -> Type) -> *) (ZipWith4Sym1 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym1 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251660 (TyFun b1628251661 (TyFun c1628251662 (TyFun d1628251663 e1628251664 -> Type) -> Type) -> Type) -> Type) -> [a1628251660] -> TyFun [b1628251661] (TyFun [c1628251662] (TyFun [d1628251663] [e1628251664] -> Type) -> Type) -> *) (ZipWith4Sym2 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym2 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251660 (TyFun b1628251661 (TyFun c1628251662 (TyFun d1628251663 e1628251664 -> Type) -> Type) -> Type) -> Type) -> [a1628251660] -> [b1628251661] -> TyFun [c1628251662] (TyFun [d1628251663] [e1628251664] -> Type) -> *) (ZipWith4Sym3 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym3 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251660 (TyFun b1628251661 (TyFun c1628251662 (TyFun d1628251663 e1628251664 -> Type) -> Type) -> Type) -> Type) -> [a1628251660] -> [b1628251661] -> [c1628251662] -> TyFun [d1628251663] [e1628251664] -> *) (ZipWith4Sym4 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym4 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) t -> () Source #

SuppressUnusedWarnings ([a1628251678] -> TyFun [b1628251679] (TyFun [c1628251680] (TyFun [d1628251681] (TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> Type) -> Type) -> Type) -> *) (Zip5Sym1 b1628251679 c1628251680 d1628251681 e1628251682 a1628251678) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym1 b1628251679 c1628251680 d1628251681 e1628251682 a1628251678) t -> () Source #

SuppressUnusedWarnings ([a1628251678] -> [b1628251679] -> TyFun [c1628251680] (TyFun [d1628251681] (TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> Type) -> Type) -> *) (Zip5Sym2 c1628251680 d1628251681 e1628251682 b1628251679 a1628251678) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym2 c1628251680 d1628251681 e1628251682 b1628251679 a1628251678) t -> () Source #

SuppressUnusedWarnings ([a1628251678] -> [b1628251679] -> [c1628251680] -> TyFun [d1628251681] (TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> Type) -> *) (Zip5Sym3 d1628251681 e1628251682 c1628251680 b1628251679 a1628251678) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym3 d1628251681 e1628251682 c1628251680 b1628251679 a1628251678) t -> () Source #

SuppressUnusedWarnings ([a1628251678] -> [b1628251679] -> [c1628251680] -> [d1628251681] -> TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> *) (Zip5Sym4 e1628251682 d1628251681 c1628251680 b1628251679 a1628251678) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym4 e1628251682 d1628251681 c1628251680 b1628251679 a1628251678) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun (TyFun a1628251660 (TyFun b1628251661 (TyFun c1628251662 (TyFun d1628251663 e1628251664 -> Type) -> Type) -> Type) -> Type) (TyFun [a1628251660] (TyFun [b1628251661] (TyFun [c1628251662] (TyFun [d1628251663] [e1628251664] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith4Sym0 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym0 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) t -> () Source #

SuppressUnusedWarnings (TyFun [(a1627953342, b1627953343, c1627953344, d1627953345, e1627953346)] ([a1627953342], [b1627953343], [c1627953344], [d1627953345], [e1627953346]) -> *) (Unzip5Sym0 a1627953342 b1627953343 c1627953344 d1627953345 e1627953346) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip5Sym0 a1627953342 b1627953343 c1627953344 d1627953345 e1627953346) t -> () Source #

SuppressUnusedWarnings (TyFun [a1628251678] (TyFun [b1628251679] (TyFun [c1628251680] (TyFun [d1628251681] (TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip5Sym0 a1628251678 b1628251679 c1628251680 d1628251681 e1628251682) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym0 a1628251678 b1628251679 c1628251680 d1628251681 e1628251682) t -> () Source #

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

Methods

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

SuppressUnusedWarnings ((TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a1628251654] (TyFun [b1628251655] (TyFun [c1628251656] (TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym1 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym1 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251654] -> TyFun [b1628251655] (TyFun [c1628251656] (TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> Type) -> Type) -> *) (ZipWith5Sym2 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym2 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251654] -> [b1628251655] -> TyFun [c1628251656] (TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> Type) -> *) (ZipWith5Sym3 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym3 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251654] -> [b1628251655] -> [c1628251656] -> TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> *) (ZipWith5Sym4 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym4 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251654] -> [b1628251655] -> [c1628251656] -> [d1628251657] -> TyFun [e1628251658] [f1628251659] -> *) (ZipWith5Sym5 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym5 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) t -> () Source #

SuppressUnusedWarnings ([a1628251672] -> TyFun [b1628251673] (TyFun [c1628251674] (TyFun [d1628251675] (TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym1 b1628251673 c1628251674 d1628251675 e1628251676 f1628251677 a1628251672) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym1 b1628251673 c1628251674 d1628251675 e1628251676 f1628251677 a1628251672) t -> () Source #

SuppressUnusedWarnings ([a1628251672] -> [b1628251673] -> TyFun [c1628251674] (TyFun [d1628251675] (TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> Type) -> Type) -> *) (Zip6Sym2 c1628251674 d1628251675 e1628251676 f1628251677 b1628251673 a1628251672) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym2 c1628251674 d1628251675 e1628251676 f1628251677 b1628251673 a1628251672) t -> () Source #

SuppressUnusedWarnings ([a1628251672] -> [b1628251673] -> [c1628251674] -> TyFun [d1628251675] (TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> Type) -> *) (Zip6Sym3 d1628251675 e1628251676 f1628251677 c1628251674 b1628251673 a1628251672) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym3 d1628251675 e1628251676 f1628251677 c1628251674 b1628251673 a1628251672) t -> () Source #

SuppressUnusedWarnings ([a1628251672] -> [b1628251673] -> [c1628251674] -> [d1628251675] -> TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> *) (Zip6Sym4 e1628251676 f1628251677 d1628251675 c1628251674 b1628251673 a1628251672) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym4 e1628251676 f1628251677 d1628251675 c1628251674 b1628251673 a1628251672) t -> () Source #

SuppressUnusedWarnings ([a1628251672] -> [b1628251673] -> [c1628251674] -> [d1628251675] -> [e1628251676] -> TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> *) (Zip6Sym5 f1628251677 e1628251676 d1628251675 c1628251674 b1628251673 a1628251672) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym5 f1628251677 e1628251676 d1628251675 c1628251674 b1628251673 a1628251672) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun (TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a1628251654] (TyFun [b1628251655] (TyFun [c1628251656] (TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym0 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym0 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) t -> () Source #

SuppressUnusedWarnings (TyFun [(a1627953336, b1627953337, c1627953338, d1627953339, e1627953340, f1627953341)] ([a1627953336], [b1627953337], [c1627953338], [d1627953339], [e1627953340], [f1627953341]) -> *) (Unzip6Sym0 a1627953336 b1627953337 c1627953338 d1627953339 e1627953340 f1627953341) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip6Sym0 a1627953336 b1627953337 c1627953338 d1627953339 e1627953340 f1627953341) t -> () Source #

SuppressUnusedWarnings (TyFun [a1628251672] (TyFun [b1628251673] (TyFun [c1628251674] (TyFun [d1628251675] (TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym0 a1628251672 b1628251673 c1628251674 d1628251675 e1628251676 f1628251677) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym0 a1628251672 b1628251673 c1628251674 d1628251675 e1628251676 f1628251677) t -> () Source #

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

Methods

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

SuppressUnusedWarnings ((TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a1628251647] (TyFun [b1628251648] (TyFun [c1628251649] (TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym1 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym1 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251647] -> TyFun [b1628251648] (TyFun [c1628251649] (TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym2 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym2 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251647] -> [b1628251648] -> TyFun [c1628251649] (TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> Type) -> *) (ZipWith6Sym3 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym3 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251647] -> [b1628251648] -> [c1628251649] -> TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> *) (ZipWith6Sym4 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym4 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251647] -> [b1628251648] -> [c1628251649] -> [d1628251650] -> TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> *) (ZipWith6Sym5 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym5 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251647] -> [b1628251648] -> [c1628251649] -> [d1628251650] -> [e1628251651] -> TyFun [f1628251652] [g1628251653] -> *) (ZipWith6Sym6 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym6 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) t -> () Source #

SuppressUnusedWarnings ([a1628251665] -> TyFun [b1628251666] (TyFun [c1628251667] (TyFun [d1628251668] (TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym1 b1628251666 c1628251667 d1628251668 e1628251669 f1628251670 g1628251671 a1628251665) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym1 b1628251666 c1628251667 d1628251668 e1628251669 f1628251670 g1628251671 a1628251665) t -> () Source #

SuppressUnusedWarnings ([a1628251665] -> [b1628251666] -> TyFun [c1628251667] (TyFun [d1628251668] (TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym2 c1628251667 d1628251668 e1628251669 f1628251670 g1628251671 b1628251666 a1628251665) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym2 c1628251667 d1628251668 e1628251669 f1628251670 g1628251671 b1628251666 a1628251665) t -> () Source #

SuppressUnusedWarnings ([a1628251665] -> [b1628251666] -> [c1628251667] -> TyFun [d1628251668] (TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> Type) -> *) (Zip7Sym3 d1628251668 e1628251669 f1628251670 g1628251671 c1628251667 b1628251666 a1628251665) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym3 d1628251668 e1628251669 f1628251670 g1628251671 c1628251667 b1628251666 a1628251665) t -> () Source #

SuppressUnusedWarnings ([a1628251665] -> [b1628251666] -> [c1628251667] -> [d1628251668] -> TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> *) (Zip7Sym4 e1628251669 f1628251670 g1628251671 d1628251668 c1628251667 b1628251666 a1628251665) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym4 e1628251669 f1628251670 g1628251671 d1628251668 c1628251667 b1628251666 a1628251665) t -> () Source #

SuppressUnusedWarnings ([a1628251665] -> [b1628251666] -> [c1628251667] -> [d1628251668] -> [e1628251669] -> TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> *) (Zip7Sym5 f1628251670 g1628251671 e1628251669 d1628251668 c1628251667 b1628251666 a1628251665) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym5 f1628251670 g1628251671 e1628251669 d1628251668 c1628251667 b1628251666 a1628251665) t -> () Source #

SuppressUnusedWarnings ([a1628251665] -> [b1628251666] -> [c1628251667] -> [d1628251668] -> [e1628251669] -> [f1628251670] -> TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> *) (Zip7Sym6 g1628251671 f1628251670 e1628251669 d1628251668 c1628251667 b1628251666 a1628251665) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym6 g1628251671 f1628251670 e1628251669 d1628251668 c1628251667 b1628251666 a1628251665) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun (TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a1628251647] (TyFun [b1628251648] (TyFun [c1628251649] (TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym0 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym0 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) t -> () Source #

SuppressUnusedWarnings (TyFun [(a1627953329, b1627953330, c1627953331, d1627953332, e1627953333, f1627953334, g1627953335)] ([a1627953329], [b1627953330], [c1627953331], [d1627953332], [e1627953333], [f1627953334], [g1627953335]) -> *) (Unzip7Sym0 a1627953329 b1627953330 c1627953331 d1627953332 e1627953333 f1627953334 g1627953335) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip7Sym0 a1627953329 b1627953330 c1627953331 d1627953332 e1627953333 f1627953334 g1627953335) t -> () Source #

SuppressUnusedWarnings (TyFun [a1628251665] (TyFun [b1628251666] (TyFun [c1628251667] (TyFun [d1628251668] (TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym0 a1628251665 b1628251666 c1628251667 d1628251668 e1628251669 f1628251670 g1628251671) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym0 a1628251665 b1628251666 c1628251667 d1628251668 e1628251669 f1628251670 g1628251671) t -> () Source #

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

Methods

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

SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a1628251639] (TyFun [b1628251640] (TyFun [c1628251641] (TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym1 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym1 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251639] -> TyFun [b1628251640] (TyFun [c1628251641] (TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym2 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym2 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251639] -> [b1628251640] -> TyFun [c1628251641] (TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym3 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym3 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251639] -> [b1628251640] -> [c1628251641] -> TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> *) (ZipWith7Sym4 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym4 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251639] -> [b1628251640] -> [c1628251641] -> [d1628251642] -> TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> *) (ZipWith7Sym5 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym5 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251639] -> [b1628251640] -> [c1628251641] -> [d1628251642] -> [e1628251643] -> TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> *) (ZipWith7Sym6 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym6 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) t -> () Source #

SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251639] -> [b1628251640] -> [c1628251641] -> [d1628251642] -> [e1628251643] -> [f1628251644] -> TyFun [g1628251645] [h1628251646] -> *) (ZipWith7Sym7 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym7 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a1628251639] (TyFun [b1628251640] (TyFun [c1628251641] (TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym0 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym0 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) t -> () Source #