singletons-2.3: A framework for generating singleton types

Copyright(C) 2014 Jan Stolarek
LicenseBSD-style (see LICENSE)
MaintainerJan Stolarek (jan.stolarek@p.lodz.pl)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Promotion.Prelude.List

Contents

Description

Defines promoted functions and datatypes relating to List, including a promoted version of all 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

Basic functions

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

Null '[] = TrueSym0 
Null ((:) _z_6989586621679458786 _z_6989586621679458789) = FalseSym0 

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

Equations

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

List transformations

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

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

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

Equations

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

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

Equations

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

Reducing lists (folds)

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

Foldr k z a_6989586621679278100 = Apply (Let6989586621679278105GoSym3 k z a_6989586621679278100) a_6989586621679278100 

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

Equations

Foldr1 _z_6989586621679457954 '[x] = x 
Foldr1 f ((:) x ((:) wild_6989586621679455411 wild_6989586621679455413)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let6989586621679457962XsSym4 f x wild_6989586621679455411 wild_6989586621679455413)) 
Foldr1 _z_6989586621679457981 '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" 

Special folds

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

Maximum '[] = Apply ErrorSym0 "Data.Singletons.List.maximum: empty list" 
Maximum ((:) wild_6989586621679455491 wild_6989586621679455493) = Apply (Apply Foldl1Sym0 MaxSym0) (Let6989586621679458179XsSym2 wild_6989586621679455491 wild_6989586621679455493) 

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

Equations

Minimum '[] = Apply ErrorSym0 "Data.Singletons.List.minimum: empty list" 
Minimum ((:) wild_6989586621679455495 wild_6989586621679455497) = Apply (Apply Foldl1Sym0 MinSym0) (Let6989586621679458193XsSym2 wild_6989586621679455495 wild_6989586621679455497) 

any_ :: (a -> Bool) -> [a] -> Bool Source #

Building lists

Scans

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

Equations

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

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

Equations

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

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

Equations

Scanr _z_6989586621679457828 q0 '[] = Apply (Apply (:$) q0) '[] 
Scanr f q0 ((:) x xs) = Case_6989586621679457855 f q0 x xs (Let6989586621679457836Scrutinee_6989586621679455415Sym4 f q0 x xs) 

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

Equations

Scanr1 _z_6989586621679457759 '[] = '[] 
Scanr1 _z_6989586621679457762 '[x] = Apply (Apply (:$) x) '[] 
Scanr1 f ((:) x ((:) wild_6989586621679455419 wild_6989586621679455421)) = Case_6989586621679457808 f x wild_6989586621679455419 wild_6989586621679455421 (Let6989586621679457789Scrutinee_6989586621679455417Sym4 f x wild_6989586621679455419 wild_6989586621679455421) 

Accumulating maps

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

Equations

MapAccumL _z_6989586621679457593 s '[] = Apply (Apply Tuple2Sym0 s) '[] 
MapAccumL f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let6989586621679457601S''Sym4 f s x xs)) (Apply (Apply (:$) (Let6989586621679457601YSym4 f s x xs)) (Let6989586621679457601YsSym4 f s x xs)) 

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

Equations

MapAccumR _z_6989586621679457421 s '[] = Apply (Apply Tuple2Sym0 s) '[] 
MapAccumR f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let6989586621679457429S''Sym4 f s x xs)) (Apply (Apply (:$) (Let6989586621679457429YSym4 f s x xs)) (Let6989586621679457429YsSym4 f s x xs)) 

Infinite lists

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

Equations

Replicate n x = Case_6989586621679455700 n x (Let6989586621679455692Scrutinee_6989586621679455503Sym2 n x) 

Unfolding

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

Equations

Unfoldr f b = Case_6989586621679457401 f b (Let6989586621679457393Scrutinee_6989586621679455423Sym2 f b) 

Sublists

Extracting sublists

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

Equations

Take _z_6989586621679455887 '[] = '[] 
Take n ((:) x xs) = Case_6989586621679455906 n x xs (Let6989586621679455893Scrutinee_6989586621679455487Sym3 n x xs) 

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

Equations

Drop _z_6989586621679455856 '[] = '[] 
Drop n ((:) x xs) = Case_6989586621679455875 n x xs (Let6989586621679455862Scrutinee_6989586621679455489Sym3 n x xs) 

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

Equations

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

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

Equations

TakeWhile _z_6989586621679456254 '[] = '[] 
TakeWhile p ((:) x xs) = Case_6989586621679456273 p x xs (Let6989586621679456260Scrutinee_6989586621679455477Sym3 p x xs) 

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

Equations

DropWhile _z_6989586621679456210 '[] = '[] 
DropWhile p ((:) x xs') = Case_6989586621679456242 p x xs' (Let6989586621679456229Scrutinee_6989586621679455479Sym3 p x xs') 

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

Equations

DropWhileEnd p a_6989586621679458801 = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_6989586621679458805Sym0 p) a_6989586621679458801)) '[]) a_6989586621679458801 

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

Equations

Span _z_6989586621679456031 '[] = Apply (Apply Tuple2Sym0 Let6989586621679456034XsSym0) Let6989586621679456034XsSym0 
Span p ((:) x xs') = Case_6989586621679456064 p x xs' (Let6989586621679456051Scrutinee_6989586621679455483Sym3 p x xs') 

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

Equations

Break _z_6989586621679455929 '[] = Apply (Apply Tuple2Sym0 Let6989586621679455932XsSym0) Let6989586621679455932XsSym0 
Break p ((:) x xs') = Case_6989586621679455962 p x xs' (Let6989586621679455949Scrutinee_6989586621679455485Sym3 p x xs') 

type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ... Source #

Equations

StripPrefix '[] ys = Apply JustSym0 ys 
StripPrefix arg_6989586621679873544 arg_6989586621679873546 = Case_6989586621679874155 arg_6989586621679873544 arg_6989586621679873546 (Apply (Apply Tuple2Sym0 arg_6989586621679873544) arg_6989586621679873546) 

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

Equations

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

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

Equations

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

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

Equations

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

Predicates

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

Equations

IsPrefixOf '[] '[] = TrueSym0 
IsPrefixOf '[] ((:) _z_6989586621679457333 _z_6989586621679457336) = TrueSym0 
IsPrefixOf ((:) _z_6989586621679457339 _z_6989586621679457342) '[] = FalseSym0 
IsPrefixOf ((:) x xs) ((:) y ys) = Apply (Apply (:&&$) (Apply (Apply (:==$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) 

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

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

Equations

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

Searching lists

Searching by equality

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

Equations

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

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

Equations

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

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

Equations

Lookup _key '[] = NothingSym0 
Lookup key ((:) '(x, y) xys) = Case_6989586621679455844 key x y xys (Let6989586621679455825Scrutinee_6989586621679455499Sym4 key x y xys) 

Searching with a predicate

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

Equations

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

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

Equations

Filter _p '[] = '[] 
Filter p ((:) x xs) = Case_6989586621679456302 p x xs (Let6989586621679456289Scrutinee_6989586621679455465Sym3 p x xs) 

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

Equations

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

Indexing lists

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

Equations

'[] :!! _z_6989586621679455659 = Apply ErrorSym0 "Data.Singletons.List.!!: index too large" 
((:) x xs) :!! n = Case_6989586621679455678 x xs n (Let6989586621679455665Scrutinee_6989586621679455505Sym3 x xs n) 

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

FindIndices p xs = Apply (Apply MapSym0 SndSym0) (Apply (Apply FilterSym0 (Apply (Apply Lambda_6989586621679457184Sym0 p) xs)) (Apply (Apply ZipSym0 xs) (Apply (Apply (Let6989586621679457155BuildListSym2 p xs) (FromInteger 0)) xs))) 

Zipping and unzipping lists

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

Equations

Zip ((:) x xs) ((:) y ys) = Apply (Apply (:$) (Apply (Apply Tuple2Sym0 x) y)) (Apply (Apply ZipSym0 xs) ys) 
Zip '[] '[] = '[] 
Zip ((:) _z_6989586621679457132 _z_6989586621679457135) '[] = '[] 
Zip '[] ((:) _z_6989586621679457138 _z_6989586621679457141) = '[] 

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

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_6989586621679457065 _z_6989586621679457068) = '[] 
Zip3 '[] ((:) _z_6989586621679457071 _z_6989586621679457074) '[] = '[] 
Zip3 '[] ((:) _z_6989586621679457077 _z_6989586621679457080) ((:) _z_6989586621679457083 _z_6989586621679457086) = '[] 
Zip3 ((:) _z_6989586621679457089 _z_6989586621679457092) '[] '[] = '[] 
Zip3 ((:) _z_6989586621679457095 _z_6989586621679457098) '[] ((:) _z_6989586621679457101 _z_6989586621679457104) = '[] 
Zip3 ((:) _z_6989586621679457107 _z_6989586621679457110) ((:) _z_6989586621679457113 _z_6989586621679457116) '[] = '[] 

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

Equations

Zip4 a_6989586621679874109 a_6989586621679874111 a_6989586621679874113 a_6989586621679874115 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621679874109) a_6989586621679874111) a_6989586621679874113) a_6989586621679874115 

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

Equations

Zip5 a_6989586621679874064 a_6989586621679874066 a_6989586621679874068 a_6989586621679874070 a_6989586621679874072 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621679874064) a_6989586621679874066) a_6989586621679874068) a_6989586621679874070) a_6989586621679874072 

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

Equations

Zip6 a_6989586621679874007 a_6989586621679874009 a_6989586621679874011 a_6989586621679874013 a_6989586621679874015 a_6989586621679874017 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621679874007) a_6989586621679874009) a_6989586621679874011) a_6989586621679874013) a_6989586621679874015) a_6989586621679874017 

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

Equations

Zip7 a_6989586621679873937 a_6989586621679873939 a_6989586621679873941 a_6989586621679873943 a_6989586621679873945 a_6989586621679873947 a_6989586621679873949 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621679873937) a_6989586621679873939) a_6989586621679873941) a_6989586621679873943) a_6989586621679873945) a_6989586621679873947) a_6989586621679873949 

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

Equations

ZipWith f ((:) x xs) ((:) y ys) = Apply (Apply (:$) (Apply (Apply f x) y)) (Apply (Apply (Apply ZipWithSym0 f) xs) ys) 
ZipWith _z_6989586621679457023 '[] '[] = '[] 
ZipWith _z_6989586621679457026 ((:) _z_6989586621679457029 _z_6989586621679457032) '[] = '[] 
ZipWith _z_6989586621679457035 '[] ((:) _z_6989586621679457038 _z_6989586621679457041) = '[] 

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

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_6989586621679456928 '[] '[] '[] = '[] 
ZipWith3 _z_6989586621679456931 '[] '[] ((:) _z_6989586621679456934 _z_6989586621679456937) = '[] 
ZipWith3 _z_6989586621679456940 '[] ((:) _z_6989586621679456943 _z_6989586621679456946) '[] = '[] 
ZipWith3 _z_6989586621679456949 '[] ((:) _z_6989586621679456952 _z_6989586621679456955) ((:) _z_6989586621679456958 _z_6989586621679456961) = '[] 
ZipWith3 _z_6989586621679456964 ((:) _z_6989586621679456967 _z_6989586621679456970) '[] '[] = '[] 
ZipWith3 _z_6989586621679456973 ((:) _z_6989586621679456976 _z_6989586621679456979) '[] ((:) _z_6989586621679456982 _z_6989586621679456985) = '[] 
ZipWith3 _z_6989586621679456988 ((:) _z_6989586621679456991 _z_6989586621679456994) ((:) _z_6989586621679456997 _z_6989586621679457000) '[] = '[] 

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

Equations

ZipWith4 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) = Apply (Apply (:$) (Apply (Apply (Apply (Apply z a) b) c) d)) (Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 z) as) bs) cs) ds) 
ZipWith4 _z_6989586621679873922 _z_6989586621679873925 _z_6989586621679873928 _z_6989586621679873931 _z_6989586621679873934 = '[] 

type family ZipWith5 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e f -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ... Source #

Equations

ZipWith5 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) ((:) e es) = Apply (Apply (:$) (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e)) (Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 z) as) bs) cs) ds) es) 
ZipWith5 _z_6989586621679873865 _z_6989586621679873868 _z_6989586621679873871 _z_6989586621679873874 _z_6989586621679873877 _z_6989586621679873880 = '[] 

type family ZipWith6 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e (TyFun f g -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ... Source #

Equations

ZipWith6 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) ((:) e es) ((:) f fs) = Apply (Apply (:$) (Apply (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e) f)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 z) as) bs) cs) ds) es) fs) 
ZipWith6 _z_6989586621679873794 _z_6989586621679873797 _z_6989586621679873800 _z_6989586621679873803 _z_6989586621679873806 _z_6989586621679873809 _z_6989586621679873812 = '[] 

type family ZipWith7 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e (TyFun f (TyFun g h -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ... Source #

Equations

ZipWith7 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) ((:) e es) ((:) f fs) ((:) g gs) = Apply (Apply (:$) (Apply (Apply (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e) f) g)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 z) as) bs) cs) ds) es) fs) gs) 
ZipWith7 _z_6989586621679873708 _z_6989586621679873711 _z_6989586621679873714 _z_6989586621679873717 _z_6989586621679873720 _z_6989586621679873723 _z_6989586621679873726 _z_6989586621679873729 = '[] 

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

Special lists

"Set" operations

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

Equations

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

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

Equations

Delete a_6989586621679456659 a_6989586621679456661 = Apply (Apply (Apply DeleteBySym0 (:==$)) a_6989586621679456659) a_6989586621679456661 

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

Equations

a_6989586621679456674 :\\ a_6989586621679456676 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 DeleteSym0)) a_6989586621679456674) a_6989586621679456676 

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

Equations

Union a_6989586621679456644 a_6989586621679456646 = Apply (Apply (Apply UnionBySym0 (:==$)) a_6989586621679456644) a_6989586621679456646 

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

Equations

Intersect a_6989586621679456447 a_6989586621679456449 = Apply (Apply (Apply IntersectBySym0 (:==$)) a_6989586621679456447) a_6989586621679456449 

Ordered lists

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

Equations

Sort a_6989586621679456550 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679456550 

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

Equations

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

Generalized functions

The "By" operations

User-supplied equality (replacing an Eq context)

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

Equations

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

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

Equations

DeleteBy _z_6989586621679456572 _z_6989586621679456575 '[] = '[] 
DeleteBy eq x ((:) y ys) = Case_6989586621679456601 eq x y ys (Let6989586621679456582Scrutinee_6989586621679455449Sym4 eq x y ys) 

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

Equations

DeleteFirstsBy eq a_6989586621679456619 a_6989586621679456621 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679456619) a_6989586621679456621 

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

Equations

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

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

Equations

GroupBy _z_6989586621679456133 '[] = '[] 
GroupBy eq ((:) x xs) = Apply (Apply (:$) (Apply (Apply (:$) x) (Let6989586621679456139YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621679456139ZsSym3 eq x xs)) 

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

Equations

IntersectBy _z_6989586621679456333 '[] '[] = '[] 
IntersectBy _z_6989586621679456336 '[] ((:) _z_6989586621679456339 _z_6989586621679456342) = '[] 
IntersectBy _z_6989586621679456345 ((:) _z_6989586621679456348 _z_6989586621679456351) '[] = '[] 
IntersectBy eq ((:) wild_6989586621679455469 wild_6989586621679455471) ((:) wild_6989586621679455473 wild_6989586621679455475) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679456410Sym0 eq) wild_6989586621679455469) wild_6989586621679455471) wild_6989586621679455473) wild_6989586621679455475)) (Let6989586621679456359XsSym5 eq wild_6989586621679455469 wild_6989586621679455471 wild_6989586621679455473 wild_6989586621679455475) 

User-supplied comparison (replacing an Ord context)

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

Equations

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

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

Equations

InsertBy _z_6989586621679456477 x '[] = Apply (Apply (:$) x) '[] 
InsertBy cmp x ((:) y ys') = Case_6989586621679456523 cmp x y ys' (Let6989586621679456504Scrutinee_6989586621679455451Sym4 cmp x y ys') 

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

Equations

MaximumBy _z_6989586621679458008 '[] = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" 
MaximumBy cmp ((:) wild_6989586621679455455 wild_6989586621679455457) = Apply (Apply Foldl1Sym0 (Let6989586621679458027MaxBySym3 cmp wild_6989586621679455455 wild_6989586621679455457)) (Let6989586621679458014XsSym3 cmp wild_6989586621679455455 wild_6989586621679455457) 

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

Equations

MinimumBy _z_6989586621679458095 '[] = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" 
MinimumBy cmp ((:) wild_6989586621679455461 wild_6989586621679455463) = Apply (Apply Foldl1Sym0 (Let6989586621679458114MinBySym3 cmp wild_6989586621679455461 wild_6989586621679455463)) (Let6989586621679458101XsSym3 cmp wild_6989586621679455461 wild_6989586621679455463) 

The "generic" operations

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

Equations

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

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

Equations

GenericTake a_6989586621679873618 a_6989586621679873620 = Apply (Apply TakeSym0 a_6989586621679873618) a_6989586621679873620 

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

Equations

GenericDrop a_6989586621679873603 a_6989586621679873605 = Apply (Apply DropSym0 a_6989586621679873603) a_6989586621679873605 

type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ... Source #

Equations

GenericSplitAt a_6989586621679873588 a_6989586621679873590 = Apply (Apply SplitAtSym0 a_6989586621679873588) a_6989586621679873590 

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

Equations

GenericIndex a_6989586621679873573 a_6989586621679873575 = Apply (Apply (:!!$) a_6989586621679873573) a_6989586621679873575 

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

Equations

GenericReplicate a_6989586621679873558 a_6989586621679873560 = Apply (Apply ReplicateSym0 a_6989586621679873558) a_6989586621679873560 

Defunctionalization symbols

type NilSym0 = '[] Source #

data (:$) (l :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type)) Source #

Instances

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

Methods

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

type Apply a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type) ((:$) a3530822107858468865) l Source # 
type Apply a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type) ((:$) a3530822107858468865) l = (:$$) a3530822107858468865 l

data (l :: a3530822107858468865) :$$ (l :: TyFun [a3530822107858468865] [a3530822107858468865]) Source #

Instances

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

Methods

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

type Apply [a] [a] ((:$$) a l1) l2 Source # 
type Apply [a] [a] ((:$$) a l1) l2 = (:) a l1 l2

type (:$$$) (t :: a3530822107858468865) (t :: [a3530822107858468865]) = (:) t t Source #

type (:++$$$) (t :: [a6989586621679277916]) (t :: [a6989586621679277916]) = (:++) t t Source #

data (l :: [a6989586621679277916]) :++$$ (l :: TyFun [a6989586621679277916] [a6989586621679277916]) Source #

Instances

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

Methods

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

type Apply [a] [a] ((:++$$) a l1) l2 Source # 
type Apply [a] [a] ((:++$$) a l1) l2 = (:++) a l1 l2

data (:++$) (l :: TyFun [a6989586621679277916] (TyFun [a6989586621679277916] [a6989586621679277916] -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679277916] (TyFun [a6989586621679277916] [a6989586621679277916] -> Type) ((:++$) a6989586621679277916) l Source # 
type Apply [a6989586621679277916] (TyFun [a6989586621679277916] [a6989586621679277916] -> Type) ((:++$) a6989586621679277916) l = (:++$$) a6989586621679277916 l

data HeadSym0 (l :: TyFun [a6989586621679454963] a6989586621679454963) Source #

Instances

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

Methods

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

type Apply [a] a (HeadSym0 a) l Source # 
type Apply [a] a (HeadSym0 a) l = Head a l

type HeadSym1 (t :: [a6989586621679454963]) = Head t Source #

data LastSym0 (l :: TyFun [a6989586621679454962] a6989586621679454962) Source #

Instances

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

Methods

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

type Apply [a] a (LastSym0 a) l Source # 
type Apply [a] a (LastSym0 a) l = Last a l

type LastSym1 (t :: [a6989586621679454962]) = Last t Source #

data TailSym0 (l :: TyFun [a6989586621679454961] [a6989586621679454961]) Source #

Instances

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

Methods

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

type Apply [a] [a] (TailSym0 a) l Source # 
type Apply [a] [a] (TailSym0 a) l = Tail a l

type TailSym1 (t :: [a6989586621679454961]) = Tail t Source #

data InitSym0 (l :: TyFun [a6989586621679454960] [a6989586621679454960]) Source #

Instances

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

Methods

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

type Apply [a] [a] (InitSym0 a) l Source # 
type Apply [a] [a] (InitSym0 a) l = Init a l

type InitSym1 (t :: [a6989586621679454960]) = Init t Source #

data NullSym0 (l :: TyFun [a6989586621679454959] Bool) Source #

Instances

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

Methods

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

type Apply [a] Bool (NullSym0 a) l Source # 
type Apply [a] Bool (NullSym0 a) l = Null a l

type NullSym1 (t :: [a6989586621679454959]) = Null t Source #

data MapSym0 (l :: TyFun (TyFun a6989586621679277917 b6989586621679277918 -> Type) (TyFun [a6989586621679277917] [b6989586621679277918] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679277917 b6989586621679277918 -> Type) (TyFun [a6989586621679277917] [b6989586621679277918] -> Type) -> *) (MapSym0 a6989586621679277917 b6989586621679277918) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a6989586621679277917 b6989586621679277918) t -> () Source #

type Apply (TyFun a6989586621679277917 b6989586621679277918 -> Type) (TyFun [a6989586621679277917] [b6989586621679277918] -> Type) (MapSym0 a6989586621679277917 b6989586621679277918) l Source # 
type Apply (TyFun a6989586621679277917 b6989586621679277918 -> Type) (TyFun [a6989586621679277917] [b6989586621679277918] -> Type) (MapSym0 a6989586621679277917 b6989586621679277918) l = MapSym1 a6989586621679277917 b6989586621679277918 l

data MapSym1 (l :: TyFun a6989586621679277917 b6989586621679277918 -> Type) (l :: TyFun [a6989586621679277917] [b6989586621679277918]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679277917 b6989586621679277918 -> Type) -> TyFun [a6989586621679277917] [b6989586621679277918] -> *) (MapSym1 a6989586621679277917 b6989586621679277918) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a6989586621679277917 b6989586621679277918) t -> () Source #

type Apply [a] [b] (MapSym1 a b l1) l2 Source # 
type Apply [a] [b] (MapSym1 a b l1) l2 = Map a b l1 l2

type MapSym2 (t :: TyFun a6989586621679277917 b6989586621679277918 -> Type) (t :: [a6989586621679277917]) = Map t t Source #

data ReverseSym0 (l :: TyFun [a6989586621679454958] [a6989586621679454958]) Source #

Instances

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

Methods

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

type Apply [a] [a] (ReverseSym0 a) l Source # 
type Apply [a] [a] (ReverseSym0 a) l = Reverse a l

type ReverseSym1 (t :: [a6989586621679454958]) = Reverse t Source #

data IntersperseSym0 (l :: TyFun a6989586621679454957 (TyFun [a6989586621679454957] [a6989586621679454957] -> Type)) Source #

Instances

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

Methods

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

type Apply a6989586621679454957 (TyFun [a6989586621679454957] [a6989586621679454957] -> Type) (IntersperseSym0 a6989586621679454957) l Source # 
type Apply a6989586621679454957 (TyFun [a6989586621679454957] [a6989586621679454957] -> Type) (IntersperseSym0 a6989586621679454957) l = IntersperseSym1 a6989586621679454957 l

data IntersperseSym1 (l :: a6989586621679454957) (l :: TyFun [a6989586621679454957] [a6989586621679454957]) Source #

Instances

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

Methods

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

type Apply [a] [a] (IntersperseSym1 a l1) l2 Source # 
type Apply [a] [a] (IntersperseSym1 a l1) l2 = Intersperse a l1 l2

type IntersperseSym2 (t :: a6989586621679454957) (t :: [a6989586621679454957]) = Intersperse t t Source #

data IntercalateSym0 (l :: TyFun [a6989586621679454956] (TyFun [[a6989586621679454956]] [a6989586621679454956] -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679454956] (TyFun [[a6989586621679454956]] [a6989586621679454956] -> Type) (IntercalateSym0 a6989586621679454956) l Source # 
type Apply [a6989586621679454956] (TyFun [[a6989586621679454956]] [a6989586621679454956] -> Type) (IntercalateSym0 a6989586621679454956) l = IntercalateSym1 a6989586621679454956 l

data IntercalateSym1 (l :: [a6989586621679454956]) (l :: TyFun [[a6989586621679454956]] [a6989586621679454956]) Source #

Instances

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

Methods

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

type Apply [[a]] [a] (IntercalateSym1 a l1) l2 Source # 
type Apply [[a]] [a] (IntercalateSym1 a l1) l2 = Intercalate a l1 l2

type IntercalateSym2 (t :: [a6989586621679454956]) (t :: [[a6989586621679454956]]) = Intercalate t t Source #

data SubsequencesSym0 (l :: TyFun [a6989586621679454955] [[a6989586621679454955]]) Source #

Instances

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

Methods

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

type Apply [a] [[a]] (SubsequencesSym0 a) l Source # 
type Apply [a] [[a]] (SubsequencesSym0 a) l = Subsequences a l

type SubsequencesSym1 (t :: [a6989586621679454955]) = Subsequences t Source #

data PermutationsSym0 (l :: TyFun [a6989586621679454952] [[a6989586621679454952]]) Source #

Instances

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

Methods

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

type Apply [a] [[a]] (PermutationsSym0 a) l Source # 
type Apply [a] [[a]] (PermutationsSym0 a) l = Permutations a l

type PermutationsSym1 (t :: [a6989586621679454952]) = Permutations t Source #

data FoldlSym0 (l :: TyFun (TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (TyFun b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (TyFun b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679240791 b6989586621679240792) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym0 a6989586621679240791 b6989586621679240792) t -> () Source #

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

data FoldlSym1 (l :: TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (l :: TyFun b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) -> TyFun b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type) -> *) (FoldlSym1 a6989586621679240791 b6989586621679240792) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym1 a6989586621679240791 b6989586621679240792) t -> () Source #

type Apply b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type) (FoldlSym1 a6989586621679240791 b6989586621679240792 l1) l2 Source # 
type Apply b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type) (FoldlSym1 a6989586621679240791 b6989586621679240792 l1) l2 = FoldlSym2 a6989586621679240791 b6989586621679240792 l1 l2

data FoldlSym2 (l :: TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (l :: b6989586621679240792) (l :: TyFun [a6989586621679240791] b6989586621679240792) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) -> b6989586621679240792 -> TyFun [a6989586621679240791] b6989586621679240792 -> *) (FoldlSym2 a6989586621679240791 b6989586621679240792) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldlSym2 a6989586621679240791 b6989586621679240792) t -> () Source #

type Apply [a] b (FoldlSym2 a b l1 l2) l3 Source # 
type Apply [a] b (FoldlSym2 a b l1 l2) l3 = Foldl a b l1 l2 l3

type FoldlSym3 (t :: TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (t :: b6989586621679240792) (t :: [a6989586621679240791]) = Foldl t t t Source #

data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) -> Type) -> *) (Foldl'Sym0 a6989586621679454950 b6989586621679454951) Source # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym0 a6989586621679454950 b6989586621679454951) t -> () Source #

type Apply (TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) -> Type) (Foldl'Sym0 a6989586621679454950 b6989586621679454951) l Source # 
type Apply (TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) -> Type) (Foldl'Sym0 a6989586621679454950 b6989586621679454951) l = Foldl'Sym1 a6989586621679454950 b6989586621679454951 l

data Foldl'Sym1 (l :: TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (l :: TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) -> TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) -> *) (Foldl'Sym1 a6989586621679454950 b6989586621679454951) Source # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym1 a6989586621679454950 b6989586621679454951) t -> () Source #

type Apply b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) (Foldl'Sym1 a6989586621679454950 b6989586621679454951 l1) l2 Source # 
type Apply b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) (Foldl'Sym1 a6989586621679454950 b6989586621679454951 l1) l2 = Foldl'Sym2 a6989586621679454950 b6989586621679454951 l1 l2

data Foldl'Sym2 (l :: TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (l :: b6989586621679454951) (l :: TyFun [a6989586621679454950] b6989586621679454951) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) -> b6989586621679454951 -> TyFun [a6989586621679454950] b6989586621679454951 -> *) (Foldl'Sym2 a6989586621679454950 b6989586621679454951) Source # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym2 a6989586621679454950 b6989586621679454951) t -> () Source #

type Apply [a] b (Foldl'Sym2 a b l1 l2) l3 Source # 
type Apply [a] b (Foldl'Sym2 a b l1 l2) l3 = Foldl' a b l1 l2 l3

type Foldl'Sym3 (t :: TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (t :: b6989586621679454951) (t :: [a6989586621679454950]) = Foldl' t t t Source #

data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (TyFun [a6989586621679454949] a6989586621679454949 -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (TyFun [a6989586621679454949] a6989586621679454949 -> Type) (Foldl1Sym0 a6989586621679454949) l Source # 
type Apply (TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (TyFun [a6989586621679454949] a6989586621679454949 -> Type) (Foldl1Sym0 a6989586621679454949) l = Foldl1Sym1 a6989586621679454949 l

data Foldl1Sym1 (l :: TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (l :: TyFun [a6989586621679454949] a6989586621679454949) Source #

Instances

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

Methods

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

type Apply [a] a (Foldl1Sym1 a l1) l2 Source # 
type Apply [a] a (Foldl1Sym1 a l1) l2 = Foldl1 a l1 l2

type Foldl1Sym2 (t :: TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (t :: [a6989586621679454949]) = Foldl1 t t Source #

data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (TyFun [a6989586621679454948] a6989586621679454948 -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (TyFun [a6989586621679454948] a6989586621679454948 -> Type) (Foldl1'Sym0 a6989586621679454948) l Source # 
type Apply (TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (TyFun [a6989586621679454948] a6989586621679454948 -> Type) (Foldl1'Sym0 a6989586621679454948) l = Foldl1'Sym1 a6989586621679454948 l

data Foldl1'Sym1 (l :: TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (l :: TyFun [a6989586621679454948] a6989586621679454948) Source #

Instances

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

Methods

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

type Apply [a] a (Foldl1'Sym1 a l1) l2 Source # 
type Apply [a] a (Foldl1'Sym1 a l1) l2 = Foldl1' a l1 l2

type Foldl1'Sym2 (t :: TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (t :: [a6989586621679454948]) = Foldl1' t t Source #

data FoldrSym0 (l :: TyFun (TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) -> Type) -> *) (FoldrSym0 a6989586621679277919 b6989586621679277920) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym0 a6989586621679277919 b6989586621679277920) t -> () Source #

type Apply (TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) -> Type) (FoldrSym0 a6989586621679277919 b6989586621679277920) l Source # 
type Apply (TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) -> Type) (FoldrSym0 a6989586621679277919 b6989586621679277920) l = FoldrSym1 a6989586621679277919 b6989586621679277920 l

data FoldrSym1 (l :: TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (l :: TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) -> TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) -> *) (FoldrSym1 a6989586621679277919 b6989586621679277920) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym1 a6989586621679277919 b6989586621679277920) t -> () Source #

type Apply b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) (FoldrSym1 a6989586621679277919 b6989586621679277920 l1) l2 Source # 
type Apply b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) (FoldrSym1 a6989586621679277919 b6989586621679277920 l1) l2 = FoldrSym2 a6989586621679277919 b6989586621679277920 l1 l2

data FoldrSym2 (l :: TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (l :: b6989586621679277920) (l :: TyFun [a6989586621679277919] b6989586621679277920) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) -> b6989586621679277920 -> TyFun [a6989586621679277919] b6989586621679277920 -> *) (FoldrSym2 a6989586621679277919 b6989586621679277920) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym2 a6989586621679277919 b6989586621679277920) t -> () Source #

type Apply [a] b (FoldrSym2 a b l1 l2) l3 Source # 
type Apply [a] b (FoldrSym2 a b l1 l2) l3 = Foldr a b l1 l2 l3

type FoldrSym3 (t :: TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (t :: b6989586621679277920) (t :: [a6989586621679277919]) = Foldr t t t Source #

data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (TyFun [a6989586621679454947] a6989586621679454947 -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (TyFun [a6989586621679454947] a6989586621679454947 -> Type) (Foldr1Sym0 a6989586621679454947) l Source # 
type Apply (TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (TyFun [a6989586621679454947] a6989586621679454947 -> Type) (Foldr1Sym0 a6989586621679454947) l = Foldr1Sym1 a6989586621679454947 l

data Foldr1Sym1 (l :: TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (l :: TyFun [a6989586621679454947] a6989586621679454947) Source #

Instances

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

Methods

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

type Apply [a] a (Foldr1Sym1 a l1) l2 Source # 
type Apply [a] a (Foldr1Sym1 a l1) l2 = Foldr1 a l1 l2

type Foldr1Sym2 (t :: TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (t :: [a6989586621679454947]) = Foldr1 t t Source #

data ConcatSym0 (l :: TyFun [[a6989586621679454946]] [a6989586621679454946]) Source #

Instances

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

Methods

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

type Apply [[a]] [a] (ConcatSym0 a) l Source # 
type Apply [[a]] [a] (ConcatSym0 a) l = Concat a l

type ConcatSym1 (t :: [[a6989586621679454946]]) = Concat t Source #

data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679454944 [b6989586621679454945] -> Type) (TyFun [a6989586621679454944] [b6989586621679454945] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679454944 [b6989586621679454945] -> Type) (TyFun [a6989586621679454944] [b6989586621679454945] -> Type) -> *) (ConcatMapSym0 a6989586621679454944 b6989586621679454945) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym0 a6989586621679454944 b6989586621679454945) t -> () Source #

type Apply (TyFun a6989586621679454944 [b6989586621679454945] -> Type) (TyFun [a6989586621679454944] [b6989586621679454945] -> Type) (ConcatMapSym0 a6989586621679454944 b6989586621679454945) l Source # 
type Apply (TyFun a6989586621679454944 [b6989586621679454945] -> Type) (TyFun [a6989586621679454944] [b6989586621679454945] -> Type) (ConcatMapSym0 a6989586621679454944 b6989586621679454945) l = ConcatMapSym1 a6989586621679454944 b6989586621679454945 l

data ConcatMapSym1 (l :: TyFun a6989586621679454944 [b6989586621679454945] -> Type) (l :: TyFun [a6989586621679454944] [b6989586621679454945]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679454944 [b6989586621679454945] -> Type) -> TyFun [a6989586621679454944] [b6989586621679454945] -> *) (ConcatMapSym1 a6989586621679454944 b6989586621679454945) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym1 a6989586621679454944 b6989586621679454945) t -> () Source #

type Apply [a] [b] (ConcatMapSym1 a b l1) l2 Source # 
type Apply [a] [b] (ConcatMapSym1 a b l1) l2 = ConcatMap a b l1 l2

type ConcatMapSym2 (t :: TyFun a6989586621679454944 [b6989586621679454945] -> Type) (t :: [a6989586621679454944]) = ConcatMap t t Source #

type AndSym1 (t :: [Bool]) = And t Source #

type OrSym1 (t :: [Bool]) = Or t Source #

data Any_Sym0 (l :: TyFun (TyFun a6989586621679444727 Bool -> Type) (TyFun [a6989586621679444727] Bool -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679444727 Bool -> Type) (TyFun [a6989586621679444727] Bool -> Type) (Any_Sym0 a6989586621679444727) l Source # 
type Apply (TyFun a6989586621679444727 Bool -> Type) (TyFun [a6989586621679444727] Bool -> Type) (Any_Sym0 a6989586621679444727) l = Any_Sym1 a6989586621679444727 l

data Any_Sym1 (l :: TyFun a6989586621679444727 Bool -> Type) (l :: TyFun [a6989586621679444727] Bool) Source #

Instances

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

Methods

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

type Apply [a] Bool (Any_Sym1 a l1) l2 Source # 
type Apply [a] Bool (Any_Sym1 a l1) l2 = Any_ a l1 l2

type Any_Sym2 (t :: TyFun a6989586621679444727 Bool -> Type) (t :: [a6989586621679444727]) = Any_ t t Source #

data AllSym0 (l :: TyFun (TyFun a6989586621679454943 Bool -> Type) (TyFun [a6989586621679454943] Bool -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454943 Bool -> Type) (TyFun [a6989586621679454943] Bool -> Type) (AllSym0 a6989586621679454943) l Source # 
type Apply (TyFun a6989586621679454943 Bool -> Type) (TyFun [a6989586621679454943] Bool -> Type) (AllSym0 a6989586621679454943) l = AllSym1 a6989586621679454943 l

data AllSym1 (l :: TyFun a6989586621679454943 Bool -> Type) (l :: TyFun [a6989586621679454943] Bool) Source #

Instances

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

Methods

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

type Apply [a] Bool (AllSym1 a l1) l2 Source # 
type Apply [a] Bool (AllSym1 a l1) l2 = All a l1 l2

type AllSym2 (t :: TyFun a6989586621679454943 Bool -> Type) (t :: [a6989586621679454943]) = All t t Source #

data ScanlSym0 (l :: TyFun (TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) -> Type) -> *) (ScanlSym0 a6989586621679454942 b6989586621679454941) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a6989586621679454942 b6989586621679454941) t -> () Source #

type Apply (TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) -> Type) (ScanlSym0 a6989586621679454942 b6989586621679454941) l Source # 
type Apply (TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) -> Type) (ScanlSym0 a6989586621679454942 b6989586621679454941) l = ScanlSym1 a6989586621679454942 b6989586621679454941 l

data ScanlSym1 (l :: TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (l :: TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) -> TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) -> *) (ScanlSym1 a6989586621679454942 b6989586621679454941) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a6989586621679454942 b6989586621679454941) t -> () Source #

type Apply b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) (ScanlSym1 a6989586621679454942 b6989586621679454941 l1) l2 Source # 
type Apply b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) (ScanlSym1 a6989586621679454942 b6989586621679454941 l1) l2 = ScanlSym2 a6989586621679454942 b6989586621679454941 l1 l2

data ScanlSym2 (l :: TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (l :: b6989586621679454941) (l :: TyFun [a6989586621679454942] [b6989586621679454941]) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) -> b6989586621679454941 -> TyFun [a6989586621679454942] [b6989586621679454941] -> *) (ScanlSym2 a6989586621679454942 b6989586621679454941) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a6989586621679454942 b6989586621679454941) t -> () Source #

type Apply [a] [b] (ScanlSym2 a b l1 l2) l3 Source # 
type Apply [a] [b] (ScanlSym2 a b l1 l2) l3 = Scanl a b l1 l2 l3

type ScanlSym3 (t :: TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (t :: b6989586621679454941) (t :: [a6989586621679454942]) = Scanl t t t Source #

data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (TyFun [a6989586621679454940] [a6989586621679454940] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (TyFun [a6989586621679454940] [a6989586621679454940] -> Type) (Scanl1Sym0 a6989586621679454940) l Source # 
type Apply (TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (TyFun [a6989586621679454940] [a6989586621679454940] -> Type) (Scanl1Sym0 a6989586621679454940) l = Scanl1Sym1 a6989586621679454940 l

data Scanl1Sym1 (l :: TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (l :: TyFun [a6989586621679454940] [a6989586621679454940]) Source #

Instances

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

Methods

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

type Apply [a] [a] (Scanl1Sym1 a l1) l2 Source # 
type Apply [a] [a] (Scanl1Sym1 a l1) l2 = Scanl1 a l1 l2

type Scanl1Sym2 (t :: TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (t :: [a6989586621679454940]) = Scanl1 t t Source #

data ScanrSym0 (l :: TyFun (TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) -> Type) -> *) (ScanrSym0 a6989586621679454938 b6989586621679454939) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a6989586621679454938 b6989586621679454939) t -> () Source #

type Apply (TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) -> Type) (ScanrSym0 a6989586621679454938 b6989586621679454939) l Source # 
type Apply (TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) -> Type) (ScanrSym0 a6989586621679454938 b6989586621679454939) l = ScanrSym1 a6989586621679454938 b6989586621679454939 l

data ScanrSym1 (l :: TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (l :: TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) -> TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) -> *) (ScanrSym1 a6989586621679454938 b6989586621679454939) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a6989586621679454938 b6989586621679454939) t -> () Source #

type Apply b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) (ScanrSym1 a6989586621679454938 b6989586621679454939 l1) l2 Source # 
type Apply b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) (ScanrSym1 a6989586621679454938 b6989586621679454939 l1) l2 = ScanrSym2 a6989586621679454938 b6989586621679454939 l1 l2

data ScanrSym2 (l :: TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (l :: b6989586621679454939) (l :: TyFun [a6989586621679454938] [b6989586621679454939]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) -> b6989586621679454939 -> TyFun [a6989586621679454938] [b6989586621679454939] -> *) (ScanrSym2 a6989586621679454938 b6989586621679454939) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a6989586621679454938 b6989586621679454939) t -> () Source #

type Apply [a] [b] (ScanrSym2 a b l1 l2) l3 Source # 
type Apply [a] [b] (ScanrSym2 a b l1 l2) l3 = Scanr a b l1 l2 l3

type ScanrSym3 (t :: TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (t :: b6989586621679454939) (t :: [a6989586621679454938]) = Scanr t t t Source #

data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (TyFun [a6989586621679454937] [a6989586621679454937] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (TyFun [a6989586621679454937] [a6989586621679454937] -> Type) (Scanr1Sym0 a6989586621679454937) l Source # 
type Apply (TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (TyFun [a6989586621679454937] [a6989586621679454937] -> Type) (Scanr1Sym0 a6989586621679454937) l = Scanr1Sym1 a6989586621679454937 l

data Scanr1Sym1 (l :: TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (l :: TyFun [a6989586621679454937] [a6989586621679454937]) Source #

Instances

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

Methods

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

type Apply [a] [a] (Scanr1Sym1 a l1) l2 Source # 
type Apply [a] [a] (Scanr1Sym1 a l1) l2 = Scanr1 a l1 l2

type Scanr1Sym2 (t :: TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (t :: [a6989586621679454937]) = Scanr1 t t Source #

data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) -> Type) -> *) (MapAccumLSym0 x6989586621679454935 acc6989586621679454934 y6989586621679454936) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym0 x6989586621679454935 acc6989586621679454934 y6989586621679454936) t -> () Source #

type Apply (TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) -> Type) (MapAccumLSym0 x6989586621679454935 acc6989586621679454934 y6989586621679454936) l Source # 
type Apply (TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) -> Type) (MapAccumLSym0 x6989586621679454935 acc6989586621679454934 y6989586621679454936) l = MapAccumLSym1 x6989586621679454935 acc6989586621679454934 y6989586621679454936 l

data MapAccumLSym1 (l :: TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (l :: TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) -> TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) -> *) (MapAccumLSym1 x6989586621679454935 acc6989586621679454934 y6989586621679454936) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym1 x6989586621679454935 acc6989586621679454934 y6989586621679454936) t -> () Source #

type Apply acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) (MapAccumLSym1 x6989586621679454935 acc6989586621679454934 y6989586621679454936 l1) l2 Source # 
type Apply acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) (MapAccumLSym1 x6989586621679454935 acc6989586621679454934 y6989586621679454936 l1) l2 = MapAccumLSym2 x6989586621679454935 acc6989586621679454934 y6989586621679454936 l1 l2

data MapAccumLSym2 (l :: TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (l :: acc6989586621679454934) (l :: TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936])) Source #

Instances

SuppressUnusedWarnings ((TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) -> acc6989586621679454934 -> TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> *) (MapAccumLSym2 x6989586621679454935 acc6989586621679454934 y6989586621679454936) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym2 x6989586621679454935 acc6989586621679454934 y6989586621679454936) t -> () Source #

type Apply [x] (acc, [y]) (MapAccumLSym2 x acc y l1 l2) l3 Source # 
type Apply [x] (acc, [y]) (MapAccumLSym2 x acc y l1 l2) l3 = MapAccumL x acc y l1 l2 l3

type MapAccumLSym3 (t :: TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (t :: acc6989586621679454934) (t :: [x6989586621679454935]) = MapAccumL t t t Source #

data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) -> Type) -> *) (MapAccumRSym0 x6989586621679454932 acc6989586621679454931 y6989586621679454933) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym0 x6989586621679454932 acc6989586621679454931 y6989586621679454933) t -> () Source #

type Apply (TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) -> Type) (MapAccumRSym0 x6989586621679454932 acc6989586621679454931 y6989586621679454933) l Source # 
type Apply (TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) -> Type) (MapAccumRSym0 x6989586621679454932 acc6989586621679454931 y6989586621679454933) l = MapAccumRSym1 x6989586621679454932 acc6989586621679454931 y6989586621679454933 l

data MapAccumRSym1 (l :: TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (l :: TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) -> TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) -> *) (MapAccumRSym1 x6989586621679454932 acc6989586621679454931 y6989586621679454933) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym1 x6989586621679454932 acc6989586621679454931 y6989586621679454933) t -> () Source #

type Apply acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) (MapAccumRSym1 x6989586621679454932 acc6989586621679454931 y6989586621679454933 l1) l2 Source # 
type Apply acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) (MapAccumRSym1 x6989586621679454932 acc6989586621679454931 y6989586621679454933 l1) l2 = MapAccumRSym2 x6989586621679454932 acc6989586621679454931 y6989586621679454933 l1 l2

data MapAccumRSym2 (l :: TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (l :: acc6989586621679454931) (l :: TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933])) Source #

Instances

SuppressUnusedWarnings ((TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) -> acc6989586621679454931 -> TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> *) (MapAccumRSym2 x6989586621679454932 acc6989586621679454931 y6989586621679454933) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym2 x6989586621679454932 acc6989586621679454931 y6989586621679454933) t -> () Source #

type Apply [x] (acc, [y]) (MapAccumRSym2 x acc y l1 l2) l3 Source # 
type Apply [x] (acc, [y]) (MapAccumRSym2 x acc y l1 l2) l3 = MapAccumR x acc y l1 l2 l3

type MapAccumRSym3 (t :: TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (t :: acc6989586621679454931) (t :: [x6989586621679454932]) = MapAccumR t t t Source #

data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (TyFun b6989586621679454929 [a6989586621679454930] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (TyFun b6989586621679454929 [a6989586621679454930] -> Type) -> *) (UnfoldrSym0 b6989586621679454929 a6989586621679454930) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 b6989586621679454929 a6989586621679454930) t -> () Source #

type Apply (TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (TyFun b6989586621679454929 [a6989586621679454930] -> Type) (UnfoldrSym0 b6989586621679454929 a6989586621679454930) l Source # 
type Apply (TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (TyFun b6989586621679454929 [a6989586621679454930] -> Type) (UnfoldrSym0 b6989586621679454929 a6989586621679454930) l = UnfoldrSym1 b6989586621679454929 a6989586621679454930 l

data UnfoldrSym1 (l :: TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (l :: TyFun b6989586621679454929 [a6989586621679454930]) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) -> TyFun b6989586621679454929 [a6989586621679454930] -> *) (UnfoldrSym1 b6989586621679454929 a6989586621679454930) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 b6989586621679454929 a6989586621679454930) t -> () Source #

type Apply b [a] (UnfoldrSym1 b a l1) l2 Source # 
type Apply b [a] (UnfoldrSym1 b a l1) l2 = Unfoldr b a l1 l2

type UnfoldrSym2 (t :: TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (t :: b6989586621679454929) = Unfoldr t t Source #

data InitsSym0 (l :: TyFun [a6989586621679454928] [[a6989586621679454928]]) Source #

Instances

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

Methods

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

type Apply [a] [[a]] (InitsSym0 a) l Source # 
type Apply [a] [[a]] (InitsSym0 a) l = Inits a l

type InitsSym1 (t :: [a6989586621679454928]) = Inits t Source #

data TailsSym0 (l :: TyFun [a6989586621679454927] [[a6989586621679454927]]) Source #

Instances

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

Methods

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

type Apply [a] [[a]] (TailsSym0 a) l Source # 
type Apply [a] [[a]] (TailsSym0 a) l = Tails a l

type TailsSym1 (t :: [a6989586621679454927]) = Tails t Source #

data IsPrefixOfSym0 (l :: TyFun [a6989586621679454926] (TyFun [a6989586621679454926] Bool -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679454926] (TyFun [a6989586621679454926] Bool -> Type) (IsPrefixOfSym0 a6989586621679454926) l Source # 
type Apply [a6989586621679454926] (TyFun [a6989586621679454926] Bool -> Type) (IsPrefixOfSym0 a6989586621679454926) l = IsPrefixOfSym1 a6989586621679454926 l

data IsPrefixOfSym1 (l :: [a6989586621679454926]) (l :: TyFun [a6989586621679454926] Bool) Source #

Instances

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

Methods

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

type Apply [a] Bool (IsPrefixOfSym1 a l1) l2 Source # 
type Apply [a] Bool (IsPrefixOfSym1 a l1) l2 = IsPrefixOf a l1 l2

type IsPrefixOfSym2 (t :: [a6989586621679454926]) (t :: [a6989586621679454926]) = IsPrefixOf t t Source #

data IsSuffixOfSym0 (l :: TyFun [a6989586621679454925] (TyFun [a6989586621679454925] Bool -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679454925] (TyFun [a6989586621679454925] Bool -> Type) (IsSuffixOfSym0 a6989586621679454925) l Source # 
type Apply [a6989586621679454925] (TyFun [a6989586621679454925] Bool -> Type) (IsSuffixOfSym0 a6989586621679454925) l = IsSuffixOfSym1 a6989586621679454925 l

data IsSuffixOfSym1 (l :: [a6989586621679454925]) (l :: TyFun [a6989586621679454925] Bool) Source #

Instances

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

Methods

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

type Apply [a] Bool (IsSuffixOfSym1 a l1) l2 Source # 
type Apply [a] Bool (IsSuffixOfSym1 a l1) l2 = IsSuffixOf a l1 l2

type IsSuffixOfSym2 (t :: [a6989586621679454925]) (t :: [a6989586621679454925]) = IsSuffixOf t t Source #

data IsInfixOfSym0 (l :: TyFun [a6989586621679454924] (TyFun [a6989586621679454924] Bool -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679454924] (TyFun [a6989586621679454924] Bool -> Type) (IsInfixOfSym0 a6989586621679454924) l Source # 
type Apply [a6989586621679454924] (TyFun [a6989586621679454924] Bool -> Type) (IsInfixOfSym0 a6989586621679454924) l = IsInfixOfSym1 a6989586621679454924 l

data IsInfixOfSym1 (l :: [a6989586621679454924]) (l :: TyFun [a6989586621679454924] Bool) Source #

Instances

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

Methods

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

type Apply [a] Bool (IsInfixOfSym1 a l1) l2 Source # 
type Apply [a] Bool (IsInfixOfSym1 a l1) l2 = IsInfixOf a l1 l2

type IsInfixOfSym2 (t :: [a6989586621679454924]) (t :: [a6989586621679454924]) = IsInfixOf t t Source #

data ElemSym0 (l :: TyFun a6989586621679454923 (TyFun [a6989586621679454923] Bool -> Type)) Source #

Instances

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

Methods

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

type Apply a6989586621679454923 (TyFun [a6989586621679454923] Bool -> Type) (ElemSym0 a6989586621679454923) l Source # 
type Apply a6989586621679454923 (TyFun [a6989586621679454923] Bool -> Type) (ElemSym0 a6989586621679454923) l = ElemSym1 a6989586621679454923 l

data ElemSym1 (l :: a6989586621679454923) (l :: TyFun [a6989586621679454923] Bool) Source #

Instances

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

Methods

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

type Apply [a] Bool (ElemSym1 a l1) l2 Source # 
type Apply [a] Bool (ElemSym1 a l1) l2 = Elem a l1 l2

type ElemSym2 (t :: a6989586621679454923) (t :: [a6989586621679454923]) = Elem t t Source #

data NotElemSym0 (l :: TyFun a6989586621679454922 (TyFun [a6989586621679454922] Bool -> Type)) Source #

Instances

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

Methods

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

type Apply a6989586621679454922 (TyFun [a6989586621679454922] Bool -> Type) (NotElemSym0 a6989586621679454922) l Source # 
type Apply a6989586621679454922 (TyFun [a6989586621679454922] Bool -> Type) (NotElemSym0 a6989586621679454922) l = NotElemSym1 a6989586621679454922 l

data NotElemSym1 (l :: a6989586621679454922) (l :: TyFun [a6989586621679454922] Bool) Source #

Instances

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

Methods

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

type Apply [a] Bool (NotElemSym1 a l1) l2 Source # 
type Apply [a] Bool (NotElemSym1 a l1) l2 = NotElem a l1 l2

type NotElemSym2 (t :: a6989586621679454922) (t :: [a6989586621679454922]) = NotElem t t Source #

data ZipSym0 (l :: TyFun [a6989586621679454920] (TyFun [b6989586621679454921] [(a6989586621679454920, b6989586621679454921)] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679454920] (TyFun [b6989586621679454921] [(a6989586621679454920, b6989586621679454921)] -> Type) -> *) (ZipSym0 a6989586621679454920 b6989586621679454921) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a6989586621679454920 b6989586621679454921) t -> () Source #

type Apply [a6989586621679454920] (TyFun [b6989586621679454921] [(a6989586621679454920, b6989586621679454921)] -> Type) (ZipSym0 a6989586621679454920 b6989586621679454921) l Source # 
type Apply [a6989586621679454920] (TyFun [b6989586621679454921] [(a6989586621679454920, b6989586621679454921)] -> Type) (ZipSym0 a6989586621679454920 b6989586621679454921) l = ZipSym1 a6989586621679454920 b6989586621679454921 l

data ZipSym1 (l :: [a6989586621679454920]) (l :: TyFun [b6989586621679454921] [(a6989586621679454920, b6989586621679454921)]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679454920] -> TyFun [b6989586621679454921] [(a6989586621679454920, b6989586621679454921)] -> *) (ZipSym1 a6989586621679454920 b6989586621679454921) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 a6989586621679454920 b6989586621679454921) t -> () Source #

type Apply [b] [(a, b)] (ZipSym1 a b l1) l2 Source # 
type Apply [b] [(a, b)] (ZipSym1 a b l1) l2 = Zip a b l1 l2

type ZipSym2 (t :: [a6989586621679454920]) (t :: [b6989586621679454921]) = Zip t t Source #

data Zip3Sym0 (l :: TyFun [a6989586621679454917] (TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679454917] (TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) -> Type) -> *) (Zip3Sym0 a6989586621679454917 b6989586621679454918 c6989586621679454919) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym0 a6989586621679454917 b6989586621679454918 c6989586621679454919) t -> () Source #

type Apply [a6989586621679454917] (TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) -> Type) (Zip3Sym0 a6989586621679454917 b6989586621679454918 c6989586621679454919) l Source # 
type Apply [a6989586621679454917] (TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) -> Type) (Zip3Sym0 a6989586621679454917 b6989586621679454918 c6989586621679454919) l = Zip3Sym1 a6989586621679454917 b6989586621679454918 c6989586621679454919 l

data Zip3Sym1 (l :: [a6989586621679454917]) (l :: TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679454917] -> TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) -> *) (Zip3Sym1 a6989586621679454917 b6989586621679454918 c6989586621679454919) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym1 a6989586621679454917 b6989586621679454918 c6989586621679454919) t -> () Source #

type Apply [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) (Zip3Sym1 a6989586621679454917 b6989586621679454918 c6989586621679454919 l1) l2 Source # 
type Apply [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) (Zip3Sym1 a6989586621679454917 b6989586621679454918 c6989586621679454919 l1) l2 = Zip3Sym2 a6989586621679454917 b6989586621679454918 c6989586621679454919 l1 l2

data Zip3Sym2 (l :: [a6989586621679454917]) (l :: [b6989586621679454918]) (l :: TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679454917] -> [b6989586621679454918] -> TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> *) (Zip3Sym2 a6989586621679454917 b6989586621679454918 c6989586621679454919) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym2 a6989586621679454917 b6989586621679454918 c6989586621679454919) t -> () Source #

type Apply [c] [(a, b, c)] (Zip3Sym2 a b c l1 l2) l3 Source # 
type Apply [c] [(a, b, c)] (Zip3Sym2 a b c l1 l2) l3 = Zip3 a b c l1 l2 l3

type Zip3Sym3 (t :: [a6989586621679454917]) (t :: [b6989586621679454918]) (t :: [c6989586621679454919]) = Zip3 t t t Source #

data ZipWithSym0 (l :: TyFun (TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679454914 b6989586621679454915 c6989586621679454916) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a6989586621679454914 b6989586621679454915 c6989586621679454916) t -> () Source #

type Apply (TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) -> Type) (ZipWithSym0 a6989586621679454914 b6989586621679454915 c6989586621679454916) l Source # 
type Apply (TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) -> Type) (ZipWithSym0 a6989586621679454914 b6989586621679454915 c6989586621679454916) l = ZipWithSym1 a6989586621679454914 b6989586621679454915 c6989586621679454916 l

data ZipWithSym1 (l :: TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (l :: TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) -> TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) -> *) (ZipWithSym1 a6989586621679454914 b6989586621679454915 c6989586621679454916) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a6989586621679454914 b6989586621679454915 c6989586621679454916) t -> () Source #

type Apply [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) (ZipWithSym1 a6989586621679454914 b6989586621679454915 c6989586621679454916 l1) l2 Source # 
type Apply [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) (ZipWithSym1 a6989586621679454914 b6989586621679454915 c6989586621679454916 l1) l2 = ZipWithSym2 a6989586621679454914 b6989586621679454915 c6989586621679454916 l1 l2

data ZipWithSym2 (l :: TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (l :: [a6989586621679454914]) (l :: TyFun [b6989586621679454915] [c6989586621679454916]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) -> [a6989586621679454914] -> TyFun [b6989586621679454915] [c6989586621679454916] -> *) (ZipWithSym2 a6989586621679454914 b6989586621679454915 c6989586621679454916) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a6989586621679454914 b6989586621679454915 c6989586621679454916) t -> () Source #

type Apply [b] [c] (ZipWithSym2 a b c l1 l2) l3 Source # 
type Apply [b] [c] (ZipWithSym2 a b c l1 l2) l3 = ZipWith a b c l1 l2 l3

type ZipWithSym3 (t :: TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (t :: [a6989586621679454914]) (t :: [b6989586621679454915]) = ZipWith t t t Source #

data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym0 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) t -> () Source #

type Apply (TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) -> Type) (ZipWith3Sym0 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) l Source # 
type Apply (TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) -> Type) (ZipWith3Sym0 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) l = ZipWith3Sym1 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913 l

data ZipWith3Sym1 (l :: TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) -> TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) -> *) (ZipWith3Sym1 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym1 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) t -> () Source #

type Apply [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) (ZipWith3Sym1 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913 l1) l2 Source # 
type Apply [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) (ZipWith3Sym1 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913 l1) l2 = ZipWith3Sym2 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913 l1 l2

data ZipWith3Sym2 (l :: TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (l :: [a6989586621679454910]) (l :: TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) -> [a6989586621679454910] -> TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> *) (ZipWith3Sym2 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym2 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) t -> () Source #

type Apply [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) (ZipWith3Sym2 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913 l1 l2) l3 Source # 
type Apply [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) (ZipWith3Sym2 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913 l1 l2) l3 = ZipWith3Sym3 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913 l1 l2 l3

data ZipWith3Sym3 (l :: TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (l :: [a6989586621679454910]) (l :: [b6989586621679454911]) (l :: TyFun [c6989586621679454912] [d6989586621679454913]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) -> [a6989586621679454910] -> [b6989586621679454911] -> TyFun [c6989586621679454912] [d6989586621679454913] -> *) (ZipWith3Sym3 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym3 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) t -> () Source #

type Apply [c] [d] (ZipWith3Sym3 a b c d l1 l2 l3) l4 Source # 
type Apply [c] [d] (ZipWith3Sym3 a b c d l1 l2 l3) l4 = ZipWith3 a b c d l1 l2 l3 l4

type ZipWith3Sym4 (t :: TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (t :: [a6989586621679454910]) (t :: [b6989586621679454911]) (t :: [c6989586621679454912]) = ZipWith3 t t t t Source #

data UnzipSym0 (l :: TyFun [(a6989586621679454908, b6989586621679454909)] ([a6989586621679454908], [b6989586621679454909])) Source #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679454908, b6989586621679454909)] ([a6989586621679454908], [b6989586621679454909]) -> *) (UnzipSym0 a6989586621679454908 b6989586621679454909) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a6989586621679454908 b6989586621679454909) t -> () Source #

type Apply [(a, b)] ([a], [b]) (UnzipSym0 a b) l Source # 
type Apply [(a, b)] ([a], [b]) (UnzipSym0 a b) l = Unzip a b l

type UnzipSym1 (t :: [(a6989586621679454908, b6989586621679454909)]) = Unzip t Source #

data Unzip3Sym0 (l :: TyFun [(a6989586621679454905, b6989586621679454906, c6989586621679454907)] ([a6989586621679454905], [b6989586621679454906], [c6989586621679454907])) Source #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679454905, b6989586621679454906, c6989586621679454907)] ([a6989586621679454905], [b6989586621679454906], [c6989586621679454907]) -> *) (Unzip3Sym0 a6989586621679454905 b6989586621679454906 c6989586621679454907) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip3Sym0 a6989586621679454905 b6989586621679454906 c6989586621679454907) t -> () Source #

type Apply [(a, b, c)] ([a], [b], [c]) (Unzip3Sym0 a b c) l Source # 
type Apply [(a, b, c)] ([a], [b], [c]) (Unzip3Sym0 a b c) l = Unzip3 a b c l

type Unzip3Sym1 (t :: [(a6989586621679454905, b6989586621679454906, c6989586621679454907)]) = Unzip3 t Source #

data Unzip4Sym0 (l :: TyFun [(a6989586621679454901, b6989586621679454902, c6989586621679454903, d6989586621679454904)] ([a6989586621679454901], [b6989586621679454902], [c6989586621679454903], [d6989586621679454904])) Source #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679454901, b6989586621679454902, c6989586621679454903, d6989586621679454904)] ([a6989586621679454901], [b6989586621679454902], [c6989586621679454903], [d6989586621679454904]) -> *) (Unzip4Sym0 a6989586621679454901 b6989586621679454902 c6989586621679454903 d6989586621679454904) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip4Sym0 a6989586621679454901 b6989586621679454902 c6989586621679454903 d6989586621679454904) t -> () Source #

type Apply [(a, b, c, d)] ([a], [b], [c], [d]) (Unzip4Sym0 a b c d) l Source # 
type Apply [(a, b, c, d)] ([a], [b], [c], [d]) (Unzip4Sym0 a b c d) l = Unzip4 a b c d l

type Unzip4Sym1 (t :: [(a6989586621679454901, b6989586621679454902, c6989586621679454903, d6989586621679454904)]) = Unzip4 t Source #

data Unzip5Sym0 (l :: TyFun [(a6989586621679454896, b6989586621679454897, c6989586621679454898, d6989586621679454899, e6989586621679454900)] ([a6989586621679454896], [b6989586621679454897], [c6989586621679454898], [d6989586621679454899], [e6989586621679454900])) Source #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679454896, b6989586621679454897, c6989586621679454898, d6989586621679454899, e6989586621679454900)] ([a6989586621679454896], [b6989586621679454897], [c6989586621679454898], [d6989586621679454899], [e6989586621679454900]) -> *) (Unzip5Sym0 a6989586621679454896 b6989586621679454897 c6989586621679454898 d6989586621679454899 e6989586621679454900) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip5Sym0 a6989586621679454896 b6989586621679454897 c6989586621679454898 d6989586621679454899 e6989586621679454900) t -> () Source #

type Apply [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) (Unzip5Sym0 a b c d e) l Source # 
type Apply [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) (Unzip5Sym0 a b c d e) l = Unzip5 a b c d e l

type Unzip5Sym1 (t :: [(a6989586621679454896, b6989586621679454897, c6989586621679454898, d6989586621679454899, e6989586621679454900)]) = Unzip5 t Source #

data Unzip6Sym0 (l :: TyFun [(a6989586621679454890, b6989586621679454891, c6989586621679454892, d6989586621679454893, e6989586621679454894, f6989586621679454895)] ([a6989586621679454890], [b6989586621679454891], [c6989586621679454892], [d6989586621679454893], [e6989586621679454894], [f6989586621679454895])) Source #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679454890, b6989586621679454891, c6989586621679454892, d6989586621679454893, e6989586621679454894, f6989586621679454895)] ([a6989586621679454890], [b6989586621679454891], [c6989586621679454892], [d6989586621679454893], [e6989586621679454894], [f6989586621679454895]) -> *) (Unzip6Sym0 a6989586621679454890 b6989586621679454891 c6989586621679454892 d6989586621679454893 e6989586621679454894 f6989586621679454895) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip6Sym0 a6989586621679454890 b6989586621679454891 c6989586621679454892 d6989586621679454893 e6989586621679454894 f6989586621679454895) t -> () Source #

type Apply [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) (Unzip6Sym0 a b c d e f) l Source # 
type Apply [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) (Unzip6Sym0 a b c d e f) l = Unzip6 a b c d e f l

type Unzip6Sym1 (t :: [(a6989586621679454890, b6989586621679454891, c6989586621679454892, d6989586621679454893, e6989586621679454894, f6989586621679454895)]) = Unzip6 t Source #

data Unzip7Sym0 (l :: TyFun [(a6989586621679454883, b6989586621679454884, c6989586621679454885, d6989586621679454886, e6989586621679454887, f6989586621679454888, g6989586621679454889)] ([a6989586621679454883], [b6989586621679454884], [c6989586621679454885], [d6989586621679454886], [e6989586621679454887], [f6989586621679454888], [g6989586621679454889])) Source #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679454883, b6989586621679454884, c6989586621679454885, d6989586621679454886, e6989586621679454887, f6989586621679454888, g6989586621679454889)] ([a6989586621679454883], [b6989586621679454884], [c6989586621679454885], [d6989586621679454886], [e6989586621679454887], [f6989586621679454888], [g6989586621679454889]) -> *) (Unzip7Sym0 a6989586621679454883 b6989586621679454884 c6989586621679454885 d6989586621679454886 e6989586621679454887 f6989586621679454888 g6989586621679454889) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip7Sym0 a6989586621679454883 b6989586621679454884 c6989586621679454885 d6989586621679454886 e6989586621679454887 f6989586621679454888 g6989586621679454889) t -> () Source #

type Apply [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) (Unzip7Sym0 a b c d e f g) l Source # 
type Apply [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) (Unzip7Sym0 a b c d e f g) l = Unzip7 a b c d e f g l

type Unzip7Sym1 (t :: [(a6989586621679454883, b6989586621679454884, c6989586621679454885, d6989586621679454886, e6989586621679454887, f6989586621679454888, g6989586621679454889)]) = Unzip7 t Source #

data DeleteSym0 (l :: TyFun a6989586621679454882 (TyFun [a6989586621679454882] [a6989586621679454882] -> Type)) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DeleteSym0 a6989586621679454882) t -> () Source #

type Apply a6989586621679454882 (TyFun [a6989586621679454882] [a6989586621679454882] -> Type) (DeleteSym0 a6989586621679454882) l Source # 
type Apply a6989586621679454882 (TyFun [a6989586621679454882] [a6989586621679454882] -> Type) (DeleteSym0 a6989586621679454882) l = DeleteSym1 a6989586621679454882 l

data DeleteSym1 (l :: a6989586621679454882) (l :: TyFun [a6989586621679454882] [a6989586621679454882]) Source #

Instances

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

Methods

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

type Apply [a] [a] (DeleteSym1 a l1) l2 Source # 
type Apply [a] [a] (DeleteSym1 a l1) l2 = Delete a l1 l2

type DeleteSym2 (t :: a6989586621679454882) (t :: [a6989586621679454882]) = Delete t t Source #

data (:\\$) (l :: TyFun [a6989586621679454881] (TyFun [a6989586621679454881] [a6989586621679454881] -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679454881] (TyFun [a6989586621679454881] [a6989586621679454881] -> Type) ((:\\$) a6989586621679454881) l Source # 
type Apply [a6989586621679454881] (TyFun [a6989586621679454881] [a6989586621679454881] -> Type) ((:\\$) a6989586621679454881) l = (:\\$$) a6989586621679454881 l

data (l :: [a6989586621679454881]) :\\$$ (l :: TyFun [a6989586621679454881] [a6989586621679454881]) Source #

Instances

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

Methods

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

type Apply [a] [a] ((:\\$$) a l1) l2 Source # 
type Apply [a] [a] ((:\\$$) a l1) l2 = (:\\) a l1 l2

type (:\\$$$) (t :: [a6989586621679454881]) (t :: [a6989586621679454881]) = (:\\) t t Source #

data IntersectSym0 (l :: TyFun [a6989586621679454868] (TyFun [a6989586621679454868] [a6989586621679454868] -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679454868] (TyFun [a6989586621679454868] [a6989586621679454868] -> Type) (IntersectSym0 a6989586621679454868) l Source # 
type Apply [a6989586621679454868] (TyFun [a6989586621679454868] [a6989586621679454868] -> Type) (IntersectSym0 a6989586621679454868) l = IntersectSym1 a6989586621679454868 l

data IntersectSym1 (l :: [a6989586621679454868]) (l :: TyFun [a6989586621679454868] [a6989586621679454868]) Source #

Instances

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

Methods

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

type Apply [a] [a] (IntersectSym1 a l1) l2 Source # 
type Apply [a] [a] (IntersectSym1 a l1) l2 = Intersect a l1 l2

type IntersectSym2 (t :: [a6989586621679454868]) (t :: [a6989586621679454868]) = Intersect t t Source #

data InsertSym0 (l :: TyFun a6989586621679454855 (TyFun [a6989586621679454855] [a6989586621679454855] -> Type)) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (InsertSym0 a6989586621679454855) t -> () Source #

type Apply a6989586621679454855 (TyFun [a6989586621679454855] [a6989586621679454855] -> Type) (InsertSym0 a6989586621679454855) l Source # 
type Apply a6989586621679454855 (TyFun [a6989586621679454855] [a6989586621679454855] -> Type) (InsertSym0 a6989586621679454855) l = InsertSym1 a6989586621679454855 l

data InsertSym1 (l :: a6989586621679454855) (l :: TyFun [a6989586621679454855] [a6989586621679454855]) Source #

Instances

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

Methods

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

type Apply [a] [a] (InsertSym1 a l1) l2 Source # 
type Apply [a] [a] (InsertSym1 a l1) l2 = Insert a l1 l2

type InsertSym2 (t :: a6989586621679454855) (t :: [a6989586621679454855]) = Insert t t Source #

data SortSym0 (l :: TyFun [a6989586621679454854] [a6989586621679454854]) Source #

Instances

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

Methods

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

type Apply [a] [a] (SortSym0 a) l Source # 
type Apply [a] [a] (SortSym0 a) l = Sort a l

type SortSym1 (t :: [a6989586621679454854]) = Sort t Source #

data DeleteBySym0 (l :: TyFun (TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (TyFun a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (TyFun a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type) -> Type) (DeleteBySym0 a6989586621679454880) l Source # 
type Apply (TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (TyFun a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type) -> Type) (DeleteBySym0 a6989586621679454880) l = DeleteBySym1 a6989586621679454880 l

data DeleteBySym1 (l :: TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (l :: TyFun a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type)) Source #

Instances

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

Methods

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

type Apply a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type) (DeleteBySym1 a6989586621679454880 l1) l2 Source # 
type Apply a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type) (DeleteBySym1 a6989586621679454880 l1) l2 = DeleteBySym2 a6989586621679454880 l1 l2

data DeleteBySym2 (l :: TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (l :: a6989586621679454880) (l :: TyFun [a6989586621679454880] [a6989586621679454880]) Source #

Instances

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

Methods

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

type Apply [a] [a] (DeleteBySym2 a l1 l2) l3 Source # 
type Apply [a] [a] (DeleteBySym2 a l1 l2) l3 = DeleteBy a l1 l2 l3

type DeleteBySym3 (t :: TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (t :: a6989586621679454880) (t :: [a6989586621679454880]) = DeleteBy t t t Source #

data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (TyFun [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (TyFun [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type) -> Type) (DeleteFirstsBySym0 a6989586621679454879) l Source # 
type Apply (TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (TyFun [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type) -> Type) (DeleteFirstsBySym0 a6989586621679454879) l = DeleteFirstsBySym1 a6989586621679454879 l

data DeleteFirstsBySym1 (l :: TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type) (DeleteFirstsBySym1 a6989586621679454879 l1) l2 Source # 
type Apply [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type) (DeleteFirstsBySym1 a6989586621679454879 l1) l2 = DeleteFirstsBySym2 a6989586621679454879 l1 l2

data DeleteFirstsBySym2 (l :: TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (l :: [a6989586621679454879]) (l :: TyFun [a6989586621679454879] [a6989586621679454879]) Source #

Instances

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

Methods

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

type Apply [a] [a] (DeleteFirstsBySym2 a l1 l2) l3 Source # 
type Apply [a] [a] (DeleteFirstsBySym2 a l1 l2) l3 = DeleteFirstsBy a l1 l2 l3

type DeleteFirstsBySym3 (t :: TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (t :: [a6989586621679454879]) (t :: [a6989586621679454879]) = DeleteFirstsBy t t t Source #

data IntersectBySym0 (l :: TyFun (TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (TyFun [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (TyFun [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type) -> Type) (IntersectBySym0 a6989586621679454867) l Source # 
type Apply (TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (TyFun [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type) -> Type) (IntersectBySym0 a6989586621679454867) l = IntersectBySym1 a6989586621679454867 l

data IntersectBySym1 (l :: TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type) (IntersectBySym1 a6989586621679454867 l1) l2 Source # 
type Apply [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type) (IntersectBySym1 a6989586621679454867 l1) l2 = IntersectBySym2 a6989586621679454867 l1 l2

data IntersectBySym2 (l :: TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (l :: [a6989586621679454867]) (l :: TyFun [a6989586621679454867] [a6989586621679454867]) Source #

Instances

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

Methods

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

type Apply [a] [a] (IntersectBySym2 a l1 l2) l3 Source # 
type Apply [a] [a] (IntersectBySym2 a l1 l2) l3 = IntersectBy a l1 l2 l3

data SortBySym0 (l :: TyFun (TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (TyFun [a6989586621679454878] [a6989586621679454878] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (TyFun [a6989586621679454878] [a6989586621679454878] -> Type) (SortBySym0 a6989586621679454878) l Source # 
type Apply (TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (TyFun [a6989586621679454878] [a6989586621679454878] -> Type) (SortBySym0 a6989586621679454878) l = SortBySym1 a6989586621679454878 l

data SortBySym1 (l :: TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679454878] [a6989586621679454878]) Source #

Instances

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

Methods

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

type Apply [a] [a] (SortBySym1 a l1) l2 Source # 
type Apply [a] [a] (SortBySym1 a l1) l2 = SortBy a l1 l2

type SortBySym2 (t :: TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (t :: [a6989586621679454878]) = SortBy t t Source #

data InsertBySym0 (l :: TyFun (TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (TyFun a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (TyFun a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type) -> Type) (InsertBySym0 a6989586621679454877) l Source # 
type Apply (TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (TyFun a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type) -> Type) (InsertBySym0 a6989586621679454877) l = InsertBySym1 a6989586621679454877 l

data InsertBySym1 (l :: TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (l :: TyFun a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type)) Source #

Instances

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

Methods

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

type Apply a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type) (InsertBySym1 a6989586621679454877 l1) l2 Source # 
type Apply a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type) (InsertBySym1 a6989586621679454877 l1) l2 = InsertBySym2 a6989586621679454877 l1 l2

data InsertBySym2 (l :: TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (l :: a6989586621679454877) (l :: TyFun [a6989586621679454877] [a6989586621679454877]) Source #

Instances

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

Methods

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

type Apply [a] [a] (InsertBySym2 a l1 l2) l3 Source # 
type Apply [a] [a] (InsertBySym2 a l1 l2) l3 = InsertBy a l1 l2 l3

type InsertBySym3 (t :: TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (t :: a6989586621679454877) (t :: [a6989586621679454877]) = InsertBy t t t Source #

data MaximumBySym0 (l :: TyFun (TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (TyFun [a6989586621679454876] a6989586621679454876 -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (TyFun [a6989586621679454876] a6989586621679454876 -> Type) (MaximumBySym0 a6989586621679454876) l Source # 
type Apply (TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (TyFun [a6989586621679454876] a6989586621679454876 -> Type) (MaximumBySym0 a6989586621679454876) l = MaximumBySym1 a6989586621679454876 l

data MaximumBySym1 (l :: TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679454876] a6989586621679454876) Source #

Instances

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

Methods

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

type Apply [a] a (MaximumBySym1 a l1) l2 Source # 
type Apply [a] a (MaximumBySym1 a l1) l2 = MaximumBy a l1 l2

type MaximumBySym2 (t :: TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (t :: [a6989586621679454876]) = MaximumBy t t Source #

data MinimumBySym0 (l :: TyFun (TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (TyFun [a6989586621679454875] a6989586621679454875 -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (TyFun [a6989586621679454875] a6989586621679454875 -> Type) (MinimumBySym0 a6989586621679454875) l Source # 
type Apply (TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (TyFun [a6989586621679454875] a6989586621679454875 -> Type) (MinimumBySym0 a6989586621679454875) l = MinimumBySym1 a6989586621679454875 l

data MinimumBySym1 (l :: TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679454875] a6989586621679454875) Source #

Instances

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

Methods

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

type Apply [a] a (MinimumBySym1 a l1) l2 Source # 
type Apply [a] a (MinimumBySym1 a l1) l2 = MinimumBy a l1 l2

type MinimumBySym2 (t :: TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (t :: [a6989586621679454875]) = MinimumBy t t Source #

data LengthSym0 (l :: TyFun [a6989586621679454846] Nat) Source #

Instances

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

Methods

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

type Apply [a] Nat (LengthSym0 a) l Source # 
type Apply [a] Nat (LengthSym0 a) l = Length a l

type LengthSym1 (t :: [a6989586621679454846]) = Length t Source #

data SumSym0 (l :: TyFun [a6989586621679454848] a6989586621679454848) Source #

Instances

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

Methods

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

type Apply [a] a (SumSym0 a) l Source # 
type Apply [a] a (SumSym0 a) l = Sum a l

type SumSym1 (t :: [a6989586621679454848]) = Sum t Source #

data ProductSym0 (l :: TyFun [a6989586621679454847] a6989586621679454847) Source #

Instances

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

Methods

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

type Apply [a] a (ProductSym0 a) l Source # 
type Apply [a] a (ProductSym0 a) l = Product a l

type ProductSym1 (t :: [a6989586621679454847]) = Product t Source #

data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679454845 [a6989586621679454845] -> Type)) Source #

Instances

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

Methods

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

type Apply Nat (TyFun a6989586621679454845 [a6989586621679454845] -> Type) (ReplicateSym0 a6989586621679454845) l Source # 
type Apply Nat (TyFun a6989586621679454845 [a6989586621679454845] -> Type) (ReplicateSym0 a6989586621679454845) l = ReplicateSym1 a6989586621679454845 l

data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679454845 [a6989586621679454845]) Source #

Instances

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

Methods

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

type Apply a [a] (ReplicateSym1 a l1) l2 Source # 
type Apply a [a] (ReplicateSym1 a l1) l2 = Replicate a l1 l2

type ReplicateSym2 (t :: Nat) (t :: a6989586621679454845) = Replicate t t Source #

data TransposeSym0 (l :: TyFun [[a6989586621679454844]] [[a6989586621679454844]]) Source #

Instances

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

Methods

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

type Apply [[a]] [[a]] (TransposeSym0 a) l Source # 
type Apply [[a]] [[a]] (TransposeSym0 a) l = Transpose a l

type TransposeSym1 (t :: [[a6989586621679454844]]) = Transpose t Source #

data TakeSym0 (l :: TyFun Nat (TyFun [a6989586621679454861] [a6989586621679454861] -> Type)) Source #

Instances

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

Methods

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

type Apply Nat (TyFun [a6989586621679454861] [a6989586621679454861] -> Type) (TakeSym0 a6989586621679454861) l Source # 
type Apply Nat (TyFun [a6989586621679454861] [a6989586621679454861] -> Type) (TakeSym0 a6989586621679454861) l = TakeSym1 a6989586621679454861 l

data TakeSym1 (l :: Nat) (l :: TyFun [a6989586621679454861] [a6989586621679454861]) Source #

Instances

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

Methods

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

type Apply [a] [a] (TakeSym1 a l1) l2 Source # 
type Apply [a] [a] (TakeSym1 a l1) l2 = Take a l1 l2

type TakeSym2 (t :: Nat) (t :: [a6989586621679454861]) = Take t t Source #

data DropSym0 (l :: TyFun Nat (TyFun [a6989586621679454860] [a6989586621679454860] -> Type)) Source #

Instances

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

Methods

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

type Apply Nat (TyFun [a6989586621679454860] [a6989586621679454860] -> Type) (DropSym0 a6989586621679454860) l Source # 
type Apply Nat (TyFun [a6989586621679454860] [a6989586621679454860] -> Type) (DropSym0 a6989586621679454860) l = DropSym1 a6989586621679454860 l

data DropSym1 (l :: Nat) (l :: TyFun [a6989586621679454860] [a6989586621679454860]) Source #

Instances

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

Methods

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

type Apply [a] [a] (DropSym1 a l1) l2 Source # 
type Apply [a] [a] (DropSym1 a l1) l2 = Drop a l1 l2

type DropSym2 (t :: Nat) (t :: [a6989586621679454860]) = Drop t t Source #

data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679454859] ([a6989586621679454859], [a6989586621679454859]) -> Type)) Source #

Instances

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

Methods

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

type Apply Nat (TyFun [a6989586621679454859] ([a6989586621679454859], [a6989586621679454859]) -> Type) (SplitAtSym0 a6989586621679454859) l Source # 
type Apply Nat (TyFun [a6989586621679454859] ([a6989586621679454859], [a6989586621679454859]) -> Type) (SplitAtSym0 a6989586621679454859) l = SplitAtSym1 a6989586621679454859 l

data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679454859] ([a6989586621679454859], [a6989586621679454859])) Source #

Instances

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

Methods

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

type Apply [a] ([a], [a]) (SplitAtSym1 a l1) l2 Source # 
type Apply [a] ([a], [a]) (SplitAtSym1 a l1) l2 = SplitAt a l1 l2

type SplitAtSym2 (t :: Nat) (t :: [a6989586621679454859]) = SplitAt t t Source #

data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679454866 Bool -> Type) (TyFun [a6989586621679454866] [a6989586621679454866] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454866 Bool -> Type) (TyFun [a6989586621679454866] [a6989586621679454866] -> Type) (TakeWhileSym0 a6989586621679454866) l Source # 
type Apply (TyFun a6989586621679454866 Bool -> Type) (TyFun [a6989586621679454866] [a6989586621679454866] -> Type) (TakeWhileSym0 a6989586621679454866) l = TakeWhileSym1 a6989586621679454866 l

data TakeWhileSym1 (l :: TyFun a6989586621679454866 Bool -> Type) (l :: TyFun [a6989586621679454866] [a6989586621679454866]) Source #

Instances

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

Methods

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

type Apply [a] [a] (TakeWhileSym1 a l1) l2 Source # 
type Apply [a] [a] (TakeWhileSym1 a l1) l2 = TakeWhile a l1 l2

type TakeWhileSym2 (t :: TyFun a6989586621679454866 Bool -> Type) (t :: [a6989586621679454866]) = TakeWhile t t Source #

data DropWhileSym0 (l :: TyFun (TyFun a6989586621679454865 Bool -> Type) (TyFun [a6989586621679454865] [a6989586621679454865] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454865 Bool -> Type) (TyFun [a6989586621679454865] [a6989586621679454865] -> Type) (DropWhileSym0 a6989586621679454865) l Source # 
type Apply (TyFun a6989586621679454865 Bool -> Type) (TyFun [a6989586621679454865] [a6989586621679454865] -> Type) (DropWhileSym0 a6989586621679454865) l = DropWhileSym1 a6989586621679454865 l

data DropWhileSym1 (l :: TyFun a6989586621679454865 Bool -> Type) (l :: TyFun [a6989586621679454865] [a6989586621679454865]) Source #

Instances

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

Methods

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

type Apply [a] [a] (DropWhileSym1 a l1) l2 Source # 
type Apply [a] [a] (DropWhileSym1 a l1) l2 = DropWhile a l1 l2

type DropWhileSym2 (t :: TyFun a6989586621679454865 Bool -> Type) (t :: [a6989586621679454865]) = DropWhile t t Source #

data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679454864 Bool -> Type) (TyFun [a6989586621679454864] [a6989586621679454864] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454864 Bool -> Type) (TyFun [a6989586621679454864] [a6989586621679454864] -> Type) (DropWhileEndSym0 a6989586621679454864) l Source # 
type Apply (TyFun a6989586621679454864 Bool -> Type) (TyFun [a6989586621679454864] [a6989586621679454864] -> Type) (DropWhileEndSym0 a6989586621679454864) l = DropWhileEndSym1 a6989586621679454864 l

data DropWhileEndSym1 (l :: TyFun a6989586621679454864 Bool -> Type) (l :: TyFun [a6989586621679454864] [a6989586621679454864]) Source #

Instances

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

Methods

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

type Apply [a] [a] (DropWhileEndSym1 a l1) l2 Source # 
type Apply [a] [a] (DropWhileEndSym1 a l1) l2 = DropWhileEnd a l1 l2

type DropWhileEndSym2 (t :: TyFun a6989586621679454864 Bool -> Type) (t :: [a6989586621679454864]) = DropWhileEnd t t Source #

data SpanSym0 (l :: TyFun (TyFun a6989586621679454863 Bool -> Type) (TyFun [a6989586621679454863] ([a6989586621679454863], [a6989586621679454863]) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454863 Bool -> Type) (TyFun [a6989586621679454863] ([a6989586621679454863], [a6989586621679454863]) -> Type) (SpanSym0 a6989586621679454863) l Source # 
type Apply (TyFun a6989586621679454863 Bool -> Type) (TyFun [a6989586621679454863] ([a6989586621679454863], [a6989586621679454863]) -> Type) (SpanSym0 a6989586621679454863) l = SpanSym1 a6989586621679454863 l

data SpanSym1 (l :: TyFun a6989586621679454863 Bool -> Type) (l :: TyFun [a6989586621679454863] ([a6989586621679454863], [a6989586621679454863])) Source #

Instances

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

Methods

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

type Apply [a] ([a], [a]) (SpanSym1 a l1) l2 Source # 
type Apply [a] ([a], [a]) (SpanSym1 a l1) l2 = Span a l1 l2

type SpanSym2 (t :: TyFun a6989586621679454863 Bool -> Type) (t :: [a6989586621679454863]) = Span t t Source #

data BreakSym0 (l :: TyFun (TyFun a6989586621679454862 Bool -> Type) (TyFun [a6989586621679454862] ([a6989586621679454862], [a6989586621679454862]) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454862 Bool -> Type) (TyFun [a6989586621679454862] ([a6989586621679454862], [a6989586621679454862]) -> Type) (BreakSym0 a6989586621679454862) l Source # 
type Apply (TyFun a6989586621679454862 Bool -> Type) (TyFun [a6989586621679454862] ([a6989586621679454862], [a6989586621679454862]) -> Type) (BreakSym0 a6989586621679454862) l = BreakSym1 a6989586621679454862 l

data BreakSym1 (l :: TyFun a6989586621679454862 Bool -> Type) (l :: TyFun [a6989586621679454862] ([a6989586621679454862], [a6989586621679454862])) Source #

Instances

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

Methods

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

type Apply [a] ([a], [a]) (BreakSym1 a l1) l2 Source # 
type Apply [a] ([a], [a]) (BreakSym1 a l1) l2 = Break a l1 l2

type BreakSym2 (t :: TyFun a6989586621679454862 Bool -> Type) (t :: [a6989586621679454862]) = Break t t Source #

data StripPrefixSym0 (l :: TyFun [a6989586621679873476] (TyFun [a6989586621679873476] (Maybe [a6989586621679873476]) -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679873476] (TyFun [a6989586621679873476] (Maybe [a6989586621679873476]) -> Type) (StripPrefixSym0 a6989586621679873476) l Source # 
type Apply [a6989586621679873476] (TyFun [a6989586621679873476] (Maybe [a6989586621679873476]) -> Type) (StripPrefixSym0 a6989586621679873476) l = StripPrefixSym1 a6989586621679873476 l

data StripPrefixSym1 (l :: [a6989586621679873476]) (l :: TyFun [a6989586621679873476] (Maybe [a6989586621679873476])) Source #

Instances

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

Methods

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

type Apply [a] (Maybe [a]) (StripPrefixSym1 a l1) l2 Source # 
type Apply [a] (Maybe [a]) (StripPrefixSym1 a l1) l2 = StripPrefix a l1 l2

type StripPrefixSym2 (t :: [a6989586621679873476]) (t :: [a6989586621679873476]) = StripPrefix t t Source #

data MaximumSym0 (l :: TyFun [a6989586621679454857] a6989586621679454857) Source #

Instances

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

Methods

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

type Apply [a] a (MaximumSym0 a) l Source # 
type Apply [a] a (MaximumSym0 a) l = Maximum a l

type MaximumSym1 (t :: [a6989586621679454857]) = Maximum t Source #

data MinimumSym0 (l :: TyFun [a6989586621679454856] a6989586621679454856) Source #

Instances

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

Methods

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

type Apply [a] a (MinimumSym0 a) l Source # 
type Apply [a] a (MinimumSym0 a) l = Minimum a l

type MinimumSym1 (t :: [a6989586621679454856]) = Minimum t Source #

data GroupSym0 (l :: TyFun [a6989586621679454858] [[a6989586621679454858]]) Source #

Instances

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

Methods

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

type Apply [a] [[a]] (GroupSym0 a) l Source # 
type Apply [a] [[a]] (GroupSym0 a) l = Group a l

type GroupSym1 (t :: [a6989586621679454858]) = Group t Source #

data GroupBySym0 (l :: TyFun (TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (TyFun [a6989586621679454853] [[a6989586621679454853]] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (TyFun [a6989586621679454853] [[a6989586621679454853]] -> Type) (GroupBySym0 a6989586621679454853) l Source # 
type Apply (TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (TyFun [a6989586621679454853] [[a6989586621679454853]] -> Type) (GroupBySym0 a6989586621679454853) l = GroupBySym1 a6989586621679454853 l

data GroupBySym1 (l :: TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454853] [[a6989586621679454853]]) Source #

Instances

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

Methods

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

type Apply [a] [[a]] (GroupBySym1 a l1) l2 Source # 
type Apply [a] [[a]] (GroupBySym1 a l1) l2 = GroupBy a l1 l2

type GroupBySym2 (t :: TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (t :: [a6989586621679454853]) = GroupBy t t Source #

data LookupSym0 (l :: TyFun a6989586621679454851 (TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun a6989586621679454851 (TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852) -> Type) -> *) (LookupSym0 a6989586621679454851 b6989586621679454852) Source # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym0 a6989586621679454851 b6989586621679454852) t -> () Source #

type Apply a6989586621679454851 (TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852) -> Type) (LookupSym0 a6989586621679454851 b6989586621679454852) l Source # 
type Apply a6989586621679454851 (TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852) -> Type) (LookupSym0 a6989586621679454851 b6989586621679454852) l = LookupSym1 a6989586621679454851 b6989586621679454852 l

data LookupSym1 (l :: a6989586621679454851) (l :: TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852)) Source #

Instances

SuppressUnusedWarnings (a6989586621679454851 -> TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852) -> *) (LookupSym1 a6989586621679454851 b6989586621679454852) Source # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym1 a6989586621679454851 b6989586621679454852) t -> () Source #

type Apply [(a, b)] (Maybe b) (LookupSym1 a b l1) l2 Source # 
type Apply [(a, b)] (Maybe b) (LookupSym1 a b l1) l2 = Lookup a b l1 l2

type LookupSym2 (t :: a6989586621679454851) (t :: [(a6989586621679454851, b6989586621679454852)]) = Lookup t t Source #

data FindSym0 (l :: TyFun (TyFun a6989586621679454873 Bool -> Type) (TyFun [a6989586621679454873] (Maybe a6989586621679454873) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454873 Bool -> Type) (TyFun [a6989586621679454873] (Maybe a6989586621679454873) -> Type) (FindSym0 a6989586621679454873) l Source # 
type Apply (TyFun a6989586621679454873 Bool -> Type) (TyFun [a6989586621679454873] (Maybe a6989586621679454873) -> Type) (FindSym0 a6989586621679454873) l = FindSym1 a6989586621679454873 l

data FindSym1 (l :: TyFun a6989586621679454873 Bool -> Type) (l :: TyFun [a6989586621679454873] (Maybe a6989586621679454873)) Source #

Instances

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

Methods

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

type Apply [a] (Maybe a) (FindSym1 a l1) l2 Source # 
type Apply [a] (Maybe a) (FindSym1 a l1) l2 = Find a l1 l2

type FindSym2 (t :: TyFun a6989586621679454873 Bool -> Type) (t :: [a6989586621679454873]) = Find t t Source #

data FilterSym0 (l :: TyFun (TyFun a6989586621679454874 Bool -> Type) (TyFun [a6989586621679454874] [a6989586621679454874] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454874 Bool -> Type) (TyFun [a6989586621679454874] [a6989586621679454874] -> Type) (FilterSym0 a6989586621679454874) l Source # 
type Apply (TyFun a6989586621679454874 Bool -> Type) (TyFun [a6989586621679454874] [a6989586621679454874] -> Type) (FilterSym0 a6989586621679454874) l = FilterSym1 a6989586621679454874 l

data FilterSym1 (l :: TyFun a6989586621679454874 Bool -> Type) (l :: TyFun [a6989586621679454874] [a6989586621679454874]) Source #

Instances

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

Methods

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

type Apply [a] [a] (FilterSym1 a l1) l2 Source # 
type Apply [a] [a] (FilterSym1 a l1) l2 = Filter a l1 l2

type FilterSym2 (t :: TyFun a6989586621679454874 Bool -> Type) (t :: [a6989586621679454874]) = Filter t t Source #

data PartitionSym0 (l :: TyFun (TyFun a6989586621679454850 Bool -> Type) (TyFun [a6989586621679454850] ([a6989586621679454850], [a6989586621679454850]) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454850 Bool -> Type) (TyFun [a6989586621679454850] ([a6989586621679454850], [a6989586621679454850]) -> Type) (PartitionSym0 a6989586621679454850) l Source # 
type Apply (TyFun a6989586621679454850 Bool -> Type) (TyFun [a6989586621679454850] ([a6989586621679454850], [a6989586621679454850]) -> Type) (PartitionSym0 a6989586621679454850) l = PartitionSym1 a6989586621679454850 l

data PartitionSym1 (l :: TyFun a6989586621679454850 Bool -> Type) (l :: TyFun [a6989586621679454850] ([a6989586621679454850], [a6989586621679454850])) Source #

Instances

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

Methods

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

type Apply [a] ([a], [a]) (PartitionSym1 a l1) l2 Source # 
type Apply [a] ([a], [a]) (PartitionSym1 a l1) l2 = Partition a l1 l2

type PartitionSym2 (t :: TyFun a6989586621679454850 Bool -> Type) (t :: [a6989586621679454850]) = Partition t t Source #

data (:!!$) (l :: TyFun [a6989586621679454843] (TyFun Nat a6989586621679454843 -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679454843] (TyFun Nat a6989586621679454843 -> Type) ((:!!$) a6989586621679454843) l Source # 
type Apply [a6989586621679454843] (TyFun Nat a6989586621679454843 -> Type) ((:!!$) a6989586621679454843) l = (:!!$$) a6989586621679454843 l

data (l :: [a6989586621679454843]) :!!$$ (l :: TyFun Nat a6989586621679454843) Source #

Instances

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

Methods

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

type Apply Nat a ((:!!$$) a l1) l2 Source # 
type Apply Nat a ((:!!$$) a l1) l2 = (:!!) a l1 l2

type (:!!$$$) (t :: [a6989586621679454843]) (t :: Nat) = (:!!) t t Source #

data ElemIndexSym0 (l :: TyFun a6989586621679454872 (TyFun [a6989586621679454872] (Maybe Nat) -> Type)) Source #

Instances

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

Methods

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

type Apply a6989586621679454872 (TyFun [a6989586621679454872] (Maybe Nat) -> Type) (ElemIndexSym0 a6989586621679454872) l Source # 
type Apply a6989586621679454872 (TyFun [a6989586621679454872] (Maybe Nat) -> Type) (ElemIndexSym0 a6989586621679454872) l = ElemIndexSym1 a6989586621679454872 l

data ElemIndexSym1 (l :: a6989586621679454872) (l :: TyFun [a6989586621679454872] (Maybe Nat)) Source #

Instances

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

Methods

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

type Apply [a] (Maybe Nat) (ElemIndexSym1 a l1) l2 Source # 
type Apply [a] (Maybe Nat) (ElemIndexSym1 a l1) l2 = ElemIndex a l1 l2

type ElemIndexSym2 (t :: a6989586621679454872) (t :: [a6989586621679454872]) = ElemIndex t t Source #

data ElemIndicesSym0 (l :: TyFun a6989586621679454871 (TyFun [a6989586621679454871] [Nat] -> Type)) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (ElemIndicesSym0 a6989586621679454871) t -> () Source #

type Apply a6989586621679454871 (TyFun [a6989586621679454871] [Nat] -> Type) (ElemIndicesSym0 a6989586621679454871) l Source # 
type Apply a6989586621679454871 (TyFun [a6989586621679454871] [Nat] -> Type) (ElemIndicesSym0 a6989586621679454871) l = ElemIndicesSym1 a6989586621679454871 l

data ElemIndicesSym1 (l :: a6989586621679454871) (l :: TyFun [a6989586621679454871] [Nat]) Source #

Instances

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

Methods

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

type Apply [a] [Nat] (ElemIndicesSym1 a l1) l2 Source # 
type Apply [a] [Nat] (ElemIndicesSym1 a l1) l2 = ElemIndices a l1 l2

type ElemIndicesSym2 (t :: a6989586621679454871) (t :: [a6989586621679454871]) = ElemIndices t t Source #

data FindIndexSym0 (l :: TyFun (TyFun a6989586621679454870 Bool -> Type) (TyFun [a6989586621679454870] (Maybe Nat) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454870 Bool -> Type) (TyFun [a6989586621679454870] (Maybe Nat) -> Type) (FindIndexSym0 a6989586621679454870) l Source # 
type Apply (TyFun a6989586621679454870 Bool -> Type) (TyFun [a6989586621679454870] (Maybe Nat) -> Type) (FindIndexSym0 a6989586621679454870) l = FindIndexSym1 a6989586621679454870 l

data FindIndexSym1 (l :: TyFun a6989586621679454870 Bool -> Type) (l :: TyFun [a6989586621679454870] (Maybe Nat)) Source #

Instances

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

Methods

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

type Apply [a] (Maybe Nat) (FindIndexSym1 a l1) l2 Source # 
type Apply [a] (Maybe Nat) (FindIndexSym1 a l1) l2 = FindIndex a l1 l2

type FindIndexSym2 (t :: TyFun a6989586621679454870 Bool -> Type) (t :: [a6989586621679454870]) = FindIndex t t Source #

data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679454869 Bool -> Type) (TyFun [a6989586621679454869] [Nat] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454869 Bool -> Type) (TyFun [a6989586621679454869] [Nat] -> Type) (FindIndicesSym0 a6989586621679454869) l Source # 
type Apply (TyFun a6989586621679454869 Bool -> Type) (TyFun [a6989586621679454869] [Nat] -> Type) (FindIndicesSym0 a6989586621679454869) l = FindIndicesSym1 a6989586621679454869 l

data FindIndicesSym1 (l :: TyFun a6989586621679454869 Bool -> Type) (l :: TyFun [a6989586621679454869] [Nat]) Source #

Instances

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

Methods

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

type Apply [a] [Nat] (FindIndicesSym1 a l1) l2 Source # 
type Apply [a] [Nat] (FindIndicesSym1 a l1) l2 = FindIndices a l1 l2

type FindIndicesSym2 (t :: TyFun a6989586621679454869 Bool -> Type) (t :: [a6989586621679454869]) = FindIndices t t Source #

data Zip4Sym0 (l :: TyFun [a6989586621679873472] (TyFun [b6989586621679873473] (TyFun [c6989586621679873474] (TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679873472] (TyFun [b6989586621679873473] (TyFun [c6989586621679873474] (TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> Type) -> Type) -> Type) -> *) (Zip4Sym0 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym0 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475) t -> () Source #

type Apply [a6989586621679873472] (TyFun [b6989586621679873473] (TyFun [c6989586621679873474] (TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> Type) -> Type) -> Type) (Zip4Sym0 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475) l Source # 
type Apply [a6989586621679873472] (TyFun [b6989586621679873473] (TyFun [c6989586621679873474] (TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> Type) -> Type) -> Type) (Zip4Sym0 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475) l = Zip4Sym1 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475 l

data Zip4Sym1 (l :: [a6989586621679873472]) (l :: TyFun [b6989586621679873473] (TyFun [c6989586621679873474] (TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873472] -> TyFun [b6989586621679873473] (TyFun [c6989586621679873474] (TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> Type) -> Type) -> *) (Zip4Sym1 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym1 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475) t -> () Source #

type Apply [b6989586621679873473] (TyFun [c6989586621679873474] (TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> Type) -> Type) (Zip4Sym1 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475 l1) l2 Source # 
type Apply [b6989586621679873473] (TyFun [c6989586621679873474] (TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> Type) -> Type) (Zip4Sym1 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475 l1) l2 = Zip4Sym2 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475 l1 l2

data Zip4Sym2 (l :: [a6989586621679873472]) (l :: [b6989586621679873473]) (l :: TyFun [c6989586621679873474] (TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873472] -> [b6989586621679873473] -> TyFun [c6989586621679873474] (TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> Type) -> *) (Zip4Sym2 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym2 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475) t -> () Source #

type Apply [c6989586621679873474] (TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> Type) (Zip4Sym2 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475 l1 l2) l3 Source # 
type Apply [c6989586621679873474] (TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> Type) (Zip4Sym2 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475 l1 l2) l3 = Zip4Sym3 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475 l1 l2 l3

data Zip4Sym3 (l :: [a6989586621679873472]) (l :: [b6989586621679873473]) (l :: [c6989586621679873474]) (l :: TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873472] -> [b6989586621679873473] -> [c6989586621679873474] -> TyFun [d6989586621679873475] [(a6989586621679873472, b6989586621679873473, c6989586621679873474, d6989586621679873475)] -> *) (Zip4Sym3 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym3 a6989586621679873472 b6989586621679873473 c6989586621679873474 d6989586621679873475) t -> () Source #

type Apply [d] [(a, b, c, d)] (Zip4Sym3 a b c d l1 l2 l3) l4 Source # 
type Apply [d] [(a, b, c, d)] (Zip4Sym3 a b c d l1 l2 l3) l4 = Zip4 a b c d l1 l2 l3 l4

type Zip4Sym4 (t :: [a6989586621679873472]) (t :: [b6989586621679873473]) (t :: [c6989586621679873474]) (t :: [d6989586621679873475]) = Zip4 t t t t Source #

data Zip5Sym0 (l :: TyFun [a6989586621679873467] (TyFun [b6989586621679873468] (TyFun [c6989586621679873469] (TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679873467] (TyFun [b6989586621679873468] (TyFun [c6989586621679873469] (TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip5Sym0 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym0 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471) t -> () Source #

type Apply [a6989586621679873467] (TyFun [b6989586621679873468] (TyFun [c6989586621679873469] (TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> Type) -> Type) -> Type) (Zip5Sym0 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471) l Source # 
type Apply [a6989586621679873467] (TyFun [b6989586621679873468] (TyFun [c6989586621679873469] (TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> Type) -> Type) -> Type) (Zip5Sym0 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471) l = Zip5Sym1 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471 l

data Zip5Sym1 (l :: [a6989586621679873467]) (l :: TyFun [b6989586621679873468] (TyFun [c6989586621679873469] (TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873467] -> TyFun [b6989586621679873468] (TyFun [c6989586621679873469] (TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> Type) -> Type) -> *) (Zip5Sym1 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym1 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471) t -> () Source #

type Apply [b6989586621679873468] (TyFun [c6989586621679873469] (TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> Type) -> Type) (Zip5Sym1 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471 l1) l2 Source # 
type Apply [b6989586621679873468] (TyFun [c6989586621679873469] (TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> Type) -> Type) (Zip5Sym1 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471 l1) l2 = Zip5Sym2 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471 l1 l2

data Zip5Sym2 (l :: [a6989586621679873467]) (l :: [b6989586621679873468]) (l :: TyFun [c6989586621679873469] (TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873467] -> [b6989586621679873468] -> TyFun [c6989586621679873469] (TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> Type) -> *) (Zip5Sym2 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym2 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471) t -> () Source #

type Apply [c6989586621679873469] (TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> Type) (Zip5Sym2 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471 l1 l2) l3 Source # 
type Apply [c6989586621679873469] (TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> Type) (Zip5Sym2 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471 l1 l2) l3 = Zip5Sym3 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471 l1 l2 l3

data Zip5Sym3 (l :: [a6989586621679873467]) (l :: [b6989586621679873468]) (l :: [c6989586621679873469]) (l :: TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873467] -> [b6989586621679873468] -> [c6989586621679873469] -> TyFun [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) -> *) (Zip5Sym3 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym3 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471) t -> () Source #

type Apply [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) (Zip5Sym3 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471 l1 l2 l3) l4 Source # 
type Apply [d6989586621679873470] (TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> Type) (Zip5Sym3 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471 l1 l2 l3) l4 = Zip5Sym4 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471 l1 l2 l3 l4

data Zip5Sym4 (l :: [a6989586621679873467]) (l :: [b6989586621679873468]) (l :: [c6989586621679873469]) (l :: [d6989586621679873470]) (l :: TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873467] -> [b6989586621679873468] -> [c6989586621679873469] -> [d6989586621679873470] -> TyFun [e6989586621679873471] [(a6989586621679873467, b6989586621679873468, c6989586621679873469, d6989586621679873470, e6989586621679873471)] -> *) (Zip5Sym4 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym4 a6989586621679873467 b6989586621679873468 c6989586621679873469 d6989586621679873470 e6989586621679873471) t -> () Source #

type Apply [e] [(a, b, c, d, e)] (Zip5Sym4 a b c d e l1 l2 l3 l4) l5 Source # 
type Apply [e] [(a, b, c, d, e)] (Zip5Sym4 a b c d e l1 l2 l3 l4) l5 = Zip5 a b c d e l1 l2 l3 l4 l5

type Zip5Sym5 (t :: [a6989586621679873467]) (t :: [b6989586621679873468]) (t :: [c6989586621679873469]) (t :: [d6989586621679873470]) (t :: [e6989586621679873471]) = Zip5 t t t t t Source #

data Zip6Sym0 (l :: TyFun [a6989586621679873461] (TyFun [b6989586621679873462] (TyFun [c6989586621679873463] (TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679873461] (TyFun [b6989586621679873462] (TyFun [c6989586621679873463] (TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym0 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym0 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) t -> () Source #

type Apply [a6989586621679873461] (TyFun [b6989586621679873462] (TyFun [c6989586621679873463] (TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip6Sym0 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) l Source # 
type Apply [a6989586621679873461] (TyFun [b6989586621679873462] (TyFun [c6989586621679873463] (TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip6Sym0 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) l = Zip6Sym1 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l

data Zip6Sym1 (l :: [a6989586621679873461]) (l :: TyFun [b6989586621679873462] (TyFun [c6989586621679873463] (TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873461] -> TyFun [b6989586621679873462] (TyFun [c6989586621679873463] (TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym1 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym1 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) t -> () Source #

type Apply [b6989586621679873462] (TyFun [c6989586621679873463] (TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> Type) -> Type) (Zip6Sym1 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l1) l2 Source # 
type Apply [b6989586621679873462] (TyFun [c6989586621679873463] (TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> Type) -> Type) (Zip6Sym1 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l1) l2 = Zip6Sym2 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l1 l2

data Zip6Sym2 (l :: [a6989586621679873461]) (l :: [b6989586621679873462]) (l :: TyFun [c6989586621679873463] (TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873461] -> [b6989586621679873462] -> TyFun [c6989586621679873463] (TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> Type) -> *) (Zip6Sym2 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym2 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) t -> () Source #

type Apply [c6989586621679873463] (TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> Type) (Zip6Sym2 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l1 l2) l3 Source # 
type Apply [c6989586621679873463] (TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> Type) (Zip6Sym2 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l1 l2) l3 = Zip6Sym3 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l1 l2 l3

data Zip6Sym3 (l :: [a6989586621679873461]) (l :: [b6989586621679873462]) (l :: [c6989586621679873463]) (l :: TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873461] -> [b6989586621679873462] -> [c6989586621679873463] -> TyFun [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) -> *) (Zip6Sym3 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym3 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) t -> () Source #

type Apply [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) (Zip6Sym3 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l1 l2 l3) l4 Source # 
type Apply [d6989586621679873464] (TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> Type) (Zip6Sym3 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l1 l2 l3) l4 = Zip6Sym4 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l1 l2 l3 l4

data Zip6Sym4 (l :: [a6989586621679873461]) (l :: [b6989586621679873462]) (l :: [c6989586621679873463]) (l :: [d6989586621679873464]) (l :: TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873461] -> [b6989586621679873462] -> [c6989586621679873463] -> [d6989586621679873464] -> TyFun [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) -> *) (Zip6Sym4 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym4 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) t -> () Source #

type Apply [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) (Zip6Sym4 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l1 l2 l3 l4) l5 Source # 
type Apply [e6989586621679873465] (TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> Type) (Zip6Sym4 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l1 l2 l3 l4) l5 = Zip6Sym5 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466 l1 l2 l3 l4 l5

data Zip6Sym5 (l :: [a6989586621679873461]) (l :: [b6989586621679873462]) (l :: [c6989586621679873463]) (l :: [d6989586621679873464]) (l :: [e6989586621679873465]) (l :: TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873461] -> [b6989586621679873462] -> [c6989586621679873463] -> [d6989586621679873464] -> [e6989586621679873465] -> TyFun [f6989586621679873466] [(a6989586621679873461, b6989586621679873462, c6989586621679873463, d6989586621679873464, e6989586621679873465, f6989586621679873466)] -> *) (Zip6Sym5 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym5 a6989586621679873461 b6989586621679873462 c6989586621679873463 d6989586621679873464 e6989586621679873465 f6989586621679873466) t -> () Source #

type Apply [f] [(a, b, c, d, e, f)] (Zip6Sym5 a b c d e f l1 l2 l3 l4 l5) l6 Source # 
type Apply [f] [(a, b, c, d, e, f)] (Zip6Sym5 a b c d e f l1 l2 l3 l4 l5) l6 = Zip6 a b c d e f l1 l2 l3 l4 l5 l6

type Zip6Sym6 (t :: [a6989586621679873461]) (t :: [b6989586621679873462]) (t :: [c6989586621679873463]) (t :: [d6989586621679873464]) (t :: [e6989586621679873465]) (t :: [f6989586621679873466]) = Zip6 t t t t t t Source #

data Zip7Sym0 (l :: TyFun [a6989586621679873454] (TyFun [b6989586621679873455] (TyFun [c6989586621679873456] (TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679873454] (TyFun [b6989586621679873455] (TyFun [c6989586621679873456] (TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym0 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym0 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) t -> () Source #

type Apply [a6989586621679873454] (TyFun [b6989586621679873455] (TyFun [c6989586621679873456] (TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym0 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) l Source # 
type Apply [a6989586621679873454] (TyFun [b6989586621679873455] (TyFun [c6989586621679873456] (TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym0 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) l = Zip7Sym1 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l

data Zip7Sym1 (l :: [a6989586621679873454]) (l :: TyFun [b6989586621679873455] (TyFun [c6989586621679873456] (TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873454] -> TyFun [b6989586621679873455] (TyFun [c6989586621679873456] (TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym1 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym1 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) t -> () Source #

type Apply [b6989586621679873455] (TyFun [c6989586621679873456] (TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym1 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1) l2 Source # 
type Apply [b6989586621679873455] (TyFun [c6989586621679873456] (TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym1 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1) l2 = Zip7Sym2 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2

data Zip7Sym2 (l :: [a6989586621679873454]) (l :: [b6989586621679873455]) (l :: TyFun [c6989586621679873456] (TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873454] -> [b6989586621679873455] -> TyFun [c6989586621679873456] (TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym2 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym2 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) t -> () Source #

type Apply [c6989586621679873456] (TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> Type) (Zip7Sym2 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2) l3 Source # 
type Apply [c6989586621679873456] (TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> Type) (Zip7Sym2 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2) l3 = Zip7Sym3 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2 l3

data Zip7Sym3 (l :: [a6989586621679873454]) (l :: [b6989586621679873455]) (l :: [c6989586621679873456]) (l :: TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873454] -> [b6989586621679873455] -> [c6989586621679873456] -> TyFun [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) -> *) (Zip7Sym3 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym3 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) t -> () Source #

type Apply [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) (Zip7Sym3 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2 l3) l4 Source # 
type Apply [d6989586621679873457] (TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> Type) (Zip7Sym3 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2 l3) l4 = Zip7Sym4 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2 l3 l4

data Zip7Sym4 (l :: [a6989586621679873454]) (l :: [b6989586621679873455]) (l :: [c6989586621679873456]) (l :: [d6989586621679873457]) (l :: TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873454] -> [b6989586621679873455] -> [c6989586621679873456] -> [d6989586621679873457] -> TyFun [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) -> *) (Zip7Sym4 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym4 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) t -> () Source #

type Apply [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) (Zip7Sym4 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2 l3 l4) l5 Source # 
type Apply [e6989586621679873458] (TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> Type) (Zip7Sym4 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2 l3 l4) l5 = Zip7Sym5 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2 l3 l4 l5

data Zip7Sym5 (l :: [a6989586621679873454]) (l :: [b6989586621679873455]) (l :: [c6989586621679873456]) (l :: [d6989586621679873457]) (l :: [e6989586621679873458]) (l :: TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873454] -> [b6989586621679873455] -> [c6989586621679873456] -> [d6989586621679873457] -> [e6989586621679873458] -> TyFun [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) -> *) (Zip7Sym5 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym5 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) t -> () Source #

type Apply [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) (Zip7Sym5 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2 l3 l4 l5) l6 Source # 
type Apply [f6989586621679873459] (TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> Type) (Zip7Sym5 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2 l3 l4 l5) l6 = Zip7Sym6 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460 l1 l2 l3 l4 l5 l6

data Zip7Sym6 (l :: [a6989586621679873454]) (l :: [b6989586621679873455]) (l :: [c6989586621679873456]) (l :: [d6989586621679873457]) (l :: [e6989586621679873458]) (l :: [f6989586621679873459]) (l :: TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873454] -> [b6989586621679873455] -> [c6989586621679873456] -> [d6989586621679873457] -> [e6989586621679873458] -> [f6989586621679873459] -> TyFun [g6989586621679873460] [(a6989586621679873454, b6989586621679873455, c6989586621679873456, d6989586621679873457, e6989586621679873458, f6989586621679873459, g6989586621679873460)] -> *) (Zip7Sym6 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym6 a6989586621679873454 b6989586621679873455 c6989586621679873456 d6989586621679873457 e6989586621679873458 f6989586621679873459 g6989586621679873460) t -> () Source #

type Apply [g] [(a, b, c, d, e, f, g)] (Zip7Sym6 a b c d e f g l1 l2 l3 l4 l5 l6) l7 Source # 
type Apply [g] [(a, b, c, d, e, f, g)] (Zip7Sym6 a b c d e f g l1 l2 l3 l4 l5 l6) l7 = Zip7 a b c d e f g l1 l2 l3 l4 l5 l6 l7

type Zip7Sym7 (t :: [a6989586621679873454]) (t :: [b6989586621679873455]) (t :: [c6989586621679873456]) (t :: [d6989586621679873457]) (t :: [e6989586621679873458]) (t :: [f6989586621679873459]) (t :: [g6989586621679873460]) = Zip7 t t t t t t t Source #

data ZipWith4Sym0 (l :: TyFun (TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873449] (TyFun [b6989586621679873450] (TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873449] (TyFun [b6989586621679873450] (TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith4Sym0 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym0 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453) t -> () Source #

type Apply (TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873449] (TyFun [b6989586621679873450] (TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> Type) -> Type) -> Type) (ZipWith4Sym0 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453) l Source # 
type Apply (TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873449] (TyFun [b6989586621679873450] (TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> Type) -> Type) -> Type) (ZipWith4Sym0 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453) l = ZipWith4Sym1 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453 l

data ZipWith4Sym1 (l :: TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679873449] (TyFun [b6989586621679873450] (TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679873449] (TyFun [b6989586621679873450] (TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> Type) -> Type) -> *) (ZipWith4Sym1 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym1 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453) t -> () Source #

type Apply [a6989586621679873449] (TyFun [b6989586621679873450] (TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> Type) -> Type) (ZipWith4Sym1 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453 l1) l2 Source # 
type Apply [a6989586621679873449] (TyFun [b6989586621679873450] (TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> Type) -> Type) (ZipWith4Sym1 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453 l1) l2 = ZipWith4Sym2 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453 l1 l2

data ZipWith4Sym2 (l :: TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873449]) (l :: TyFun [b6989586621679873450] (TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873449] -> TyFun [b6989586621679873450] (TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> Type) -> *) (ZipWith4Sym2 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym2 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453) t -> () Source #

type Apply [b6989586621679873450] (TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> Type) (ZipWith4Sym2 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453 l1 l2) l3 Source # 
type Apply [b6989586621679873450] (TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> Type) (ZipWith4Sym2 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453 l1 l2) l3 = ZipWith4Sym3 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453 l1 l2 l3

data ZipWith4Sym3 (l :: TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873449]) (l :: [b6989586621679873450]) (l :: TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873449] -> [b6989586621679873450] -> TyFun [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) -> *) (ZipWith4Sym3 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym3 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453) t -> () Source #

type Apply [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) (ZipWith4Sym3 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453 l1 l2 l3) l4 Source # 
type Apply [c6989586621679873451] (TyFun [d6989586621679873452] [e6989586621679873453] -> Type) (ZipWith4Sym3 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453 l1 l2 l3) l4 = ZipWith4Sym4 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453 l1 l2 l3 l4

data ZipWith4Sym4 (l :: TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873449]) (l :: [b6989586621679873450]) (l :: [c6989586621679873451]) (l :: TyFun [d6989586621679873452] [e6989586621679873453]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873449] -> [b6989586621679873450] -> [c6989586621679873451] -> TyFun [d6989586621679873452] [e6989586621679873453] -> *) (ZipWith4Sym4 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym4 a6989586621679873449 b6989586621679873450 c6989586621679873451 d6989586621679873452 e6989586621679873453) t -> () Source #

type Apply [d] [e] (ZipWith4Sym4 a b c d e l1 l2 l3 l4) l5 Source # 
type Apply [d] [e] (ZipWith4Sym4 a b c d e l1 l2 l3 l4) l5 = ZipWith4 a b c d e l1 l2 l3 l4 l5

type ZipWith4Sym5 (t :: TyFun a6989586621679873449 (TyFun b6989586621679873450 (TyFun c6989586621679873451 (TyFun d6989586621679873452 e6989586621679873453 -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679873449]) (t :: [b6989586621679873450]) (t :: [c6989586621679873451]) (t :: [d6989586621679873452]) = ZipWith4 t t t t t Source #

data ZipWith5Sym0 (l :: TyFun (TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873443] (TyFun [b6989586621679873444] (TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873443] (TyFun [b6989586621679873444] (TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym0 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym0 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) t -> () Source #

type Apply (TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873443] (TyFun [b6989586621679873444] (TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym0 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) l Source # 
type Apply (TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873443] (TyFun [b6989586621679873444] (TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym0 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) l = ZipWith5Sym1 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l

data ZipWith5Sym1 (l :: TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679873443] (TyFun [b6989586621679873444] (TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679873443] (TyFun [b6989586621679873444] (TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym1 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym1 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) t -> () Source #

type Apply [a6989586621679873443] (TyFun [b6989586621679873444] (TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym1 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l1) l2 Source # 
type Apply [a6989586621679873443] (TyFun [b6989586621679873444] (TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym1 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l1) l2 = ZipWith5Sym2 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l1 l2

data ZipWith5Sym2 (l :: TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873443]) (l :: TyFun [b6989586621679873444] (TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873443] -> TyFun [b6989586621679873444] (TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> Type) -> *) (ZipWith5Sym2 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym2 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) t -> () Source #

type Apply [b6989586621679873444] (TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> Type) (ZipWith5Sym2 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l1 l2) l3 Source # 
type Apply [b6989586621679873444] (TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> Type) (ZipWith5Sym2 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l1 l2) l3 = ZipWith5Sym3 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l1 l2 l3

data ZipWith5Sym3 (l :: TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873443]) (l :: [b6989586621679873444]) (l :: TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873443] -> [b6989586621679873444] -> TyFun [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) -> *) (ZipWith5Sym3 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym3 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) t -> () Source #

type Apply [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) (ZipWith5Sym3 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l1 l2 l3) l4 Source # 
type Apply [c6989586621679873445] (TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> Type) (ZipWith5Sym3 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l1 l2 l3) l4 = ZipWith5Sym4 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l1 l2 l3 l4

data ZipWith5Sym4 (l :: TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873443]) (l :: [b6989586621679873444]) (l :: [c6989586621679873445]) (l :: TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873443] -> [b6989586621679873444] -> [c6989586621679873445] -> TyFun [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) -> *) (ZipWith5Sym4 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym4 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) t -> () Source #

type Apply [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) (ZipWith5Sym4 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l1 l2 l3 l4) l5 Source # 
type Apply [d6989586621679873446] (TyFun [e6989586621679873447] [f6989586621679873448] -> Type) (ZipWith5Sym4 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l1 l2 l3 l4) l5 = ZipWith5Sym5 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448 l1 l2 l3 l4 l5

data ZipWith5Sym5 (l :: TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873443]) (l :: [b6989586621679873444]) (l :: [c6989586621679873445]) (l :: [d6989586621679873446]) (l :: TyFun [e6989586621679873447] [f6989586621679873448]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873443] -> [b6989586621679873444] -> [c6989586621679873445] -> [d6989586621679873446] -> TyFun [e6989586621679873447] [f6989586621679873448] -> *) (ZipWith5Sym5 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym5 a6989586621679873443 b6989586621679873444 c6989586621679873445 d6989586621679873446 e6989586621679873447 f6989586621679873448) t -> () Source #

type Apply [e] [f] (ZipWith5Sym5 a b c d e f l1 l2 l3 l4 l5) l6 Source # 
type Apply [e] [f] (ZipWith5Sym5 a b c d e f l1 l2 l3 l4 l5) l6 = ZipWith5 a b c d e f l1 l2 l3 l4 l5 l6

type ZipWith5Sym6 (t :: TyFun a6989586621679873443 (TyFun b6989586621679873444 (TyFun c6989586621679873445 (TyFun d6989586621679873446 (TyFun e6989586621679873447 f6989586621679873448 -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679873443]) (t :: [b6989586621679873444]) (t :: [c6989586621679873445]) (t :: [d6989586621679873446]) (t :: [e6989586621679873447]) = ZipWith5 t t t t t t Source #

data ZipWith6Sym0 (l :: TyFun (TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873436] (TyFun [b6989586621679873437] (TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873436] (TyFun [b6989586621679873437] (TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym0 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym0 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) t -> () Source #

type Apply (TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873436] (TyFun [b6989586621679873437] (TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym0 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) l Source # 
type Apply (TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873436] (TyFun [b6989586621679873437] (TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym0 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) l = ZipWith6Sym1 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l

data ZipWith6Sym1 (l :: TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679873436] (TyFun [b6989586621679873437] (TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679873436] (TyFun [b6989586621679873437] (TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym1 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym1 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) t -> () Source #

type Apply [a6989586621679873436] (TyFun [b6989586621679873437] (TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym1 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1) l2 Source # 
type Apply [a6989586621679873436] (TyFun [b6989586621679873437] (TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym1 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1) l2 = ZipWith6Sym2 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2

data ZipWith6Sym2 (l :: TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873436]) (l :: TyFun [b6989586621679873437] (TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873436] -> TyFun [b6989586621679873437] (TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym2 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym2 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) t -> () Source #

type Apply [b6989586621679873437] (TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym2 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2) l3 Source # 
type Apply [b6989586621679873437] (TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym2 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2) l3 = ZipWith6Sym3 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2 l3

data ZipWith6Sym3 (l :: TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873436]) (l :: [b6989586621679873437]) (l :: TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873436] -> [b6989586621679873437] -> TyFun [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) -> *) (ZipWith6Sym3 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym3 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) t -> () Source #

type Apply [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) (ZipWith6Sym3 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2 l3) l4 Source # 
type Apply [c6989586621679873438] (TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> Type) (ZipWith6Sym3 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2 l3) l4 = ZipWith6Sym4 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2 l3 l4

data ZipWith6Sym4 (l :: TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873436]) (l :: [b6989586621679873437]) (l :: [c6989586621679873438]) (l :: TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873436] -> [b6989586621679873437] -> [c6989586621679873438] -> TyFun [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) -> *) (ZipWith6Sym4 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym4 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) t -> () Source #

type Apply [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) (ZipWith6Sym4 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2 l3 l4) l5 Source # 
type Apply [d6989586621679873439] (TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> Type) (ZipWith6Sym4 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2 l3 l4) l5 = ZipWith6Sym5 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2 l3 l4 l5

data ZipWith6Sym5 (l :: TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873436]) (l :: [b6989586621679873437]) (l :: [c6989586621679873438]) (l :: [d6989586621679873439]) (l :: TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873436] -> [b6989586621679873437] -> [c6989586621679873438] -> [d6989586621679873439] -> TyFun [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) -> *) (ZipWith6Sym5 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym5 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) t -> () Source #

type Apply [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) (ZipWith6Sym5 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2 l3 l4 l5) l6 Source # 
type Apply [e6989586621679873440] (TyFun [f6989586621679873441] [g6989586621679873442] -> Type) (ZipWith6Sym5 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2 l3 l4 l5) l6 = ZipWith6Sym6 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442 l1 l2 l3 l4 l5 l6

data ZipWith6Sym6 (l :: TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873436]) (l :: [b6989586621679873437]) (l :: [c6989586621679873438]) (l :: [d6989586621679873439]) (l :: [e6989586621679873440]) (l :: TyFun [f6989586621679873441] [g6989586621679873442]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873436] -> [b6989586621679873437] -> [c6989586621679873438] -> [d6989586621679873439] -> [e6989586621679873440] -> TyFun [f6989586621679873441] [g6989586621679873442] -> *) (ZipWith6Sym6 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym6 a6989586621679873436 b6989586621679873437 c6989586621679873438 d6989586621679873439 e6989586621679873440 f6989586621679873441 g6989586621679873442) t -> () Source #

type Apply [f] [g] (ZipWith6Sym6 a b c d e f g l1 l2 l3 l4 l5 l6) l7 Source # 
type Apply [f] [g] (ZipWith6Sym6 a b c d e f g l1 l2 l3 l4 l5 l6) l7 = ZipWith6 a b c d e f g l1 l2 l3 l4 l5 l6 l7

type ZipWith6Sym7 (t :: TyFun a6989586621679873436 (TyFun b6989586621679873437 (TyFun c6989586621679873438 (TyFun d6989586621679873439 (TyFun e6989586621679873440 (TyFun f6989586621679873441 g6989586621679873442 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679873436]) (t :: [b6989586621679873437]) (t :: [c6989586621679873438]) (t :: [d6989586621679873439]) (t :: [e6989586621679873440]) (t :: [f6989586621679873441]) = ZipWith6 t t t t t t t Source #

data ZipWith7Sym0 (l :: TyFun (TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873428] (TyFun [b6989586621679873429] (TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873428] (TyFun [b6989586621679873429] (TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym0 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym0 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) t -> () Source #

type Apply (TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873428] (TyFun [b6989586621679873429] (TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym0 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) l Source # 
type Apply (TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679873428] (TyFun [b6989586621679873429] (TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym0 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) l = ZipWith7Sym1 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l

data ZipWith7Sym1 (l :: TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679873428] (TyFun [b6989586621679873429] (TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679873428] (TyFun [b6989586621679873429] (TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym1 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym1 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) t -> () Source #

type Apply [a6989586621679873428] (TyFun [b6989586621679873429] (TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym1 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1) l2 Source # 
type Apply [a6989586621679873428] (TyFun [b6989586621679873429] (TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym1 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1) l2 = ZipWith7Sym2 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2

data ZipWith7Sym2 (l :: TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873428]) (l :: TyFun [b6989586621679873429] (TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873428] -> TyFun [b6989586621679873429] (TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym2 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym2 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) t -> () Source #

type Apply [b6989586621679873429] (TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym2 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2) l3 Source # 
type Apply [b6989586621679873429] (TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym2 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2) l3 = ZipWith7Sym3 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3

data ZipWith7Sym3 (l :: TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873428]) (l :: [b6989586621679873429]) (l :: TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873428] -> [b6989586621679873429] -> TyFun [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym3 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym3 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) t -> () Source #

type Apply [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym3 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3) l4 Source # 
type Apply [c6989586621679873430] (TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym3 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3) l4 = ZipWith7Sym4 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3 l4

data ZipWith7Sym4 (l :: TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873428]) (l :: [b6989586621679873429]) (l :: [c6989586621679873430]) (l :: TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873428] -> [b6989586621679873429] -> [c6989586621679873430] -> TyFun [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) -> *) (ZipWith7Sym4 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym4 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) t -> () Source #

type Apply [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) (ZipWith7Sym4 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3 l4) l5 Source # 
type Apply [d6989586621679873431] (TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> Type) (ZipWith7Sym4 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3 l4) l5 = ZipWith7Sym5 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3 l4 l5

data ZipWith7Sym5 (l :: TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873428]) (l :: [b6989586621679873429]) (l :: [c6989586621679873430]) (l :: [d6989586621679873431]) (l :: TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873428] -> [b6989586621679873429] -> [c6989586621679873430] -> [d6989586621679873431] -> TyFun [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) -> *) (ZipWith7Sym5 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym5 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) t -> () Source #

type Apply [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) (ZipWith7Sym5 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3 l4 l5) l6 Source # 
type Apply [e6989586621679873432] (TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> Type) (ZipWith7Sym5 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3 l4 l5) l6 = ZipWith7Sym6 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3 l4 l5 l6

data ZipWith7Sym6 (l :: TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873428]) (l :: [b6989586621679873429]) (l :: [c6989586621679873430]) (l :: [d6989586621679873431]) (l :: [e6989586621679873432]) (l :: TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873428] -> [b6989586621679873429] -> [c6989586621679873430] -> [d6989586621679873431] -> [e6989586621679873432] -> TyFun [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) -> *) (ZipWith7Sym6 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym6 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) t -> () Source #

type Apply [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) (ZipWith7Sym6 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3 l4 l5 l6) l7 Source # 
type Apply [f6989586621679873433] (TyFun [g6989586621679873434] [h6989586621679873435] -> Type) (ZipWith7Sym6 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3 l4 l5 l6) l7 = ZipWith7Sym7 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435 l1 l2 l3 l4 l5 l6 l7

data ZipWith7Sym7 (l :: TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679873428]) (l :: [b6989586621679873429]) (l :: [c6989586621679873430]) (l :: [d6989586621679873431]) (l :: [e6989586621679873432]) (l :: [f6989586621679873433]) (l :: TyFun [g6989586621679873434] [h6989586621679873435]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679873428] -> [b6989586621679873429] -> [c6989586621679873430] -> [d6989586621679873431] -> [e6989586621679873432] -> [f6989586621679873433] -> TyFun [g6989586621679873434] [h6989586621679873435] -> *) (ZipWith7Sym7 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym7 a6989586621679873428 b6989586621679873429 c6989586621679873430 d6989586621679873431 e6989586621679873432 f6989586621679873433 g6989586621679873434 h6989586621679873435) t -> () Source #

type Apply [g] [h] (ZipWith7Sym7 a b c d e f g h l1 l2 l3 l4 l5 l6 l7) l8 Source # 
type Apply [g] [h] (ZipWith7Sym7 a b c d e f g h l1 l2 l3 l4 l5 l6 l7) l8 = ZipWith7 a b c d e f g h l1 l2 l3 l4 l5 l6 l7 l8

type ZipWith7Sym8 (t :: TyFun a6989586621679873428 (TyFun b6989586621679873429 (TyFun c6989586621679873430 (TyFun d6989586621679873431 (TyFun e6989586621679873432 (TyFun f6989586621679873433 (TyFun g6989586621679873434 h6989586621679873435 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679873428]) (t :: [b6989586621679873429]) (t :: [c6989586621679873430]) (t :: [d6989586621679873431]) (t :: [e6989586621679873432]) (t :: [f6989586621679873433]) (t :: [g6989586621679873434]) = ZipWith7 t t t t t t t t Source #

data NubSym0 (l :: TyFun [a6989586621679454842] [a6989586621679454842]) Source #

Instances

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

Methods

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

type Apply [a] [a] (NubSym0 a) l Source # 
type Apply [a] [a] (NubSym0 a) l = Nub a l

type NubSym1 (t :: [a6989586621679454842]) = Nub t Source #

data NubBySym0 (l :: TyFun (TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (TyFun [a6989586621679454841] [a6989586621679454841] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (TyFun [a6989586621679454841] [a6989586621679454841] -> Type) (NubBySym0 a6989586621679454841) l Source # 
type Apply (TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (TyFun [a6989586621679454841] [a6989586621679454841] -> Type) (NubBySym0 a6989586621679454841) l = NubBySym1 a6989586621679454841 l

data NubBySym1 (l :: TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454841] [a6989586621679454841]) Source #

Instances

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

Methods

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

type Apply [a] [a] (NubBySym1 a l1) l2 Source # 
type Apply [a] [a] (NubBySym1 a l1) l2 = NubBy a l1 l2

type NubBySym2 (t :: TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (t :: [a6989586621679454841]) = NubBy t t Source #

data UnionSym0 (l :: TyFun [a6989586621679454838] (TyFun [a6989586621679454838] [a6989586621679454838] -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679454838] (TyFun [a6989586621679454838] [a6989586621679454838] -> Type) (UnionSym0 a6989586621679454838) l Source # 
type Apply [a6989586621679454838] (TyFun [a6989586621679454838] [a6989586621679454838] -> Type) (UnionSym0 a6989586621679454838) l = UnionSym1 a6989586621679454838 l

data UnionSym1 (l :: [a6989586621679454838]) (l :: TyFun [a6989586621679454838] [a6989586621679454838]) Source #

Instances

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

Methods

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

type Apply [a] [a] (UnionSym1 a l1) l2 Source # 
type Apply [a] [a] (UnionSym1 a l1) l2 = Union a l1 l2

type UnionSym2 (t :: [a6989586621679454838]) (t :: [a6989586621679454838]) = Union t t Source #

data UnionBySym0 (l :: TyFun (TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (TyFun [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (TyFun [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type) -> Type) (UnionBySym0 a6989586621679454839) l Source # 
type Apply (TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (TyFun [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type) -> Type) (UnionBySym0 a6989586621679454839) l = UnionBySym1 a6989586621679454839 l

data UnionBySym1 (l :: TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type) (UnionBySym1 a6989586621679454839 l1) l2 Source # 
type Apply [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type) (UnionBySym1 a6989586621679454839 l1) l2 = UnionBySym2 a6989586621679454839 l1 l2

data UnionBySym2 (l :: TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (l :: [a6989586621679454839]) (l :: TyFun [a6989586621679454839] [a6989586621679454839]) Source #

Instances

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

Methods

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

type Apply [a] [a] (UnionBySym2 a l1 l2) l3 Source # 
type Apply [a] [a] (UnionBySym2 a l1 l2) l3 = UnionBy a l1 l2 l3

type UnionBySym3 (t :: TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (t :: [a6989586621679454839]) (t :: [a6989586621679454839]) = UnionBy t t t Source #

data GenericLengthSym0 (l :: TyFun [a6989586621679454837] i6989586621679454836) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679454837] i6989586621679454836 -> *) (GenericLengthSym0 a6989586621679454837 i6989586621679454836) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericLengthSym0 a6989586621679454837 i6989586621679454836) t -> () Source #

type Apply [a] k2 (GenericLengthSym0 a k2) l Source # 
type Apply [a] k2 (GenericLengthSym0 a k2) l = GenericLength a k2 l

type GenericLengthSym1 (t :: [a6989586621679454837]) = GenericLength t Source #

data GenericTakeSym0 (l :: TyFun i6989586621679873426 (TyFun [a6989586621679873427] [a6989586621679873427] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun i6989586621679873426 (TyFun [a6989586621679873427] [a6989586621679873427] -> Type) -> *) (GenericTakeSym0 i6989586621679873426 a6989586621679873427) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym0 i6989586621679873426 a6989586621679873427) t -> () Source #

type Apply i6989586621679873426 (TyFun [a6989586621679873427] [a6989586621679873427] -> Type) (GenericTakeSym0 i6989586621679873426 a6989586621679873427) l Source # 
type Apply i6989586621679873426 (TyFun [a6989586621679873427] [a6989586621679873427] -> Type) (GenericTakeSym0 i6989586621679873426 a6989586621679873427) l = GenericTakeSym1 i6989586621679873426 a6989586621679873427 l

data GenericTakeSym1 (l :: i6989586621679873426) (l :: TyFun [a6989586621679873427] [a6989586621679873427]) Source #

Instances

SuppressUnusedWarnings (i6989586621679873426 -> TyFun [a6989586621679873427] [a6989586621679873427] -> *) (GenericTakeSym1 i6989586621679873426 a6989586621679873427) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym1 i6989586621679873426 a6989586621679873427) t -> () Source #

type Apply [a] [a] (GenericTakeSym1 i a l1) l2 Source # 
type Apply [a] [a] (GenericTakeSym1 i a l1) l2 = GenericTake i a l1 l2

type GenericTakeSym2 (t :: i6989586621679873426) (t :: [a6989586621679873427]) = GenericTake t t Source #

data GenericDropSym0 (l :: TyFun i6989586621679873424 (TyFun [a6989586621679873425] [a6989586621679873425] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun i6989586621679873424 (TyFun [a6989586621679873425] [a6989586621679873425] -> Type) -> *) (GenericDropSym0 i6989586621679873424 a6989586621679873425) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym0 i6989586621679873424 a6989586621679873425) t -> () Source #

type Apply i6989586621679873424 (TyFun [a6989586621679873425] [a6989586621679873425] -> Type) (GenericDropSym0 i6989586621679873424 a6989586621679873425) l Source # 
type Apply i6989586621679873424 (TyFun [a6989586621679873425] [a6989586621679873425] -> Type) (GenericDropSym0 i6989586621679873424 a6989586621679873425) l = GenericDropSym1 i6989586621679873424 a6989586621679873425 l

data GenericDropSym1 (l :: i6989586621679873424) (l :: TyFun [a6989586621679873425] [a6989586621679873425]) Source #

Instances

SuppressUnusedWarnings (i6989586621679873424 -> TyFun [a6989586621679873425] [a6989586621679873425] -> *) (GenericDropSym1 i6989586621679873424 a6989586621679873425) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym1 i6989586621679873424 a6989586621679873425) t -> () Source #

type Apply [a] [a] (GenericDropSym1 i a l1) l2 Source # 
type Apply [a] [a] (GenericDropSym1 i a l1) l2 = GenericDrop i a l1 l2

type GenericDropSym2 (t :: i6989586621679873424) (t :: [a6989586621679873425]) = GenericDrop t t Source #

data GenericSplitAtSym0 (l :: TyFun i6989586621679873422 (TyFun [a6989586621679873423] ([a6989586621679873423], [a6989586621679873423]) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun i6989586621679873422 (TyFun [a6989586621679873423] ([a6989586621679873423], [a6989586621679873423]) -> Type) -> *) (GenericSplitAtSym0 i6989586621679873422 a6989586621679873423) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym0 i6989586621679873422 a6989586621679873423) t -> () Source #

type Apply i6989586621679873422 (TyFun [a6989586621679873423] ([a6989586621679873423], [a6989586621679873423]) -> Type) (GenericSplitAtSym0 i6989586621679873422 a6989586621679873423) l Source # 
type Apply i6989586621679873422 (TyFun [a6989586621679873423] ([a6989586621679873423], [a6989586621679873423]) -> Type) (GenericSplitAtSym0 i6989586621679873422 a6989586621679873423) l = GenericSplitAtSym1 i6989586621679873422 a6989586621679873423 l

data GenericSplitAtSym1 (l :: i6989586621679873422) (l :: TyFun [a6989586621679873423] ([a6989586621679873423], [a6989586621679873423])) Source #

Instances

SuppressUnusedWarnings (i6989586621679873422 -> TyFun [a6989586621679873423] ([a6989586621679873423], [a6989586621679873423]) -> *) (GenericSplitAtSym1 i6989586621679873422 a6989586621679873423) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym1 i6989586621679873422 a6989586621679873423) t -> () Source #

type Apply [a] ([a], [a]) (GenericSplitAtSym1 i a l1) l2 Source # 
type Apply [a] ([a], [a]) (GenericSplitAtSym1 i a l1) l2 = GenericSplitAt i a l1 l2

type GenericSplitAtSym2 (t :: i6989586621679873422) (t :: [a6989586621679873423]) = GenericSplitAt t t Source #

data GenericIndexSym0 (l :: TyFun [a6989586621679873421] (TyFun i6989586621679873420 a6989586621679873421 -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679873421] (TyFun i6989586621679873420 a6989586621679873421 -> Type) -> *) (GenericIndexSym0 i6989586621679873420 a6989586621679873421) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym0 i6989586621679873420 a6989586621679873421) t -> () Source #

type Apply [a6989586621679873421] (TyFun i6989586621679873420 a6989586621679873421 -> Type) (GenericIndexSym0 i6989586621679873420 a6989586621679873421) l Source # 
type Apply [a6989586621679873421] (TyFun i6989586621679873420 a6989586621679873421 -> Type) (GenericIndexSym0 i6989586621679873420 a6989586621679873421) l = GenericIndexSym1 i6989586621679873420 a6989586621679873421 l

data GenericIndexSym1 (l :: [a6989586621679873421]) (l :: TyFun i6989586621679873420 a6989586621679873421) Source #

Instances

SuppressUnusedWarnings ([a6989586621679873421] -> TyFun i6989586621679873420 a6989586621679873421 -> *) (GenericIndexSym1 i6989586621679873420 a6989586621679873421) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym1 i6989586621679873420 a6989586621679873421) t -> () Source #

type Apply i a (GenericIndexSym1 i a l1) l2 Source # 
type Apply i a (GenericIndexSym1 i a l1) l2 = GenericIndex i a l1 l2

type GenericIndexSym2 (t :: [a6989586621679873421]) (t :: i6989586621679873420) = GenericIndex t t Source #

data GenericReplicateSym0 (l :: TyFun i6989586621679873418 (TyFun a6989586621679873419 [a6989586621679873419] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun i6989586621679873418 (TyFun a6989586621679873419 [a6989586621679873419] -> Type) -> *) (GenericReplicateSym0 i6989586621679873418 a6989586621679873419) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym0 i6989586621679873418 a6989586621679873419) t -> () Source #

type Apply i6989586621679873418 (TyFun a6989586621679873419 [a6989586621679873419] -> Type) (GenericReplicateSym0 i6989586621679873418 a6989586621679873419) l Source # 
type Apply i6989586621679873418 (TyFun a6989586621679873419 [a6989586621679873419] -> Type) (GenericReplicateSym0 i6989586621679873418 a6989586621679873419) l = GenericReplicateSym1 i6989586621679873418 a6989586621679873419 l

data GenericReplicateSym1 (l :: i6989586621679873418) (l :: TyFun a6989586621679873419 [a6989586621679873419]) Source #

Instances

SuppressUnusedWarnings (i6989586621679873418 -> TyFun a6989586621679873419 [a6989586621679873419] -> *) (GenericReplicateSym1 i6989586621679873418 a6989586621679873419) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym1 i6989586621679873418 a6989586621679873419) t -> () Source #

type Apply a [a] (GenericReplicateSym1 i a l1) l2 Source # 
type Apply a [a] (GenericReplicateSym1 i a l1) l2 = GenericReplicate i a l1 l2

type GenericReplicateSym2 (t :: i6989586621679873418) (t :: a6989586621679873419) = GenericReplicate t t Source #