singletons-2.3.1: A framework for generating singleton types

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

Data.Singletons.TH

Contents

Description

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

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

Synopsis

Primary Template Haskell generation functions

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

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

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

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

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

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

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

to generate singletons for Prelude types.

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

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

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

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

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

Generate defunctionalization symbols for existing type family

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

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

Functions to generate equality instances

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

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

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

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

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

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

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

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

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

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

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

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

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

Create instances of SDecide for each type in the list.

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

Create instance of SDecide for the given type.

Functions to generate Ord instances

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

Produce instances for POrd from the given types

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

Produce an instance for POrd from the given type

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

Create instances of SOrd for the given types

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

Create instance of SOrd for the given type

Functions to generate Bounded instances

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

Produce instances for PBounded from the given types

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

Produce an instance for PBounded from the given type

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

Create instances of SBounded for the given types

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

Create instance of SBounded for the given type

Functions to generate Enum instances

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

Produce instances for PEnum from the given types

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

Produce an instance for PEnum from the given type

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

Create instances of SEnum for the given types

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

Create instance of SEnum for the given type

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 [a] Source # 
data Sing [a] where
data Sing (Maybe a) Source # 
data Sing (Maybe a) where
data Sing (NonEmpty a) Source # 
data Sing (NonEmpty a) where
data Sing (Either a b) Source # 
data Sing (Either a b) where
data Sing (a, b) Source # 
data Sing (a, b) where
data Sing ((~>) k1 k2) Source # 
data Sing ((~>) k1 k2) = SLambda {}
data Sing (a, b, c) Source # 
data Sing (a, b, c) where
data Sing (a, b, c, d) Source # 
data Sing (a, b, c, d) where
data Sing (a, b, c, d, e) Source # 
data Sing (a, b, c, d, e) where
data Sing (a, b, c, d, e, f) Source # 
data Sing (a, b, c, d, e, f) where
data Sing (a, b, c, d, e, f, g) Source # 
data Sing (a, b, c, d, e, f, g) where

Auxiliary definitions

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

class PEq a Source #

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

Associated Types

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

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

Instances

PEq Bool Source # 

Associated Types

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

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

PEq Ordering Source # 

Associated Types

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

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

PEq () Source # 

Associated Types

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

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

PEq [k] Source # 

Associated Types

type ([k] :== (x :: [k])) (y :: [k]) :: Bool Source #

type ([k] :/= (x :: [k])) (y :: [k]) :: Bool Source #

PEq (Maybe k) Source # 

Associated Types

type ((Maybe k) :== (x :: Maybe k)) (y :: Maybe k) :: Bool Source #

type ((Maybe k) :/= (x :: Maybe k)) (y :: Maybe k) :: Bool Source #

PEq (NonEmpty k) Source # 

Associated Types

type ((NonEmpty k) :== (x :: NonEmpty k)) (y :: NonEmpty k) :: Bool Source #

type ((NonEmpty k) :/= (x :: NonEmpty k)) (y :: NonEmpty k) :: Bool Source #

PEq (Either k1 k2) Source # 

Associated Types

type ((Either k1 k2) :== (x :: Either k1 k2)) (y :: Either k1 k2) :: Bool Source #

type ((Either k1 k2) :/= (x :: Either k1 k2)) (y :: Either k1 k2) :: Bool Source #

PEq (k1, k2) Source # 

Associated Types

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

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

PEq (k1, k2, k3) Source # 

Associated Types

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

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

PEq (k1, k2, k3, k4) Source # 

Associated Types

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

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

PEq (k1, k2, k3, k4, k5) Source # 

Associated Types

type ((k1, k2, k3, k4, k5) :== (x :: (k1, k2, k3, k4, k5))) (y :: (k1, k2, k3, k4, k5)) :: Bool Source #

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

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

Associated Types

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

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

PEq (k1, k2, k3, k4, k5, k6, k7) Source # 

Associated Types

type ((k1, k2, k3, k4, k5, k6, k7) :== (x :: (k1, k2, k3, k4, k5, k6, k7))) (y :: (k1, k2, k3, k4, k5, k6, k7)) :: Bool Source #

type ((k1, k2, k3, k4, k5, k6, k7) :/= (x :: (k1, k2, k3, k4, k5, k6, k7))) (y :: (k1, k2, k3, k4, k5, k6, k7)) :: 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_6989586621679277808 = 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 :: k) (b :: k). Sing a -> Sing b -> Sing (a :== b) infix 4 Source #

Boolean equality on singletons

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

Boolean disequality on singletons

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

Boolean disequality on singletons

Instances

SEq Bool Source # 

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 a => SEq [a] Source # 

Methods

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

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

SEq a => SEq (Maybe a) Source # 

Methods

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

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

SEq a => SEq (NonEmpty a) Source # 

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

(%:==) :: Sing (a, b, c, d, e) a -> Sing (a, b, c, d, e) b -> Sing Bool (((a, b, c, d, e) :== a) b) Source #

(%:/=) :: Sing (a, b, c, d, e) a -> Sing (a, b, c, d, e) b -> Sing Bool (((a, b, c, d, e) :/= a) b) Source #

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

Methods

(%:==) :: Sing (a, b, c, d, e, f) a -> Sing (a, b, c, d, e, f) b -> Sing Bool (((a, b, c, d, e, f) :== a) b) Source #

(%:/=) :: Sing (a, b, c, d, e, f) a -> Sing (a, b, c, d, e, f) b -> Sing Bool (((a, b, c, d, e, f) :/= a) b) Source #

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

Methods

(%:==) :: Sing (a, b, c, d, e, f, g) a -> Sing (a, b, c, d, e, f, g) b -> Sing Bool (((a, b, c, d, e, f, g) :== a) b) Source #

(%:/=) :: Sing (a, b, c, d, e, f, g) a -> Sing (a, b, c, d, e, f, g) b -> Sing Bool (((a, b, c, d, e, f, g) :/= a) b) Source #

class PEq a => POrd (a :: Type) 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 Source # 

Associated Types

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

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

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

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

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

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

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

POrd Ordering Source # 

Associated Types

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

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

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

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

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

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

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

POrd () Source # 

Associated Types

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

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

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

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

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

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

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

POrd [a] Source # 

Associated Types

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

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

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

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

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

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

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

POrd (Maybe a) Source # 

Associated Types

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

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

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

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

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

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

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

POrd (NonEmpty a) Source # 

Associated Types

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

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

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

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

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

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

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

POrd (Either a b) Source # 

Associated Types

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

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

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

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

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

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

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

POrd (a, b) Source # 

Associated Types

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

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

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

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

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

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

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

POrd (a, b, c) Source # 

Associated Types

type Compare (a, b, c) (arg :: (a, b, c)) (arg :: (a, b, c)) :: Ordering Source #

type ((a, b, c) :< (arg :: (a, b, c))) (arg :: (a, b, c)) :: Bool Source #

type ((a, b, c) :<= (arg :: (a, b, c))) (arg :: (a, b, c)) :: Bool Source #

type ((a, b, c) :> (arg :: (a, b, c))) (arg :: (a, b, c)) :: Bool Source #

type ((a, b, c) :>= (arg :: (a, b, c))) (arg :: (a, b, c)) :: Bool Source #

type Max (a, b, c) (arg :: (a, b, c)) (arg :: (a, b, c)) :: a Source #

type Min (a, b, c) (arg :: (a, b, c)) (arg :: (a, b, c)) :: a Source #

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

Associated Types

type Compare (a, b, c, d) (arg :: (a, b, c, d)) (arg :: (a, b, c, d)) :: Ordering Source #

type ((a, b, c, d) :< (arg :: (a, b, c, d))) (arg :: (a, b, c, d)) :: Bool Source #

type ((a, b, c, d) :<= (arg :: (a, b, c, d))) (arg :: (a, b, c, d)) :: Bool Source #

type ((a, b, c, d) :> (arg :: (a, b, c, d))) (arg :: (a, b, c, d)) :: Bool Source #

type ((a, b, c, d) :>= (arg :: (a, b, c, d))) (arg :: (a, b, c, d)) :: Bool Source #

type Max (a, b, c, d) (arg :: (a, b, c, d)) (arg :: (a, b, c, d)) :: a Source #

type Min (a, b, c, d) (arg :: (a, b, c, d)) (arg :: (a, b, c, d)) :: a Source #

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

Associated Types

type Compare (a, b, c, d, e) (arg :: (a, b, c, d, e)) (arg :: (a, b, c, d, e)) :: Ordering Source #

type ((a, b, c, d, e) :< (arg :: (a, b, c, d, e))) (arg :: (a, b, c, d, e)) :: Bool Source #

type ((a, b, c, d, e) :<= (arg :: (a, b, c, d, e))) (arg :: (a, b, c, d, e)) :: Bool Source #

type ((a, b, c, d, e) :> (arg :: (a, b, c, d, e))) (arg :: (a, b, c, d, e)) :: Bool Source #

type ((a, b, c, d, e) :>= (arg :: (a, b, c, d, e))) (arg :: (a, b, c, d, e)) :: Bool Source #

type Max (a, b, c, d, e) (arg :: (a, b, c, d, e)) (arg :: (a, b, c, d, e)) :: a Source #

type Min (a, b, c, d, e) (arg :: (a, b, c, d, e)) (arg :: (a, b, c, d, e)) :: a Source #

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

Associated Types

type Compare (a, b, c, d, e, f) (arg :: (a, b, c, d, e, f)) (arg :: (a, b, c, d, e, f)) :: Ordering Source #

type ((a, b, c, d, e, f) :< (arg :: (a, b, c, d, e, f))) (arg :: (a, b, c, d, e, f)) :: Bool Source #

type ((a, b, c, d, e, f) :<= (arg :: (a, b, c, d, e, f))) (arg :: (a, b, c, d, e, f)) :: Bool Source #

type ((a, b, c, d, e, f) :> (arg :: (a, b, c, d, e, f))) (arg :: (a, b, c, d, e, f)) :: Bool Source #

type ((a, b, c, d, e, f) :>= (arg :: (a, b, c, d, e, f))) (arg :: (a, b, c, d, e, f)) :: Bool Source #

type Max (a, b, c, d, e, f) (arg :: (a, b, c, d, e, f)) (arg :: (a, b, c, d, e, f)) :: a Source #

type Min (a, b, c, d, e, f) (arg :: (a, b, c, d, e, f)) (arg :: (a, b, c, d, e, f)) :: a Source #

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

Associated Types

type Compare (a, b, c, d, e, f, g) (arg :: (a, b, c, d, e, f, g)) (arg :: (a, b, c, d, e, f, g)) :: Ordering Source #

type ((a, b, c, d, e, f, g) :< (arg :: (a, b, c, d, e, f, g))) (arg :: (a, b, c, d, e, f, g)) :: Bool Source #

type ((a, b, c, d, e, f, g) :<= (arg :: (a, b, c, d, e, f, g))) (arg :: (a, b, c, d, e, f, g)) :: Bool Source #

type ((a, b, c, d, e, f, g) :> (arg :: (a, b, c, d, e, f, g))) (arg :: (a, b, c, d, e, f, g)) :: Bool Source #

type ((a, b, c, d, e, f, g) :>= (arg :: (a, b, c, d, e, f, g))) (arg :: (a, b, c, d, e, f, g)) :: Bool Source #

type Max (a, b, c, d, e, f, g) (arg :: (a, b, c, d, e, f, g)) (arg :: (a, b, c, d, e, f, g)) :: a Source #

type Min (a, b, c, d, e, f, g) (arg :: (a, b, c, d, e, f, g)) (arg :: (a, b, c, d, e, f, g)) :: a Source #

class SEq a => SOrd a where Source #

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

sMin :: forall (t :: a) (t :: a). ((Apply (Apply MinSym0 t) t :: a) ~ Apply (Apply Min_6989586621679314166Sym0 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 a, SOrd [a]) => SOrd [a] Source # 

Methods

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

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

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

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

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

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

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

SOrd a => SOrd (Maybe a) Source # 

Methods

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

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

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

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

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

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

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

(SOrd a, SOrd [a]) => SOrd (NonEmpty a) Source # 
(SOrd a, SOrd b) => SOrd (Either a b) Source # 

Methods

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

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

Methods

sCompare :: Sing (a, b, c) t -> Sing (a, b, c) t -> Sing Ordering (Apply (a, b, c) Ordering (Apply (a, b, c) (TyFun (a, b, c) Ordering -> Type) (CompareSym0 (a, b, c)) t) t) Source #

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

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

(%:>) :: Sing (a, b, c) t -> Sing (a, b, c) t -> Sing Bool (Apply (a, b, c) Bool (Apply (a, b, c) (TyFun (a, b, c) Bool -> Type) ((:>$) (a, b, c)) t) t) Source #

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

sMax :: Sing (a, b, c) t -> Sing (a, b, c) t -> Sing (a, b, c) (Apply (a, b, c) (a, b, c) (Apply (a, b, c) (TyFun (a, b, c) (a, b, c) -> Type) (MaxSym0 (a, b, c)) t) t) Source #

sMin :: Sing (a, b, c) t -> Sing (a, b, c) t -> Sing (a, b, c) (Apply (a, b, c) (a, b, c) (Apply (a, b, c) (TyFun (a, b, c) (a, b, c) -> Type) (MinSym0 (a, b, c)) t) t) Source #

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

Methods

sCompare :: Sing (a, b, c, d) t -> Sing (a, b, c, d) t -> Sing Ordering (Apply (a, b, c, d) Ordering (Apply (a, b, c, d) (TyFun (a, b, c, d) Ordering -> Type) (CompareSym0 (a, b, c, d)) t) t) Source #

(%:<) :: Sing (a, b, c, d) t -> Sing (a, b, c, d) t -> Sing Bool (Apply (a, b, c, d) Bool (Apply (a, b, c, d) (TyFun (a, b, c, d) Bool -> Type) ((:<$) (a, b, c, d)) t) t) Source #

(%:<=) :: Sing (a, b, c, d) t -> Sing (a, b, c, d) t -> Sing Bool (Apply (a, b, c, d) Bool (Apply (a, b, c, d) (TyFun (a, b, c, d) Bool -> Type) ((:<=$) (a, b, c, d)) t) t) Source #

(%:>) :: Sing (a, b, c, d) t -> Sing (a, b, c, d) t -> Sing Bool (Apply (a, b, c, d) Bool (Apply (a, b, c, d) (TyFun (a, b, c, d) Bool -> Type) ((:>$) (a, b, c, d)) t) t) Source #

(%:>=) :: Sing (a, b, c, d) t -> Sing (a, b, c, d) t -> Sing Bool (Apply (a, b, c, d) Bool (Apply (a, b, c, d) (TyFun (a, b, c, d) Bool -> Type) ((:>=$) (a, b, c, d)) t) t) Source #

sMax :: Sing (a, b, c, d) t -> Sing (a, b, c, d) t -> Sing (a, b, c, d) (Apply (a, b, c, d) (a, b, c, d) (Apply (a, b, c, d) (TyFun (a, b, c, d) (a, b, c, d) -> Type) (MaxSym0 (a, b, c, d)) t) t) Source #

sMin :: Sing (a, b, c, d) t -> Sing (a, b, c, d) t -> Sing (a, b, c, d) (Apply (a, b, c, d) (a, b, c, d) (Apply (a, b, c, d) (TyFun (a, b, c, d) (a, b, c, d) -> Type) (MinSym0 (a, b, c, d)) t) t) Source #

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

Methods

sCompare :: Sing (a, b, c, d, e) t -> Sing (a, b, c, d, e) t -> Sing Ordering (Apply (a, b, c, d, e) Ordering (Apply (a, b, c, d, e) (TyFun (a, b, c, d, e) Ordering -> Type) (CompareSym0 (a, b, c, d, e)) t) t) Source #

(%:<) :: Sing (a, b, c, d, e) t -> Sing (a, b, c, d, e) t -> Sing Bool (Apply (a, b, c, d, e) Bool (Apply (a, b, c, d, e) (TyFun (a, b, c, d, e) Bool -> Type) ((:<$) (a, b, c, d, e)) t) t) Source #

(%:<=) :: Sing (a, b, c, d, e) t -> Sing (a, b, c, d, e) t -> Sing Bool (Apply (a, b, c, d, e) Bool (Apply (a, b, c, d, e) (TyFun (a, b, c, d, e) Bool -> Type) ((:<=$) (a, b, c, d, e)) t) t) Source #

(%:>) :: Sing (a, b, c, d, e) t -> Sing (a, b, c, d, e) t -> Sing Bool (Apply (a, b, c, d, e) Bool (Apply (a, b, c, d, e) (TyFun (a, b, c, d, e) Bool -> Type) ((:>$) (a, b, c, d, e)) t) t) Source #

(%:>=) :: Sing (a, b, c, d, e) t -> Sing (a, b, c, d, e) t -> Sing Bool (Apply (a, b, c, d, e) Bool (Apply (a, b, c, d, e) (TyFun (a, b, c, d, e) Bool -> Type) ((:>=$) (a, b, c, d, e)) t) t) Source #

sMax :: Sing (a, b, c, d, e) t -> Sing (a, b, c, d, e) t -> Sing (a, b, c, d, e) (Apply (a, b, c, d, e) (a, b, c, d, e) (Apply (a, b, c, d, e) (TyFun (a, b, c, d, e) (a, b, c, d, e) -> Type) (MaxSym0 (a, b, c, d, e)) t) t) Source #

sMin :: Sing (a, b, c, d, e) t -> Sing (a, b, c, d, e) t -> Sing (a, b, c, d, e) (Apply (a, b, c, d, e) (a, b, c, d, e) (Apply (a, b, c, d, e) (TyFun (a, b, c, d, e) (a, b, c, d, e) -> Type) (MinSym0 (a, b, c, d, e)) t) t) Source #

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

Methods

sCompare :: Sing (a, b, c, d, e, f) t -> Sing (a, b, c, d, e, f) t -> Sing Ordering (Apply (a, b, c, d, e, f) Ordering (Apply (a, b, c, d, e, f) (TyFun (a, b, c, d, e, f) Ordering -> Type) (CompareSym0 (a, b, c, d, e, f)) t) t) Source #

(%:<) :: Sing (a, b, c, d, e, f) t -> Sing (a, b, c, d, e, f) t -> Sing Bool (Apply (a, b, c, d, e, f) Bool (Apply (a, b, c, d, e, f) (TyFun (a, b, c, d, e, f) Bool -> Type) ((:<$) (a, b, c, d, e, f)) t) t) Source #

(%:<=) :: Sing (a, b, c, d, e, f) t -> Sing (a, b, c, d, e, f) t -> Sing Bool (Apply (a, b, c, d, e, f) Bool (Apply (a, b, c, d, e, f) (TyFun (a, b, c, d, e, f) Bool -> Type) ((:<=$) (a, b, c, d, e, f)) t) t) Source #

(%:>) :: Sing (a, b, c, d, e, f) t -> Sing (a, b, c, d, e, f) t -> Sing Bool (Apply (a, b, c, d, e, f) Bool (Apply (a, b, c, d, e, f) (TyFun (a, b, c, d, e, f) Bool -> Type) ((:>$) (a, b, c, d, e, f)) t) t) Source #

(%:>=) :: Sing (a, b, c, d, e, f) t -> Sing (a, b, c, d, e, f) t -> Sing Bool (Apply (a, b, c, d, e, f) Bool (Apply (a, b, c, d, e, f) (TyFun (a, b, c, d, e, f) Bool -> Type) ((:>=$) (a, b, c, d, e, f)) t) t) Source #

sMax :: Sing (a, b, c, d, e, f) t -> Sing (a, b, c, d, e, f) t -> Sing (a, b, c, d, e, f) (Apply (a, b, c, d, e, f) (a, b, c, d, e, f) (Apply (a, b, c, d, e, f) (TyFun (a, b, c, d, e, f) (a, b, c, d, e, f) -> Type) (MaxSym0 (a, b, c, d, e, f)) t) t) Source #

sMin :: Sing (a, b, c, d, e, f) t -> Sing (a, b, c, d, e, f) t -> Sing (a, b, c, d, e, f) (Apply (a, b, c, d, e, f) (a, b, c, d, e, f) (Apply (a, b, c, d, e, f) (TyFun (a, b, c, d, e, f) (a, b, c, d, e, f) -> Type) (MinSym0 (a, b, c, d, e, f)) t) t) Source #

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

Methods

sCompare :: Sing (a, b, c, d, e, f, g) t -> Sing (a, b, c, d, e, f, g) t -> Sing Ordering (Apply (a, b, c, d, e, f, g) Ordering (Apply (a, b, c, d, e, f, g) (TyFun (a, b, c, d, e, f, g) Ordering -> Type) (CompareSym0 (a, b, c, d, e, f, g)) t) t) Source #

(%:<) :: Sing (a, b, c, d, e, f, g) t -> Sing (a, b, c, d, e, f, g) t -> Sing Bool (Apply (a, b, c, d, e, f, g) Bool (Apply (a, b, c, d, e, f, g) (TyFun (a, b, c, d, e, f, g) Bool -> Type) ((:<$) (a, b, c, d, e, f, g)) t) t) Source #

(%:<=) :: Sing (a, b, c, d, e, f, g) t -> Sing (a, b, c, d, e, f, g) t -> Sing Bool (Apply (a, b, c, d, e, f, g) Bool (Apply (a, b, c, d, e, f, g) (TyFun (a, b, c, d, e, f, g) Bool -> Type) ((:<=$) (a, b, c, d, e, f, g)) t) t) Source #

(%:>) :: Sing (a, b, c, d, e, f, g) t -> Sing (a, b, c, d, e, f, g) t -> Sing Bool (Apply (a, b, c, d, e, f, g) Bool (Apply (a, b, c, d, e, f, g) (TyFun (a, b, c, d, e, f, g) Bool -> Type) ((:>$) (a, b, c, d, e, f, g)) t) t) Source #

(%:>=) :: Sing (a, b, c, d, e, f, g) t -> Sing (a, b, c, d, e, f, g) t -> Sing Bool (Apply (a, b, c, d, e, f, g) Bool (Apply (a, b, c, d, e, f, g) (TyFun (a, b, c, d, e, f, g) Bool -> Type) ((:>=$) (a, b, c, d, e, f, g)) t) t) Source #

sMax :: Sing (a, b, c, d, e, f, g) t -> Sing (a, b, c, d, e, f, g) t -> Sing (a, b, c, d, e, f, g) (Apply (a, b, c, d, e, f, g) (a, b, c, d, e, f, g) (Apply (a, b, c, d, e, f, g) (TyFun (a, b, c, d, e, f, g) (a, b, c, d, e, f, g) -> Type) (MaxSym0 (a, b, c, d, e, f, g)) t) t) Source #

sMin :: Sing (a, b, c, d, e, f, g) t -> Sing (a, b, c, d, e, f, g) t -> Sing (a, b, c, d, e, f, g) (Apply (a, b, c, d, e, f, g) (a, b, c, d, e, f, g) (Apply (a, b, c, d, e, f, g) (TyFun (a, b, c, d, e, f, g) (a, b, c, d, e, f, g) -> Type) (MinSym0 (a, b, c, d, e, f, g)) t) t) Source #

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

Equations

ThenCmp EQ x = x 
ThenCmp LT _z_6989586621679320849 = LTSym0 
ThenCmp GT _z_6989586621679320852 = GTSym0 

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

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

Equations

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

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

type family Any k0 :: k0 where ... #

The type constructor Any is type to which you can unsafely coerce any lifted type, and back. More concretely, for a lifted type t and value x :: t, -- unsafeCoerce (unsafeCoerce x :: Any) :: t is equivalent to x.

class SDecide k where Source #

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

Minimal complete definition

(%~)

Methods

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

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

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

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

Since: 4.7.0.0

Constructors

Refl :: (:~:) k a a 

Instances

TestCoercion k ((:~:) k a)

Since: 4.7.0.0

Methods

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

TestEquality k ((:~:) k a)

Since: 4.7.0.0

Methods

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

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

Since: 4.7.0.0

Methods

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

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

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

Since: 4.7.0.0

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)

Since: 4.7.0.0

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)

Since: 4.7.0.0

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

Since: 4.8.0.0

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

Since: 4.8.0.0

Methods

compare :: Void -> Void -> Ordering #

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

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

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

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

max :: Void -> Void -> Void #

min :: Void -> Void -> Void #

Read Void

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

Show Void

Since: 4.8.0.0

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Ix Void

Since: 4.8.0.0

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

Since: 4.9.0.0

Methods

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

sconcat :: NonEmpty Void -> Void #

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

Exception Void

Since: 4.8.0.0

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 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 :: TyFun k06989586621679402464 k6989586621679402466) Source #

Instances

SuppressUnusedWarnings (TyFun k06989586621679402464 k6989586621679402466 -> *) (ErrorSym0 k06989586621679402464 k6989586621679402466) Source # 

Methods

suppressUnusedWarnings :: Proxy (ErrorSym0 k06989586621679402464 k6989586621679402466) t -> () Source #

type Apply k0 k2 (ErrorSym0 k0 k2) l Source # 
type Apply k0 k2 (ErrorSym0 k0 k2) l = Error k0 k2 l

type LTSym0 = LT Source #

type EQSym0 = EQ Source #

type GTSym0 = GT Source #

type Tuple0Sym0 = '() Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple2Sym0 a3530822107858468865 b3530822107858468866) t -> () Source #

type Apply a3530822107858468865 (TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> Type) (Tuple2Sym0 a3530822107858468865 b3530822107858468866) l Source # 
type Apply a3530822107858468865 (TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> Type) (Tuple2Sym0 a3530822107858468865 b3530822107858468866) l = Tuple2Sym1 a3530822107858468865 b3530822107858468866 l

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple2Sym1 a3530822107858468865 b3530822107858468866) t -> () Source #

type Apply k1 (k2, k1) (Tuple2Sym1 k2 k1 l1) l2 Source # 
type Apply k1 (k2, k1) (Tuple2Sym1 k2 k1 l1) l2 = (,) k2 k1 l1 l2

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867) t -> () Source #

type Apply a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> Type) (Tuple3Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867) l Source # 
type Apply a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> Type) (Tuple3Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867) l = Tuple3Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 l

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867) t -> () Source #

type Apply b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) (Tuple3Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 l1) l2 Source # 
type Apply b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) (Tuple3Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 l1) l2 = Tuple3Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 l1 l2

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867) t -> () Source #

type Apply k3 (k2, k1, k3) (Tuple3Sym2 k2 k1 k3 l1 l2) l3 Source # 
type Apply k3 (k2, k1, k3) (Tuple3Sym2 k2 k1 k3 l1 l2) l3 = (,,) k2 k1 k3 l1 l2 l3

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) t -> () Source #

type Apply a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> Type) (Tuple4Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) l Source # 
type Apply a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> Type) (Tuple4Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) l = Tuple4Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 l

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) t -> () Source #

type Apply b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) (Tuple4Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 l1) l2 Source # 
type Apply b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) (Tuple4Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 l1) l2 = Tuple4Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 l1 l2

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) t -> () Source #

type Apply c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) (Tuple4Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 l1 l2) l3 Source # 
type Apply c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) (Tuple4Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 l1 l2) l3 = Tuple4Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 l1 l2 l3

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) t -> () Source #

type Apply k4 (k2, k1, k3, k4) (Tuple4Sym3 k2 k1 k3 k4 l1 l2 l3) l4 Source # 
type Apply k4 (k2, k1, k3, k4) (Tuple4Sym3 k2 k1 k3 k4 l1 l2 l3) l4 = (,,,) k2 k1 k3 k4 l1 l2 l3 l4

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () Source #

type Apply a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> Type) (Tuple5Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) l Source # 
type Apply a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> Type) (Tuple5Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) l = Tuple5Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 l

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () Source #

type Apply b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) (Tuple5Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 l1) l2 Source # 
type Apply b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) (Tuple5Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 l1) l2 = Tuple5Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 l1 l2

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () Source #

type Apply c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) (Tuple5Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 l1 l2) l3 Source # 
type Apply c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) (Tuple5Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 l1 l2) l3 = Tuple5Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 l1 l2 l3

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () Source #

type Apply d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) (Tuple5Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 l1 l2 l3) l4 Source # 
type Apply d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) (Tuple5Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 l1 l2 l3) l4 = Tuple5Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 l1 l2 l3 l4

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () Source #

type Apply k5 (k2, k1, k3, k4, k5) (Tuple5Sym4 k2 k1 k3 k4 k5 l1 l2 l3 l4) l5 Source # 
type Apply k5 (k2, k1, k3, k4, k5) (Tuple5Sym4 k2 k1 k3 k4 k5 l1 l2 l3 l4) l5 = (,,,,) k2 k1 k3 k4 k5 l1 l2 l3 l4 l5

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

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

Instances

SuppressUnusedWarnings (TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple6Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () Source #

type Apply a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple6Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) l Source # 
type Apply a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple6Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) l = Tuple6Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 l

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

Instances

SuppressUnusedWarnings (a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple6Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () Source #

type Apply b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) (Tuple6Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 l1) l2 Source # 
type Apply b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) (Tuple6Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 l1) l2 = Tuple6Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 l1 l2

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

Instances

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> *) (Tuple6Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () Source #

type Apply c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) (Tuple6Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 l1 l2) l3 Source # 
type Apply c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) (Tuple6Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 l1 l2) l3 = Tuple6Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 l1 l2 l3

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () Source #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () Source #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym5 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () Source #

type Apply k6 (k2, k1, k3, k4, k5, k6) (Tuple6Sym5 k2 k1 k3 k4 k5 k6 l1 l2 l3 l4 l5) l6 Source # 
type Apply k6 (k2, k1, k3, k4, k5, k6) (Tuple6Sym5 k2 k1 k3 k4 k5 k6 l1 l2 l3 l4 l5) l6 = (,,,,,) k2 k1 k3 k4 k5 k6 l1 l2 l3 l4 l5 l6

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

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

Instances

SuppressUnusedWarnings (TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

type Apply a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) l Source # 
type Apply a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) l = Tuple7Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871 l

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

Instances

SuppressUnusedWarnings (a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

type Apply b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871 l1) l2 Source # 
type Apply b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) (Tuple7Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871 l1) l2 = Tuple7Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871 l1 l2

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

Instances

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

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

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

Instances

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> *) (Tuple7Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

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

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

Instances

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> *) (Tuple7Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym5 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym6 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

type Apply k7 (k2, k1, k3, k4, k5, k6, k7) (Tuple7Sym6 k2 k1 k3 k4 k5 k6 k7 l1 l2 l3 l4 l5 l6) l7 Source # 
type Apply k7 (k2, k1, k3, k4, k5, k6, k7) (Tuple7Sym6 k2 k1 k3 k4 k5 k6 k7 l1 l2 l3 l4 l5 l6) l7 = (,,,,,,) k2 k1 k3 k4 k5 k6 k7 l1 l2 l3 l4 l5 l6 l7

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

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

Instances

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

Methods

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

type Apply a6989586621679312550 (TyFun a6989586621679312550 Ordering -> Type) (CompareSym0 a6989586621679312550) l Source # 
type Apply a6989586621679312550 (TyFun a6989586621679312550 Ordering -> Type) (CompareSym0 a6989586621679312550) l = CompareSym1 a6989586621679312550 l

data FoldlSym0 (l :: TyFun (TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679242245 b6989586621679242246) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym0 a6989586621679242245 b6989586621679242246) t -> () Source #

type Apply (TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type) -> Type) (FoldlSym0 a6989586621679242245 b6989586621679242246) l Source # 
type Apply (TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type) -> Type) (FoldlSym0 a6989586621679242245 b6989586621679242246) l = FoldlSym1 a6989586621679242245 b6989586621679242246 l

class SuppressUnusedWarnings (t :: k) where Source #

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

Minimal complete definition

suppressUnusedWarnings

Instances

SuppressUnusedWarnings (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 Nat Constraint -> *) KnownNatSym0 Source # 
SuppressUnusedWarnings (TyFun Symbol Constraint -> *) KnownSymbolSym0 Source # 
SuppressUnusedWarnings (TyFun (NonEmpty Bool) Bool -> *) XorSym0 Source # 
SuppressUnusedWarnings ((TyFun a6989586621679445674 Bool -> Type) -> (TyFun a6989586621679445674 a6989586621679445674 -> Type) -> TyFun a6989586621679445674 a6989586621679445674 -> *) (UntilSym2 a6989586621679445674) Source # 

Methods

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

SuppressUnusedWarnings ((TyFun a6989586621679445674 Bool -> Type) -> TyFun (TyFun a6989586621679445674 a6989586621679445674 -> Type) (TyFun a6989586621679445674 a6989586621679445674 -> Type) -> *) (UntilSym1 a6989586621679445674) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings ((TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729602) (NonEmpty a6989586621679729602) -> *) (NubBySym1 a6989586621679729602) Source # 

Methods

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

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

Methods

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

SuppressUnusedWarnings ((TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617)) -> *) (GroupBy1Sym1 a6989586621679729617) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupBy1Sym1 a6989586621679729617) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings ((TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729600) (NonEmpty a6989586621679729600) -> *) (SortBySym1 a6989586621679729600) Source # 

Methods

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

SuppressUnusedWarnings ((TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637) -> *) (Scanl1Sym1 a6989586621679729637) Source # 

Methods

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

SuppressUnusedWarnings ((TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636) -> *) (Scanr1Sym1 a6989586621679729636) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (a6989586621679075408 -> TyFun [a6989586621679075408] (NonEmpty a6989586621679075408) -> *) ((:|$$) a6989586621679075408) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:|$$) a6989586621679075408) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (a6989586621679729635 -> TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635) -> *) (IntersperseSym1 a6989586621679729635) Source # 

Methods

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

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

Methods

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

SuppressUnusedWarnings (a6989586621679729653 -> TyFun (NonEmpty a6989586621679729653) (NonEmpty a6989586621679729653) -> *) ((:<|$$) a6989586621679729653) Source # 

Methods

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

SuppressUnusedWarnings (a6989586621679729652 -> TyFun (NonEmpty a6989586621679729652) (NonEmpty a6989586621679729652) -> *) (ConsSym1 a6989586621679729652) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConsSym1 a6989586621679729652) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (NonEmpty a6989586621679729611 -> TyFun Nat a6989586621679729611 -> *) ((:!!$$) a6989586621679729611) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729602) (NonEmpty a6989586621679729602) -> Type) -> *) (NubBySym0 a6989586621679729602) Source # 

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617)) -> Type) -> *) (GroupBy1Sym0 a6989586621679729617) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupBy1Sym0 a6989586621679729617) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679729600) (NonEmpty a6989586621679729600) -> Type) -> *) (SortBySym0 a6989586621679729600) Source # 

Methods

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

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637) -> Type) -> *) (Scanl1Sym0 a6989586621679729637) Source # 

Methods

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

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636) -> Type) -> *) (Scanr1Sym0 a6989586621679729636) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun [a6989586621679729650] (NonEmpty a6989586621679729650) -> *) (FromListSym0 a6989586621679729650) Source # 

Methods

suppressUnusedWarnings :: Proxy (FromListSym0 a6989586621679729650) t -> () Source #

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun [a6989586621679729661] (Maybe (NonEmpty a6989586621679729661)) -> *) (NonEmpty_Sym0 a6989586621679729661) Source # 

Methods

suppressUnusedWarnings :: Proxy (NonEmpty_Sym0 a6989586621679729661) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun a6989586621679075408 (TyFun [a6989586621679075408] (NonEmpty a6989586621679075408) -> Type) -> *) ((:|$) a6989586621679075408) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:|$) a6989586621679075408) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy (InsertSym0 a6989586621679458088) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (DeleteSym0 a6989586621679458115) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (ElemIndicesSym0 a6989586621679458104) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun a6989586621679729635 (TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635) -> Type) -> *) (IntersperseSym0 a6989586621679729635) Source # 

Methods

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

SuppressUnusedWarnings (TyFun a6989586621679729642 (TyFun [a6989586621679729642] (NonEmpty a6989586621679729642) -> Type) -> *) (InsertSym0 a6989586621679729642) Source # 

Methods

suppressUnusedWarnings :: Proxy (InsertSym0 a6989586621679729642) t -> () Source #

SuppressUnusedWarnings (TyFun a6989586621679729653 (TyFun (NonEmpty a6989586621679729653) (NonEmpty a6989586621679729653) -> Type) -> *) ((:<|$) a6989586621679729653) Source # 

Methods

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

SuppressUnusedWarnings (TyFun a6989586621679729652 (TyFun (NonEmpty a6989586621679729652) (NonEmpty a6989586621679729652) -> Type) -> *) (ConsSym0 a6989586621679729652) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConsSym0 a6989586621679729652) t -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729603) (NonEmpty a6989586621679729603) -> *) (NubSym0 a6989586621679729603) Source # 

Methods

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

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729611) (TyFun Nat a6989586621679729611 -> Type) -> *) ((:!!$) a6989586621679729611) Source # 

Methods

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

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729618) (NonEmpty (NonEmpty a6989586621679729618)) -> *) (Group1Sym0 a6989586621679729618) Source # 

Methods

suppressUnusedWarnings :: Proxy (Group1Sym0 a6989586621679729618) t -> () Source #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729649) [a6989586621679729649] -> *) (ToListSym0 a6989586621679729649) Source # 

Methods

suppressUnusedWarnings :: Proxy (ToListSym0 a6989586621679729649) t -> () Source #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729634) (NonEmpty a6989586621679729634) -> *) (ReverseSym0 a6989586621679729634) Source # 

Methods

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

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729651) (NonEmpty a6989586621679729651) -> *) (SortSym0 a6989586621679729651) Source # 

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729655) a6989586621679729655 -> *) (LastSym0 a6989586621679729655) Source # 

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729657) a6989586621679729657 -> *) (HeadSym0 a6989586621679729657) Source # 

Methods

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

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729660) (a6989586621679729660, Maybe (NonEmpty a6989586621679729660)) -> *) (UnconsSym0 a6989586621679729660) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnconsSym0 a6989586621679729660) t -> () Source #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729664) Nat -> *) (LengthSym0 a6989586621679729664) Source # 

Methods

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

SuppressUnusedWarnings (TyFun (NonEmpty (NonEmpty a6989586621679729601)) (NonEmpty (NonEmpty a6989586621679729601)) -> *) (TransposeSym0 a6989586621679729601) Source # 

Methods

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

SuppressUnusedWarnings ((TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) -> b6989586621679242246 -> TyFun [a6989586621679242245] b6989586621679242246 -> *) (FoldlSym2 a6989586621679242245 b6989586621679242246) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym2 a6989586621679242245 b6989586621679242246) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) -> TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type) -> *) (FoldlSym1 a6989586621679242245 b6989586621679242246) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym1 a6989586621679242245 b6989586621679242246) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679281046 b6989586621679281047 -> Type) -> TyFun [a6989586621679281046] [b6989586621679281047] -> *) (MapSym1 a6989586621679281046 b6989586621679281047) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a6989586621679281046 b6989586621679281047) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) -> b6989586621679281049 -> TyFun [a6989586621679281048] b6989586621679281049 -> *) (FoldrSym2 a6989586621679281048 b6989586621679281049) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym2 a6989586621679281048 b6989586621679281049) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) -> TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type) -> *) (FoldrSym1 a6989586621679281048 b6989586621679281049) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym1 a6989586621679281048 b6989586621679281049) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679312540 a6989586621679312539 -> Type) -> b6989586621679312540 -> TyFun b6989586621679312540 Ordering -> *) (ComparingSym2 a6989586621679312539 b6989586621679312540) Source # 

Methods

suppressUnusedWarnings :: Proxy (ComparingSym2 a6989586621679312539 b6989586621679312540) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679312540 a6989586621679312539 -> Type) -> TyFun b6989586621679312540 (TyFun b6989586621679312540 Ordering -> Type) -> *) (ComparingSym1 a6989586621679312539 b6989586621679312540) Source # 

Methods

suppressUnusedWarnings :: Proxy (ComparingSym1 a6989586621679312539 b6989586621679312540) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679427549 (Maybe b6989586621679427550) -> Type) -> TyFun [a6989586621679427549] [b6989586621679427550] -> *) (MapMaybeSym1 a6989586621679427549 b6989586621679427550) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapMaybeSym1 a6989586621679427549 b6989586621679427550) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) -> TyFun b6989586621679458162 [a6989586621679458163] -> *) (UnfoldrSym1 b6989586621679458162 a6989586621679458163) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 b6989586621679458162 a6989586621679458163) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) -> TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type) -> *) (ScanrSym1 a6989586621679458171 b6989586621679458172) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a6989586621679458171 b6989586621679458172) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) -> b6989586621679458172 -> TyFun [a6989586621679458171] [b6989586621679458172] -> *) (ScanrSym2 a6989586621679458171 b6989586621679458172) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a6989586621679458171 b6989586621679458172) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) -> TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type) -> *) (ScanlSym1 a6989586621679458175 b6989586621679458174) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a6989586621679458175 b6989586621679458174) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) -> b6989586621679458174 -> TyFun [a6989586621679458175] [b6989586621679458174] -> *) (ScanlSym2 a6989586621679458175 b6989586621679458174) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a6989586621679458175 b6989586621679458174) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679458177 [b6989586621679458178] -> Type) -> TyFun [a6989586621679458177] [b6989586621679458178] -> *) (ConcatMapSym1 a6989586621679458177 b6989586621679458178) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym1 a6989586621679458177 b6989586621679458178) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) -> b6989586621679458184 -> TyFun [a6989586621679458183] b6989586621679458184 -> *) (Foldl'Sym2 a6989586621679458183 b6989586621679458184) Source # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym2 a6989586621679458183 b6989586621679458184) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) -> TyFun b6989586621679458184 (TyFun [a6989586621679458183] b6989586621679458184 -> Type) -> *) (Foldl'Sym1 a6989586621679458183 b6989586621679458184) Source # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym1 a6989586621679458183 b6989586621679458184) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679729622 b6989586621679729621 -> Type) -> TyFun [a6989586621679729622] [NonEmpty a6989586621679729622] -> *) (GroupWithSym1 b6989586621679729621 a6989586621679729622) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupWithSym1 b6989586621679729621 a6989586621679729622) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679729620 b6989586621679729619 -> Type) -> TyFun [a6989586621679729620] [NonEmpty a6989586621679729620] -> *) (GroupAllWithSym1 b6989586621679729619 a6989586621679729620) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWithSym1 b6989586621679729619 a6989586621679729620) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679729616 b6989586621679729615 -> Type) -> TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)) -> *) (GroupWith1Sym1 b6989586621679729615 a6989586621679729616) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupWith1Sym1 b6989586621679729615 a6989586621679729616) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679729645 b6989586621679729646 -> Type) -> TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646) -> *) (MapSym1 a6989586621679729645 b6989586621679729646) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a6989586621679729645 b6989586621679729646) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679729599 o6989586621679729598 -> Type) -> TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599) -> *) (SortWithSym1 o6989586621679729598 a6989586621679729599) Source # 

Methods

suppressUnusedWarnings :: Proxy (SortWithSym1 o6989586621679729598 a6989586621679729599) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679729614 b6989586621679729613 -> Type) -> TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)) -> *) (GroupAllWith1Sym1 b6989586621679729613 a6989586621679729614) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWith1Sym1 b6989586621679729613 a6989586621679729614) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) -> b6989586621679729640 -> TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> *) (ScanlSym2 a6989586621679729641 b6989586621679729640) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a6989586621679729641 b6989586621679729640) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) -> TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) -> *) (ScanlSym1 a6989586621679729641 b6989586621679729640) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a6989586621679729641 b6989586621679729640) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) -> b6989586621679729639 -> TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> *) (ScanrSym2 a6989586621679729638 b6989586621679729639) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a6989586621679729638 b6989586621679729639) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) -> TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) -> *) (ScanrSym1 a6989586621679729638 b6989586621679729639) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a6989586621679729638 b6989586621679729639) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) -> TyFun a6989586621679729658 (NonEmpty b6989586621679729659) -> *) (UnfoldrSym1 a6989586621679729658 b6989586621679729659) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 a6989586621679729658 b6989586621679729659) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) -> TyFun a6989586621679729662 (NonEmpty b6989586621679729663) -> *) (UnfoldSym1 a6989586621679729662 b6989586621679729663) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldSym1 a6989586621679729662 b6989586621679729663) t -> () Source #

SuppressUnusedWarnings ([a6989586621679458153] -> TyFun [b6989586621679458154] [(a6989586621679458153, b6989586621679458154)] -> *) (ZipSym1 a6989586621679458153 b6989586621679458154) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 a6989586621679458153 b6989586621679458154) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876654] -> TyFun i6989586621679876653 a6989586621679876654 -> *) (GenericIndexSym1 i6989586621679876653 a6989586621679876654) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym1 i6989586621679876653 a6989586621679876654) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple2Sym1 a3530822107858468865 b3530822107858468866) t -> () Source #

SuppressUnusedWarnings (a6989586621679281033 -> TyFun b6989586621679281034 b6989586621679281034 -> *) (SeqSym1 a6989586621679281033 b6989586621679281034) Source # 

Methods

suppressUnusedWarnings :: Proxy (SeqSym1 a6989586621679281033 b6989586621679281034) t -> () Source #

SuppressUnusedWarnings (a6989586621679281042 -> TyFun b6989586621679281043 a6989586621679281042 -> *) (ConstSym1 b6989586621679281043 a6989586621679281042) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConstSym1 b6989586621679281043 a6989586621679281042) t -> () Source #

SuppressUnusedWarnings (a6989586621679292901 -> TyFun (TyFun a6989586621679292901 b6989586621679292902 -> Type) b6989586621679292902 -> *) ((:&$$) a6989586621679292901 b6989586621679292902) Source # 

Methods

suppressUnusedWarnings :: Proxy (a6989586621679292901 :&$$ b6989586621679292902) t -> () Source #

SuppressUnusedWarnings (b6989586621679426444 -> (TyFun a6989586621679426445 b6989586621679426444 -> Type) -> TyFun (Maybe a6989586621679426445) b6989586621679426444 -> *) (Maybe_Sym2 a6989586621679426445 b6989586621679426444) Source # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym2 a6989586621679426445 b6989586621679426444) t -> () Source #

SuppressUnusedWarnings (b6989586621679426444 -> TyFun (TyFun a6989586621679426445 b6989586621679426444 -> Type) (TyFun (Maybe a6989586621679426445) b6989586621679426444 -> Type) -> *) (Maybe_Sym1 a6989586621679426445 b6989586621679426444) Source # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym1 a6989586621679426445 b6989586621679426444) t -> () Source #

SuppressUnusedWarnings (a6989586621679458084 -> TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085) -> *) (LookupSym1 a6989586621679458084 b6989586621679458085) Source # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym1 a6989586621679458084 b6989586621679458085) t -> () Source #

SuppressUnusedWarnings (i6989586621679876651 -> TyFun a6989586621679876652 [a6989586621679876652] -> *) (GenericReplicateSym1 i6989586621679876651 a6989586621679876652) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym1 i6989586621679876651 a6989586621679876652) t -> () Source #

SuppressUnusedWarnings (i6989586621679876655 -> TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]) -> *) (GenericSplitAtSym1 i6989586621679876655 a6989586621679876656) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym1 i6989586621679876655 a6989586621679876656) t -> () Source #

SuppressUnusedWarnings (i6989586621679876657 -> TyFun [a6989586621679876658] [a6989586621679876658] -> *) (GenericDropSym1 i6989586621679876657 a6989586621679876658) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym1 i6989586621679876657 a6989586621679876658) t -> () Source #

SuppressUnusedWarnings (i6989586621679876659 -> TyFun [a6989586621679876660] [a6989586621679876660] -> *) (GenericTakeSym1 i6989586621679876659 a6989586621679876660) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym1 i6989586621679876659 a6989586621679876660) t -> () Source #

SuppressUnusedWarnings (NonEmpty a6989586621679729609 -> TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610)) -> *) (ZipSym1 a6989586621679729609 b6989586621679729610) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 a6989586621679729609 b6989586621679729610) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679242245 b6989586621679242246) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym0 a6989586621679242245 b6989586621679242246) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679281046 b6989586621679281047 -> Type) (TyFun [a6989586621679281046] [b6989586621679281047] -> Type) -> *) (MapSym0 a6989586621679281046 b6989586621679281047) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a6989586621679281046 b6989586621679281047) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type) -> Type) -> *) (FoldrSym0 a6989586621679281048 b6989586621679281049) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym0 a6989586621679281048 b6989586621679281049) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679312540 a6989586621679312539 -> Type) (TyFun b6989586621679312540 (TyFun b6989586621679312540 Ordering -> Type) -> Type) -> *) (ComparingSym0 a6989586621679312539 b6989586621679312540) Source # 

Methods

suppressUnusedWarnings :: Proxy (ComparingSym0 a6989586621679312539 b6989586621679312540) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679427549 (Maybe b6989586621679427550) -> Type) (TyFun [a6989586621679427549] [b6989586621679427550] -> Type) -> *) (MapMaybeSym0 a6989586621679427549 b6989586621679427550) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapMaybeSym0 a6989586621679427549 b6989586621679427550) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) (TyFun b6989586621679458162 [a6989586621679458163] -> Type) -> *) (UnfoldrSym0 b6989586621679458162 a6989586621679458163) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 b6989586621679458162 a6989586621679458163) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type) -> Type) -> *) (ScanrSym0 a6989586621679458171 b6989586621679458172) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a6989586621679458171 b6989586621679458172) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type) -> Type) -> *) (ScanlSym0 a6989586621679458175 b6989586621679458174) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a6989586621679458175 b6989586621679458174) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679458177 [b6989586621679458178] -> Type) (TyFun [a6989586621679458177] [b6989586621679458178] -> Type) -> *) (ConcatMapSym0 a6989586621679458177 b6989586621679458178) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym0 a6989586621679458177 b6989586621679458178) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (TyFun b6989586621679458184 (TyFun [a6989586621679458183] b6989586621679458184 -> Type) -> Type) -> *) (Foldl'Sym0 a6989586621679458183 b6989586621679458184) Source # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym0 a6989586621679458183 b6989586621679458184) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729622 b6989586621679729621 -> Type) (TyFun [a6989586621679729622] [NonEmpty a6989586621679729622] -> Type) -> *) (GroupWithSym0 b6989586621679729621 a6989586621679729622) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupWithSym0 b6989586621679729621 a6989586621679729622) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729620 b6989586621679729619 -> Type) (TyFun [a6989586621679729620] [NonEmpty a6989586621679729620] -> Type) -> *) (GroupAllWithSym0 b6989586621679729619 a6989586621679729620) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWithSym0 b6989586621679729619 a6989586621679729620) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729616 b6989586621679729615 -> Type) (TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)) -> Type) -> *) (GroupWith1Sym0 b6989586621679729615 a6989586621679729616) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupWith1Sym0 b6989586621679729615 a6989586621679729616) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729645 b6989586621679729646 -> Type) (TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646) -> Type) -> *) (MapSym0 a6989586621679729645 b6989586621679729646) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a6989586621679729645 b6989586621679729646) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729599 o6989586621679729598 -> Type) (TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599) -> Type) -> *) (SortWithSym0 o6989586621679729598 a6989586621679729599) Source # 

Methods

suppressUnusedWarnings :: Proxy (SortWithSym0 o6989586621679729598 a6989586621679729599) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729614 b6989586621679729613 -> Type) (TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)) -> Type) -> *) (GroupAllWith1Sym0 b6989586621679729613 a6989586621679729614) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWith1Sym0 b6989586621679729613 a6989586621679729614) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) -> Type) -> *) (ScanlSym0 a6989586621679729641 b6989586621679729640) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a6989586621679729641 b6989586621679729640) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) -> Type) -> *) (ScanrSym0 a6989586621679729638 b6989586621679729639) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a6989586621679729638 b6989586621679729639) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (TyFun a6989586621679729658 (NonEmpty b6989586621679729659) -> Type) -> *) (UnfoldrSym0 a6989586621679729658 b6989586621679729659) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 a6989586621679729658 b6989586621679729659) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) (TyFun a6989586621679729662 (NonEmpty b6989586621679729663) -> Type) -> *) (UnfoldSym0 a6989586621679729662 b6989586621679729663) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldSym0 a6989586621679729662 b6989586621679729663) t -> () Source #

SuppressUnusedWarnings (TyFun [Either a6989586621679437399 b6989586621679437400] [b6989586621679437400] -> *) (RightsSym0 a6989586621679437399 b6989586621679437400) Source # 

Methods

suppressUnusedWarnings :: Proxy (RightsSym0 a6989586621679437399 b6989586621679437400) t -> () Source #

SuppressUnusedWarnings (TyFun [Either a6989586621679437401 b6989586621679437402] [a6989586621679437401] -> *) (LeftsSym0 b6989586621679437402 a6989586621679437401) Source # 

Methods

suppressUnusedWarnings :: Proxy (LeftsSym0 b6989586621679437402 a6989586621679437401) t -> () Source #

SuppressUnusedWarnings (TyFun [(a6989586621679458141, b6989586621679458142)] ([a6989586621679458141], [b6989586621679458142]) -> *) (UnzipSym0 a6989586621679458141 b6989586621679458142) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a6989586621679458141 b6989586621679458142) t -> () Source #

SuppressUnusedWarnings (TyFun [a6989586621679458070] i6989586621679458069 -> *) (GenericLengthSym0 a6989586621679458070 i6989586621679458069) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericLengthSym0 a6989586621679458070 i6989586621679458069) t -> () Source #

SuppressUnusedWarnings (TyFun [a6989586621679458153] (TyFun [b6989586621679458154] [(a6989586621679458153, b6989586621679458154)] -> Type) -> *) (ZipSym0 a6989586621679458153 b6989586621679458154) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a6989586621679458153 b6989586621679458154) t -> () Source #

SuppressUnusedWarnings (TyFun [a6989586621679876654] (TyFun i6989586621679876653 a6989586621679876654 -> Type) -> *) (GenericIndexSym0 i6989586621679876653 a6989586621679876654) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym0 i6989586621679876653 a6989586621679876654) t -> () Source #

SuppressUnusedWarnings (TyFun (Either a6989586621679437393 b6989586621679437394) Bool -> *) (IsRightSym0 a6989586621679437393 b6989586621679437394) Source # 

Methods

suppressUnusedWarnings :: Proxy (IsRightSym0 a6989586621679437393 b6989586621679437394) t -> () Source #

SuppressUnusedWarnings (TyFun (Either a6989586621679437395 b6989586621679437396) Bool -> *) (IsLeftSym0 a6989586621679437395 b6989586621679437396) Source # 

Methods

suppressUnusedWarnings :: Proxy (IsLeftSym0 a6989586621679437395 b6989586621679437396) t -> () Source #

SuppressUnusedWarnings (TyFun (a6989586621679422498, b6989586621679422499) (b6989586621679422499, a6989586621679422498) -> *) (SwapSym0 b6989586621679422499 a6989586621679422498) Source # 

Methods

suppressUnusedWarnings :: Proxy (SwapSym0 b6989586621679422499 a6989586621679422498) t -> () Source #

SuppressUnusedWarnings (TyFun (a6989586621679422506, b6989586621679422507) b6989586621679422507 -> *) (SndSym0 a6989586621679422506 b6989586621679422507) Source # 

Methods

suppressUnusedWarnings :: Proxy (SndSym0 a6989586621679422506 b6989586621679422507) t -> () Source #

SuppressUnusedWarnings (TyFun (a6989586621679422508, b6989586621679422509) a6989586621679422508 -> *) (FstSym0 b6989586621679422509 a6989586621679422508) Source # 

Methods

suppressUnusedWarnings :: Proxy (FstSym0 b6989586621679422509 a6989586621679422508) t -> () Source #

SuppressUnusedWarnings (TyFun a6989586621679075399 (Either a6989586621679075399 b6989586621679075400) -> *) (LeftSym0 a6989586621679075399 b6989586621679075400) Source # 

Methods

suppressUnusedWarnings :: Proxy (LeftSym0 a6989586621679075399 b6989586621679075400) t -> () Source #

SuppressUnusedWarnings (TyFun b6989586621679075400 (Either a6989586621679075399 b6989586621679075400) -> *) (RightSym0 a6989586621679075399 b6989586621679075400) Source # 

Methods

suppressUnusedWarnings :: Proxy (RightSym0 a6989586621679075399 b6989586621679075400) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple2Sym0 a3530822107858468865 b3530822107858468866) t -> () Source #

SuppressUnusedWarnings (TyFun a6989586621679281033 (TyFun b6989586621679281034 b6989586621679281034 -> Type) -> *) (SeqSym0 a6989586621679281033 b6989586621679281034) Source # 

Methods

suppressUnusedWarnings :: Proxy (SeqSym0 a6989586621679281033 b6989586621679281034) t -> () Source #

SuppressUnusedWarnings (TyFun a6989586621679281042 (TyFun b6989586621679281043 a6989586621679281042 -> Type) -> *) (ConstSym0 b6989586621679281043 a6989586621679281042) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConstSym0 b6989586621679281043 a6989586621679281042) t -> () Source #

SuppressUnusedWarnings (TyFun a6989586621679292901 (TyFun (TyFun a6989586621679292901 b6989586621679292902 -> Type) b6989586621679292902 -> Type) -> *) ((:&$) a6989586621679292901 b6989586621679292902) Source # 

Methods

suppressUnusedWarnings :: Proxy (a6989586621679292901 :&$ b6989586621679292902) t -> () Source #

SuppressUnusedWarnings (TyFun k06989586621679402464 k6989586621679402466 -> *) (ErrorSym0 k06989586621679402464 k6989586621679402466) Source # 

Methods

suppressUnusedWarnings :: Proxy (ErrorSym0 k06989586621679402464 k6989586621679402466) t -> () Source #

SuppressUnusedWarnings (TyFun b6989586621679426444 (TyFun (TyFun a6989586621679426445 b6989586621679426444 -> Type) (TyFun (Maybe a6989586621679426445) b6989586621679426444 -> Type) -> Type) -> *) (Maybe_Sym0 a6989586621679426445 b6989586621679426444) Source # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym0 a6989586621679426445 b6989586621679426444) t -> () Source #

SuppressUnusedWarnings (TyFun a6989586621679458084 (TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085) -> Type) -> *) (LookupSym0 a6989586621679458084 b6989586621679458085) Source # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym0 a6989586621679458084 b6989586621679458085) t -> () Source #

SuppressUnusedWarnings (TyFun i6989586621679876651 (TyFun a6989586621679876652 [a6989586621679876652] -> Type) -> *) (GenericReplicateSym0 i6989586621679876651 a6989586621679876652) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym0 i6989586621679876651 a6989586621679876652) t -> () Source #

SuppressUnusedWarnings (TyFun i6989586621679876655 (TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]) -> Type) -> *) (GenericSplitAtSym0 i6989586621679876655 a6989586621679876656) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym0 i6989586621679876655 a6989586621679876656) t -> () Source #

SuppressUnusedWarnings (TyFun i6989586621679876657 (TyFun [a6989586621679876658] [a6989586621679876658] -> Type) -> *) (GenericDropSym0 i6989586621679876657 a6989586621679876658) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym0 i6989586621679876657 a6989586621679876658) t -> () Source #

SuppressUnusedWarnings (TyFun i6989586621679876659 (TyFun [a6989586621679876660] [a6989586621679876660] -> Type) -> *) (GenericTakeSym0 i6989586621679876659 a6989586621679876660) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym0 i6989586621679876659 a6989586621679876660) t -> () Source #

SuppressUnusedWarnings (TyFun (NonEmpty (a6989586621679729604, b6989586621679729605)) (NonEmpty a6989586621679729604, NonEmpty b6989586621679729605) -> *) (UnzipSym0 a6989586621679729604 b6989586621679729605) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a6989586621679729604 b6989586621679729605) t -> () Source #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729609) (TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610)) -> Type) -> *) (ZipSym0 a6989586621679729609 b6989586621679729610) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a6989586621679729609 b6989586621679729610) t -> () Source #

SuppressUnusedWarnings ((TyFun (a6989586621679422503, b6989586621679422504) c6989586621679422505 -> Type) -> a6989586621679422503 -> TyFun b6989586621679422504 c6989586621679422505 -> *) (CurrySym2 a6989586621679422503 b6989586621679422504 c6989586621679422505) Source # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym2 a6989586621679422503 b6989586621679422504 c6989586621679422505) t -> () Source #

SuppressUnusedWarnings ((TyFun (a6989586621679422503, b6989586621679422504) c6989586621679422505 -> Type) -> TyFun a6989586621679422503 (TyFun b6989586621679422504 c6989586621679422505 -> Type) -> *) (CurrySym1 a6989586621679422503 b6989586621679422504 c6989586621679422505) Source # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym1 a6989586621679422503 b6989586621679422504 c6989586621679422505) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679281036 (TyFun b6989586621679281037 c6989586621679281038 -> Type) -> Type) -> b6989586621679281037 -> TyFun a6989586621679281036 c6989586621679281038 -> *) (FlipSym2 b6989586621679281037 a6989586621679281036 c6989586621679281038) Source # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym2 b6989586621679281037 a6989586621679281036 c6989586621679281038) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679281036 (TyFun b6989586621679281037 c6989586621679281038 -> Type) -> Type) -> TyFun b6989586621679281037 (TyFun a6989586621679281036 c6989586621679281038 -> Type) -> *) (FlipSym1 b6989586621679281037 a6989586621679281036 c6989586621679281038) Source # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym1 b6989586621679281037 a6989586621679281036 c6989586621679281038) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679281039 c6989586621679281040 -> Type) -> (TyFun a6989586621679281041 b6989586621679281039 -> Type) -> TyFun a6989586621679281041 c6989586621679281040 -> *) ((:.$$$) b6989586621679281039 a6989586621679281041 c6989586621679281040) Source # 

Methods

suppressUnusedWarnings :: Proxy ((b6989586621679281039 :.$$$ a6989586621679281041) c6989586621679281040) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679281039 c6989586621679281040 -> Type) -> TyFun (TyFun a6989586621679281041 b6989586621679281039 -> Type) (TyFun a6989586621679281041 c6989586621679281040 -> Type) -> *) ((:.$$) b6989586621679281039 a6989586621679281041 c6989586621679281040) Source # 

Methods

suppressUnusedWarnings :: Proxy ((b6989586621679281039 :.$$ a6989586621679281041) c6989586621679281040) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679292903 (TyFun b6989586621679292903 c6989586621679292904 -> Type) -> Type) -> (TyFun a6989586621679292905 b6989586621679292903 -> Type) -> a6989586621679292905 -> TyFun a6989586621679292905 c6989586621679292904 -> *) (OnSym3 b6989586621679292903 a6989586621679292905 c6989586621679292904) Source # 

Methods

suppressUnusedWarnings :: Proxy (OnSym3 b6989586621679292903 a6989586621679292905 c6989586621679292904) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679292903 (TyFun b6989586621679292903 c6989586621679292904 -> Type) -> Type) -> (TyFun a6989586621679292905 b6989586621679292903 -> Type) -> TyFun a6989586621679292905 (TyFun a6989586621679292905 c6989586621679292904 -> Type) -> *) (OnSym2 b6989586621679292903 a6989586621679292905 c6989586621679292904) Source # 

Methods

suppressUnusedWarnings :: Proxy (OnSym2 b6989586621679292903 a6989586621679292905 c6989586621679292904) t -> () Source #

SuppressUnusedWarnings ((TyFun b6989586621679292903 (TyFun b6989586621679292903 c6989586621679292904 -> Type) -> Type) -> TyFun (TyFun a6989586621679292905 b6989586621679292903 -> Type) (TyFun a6989586621679292905 (TyFun a6989586621679292905 c6989586621679292904 -> Type) -> Type) -> *) (OnSym1 b6989586621679292903 a6989586621679292905 c6989586621679292904) Source # 

Methods

suppressUnusedWarnings :: Proxy (OnSym1 b6989586621679292903 a6989586621679292905 c6989586621679292904) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679422500 (TyFun b6989586621679422501 c6989586621679422502 -> Type) -> Type) -> TyFun (a6989586621679422500, b6989586621679422501) c6989586621679422502 -> *) (UncurrySym1 a6989586621679422500 b6989586621679422501 c6989586621679422502) Source # 

Methods

suppressUnusedWarnings :: Proxy (UncurrySym1 a6989586621679422500 b6989586621679422501 c6989586621679422502) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679436289 c6989586621679436290 -> Type) -> (TyFun b6989586621679436291 c6989586621679436290 -> Type) -> TyFun (Either a6989586621679436289 b6989586621679436291) c6989586621679436290 -> *) (Either_Sym2 a6989586621679436289 b6989586621679436291 c6989586621679436290) Source # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym2 a6989586621679436289 b6989586621679436291 c6989586621679436290) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679436289 c6989586621679436290 -> Type) -> TyFun (TyFun b6989586621679436291 c6989586621679436290 -> Type) (TyFun (Either a6989586621679436289 b6989586621679436291) c6989586621679436290 -> Type) -> *) (Either_Sym1 a6989586621679436289 b6989586621679436291 c6989586621679436290) Source # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym1 a6989586621679436289 b6989586621679436291 c6989586621679436290) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) -> TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) -> *) (ZipWithSym1 a6989586621679458147 b6989586621679458148 c6989586621679458149) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a6989586621679458147 b6989586621679458148 c6989586621679458149) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) -> [a6989586621679458147] -> TyFun [b6989586621679458148] [c6989586621679458149] -> *) (ZipWithSym2 a6989586621679458147 b6989586621679458148 c6989586621679458149) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a6989586621679458147 b6989586621679458148 c6989586621679458149) t -> () Source #

SuppressUnusedWarnings ((TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) -> TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) -> *) (MapAccumRSym1 x6989586621679458165 acc6989586621679458164 y6989586621679458166) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym1 x6989586621679458165 acc6989586621679458164 y6989586621679458166) t -> () Source #

SuppressUnusedWarnings ((TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) -> acc6989586621679458164 -> TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> *) (MapAccumRSym2 x6989586621679458165 acc6989586621679458164 y6989586621679458166) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym2 x6989586621679458165 acc6989586621679458164 y6989586621679458166) t -> () Source #

SuppressUnusedWarnings ((TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) -> TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) -> *) (MapAccumLSym1 x6989586621679458168 acc6989586621679458167 y6989586621679458169) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym1 x6989586621679458168 acc6989586621679458167 y6989586621679458169) t -> () Source #

SuppressUnusedWarnings ((TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) -> acc6989586621679458167 -> TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> *) (MapAccumLSym2 x6989586621679458168 acc6989586621679458167 y6989586621679458169) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym2 x6989586621679458168 acc6989586621679458167 y6989586621679458169) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) -> NonEmpty a6989586621679729606 -> TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> *) (ZipWithSym2 a6989586621679729606 b6989586621679729607 c6989586621679729608) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a6989586621679729606 b6989586621679729607 c6989586621679729608) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) -> *) (ZipWithSym1 a6989586621679729606 b6989586621679729607 c6989586621679729608) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a6989586621679729606 b6989586621679729607 c6989586621679729608) t -> () Source #

SuppressUnusedWarnings ([a6989586621679458150] -> TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) -> *) (Zip3Sym1 a6989586621679458150 b6989586621679458151 c6989586621679458152) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym1 a6989586621679458150 b6989586621679458151 c6989586621679458152) t -> () Source #

SuppressUnusedWarnings ([a6989586621679458150] -> [b6989586621679458151] -> TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> *) (Zip3Sym2 a6989586621679458150 b6989586621679458151 c6989586621679458152) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym2 a6989586621679458150 b6989586621679458151 c6989586621679458152) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun (a6989586621679422503, b6989586621679422504) c6989586621679422505 -> Type) (TyFun a6989586621679422503 (TyFun b6989586621679422504 c6989586621679422505 -> Type) -> Type) -> *) (CurrySym0 a6989586621679422503 b6989586621679422504 c6989586621679422505) Source # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym0 a6989586621679422503 b6989586621679422504 c6989586621679422505) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679281036 (TyFun b6989586621679281037 c6989586621679281038 -> Type) -> Type) (TyFun b6989586621679281037 (TyFun a6989586621679281036 c6989586621679281038 -> Type) -> Type) -> *) (FlipSym0 b6989586621679281037 a6989586621679281036 c6989586621679281038) Source # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym0 b6989586621679281037 a6989586621679281036 c6989586621679281038) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679281039 c6989586621679281040 -> Type) (TyFun (TyFun a6989586621679281041 b6989586621679281039 -> Type) (TyFun a6989586621679281041 c6989586621679281040 -> Type) -> Type) -> *) ((:.$) b6989586621679281039 a6989586621679281041 c6989586621679281040) Source # 

Methods

suppressUnusedWarnings :: Proxy ((b6989586621679281039 :.$ a6989586621679281041) c6989586621679281040) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679292903 (TyFun b6989586621679292903 c6989586621679292904 -> Type) -> Type) (TyFun (TyFun a6989586621679292905 b6989586621679292903 -> Type) (TyFun a6989586621679292905 (TyFun a6989586621679292905 c6989586621679292904 -> Type) -> Type) -> Type) -> *) (OnSym0 b6989586621679292903 a6989586621679292905 c6989586621679292904) Source # 

Methods

suppressUnusedWarnings :: Proxy (OnSym0 b6989586621679292903 a6989586621679292905 c6989586621679292904) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679422500 (TyFun b6989586621679422501 c6989586621679422502 -> Type) -> Type) (TyFun (a6989586621679422500, b6989586621679422501) c6989586621679422502 -> Type) -> *) (UncurrySym0 a6989586621679422500 b6989586621679422501 c6989586621679422502) Source # 

Methods

suppressUnusedWarnings :: Proxy (UncurrySym0 a6989586621679422500 b6989586621679422501 c6989586621679422502) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679436289 c6989586621679436290 -> Type) (TyFun (TyFun b6989586621679436291 c6989586621679436290 -> Type) (TyFun (Either a6989586621679436289 b6989586621679436291) c6989586621679436290 -> Type) -> Type) -> *) (Either_Sym0 a6989586621679436289 b6989586621679436291 c6989586621679436290) Source # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym0 a6989586621679436289 b6989586621679436291 c6989586621679436290) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679458147 b6989586621679458148 c6989586621679458149) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a6989586621679458147 b6989586621679458148 c6989586621679458149) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) -> Type) -> *) (MapAccumRSym0 x6989586621679458165 acc6989586621679458164 y6989586621679458166) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym0 x6989586621679458165 acc6989586621679458164 y6989586621679458166) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) -> Type) -> *) (MapAccumLSym0 x6989586621679458168 acc6989586621679458167 y6989586621679458169) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym0 x6989586621679458168 acc6989586621679458167 y6989586621679458169) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679729606 b6989586621679729607 c6989586621679729608) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a6989586621679729606 b6989586621679729607 c6989586621679729608) t -> () Source #

SuppressUnusedWarnings (TyFun [(a6989586621679458138, b6989586621679458139, c6989586621679458140)] ([a6989586621679458138], [b6989586621679458139], [c6989586621679458140]) -> *) (Unzip3Sym0 a6989586621679458138 b6989586621679458139 c6989586621679458140) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip3Sym0 a6989586621679458138 b6989586621679458139 c6989586621679458140) t -> () Source #

SuppressUnusedWarnings (TyFun [a6989586621679458150] (TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) -> Type) -> *) (Zip3Sym0 a6989586621679458150 b6989586621679458151 c6989586621679458152) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym0 a6989586621679458150 b6989586621679458151 c6989586621679458152) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) -> TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) -> *) (ZipWith3Sym1 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym1 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) -> [a6989586621679458143] -> TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> *) (ZipWith3Sym2 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym2 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) -> [a6989586621679458143] -> [b6989586621679458144] -> TyFun [c6989586621679458145] [d6989586621679458146] -> *) (ZipWith3Sym3 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym3 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876705] -> [b6989586621679876706] -> [c6989586621679876707] -> TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> *) (Zip4Sym3 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym3 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876705] -> [b6989586621679876706] -> TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> *) (Zip4Sym2 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym2 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876705] -> TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) -> *) (Zip4Sym1 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym1 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym0 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) t -> () Source #

SuppressUnusedWarnings (TyFun [(a6989586621679458134, b6989586621679458135, c6989586621679458136, d6989586621679458137)] ([a6989586621679458134], [b6989586621679458135], [c6989586621679458136], [d6989586621679458137]) -> *) (Unzip4Sym0 a6989586621679458134 b6989586621679458135 c6989586621679458136 d6989586621679458137) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip4Sym0 a6989586621679458134 b6989586621679458135 c6989586621679458136 d6989586621679458137) t -> () Source #

SuppressUnusedWarnings (TyFun [a6989586621679876705] (TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) -> Type) -> *) (Zip4Sym0 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym0 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) -> *) (ZipWith4Sym1 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym1 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876682] -> TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> *) (ZipWith4Sym2 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym2 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876682] -> [b6989586621679876683] -> TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> *) (ZipWith4Sym3 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym3 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876682] -> [b6989586621679876683] -> [c6989586621679876684] -> TyFun [d6989586621679876685] [e6989586621679876686] -> *) (ZipWith4Sym4 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym4 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876700] -> [b6989586621679876701] -> [c6989586621679876702] -> [d6989586621679876703] -> TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> *) (Zip5Sym4 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym4 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876700] -> [b6989586621679876701] -> [c6989586621679876702] -> TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> *) (Zip5Sym3 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym3 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876700] -> [b6989586621679876701] -> TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> *) (Zip5Sym2 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym2 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876700] -> TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) -> *) (Zip5Sym1 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym1 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith4Sym0 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym0 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) t -> () Source #

SuppressUnusedWarnings (TyFun [(a6989586621679458129, b6989586621679458130, c6989586621679458131, d6989586621679458132, e6989586621679458133)] ([a6989586621679458129], [b6989586621679458130], [c6989586621679458131], [d6989586621679458132], [e6989586621679458133]) -> *) (Unzip5Sym0 a6989586621679458129 b6989586621679458130 c6989586621679458131 d6989586621679458132 e6989586621679458133) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip5Sym0 a6989586621679458129 b6989586621679458130 c6989586621679458131 d6989586621679458132 e6989586621679458133) t -> () Source #

SuppressUnusedWarnings (TyFun [a6989586621679876700] (TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip5Sym0 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym0 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym1 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym1 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876676] -> TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> *) (ZipWith5Sym2 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym2 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876676] -> [b6989586621679876677] -> TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> *) (ZipWith5Sym3 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym3 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876676] -> [b6989586621679876677] -> [c6989586621679876678] -> TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> *) (ZipWith5Sym4 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym4 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876676] -> [b6989586621679876677] -> [c6989586621679876678] -> [d6989586621679876679] -> TyFun [e6989586621679876680] [f6989586621679876681] -> *) (ZipWith5Sym5 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym5 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876694] -> [b6989586621679876695] -> [c6989586621679876696] -> [d6989586621679876697] -> [e6989586621679876698] -> TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> *) (Zip6Sym5 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym5 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876694] -> [b6989586621679876695] -> [c6989586621679876696] -> [d6989586621679876697] -> TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> *) (Zip6Sym4 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym4 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876694] -> [b6989586621679876695] -> [c6989586621679876696] -> TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> *) (Zip6Sym3 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym3 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876694] -> [b6989586621679876695] -> TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> *) (Zip6Sym2 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym2 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876694] -> TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym1 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym1 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym5 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () Source #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> *) (Tuple6Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () Source #

SuppressUnusedWarnings (a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple6Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym0 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym0 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) t -> () Source #

SuppressUnusedWarnings (TyFun [(a6989586621679458123, b6989586621679458124, c6989586621679458125, d6989586621679458126, e6989586621679458127, f6989586621679458128)] ([a6989586621679458123], [b6989586621679458124], [c6989586621679458125], [d6989586621679458126], [e6989586621679458127], [f6989586621679458128]) -> *) (Unzip6Sym0 a6989586621679458123 b6989586621679458124 c6989586621679458125 d6989586621679458126 e6989586621679458127 f6989586621679458128) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip6Sym0 a6989586621679458123 b6989586621679458124 c6989586621679458125 d6989586621679458126 e6989586621679458127 f6989586621679458128) t -> () Source #

SuppressUnusedWarnings (TyFun [a6989586621679876694] (TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym0 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym0 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) t -> () Source #

SuppressUnusedWarnings (TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple6Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym1 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym1 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym2 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym2 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> [b6989586621679876670] -> TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> *) (ZipWith6Sym3 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym3 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> [b6989586621679876670] -> [c6989586621679876671] -> TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> *) (ZipWith6Sym4 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym4 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> [b6989586621679876670] -> [c6989586621679876671] -> [d6989586621679876672] -> TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> *) (ZipWith6Sym5 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym5 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> [b6989586621679876670] -> [c6989586621679876671] -> [d6989586621679876672] -> [e6989586621679876673] -> TyFun [f6989586621679876674] [g6989586621679876675] -> *) (ZipWith6Sym6 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym6 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> [c6989586621679876689] -> [d6989586621679876690] -> [e6989586621679876691] -> [f6989586621679876692] -> TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> *) (Zip7Sym6 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym6 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> [c6989586621679876689] -> [d6989586621679876690] -> [e6989586621679876691] -> TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> *) (Zip7Sym5 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym5 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> [c6989586621679876689] -> [d6989586621679876690] -> TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> *) (Zip7Sym4 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym4 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> [c6989586621679876689] -> TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> *) (Zip7Sym3 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym3 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym2 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym2 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

SuppressUnusedWarnings ([a6989586621679876687] -> TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym1 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym1 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym6 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

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

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym5 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> *) (Tuple7Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> *) (Tuple7Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

SuppressUnusedWarnings (a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym0 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym0 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

SuppressUnusedWarnings (TyFun [(a6989586621679458116, b6989586621679458117, c6989586621679458118, d6989586621679458119, e6989586621679458120, f6989586621679458121, g6989586621679458122)] ([a6989586621679458116], [b6989586621679458117], [c6989586621679458118], [d6989586621679458119], [e6989586621679458120], [f6989586621679458121], [g6989586621679458122]) -> *) (Unzip7Sym0 a6989586621679458116 b6989586621679458117 c6989586621679458118 d6989586621679458119 e6989586621679458120 f6989586621679458121 g6989586621679458122) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip7Sym0 a6989586621679458116 b6989586621679458117 c6989586621679458118 d6989586621679458119 e6989586621679458120 f6989586621679458121 g6989586621679458122) t -> () Source #

SuppressUnusedWarnings (TyFun [a6989586621679876687] (TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym0 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym0 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

SuppressUnusedWarnings (TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (TyFun f3530822107858468870 (TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Tuple7Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) Source # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym1 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym1 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym2 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym2 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym3 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym3 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> [c6989586621679876663] -> TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> *) (ZipWith7Sym4 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym4 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> [c6989586621679876663] -> [d6989586621679876664] -> TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> *) (ZipWith7Sym5 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym5 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> [c6989586621679876663] -> [d6989586621679876664] -> [e6989586621679876665] -> TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> *) (ZipWith7Sym6 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym6 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> [c6989586621679876663] -> [d6989586621679876664] -> [e6989586621679876665] -> [f6989586621679876666] -> TyFun [g6989586621679876667] [h6989586621679876668] -> *) (ZipWith7Sym7 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym7 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym0 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym0 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #