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

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

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

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

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

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

to generate singletons for Prelude types.

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

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

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

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

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

Generate defunctionalization symbols for existing type family

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

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

Functions to generate equality instances

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

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

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

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

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

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

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

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

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

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

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

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

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

Create instances of SDecide for each type in the list.

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

Create instance of SDecide for the given type.

Functions to generate Ord instances

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

Produce instances for POrd from the given types

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

Produce an instance for POrd from the given type

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

Create instances of SOrd for the given types

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

Create instance of SOrd for the given type

Functions to generate Bounded instances

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

Produce instances for PBounded from the given types

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

Produce an instance for PBounded from the given type

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

Create instances of SBounded for the given types

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

Create instance of SBounded for the given type

Functions to generate Enum instances

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

Produce instances for PEnum from the given types

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

Produce an instance for PEnum from the given type

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

Create instances of SEnum for the given types

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

Create instance of SEnum for the given type

Utility functions

cases #

Arguments

:: DsMonad q 
=> Name

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

-> q Exp

The scrutinee, in a Template Haskell quote

-> q Exp

The body, in a Template Haskell quote

-> q Exp 

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

sCases #

Arguments

:: DsMonad q 
=> Name

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

-> q Exp

The scrutinee, in a Template Haskell quote

-> q Exp

The body, in a Template Haskell quote

-> q Exp 

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

Basic singleton definitions

data family Sing (a :: k) #

The singleton kind-indexed data family.

Instances

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

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

Associated Types

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

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

Instances

PEq Bool # 

Associated Types

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

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

PEq Ordering # 

Associated Types

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

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

PEq () # 

Associated Types

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

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

PEq [k] # 

Associated Types

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

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

PEq (Maybe k) # 

Associated Types

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

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

PEq (NonEmpty k) # 

Associated Types

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

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

PEq (Either k1 k2) # 

Associated Types

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

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

PEq (k1, k2) # 

Associated Types

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

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

PEq (k1, k2, k3) # 

Associated Types

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

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

PEq (k1, k2, k3, k4) # 

Associated Types

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

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

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

Associated Types

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

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

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

Associated Types

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

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

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

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 #

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 #

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

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

Equations

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

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

Conditional over singletons

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

Equations

False :&& _z_6989586621679241433 = FalseSym0 
True :&& x = x 

class SEq k where #

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

Minimal complete definition

(%:==)

Methods

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

Boolean equality on singletons

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

Boolean disequality on singletons

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

Boolean disequality on singletons

Instances

SEq Bool # 

Methods

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

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

SEq Ordering # 

Methods

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

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

SEq () # 

Methods

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

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

SEq a => SEq [a] # 

Methods

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

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

SEq a => SEq (Maybe a) # 

Methods

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

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

SEq a => SEq (NonEmpty a) # 

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

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

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

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

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

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

class PEq a => POrd (a :: Type) #

Associated Types

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

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

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

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

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

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

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

Instances

POrd Bool # 

Associated Types

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

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

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

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

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

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

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

POrd Ordering # 

Associated Types

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

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

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

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

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

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

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

POrd () # 

Associated Types

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

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

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

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

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

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

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

POrd [a] # 

Associated Types

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

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

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

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

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

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

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

POrd (Maybe a) # 

Associated Types

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

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

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

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

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

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

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

POrd (NonEmpty a) # 

Associated Types

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

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

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

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

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

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

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

POrd (Either a b) # 

Associated Types

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

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

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

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

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

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

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

POrd (a, b) # 

Associated Types

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

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

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

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

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

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

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

POrd (a, b, c) # 

Associated Types

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

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

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

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

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

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

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

POrd (a, b, c, d) # 

Associated Types

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

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

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

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

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

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

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

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

Associated Types

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

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

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

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

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

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

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

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

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 #

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

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

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

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

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

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

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

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 #

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 #

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 #

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 #

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 #

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 #

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 #

class SEq a => SOrd a where #

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Instances

SOrd Bool # 
SOrd Ordering # 
SOrd () # 

Methods

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

SOrd a => SOrd (Maybe a) # 

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Equations

ThenCmp EQ x = x 
ThenCmp LT _z_6989586621679278401 = LTSym0 
ThenCmp GT _z_6989586621679278404 = GTSym0 

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

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

Equations

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

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 #

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

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 #

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

data Decision a #

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

Constructors

Proved a

Witness for a

Disproved (Refuted a)

Proof that no a exists

data SomeSing k where #

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

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

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

Constructors

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

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

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

data ErrorSym0 (l :: TyFun k06989586621679342626 k6989586621679342628) #

Instances

SuppressUnusedWarnings (TyFun k06989586621679342626 k6989586621679342628 -> *) (ErrorSym0 k06989586621679342626 k6989586621679342628) # 

Methods

suppressUnusedWarnings :: Proxy (ErrorSym0 k06989586621679342626 k6989586621679342628) t -> () #

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

type TrueSym0 = True #

type LTSym0 = LT #

type EQSym0 = EQ #

type GTSym0 = GT #

type Tuple0Sym0 = '() #

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

Instances

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

Methods

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

type Apply a3530822107858468865 (TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> Type) (Tuple2Sym0 a3530822107858468865 b3530822107858468866) l # 
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)) #

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

type Apply a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> Type) (Tuple3Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867) l # 
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)) #

Instances

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

Methods

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

type Apply b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) (Tuple3Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 l1) l2 # 
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)) #

Instances

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

Methods

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

type Apply k3 (k2, k1, k3) (Tuple3Sym2 k2 k1 k3 l1 l2) l3 # 
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) #

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

Instances

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

Methods

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

type Apply a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> Type) (Tuple4Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) l # 
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)) #

Instances

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

Methods

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

type Apply b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) (Tuple4Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 l1) l2 # 
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)) #

Instances

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

Methods

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

type Apply c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) (Tuple4Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 l1 l2) l3 # 
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)) #

Instances

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

Methods

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

type Apply k4 (k2, k1, k3, k4) (Tuple4Sym3 k2 k1 k3 k4 l1 l2 l3) l4 # 
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) #

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

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

Methods

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

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

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

Methods

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

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

Instances

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

Methods

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

type Apply c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) (Tuple5Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 l1 l2) l3 # 
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)) #

Instances

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

Methods

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

type Apply d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) (Tuple5Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 l1 l2 l3) l4 # 
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)) #

Instances

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

Methods

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

type Apply k5 (k2, k1, k3, k4, k5) (Tuple5Sym4 k2 k1 k3 k4 k5 l1 l2 l3 l4) l5 # 
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) #

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

Instances

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

Methods

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

type Apply e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) (Tuple6Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 l1 l2 l3 l4) l5 # 
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)) #

Instances

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

Methods

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

type Apply k6 (k2, k1, k3, k4, k5, k6) (Tuple6Sym5 k2 k1 k3 k4 k5 k6 l1 l2 l3 l4 l5) l6 # 
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) #

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Instances

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

Methods

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

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

data FoldlSym0 (l :: TyFun (TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type) -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679213672 b6989586621679213673) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym0 a6989586621679213672 b6989586621679213673) t -> () #

type Apply (TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type) -> Type) (FoldlSym0 a6989586621679213672 b6989586621679213673) l # 
type Apply (TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type) -> Type) (FoldlSym0 a6989586621679213672 b6989586621679213673) l = FoldlSym1 a6989586621679213672 b6989586621679213673 l

class SuppressUnusedWarnings (t :: k) where #

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

Minimal complete definition

suppressUnusedWarnings

Methods

suppressUnusedWarnings :: Proxy t -> () #

Instances

SuppressUnusedWarnings (Bool -> TyFun Bool Bool -> *) (:&&$$) # 
SuppressUnusedWarnings (Bool -> TyFun Bool Bool -> *) (:||$$) # 
SuppressUnusedWarnings (Ordering -> TyFun Ordering Ordering -> *) ThenCmpSym1 # 
SuppressUnusedWarnings (Nat -> TyFun Nat Nat -> *) (:^$$) # 
SuppressUnusedWarnings (TyFun Bool Bool -> *) NotSym0 # 
SuppressUnusedWarnings (TyFun Bool (TyFun Bool Bool -> Type) -> *) (:&&$) # 
SuppressUnusedWarnings (TyFun Bool (TyFun Bool Bool -> Type) -> *) (:||$) # 
SuppressUnusedWarnings (TyFun [Bool] Bool -> *) AndSym0 # 
SuppressUnusedWarnings (TyFun [Bool] Bool -> *) OrSym0 # 
SuppressUnusedWarnings (TyFun Ordering (TyFun Ordering Ordering -> Type) -> *) ThenCmpSym0 # 
SuppressUnusedWarnings (TyFun Nat (TyFun Nat Nat -> *) -> *) (:^$) # 
SuppressUnusedWarnings (TyFun Nat Constraint -> *) KnownNatSym0 # 
SuppressUnusedWarnings (TyFun Symbol Constraint -> *) KnownSymbolSym0 # 
SuppressUnusedWarnings (TyFun (NonEmpty Bool) Bool -> *) XorSym0 # 
SuppressUnusedWarnings ((TyFun a6989586621679377359 Bool -> Type) -> (TyFun a6989586621679377359 a6989586621679377359 -> Type) -> TyFun a6989586621679377359 a6989586621679377359 -> *) (UntilSym2 a6989586621679377359) # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy (GroupBy1Sym1 a6989586621679608999) t -> () #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings ((TyFun a6989586621679609019 (TyFun a6989586621679609019 a6989586621679609019 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679609019) (NonEmpty a6989586621679609019) -> *) (Scanl1Sym1 a6989586621679609019) # 

Methods

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

SuppressUnusedWarnings ((TyFun a6989586621679609018 (TyFun a6989586621679609018 a6989586621679609018 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679609018) (NonEmpty a6989586621679609018) -> *) (Scanr1Sym1 a6989586621679609018) # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy ((:|$$) a6989586621679073600) t -> () #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (a6989586621679609017 -> TyFun (NonEmpty a6989586621679609017) (NonEmpty a6989586621679609017) -> *) (IntersperseSym1 a6989586621679609017) # 

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (a6989586621679609034 -> TyFun (NonEmpty a6989586621679609034) (NonEmpty a6989586621679609034) -> *) (ConsSym1 a6989586621679609034) # 

Methods

suppressUnusedWarnings :: Proxy (ConsSym1 a6989586621679609034) t -> () #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy (GroupBy1Sym0 a6989586621679608999) t -> () #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609019 (TyFun a6989586621679609019 a6989586621679609019 -> Type) -> Type) (TyFun (NonEmpty a6989586621679609019) (NonEmpty a6989586621679609019) -> Type) -> *) (Scanl1Sym0 a6989586621679609019) # 

Methods

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

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609018 (TyFun a6989586621679609018 a6989586621679609018 -> Type) -> Type) (TyFun (NonEmpty a6989586621679609018) (NonEmpty a6989586621679609018) -> Type) -> *) (Scanr1Sym0 a6989586621679609018) # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy (FromListSym0 a6989586621679609032) t -> () #

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

Methods

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

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy (NonEmpty_Sym0 a6989586621679609043) t -> () #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

suppressUnusedWarnings :: Proxy (ToEnumSym0 a6989586621679673920) t -> () #

SuppressUnusedWarnings (TyFun a3530822107858468865 (Maybe a3530822107858468865) -> *) (JustSym0 a3530822107858468865) # 

Methods

suppressUnusedWarnings :: Proxy (JustSym0 a3530822107858468865) t -> () #

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

Methods

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

SuppressUnusedWarnings (TyFun a6989586621679073600 (TyFun [a6989586621679073600] (NonEmpty a6989586621679073600) -> Type) -> *) ((:|$) a6989586621679073600) # 

Methods

suppressUnusedWarnings :: Proxy ((:|$) a6989586621679073600) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679240786 (TyFun a6989586621679240786 (TyFun Bool a6989586621679240786 -> Type) -> Type) -> *) (Bool_Sym0 a6989586621679240786) # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

SuppressUnusedWarnings (TyFun a6989586621679348813 a6989586621679348813 -> *) (AbsSym0 a6989586621679348813) # 

Methods

suppressUnusedWarnings :: Proxy (AbsSym0 a6989586621679348813) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679348813 (TyFun a6989586621679348813 a6989586621679348813 -> Type) -> *) ((:*$) a6989586621679348813) # 

Methods

suppressUnusedWarnings :: Proxy ((:*$) a6989586621679348813) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679351104 (TyFun a6989586621679351104 a6989586621679351104 -> Type) -> *) (SubtractSym0 a6989586621679351104) # 

Methods

suppressUnusedWarnings :: Proxy (SubtractSym0 a6989586621679351104) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679362575 (TyFun (Maybe a6989586621679362575) a6989586621679362575 -> Type) -> *) (FromMaybeSym0 a6989586621679362575) # 

Methods

suppressUnusedWarnings :: Proxy (FromMaybeSym0 a6989586621679362575) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679389240 (TyFun [a6989586621679389240] [a6989586621679389240] -> Type) -> *) (InsertSym0 a6989586621679389240) # 

Methods

suppressUnusedWarnings :: Proxy (InsertSym0 a6989586621679389240) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679389267 (TyFun [a6989586621679389267] [a6989586621679389267] -> Type) -> *) (DeleteSym0 a6989586621679389267) # 

Methods

suppressUnusedWarnings :: Proxy (DeleteSym0 a6989586621679389267) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679389256 (TyFun [a6989586621679389256] [Nat] -> Type) -> *) (ElemIndicesSym0 a6989586621679389256) # 

Methods

suppressUnusedWarnings :: Proxy (ElemIndicesSym0 a6989586621679389256) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679389257 (TyFun [a6989586621679389257] (Maybe Nat) -> Type) -> *) (ElemIndexSym0 a6989586621679389257) # 

Methods

suppressUnusedWarnings :: Proxy (ElemIndexSym0 a6989586621679389257) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679389307 (TyFun [a6989586621679389307] Bool -> Type) -> *) (NotElemSym0 a6989586621679389307) # 

Methods

suppressUnusedWarnings :: Proxy (NotElemSym0 a6989586621679389307) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679389308 (TyFun [a6989586621679389308] Bool -> Type) -> *) (ElemSym0 a6989586621679389308) # 

Methods

suppressUnusedWarnings :: Proxy (ElemSym0 a6989586621679389308) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679389342 (TyFun [a6989586621679389342] [a6989586621679389342] -> Type) -> *) (IntersperseSym0 a6989586621679389342) # 

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym0 a6989586621679389342) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679609017 (TyFun (NonEmpty a6989586621679609017) (NonEmpty a6989586621679609017) -> Type) -> *) (IntersperseSym0 a6989586621679609017) # 

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym0 a6989586621679609017) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679609024 (TyFun [a6989586621679609024] (NonEmpty a6989586621679609024) -> Type) -> *) (InsertSym0 a6989586621679609024) # 

Methods

suppressUnusedWarnings :: Proxy (InsertSym0 a6989586621679609024) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679609035 (TyFun (NonEmpty a6989586621679609035) (NonEmpty a6989586621679609035) -> Type) -> *) ((:<|$) a6989586621679609035) # 

Methods

suppressUnusedWarnings :: Proxy ((:<|$) a6989586621679609035) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679609034 (TyFun (NonEmpty a6989586621679609034) (NonEmpty a6989586621679609034) -> Type) -> *) (ConsSym0 a6989586621679609034) # 

Methods

suppressUnusedWarnings :: Proxy (ConsSym0 a6989586621679609034) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679673920 (TyFun a6989586621679673920 (TyFun a6989586621679673920 [a6989586621679673920] -> Type) -> Type) -> *) (EnumFromThenToSym0 a6989586621679673920) # 

Methods

suppressUnusedWarnings :: Proxy (EnumFromThenToSym0 a6989586621679673920) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679673920 (TyFun a6989586621679673920 [a6989586621679673920] -> Type) -> *) (EnumFromToSym0 a6989586621679673920) # 

Methods

suppressUnusedWarnings :: Proxy (EnumFromToSym0 a6989586621679673920) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679673920 Nat -> *) (FromEnumSym0 a6989586621679673920) # 

Methods

suppressUnusedWarnings :: Proxy (FromEnumSym0 a6989586621679673920) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679673920 a6989586621679673920 -> *) (PredSym0 a6989586621679673920) # 

Methods

suppressUnusedWarnings :: Proxy (PredSym0 a6989586621679673920) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679673920 a6989586621679673920 -> *) (SuccSym0 a6989586621679673920) # 

Methods

suppressUnusedWarnings :: Proxy (SuccSym0 a6989586621679673920) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679608985) (NonEmpty a6989586621679608985) -> *) (NubSym0 a6989586621679608985) # 

Methods

suppressUnusedWarnings :: Proxy (NubSym0 a6989586621679608985) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679608993) (TyFun Nat a6989586621679608993 -> Type) -> *) ((:!!$) a6989586621679608993) # 

Methods

suppressUnusedWarnings :: Proxy ((:!!$) a6989586621679608993) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609000) (NonEmpty (NonEmpty a6989586621679609000)) -> *) (Group1Sym0 a6989586621679609000) # 

Methods

suppressUnusedWarnings :: Proxy (Group1Sym0 a6989586621679609000) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609031) [a6989586621679609031] -> *) (ToListSym0 a6989586621679609031) # 

Methods

suppressUnusedWarnings :: Proxy (ToListSym0 a6989586621679609031) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609016) (NonEmpty a6989586621679609016) -> *) (ReverseSym0 a6989586621679609016) # 

Methods

suppressUnusedWarnings :: Proxy (ReverseSym0 a6989586621679609016) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609033) (NonEmpty a6989586621679609033) -> *) (SortSym0 a6989586621679609033) # 

Methods

suppressUnusedWarnings :: Proxy (SortSym0 a6989586621679609033) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609036) [a6989586621679609036] -> *) (InitSym0 a6989586621679609036) # 

Methods

suppressUnusedWarnings :: Proxy (InitSym0 a6989586621679609036) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609037) a6989586621679609037 -> *) (LastSym0 a6989586621679609037) # 

Methods

suppressUnusedWarnings :: Proxy (LastSym0 a6989586621679609037) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609038) [a6989586621679609038] -> *) (TailSym0 a6989586621679609038) # 

Methods

suppressUnusedWarnings :: Proxy (TailSym0 a6989586621679609038) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609039) a6989586621679609039 -> *) (HeadSym0 a6989586621679609039) # 

Methods

suppressUnusedWarnings :: Proxy (HeadSym0 a6989586621679609039) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609042) (a6989586621679609042, Maybe (NonEmpty a6989586621679609042)) -> *) (UnconsSym0 a6989586621679609042) # 

Methods

suppressUnusedWarnings :: Proxy (UnconsSym0 a6989586621679609042) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609046) Nat -> *) (LengthSym0 a6989586621679609046) # 

Methods

suppressUnusedWarnings :: Proxy (LengthSym0 a6989586621679609046) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty (NonEmpty a6989586621679608983)) (NonEmpty (NonEmpty a6989586621679608983)) -> *) (TransposeSym0 a6989586621679608983) # 

Methods

suppressUnusedWarnings :: Proxy (TransposeSym0 a6989586621679608983) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) -> b6989586621679213673 -> TyFun [a6989586621679213672] b6989586621679213673 -> *) (FoldlSym2 a6989586621679213672 b6989586621679213673) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym2 a6989586621679213672 b6989586621679213673) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) -> TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type) -> *) (FoldlSym1 a6989586621679213672 b6989586621679213673) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym1 a6989586621679213672 b6989586621679213673) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679244032 b6989586621679244033 -> Type) -> TyFun [a6989586621679244032] [b6989586621679244033] -> *) (MapSym1 a6989586621679244032 b6989586621679244033) # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a6989586621679244032 b6989586621679244033) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) -> b6989586621679244035 -> TyFun [a6989586621679244034] b6989586621679244035 -> *) (FoldrSym2 a6989586621679244034 b6989586621679244035) # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym2 a6989586621679244034 b6989586621679244035) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) -> TyFun b6989586621679244035 (TyFun [a6989586621679244034] b6989586621679244035 -> Type) -> *) (FoldrSym1 a6989586621679244034 b6989586621679244035) # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym1 a6989586621679244034 b6989586621679244035) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679269804 a6989586621679269803 -> Type) -> b6989586621679269804 -> TyFun b6989586621679269804 Ordering -> *) (ComparingSym2 a6989586621679269803 b6989586621679269804) # 

Methods

suppressUnusedWarnings :: Proxy (ComparingSym2 a6989586621679269803 b6989586621679269804) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679269804 a6989586621679269803 -> Type) -> TyFun b6989586621679269804 (TyFun b6989586621679269804 Ordering -> Type) -> *) (ComparingSym1 a6989586621679269803 b6989586621679269804) # 

Methods

suppressUnusedWarnings :: Proxy (ComparingSym1 a6989586621679269803 b6989586621679269804) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679362570 (Maybe b6989586621679362571) -> Type) -> TyFun [a6989586621679362570] [b6989586621679362571] -> *) (MapMaybeSym1 a6989586621679362570 b6989586621679362571) # 

Methods

suppressUnusedWarnings :: Proxy (MapMaybeSym1 a6989586621679362570 b6989586621679362571) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679389314 (Maybe (a6989586621679389315, b6989586621679389314)) -> Type) -> TyFun b6989586621679389314 [a6989586621679389315] -> *) (UnfoldrSym1 b6989586621679389314 a6989586621679389315) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 b6989586621679389314 a6989586621679389315) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) -> TyFun b6989586621679389324 (TyFun [a6989586621679389323] [b6989586621679389324] -> Type) -> *) (ScanrSym1 a6989586621679389323 b6989586621679389324) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a6989586621679389323 b6989586621679389324) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) -> b6989586621679389324 -> TyFun [a6989586621679389323] [b6989586621679389324] -> *) (ScanrSym2 a6989586621679389323 b6989586621679389324) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a6989586621679389323 b6989586621679389324) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) -> TyFun b6989586621679389326 (TyFun [a6989586621679389327] [b6989586621679389326] -> Type) -> *) (ScanlSym1 a6989586621679389327 b6989586621679389326) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a6989586621679389327 b6989586621679389326) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) -> b6989586621679389326 -> TyFun [a6989586621679389327] [b6989586621679389326] -> *) (ScanlSym2 a6989586621679389327 b6989586621679389326) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a6989586621679389327 b6989586621679389326) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679389329 [b6989586621679389330] -> Type) -> TyFun [a6989586621679389329] [b6989586621679389330] -> *) (ConcatMapSym1 a6989586621679389329 b6989586621679389330) # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym1 a6989586621679389329 b6989586621679389330) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) -> b6989586621679389336 -> TyFun [a6989586621679389335] b6989586621679389336 -> *) (Foldl'Sym2 a6989586621679389335 b6989586621679389336) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym2 a6989586621679389335 b6989586621679389336) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) -> TyFun b6989586621679389336 (TyFun [a6989586621679389335] b6989586621679389336 -> Type) -> *) (Foldl'Sym1 a6989586621679389335 b6989586621679389336) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym1 a6989586621679389335 b6989586621679389336) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679609004 b6989586621679609003 -> Type) -> TyFun [a6989586621679609004] [NonEmpty a6989586621679609004] -> *) (GroupWithSym1 b6989586621679609003 a6989586621679609004) # 

Methods

suppressUnusedWarnings :: Proxy (GroupWithSym1 b6989586621679609003 a6989586621679609004) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679609002 b6989586621679609001 -> Type) -> TyFun [a6989586621679609002] [NonEmpty a6989586621679609002] -> *) (GroupAllWithSym1 b6989586621679609001 a6989586621679609002) # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWithSym1 b6989586621679609001 a6989586621679609002) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679608998 b6989586621679608997 -> Type) -> TyFun (NonEmpty a6989586621679608998) (NonEmpty (NonEmpty a6989586621679608998)) -> *) (GroupWith1Sym1 b6989586621679608997 a6989586621679608998) # 

Methods

suppressUnusedWarnings :: Proxy (GroupWith1Sym1 b6989586621679608997 a6989586621679608998) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679609027 b6989586621679609028 -> Type) -> TyFun (NonEmpty a6989586621679609027) (NonEmpty b6989586621679609028) -> *) (MapSym1 a6989586621679609027 b6989586621679609028) # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a6989586621679609027 b6989586621679609028) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679608981 o6989586621679608980 -> Type) -> TyFun (NonEmpty a6989586621679608981) (NonEmpty a6989586621679608981) -> *) (SortWithSym1 o6989586621679608980 a6989586621679608981) # 

Methods

suppressUnusedWarnings :: Proxy (SortWithSym1 o6989586621679608980 a6989586621679608981) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679608996 b6989586621679608995 -> Type) -> TyFun (NonEmpty a6989586621679608996) (NonEmpty (NonEmpty a6989586621679608996)) -> *) (GroupAllWith1Sym1 b6989586621679608995 a6989586621679608996) # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWith1Sym1 b6989586621679608995 a6989586621679608996) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) -> b6989586621679609022 -> TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> *) (ScanlSym2 a6989586621679609023 b6989586621679609022) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a6989586621679609023 b6989586621679609022) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) -> TyFun b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type) -> *) (ScanlSym1 a6989586621679609023 b6989586621679609022) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a6989586621679609023 b6989586621679609022) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) -> b6989586621679609021 -> TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> *) (ScanrSym2 a6989586621679609020 b6989586621679609021) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a6989586621679609020 b6989586621679609021) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) -> TyFun b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type) -> *) (ScanrSym1 a6989586621679609020 b6989586621679609021) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a6989586621679609020 b6989586621679609021) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) -> TyFun a6989586621679609040 (NonEmpty b6989586621679609041) -> *) (UnfoldrSym1 a6989586621679609040 b6989586621679609041) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 a6989586621679609040 b6989586621679609041) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679609044 (b6989586621679609045, Maybe a6989586621679609044) -> Type) -> TyFun a6989586621679609044 (NonEmpty b6989586621679609045) -> *) (UnfoldSym1 a6989586621679609044 b6989586621679609045) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldSym1 a6989586621679609044 b6989586621679609045) t -> () #

SuppressUnusedWarnings ([a6989586621679389305] -> TyFun [b6989586621679389306] [(a6989586621679389305, b6989586621679389306)] -> *) (ZipSym1 a6989586621679389305 b6989586621679389306) # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 a6989586621679389305 b6989586621679389306) t -> () #

SuppressUnusedWarnings ([a6989586621679727889] -> TyFun i6989586621679727888 a6989586621679727889 -> *) (GenericIndexSym1 i6989586621679727888 a6989586621679727889) # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym1 i6989586621679727888 a6989586621679727889) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> *) (Tuple2Sym1 a3530822107858468865 b3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple2Sym1 a3530822107858468865 b3530822107858468866) t -> () #

SuppressUnusedWarnings (a6989586621679244019 -> TyFun b6989586621679244020 b6989586621679244020 -> *) (SeqSym1 a6989586621679244019 b6989586621679244020) # 

Methods

suppressUnusedWarnings :: Proxy (SeqSym1 a6989586621679244019 b6989586621679244020) t -> () #

SuppressUnusedWarnings (a6989586621679244028 -> TyFun b6989586621679244029 a6989586621679244028 -> *) (ConstSym1 b6989586621679244029 a6989586621679244028) # 

Methods

suppressUnusedWarnings :: Proxy (ConstSym1 b6989586621679244029 a6989586621679244028) t -> () #

SuppressUnusedWarnings (a6989586621679253489 -> TyFun (TyFun a6989586621679253489 b6989586621679253490 -> Type) b6989586621679253490 -> *) ((:&$$) a6989586621679253489 b6989586621679253490) # 

Methods

suppressUnusedWarnings :: Proxy (a6989586621679253489 :&$$ b6989586621679253490) t -> () #

SuppressUnusedWarnings (b6989586621679361465 -> (TyFun a6989586621679361466 b6989586621679361465 -> Type) -> TyFun (Maybe a6989586621679361466) b6989586621679361465 -> *) (Maybe_Sym2 a6989586621679361466 b6989586621679361465) # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym2 a6989586621679361466 b6989586621679361465) t -> () #

SuppressUnusedWarnings (b6989586621679361465 -> TyFun (TyFun a6989586621679361466 b6989586621679361465 -> Type) (TyFun (Maybe a6989586621679361466) b6989586621679361465 -> Type) -> *) (Maybe_Sym1 a6989586621679361466 b6989586621679361465) # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym1 a6989586621679361466 b6989586621679361465) t -> () #

SuppressUnusedWarnings (a6989586621679389236 -> TyFun [(a6989586621679389236, b6989586621679389237)] (Maybe b6989586621679389237) -> *) (LookupSym1 a6989586621679389236 b6989586621679389237) # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym1 a6989586621679389236 b6989586621679389237) t -> () #

SuppressUnusedWarnings (i6989586621679727886 -> TyFun a6989586621679727887 [a6989586621679727887] -> *) (GenericReplicateSym1 i6989586621679727886 a6989586621679727887) # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym1 i6989586621679727886 a6989586621679727887) t -> () #

SuppressUnusedWarnings (i6989586621679727890 -> TyFun [a6989586621679727891] ([a6989586621679727891], [a6989586621679727891]) -> *) (GenericSplitAtSym1 i6989586621679727890 a6989586621679727891) # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym1 i6989586621679727890 a6989586621679727891) t -> () #

SuppressUnusedWarnings (i6989586621679727892 -> TyFun [a6989586621679727893] [a6989586621679727893] -> *) (GenericDropSym1 i6989586621679727892 a6989586621679727893) # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym1 i6989586621679727892 a6989586621679727893) t -> () #

SuppressUnusedWarnings (i6989586621679727894 -> TyFun [a6989586621679727895] [a6989586621679727895] -> *) (GenericTakeSym1 i6989586621679727894 a6989586621679727895) # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym1 i6989586621679727894 a6989586621679727895) t -> () #

SuppressUnusedWarnings (NonEmpty a6989586621679608991 -> TyFun (NonEmpty b6989586621679608992) (NonEmpty (a6989586621679608991, b6989586621679608992)) -> *) (ZipSym1 a6989586621679608991 b6989586621679608992) # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 a6989586621679608991 b6989586621679608992) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679213672 b6989586621679213673) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym0 a6989586621679213672 b6989586621679213673) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679244032 b6989586621679244033 -> Type) (TyFun [a6989586621679244032] [b6989586621679244033] -> Type) -> *) (MapSym0 a6989586621679244032 b6989586621679244033) # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a6989586621679244032 b6989586621679244033) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) (TyFun b6989586621679244035 (TyFun [a6989586621679244034] b6989586621679244035 -> Type) -> Type) -> *) (FoldrSym0 a6989586621679244034 b6989586621679244035) # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym0 a6989586621679244034 b6989586621679244035) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679269804 a6989586621679269803 -> Type) (TyFun b6989586621679269804 (TyFun b6989586621679269804 Ordering -> Type) -> Type) -> *) (ComparingSym0 a6989586621679269803 b6989586621679269804) # 

Methods

suppressUnusedWarnings :: Proxy (ComparingSym0 a6989586621679269803 b6989586621679269804) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679362570 (Maybe b6989586621679362571) -> Type) (TyFun [a6989586621679362570] [b6989586621679362571] -> Type) -> *) (MapMaybeSym0 a6989586621679362570 b6989586621679362571) # 

Methods

suppressUnusedWarnings :: Proxy (MapMaybeSym0 a6989586621679362570 b6989586621679362571) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679389314 (Maybe (a6989586621679389315, b6989586621679389314)) -> Type) (TyFun b6989586621679389314 [a6989586621679389315] -> Type) -> *) (UnfoldrSym0 b6989586621679389314 a6989586621679389315) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 b6989586621679389314 a6989586621679389315) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) (TyFun b6989586621679389324 (TyFun [a6989586621679389323] [b6989586621679389324] -> Type) -> Type) -> *) (ScanrSym0 a6989586621679389323 b6989586621679389324) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a6989586621679389323 b6989586621679389324) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) (TyFun b6989586621679389326 (TyFun [a6989586621679389327] [b6989586621679389326] -> Type) -> Type) -> *) (ScanlSym0 a6989586621679389327 b6989586621679389326) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a6989586621679389327 b6989586621679389326) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679389329 [b6989586621679389330] -> Type) (TyFun [a6989586621679389329] [b6989586621679389330] -> Type) -> *) (ConcatMapSym0 a6989586621679389329 b6989586621679389330) # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym0 a6989586621679389329 b6989586621679389330) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) (TyFun b6989586621679389336 (TyFun [a6989586621679389335] b6989586621679389336 -> Type) -> Type) -> *) (Foldl'Sym0 a6989586621679389335 b6989586621679389336) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym0 a6989586621679389335 b6989586621679389336) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609004 b6989586621679609003 -> Type) (TyFun [a6989586621679609004] [NonEmpty a6989586621679609004] -> Type) -> *) (GroupWithSym0 b6989586621679609003 a6989586621679609004) # 

Methods

suppressUnusedWarnings :: Proxy (GroupWithSym0 b6989586621679609003 a6989586621679609004) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609002 b6989586621679609001 -> Type) (TyFun [a6989586621679609002] [NonEmpty a6989586621679609002] -> Type) -> *) (GroupAllWithSym0 b6989586621679609001 a6989586621679609002) # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWithSym0 b6989586621679609001 a6989586621679609002) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679608998 b6989586621679608997 -> Type) (TyFun (NonEmpty a6989586621679608998) (NonEmpty (NonEmpty a6989586621679608998)) -> Type) -> *) (GroupWith1Sym0 b6989586621679608997 a6989586621679608998) # 

Methods

suppressUnusedWarnings :: Proxy (GroupWith1Sym0 b6989586621679608997 a6989586621679608998) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609027 b6989586621679609028 -> Type) (TyFun (NonEmpty a6989586621679609027) (NonEmpty b6989586621679609028) -> Type) -> *) (MapSym0 a6989586621679609027 b6989586621679609028) # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a6989586621679609027 b6989586621679609028) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679608981 o6989586621679608980 -> Type) (TyFun (NonEmpty a6989586621679608981) (NonEmpty a6989586621679608981) -> Type) -> *) (SortWithSym0 o6989586621679608980 a6989586621679608981) # 

Methods

suppressUnusedWarnings :: Proxy (SortWithSym0 o6989586621679608980 a6989586621679608981) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679608996 b6989586621679608995 -> Type) (TyFun (NonEmpty a6989586621679608996) (NonEmpty (NonEmpty a6989586621679608996)) -> Type) -> *) (GroupAllWith1Sym0 b6989586621679608995 a6989586621679608996) # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWith1Sym0 b6989586621679608995 a6989586621679608996) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) (TyFun b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type) -> Type) -> *) (ScanlSym0 a6989586621679609023 b6989586621679609022) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a6989586621679609023 b6989586621679609022) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) (TyFun b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type) -> Type) -> *) (ScanrSym0 a6989586621679609020 b6989586621679609021) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a6989586621679609020 b6989586621679609021) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) (TyFun a6989586621679609040 (NonEmpty b6989586621679609041) -> Type) -> *) (UnfoldrSym0 a6989586621679609040 b6989586621679609041) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 a6989586621679609040 b6989586621679609041) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609044 (b6989586621679609045, Maybe a6989586621679609044) -> Type) (TyFun a6989586621679609044 (NonEmpty b6989586621679609045) -> Type) -> *) (UnfoldSym0 a6989586621679609044 b6989586621679609045) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldSym0 a6989586621679609044 b6989586621679609045) t -> () #

SuppressUnusedWarnings (TyFun [Either a6989586621679370699 b6989586621679370700] [b6989586621679370700] -> *) (RightsSym0 a6989586621679370699 b6989586621679370700) # 

Methods

suppressUnusedWarnings :: Proxy (RightsSym0 a6989586621679370699 b6989586621679370700) t -> () #

SuppressUnusedWarnings (TyFun [Either a6989586621679370701 b6989586621679370702] [a6989586621679370701] -> *) (LeftsSym0 b6989586621679370702 a6989586621679370701) # 

Methods

suppressUnusedWarnings :: Proxy (LeftsSym0 b6989586621679370702 a6989586621679370701) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679389293, b6989586621679389294)] ([a6989586621679389293], [b6989586621679389294]) -> *) (UnzipSym0 a6989586621679389293 b6989586621679389294) # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a6989586621679389293 b6989586621679389294) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679389222] i6989586621679389221 -> *) (GenericLengthSym0 a6989586621679389222 i6989586621679389221) # 

Methods

suppressUnusedWarnings :: Proxy (GenericLengthSym0 a6989586621679389222 i6989586621679389221) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679389305] (TyFun [b6989586621679389306] [(a6989586621679389305, b6989586621679389306)] -> Type) -> *) (ZipSym0 a6989586621679389305 b6989586621679389306) # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a6989586621679389305 b6989586621679389306) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679727889] (TyFun i6989586621679727888 a6989586621679727889 -> Type) -> *) (GenericIndexSym0 i6989586621679727888 a6989586621679727889) # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym0 i6989586621679727888 a6989586621679727889) t -> () #

SuppressUnusedWarnings (TyFun (Either a6989586621679370693 b6989586621679370694) Bool -> *) (IsRightSym0 a6989586621679370693 b6989586621679370694) # 

Methods

suppressUnusedWarnings :: Proxy (IsRightSym0 a6989586621679370693 b6989586621679370694) t -> () #

SuppressUnusedWarnings (TyFun (Either a6989586621679370695 b6989586621679370696) Bool -> *) (IsLeftSym0 a6989586621679370695 b6989586621679370696) # 

Methods

suppressUnusedWarnings :: Proxy (IsLeftSym0 a6989586621679370695 b6989586621679370696) t -> () #

SuppressUnusedWarnings (TyFun (a6989586621679358267, b6989586621679358268) (b6989586621679358268, a6989586621679358267) -> *) (SwapSym0 b6989586621679358268 a6989586621679358267) # 

Methods

suppressUnusedWarnings :: Proxy (SwapSym0 b6989586621679358268 a6989586621679358267) t -> () #

SuppressUnusedWarnings (TyFun (a6989586621679358275, b6989586621679358276) b6989586621679358276 -> *) (SndSym0 a6989586621679358275 b6989586621679358276) # 

Methods

suppressUnusedWarnings :: Proxy (SndSym0 a6989586621679358275 b6989586621679358276) t -> () #

SuppressUnusedWarnings (TyFun (a6989586621679358277, b6989586621679358278) a6989586621679358277 -> *) (FstSym0 b6989586621679358278 a6989586621679358277) # 

Methods

suppressUnusedWarnings :: Proxy (FstSym0 b6989586621679358278 a6989586621679358277) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679073591 (Either a6989586621679073591 b6989586621679073592) -> *) (LeftSym0 a6989586621679073591 b6989586621679073592) # 

Methods

suppressUnusedWarnings :: Proxy (LeftSym0 a6989586621679073591 b6989586621679073592) t -> () #

SuppressUnusedWarnings (TyFun b6989586621679073592 (Either a6989586621679073591 b6989586621679073592) -> *) (RightSym0 a6989586621679073591 b6989586621679073592) # 

Methods

suppressUnusedWarnings :: Proxy (RightSym0 a6989586621679073591 b6989586621679073592) t -> () #

SuppressUnusedWarnings (TyFun a3530822107858468865 (TyFun b3530822107858468866 (a3530822107858468865, b3530822107858468866) -> Type) -> *) (Tuple2Sym0 a3530822107858468865 b3530822107858468866) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple2Sym0 a3530822107858468865 b3530822107858468866) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679244019 (TyFun b6989586621679244020 b6989586621679244020 -> Type) -> *) (SeqSym0 a6989586621679244019 b6989586621679244020) # 

Methods

suppressUnusedWarnings :: Proxy (SeqSym0 a6989586621679244019 b6989586621679244020) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679244028 (TyFun b6989586621679244029 a6989586621679244028 -> Type) -> *) (ConstSym0 b6989586621679244029 a6989586621679244028) # 

Methods

suppressUnusedWarnings :: Proxy (ConstSym0 b6989586621679244029 a6989586621679244028) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679253489 (TyFun (TyFun a6989586621679253489 b6989586621679253490 -> Type) b6989586621679253490 -> Type) -> *) ((:&$) a6989586621679253489 b6989586621679253490) # 

Methods

suppressUnusedWarnings :: Proxy (a6989586621679253489 :&$ b6989586621679253490) t -> () #

SuppressUnusedWarnings (TyFun k06989586621679342626 k6989586621679342628 -> *) (ErrorSym0 k06989586621679342626 k6989586621679342628) # 

Methods

suppressUnusedWarnings :: Proxy (ErrorSym0 k06989586621679342626 k6989586621679342628) t -> () #

SuppressUnusedWarnings (TyFun b6989586621679361465 (TyFun (TyFun a6989586621679361466 b6989586621679361465 -> Type) (TyFun (Maybe a6989586621679361466) b6989586621679361465 -> Type) -> Type) -> *) (Maybe_Sym0 a6989586621679361466 b6989586621679361465) # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym0 a6989586621679361466 b6989586621679361465) t -> () #

SuppressUnusedWarnings (TyFun a6989586621679389236 (TyFun [(a6989586621679389236, b6989586621679389237)] (Maybe b6989586621679389237) -> Type) -> *) (LookupSym0 a6989586621679389236 b6989586621679389237) # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym0 a6989586621679389236 b6989586621679389237) t -> () #

SuppressUnusedWarnings (TyFun i6989586621679727886 (TyFun a6989586621679727887 [a6989586621679727887] -> Type) -> *) (GenericReplicateSym0 i6989586621679727886 a6989586621679727887) # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym0 i6989586621679727886 a6989586621679727887) t -> () #

SuppressUnusedWarnings (TyFun i6989586621679727890 (TyFun [a6989586621679727891] ([a6989586621679727891], [a6989586621679727891]) -> Type) -> *) (GenericSplitAtSym0 i6989586621679727890 a6989586621679727891) # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym0 i6989586621679727890 a6989586621679727891) t -> () #

SuppressUnusedWarnings (TyFun i6989586621679727892 (TyFun [a6989586621679727893] [a6989586621679727893] -> Type) -> *) (GenericDropSym0 i6989586621679727892 a6989586621679727893) # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym0 i6989586621679727892 a6989586621679727893) t -> () #

SuppressUnusedWarnings (TyFun i6989586621679727894 (TyFun [a6989586621679727895] [a6989586621679727895] -> Type) -> *) (GenericTakeSym0 i6989586621679727894 a6989586621679727895) # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym0 i6989586621679727894 a6989586621679727895) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty (a6989586621679608986, b6989586621679608987)) (NonEmpty a6989586621679608986, NonEmpty b6989586621679608987) -> *) (UnzipSym0 a6989586621679608986 b6989586621679608987) # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a6989586621679608986 b6989586621679608987) t -> () #

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679608991) (TyFun (NonEmpty b6989586621679608992) (NonEmpty (a6989586621679608991, b6989586621679608992)) -> Type) -> *) (ZipSym0 a6989586621679608991 b6989586621679608992) # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a6989586621679608991 b6989586621679608992) t -> () #

SuppressUnusedWarnings ((TyFun (a6989586621679358272, b6989586621679358273) c6989586621679358274 -> Type) -> a6989586621679358272 -> TyFun b6989586621679358273 c6989586621679358274 -> *) (CurrySym2 a6989586621679358272 b6989586621679358273 c6989586621679358274) # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym2 a6989586621679358272 b6989586621679358273 c6989586621679358274) t -> () #

SuppressUnusedWarnings ((TyFun (a6989586621679358272, b6989586621679358273) c6989586621679358274 -> Type) -> TyFun a6989586621679358272 (TyFun b6989586621679358273 c6989586621679358274 -> Type) -> *) (CurrySym1 a6989586621679358272 b6989586621679358273 c6989586621679358274) # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym1 a6989586621679358272 b6989586621679358273 c6989586621679358274) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679244022 (TyFun b6989586621679244023 c6989586621679244024 -> Type) -> Type) -> b6989586621679244023 -> TyFun a6989586621679244022 c6989586621679244024 -> *) (FlipSym2 b6989586621679244023 a6989586621679244022 c6989586621679244024) # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym2 b6989586621679244023 a6989586621679244022 c6989586621679244024) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679244022 (TyFun b6989586621679244023 c6989586621679244024 -> Type) -> Type) -> TyFun b6989586621679244023 (TyFun a6989586621679244022 c6989586621679244024 -> Type) -> *) (FlipSym1 b6989586621679244023 a6989586621679244022 c6989586621679244024) # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym1 b6989586621679244023 a6989586621679244022 c6989586621679244024) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679244025 c6989586621679244026 -> Type) -> (TyFun a6989586621679244027 b6989586621679244025 -> Type) -> TyFun a6989586621679244027 c6989586621679244026 -> *) ((:.$$$) b6989586621679244025 a6989586621679244027 c6989586621679244026) # 

Methods

suppressUnusedWarnings :: Proxy ((b6989586621679244025 :.$$$ a6989586621679244027) c6989586621679244026) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679244025 c6989586621679244026 -> Type) -> TyFun (TyFun a6989586621679244027 b6989586621679244025 -> Type) (TyFun a6989586621679244027 c6989586621679244026 -> Type) -> *) ((:.$$) b6989586621679244025 a6989586621679244027 c6989586621679244026) # 

Methods

suppressUnusedWarnings :: Proxy ((b6989586621679244025 :.$$ a6989586621679244027) c6989586621679244026) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679253491 (TyFun b6989586621679253491 c6989586621679253492 -> Type) -> Type) -> (TyFun a6989586621679253493 b6989586621679253491 -> Type) -> a6989586621679253493 -> TyFun a6989586621679253493 c6989586621679253492 -> *) (OnSym3 b6989586621679253491 a6989586621679253493 c6989586621679253492) # 

Methods

suppressUnusedWarnings :: Proxy (OnSym3 b6989586621679253491 a6989586621679253493 c6989586621679253492) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679253491 (TyFun b6989586621679253491 c6989586621679253492 -> Type) -> Type) -> (TyFun a6989586621679253493 b6989586621679253491 -> Type) -> TyFun a6989586621679253493 (TyFun a6989586621679253493 c6989586621679253492 -> Type) -> *) (OnSym2 b6989586621679253491 a6989586621679253493 c6989586621679253492) # 

Methods

suppressUnusedWarnings :: Proxy (OnSym2 b6989586621679253491 a6989586621679253493 c6989586621679253492) t -> () #

SuppressUnusedWarnings ((TyFun b6989586621679253491 (TyFun b6989586621679253491 c6989586621679253492 -> Type) -> Type) -> TyFun (TyFun a6989586621679253493 b6989586621679253491 -> Type) (TyFun a6989586621679253493 (TyFun a6989586621679253493 c6989586621679253492 -> Type) -> Type) -> *) (OnSym1 b6989586621679253491 a6989586621679253493 c6989586621679253492) # 

Methods

suppressUnusedWarnings :: Proxy (OnSym1 b6989586621679253491 a6989586621679253493 c6989586621679253492) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679358269 (TyFun b6989586621679358270 c6989586621679358271 -> Type) -> Type) -> TyFun (a6989586621679358269, b6989586621679358270) c6989586621679358271 -> *) (UncurrySym1 a6989586621679358269 b6989586621679358270 c6989586621679358271) # 

Methods

suppressUnusedWarnings :: Proxy (UncurrySym1 a6989586621679358269 b6989586621679358270 c6989586621679358271) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679369589 c6989586621679369590 -> Type) -> (TyFun b6989586621679369591 c6989586621679369590 -> Type) -> TyFun (Either a6989586621679369589 b6989586621679369591) c6989586621679369590 -> *) (Either_Sym2 a6989586621679369589 b6989586621679369591 c6989586621679369590) # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym2 a6989586621679369589 b6989586621679369591 c6989586621679369590) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679369589 c6989586621679369590 -> Type) -> TyFun (TyFun b6989586621679369591 c6989586621679369590 -> Type) (TyFun (Either a6989586621679369589 b6989586621679369591) c6989586621679369590 -> Type) -> *) (Either_Sym1 a6989586621679369589 b6989586621679369591 c6989586621679369590) # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym1 a6989586621679369589 b6989586621679369591 c6989586621679369590) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) -> TyFun [a6989586621679389299] (TyFun [b6989586621679389300] [c6989586621679389301] -> Type) -> *) (ZipWithSym1 a6989586621679389299 b6989586621679389300 c6989586621679389301) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a6989586621679389299 b6989586621679389300 c6989586621679389301) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) -> [a6989586621679389299] -> TyFun [b6989586621679389300] [c6989586621679389301] -> *) (ZipWithSym2 a6989586621679389299 b6989586621679389300 c6989586621679389301) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a6989586621679389299 b6989586621679389300 c6989586621679389301) t -> () #

SuppressUnusedWarnings ((TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) -> TyFun acc6989586621679389316 (TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]) -> Type) -> *) (MapAccumRSym1 x6989586621679389317 acc6989586621679389316 y6989586621679389318) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym1 x6989586621679389317 acc6989586621679389316 y6989586621679389318) t -> () #

SuppressUnusedWarnings ((TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) -> acc6989586621679389316 -> TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]) -> *) (MapAccumRSym2 x6989586621679389317 acc6989586621679389316 y6989586621679389318) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym2 x6989586621679389317 acc6989586621679389316 y6989586621679389318) t -> () #

SuppressUnusedWarnings ((TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) -> TyFun acc6989586621679389319 (TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]) -> Type) -> *) (MapAccumLSym1 x6989586621679389320 acc6989586621679389319 y6989586621679389321) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym1 x6989586621679389320 acc6989586621679389319 y6989586621679389321) t -> () #

SuppressUnusedWarnings ((TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) -> acc6989586621679389319 -> TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]) -> *) (MapAccumLSym2 x6989586621679389320 acc6989586621679389319 y6989586621679389321) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym2 x6989586621679389320 acc6989586621679389319 y6989586621679389321) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) -> NonEmpty a6989586621679608988 -> TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> *) (ZipWithSym2 a6989586621679608988 b6989586621679608989 c6989586621679608990) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a6989586621679608988 b6989586621679608989 c6989586621679608990) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type) -> *) (ZipWithSym1 a6989586621679608988 b6989586621679608989 c6989586621679608990) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a6989586621679608988 b6989586621679608989 c6989586621679608990) t -> () #

SuppressUnusedWarnings ([a6989586621679389302] -> TyFun [b6989586621679389303] (TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)] -> Type) -> *) (Zip3Sym1 a6989586621679389302 b6989586621679389303 c6989586621679389304) # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym1 a6989586621679389302 b6989586621679389303 c6989586621679389304) t -> () #

SuppressUnusedWarnings ([a6989586621679389302] -> [b6989586621679389303] -> TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)] -> *) (Zip3Sym2 a6989586621679389302 b6989586621679389303 c6989586621679389304) # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym2 a6989586621679389302 b6989586621679389303 c6989586621679389304) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> *) (Tuple3Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> *) (Tuple3Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867) t -> () #

SuppressUnusedWarnings (TyFun (TyFun (a6989586621679358272, b6989586621679358273) c6989586621679358274 -> Type) (TyFun a6989586621679358272 (TyFun b6989586621679358273 c6989586621679358274 -> Type) -> Type) -> *) (CurrySym0 a6989586621679358272 b6989586621679358273 c6989586621679358274) # 

Methods

suppressUnusedWarnings :: Proxy (CurrySym0 a6989586621679358272 b6989586621679358273 c6989586621679358274) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679244022 (TyFun b6989586621679244023 c6989586621679244024 -> Type) -> Type) (TyFun b6989586621679244023 (TyFun a6989586621679244022 c6989586621679244024 -> Type) -> Type) -> *) (FlipSym0 b6989586621679244023 a6989586621679244022 c6989586621679244024) # 

Methods

suppressUnusedWarnings :: Proxy (FlipSym0 b6989586621679244023 a6989586621679244022 c6989586621679244024) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679244025 c6989586621679244026 -> Type) (TyFun (TyFun a6989586621679244027 b6989586621679244025 -> Type) (TyFun a6989586621679244027 c6989586621679244026 -> Type) -> Type) -> *) ((:.$) b6989586621679244025 a6989586621679244027 c6989586621679244026) # 

Methods

suppressUnusedWarnings :: Proxy ((b6989586621679244025 :.$ a6989586621679244027) c6989586621679244026) t -> () #

SuppressUnusedWarnings (TyFun (TyFun b6989586621679253491 (TyFun b6989586621679253491 c6989586621679253492 -> Type) -> Type) (TyFun (TyFun a6989586621679253493 b6989586621679253491 -> Type) (TyFun a6989586621679253493 (TyFun a6989586621679253493 c6989586621679253492 -> Type) -> Type) -> Type) -> *) (OnSym0 b6989586621679253491 a6989586621679253493 c6989586621679253492) # 

Methods

suppressUnusedWarnings :: Proxy (OnSym0 b6989586621679253491 a6989586621679253493 c6989586621679253492) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679358269 (TyFun b6989586621679358270 c6989586621679358271 -> Type) -> Type) (TyFun (a6989586621679358269, b6989586621679358270) c6989586621679358271 -> Type) -> *) (UncurrySym0 a6989586621679358269 b6989586621679358270 c6989586621679358271) # 

Methods

suppressUnusedWarnings :: Proxy (UncurrySym0 a6989586621679358269 b6989586621679358270 c6989586621679358271) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679369589 c6989586621679369590 -> Type) (TyFun (TyFun b6989586621679369591 c6989586621679369590 -> Type) (TyFun (Either a6989586621679369589 b6989586621679369591) c6989586621679369590 -> Type) -> Type) -> *) (Either_Sym0 a6989586621679369589 b6989586621679369591 c6989586621679369590) # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym0 a6989586621679369589 b6989586621679369591 c6989586621679369590) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) (TyFun [a6989586621679389299] (TyFun [b6989586621679389300] [c6989586621679389301] -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679389299 b6989586621679389300 c6989586621679389301) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a6989586621679389299 b6989586621679389300 c6989586621679389301) t -> () #

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) (TyFun acc6989586621679389316 (TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]) -> Type) -> Type) -> *) (MapAccumRSym0 x6989586621679389317 acc6989586621679389316 y6989586621679389318) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym0 x6989586621679389317 acc6989586621679389316 y6989586621679389318) t -> () #

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) (TyFun acc6989586621679389319 (TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]) -> Type) -> Type) -> *) (MapAccumLSym0 x6989586621679389320 acc6989586621679389319 y6989586621679389321) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym0 x6989586621679389320 acc6989586621679389319 y6989586621679389321) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) (TyFun (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679608988 b6989586621679608989 c6989586621679608990) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a6989586621679608988 b6989586621679608989 c6989586621679608990) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679389290, b6989586621679389291, c6989586621679389292)] ([a6989586621679389290], [b6989586621679389291], [c6989586621679389292]) -> *) (Unzip3Sym0 a6989586621679389290 b6989586621679389291 c6989586621679389292) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip3Sym0 a6989586621679389290 b6989586621679389291 c6989586621679389292) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679389302] (TyFun [b6989586621679389303] (TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)] -> Type) -> Type) -> *) (Zip3Sym0 a6989586621679389302 b6989586621679389303 c6989586621679389304) # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym0 a6989586621679389302 b6989586621679389303 c6989586621679389304) t -> () #

SuppressUnusedWarnings (TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> Type) -> Type) -> *) (Tuple3Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple3Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) -> TyFun [a6989586621679389295] (TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) -> Type) -> *) (ZipWith3Sym1 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym1 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) -> [a6989586621679389295] -> TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) -> *) (ZipWith3Sym2 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym2 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) -> [a6989586621679389295] -> [b6989586621679389296] -> TyFun [c6989586621679389297] [d6989586621679389298] -> *) (ZipWith3Sym3 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym3 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) t -> () #

SuppressUnusedWarnings ([a6989586621679727940] -> [b6989586621679727941] -> [c6989586621679727942] -> TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> *) (Zip4Sym3 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym3 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) t -> () #

SuppressUnusedWarnings ([a6989586621679727940] -> [b6989586621679727941] -> TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) -> *) (Zip4Sym2 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym2 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) t -> () #

SuppressUnusedWarnings ([a6989586621679727940] -> TyFun [b6989586621679727941] (TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) -> Type) -> *) (Zip4Sym1 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym1 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> *) (Tuple4Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> *) (Tuple4Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> *) (Tuple4Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (TyFun [a6989586621679389295] (TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym0 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679389286, b6989586621679389287, c6989586621679389288, d6989586621679389289)] ([a6989586621679389286], [b6989586621679389287], [c6989586621679389288], [d6989586621679389289]) -> *) (Unzip4Sym0 a6989586621679389286 b6989586621679389287 c6989586621679389288 d6989586621679389289) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip4Sym0 a6989586621679389286 b6989586621679389287 c6989586621679389288 d6989586621679389289) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679727940] (TyFun [b6989586621679727941] (TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) -> Type) -> Type) -> *) (Zip4Sym0 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym0 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) t -> () #

SuppressUnusedWarnings (TyFun a3530822107858468865 (TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> Type) -> Type) -> Type) -> *) (Tuple4Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple4Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679727917] (TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) -> Type) -> *) (ZipWith4Sym1 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym1 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727917] -> TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) -> *) (ZipWith4Sym2 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym2 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727917] -> [b6989586621679727918] -> TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> *) (ZipWith4Sym3 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym3 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727917] -> [b6989586621679727918] -> [c6989586621679727919] -> TyFun [d6989586621679727920] [e6989586621679727921] -> *) (ZipWith4Sym4 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym4 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) t -> () #

SuppressUnusedWarnings ([a6989586621679727935] -> [b6989586621679727936] -> [c6989586621679727937] -> [d6989586621679727938] -> TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> *) (Zip5Sym4 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym4 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) t -> () #

SuppressUnusedWarnings ([a6989586621679727935] -> [b6989586621679727936] -> [c6989586621679727937] -> TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> *) (Zip5Sym3 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym3 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) t -> () #

SuppressUnusedWarnings ([a6989586621679727935] -> [b6989586621679727936] -> TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) -> *) (Zip5Sym2 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym2 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) t -> () #

SuppressUnusedWarnings ([a6989586621679727935] -> TyFun [b6989586621679727936] (TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) -> Type) -> *) (Zip5Sym1 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym1 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> *) (Tuple5Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> *) (Tuple5Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> *) (Tuple5Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> TyFun b3530822107858468866 (TyFun c3530822107858468867 (TyFun d3530822107858468868 (TyFun e3530822107858468869 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> Type) -> Type) -> Type) -> *) (Tuple5Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727917] (TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith4Sym0 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym0 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679389281, b6989586621679389282, c6989586621679389283, d6989586621679389284, e6989586621679389285)] ([a6989586621679389281], [b6989586621679389282], [c6989586621679389283], [d6989586621679389284], [e6989586621679389285]) -> *) (Unzip5Sym0 a6989586621679389281 b6989586621679389282 c6989586621679389283 d6989586621679389284 e6989586621679389285) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip5Sym0 a6989586621679389281 b6989586621679389282 c6989586621679389283 d6989586621679389284 e6989586621679389285) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679727935] (TyFun [b6989586621679727936] (TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip5Sym0 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym0 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) t -> () #

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) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple5Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679727911] (TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym1 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym1 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727911] -> TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) -> *) (ZipWith5Sym2 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym2 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727911] -> [b6989586621679727912] -> TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> *) (ZipWith5Sym3 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym3 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727911] -> [b6989586621679727912] -> [c6989586621679727913] -> TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> *) (ZipWith5Sym4 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym4 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727911] -> [b6989586621679727912] -> [c6989586621679727913] -> [d6989586621679727914] -> TyFun [e6989586621679727915] [f6989586621679727916] -> *) (ZipWith5Sym5 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym5 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) t -> () #

SuppressUnusedWarnings ([a6989586621679727929] -> [b6989586621679727930] -> [c6989586621679727931] -> [d6989586621679727932] -> [e6989586621679727933] -> TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> *) (Zip6Sym5 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym5 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) t -> () #

SuppressUnusedWarnings ([a6989586621679727929] -> [b6989586621679727930] -> [c6989586621679727931] -> [d6989586621679727932] -> TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> *) (Zip6Sym4 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym4 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) t -> () #

SuppressUnusedWarnings ([a6989586621679727929] -> [b6989586621679727930] -> [c6989586621679727931] -> TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> *) (Zip6Sym3 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym3 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) t -> () #

SuppressUnusedWarnings ([a6989586621679727929] -> [b6989586621679727930] -> TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) -> *) (Zip6Sym2 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym2 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) t -> () #

SuppressUnusedWarnings ([a6989586621679727929] -> TyFun [b6989586621679727930] (TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym1 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym1 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> e3530822107858468869 -> TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> *) (Tuple6Sym5 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym5 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> TyFun e3530822107858468869 (TyFun f3530822107858468870 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> Type) -> *) (Tuple6Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () #

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) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () #

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) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () #

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) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727911] (TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym0 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym0 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679389275, b6989586621679389276, c6989586621679389277, d6989586621679389278, e6989586621679389279, f6989586621679389280)] ([a6989586621679389275], [b6989586621679389276], [c6989586621679389277], [d6989586621679389278], [e6989586621679389279], [f6989586621679389280]) -> *) (Unzip6Sym0 a6989586621679389275 b6989586621679389276 c6989586621679389277 d6989586621679389278 e6989586621679389279 f6989586621679389280) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip6Sym0 a6989586621679389275 b6989586621679389276 c6989586621679389277 d6989586621679389278 e6989586621679389279 f6989586621679389280) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679727929] (TyFun [b6989586621679727930] (TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym0 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym0 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) t -> () #

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) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple6Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679727904] (TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym1 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym1 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727904] -> TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym2 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym2 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727904] -> [b6989586621679727905] -> TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> *) (ZipWith6Sym3 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym3 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727904] -> [b6989586621679727905] -> [c6989586621679727906] -> TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> *) (ZipWith6Sym4 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym4 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727904] -> [b6989586621679727905] -> [c6989586621679727906] -> [d6989586621679727907] -> TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> *) (ZipWith6Sym5 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym5 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727904] -> [b6989586621679727905] -> [c6989586621679727906] -> [d6989586621679727907] -> [e6989586621679727908] -> TyFun [f6989586621679727909] [g6989586621679727910] -> *) (ZipWith6Sym6 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym6 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) t -> () #

SuppressUnusedWarnings ([a6989586621679727922] -> [b6989586621679727923] -> [c6989586621679727924] -> [d6989586621679727925] -> [e6989586621679727926] -> [f6989586621679727927] -> TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> *) (Zip7Sym6 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym6 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) t -> () #

SuppressUnusedWarnings ([a6989586621679727922] -> [b6989586621679727923] -> [c6989586621679727924] -> [d6989586621679727925] -> [e6989586621679727926] -> TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> *) (Zip7Sym5 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym5 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) t -> () #

SuppressUnusedWarnings ([a6989586621679727922] -> [b6989586621679727923] -> [c6989586621679727924] -> [d6989586621679727925] -> TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> *) (Zip7Sym4 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym4 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) t -> () #

SuppressUnusedWarnings ([a6989586621679727922] -> [b6989586621679727923] -> [c6989586621679727924] -> TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> *) (Zip7Sym3 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym3 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) t -> () #

SuppressUnusedWarnings ([a6989586621679727922] -> [b6989586621679727923] -> TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym2 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym2 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) t -> () #

SuppressUnusedWarnings ([a6989586621679727922] -> TyFun [b6989586621679727923] (TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym1 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym1 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) t -> () #

SuppressUnusedWarnings (a3530822107858468865 -> b3530822107858468866 -> c3530822107858468867 -> d3530822107858468868 -> e3530822107858468869 -> f3530822107858468870 -> TyFun g3530822107858468871 (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> *) (Tuple7Sym6 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym6 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () #

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) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym5 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () #

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) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym4 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () #

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) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym3 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () #

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) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym2 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () #

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) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym1 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727904] (TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym0 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym0 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) t -> () #

SuppressUnusedWarnings (TyFun [(a6989586621679389268, b6989586621679389269, c6989586621679389270, d6989586621679389271, e6989586621679389272, f6989586621679389273, g6989586621679389274)] ([a6989586621679389268], [b6989586621679389269], [c6989586621679389270], [d6989586621679389271], [e6989586621679389272], [f6989586621679389273], [g6989586621679389274]) -> *) (Unzip7Sym0 a6989586621679389268 b6989586621679389269 c6989586621679389270 d6989586621679389271 e6989586621679389272 f6989586621679389273 g6989586621679389274) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip7Sym0 a6989586621679389268 b6989586621679389269 c6989586621679389270 d6989586621679389271 e6989586621679389272 f6989586621679389273 g6989586621679389274) t -> () #

SuppressUnusedWarnings (TyFun [a6989586621679727922] (TyFun [b6989586621679727923] (TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym0 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym0 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) t -> () #

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) # 

Methods

suppressUnusedWarnings :: Proxy (Tuple7Sym0 a3530822107858468865 b3530822107858468866 c3530822107858468867 d3530822107858468868 e3530822107858468869 f3530822107858468870 g3530822107858468871) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679727896] (TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym1 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym1 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727896] -> TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym2 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym2 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727896] -> [b6989586621679727897] -> TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym3 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym3 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727896] -> [b6989586621679727897] -> [c6989586621679727898] -> TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> *) (ZipWith7Sym4 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym4 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727896] -> [b6989586621679727897] -> [c6989586621679727898] -> [d6989586621679727899] -> TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> *) (ZipWith7Sym5 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym5 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727896] -> [b6989586621679727897] -> [c6989586621679727898] -> [d6989586621679727899] -> [e6989586621679727900] -> TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> *) (ZipWith7Sym6 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym6 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) t -> () #

SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727896] -> [b6989586621679727897] -> [c6989586621679727898] -> [d6989586621679727899] -> [e6989586621679727900] -> [f6989586621679727901] -> TyFun [g6989586621679727902] [h6989586621679727903] -> *) (ZipWith7Sym7 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym7 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) t -> () #

SuppressUnusedWarnings (TyFun (TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727896] (TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym0 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym0 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) t -> () #