singletons-2.2: A framework for generating singleton types

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

Data.Singletons.Prelude.List

Contents

Description

Defines functions and datatypes relating to the singleton for '[]', including a singletons version of a few of the definitions in Data.List.

Because many of these definitions are produced by Template Haskell, it is not possible to create proper Haddock documentation. Please look up the corresponding operation in Data.List. Also, please excuse the apparent repeated variable names. This is due to an interaction between Template Haskell and Haddock.

Synopsis

The singleton for lists

data family Sing (a :: k) #

The singleton kind-indexed data family.

Instances

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

Though Haddock doesn't show it, the Sing instance above declares constructors

SNil  :: Sing '[]
SCons :: Sing (h :: k) -> Sing (t :: [k]) -> Sing (h ': t)

type SList = (Sing :: [a] -> Type) #

SList is a kind-restricted synonym for Sing: type SList (a :: [k]) = Sing a

Basic functions

type family (a :: [a]) :++ (a :: [a]) :: [a] where ... infixr 5 #

Equations

'[] :++ ys = ys 
((:) x xs) :++ ys = Apply (Apply (:$) x) (Apply (Apply (:++$) xs) ys) 

(%:++) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:++$) t) t :: [a]) infixr 5 #

type family Head (a :: [a]) :: a where ... #

Equations

Head ((:) a _z_6989586621680001796) = a 
Head '[] = Apply ErrorSym0 "Data.Singletons.List.head: empty list" 

sHead :: forall t. Sing t -> Sing (Apply HeadSym0 t :: a) #

type family Last (a :: [a]) :: a where ... #

Equations

Last '[] = Apply ErrorSym0 "Data.Singletons.List.last: empty list" 
Last '[x] = x 
Last ((:) _z_6989586621680001786 ((:) x xs)) = Apply LastSym0 (Apply (Apply (:$) x) xs) 

sLast :: forall t. Sing t -> Sing (Apply LastSym0 t :: a) #

type family Tail (a :: [a]) :: [a] where ... #

Equations

Tail ((:) _z_6989586621680001777 t) = t 
Tail '[] = Apply ErrorSym0 "Data.Singletons.List.tail: empty list" 

sTail :: forall t. Sing t -> Sing (Apply TailSym0 t :: [a]) #

type family Init (a :: [a]) :: [a] where ... #

Equations

Init '[] = Apply ErrorSym0 "Data.Singletons.List.init: empty list" 
Init ((:) x xs) = Apply (Apply (Let6989586621680001746Init'Sym2 x xs) x) xs 

sInit :: forall t. Sing t -> Sing (Apply InitSym0 t :: [a]) #

type family Null (a :: [a]) :: Bool where ... #

Equations

Null '[] = TrueSym0 
Null ((:) _z_6989586621680001675 _z_6989586621680001678) = FalseSym0 

sNull :: forall t. Sing t -> Sing (Apply NullSym0 t :: Bool) #

type family Length (a :: [a]) :: Nat where ... #

Equations

Length '[] = FromInteger 0 
Length ((:) _z_6989586621679998590 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply LengthSym0 xs) 

sLength :: forall t. Sing t -> Sing (Apply LengthSym0 t :: Nat) #

List transformations

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

Equations

Map _z_6989586621679703561 '[] = '[] 
Map f ((:) x xs) = Apply (Apply (:$) (Apply f x)) (Apply (Apply MapSym0 f) xs) 

sMap :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b]) #

type family Reverse (a :: [a]) :: [a] where ... #

Equations

Reverse l = Apply (Apply (Let6989586621680001641RevSym1 l) l) '[] 

sReverse :: forall t. Sing t -> Sing (Apply ReverseSym0 t :: [a]) #

type family Intersperse (a :: a) (a :: [a]) :: [a] where ... #

Equations

Intersperse _z_6989586621680001619 '[] = '[] 
Intersperse sep ((:) x xs) = Apply (Apply (:$) x) (Apply (Apply PrependToAllSym0 sep) xs) 

sIntersperse :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a]) #

type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ... #

Equations

Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) 

sIntercalate :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a]) #

type family Transpose (a :: [[a]]) :: [[a]] where ... #

Equations

Transpose '[] = '[] 
Transpose ((:) '[] xss) = Apply TransposeSym0 xss 
Transpose ((:) ((:) x xs) xss) = Apply (Apply (:$) (Apply (Apply (:$) x) (Apply (Apply MapSym0 HeadSym0) xss))) (Apply TransposeSym0 (Apply (Apply (:$) xs) (Apply (Apply MapSym0 TailSym0) xss))) 

sTranspose :: forall t. Sing t -> Sing (Apply TransposeSym0 t :: [[a]]) #

type family Subsequences (a :: [a]) :: [[a]] where ... #

Equations

Subsequences xs = Apply (Apply (:$) '[]) (Apply NonEmptySubsequencesSym0 xs) 

sSubsequences :: forall t. Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]]) #

type family Permutations (a :: [a]) :: [[a]] where ... #

Equations

Permutations xs0 = Apply (Apply (:$) xs0) (Apply (Apply (Let6989586621680001194PermsSym1 xs0) xs0) '[]) 

sPermutations :: forall t. Sing t -> Sing (Apply PermutationsSym0 t :: [[a]]) #

Reducing lists (folds)

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

Equations

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

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

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

Equations

Foldl' f z0 xs0 = Apply (Apply (Let6989586621680001108LgoSym3 f z0 xs0) z0) xs0 

sFoldl' :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) #

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

Equations

Foldl1 f ((:) x xs) = Apply (Apply (Apply FoldlSym0 f) x) xs 
Foldl1 _z_6989586621680000885 '[] = Apply ErrorSym0 "Data.Singletons.List.foldl1: empty list" 

sFoldl1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) #

type family Foldl1' (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ... #

Equations

Foldl1' f ((:) x xs) = Apply (Apply (Apply Foldl'Sym0 f) x) xs 
Foldl1' _z_6989586621680001186 '[] = Apply ErrorSym0 "Data.Singletons.List.foldl1': empty list" 

sFoldl1' :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a) #

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

Equations

Foldr k z a_6989586621679703582 = Apply (Let6989586621679703587GoSym3 k z a_6989586621679703582) a_6989586621679703582 

sFoldr :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) #

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

Equations

Foldr1 _z_6989586621680000843 '[x] = x 
Foldr1 f ((:) x ((:) wild_6989586621679997571 wild_6989586621679997573)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let6989586621680000851XsSym4 f x wild_6989586621679997571 wild_6989586621679997573)) 
Foldr1 _z_6989586621680000870 '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" 

sFoldr1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) #

Special folds

type family Concat (a :: [[a]]) :: [a] where ... #

Equations

Concat a_6989586621680000827 = Apply (Apply (Apply FoldrSym0 (:++$)) '[]) a_6989586621680000827 

sConcat :: forall t. Sing t -> Sing (Apply ConcatSym0 t :: [a]) #

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

Equations

ConcatMap f a_6989586621680000823 = Apply (Apply (Apply FoldrSym0 (Apply (Apply (:.$) (:++$)) f)) '[]) a_6989586621680000823 

sConcatMap :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) #

type family And (a :: [Bool]) :: Bool where ... #

Equations

And '[] = TrueSym0 
And ((:) x xs) = Apply (Apply (:&&$) x) (Apply AndSym0 xs) 

sAnd :: forall t. Sing t -> Sing (Apply AndSym0 t :: Bool) #

type family Or (a :: [Bool]) :: Bool where ... #

Equations

Or '[] = FalseSym0 
Or ((:) x xs) = Apply (Apply (:||$) x) (Apply OrSym0 xs) 

sOr :: forall t. Sing t -> Sing (Apply OrSym0 t :: Bool) #

type family Any_ (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ... #

Equations

Any_ _z_6989586621679986434 '[] = FalseSym0 
Any_ p ((:) x xs) = Apply (Apply (:||$) (Apply p x)) (Apply (Apply Any_Sym0 p) xs) 

sAny_ :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Any_Sym0 t) t :: Bool) #

type family All (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ... #

Equations

All _z_6989586621680000796 '[] = TrueSym0 
All p ((:) x xs) = Apply (Apply (:&&$) (Apply p x)) (Apply (Apply AllSym0 p) xs) 

sAll :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) #

type family Sum (a :: [a]) :: a where ... #

Equations

Sum l = Apply (Apply (Let6989586621679998623Sum'Sym1 l) l) (FromInteger 0) 

sSum :: forall t. SNum a => Sing t -> Sing (Apply SumSym0 t :: a) #

type family Product (a :: [a]) :: a where ... #

Equations

Product l = Apply (Apply (Let6989586621679998599ProdSym1 l) l) (FromInteger 1) 

sProduct :: forall t. SNum a => Sing t -> Sing (Apply ProductSym0 t :: a) #

type family Maximum (a :: [a]) :: a where ... #

Equations

Maximum '[] = Apply ErrorSym0 "Data.Singletons.List.maximum: empty list" 
Maximum ((:) wild_6989586621679997651 wild_6989586621679997653) = Apply (Apply Foldl1Sym0 MaxSym0) (Let6989586621680001068XsSym2 wild_6989586621679997651 wild_6989586621679997653) 

sMaximum :: forall t. SOrd a => Sing t -> Sing (Apply MaximumSym0 t :: a) #

type family Minimum (a :: [a]) :: a where ... #

Equations

Minimum '[] = Apply ErrorSym0 "Data.Singletons.List.minimum: empty list" 
Minimum ((:) wild_6989586621679997655 wild_6989586621679997657) = Apply (Apply Foldl1Sym0 MinSym0) (Let6989586621680001082XsSym2 wild_6989586621679997655 wild_6989586621679997657) 

sMinimum :: forall t. SOrd a => Sing t -> Sing (Apply MinimumSym0 t :: a) #

any_ :: forall a. (a -> Bool) -> [a] -> Bool #

Building lists

Scans

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

Equations

Scanl f q ls = Apply (Apply (:$) q) (Case_6989586621680000767 f q ls ls) 

sScanl :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b]) #

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

Equations

Scanl1 f ((:) x xs) = Apply (Apply (Apply ScanlSym0 f) x) xs 
Scanl1 _z_6989586621680000784 '[] = '[] 

sScanl1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a]) #

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

Equations

Scanr _z_6989586621680000717 q0 '[] = Apply (Apply (:$) q0) '[] 
Scanr f q0 ((:) x xs) = Case_6989586621680000744 f q0 x xs (Let6989586621680000725Scrutinee_6989586621679997575Sym4 f q0 x xs) 

sScanr :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b]) #

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

Equations

Scanr1 _z_6989586621680000648 '[] = '[] 
Scanr1 _z_6989586621680000651 '[x] = Apply (Apply (:$) x) '[] 
Scanr1 f ((:) x ((:) wild_6989586621679997579 wild_6989586621679997581)) = Case_6989586621680000697 f x wild_6989586621679997579 wild_6989586621679997581 (Let6989586621680000678Scrutinee_6989586621679997577Sym4 f x wild_6989586621679997579 wild_6989586621679997581) 

sScanr1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a]) #

Accumulating maps

type family MapAccumL (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... #

Equations

MapAccumL _z_6989586621680000482 s '[] = Apply (Apply Tuple2Sym0 s) '[] 
MapAccumL f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let6989586621680000490S''Sym4 f s x xs)) (Apply (Apply (:$) (Let6989586621680000490YSym4 f s x xs)) (Let6989586621680000490YsSym4 f s x xs)) 

sMapAccumL :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (acc, [y])) #

type family MapAccumR (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... #

Equations

MapAccumR _z_6989586621680000310 s '[] = Apply (Apply Tuple2Sym0 s) '[] 
MapAccumR f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let6989586621680000318S''Sym4 f s x xs)) (Apply (Apply (:$) (Let6989586621680000318YSym4 f s x xs)) (Let6989586621680000318YsSym4 f s x xs)) 

sMapAccumR :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (acc, [y])) #

Cyclical lists

type family Replicate (a :: Nat) (a :: a) :: [a] where ... #

Equations

Replicate n x = Case_6989586621679998583 n x (Let6989586621679998575Scrutinee_6989586621679997663Sym2 n x) 

sReplicate :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a]) #

Unfolding

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

Equations

Unfoldr f b = Case_6989586621680000290 f b (Let6989586621680000282Scrutinee_6989586621679997583Sym2 f b) 

sUnfoldr :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a]) #

Sublists

Extracting sublists

type family Take (a :: Nat) (a :: [a]) :: [a] where ... #

Equations

Take _z_6989586621679998770 '[] = '[] 
Take n ((:) x xs) = Case_6989586621679998789 n x xs (Let6989586621679998776Scrutinee_6989586621679997647Sym3 n x xs) 

sTake :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) #

type family Drop (a :: Nat) (a :: [a]) :: [a] where ... #

Equations

Drop _z_6989586621679998739 '[] = '[] 
Drop n ((:) x xs) = Case_6989586621679998758 n x xs (Let6989586621679998745Scrutinee_6989586621679997649Sym3 n x xs) 

sDrop :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) #

type family SplitAt (a :: Nat) (a :: [a]) :: ([a], [a]) where ... #

Equations

SplitAt n xs = Apply (Apply Tuple2Sym0 (Apply (Apply TakeSym0 n) xs)) (Apply (Apply DropSym0 n) xs) 

sSplitAt :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) #

type family TakeWhile (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ... #

Equations

TakeWhile _z_6989586621679999143 '[] = '[] 
TakeWhile p ((:) x xs) = Case_6989586621679999162 p x xs (Let6989586621679999149Scrutinee_6989586621679997637Sym3 p x xs) 

sTakeWhile :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) #

type family DropWhile (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ... #

Equations

DropWhile _z_6989586621679999099 '[] = '[] 
DropWhile p ((:) x xs') = Case_6989586621679999131 p x xs' (Let6989586621679999118Scrutinee_6989586621679997639Sym3 p x xs') 

sDropWhile :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) #

type family DropWhileEnd (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ... #

Equations

DropWhileEnd p a_6989586621680001690 = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_6989586621680001694Sym0 p) a_6989586621680001690)) '[]) a_6989586621680001690 

sDropWhileEnd :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a]) #

type family Span (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... #

Equations

Span _z_6989586621679998917 '[] = Apply (Apply Tuple2Sym0 (Let6989586621679998920XsSym1 _z_6989586621679998917)) (Let6989586621679998920XsSym1 _z_6989586621679998917) 
Span p ((:) x xs') = Case_6989586621679998953 p x xs' (Let6989586621679998940Scrutinee_6989586621679997643Sym3 p x xs') 

sSpan :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) #

type family Break (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... #

Equations

Break _z_6989586621679998812 '[] = Apply (Apply Tuple2Sym0 (Let6989586621679998815XsSym1 _z_6989586621679998812)) (Let6989586621679998815XsSym1 _z_6989586621679998812) 
Break p ((:) x xs') = Case_6989586621679998848 p x xs' (Let6989586621679998835Scrutinee_6989586621679997645Sym3 p x xs') 

sBreak :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) #

type family Group (a :: [a]) :: [[a]] where ... #

Equations

Group xs = Apply (Apply GroupBySym0 (:==$)) xs 

sGroup :: forall t. SEq a => Sing t -> Sing (Apply GroupSym0 t :: [[a]]) #

type family Inits (a :: [a]) :: [[a]] where ... #

Equations

Inits xs = Apply (Apply (:$) '[]) (Case_6989586621680000266 xs xs) 

sInits :: forall t. Sing t -> Sing (Apply InitsSym0 t :: [[a]]) #

type family Tails (a :: [a]) :: [[a]] where ... #

Equations

Tails xs = Apply (Apply (:$) xs) (Case_6989586621680000243 xs xs) 

sTails :: forall t. Sing t -> Sing (Apply TailsSym0 t :: [[a]]) #

Predicates

type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... #

Equations

IsPrefixOf '[] '[] = TrueSym0 
IsPrefixOf '[] ((:) _z_6989586621680000222 _z_6989586621680000225) = TrueSym0 
IsPrefixOf ((:) _z_6989586621680000228 _z_6989586621680000231) '[] = FalseSym0 
IsPrefixOf ((:) x xs) ((:) y ys) = Apply (Apply (:&&$) (Apply (Apply (:==$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) 

sIsPrefixOf :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) #

type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ... #

sIsSuffixOf :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) #

type family IsInfixOf (a :: [a]) (a :: [a]) :: Bool where ... #

Equations

IsInfixOf needle haystack = Apply (Apply Any_Sym0 (Apply IsPrefixOfSym0 needle)) (Apply TailsSym0 haystack) 

sIsInfixOf :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool) #

Searching lists

Searching by equality

type family Elem (a :: a) (a :: [a]) :: Bool where ... #

Equations

Elem _z_6989586621680000159 '[] = FalseSym0 
Elem x ((:) y ys) = Apply (Apply (:||$) (Apply (Apply (:==$) x) y)) (Apply (Apply ElemSym0 x) ys) 

sElem :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) #

type family NotElem (a :: a) (a :: [a]) :: Bool where ... #

Equations

NotElem _z_6989586621680000144 '[] = TrueSym0 
NotElem x ((:) y ys) = Apply (Apply (:&&$) (Apply (Apply (:/=$) x) y)) (Apply (Apply NotElemSym0 x) ys) 

sNotElem :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) #

type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... #

Equations

Lookup _key '[] = NothingSym0 
Lookup key ((:) '(x, y) xys) = Case_6989586621679998727 key x y xys (Let6989586621679998708Scrutinee_6989586621679997659Sym4 key x y xys) 

sLookup :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b) #

Searching with a predicate

type family Find (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe a where ... #

Equations

Find p a_6989586621679999203 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FilterSym0 p)) a_6989586621679999203 

sFind :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a) #

type family Filter (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ... #

Equations

Filter _p '[] = '[] 
Filter p ((:) x xs) = Case_6989586621679999191 p x xs (Let6989586621679999178Scrutinee_6989586621679997625Sym3 p x xs) 

sFilter :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) #

type family Partition (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... #

Equations

Partition p xs = Apply (Apply (Apply FoldrSym0 (Apply SelectSym0 p)) (Apply (Apply Tuple2Sym0 '[]) '[])) xs 

sPartition :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) #

Indexing lists

type family (a :: [a]) :!! (a :: Nat) :: a where ... #

Equations

'[] :!! _z_6989586621679998542 = Apply ErrorSym0 "Data.Singletons.List.!!: index too large" 
((:) x xs) :!! n = Case_6989586621679998561 x xs n (Let6989586621679998548Scrutinee_6989586621679997665Sym3 x xs n) 

(%:!!) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:!!$) t) t :: a) #

type family ElemIndex (a :: a) (a :: [a]) :: Maybe Nat where ... #

Equations

ElemIndex x a_6989586621680000131 = Apply (Apply FindIndexSym0 (Apply (:==$) x)) a_6989586621680000131 

sElemIndex :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat) #

type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ... #

Equations

ElemIndices x a_6989586621680000105 = Apply (Apply FindIndicesSym0 (Apply (:==$) x)) a_6989586621680000105 

sElemIndices :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat]) #

type family FindIndex (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe Nat where ... #

Equations

FindIndex p a_6989586621680000118 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621680000118 

sFindIndex :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat) #

type family FindIndices (a :: TyFun a Bool -> Type) (a :: [a]) :: [Nat] where ... #

Equations

FindIndices p xs = Apply (Apply MapSym0 SndSym0) (Apply (Apply FilterSym0 (Apply (Apply Lambda_6989586621680000073Sym0 p) xs)) (Apply (Apply ZipSym0 xs) (Apply (Apply (Let6989586621680000044BuildListSym2 p xs) (FromInteger 0)) xs))) 

sFindIndices :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat]) #

Zipping and unzipping lists

type family Zip (a :: [a]) (a :: [b]) :: [(a, b)] where ... #

Equations

Zip ((:) x xs) ((:) y ys) = Apply (Apply (:$) (Apply (Apply Tuple2Sym0 x) y)) (Apply (Apply ZipSym0 xs) ys) 
Zip '[] '[] = '[] 
Zip ((:) _z_6989586621680000021 _z_6989586621680000024) '[] = '[] 
Zip '[] ((:) _z_6989586621680000027 _z_6989586621680000030) = '[] 

sZip :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)]) #

type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ... #

Equations

Zip3 ((:) a as) ((:) b bs) ((:) c cs) = Apply (Apply (:$) (Apply (Apply (Apply Tuple3Sym0 a) b) c)) (Apply (Apply (Apply Zip3Sym0 as) bs) cs) 
Zip3 '[] '[] '[] = '[] 
Zip3 '[] '[] ((:) _z_6989586621679999954 _z_6989586621679999957) = '[] 
Zip3 '[] ((:) _z_6989586621679999960 _z_6989586621679999963) '[] = '[] 
Zip3 '[] ((:) _z_6989586621679999966 _z_6989586621679999969) ((:) _z_6989586621679999972 _z_6989586621679999975) = '[] 
Zip3 ((:) _z_6989586621679999978 _z_6989586621679999981) '[] '[] = '[] 
Zip3 ((:) _z_6989586621679999984 _z_6989586621679999987) '[] ((:) _z_6989586621679999990 _z_6989586621679999993) = '[] 
Zip3 ((:) _z_6989586621679999996 _z_6989586621679999999) ((:) _z_6989586621680000002 _z_6989586621680000005) '[] = '[] 

sZip3 :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)]) #

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

Equations

ZipWith f ((:) x xs) ((:) y ys) = Apply (Apply (:$) (Apply (Apply f x) y)) (Apply (Apply (Apply ZipWithSym0 f) xs) ys) 
ZipWith _z_6989586621679999912 '[] '[] = '[] 
ZipWith _z_6989586621679999915 ((:) _z_6989586621679999918 _z_6989586621679999921) '[] = '[] 
ZipWith _z_6989586621679999924 '[] ((:) _z_6989586621679999927 _z_6989586621679999930) = '[] 

sZipWith :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c]) #

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

Equations

ZipWith3 z ((:) a as) ((:) b bs) ((:) c cs) = Apply (Apply (:$) (Apply (Apply (Apply z a) b) c)) (Apply (Apply (Apply (Apply ZipWith3Sym0 z) as) bs) cs) 
ZipWith3 _z_6989586621679999817 '[] '[] '[] = '[] 
ZipWith3 _z_6989586621679999820 '[] '[] ((:) _z_6989586621679999823 _z_6989586621679999826) = '[] 
ZipWith3 _z_6989586621679999829 '[] ((:) _z_6989586621679999832 _z_6989586621679999835) '[] = '[] 
ZipWith3 _z_6989586621679999838 '[] ((:) _z_6989586621679999841 _z_6989586621679999844) ((:) _z_6989586621679999847 _z_6989586621679999850) = '[] 
ZipWith3 _z_6989586621679999853 ((:) _z_6989586621679999856 _z_6989586621679999859) '[] '[] = '[] 
ZipWith3 _z_6989586621679999862 ((:) _z_6989586621679999865 _z_6989586621679999868) '[] ((:) _z_6989586621679999871 _z_6989586621679999874) = '[] 
ZipWith3 _z_6989586621679999877 ((:) _z_6989586621679999880 _z_6989586621679999883) ((:) _z_6989586621679999886 _z_6989586621679999889) '[] = '[] 

sZipWith3 :: forall t t t t. Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d]) #

type family Unzip (a :: [(a, b)]) :: ([a], [b]) where ... #

Equations

Unzip xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679999763Sym0 xs)) (Apply (Apply Tuple2Sym0 '[]) '[])) xs 

sUnzip :: forall t. Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b])) #

type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ... #

Equations

Unzip3 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679999731Sym0 xs)) (Apply (Apply (Apply Tuple3Sym0 '[]) '[]) '[])) xs 

sUnzip3 :: forall t. Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c])) #

type family Unzip4 (a :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ... #

Equations

Unzip4 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679999697Sym0 xs)) (Apply (Apply (Apply (Apply Tuple4Sym0 '[]) '[]) '[]) '[])) xs 

sUnzip4 :: forall t. Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d])) #

type family Unzip5 (a :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ... #

Equations

Unzip5 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679999661Sym0 xs)) (Apply (Apply (Apply (Apply (Apply Tuple5Sym0 '[]) '[]) '[]) '[]) '[])) xs 

sUnzip5 :: forall t. Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e])) #

type family Unzip6 (a :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ... #

Equations

Unzip6 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679999623Sym0 xs)) (Apply (Apply (Apply (Apply (Apply (Apply Tuple6Sym0 '[]) '[]) '[]) '[]) '[]) '[])) xs 

sUnzip6 :: forall t. Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f])) #

type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... #

Equations

Unzip7 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679999583Sym0 xs)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply Tuple7Sym0 '[]) '[]) '[]) '[]) '[]) '[]) '[])) xs 

sUnzip7 :: forall t. Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g])) #

Special lists

"Set" operations

type family Nub (a :: [a]) :: [a] where ... #

Equations

Nub l = Apply (Apply (Let6989586621680000170Nub'Sym1 l) l) '[] 

sNub :: forall t. SEq a => Sing t -> Sing (Apply NubSym0 t :: [a]) #

type family Delete (a :: a) (a :: [a]) :: [a] where ... #

Equations

Delete a_6989586621679999548 a_6989586621679999550 = Apply (Apply (Apply DeleteBySym0 (:==$)) a_6989586621679999548) a_6989586621679999550 

sDelete :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a]) #

type family (a :: [a]) :\\ (a :: [a]) :: [a] where ... infix 5 #

Equations

a_6989586621679999563 :\\ a_6989586621679999565 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 DeleteSym0)) a_6989586621679999563) a_6989586621679999565 

(%:\\) :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply (:\\$) t) t :: [a]) infix 5 #

type family Union (a :: [a]) (a :: [a]) :: [a] where ... #

Equations

Union a_6989586621679999533 a_6989586621679999535 = Apply (Apply (Apply UnionBySym0 (:==$)) a_6989586621679999533) a_6989586621679999535 

sUnion :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a]) #

type family Intersect (a :: [a]) (a :: [a]) :: [a] where ... #

Equations

Intersect a_6989586621679999336 a_6989586621679999338 = Apply (Apply (Apply IntersectBySym0 (:==$)) a_6989586621679999336) a_6989586621679999338 

sIntersect :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a]) #

Ordered lists

type family Insert (a :: a) (a :: [a]) :: [a] where ... #

Equations

Insert e ls = Apply (Apply (Apply InsertBySym0 CompareSym0) e) ls 

sInsert :: forall t t. SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a]) #

type family Sort (a :: [a]) :: [a] where ... #

Equations

Sort a_6989586621679999439 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679999439 

sSort :: forall t. SOrd a => Sing t -> Sing (Apply SortSym0 t :: [a]) #

Generalized functions

The "By" operations

User-supplied equality (replacing an Eq context)

The predicate is assumed to define an equivalence.

type family NubBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [a] where ... #

Equations

NubBy eq l = Apply (Apply (Let6989586621679998477NubBy'Sym2 eq l) l) '[] 

sNubBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a]) #

type family DeleteBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... #

Equations

DeleteBy _z_6989586621679999461 _z_6989586621679999464 '[] = '[] 
DeleteBy eq x ((:) y ys) = Case_6989586621679999490 eq x y ys (Let6989586621679999471Scrutinee_6989586621679997609Sym4 eq x y ys) 

sDeleteBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a]) #

type family DeleteFirstsBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... #

Equations

DeleteFirstsBy eq a_6989586621679999508 a_6989586621679999510 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679999508) a_6989586621679999510 

sDeleteFirstsBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a]) #

type family UnionBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... #

Equations

UnionBy eq xs ys = Apply (Apply (:++$) xs) (Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) (Apply (Apply NubBySym0 eq) ys)) xs) 

sUnionBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a]) #

type family IntersectBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... #

Equations

IntersectBy _z_6989586621679999222 '[] '[] = '[] 
IntersectBy _z_6989586621679999225 '[] ((:) _z_6989586621679999228 _z_6989586621679999231) = '[] 
IntersectBy _z_6989586621679999234 ((:) _z_6989586621679999237 _z_6989586621679999240) '[] = '[] 
IntersectBy eq ((:) wild_6989586621679997629 wild_6989586621679997631) ((:) wild_6989586621679997633 wild_6989586621679997635) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679999299Sym0 eq) wild_6989586621679997629) wild_6989586621679997631) wild_6989586621679997633) wild_6989586621679997635)) (Let6989586621679999248XsSym5 eq wild_6989586621679997629 wild_6989586621679997631 wild_6989586621679997633 wild_6989586621679997635) 

sIntersectBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a]) #

type family GroupBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [[a]] where ... #

Equations

GroupBy _z_6989586621679999022 '[] = '[] 
GroupBy eq ((:) x xs) = Apply (Apply (:$) (Apply (Apply (:$) x) (Let6989586621679999028YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621679999028ZsSym3 eq x xs)) 

sGroupBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]]) #

User-supplied comparison (replacing an Ord context)

The function is assumed to define a total ordering.

type family SortBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: [a] where ... #

Equations

SortBy cmp a_6989586621679999435 = Apply (Apply (Apply FoldrSym0 (Apply InsertBySym0 cmp)) '[]) a_6989586621679999435 

sSortBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a]) #

type family InsertBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... #

Equations

InsertBy _z_6989586621679999366 x '[] = Apply (Apply (:$) x) '[] 
InsertBy cmp x ((:) y ys') = Case_6989586621679999412 cmp x y ys' (Let6989586621679999393Scrutinee_6989586621679997611Sym4 cmp x y ys') 

sInsertBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a]) #

type family MaximumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... #

Equations

MaximumBy _z_6989586621680000897 '[] = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" 
MaximumBy cmp ((:) wild_6989586621679997615 wild_6989586621679997617) = Apply (Apply Foldl1Sym0 (Let6989586621680000916MaxBySym3 cmp wild_6989586621679997615 wild_6989586621679997617)) (Let6989586621680000903XsSym3 cmp wild_6989586621679997615 wild_6989586621679997617) 

sMaximumBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) #

type family MinimumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... #

Equations

MinimumBy _z_6989586621680000984 '[] = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" 
MinimumBy cmp ((:) wild_6989586621679997621 wild_6989586621679997623) = Apply (Apply Foldl1Sym0 (Let6989586621680001003MinBySym3 cmp wild_6989586621679997621 wild_6989586621679997623)) (Let6989586621680000990XsSym3 cmp wild_6989586621679997621 wild_6989586621679997623) 

sMinimumBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) #

The "generic" operations

The prefix `generic' indicates an overloaded function that is a generalized version of a Prelude function.

type family GenericLength (a :: [a]) :: i where ... #

Equations

GenericLength '[] = FromInteger 0 
GenericLength ((:) _z_6989586621679998437 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply GenericLengthSym0 xs) 

sGenericLength :: forall t. SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i) #

Defunctionalization symbols

type NilSym0 = '[] #

data (:$) l #

Instances

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

Methods

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

type Apply a3530822107858468866 (TyFun [a3530822107858468866] [a3530822107858468866] -> Type) ((:$) a3530822107858468866) l0 # 
type Apply a3530822107858468866 (TyFun [a3530822107858468866] [a3530822107858468866] -> Type) ((:$) a3530822107858468866) l0 = (:$$) a3530822107858468866 l0

data l :$$ l #

Instances

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

Methods

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

type Apply [a3530822107858468866] [a3530822107858468866] ((:$$) a3530822107858468866 l0) l1 # 
type Apply [a3530822107858468866] [a3530822107858468866] ((:$$) a3530822107858468866 l0) l1 = (:$$$) a3530822107858468866 l0 l1

type (:$$$) t t = (:) t t #

type (:++$$$) t t = (:++) t t #

data l :++$$ l #

Instances

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

Methods

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

type Apply [a6989586621679703398] [a6989586621679703398] ((:++$$) a6989586621679703398 l0) l1 # 
type Apply [a6989586621679703398] [a6989586621679703398] ((:++$$) a6989586621679703398 l0) l1 = (:++$$$) a6989586621679703398 l0 l1

data (:++$) l #

Instances

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

Methods

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

type Apply [a6989586621679703398] (TyFun [a6989586621679703398] [a6989586621679703398] -> Type) ((:++$) a6989586621679703398) l0 # 
type Apply [a6989586621679703398] (TyFun [a6989586621679703398] [a6989586621679703398] -> Type) ((:++$) a6989586621679703398) l0 = (:++$$) a6989586621679703398 l0

data HeadSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997124] a6989586621679997124 (HeadSym0 a6989586621679997124) l0 # 
type Apply [a6989586621679997124] a6989586621679997124 (HeadSym0 a6989586621679997124) l0 = HeadSym1 a6989586621679997124 l0

type HeadSym1 t = Head t #

data LastSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997123] a6989586621679997123 (LastSym0 a6989586621679997123) l0 # 
type Apply [a6989586621679997123] a6989586621679997123 (LastSym0 a6989586621679997123) l0 = LastSym1 a6989586621679997123 l0

type LastSym1 t = Last t #

data TailSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997122] [a6989586621679997122] (TailSym0 a6989586621679997122) l0 # 
type Apply [a6989586621679997122] [a6989586621679997122] (TailSym0 a6989586621679997122) l0 = TailSym1 a6989586621679997122 l0

type TailSym1 t = Tail t #

data InitSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997121] [a6989586621679997121] (InitSym0 a6989586621679997121) l0 # 
type Apply [a6989586621679997121] [a6989586621679997121] (InitSym0 a6989586621679997121) l0 = InitSym1 a6989586621679997121 l0

type InitSym1 t = Init t #

data NullSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997120] Bool (NullSym0 a6989586621679997120) l0 # 
type Apply [a6989586621679997120] Bool (NullSym0 a6989586621679997120) l0 = NullSym1 a6989586621679997120 l0

type NullSym1 t = Null t #

data LengthSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997007] Nat (LengthSym0 a6989586621679997007) l0 # 
type Apply [a6989586621679997007] Nat (LengthSym0 a6989586621679997007) l0 = LengthSym1 a6989586621679997007 l0

type LengthSym1 t = Length t #

data MapSym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679703399 b6989586621679703400 -> Type) (TyFun [a6989586621679703399] [b6989586621679703400] -> Type) -> *) (MapSym0 a6989586621679703399 b6989586621679703400) # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a6989586621679703399 b6989586621679703400) t -> () #

type Apply (TyFun a6989586621679703399 b6989586621679703400 -> Type) (TyFun [a6989586621679703399] [b6989586621679703400] -> Type) (MapSym0 a6989586621679703399 b6989586621679703400) l0 # 
type Apply (TyFun a6989586621679703399 b6989586621679703400 -> Type) (TyFun [a6989586621679703399] [b6989586621679703400] -> Type) (MapSym0 a6989586621679703399 b6989586621679703400) l0 = MapSym1 a6989586621679703399 b6989586621679703400 l0

data MapSym1 l l #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679703399 b6989586621679703400 -> Type) -> TyFun [a6989586621679703399] [b6989586621679703400] -> *) (MapSym1 a6989586621679703399 b6989586621679703400) # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a6989586621679703399 b6989586621679703400) t -> () #

type Apply [a6989586621679703399] [b6989586621679703400] (MapSym1 a6989586621679703399 b6989586621679703400 l0) l1 # 
type Apply [a6989586621679703399] [b6989586621679703400] (MapSym1 a6989586621679703399 b6989586621679703400 l0) l1 = MapSym2 a6989586621679703399 b6989586621679703400 l0 l1

type MapSym2 t t = Map t t #

data ReverseSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997119] [a6989586621679997119] (ReverseSym0 a6989586621679997119) l0 # 
type Apply [a6989586621679997119] [a6989586621679997119] (ReverseSym0 a6989586621679997119) l0 = ReverseSym1 a6989586621679997119 l0

type ReverseSym1 t = Reverse t #

data IntersperseSym0 l #

Instances

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

Methods

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

type Apply a6989586621679997118 (TyFun [a6989586621679997118] [a6989586621679997118] -> Type) (IntersperseSym0 a6989586621679997118) l0 # 
type Apply a6989586621679997118 (TyFun [a6989586621679997118] [a6989586621679997118] -> Type) (IntersperseSym0 a6989586621679997118) l0 = IntersperseSym1 a6989586621679997118 l0

data IntersperseSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997118] [a6989586621679997118] (IntersperseSym1 a6989586621679997118 l0) l1 # 
type Apply [a6989586621679997118] [a6989586621679997118] (IntersperseSym1 a6989586621679997118 l0) l1 = IntersperseSym2 a6989586621679997118 l0 l1

data IntercalateSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997117] (TyFun [[a6989586621679997117]] [a6989586621679997117] -> Type) (IntercalateSym0 a6989586621679997117) l0 # 
type Apply [a6989586621679997117] (TyFun [[a6989586621679997117]] [a6989586621679997117] -> Type) (IntercalateSym0 a6989586621679997117) l0 = IntercalateSym1 a6989586621679997117 l0

data IntercalateSym1 l l #

Instances

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

Methods

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

type Apply [[a6989586621679997117]] [a6989586621679997117] (IntercalateSym1 a6989586621679997117 l0) l1 # 
type Apply [[a6989586621679997117]] [a6989586621679997117] (IntercalateSym1 a6989586621679997117 l0) l1 = IntercalateSym2 a6989586621679997117 l0 l1

data TransposeSym0 l #

Instances

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

Methods

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

type Apply [[a6989586621679997005]] [[a6989586621679997005]] (TransposeSym0 a6989586621679997005) l0 # 
type Apply [[a6989586621679997005]] [[a6989586621679997005]] (TransposeSym0 a6989586621679997005) l0 = TransposeSym1 a6989586621679997005 l0

data SubsequencesSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997116] [[a6989586621679997116]] (SubsequencesSym0 a6989586621679997116) l0 # 
type Apply [a6989586621679997116] [[a6989586621679997116]] (SubsequencesSym0 a6989586621679997116) l0 = SubsequencesSym1 a6989586621679997116 l0

data PermutationsSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997113] [[a6989586621679997113]] (PermutationsSym0 a6989586621679997113) l0 # 
type Apply [a6989586621679997113] [[a6989586621679997113]] (PermutationsSym0 a6989586621679997113) l0 = PermutationsSym1 a6989586621679997113 l0

data FoldlSym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679650486 (TyFun a6989586621679650485 b6989586621679650486 -> Type) -> Type) (TyFun b6989586621679650486 (TyFun [a6989586621679650485] b6989586621679650486 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679650485 b6989586621679650486) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym0 a6989586621679650485 b6989586621679650486) t -> () #

type Apply (TyFun b6989586621679650486 (TyFun a6989586621679650485 b6989586621679650486 -> Type) -> Type) (TyFun b6989586621679650486 (TyFun [a6989586621679650485] b6989586621679650486 -> Type) -> Type) (FoldlSym0 a6989586621679650485 b6989586621679650486) l0 # 
type Apply (TyFun b6989586621679650486 (TyFun a6989586621679650485 b6989586621679650486 -> Type) -> Type) (TyFun b6989586621679650486 (TyFun [a6989586621679650485] b6989586621679650486 -> Type) -> Type) (FoldlSym0 a6989586621679650485 b6989586621679650486) l0 = FoldlSym1 a6989586621679650485 b6989586621679650486 l0

data FoldlSym1 l l #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679650486 (TyFun a6989586621679650485 b6989586621679650486 -> Type) -> Type) -> TyFun b6989586621679650486 (TyFun [a6989586621679650485] b6989586621679650486 -> Type) -> *) (FoldlSym1 a6989586621679650485 b6989586621679650486) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym1 a6989586621679650485 b6989586621679650486) t -> () #

type Apply b6989586621679650486 (TyFun [a6989586621679650485] b6989586621679650486 -> Type) (FoldlSym1 a6989586621679650485 b6989586621679650486 l0) l1 # 
type Apply b6989586621679650486 (TyFun [a6989586621679650485] b6989586621679650486 -> Type) (FoldlSym1 a6989586621679650485 b6989586621679650486 l0) l1 = FoldlSym2 a6989586621679650485 b6989586621679650486 l0 l1

data FoldlSym2 l l l #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679650486 (TyFun a6989586621679650485 b6989586621679650486 -> Type) -> Type) -> b6989586621679650486 -> TyFun [a6989586621679650485] b6989586621679650486 -> *) (FoldlSym2 a6989586621679650485 b6989586621679650486) # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym2 a6989586621679650485 b6989586621679650486) t -> () #

type Apply [a6989586621679650485] b6989586621679650486 (FoldlSym2 a6989586621679650485 b6989586621679650486 l1 l0) l2 # 
type Apply [a6989586621679650485] b6989586621679650486 (FoldlSym2 a6989586621679650485 b6989586621679650486 l1 l0) l2 = FoldlSym3 a6989586621679650485 b6989586621679650486 l1 l0 l2

type FoldlSym3 t t t = Foldl t t t #

data Foldl'Sym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679997112 (TyFun a6989586621679997111 b6989586621679997112 -> Type) -> Type) (TyFun b6989586621679997112 (TyFun [a6989586621679997111] b6989586621679997112 -> Type) -> Type) -> *) (Foldl'Sym0 a6989586621679997111 b6989586621679997112) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym0 a6989586621679997111 b6989586621679997112) t -> () #

type Apply (TyFun b6989586621679997112 (TyFun a6989586621679997111 b6989586621679997112 -> Type) -> Type) (TyFun b6989586621679997112 (TyFun [a6989586621679997111] b6989586621679997112 -> Type) -> Type) (Foldl'Sym0 a6989586621679997111 b6989586621679997112) l0 # 
type Apply (TyFun b6989586621679997112 (TyFun a6989586621679997111 b6989586621679997112 -> Type) -> Type) (TyFun b6989586621679997112 (TyFun [a6989586621679997111] b6989586621679997112 -> Type) -> Type) (Foldl'Sym0 a6989586621679997111 b6989586621679997112) l0 = Foldl'Sym1 a6989586621679997111 b6989586621679997112 l0

data Foldl'Sym1 l l #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679997112 (TyFun a6989586621679997111 b6989586621679997112 -> Type) -> Type) -> TyFun b6989586621679997112 (TyFun [a6989586621679997111] b6989586621679997112 -> Type) -> *) (Foldl'Sym1 a6989586621679997111 b6989586621679997112) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym1 a6989586621679997111 b6989586621679997112) t -> () #

type Apply b6989586621679997112 (TyFun [a6989586621679997111] b6989586621679997112 -> Type) (Foldl'Sym1 a6989586621679997111 b6989586621679997112 l0) l1 # 
type Apply b6989586621679997112 (TyFun [a6989586621679997111] b6989586621679997112 -> Type) (Foldl'Sym1 a6989586621679997111 b6989586621679997112 l0) l1 = Foldl'Sym2 a6989586621679997111 b6989586621679997112 l0 l1

data Foldl'Sym2 l l l #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679997112 (TyFun a6989586621679997111 b6989586621679997112 -> Type) -> Type) -> b6989586621679997112 -> TyFun [a6989586621679997111] b6989586621679997112 -> *) (Foldl'Sym2 a6989586621679997111 b6989586621679997112) # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym2 a6989586621679997111 b6989586621679997112) t -> () #

type Apply [a6989586621679997111] b6989586621679997112 (Foldl'Sym2 a6989586621679997111 b6989586621679997112 l1 l0) l2 # 
type Apply [a6989586621679997111] b6989586621679997112 (Foldl'Sym2 a6989586621679997111 b6989586621679997112 l1 l0) l2 = Foldl'Sym3 a6989586621679997111 b6989586621679997112 l1 l0 l2

type Foldl'Sym3 t t t = Foldl' t t t #

data Foldl1Sym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997110 (TyFun a6989586621679997110 a6989586621679997110 -> Type) -> Type) (TyFun [a6989586621679997110] a6989586621679997110 -> Type) (Foldl1Sym0 a6989586621679997110) l0 # 
type Apply (TyFun a6989586621679997110 (TyFun a6989586621679997110 a6989586621679997110 -> Type) -> Type) (TyFun [a6989586621679997110] a6989586621679997110 -> Type) (Foldl1Sym0 a6989586621679997110) l0 = Foldl1Sym1 a6989586621679997110 l0

data Foldl1Sym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997110] a6989586621679997110 (Foldl1Sym1 a6989586621679997110 l0) l1 # 
type Apply [a6989586621679997110] a6989586621679997110 (Foldl1Sym1 a6989586621679997110 l0) l1 = Foldl1Sym2 a6989586621679997110 l0 l1

type Foldl1Sym2 t t = Foldl1 t t #

data Foldl1'Sym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997109 (TyFun a6989586621679997109 a6989586621679997109 -> Type) -> Type) (TyFun [a6989586621679997109] a6989586621679997109 -> Type) (Foldl1'Sym0 a6989586621679997109) l0 # 
type Apply (TyFun a6989586621679997109 (TyFun a6989586621679997109 a6989586621679997109 -> Type) -> Type) (TyFun [a6989586621679997109] a6989586621679997109 -> Type) (Foldl1'Sym0 a6989586621679997109) l0 = Foldl1'Sym1 a6989586621679997109 l0

data Foldl1'Sym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997109] a6989586621679997109 (Foldl1'Sym1 a6989586621679997109 l0) l1 # 
type Apply [a6989586621679997109] a6989586621679997109 (Foldl1'Sym1 a6989586621679997109 l0) l1 = Foldl1'Sym2 a6989586621679997109 l0 l1

type Foldl1'Sym2 t t = Foldl1' t t #

data FoldrSym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679703401 (TyFun b6989586621679703402 b6989586621679703402 -> Type) -> Type) (TyFun b6989586621679703402 (TyFun [a6989586621679703401] b6989586621679703402 -> Type) -> Type) -> *) (FoldrSym0 a6989586621679703401 b6989586621679703402) # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym0 a6989586621679703401 b6989586621679703402) t -> () #

type Apply (TyFun a6989586621679703401 (TyFun b6989586621679703402 b6989586621679703402 -> Type) -> Type) (TyFun b6989586621679703402 (TyFun [a6989586621679703401] b6989586621679703402 -> Type) -> Type) (FoldrSym0 a6989586621679703401 b6989586621679703402) l0 # 
type Apply (TyFun a6989586621679703401 (TyFun b6989586621679703402 b6989586621679703402 -> Type) -> Type) (TyFun b6989586621679703402 (TyFun [a6989586621679703401] b6989586621679703402 -> Type) -> Type) (FoldrSym0 a6989586621679703401 b6989586621679703402) l0 = FoldrSym1 a6989586621679703401 b6989586621679703402 l0

data FoldrSym1 l l #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679703401 (TyFun b6989586621679703402 b6989586621679703402 -> Type) -> Type) -> TyFun b6989586621679703402 (TyFun [a6989586621679703401] b6989586621679703402 -> Type) -> *) (FoldrSym1 a6989586621679703401 b6989586621679703402) # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym1 a6989586621679703401 b6989586621679703402) t -> () #

type Apply b6989586621679703402 (TyFun [a6989586621679703401] b6989586621679703402 -> Type) (FoldrSym1 a6989586621679703401 b6989586621679703402 l0) l1 # 
type Apply b6989586621679703402 (TyFun [a6989586621679703401] b6989586621679703402 -> Type) (FoldrSym1 a6989586621679703401 b6989586621679703402 l0) l1 = FoldrSym2 a6989586621679703401 b6989586621679703402 l0 l1

data FoldrSym2 l l l #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679703401 (TyFun b6989586621679703402 b6989586621679703402 -> Type) -> Type) -> b6989586621679703402 -> TyFun [a6989586621679703401] b6989586621679703402 -> *) (FoldrSym2 a6989586621679703401 b6989586621679703402) # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym2 a6989586621679703401 b6989586621679703402) t -> () #

type Apply [a6989586621679703401] b6989586621679703402 (FoldrSym2 a6989586621679703401 b6989586621679703402 l1 l0) l2 # 
type Apply [a6989586621679703401] b6989586621679703402 (FoldrSym2 a6989586621679703401 b6989586621679703402 l1 l0) l2 = FoldrSym3 a6989586621679703401 b6989586621679703402 l1 l0 l2

type FoldrSym3 t t t = Foldr t t t #

data Foldr1Sym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997108 (TyFun a6989586621679997108 a6989586621679997108 -> Type) -> Type) (TyFun [a6989586621679997108] a6989586621679997108 -> Type) (Foldr1Sym0 a6989586621679997108) l0 # 
type Apply (TyFun a6989586621679997108 (TyFun a6989586621679997108 a6989586621679997108 -> Type) -> Type) (TyFun [a6989586621679997108] a6989586621679997108 -> Type) (Foldr1Sym0 a6989586621679997108) l0 = Foldr1Sym1 a6989586621679997108 l0

data Foldr1Sym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997108] a6989586621679997108 (Foldr1Sym1 a6989586621679997108 l0) l1 # 
type Apply [a6989586621679997108] a6989586621679997108 (Foldr1Sym1 a6989586621679997108 l0) l1 = Foldr1Sym2 a6989586621679997108 l0 l1

type Foldr1Sym2 t t = Foldr1 t t #

data ConcatSym0 l #

Instances

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

Methods

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

type Apply [[a6989586621679997107]] [a6989586621679997107] (ConcatSym0 a6989586621679997107) l0 # 
type Apply [[a6989586621679997107]] [a6989586621679997107] (ConcatSym0 a6989586621679997107) l0 = ConcatSym1 a6989586621679997107 l0

type ConcatSym1 t = Concat t #

data ConcatMapSym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679997105 [b6989586621679997106] -> Type) (TyFun [a6989586621679997105] [b6989586621679997106] -> Type) -> *) (ConcatMapSym0 a6989586621679997105 b6989586621679997106) # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym0 a6989586621679997105 b6989586621679997106) t -> () #

type Apply (TyFun a6989586621679997105 [b6989586621679997106] -> Type) (TyFun [a6989586621679997105] [b6989586621679997106] -> Type) (ConcatMapSym0 a6989586621679997105 b6989586621679997106) l0 # 
type Apply (TyFun a6989586621679997105 [b6989586621679997106] -> Type) (TyFun [a6989586621679997105] [b6989586621679997106] -> Type) (ConcatMapSym0 a6989586621679997105 b6989586621679997106) l0 = ConcatMapSym1 a6989586621679997105 b6989586621679997106 l0

data ConcatMapSym1 l l #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679997105 [b6989586621679997106] -> Type) -> TyFun [a6989586621679997105] [b6989586621679997106] -> *) (ConcatMapSym1 a6989586621679997105 b6989586621679997106) # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym1 a6989586621679997105 b6989586621679997106) t -> () #

type Apply [a6989586621679997105] [b6989586621679997106] (ConcatMapSym1 a6989586621679997105 b6989586621679997106 l0) l1 # 
type Apply [a6989586621679997105] [b6989586621679997106] (ConcatMapSym1 a6989586621679997105 b6989586621679997106 l0) l1 = ConcatMapSym2 a6989586621679997105 b6989586621679997106 l0 l1

type ConcatMapSym2 t t = ConcatMap t t #

data AndSym0 l #

type AndSym1 t = And t #

data OrSym0 l #

Instances

type OrSym1 t = Or t #

data Any_Sym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679986420 Bool -> Type) (TyFun [a6989586621679986420] Bool -> Type) (Any_Sym0 a6989586621679986420) l0 # 
type Apply (TyFun a6989586621679986420 Bool -> Type) (TyFun [a6989586621679986420] Bool -> Type) (Any_Sym0 a6989586621679986420) l0 = Any_Sym1 a6989586621679986420 l0

data Any_Sym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679986420] Bool (Any_Sym1 a6989586621679986420 l0) l1 # 
type Apply [a6989586621679986420] Bool (Any_Sym1 a6989586621679986420 l0) l1 = Any_Sym2 a6989586621679986420 l0 l1

type Any_Sym2 t t = Any_ t t #

data AllSym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997104 Bool -> Type) (TyFun [a6989586621679997104] Bool -> Type) (AllSym0 a6989586621679997104) l0 # 
type Apply (TyFun a6989586621679997104 Bool -> Type) (TyFun [a6989586621679997104] Bool -> Type) (AllSym0 a6989586621679997104) l0 = AllSym1 a6989586621679997104 l0

data AllSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997104] Bool (AllSym1 a6989586621679997104 l0) l1 # 
type Apply [a6989586621679997104] Bool (AllSym1 a6989586621679997104 l0) l1 = AllSym2 a6989586621679997104 l0 l1

type AllSym2 t t = All t t #

data SumSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997009] a6989586621679997009 (SumSym0 a6989586621679997009) l0 # 
type Apply [a6989586621679997009] a6989586621679997009 (SumSym0 a6989586621679997009) l0 = SumSym1 a6989586621679997009 l0

type SumSym1 t = Sum t #

data ProductSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997008] a6989586621679997008 (ProductSym0 a6989586621679997008) l0 # 
type Apply [a6989586621679997008] a6989586621679997008 (ProductSym0 a6989586621679997008) l0 = ProductSym1 a6989586621679997008 l0

type ProductSym1 t = Product t #

data MaximumSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997018] a6989586621679997018 (MaximumSym0 a6989586621679997018) l0 # 
type Apply [a6989586621679997018] a6989586621679997018 (MaximumSym0 a6989586621679997018) l0 = MaximumSym1 a6989586621679997018 l0

type MaximumSym1 t = Maximum t #

data MinimumSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997017] a6989586621679997017 (MinimumSym0 a6989586621679997017) l0 # 
type Apply [a6989586621679997017] a6989586621679997017 (MinimumSym0 a6989586621679997017) l0 = MinimumSym1 a6989586621679997017 l0

type MinimumSym1 t = Minimum t #

data ScanlSym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679997102 (TyFun a6989586621679997103 b6989586621679997102 -> Type) -> Type) (TyFun b6989586621679997102 (TyFun [a6989586621679997103] [b6989586621679997102] -> Type) -> Type) -> *) (ScanlSym0 a6989586621679997103 b6989586621679997102) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a6989586621679997103 b6989586621679997102) t -> () #

type Apply (TyFun b6989586621679997102 (TyFun a6989586621679997103 b6989586621679997102 -> Type) -> Type) (TyFun b6989586621679997102 (TyFun [a6989586621679997103] [b6989586621679997102] -> Type) -> Type) (ScanlSym0 a6989586621679997103 b6989586621679997102) l0 # 
type Apply (TyFun b6989586621679997102 (TyFun a6989586621679997103 b6989586621679997102 -> Type) -> Type) (TyFun b6989586621679997102 (TyFun [a6989586621679997103] [b6989586621679997102] -> Type) -> Type) (ScanlSym0 a6989586621679997103 b6989586621679997102) l0 = ScanlSym1 a6989586621679997103 b6989586621679997102 l0

data ScanlSym1 l l #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679997102 (TyFun a6989586621679997103 b6989586621679997102 -> Type) -> Type) -> TyFun b6989586621679997102 (TyFun [a6989586621679997103] [b6989586621679997102] -> Type) -> *) (ScanlSym1 a6989586621679997103 b6989586621679997102) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a6989586621679997103 b6989586621679997102) t -> () #

type Apply b6989586621679997102 (TyFun [a6989586621679997103] [b6989586621679997102] -> Type) (ScanlSym1 a6989586621679997103 b6989586621679997102 l0) l1 # 
type Apply b6989586621679997102 (TyFun [a6989586621679997103] [b6989586621679997102] -> Type) (ScanlSym1 a6989586621679997103 b6989586621679997102 l0) l1 = ScanlSym2 a6989586621679997103 b6989586621679997102 l0 l1

data ScanlSym2 l l l #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679997102 (TyFun a6989586621679997103 b6989586621679997102 -> Type) -> Type) -> b6989586621679997102 -> TyFun [a6989586621679997103] [b6989586621679997102] -> *) (ScanlSym2 a6989586621679997103 b6989586621679997102) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a6989586621679997103 b6989586621679997102) t -> () #

type Apply [a6989586621679997103] [b6989586621679997102] (ScanlSym2 a6989586621679997103 b6989586621679997102 l1 l0) l2 # 
type Apply [a6989586621679997103] [b6989586621679997102] (ScanlSym2 a6989586621679997103 b6989586621679997102 l1 l0) l2 = ScanlSym3 a6989586621679997103 b6989586621679997102 l1 l0 l2

type ScanlSym3 t t t = Scanl t t t #

data Scanl1Sym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997101 (TyFun a6989586621679997101 a6989586621679997101 -> Type) -> Type) (TyFun [a6989586621679997101] [a6989586621679997101] -> Type) (Scanl1Sym0 a6989586621679997101) l0 # 
type Apply (TyFun a6989586621679997101 (TyFun a6989586621679997101 a6989586621679997101 -> Type) -> Type) (TyFun [a6989586621679997101] [a6989586621679997101] -> Type) (Scanl1Sym0 a6989586621679997101) l0 = Scanl1Sym1 a6989586621679997101 l0

data Scanl1Sym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997101] [a6989586621679997101] (Scanl1Sym1 a6989586621679997101 l0) l1 # 
type Apply [a6989586621679997101] [a6989586621679997101] (Scanl1Sym1 a6989586621679997101 l0) l1 = Scanl1Sym2 a6989586621679997101 l0 l1

type Scanl1Sym2 t t = Scanl1 t t #

data ScanrSym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679997099 (TyFun b6989586621679997100 b6989586621679997100 -> Type) -> Type) (TyFun b6989586621679997100 (TyFun [a6989586621679997099] [b6989586621679997100] -> Type) -> Type) -> *) (ScanrSym0 a6989586621679997099 b6989586621679997100) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a6989586621679997099 b6989586621679997100) t -> () #

type Apply (TyFun a6989586621679997099 (TyFun b6989586621679997100 b6989586621679997100 -> Type) -> Type) (TyFun b6989586621679997100 (TyFun [a6989586621679997099] [b6989586621679997100] -> Type) -> Type) (ScanrSym0 a6989586621679997099 b6989586621679997100) l0 # 
type Apply (TyFun a6989586621679997099 (TyFun b6989586621679997100 b6989586621679997100 -> Type) -> Type) (TyFun b6989586621679997100 (TyFun [a6989586621679997099] [b6989586621679997100] -> Type) -> Type) (ScanrSym0 a6989586621679997099 b6989586621679997100) l0 = ScanrSym1 a6989586621679997099 b6989586621679997100 l0

data ScanrSym1 l l #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679997099 (TyFun b6989586621679997100 b6989586621679997100 -> Type) -> Type) -> TyFun b6989586621679997100 (TyFun [a6989586621679997099] [b6989586621679997100] -> Type) -> *) (ScanrSym1 a6989586621679997099 b6989586621679997100) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a6989586621679997099 b6989586621679997100) t -> () #

type Apply b6989586621679997100 (TyFun [a6989586621679997099] [b6989586621679997100] -> Type) (ScanrSym1 a6989586621679997099 b6989586621679997100 l0) l1 # 
type Apply b6989586621679997100 (TyFun [a6989586621679997099] [b6989586621679997100] -> Type) (ScanrSym1 a6989586621679997099 b6989586621679997100 l0) l1 = ScanrSym2 a6989586621679997099 b6989586621679997100 l0 l1

data ScanrSym2 l l l #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679997099 (TyFun b6989586621679997100 b6989586621679997100 -> Type) -> Type) -> b6989586621679997100 -> TyFun [a6989586621679997099] [b6989586621679997100] -> *) (ScanrSym2 a6989586621679997099 b6989586621679997100) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a6989586621679997099 b6989586621679997100) t -> () #

type Apply [a6989586621679997099] [b6989586621679997100] (ScanrSym2 a6989586621679997099 b6989586621679997100 l1 l0) l2 # 
type Apply [a6989586621679997099] [b6989586621679997100] (ScanrSym2 a6989586621679997099 b6989586621679997100 l1 l0) l2 = ScanrSym3 a6989586621679997099 b6989586621679997100 l1 l0 l2

type ScanrSym3 t t t = Scanr t t t #

data Scanr1Sym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997098 (TyFun a6989586621679997098 a6989586621679997098 -> Type) -> Type) (TyFun [a6989586621679997098] [a6989586621679997098] -> Type) (Scanr1Sym0 a6989586621679997098) l0 # 
type Apply (TyFun a6989586621679997098 (TyFun a6989586621679997098 a6989586621679997098 -> Type) -> Type) (TyFun [a6989586621679997098] [a6989586621679997098] -> Type) (Scanr1Sym0 a6989586621679997098) l0 = Scanr1Sym1 a6989586621679997098 l0

data Scanr1Sym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997098] [a6989586621679997098] (Scanr1Sym1 a6989586621679997098 l0) l1 # 
type Apply [a6989586621679997098] [a6989586621679997098] (Scanr1Sym1 a6989586621679997098 l0) l1 = Scanr1Sym2 a6989586621679997098 l0 l1

type Scanr1Sym2 t t = Scanr1 t t #

data MapAccumLSym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679997095 (TyFun x6989586621679997096 (acc6989586621679997095, y6989586621679997097) -> Type) -> Type) (TyFun acc6989586621679997095 (TyFun [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) -> Type) -> Type) -> *) (MapAccumLSym0 x6989586621679997096 acc6989586621679997095 y6989586621679997097) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym0 x6989586621679997096 acc6989586621679997095 y6989586621679997097) t -> () #

type Apply (TyFun acc6989586621679997095 (TyFun x6989586621679997096 (acc6989586621679997095, y6989586621679997097) -> Type) -> Type) (TyFun acc6989586621679997095 (TyFun [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) -> Type) -> Type) (MapAccumLSym0 x6989586621679997096 acc6989586621679997095 y6989586621679997097) l0 # 
type Apply (TyFun acc6989586621679997095 (TyFun x6989586621679997096 (acc6989586621679997095, y6989586621679997097) -> Type) -> Type) (TyFun acc6989586621679997095 (TyFun [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) -> Type) -> Type) (MapAccumLSym0 x6989586621679997096 acc6989586621679997095 y6989586621679997097) l0 = MapAccumLSym1 x6989586621679997096 acc6989586621679997095 y6989586621679997097 l0

data MapAccumLSym1 l l #

Instances

SuppressUnusedWarnings ((TyFun acc6989586621679997095 (TyFun x6989586621679997096 (acc6989586621679997095, y6989586621679997097) -> Type) -> Type) -> TyFun acc6989586621679997095 (TyFun [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) -> Type) -> *) (MapAccumLSym1 x6989586621679997096 acc6989586621679997095 y6989586621679997097) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym1 x6989586621679997096 acc6989586621679997095 y6989586621679997097) t -> () #

type Apply acc6989586621679997095 (TyFun [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) -> Type) (MapAccumLSym1 x6989586621679997096 acc6989586621679997095 y6989586621679997097 l0) l1 # 
type Apply acc6989586621679997095 (TyFun [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) -> Type) (MapAccumLSym1 x6989586621679997096 acc6989586621679997095 y6989586621679997097 l0) l1 = MapAccumLSym2 x6989586621679997096 acc6989586621679997095 y6989586621679997097 l0 l1

data MapAccumLSym2 l l l #

Instances

SuppressUnusedWarnings ((TyFun acc6989586621679997095 (TyFun x6989586621679997096 (acc6989586621679997095, y6989586621679997097) -> Type) -> Type) -> acc6989586621679997095 -> TyFun [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) -> *) (MapAccumLSym2 x6989586621679997096 acc6989586621679997095 y6989586621679997097) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym2 x6989586621679997096 acc6989586621679997095 y6989586621679997097) t -> () #

type Apply [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) (MapAccumLSym2 x6989586621679997096 acc6989586621679997095 y6989586621679997097 l1 l0) l2 # 
type Apply [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) (MapAccumLSym2 x6989586621679997096 acc6989586621679997095 y6989586621679997097 l1 l0) l2 = MapAccumLSym3 x6989586621679997096 acc6989586621679997095 y6989586621679997097 l1 l0 l2

type MapAccumLSym3 t t t = MapAccumL t t t #

data MapAccumRSym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679997092 (TyFun x6989586621679997093 (acc6989586621679997092, y6989586621679997094) -> Type) -> Type) (TyFun acc6989586621679997092 (TyFun [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) -> Type) -> Type) -> *) (MapAccumRSym0 x6989586621679997093 acc6989586621679997092 y6989586621679997094) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym0 x6989586621679997093 acc6989586621679997092 y6989586621679997094) t -> () #

type Apply (TyFun acc6989586621679997092 (TyFun x6989586621679997093 (acc6989586621679997092, y6989586621679997094) -> Type) -> Type) (TyFun acc6989586621679997092 (TyFun [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) -> Type) -> Type) (MapAccumRSym0 x6989586621679997093 acc6989586621679997092 y6989586621679997094) l0 # 
type Apply (TyFun acc6989586621679997092 (TyFun x6989586621679997093 (acc6989586621679997092, y6989586621679997094) -> Type) -> Type) (TyFun acc6989586621679997092 (TyFun [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) -> Type) -> Type) (MapAccumRSym0 x6989586621679997093 acc6989586621679997092 y6989586621679997094) l0 = MapAccumRSym1 x6989586621679997093 acc6989586621679997092 y6989586621679997094 l0

data MapAccumRSym1 l l #

Instances

SuppressUnusedWarnings ((TyFun acc6989586621679997092 (TyFun x6989586621679997093 (acc6989586621679997092, y6989586621679997094) -> Type) -> Type) -> TyFun acc6989586621679997092 (TyFun [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) -> Type) -> *) (MapAccumRSym1 x6989586621679997093 acc6989586621679997092 y6989586621679997094) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym1 x6989586621679997093 acc6989586621679997092 y6989586621679997094) t -> () #

type Apply acc6989586621679997092 (TyFun [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) -> Type) (MapAccumRSym1 x6989586621679997093 acc6989586621679997092 y6989586621679997094 l0) l1 # 
type Apply acc6989586621679997092 (TyFun [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) -> Type) (MapAccumRSym1 x6989586621679997093 acc6989586621679997092 y6989586621679997094 l0) l1 = MapAccumRSym2 x6989586621679997093 acc6989586621679997092 y6989586621679997094 l0 l1

data MapAccumRSym2 l l l #

Instances

SuppressUnusedWarnings ((TyFun acc6989586621679997092 (TyFun x6989586621679997093 (acc6989586621679997092, y6989586621679997094) -> Type) -> Type) -> acc6989586621679997092 -> TyFun [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) -> *) (MapAccumRSym2 x6989586621679997093 acc6989586621679997092 y6989586621679997094) # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym2 x6989586621679997093 acc6989586621679997092 y6989586621679997094) t -> () #

type Apply [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) (MapAccumRSym2 x6989586621679997093 acc6989586621679997092 y6989586621679997094 l1 l0) l2 # 
type Apply [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) (MapAccumRSym2 x6989586621679997093 acc6989586621679997092 y6989586621679997094 l1 l0) l2 = MapAccumRSym3 x6989586621679997093 acc6989586621679997092 y6989586621679997094 l1 l0 l2

type MapAccumRSym3 t t t = MapAccumR t t t #

data ReplicateSym0 l #

Instances

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

Methods

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

type Apply Nat (TyFun a6989586621679997006 [a6989586621679997006] -> Type) (ReplicateSym0 a6989586621679997006) l0 # 
type Apply Nat (TyFun a6989586621679997006 [a6989586621679997006] -> Type) (ReplicateSym0 a6989586621679997006) l0 = ReplicateSym1 a6989586621679997006 l0

data ReplicateSym1 l l #

Instances

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

Methods

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

type Apply a6989586621679997006 [a6989586621679997006] (ReplicateSym1 a6989586621679997006 l0) l1 # 
type Apply a6989586621679997006 [a6989586621679997006] (ReplicateSym1 a6989586621679997006 l0) l1 = ReplicateSym2 a6989586621679997006 l0 l1

type ReplicateSym2 t t = Replicate t t #

data UnfoldrSym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679997090 (Maybe (a6989586621679997091, b6989586621679997090)) -> Type) (TyFun b6989586621679997090 [a6989586621679997091] -> Type) -> *) (UnfoldrSym0 b6989586621679997090 a6989586621679997091) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 b6989586621679997090 a6989586621679997091) t -> () #

type Apply (TyFun b6989586621679997090 (Maybe (a6989586621679997091, b6989586621679997090)) -> Type) (TyFun b6989586621679997090 [a6989586621679997091] -> Type) (UnfoldrSym0 b6989586621679997090 a6989586621679997091) l0 # 
type Apply (TyFun b6989586621679997090 (Maybe (a6989586621679997091, b6989586621679997090)) -> Type) (TyFun b6989586621679997090 [a6989586621679997091] -> Type) (UnfoldrSym0 b6989586621679997090 a6989586621679997091) l0 = UnfoldrSym1 a6989586621679997091 b6989586621679997090 l0

data UnfoldrSym1 l l #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679997090 (Maybe (a6989586621679997091, b6989586621679997090)) -> Type) -> TyFun b6989586621679997090 [a6989586621679997091] -> *) (UnfoldrSym1 a6989586621679997091 b6989586621679997090) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 a6989586621679997091 b6989586621679997090) t -> () #

type Apply b6989586621679997090 [a6989586621679997091] (UnfoldrSym1 a6989586621679997091 b6989586621679997090 l0) l1 # 
type Apply b6989586621679997090 [a6989586621679997091] (UnfoldrSym1 a6989586621679997091 b6989586621679997090 l0) l1 = UnfoldrSym2 a6989586621679997091 b6989586621679997090 l0 l1

type UnfoldrSym2 t t = Unfoldr t t #

data TakeSym0 l #

Instances

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

Methods

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

type Apply Nat (TyFun [a6989586621679997022] [a6989586621679997022] -> Type) (TakeSym0 a6989586621679997022) l0 # 
type Apply Nat (TyFun [a6989586621679997022] [a6989586621679997022] -> Type) (TakeSym0 a6989586621679997022) l0 = TakeSym1 a6989586621679997022 l0

data TakeSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997022] [a6989586621679997022] (TakeSym1 a6989586621679997022 l0) l1 # 
type Apply [a6989586621679997022] [a6989586621679997022] (TakeSym1 a6989586621679997022 l0) l1 = TakeSym2 a6989586621679997022 l0 l1

type TakeSym2 t t = Take t t #

data DropSym0 l #

Instances

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

Methods

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

type Apply Nat (TyFun [a6989586621679997021] [a6989586621679997021] -> Type) (DropSym0 a6989586621679997021) l0 # 
type Apply Nat (TyFun [a6989586621679997021] [a6989586621679997021] -> Type) (DropSym0 a6989586621679997021) l0 = DropSym1 a6989586621679997021 l0

data DropSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997021] [a6989586621679997021] (DropSym1 a6989586621679997021 l0) l1 # 
type Apply [a6989586621679997021] [a6989586621679997021] (DropSym1 a6989586621679997021 l0) l1 = DropSym2 a6989586621679997021 l0 l1

type DropSym2 t t = Drop t t #

data SplitAtSym0 l #

Instances

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

Methods

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

type Apply Nat (TyFun [a6989586621679997020] ([a6989586621679997020], [a6989586621679997020]) -> Type) (SplitAtSym0 a6989586621679997020) l0 # 
type Apply Nat (TyFun [a6989586621679997020] ([a6989586621679997020], [a6989586621679997020]) -> Type) (SplitAtSym0 a6989586621679997020) l0 = SplitAtSym1 a6989586621679997020 l0

data SplitAtSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997020] ([a6989586621679997020], [a6989586621679997020]) (SplitAtSym1 a6989586621679997020 l0) l1 # 
type Apply [a6989586621679997020] ([a6989586621679997020], [a6989586621679997020]) (SplitAtSym1 a6989586621679997020 l0) l1 = SplitAtSym2 a6989586621679997020 l0 l1

type SplitAtSym2 t t = SplitAt t t #

data TakeWhileSym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997027 Bool -> Type) (TyFun [a6989586621679997027] [a6989586621679997027] -> Type) (TakeWhileSym0 a6989586621679997027) l0 # 
type Apply (TyFun a6989586621679997027 Bool -> Type) (TyFun [a6989586621679997027] [a6989586621679997027] -> Type) (TakeWhileSym0 a6989586621679997027) l0 = TakeWhileSym1 a6989586621679997027 l0

data TakeWhileSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997027] [a6989586621679997027] (TakeWhileSym1 a6989586621679997027 l0) l1 # 
type Apply [a6989586621679997027] [a6989586621679997027] (TakeWhileSym1 a6989586621679997027 l0) l1 = TakeWhileSym2 a6989586621679997027 l0 l1

type TakeWhileSym2 t t = TakeWhile t t #

data DropWhileSym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997026 Bool -> Type) (TyFun [a6989586621679997026] [a6989586621679997026] -> Type) (DropWhileSym0 a6989586621679997026) l0 # 
type Apply (TyFun a6989586621679997026 Bool -> Type) (TyFun [a6989586621679997026] [a6989586621679997026] -> Type) (DropWhileSym0 a6989586621679997026) l0 = DropWhileSym1 a6989586621679997026 l0

data DropWhileSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997026] [a6989586621679997026] (DropWhileSym1 a6989586621679997026 l0) l1 # 
type Apply [a6989586621679997026] [a6989586621679997026] (DropWhileSym1 a6989586621679997026 l0) l1 = DropWhileSym2 a6989586621679997026 l0 l1

type DropWhileSym2 t t = DropWhile t t #

data DropWhileEndSym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997025 Bool -> Type) (TyFun [a6989586621679997025] [a6989586621679997025] -> Type) (DropWhileEndSym0 a6989586621679997025) l0 # 
type Apply (TyFun a6989586621679997025 Bool -> Type) (TyFun [a6989586621679997025] [a6989586621679997025] -> Type) (DropWhileEndSym0 a6989586621679997025) l0 = DropWhileEndSym1 a6989586621679997025 l0

data DropWhileEndSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997025] [a6989586621679997025] (DropWhileEndSym1 a6989586621679997025 l0) l1 # 
type Apply [a6989586621679997025] [a6989586621679997025] (DropWhileEndSym1 a6989586621679997025 l0) l1 = DropWhileEndSym2 a6989586621679997025 l0 l1

data SpanSym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997024 Bool -> Type) (TyFun [a6989586621679997024] ([a6989586621679997024], [a6989586621679997024]) -> Type) (SpanSym0 a6989586621679997024) l0 # 
type Apply (TyFun a6989586621679997024 Bool -> Type) (TyFun [a6989586621679997024] ([a6989586621679997024], [a6989586621679997024]) -> Type) (SpanSym0 a6989586621679997024) l0 = SpanSym1 a6989586621679997024 l0

data SpanSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997024] ([a6989586621679997024], [a6989586621679997024]) (SpanSym1 a6989586621679997024 l0) l1 # 
type Apply [a6989586621679997024] ([a6989586621679997024], [a6989586621679997024]) (SpanSym1 a6989586621679997024 l0) l1 = SpanSym2 a6989586621679997024 l0 l1

type SpanSym2 t t = Span t t #

data BreakSym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997023 Bool -> Type) (TyFun [a6989586621679997023] ([a6989586621679997023], [a6989586621679997023]) -> Type) (BreakSym0 a6989586621679997023) l0 # 
type Apply (TyFun a6989586621679997023 Bool -> Type) (TyFun [a6989586621679997023] ([a6989586621679997023], [a6989586621679997023]) -> Type) (BreakSym0 a6989586621679997023) l0 = BreakSym1 a6989586621679997023 l0

data BreakSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997023] ([a6989586621679997023], [a6989586621679997023]) (BreakSym1 a6989586621679997023 l0) l1 # 
type Apply [a6989586621679997023] ([a6989586621679997023], [a6989586621679997023]) (BreakSym1 a6989586621679997023 l0) l1 = BreakSym2 a6989586621679997023 l0 l1

type BreakSym2 t t = Break t t #

data GroupSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997019] [[a6989586621679997019]] (GroupSym0 a6989586621679997019) l0 # 
type Apply [a6989586621679997019] [[a6989586621679997019]] (GroupSym0 a6989586621679997019) l0 = GroupSym1 a6989586621679997019 l0

type GroupSym1 t = Group t #

data InitsSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997089] [[a6989586621679997089]] (InitsSym0 a6989586621679997089) l0 # 
type Apply [a6989586621679997089] [[a6989586621679997089]] (InitsSym0 a6989586621679997089) l0 = InitsSym1 a6989586621679997089 l0

type InitsSym1 t = Inits t #

data TailsSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997088] [[a6989586621679997088]] (TailsSym0 a6989586621679997088) l0 # 
type Apply [a6989586621679997088] [[a6989586621679997088]] (TailsSym0 a6989586621679997088) l0 = TailsSym1 a6989586621679997088 l0

type TailsSym1 t = Tails t #

data IsPrefixOfSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997087] (TyFun [a6989586621679997087] Bool -> Type) (IsPrefixOfSym0 a6989586621679997087) l0 # 
type Apply [a6989586621679997087] (TyFun [a6989586621679997087] Bool -> Type) (IsPrefixOfSym0 a6989586621679997087) l0 = IsPrefixOfSym1 a6989586621679997087 l0

data IsPrefixOfSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997087] Bool (IsPrefixOfSym1 a6989586621679997087 l0) l1 # 
type Apply [a6989586621679997087] Bool (IsPrefixOfSym1 a6989586621679997087 l0) l1 = IsPrefixOfSym2 a6989586621679997087 l0 l1

type IsPrefixOfSym2 t t = IsPrefixOf t t #

data IsSuffixOfSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997086] (TyFun [a6989586621679997086] Bool -> Type) (IsSuffixOfSym0 a6989586621679997086) l0 # 
type Apply [a6989586621679997086] (TyFun [a6989586621679997086] Bool -> Type) (IsSuffixOfSym0 a6989586621679997086) l0 = IsSuffixOfSym1 a6989586621679997086 l0

data IsSuffixOfSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997086] Bool (IsSuffixOfSym1 a6989586621679997086 l0) l1 # 
type Apply [a6989586621679997086] Bool (IsSuffixOfSym1 a6989586621679997086 l0) l1 = IsSuffixOfSym2 a6989586621679997086 l0 l1

type IsSuffixOfSym2 t t = IsSuffixOf t t #

data IsInfixOfSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997085] (TyFun [a6989586621679997085] Bool -> Type) (IsInfixOfSym0 a6989586621679997085) l0 # 
type Apply [a6989586621679997085] (TyFun [a6989586621679997085] Bool -> Type) (IsInfixOfSym0 a6989586621679997085) l0 = IsInfixOfSym1 a6989586621679997085 l0

data IsInfixOfSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997085] Bool (IsInfixOfSym1 a6989586621679997085 l0) l1 # 
type Apply [a6989586621679997085] Bool (IsInfixOfSym1 a6989586621679997085 l0) l1 = IsInfixOfSym2 a6989586621679997085 l0 l1

type IsInfixOfSym2 t t = IsInfixOf t t #

data ElemSym0 l #

Instances

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

Methods

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

type Apply a6989586621679997084 (TyFun [a6989586621679997084] Bool -> Type) (ElemSym0 a6989586621679997084) l0 # 
type Apply a6989586621679997084 (TyFun [a6989586621679997084] Bool -> Type) (ElemSym0 a6989586621679997084) l0 = ElemSym1 a6989586621679997084 l0

data ElemSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997084] Bool (ElemSym1 a6989586621679997084 l0) l1 # 
type Apply [a6989586621679997084] Bool (ElemSym1 a6989586621679997084 l0) l1 = ElemSym2 a6989586621679997084 l0 l1

type ElemSym2 t t = Elem t t #

data NotElemSym0 l #

Instances

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

Methods

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

type Apply a6989586621679997083 (TyFun [a6989586621679997083] Bool -> Type) (NotElemSym0 a6989586621679997083) l0 # 
type Apply a6989586621679997083 (TyFun [a6989586621679997083] Bool -> Type) (NotElemSym0 a6989586621679997083) l0 = NotElemSym1 a6989586621679997083 l0

data NotElemSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997083] Bool (NotElemSym1 a6989586621679997083 l0) l1 # 
type Apply [a6989586621679997083] Bool (NotElemSym1 a6989586621679997083 l0) l1 = NotElemSym2 a6989586621679997083 l0 l1

type NotElemSym2 t t = NotElem t t #

data LookupSym0 l #

Instances

SuppressUnusedWarnings (TyFun a6989586621679997012 (TyFun [(a6989586621679997012, b6989586621679997013)] (Maybe b6989586621679997013) -> Type) -> *) (LookupSym0 a6989586621679997012 b6989586621679997013) # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym0 a6989586621679997012 b6989586621679997013) t -> () #

type Apply a6989586621679997012 (TyFun [(a6989586621679997012, b6989586621679997013)] (Maybe b6989586621679997013) -> Type) (LookupSym0 a6989586621679997012 b6989586621679997013) l0 # 
type Apply a6989586621679997012 (TyFun [(a6989586621679997012, b6989586621679997013)] (Maybe b6989586621679997013) -> Type) (LookupSym0 a6989586621679997012 b6989586621679997013) l0 = LookupSym1 b6989586621679997013 a6989586621679997012 l0

data LookupSym1 l l #

Instances

SuppressUnusedWarnings (a6989586621679997012 -> TyFun [(a6989586621679997012, b6989586621679997013)] (Maybe b6989586621679997013) -> *) (LookupSym1 b6989586621679997013 a6989586621679997012) # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym1 b6989586621679997013 a6989586621679997012) t -> () #

type Apply [(a6989586621679997012, b6989586621679997013)] (Maybe b6989586621679997013) (LookupSym1 b6989586621679997013 a6989586621679997012 l0) l1 # 
type Apply [(a6989586621679997012, b6989586621679997013)] (Maybe b6989586621679997013) (LookupSym1 b6989586621679997013 a6989586621679997012 l0) l1 = LookupSym2 b6989586621679997013 a6989586621679997012 l0 l1

type LookupSym2 t t = Lookup t t #

data FindSym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997034 Bool -> Type) (TyFun [a6989586621679997034] (Maybe a6989586621679997034) -> Type) (FindSym0 a6989586621679997034) l0 # 
type Apply (TyFun a6989586621679997034 Bool -> Type) (TyFun [a6989586621679997034] (Maybe a6989586621679997034) -> Type) (FindSym0 a6989586621679997034) l0 = FindSym1 a6989586621679997034 l0

data FindSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997034] (Maybe a6989586621679997034) (FindSym1 a6989586621679997034 l0) l1 # 
type Apply [a6989586621679997034] (Maybe a6989586621679997034) (FindSym1 a6989586621679997034 l0) l1 = FindSym2 a6989586621679997034 l0 l1

type FindSym2 t t = Find t t #

data FilterSym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997035 Bool -> Type) (TyFun [a6989586621679997035] [a6989586621679997035] -> Type) (FilterSym0 a6989586621679997035) l0 # 
type Apply (TyFun a6989586621679997035 Bool -> Type) (TyFun [a6989586621679997035] [a6989586621679997035] -> Type) (FilterSym0 a6989586621679997035) l0 = FilterSym1 a6989586621679997035 l0

data FilterSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997035] [a6989586621679997035] (FilterSym1 a6989586621679997035 l0) l1 # 
type Apply [a6989586621679997035] [a6989586621679997035] (FilterSym1 a6989586621679997035 l0) l1 = FilterSym2 a6989586621679997035 l0 l1

type FilterSym2 t t = Filter t t #

data PartitionSym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997011 Bool -> Type) (TyFun [a6989586621679997011] ([a6989586621679997011], [a6989586621679997011]) -> Type) (PartitionSym0 a6989586621679997011) l0 # 
type Apply (TyFun a6989586621679997011 Bool -> Type) (TyFun [a6989586621679997011] ([a6989586621679997011], [a6989586621679997011]) -> Type) (PartitionSym0 a6989586621679997011) l0 = PartitionSym1 a6989586621679997011 l0

data PartitionSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997011] ([a6989586621679997011], [a6989586621679997011]) (PartitionSym1 a6989586621679997011 l0) l1 # 
type Apply [a6989586621679997011] ([a6989586621679997011], [a6989586621679997011]) (PartitionSym1 a6989586621679997011 l0) l1 = PartitionSym2 a6989586621679997011 l0 l1

type PartitionSym2 t t = Partition t t #

data (:!!$) l #

Instances

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

Methods

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

type Apply [a6989586621679997004] (TyFun Nat a6989586621679997004 -> Type) ((:!!$) a6989586621679997004) l0 # 
type Apply [a6989586621679997004] (TyFun Nat a6989586621679997004 -> Type) ((:!!$) a6989586621679997004) l0 = (:!!$$) a6989586621679997004 l0

data l :!!$$ l #

Instances

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

Methods

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

type Apply Nat a6989586621679997004 ((:!!$$) a6989586621679997004 l0) l1 # 
type Apply Nat a6989586621679997004 ((:!!$$) a6989586621679997004 l0) l1 = (:!!$$$) a6989586621679997004 l0 l1

type (:!!$$$) t t = (:!!) t t #

data ElemIndexSym0 l #

Instances

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

Methods

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

type Apply a6989586621679997033 (TyFun [a6989586621679997033] (Maybe Nat) -> Type) (ElemIndexSym0 a6989586621679997033) l0 # 
type Apply a6989586621679997033 (TyFun [a6989586621679997033] (Maybe Nat) -> Type) (ElemIndexSym0 a6989586621679997033) l0 = ElemIndexSym1 a6989586621679997033 l0

data ElemIndexSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997033] (Maybe Nat) (ElemIndexSym1 a6989586621679997033 l0) l1 # 
type Apply [a6989586621679997033] (Maybe Nat) (ElemIndexSym1 a6989586621679997033 l0) l1 = ElemIndexSym2 a6989586621679997033 l0 l1

type ElemIndexSym2 t t = ElemIndex t t #

data ElemIndicesSym0 l #

Instances

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

Methods

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

type Apply a6989586621679997032 (TyFun [a6989586621679997032] [Nat] -> Type) (ElemIndicesSym0 a6989586621679997032) l0 # 
type Apply a6989586621679997032 (TyFun [a6989586621679997032] [Nat] -> Type) (ElemIndicesSym0 a6989586621679997032) l0 = ElemIndicesSym1 a6989586621679997032 l0

data ElemIndicesSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997032] [Nat] (ElemIndicesSym1 a6989586621679997032 l0) l1 # 
type Apply [a6989586621679997032] [Nat] (ElemIndicesSym1 a6989586621679997032 l0) l1 = ElemIndicesSym2 a6989586621679997032 l0 l1

data FindIndexSym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997031 Bool -> Type) (TyFun [a6989586621679997031] (Maybe Nat) -> Type) (FindIndexSym0 a6989586621679997031) l0 # 
type Apply (TyFun a6989586621679997031 Bool -> Type) (TyFun [a6989586621679997031] (Maybe Nat) -> Type) (FindIndexSym0 a6989586621679997031) l0 = FindIndexSym1 a6989586621679997031 l0

data FindIndexSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997031] (Maybe Nat) (FindIndexSym1 a6989586621679997031 l0) l1 # 
type Apply [a6989586621679997031] (Maybe Nat) (FindIndexSym1 a6989586621679997031 l0) l1 = FindIndexSym2 a6989586621679997031 l0 l1

type FindIndexSym2 t t = FindIndex t t #

data FindIndicesSym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997030 Bool -> Type) (TyFun [a6989586621679997030] [Nat] -> Type) (FindIndicesSym0 a6989586621679997030) l0 # 
type Apply (TyFun a6989586621679997030 Bool -> Type) (TyFun [a6989586621679997030] [Nat] -> Type) (FindIndicesSym0 a6989586621679997030) l0 = FindIndicesSym1 a6989586621679997030 l0

data FindIndicesSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997030] [Nat] (FindIndicesSym1 a6989586621679997030 l0) l1 # 
type Apply [a6989586621679997030] [Nat] (FindIndicesSym1 a6989586621679997030 l0) l1 = FindIndicesSym2 a6989586621679997030 l0 l1

data ZipSym0 l #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679997081] (TyFun [b6989586621679997082] [(a6989586621679997081, b6989586621679997082)] -> Type) -> *) (ZipSym0 a6989586621679997081 b6989586621679997082) # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a6989586621679997081 b6989586621679997082) t -> () #

type Apply [a6989586621679997081] (TyFun [b6989586621679997082] [(a6989586621679997081, b6989586621679997082)] -> Type) (ZipSym0 a6989586621679997081 b6989586621679997082) l0 # 
type Apply [a6989586621679997081] (TyFun [b6989586621679997082] [(a6989586621679997081, b6989586621679997082)] -> Type) (ZipSym0 a6989586621679997081 b6989586621679997082) l0 = ZipSym1 b6989586621679997082 a6989586621679997081 l0

data ZipSym1 l l #

Instances

SuppressUnusedWarnings ([a6989586621679997081] -> TyFun [b6989586621679997082] [(a6989586621679997081, b6989586621679997082)] -> *) (ZipSym1 b6989586621679997082 a6989586621679997081) # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 b6989586621679997082 a6989586621679997081) t -> () #

type Apply [b6989586621679997082] [(a6989586621679997081, b6989586621679997082)] (ZipSym1 b6989586621679997082 a6989586621679997081 l0) l1 # 
type Apply [b6989586621679997082] [(a6989586621679997081, b6989586621679997082)] (ZipSym1 b6989586621679997082 a6989586621679997081 l0) l1 = ZipSym2 b6989586621679997082 a6989586621679997081 l0 l1

type ZipSym2 t t = Zip t t #

data Zip3Sym0 l #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679997078] (TyFun [b6989586621679997079] (TyFun [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] -> Type) -> Type) -> *) (Zip3Sym0 a6989586621679997078 b6989586621679997079 c6989586621679997080) # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym0 a6989586621679997078 b6989586621679997079 c6989586621679997080) t -> () #

type Apply [a6989586621679997078] (TyFun [b6989586621679997079] (TyFun [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] -> Type) -> Type) (Zip3Sym0 a6989586621679997078 b6989586621679997079 c6989586621679997080) l0 # 
type Apply [a6989586621679997078] (TyFun [b6989586621679997079] (TyFun [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] -> Type) -> Type) (Zip3Sym0 a6989586621679997078 b6989586621679997079 c6989586621679997080) l0 = Zip3Sym1 b6989586621679997079 c6989586621679997080 a6989586621679997078 l0

data Zip3Sym1 l l #

Instances

SuppressUnusedWarnings ([a6989586621679997078] -> TyFun [b6989586621679997079] (TyFun [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] -> Type) -> *) (Zip3Sym1 b6989586621679997079 c6989586621679997080 a6989586621679997078) # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym1 b6989586621679997079 c6989586621679997080 a6989586621679997078) t -> () #

type Apply [b6989586621679997079] (TyFun [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] -> Type) (Zip3Sym1 b6989586621679997079 c6989586621679997080 a6989586621679997078 l0) l1 # 
type Apply [b6989586621679997079] (TyFun [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] -> Type) (Zip3Sym1 b6989586621679997079 c6989586621679997080 a6989586621679997078 l0) l1 = Zip3Sym2 c6989586621679997080 b6989586621679997079 a6989586621679997078 l0 l1

data Zip3Sym2 l l l #

Instances

SuppressUnusedWarnings ([a6989586621679997078] -> [b6989586621679997079] -> TyFun [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] -> *) (Zip3Sym2 c6989586621679997080 b6989586621679997079 a6989586621679997078) # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym2 c6989586621679997080 b6989586621679997079 a6989586621679997078) t -> () #

type Apply [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] (Zip3Sym2 c6989586621679997080 b6989586621679997079 a6989586621679997078 l1 l0) l2 # 
type Apply [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] (Zip3Sym2 c6989586621679997080 b6989586621679997079 a6989586621679997078 l1 l0) l2 = Zip3Sym3 c6989586621679997080 b6989586621679997079 a6989586621679997078 l1 l0 l2

type Zip3Sym3 t t t = Zip3 t t t #

data ZipWithSym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679997075 (TyFun b6989586621679997076 c6989586621679997077 -> Type) -> Type) (TyFun [a6989586621679997075] (TyFun [b6989586621679997076] [c6989586621679997077] -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679997075 b6989586621679997076 c6989586621679997077) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a6989586621679997075 b6989586621679997076 c6989586621679997077) t -> () #

type Apply (TyFun a6989586621679997075 (TyFun b6989586621679997076 c6989586621679997077 -> Type) -> Type) (TyFun [a6989586621679997075] (TyFun [b6989586621679997076] [c6989586621679997077] -> Type) -> Type) (ZipWithSym0 a6989586621679997075 b6989586621679997076 c6989586621679997077) l0 # 
type Apply (TyFun a6989586621679997075 (TyFun b6989586621679997076 c6989586621679997077 -> Type) -> Type) (TyFun [a6989586621679997075] (TyFun [b6989586621679997076] [c6989586621679997077] -> Type) -> Type) (ZipWithSym0 a6989586621679997075 b6989586621679997076 c6989586621679997077) l0 = ZipWithSym1 a6989586621679997075 b6989586621679997076 c6989586621679997077 l0

data ZipWithSym1 l l #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679997075 (TyFun b6989586621679997076 c6989586621679997077 -> Type) -> Type) -> TyFun [a6989586621679997075] (TyFun [b6989586621679997076] [c6989586621679997077] -> Type) -> *) (ZipWithSym1 a6989586621679997075 b6989586621679997076 c6989586621679997077) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a6989586621679997075 b6989586621679997076 c6989586621679997077) t -> () #

type Apply [a6989586621679997075] (TyFun [b6989586621679997076] [c6989586621679997077] -> Type) (ZipWithSym1 a6989586621679997075 b6989586621679997076 c6989586621679997077 l0) l1 # 
type Apply [a6989586621679997075] (TyFun [b6989586621679997076] [c6989586621679997077] -> Type) (ZipWithSym1 a6989586621679997075 b6989586621679997076 c6989586621679997077 l0) l1 = ZipWithSym2 a6989586621679997075 b6989586621679997076 c6989586621679997077 l0 l1

data ZipWithSym2 l l l #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679997075 (TyFun b6989586621679997076 c6989586621679997077 -> Type) -> Type) -> [a6989586621679997075] -> TyFun [b6989586621679997076] [c6989586621679997077] -> *) (ZipWithSym2 a6989586621679997075 b6989586621679997076 c6989586621679997077) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a6989586621679997075 b6989586621679997076 c6989586621679997077) t -> () #

type Apply [b6989586621679997076] [c6989586621679997077] (ZipWithSym2 a6989586621679997075 b6989586621679997076 c6989586621679997077 l1 l0) l2 # 
type Apply [b6989586621679997076] [c6989586621679997077] (ZipWithSym2 a6989586621679997075 b6989586621679997076 c6989586621679997077 l1 l0) l2 = ZipWithSym3 a6989586621679997075 b6989586621679997076 c6989586621679997077 l1 l0 l2

type ZipWithSym3 t t t = ZipWith t t t #

data ZipWith3Sym0 l #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679997071 (TyFun b6989586621679997072 (TyFun c6989586621679997073 d6989586621679997074 -> Type) -> Type) -> Type) (TyFun [a6989586621679997071] (TyFun [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym0 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) t -> () #

type Apply (TyFun a6989586621679997071 (TyFun b6989586621679997072 (TyFun c6989586621679997073 d6989586621679997074 -> Type) -> Type) -> Type) (TyFun [a6989586621679997071] (TyFun [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) -> Type) -> Type) (ZipWith3Sym0 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) l0 # 
type Apply (TyFun a6989586621679997071 (TyFun b6989586621679997072 (TyFun c6989586621679997073 d6989586621679997074 -> Type) -> Type) -> Type) (TyFun [a6989586621679997071] (TyFun [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) -> Type) -> Type) (ZipWith3Sym0 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) l0 = ZipWith3Sym1 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l0

data ZipWith3Sym1 l l #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679997071 (TyFun b6989586621679997072 (TyFun c6989586621679997073 d6989586621679997074 -> Type) -> Type) -> Type) -> TyFun [a6989586621679997071] (TyFun [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) -> Type) -> *) (ZipWith3Sym1 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym1 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) t -> () #

type Apply [a6989586621679997071] (TyFun [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) -> Type) (ZipWith3Sym1 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l0) l1 # 
type Apply [a6989586621679997071] (TyFun [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) -> Type) (ZipWith3Sym1 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l0) l1 = ZipWith3Sym2 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l0 l1

data ZipWith3Sym2 l l l #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679997071 (TyFun b6989586621679997072 (TyFun c6989586621679997073 d6989586621679997074 -> Type) -> Type) -> Type) -> [a6989586621679997071] -> TyFun [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) -> *) (ZipWith3Sym2 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym2 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) t -> () #

type Apply [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) (ZipWith3Sym2 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l1 l0) l2 # 
type Apply [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) (ZipWith3Sym2 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l1 l0) l2 = ZipWith3Sym3 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l1 l0 l2

data ZipWith3Sym3 l l l l #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679997071 (TyFun b6989586621679997072 (TyFun c6989586621679997073 d6989586621679997074 -> Type) -> Type) -> Type) -> [a6989586621679997071] -> [b6989586621679997072] -> TyFun [c6989586621679997073] [d6989586621679997074] -> *) (ZipWith3Sym3 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym3 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) t -> () #

type Apply [c6989586621679997073] [d6989586621679997074] (ZipWith3Sym3 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l2 l1 l0) l3 # 
type Apply [c6989586621679997073] [d6989586621679997074] (ZipWith3Sym3 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l2 l1 l0) l3 = ZipWith3Sym4 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l2 l1 l0 l3

type ZipWith3Sym4 t t t t = ZipWith3 t t t t #

data UnzipSym0 l #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679997069, b6989586621679997070)] ([a6989586621679997069], [b6989586621679997070]) -> *) (UnzipSym0 a6989586621679997069 b6989586621679997070) # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a6989586621679997069 b6989586621679997070) t -> () #

type Apply [(a6989586621679997069, b6989586621679997070)] ([a6989586621679997069], [b6989586621679997070]) (UnzipSym0 a6989586621679997069 b6989586621679997070) l0 # 
type Apply [(a6989586621679997069, b6989586621679997070)] ([a6989586621679997069], [b6989586621679997070]) (UnzipSym0 a6989586621679997069 b6989586621679997070) l0 = UnzipSym1 a6989586621679997069 b6989586621679997070 l0

type UnzipSym1 t = Unzip t #

data Unzip3Sym0 l #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679997066, b6989586621679997067, c6989586621679997068)] ([a6989586621679997066], [b6989586621679997067], [c6989586621679997068]) -> *) (Unzip3Sym0 a6989586621679997066 b6989586621679997067 c6989586621679997068) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip3Sym0 a6989586621679997066 b6989586621679997067 c6989586621679997068) t -> () #

type Apply [(a6989586621679997066, b6989586621679997067, c6989586621679997068)] ([a6989586621679997066], [b6989586621679997067], [c6989586621679997068]) (Unzip3Sym0 a6989586621679997066 b6989586621679997067 c6989586621679997068) l0 # 
type Apply [(a6989586621679997066, b6989586621679997067, c6989586621679997068)] ([a6989586621679997066], [b6989586621679997067], [c6989586621679997068]) (Unzip3Sym0 a6989586621679997066 b6989586621679997067 c6989586621679997068) l0 = Unzip3Sym1 a6989586621679997066 b6989586621679997067 c6989586621679997068 l0

type Unzip3Sym1 t = Unzip3 t #

data Unzip4Sym0 l #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679997062, b6989586621679997063, c6989586621679997064, d6989586621679997065)] ([a6989586621679997062], [b6989586621679997063], [c6989586621679997064], [d6989586621679997065]) -> *) (Unzip4Sym0 a6989586621679997062 b6989586621679997063 c6989586621679997064 d6989586621679997065) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip4Sym0 a6989586621679997062 b6989586621679997063 c6989586621679997064 d6989586621679997065) t -> () #

type Apply [(a6989586621679997062, b6989586621679997063, c6989586621679997064, d6989586621679997065)] ([a6989586621679997062], [b6989586621679997063], [c6989586621679997064], [d6989586621679997065]) (Unzip4Sym0 a6989586621679997062 b6989586621679997063 c6989586621679997064 d6989586621679997065) l0 # 
type Apply [(a6989586621679997062, b6989586621679997063, c6989586621679997064, d6989586621679997065)] ([a6989586621679997062], [b6989586621679997063], [c6989586621679997064], [d6989586621679997065]) (Unzip4Sym0 a6989586621679997062 b6989586621679997063 c6989586621679997064 d6989586621679997065) l0 = Unzip4Sym1 a6989586621679997062 b6989586621679997063 c6989586621679997064 d6989586621679997065 l0

type Unzip4Sym1 t = Unzip4 t #

data Unzip5Sym0 l #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679997057, b6989586621679997058, c6989586621679997059, d6989586621679997060, e6989586621679997061)] ([a6989586621679997057], [b6989586621679997058], [c6989586621679997059], [d6989586621679997060], [e6989586621679997061]) -> *) (Unzip5Sym0 a6989586621679997057 b6989586621679997058 c6989586621679997059 d6989586621679997060 e6989586621679997061) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip5Sym0 a6989586621679997057 b6989586621679997058 c6989586621679997059 d6989586621679997060 e6989586621679997061) t -> () #

type Apply [(a6989586621679997057, b6989586621679997058, c6989586621679997059, d6989586621679997060, e6989586621679997061)] ([a6989586621679997057], [b6989586621679997058], [c6989586621679997059], [d6989586621679997060], [e6989586621679997061]) (Unzip5Sym0 a6989586621679997057 b6989586621679997058 c6989586621679997059 d6989586621679997060 e6989586621679997061) l0 # 
type Apply [(a6989586621679997057, b6989586621679997058, c6989586621679997059, d6989586621679997060, e6989586621679997061)] ([a6989586621679997057], [b6989586621679997058], [c6989586621679997059], [d6989586621679997060], [e6989586621679997061]) (Unzip5Sym0 a6989586621679997057 b6989586621679997058 c6989586621679997059 d6989586621679997060 e6989586621679997061) l0 = Unzip5Sym1 a6989586621679997057 b6989586621679997058 c6989586621679997059 d6989586621679997060 e6989586621679997061 l0

type Unzip5Sym1 t = Unzip5 t #

data Unzip6Sym0 l #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679997051, b6989586621679997052, c6989586621679997053, d6989586621679997054, e6989586621679997055, f6989586621679997056)] ([a6989586621679997051], [b6989586621679997052], [c6989586621679997053], [d6989586621679997054], [e6989586621679997055], [f6989586621679997056]) -> *) (Unzip6Sym0 a6989586621679997051 b6989586621679997052 c6989586621679997053 d6989586621679997054 e6989586621679997055 f6989586621679997056) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip6Sym0 a6989586621679997051 b6989586621679997052 c6989586621679997053 d6989586621679997054 e6989586621679997055 f6989586621679997056) t -> () #

type Apply [(a6989586621679997051, b6989586621679997052, c6989586621679997053, d6989586621679997054, e6989586621679997055, f6989586621679997056)] ([a6989586621679997051], [b6989586621679997052], [c6989586621679997053], [d6989586621679997054], [e6989586621679997055], [f6989586621679997056]) (Unzip6Sym0 a6989586621679997051 b6989586621679997052 c6989586621679997053 d6989586621679997054 e6989586621679997055 f6989586621679997056) l0 # 
type Apply [(a6989586621679997051, b6989586621679997052, c6989586621679997053, d6989586621679997054, e6989586621679997055, f6989586621679997056)] ([a6989586621679997051], [b6989586621679997052], [c6989586621679997053], [d6989586621679997054], [e6989586621679997055], [f6989586621679997056]) (Unzip6Sym0 a6989586621679997051 b6989586621679997052 c6989586621679997053 d6989586621679997054 e6989586621679997055 f6989586621679997056) l0 = Unzip6Sym1 a6989586621679997051 b6989586621679997052 c6989586621679997053 d6989586621679997054 e6989586621679997055 f6989586621679997056 l0

type Unzip6Sym1 t = Unzip6 t #

data Unzip7Sym0 l #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679997044, b6989586621679997045, c6989586621679997046, d6989586621679997047, e6989586621679997048, f6989586621679997049, g6989586621679997050)] ([a6989586621679997044], [b6989586621679997045], [c6989586621679997046], [d6989586621679997047], [e6989586621679997048], [f6989586621679997049], [g6989586621679997050]) -> *) (Unzip7Sym0 a6989586621679997044 b6989586621679997045 c6989586621679997046 d6989586621679997047 e6989586621679997048 f6989586621679997049 g6989586621679997050) # 

Methods

suppressUnusedWarnings :: Proxy (Unzip7Sym0 a6989586621679997044 b6989586621679997045 c6989586621679997046 d6989586621679997047 e6989586621679997048 f6989586621679997049 g6989586621679997050) t -> () #

type Apply [(a6989586621679997044, b6989586621679997045, c6989586621679997046, d6989586621679997047, e6989586621679997048, f6989586621679997049, g6989586621679997050)] ([a6989586621679997044], [b6989586621679997045], [c6989586621679997046], [d6989586621679997047], [e6989586621679997048], [f6989586621679997049], [g6989586621679997050]) (Unzip7Sym0 a6989586621679997044 b6989586621679997045 c6989586621679997046 d6989586621679997047 e6989586621679997048 f6989586621679997049 g6989586621679997050) l0 # 
type Apply [(a6989586621679997044, b6989586621679997045, c6989586621679997046, d6989586621679997047, e6989586621679997048, f6989586621679997049, g6989586621679997050)] ([a6989586621679997044], [b6989586621679997045], [c6989586621679997046], [d6989586621679997047], [e6989586621679997048], [f6989586621679997049], [g6989586621679997050]) (Unzip7Sym0 a6989586621679997044 b6989586621679997045 c6989586621679997046 d6989586621679997047 e6989586621679997048 f6989586621679997049 g6989586621679997050) l0 = Unzip7Sym1 a6989586621679997044 b6989586621679997045 c6989586621679997046 d6989586621679997047 e6989586621679997048 f6989586621679997049 g6989586621679997050 l0

type Unzip7Sym1 t = Unzip7 t #

data NubSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997003] [a6989586621679997003] (NubSym0 a6989586621679997003) l0 # 
type Apply [a6989586621679997003] [a6989586621679997003] (NubSym0 a6989586621679997003) l0 = NubSym1 a6989586621679997003 l0

type NubSym1 t = Nub t #

data DeleteSym0 l #

Instances

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

Methods

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

type Apply a6989586621679997043 (TyFun [a6989586621679997043] [a6989586621679997043] -> Type) (DeleteSym0 a6989586621679997043) l0 # 
type Apply a6989586621679997043 (TyFun [a6989586621679997043] [a6989586621679997043] -> Type) (DeleteSym0 a6989586621679997043) l0 = DeleteSym1 a6989586621679997043 l0

data DeleteSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997043] [a6989586621679997043] (DeleteSym1 a6989586621679997043 l0) l1 # 
type Apply [a6989586621679997043] [a6989586621679997043] (DeleteSym1 a6989586621679997043 l0) l1 = DeleteSym2 a6989586621679997043 l0 l1

type DeleteSym2 t t = Delete t t #

data (:\\$) l #

Instances

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

Methods

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

type Apply [a6989586621679997042] (TyFun [a6989586621679997042] [a6989586621679997042] -> Type) ((:\\$) a6989586621679997042) l0 # 
type Apply [a6989586621679997042] (TyFun [a6989586621679997042] [a6989586621679997042] -> Type) ((:\\$) a6989586621679997042) l0 = (:\\$$) a6989586621679997042 l0

data l :\\$$ l #

Instances

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

Methods

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

type Apply [a6989586621679997042] [a6989586621679997042] ((:\\$$) a6989586621679997042 l0) l1 # 
type Apply [a6989586621679997042] [a6989586621679997042] ((:\\$$) a6989586621679997042 l0) l1 = (:\\$$$) a6989586621679997042 l0 l1

type (:\\$$$) t t = (:\\) t t #

data UnionSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679996999] (TyFun [a6989586621679996999] [a6989586621679996999] -> Type) (UnionSym0 a6989586621679996999) l0 # 
type Apply [a6989586621679996999] (TyFun [a6989586621679996999] [a6989586621679996999] -> Type) (UnionSym0 a6989586621679996999) l0 = UnionSym1 a6989586621679996999 l0

data UnionSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679996999] [a6989586621679996999] (UnionSym1 a6989586621679996999 l0) l1 # 
type Apply [a6989586621679996999] [a6989586621679996999] (UnionSym1 a6989586621679996999 l0) l1 = UnionSym2 a6989586621679996999 l0 l1

type UnionSym2 t t = Union t t #

data IntersectSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997029] (TyFun [a6989586621679997029] [a6989586621679997029] -> Type) (IntersectSym0 a6989586621679997029) l0 # 
type Apply [a6989586621679997029] (TyFun [a6989586621679997029] [a6989586621679997029] -> Type) (IntersectSym0 a6989586621679997029) l0 = IntersectSym1 a6989586621679997029 l0

data IntersectSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997029] [a6989586621679997029] (IntersectSym1 a6989586621679997029 l0) l1 # 
type Apply [a6989586621679997029] [a6989586621679997029] (IntersectSym1 a6989586621679997029 l0) l1 = IntersectSym2 a6989586621679997029 l0 l1

type IntersectSym2 t t = Intersect t t #

data InsertSym0 l #

Instances

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

Methods

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

type Apply a6989586621679997016 (TyFun [a6989586621679997016] [a6989586621679997016] -> Type) (InsertSym0 a6989586621679997016) l0 # 
type Apply a6989586621679997016 (TyFun [a6989586621679997016] [a6989586621679997016] -> Type) (InsertSym0 a6989586621679997016) l0 = InsertSym1 a6989586621679997016 l0

data InsertSym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997016] [a6989586621679997016] (InsertSym1 a6989586621679997016 l0) l1 # 
type Apply [a6989586621679997016] [a6989586621679997016] (InsertSym1 a6989586621679997016 l0) l1 = InsertSym2 a6989586621679997016 l0 l1

type InsertSym2 t t = Insert t t #

data SortSym0 l #

Instances

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

Methods

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

type Apply [a6989586621679997015] [a6989586621679997015] (SortSym0 a6989586621679997015) l0 # 
type Apply [a6989586621679997015] [a6989586621679997015] (SortSym0 a6989586621679997015) l0 = SortSym1 a6989586621679997015 l0

type SortSym1 t = Sort t #

data NubBySym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997002 (TyFun a6989586621679997002 Bool -> Type) -> Type) (TyFun [a6989586621679997002] [a6989586621679997002] -> Type) (NubBySym0 a6989586621679997002) l0 # 
type Apply (TyFun a6989586621679997002 (TyFun a6989586621679997002 Bool -> Type) -> Type) (TyFun [a6989586621679997002] [a6989586621679997002] -> Type) (NubBySym0 a6989586621679997002) l0 = NubBySym1 a6989586621679997002 l0

data NubBySym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997002] [a6989586621679997002] (NubBySym1 a6989586621679997002 l0) l1 # 
type Apply [a6989586621679997002] [a6989586621679997002] (NubBySym1 a6989586621679997002 l0) l1 = NubBySym2 a6989586621679997002 l0 l1

type NubBySym2 t t = NubBy t t #

data DeleteBySym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997041 (TyFun a6989586621679997041 Bool -> Type) -> Type) (TyFun a6989586621679997041 (TyFun [a6989586621679997041] [a6989586621679997041] -> Type) -> Type) (DeleteBySym0 a6989586621679997041) l0 # 
type Apply (TyFun a6989586621679997041 (TyFun a6989586621679997041 Bool -> Type) -> Type) (TyFun a6989586621679997041 (TyFun [a6989586621679997041] [a6989586621679997041] -> Type) -> Type) (DeleteBySym0 a6989586621679997041) l0 = DeleteBySym1 a6989586621679997041 l0

data DeleteBySym1 l l #

Instances

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

Methods

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

type Apply a6989586621679997041 (TyFun [a6989586621679997041] [a6989586621679997041] -> Type) (DeleteBySym1 a6989586621679997041 l0) l1 # 
type Apply a6989586621679997041 (TyFun [a6989586621679997041] [a6989586621679997041] -> Type) (DeleteBySym1 a6989586621679997041 l0) l1 = DeleteBySym2 a6989586621679997041 l0 l1

data DeleteBySym2 l l l #

Instances

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

Methods

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

type Apply [a6989586621679997041] [a6989586621679997041] (DeleteBySym2 a6989586621679997041 l1 l0) l2 # 
type Apply [a6989586621679997041] [a6989586621679997041] (DeleteBySym2 a6989586621679997041 l1 l0) l2 = DeleteBySym3 a6989586621679997041 l1 l0 l2

type DeleteBySym3 t t t = DeleteBy t t t #

data DeleteFirstsBySym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997040 (TyFun a6989586621679997040 Bool -> Type) -> Type) (TyFun [a6989586621679997040] (TyFun [a6989586621679997040] [a6989586621679997040] -> Type) -> Type) (DeleteFirstsBySym0 a6989586621679997040) l0 # 
type Apply (TyFun a6989586621679997040 (TyFun a6989586621679997040 Bool -> Type) -> Type) (TyFun [a6989586621679997040] (TyFun [a6989586621679997040] [a6989586621679997040] -> Type) -> Type) (DeleteFirstsBySym0 a6989586621679997040) l0 = DeleteFirstsBySym1 a6989586621679997040 l0

data DeleteFirstsBySym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997040] (TyFun [a6989586621679997040] [a6989586621679997040] -> Type) (DeleteFirstsBySym1 a6989586621679997040 l0) l1 # 
type Apply [a6989586621679997040] (TyFun [a6989586621679997040] [a6989586621679997040] -> Type) (DeleteFirstsBySym1 a6989586621679997040 l0) l1 = DeleteFirstsBySym2 a6989586621679997040 l0 l1

data DeleteFirstsBySym2 l l l #

Instances

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

Methods

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

type Apply [a6989586621679997040] [a6989586621679997040] (DeleteFirstsBySym2 a6989586621679997040 l1 l0) l2 # 
type Apply [a6989586621679997040] [a6989586621679997040] (DeleteFirstsBySym2 a6989586621679997040 l1 l0) l2 = DeleteFirstsBySym3 a6989586621679997040 l1 l0 l2

data UnionBySym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997000 (TyFun a6989586621679997000 Bool -> Type) -> Type) (TyFun [a6989586621679997000] (TyFun [a6989586621679997000] [a6989586621679997000] -> Type) -> Type) (UnionBySym0 a6989586621679997000) l0 # 
type Apply (TyFun a6989586621679997000 (TyFun a6989586621679997000 Bool -> Type) -> Type) (TyFun [a6989586621679997000] (TyFun [a6989586621679997000] [a6989586621679997000] -> Type) -> Type) (UnionBySym0 a6989586621679997000) l0 = UnionBySym1 a6989586621679997000 l0

data UnionBySym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997000] (TyFun [a6989586621679997000] [a6989586621679997000] -> Type) (UnionBySym1 a6989586621679997000 l0) l1 # 
type Apply [a6989586621679997000] (TyFun [a6989586621679997000] [a6989586621679997000] -> Type) (UnionBySym1 a6989586621679997000 l0) l1 = UnionBySym2 a6989586621679997000 l0 l1

data UnionBySym2 l l l #

Instances

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

Methods

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

type Apply [a6989586621679997000] [a6989586621679997000] (UnionBySym2 a6989586621679997000 l1 l0) l2 # 
type Apply [a6989586621679997000] [a6989586621679997000] (UnionBySym2 a6989586621679997000 l1 l0) l2 = UnionBySym3 a6989586621679997000 l1 l0 l2

type UnionBySym3 t t t = UnionBy t t t #

data IntersectBySym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997028 (TyFun a6989586621679997028 Bool -> Type) -> Type) (TyFun [a6989586621679997028] (TyFun [a6989586621679997028] [a6989586621679997028] -> Type) -> Type) (IntersectBySym0 a6989586621679997028) l0 # 
type Apply (TyFun a6989586621679997028 (TyFun a6989586621679997028 Bool -> Type) -> Type) (TyFun [a6989586621679997028] (TyFun [a6989586621679997028] [a6989586621679997028] -> Type) -> Type) (IntersectBySym0 a6989586621679997028) l0 = IntersectBySym1 a6989586621679997028 l0

data IntersectBySym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997028] (TyFun [a6989586621679997028] [a6989586621679997028] -> Type) (IntersectBySym1 a6989586621679997028 l0) l1 # 
type Apply [a6989586621679997028] (TyFun [a6989586621679997028] [a6989586621679997028] -> Type) (IntersectBySym1 a6989586621679997028 l0) l1 = IntersectBySym2 a6989586621679997028 l0 l1

data IntersectBySym2 l l l #

Instances

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

Methods

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

type Apply [a6989586621679997028] [a6989586621679997028] (IntersectBySym2 a6989586621679997028 l1 l0) l2 # 
type Apply [a6989586621679997028] [a6989586621679997028] (IntersectBySym2 a6989586621679997028 l1 l0) l2 = IntersectBySym3 a6989586621679997028 l1 l0 l2

type IntersectBySym3 t t t = IntersectBy t t t #

data GroupBySym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997014 (TyFun a6989586621679997014 Bool -> Type) -> Type) (TyFun [a6989586621679997014] [[a6989586621679997014]] -> Type) (GroupBySym0 a6989586621679997014) l0 # 
type Apply (TyFun a6989586621679997014 (TyFun a6989586621679997014 Bool -> Type) -> Type) (TyFun [a6989586621679997014] [[a6989586621679997014]] -> Type) (GroupBySym0 a6989586621679997014) l0 = GroupBySym1 a6989586621679997014 l0

data GroupBySym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997014] [[a6989586621679997014]] (GroupBySym1 a6989586621679997014 l0) l1 # 
type Apply [a6989586621679997014] [[a6989586621679997014]] (GroupBySym1 a6989586621679997014 l0) l1 = GroupBySym2 a6989586621679997014 l0 l1

type GroupBySym2 t t = GroupBy t t #

data SortBySym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997039 (TyFun a6989586621679997039 Ordering -> Type) -> Type) (TyFun [a6989586621679997039] [a6989586621679997039] -> Type) (SortBySym0 a6989586621679997039) l0 # 
type Apply (TyFun a6989586621679997039 (TyFun a6989586621679997039 Ordering -> Type) -> Type) (TyFun [a6989586621679997039] [a6989586621679997039] -> Type) (SortBySym0 a6989586621679997039) l0 = SortBySym1 a6989586621679997039 l0

data SortBySym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997039] [a6989586621679997039] (SortBySym1 a6989586621679997039 l0) l1 # 
type Apply [a6989586621679997039] [a6989586621679997039] (SortBySym1 a6989586621679997039 l0) l1 = SortBySym2 a6989586621679997039 l0 l1

type SortBySym2 t t = SortBy t t #

data InsertBySym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997038 (TyFun a6989586621679997038 Ordering -> Type) -> Type) (TyFun a6989586621679997038 (TyFun [a6989586621679997038] [a6989586621679997038] -> Type) -> Type) (InsertBySym0 a6989586621679997038) l0 # 
type Apply (TyFun a6989586621679997038 (TyFun a6989586621679997038 Ordering -> Type) -> Type) (TyFun a6989586621679997038 (TyFun [a6989586621679997038] [a6989586621679997038] -> Type) -> Type) (InsertBySym0 a6989586621679997038) l0 = InsertBySym1 a6989586621679997038 l0

data InsertBySym1 l l #

Instances

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

Methods

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

type Apply a6989586621679997038 (TyFun [a6989586621679997038] [a6989586621679997038] -> Type) (InsertBySym1 a6989586621679997038 l0) l1 # 
type Apply a6989586621679997038 (TyFun [a6989586621679997038] [a6989586621679997038] -> Type) (InsertBySym1 a6989586621679997038 l0) l1 = InsertBySym2 a6989586621679997038 l0 l1

data InsertBySym2 l l l #

Instances

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

Methods

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

type Apply [a6989586621679997038] [a6989586621679997038] (InsertBySym2 a6989586621679997038 l1 l0) l2 # 
type Apply [a6989586621679997038] [a6989586621679997038] (InsertBySym2 a6989586621679997038 l1 l0) l2 = InsertBySym3 a6989586621679997038 l1 l0 l2

type InsertBySym3 t t t = InsertBy t t t #

data MaximumBySym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997037 (TyFun a6989586621679997037 Ordering -> Type) -> Type) (TyFun [a6989586621679997037] a6989586621679997037 -> Type) (MaximumBySym0 a6989586621679997037) l0 # 
type Apply (TyFun a6989586621679997037 (TyFun a6989586621679997037 Ordering -> Type) -> Type) (TyFun [a6989586621679997037] a6989586621679997037 -> Type) (MaximumBySym0 a6989586621679997037) l0 = MaximumBySym1 a6989586621679997037 l0

data MaximumBySym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997037] a6989586621679997037 (MaximumBySym1 a6989586621679997037 l0) l1 # 
type Apply [a6989586621679997037] a6989586621679997037 (MaximumBySym1 a6989586621679997037 l0) l1 = MaximumBySym2 a6989586621679997037 l0 l1

type MaximumBySym2 t t = MaximumBy t t #

data MinimumBySym0 l #

Instances

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

Methods

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

type Apply (TyFun a6989586621679997036 (TyFun a6989586621679997036 Ordering -> Type) -> Type) (TyFun [a6989586621679997036] a6989586621679997036 -> Type) (MinimumBySym0 a6989586621679997036) l0 # 
type Apply (TyFun a6989586621679997036 (TyFun a6989586621679997036 Ordering -> Type) -> Type) (TyFun [a6989586621679997036] a6989586621679997036 -> Type) (MinimumBySym0 a6989586621679997036) l0 = MinimumBySym1 a6989586621679997036 l0

data MinimumBySym1 l l #

Instances

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

Methods

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

type Apply [a6989586621679997036] a6989586621679997036 (MinimumBySym1 a6989586621679997036 l0) l1 # 
type Apply [a6989586621679997036] a6989586621679997036 (MinimumBySym1 a6989586621679997036 l0) l1 = MinimumBySym2 a6989586621679997036 l0 l1

type MinimumBySym2 t t = MinimumBy t t #

data GenericLengthSym0 l #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679996998] i6989586621679996997 -> *) (GenericLengthSym0 a6989586621679996998 i6989586621679996997) # 

Methods

suppressUnusedWarnings :: Proxy (GenericLengthSym0 a6989586621679996998 i6989586621679996997) t -> () #

type Apply [a6989586621679996998] k2 (GenericLengthSym0 a6989586621679996998 k2) l0 # 
type Apply [a6989586621679996998] k2 (GenericLengthSym0 a6989586621679996998 k2) l0 = GenericLengthSym1 k2 a6989586621679996998 l0