singletons-2.3.1: 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_6989586621679462140) = 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_6989586621679462130 ((:) x xs)) = Apply LastSym0 (Apply (Apply (:$) x) xs) 

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

Equations

Tail ((:) _z_6989586621679462121 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 (Let6989586621679462090Init'Sym2 x xs) x) xs 

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

Equations

Null '[] = TrueSym0 
Null ((:) _z_6989586621679462019 _z_6989586621679462022) = FalseSym0 

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

Equations

Length '[] = FromInteger 0 
Length ((:) _z_6989586621679458940 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_6989586621679281208 '[] = '[] 
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 (Let6989586621679461985RevSym1 l) l) '[] 

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

Equations

Intersperse _z_6989586621679461963 '[] = '[] 
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 (Let6989586621679461538PermsSym1 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 (Let6989586621679242274LgoSym3 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 (Let6989586621679461452LgoSym3 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_6989586621679461229 '[] = 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_6989586621679461530 '[] = 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_6989586621679281229 = Apply (Let6989586621679281234GoSym3 k z a_6989586621679281229) a_6989586621679281229 

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

Equations

Foldr1 _z_6989586621679461187 '[x] = x 
Foldr1 f ((:) x ((:) wild_6989586621679458644 wild_6989586621679458646)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let6989586621679461195XsSym4 f x wild_6989586621679458644 wild_6989586621679458646)) 
Foldr1 _z_6989586621679461214 '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" 

Special folds

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

Equations

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

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

Equations

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

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_6989586621679447974 '[] = 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_6989586621679461140 '[] = 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 (Let6989586621679458973Sum'Sym1 l) l) (FromInteger 0) 

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

Equations

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

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

Equations

Maximum '[] = Apply ErrorSym0 "Data.Singletons.List.maximum: empty list" 
Maximum ((:) wild_6989586621679458724 wild_6989586621679458726) = Apply (Apply Foldl1Sym0 MaxSym0) (Let6989586621679461412XsSym2 wild_6989586621679458724 wild_6989586621679458726) 

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

Equations

Minimum '[] = Apply ErrorSym0 "Data.Singletons.List.minimum: empty list" 
Minimum ((:) wild_6989586621679458728 wild_6989586621679458730) = Apply (Apply Foldl1Sym0 MinSym0) (Let6989586621679461426XsSym2 wild_6989586621679458728 wild_6989586621679458730) 

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_6989586621679461111 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_6989586621679461128 '[] = '[] 

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

Equations

Scanr _z_6989586621679461061 q0 '[] = Apply (Apply (:$) q0) '[] 
Scanr f q0 ((:) x xs) = Case_6989586621679461088 f q0 x xs (Let6989586621679461069Scrutinee_6989586621679458648Sym4 f q0 x xs) 

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

Equations

Scanr1 _z_6989586621679460992 '[] = '[] 
Scanr1 _z_6989586621679460995 '[x] = Apply (Apply (:$) x) '[] 
Scanr1 f ((:) x ((:) wild_6989586621679458652 wild_6989586621679458654)) = Case_6989586621679461041 f x wild_6989586621679458652 wild_6989586621679458654 (Let6989586621679461022Scrutinee_6989586621679458650Sym4 f x wild_6989586621679458652 wild_6989586621679458654) 

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_6989586621679460826 s '[] = Apply (Apply Tuple2Sym0 s) '[] 
MapAccumL f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let6989586621679460834S''Sym4 f s x xs)) (Apply (Apply (:$) (Let6989586621679460834YSym4 f s x xs)) (Let6989586621679460834YsSym4 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_6989586621679460654 s '[] = Apply (Apply Tuple2Sym0 s) '[] 
MapAccumR f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let6989586621679460662S''Sym4 f s x xs)) (Apply (Apply (:$) (Let6989586621679460662YSym4 f s x xs)) (Let6989586621679460662YsSym4 f s x xs)) 

Infinite lists

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

Equations

Replicate n x = Case_6989586621679458933 n x (Let6989586621679458925Scrutinee_6989586621679458736Sym2 n x) 

Unfolding

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

Equations

Unfoldr f b = Case_6989586621679460634 f b (Let6989586621679460626Scrutinee_6989586621679458656Sym2 f b) 

Sublists

Extracting sublists

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

Equations

Take _z_6989586621679459120 '[] = '[] 
Take n ((:) x xs) = Case_6989586621679459139 n x xs (Let6989586621679459126Scrutinee_6989586621679458720Sym3 n x xs) 

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

Equations

Drop _z_6989586621679459089 '[] = '[] 
Drop n ((:) x xs) = Case_6989586621679459108 n x xs (Let6989586621679459095Scrutinee_6989586621679458722Sym3 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_6989586621679459487 '[] = '[] 
TakeWhile p ((:) x xs) = Case_6989586621679459506 p x xs (Let6989586621679459493Scrutinee_6989586621679458710Sym3 p x xs) 

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

Equations

DropWhile _z_6989586621679459443 '[] = '[] 
DropWhile p ((:) x xs') = Case_6989586621679459475 p x xs' (Let6989586621679459462Scrutinee_6989586621679458712Sym3 p x xs') 

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

Equations

DropWhileEnd p a_6989586621679462034 = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_6989586621679462038Sym0 p) a_6989586621679462034)) '[]) a_6989586621679462034 

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

Equations

Span _z_6989586621679459264 '[] = Apply (Apply Tuple2Sym0 Let6989586621679459267XsSym0) Let6989586621679459267XsSym0 
Span p ((:) x xs') = Case_6989586621679459297 p x xs' (Let6989586621679459284Scrutinee_6989586621679458716Sym3 p x xs') 

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

Equations

Break _z_6989586621679459162 '[] = Apply (Apply Tuple2Sym0 Let6989586621679459165XsSym0) Let6989586621679459165XsSym0 
Break p ((:) x xs') = Case_6989586621679459195 p x xs' (Let6989586621679459182Scrutinee_6989586621679458718Sym3 p x xs') 

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

Equations

StripPrefix '[] ys = Apply JustSym0 ys 
StripPrefix arg_6989586621679876777 arg_6989586621679876779 = Case_6989586621679877388 arg_6989586621679876777 arg_6989586621679876779 (Apply (Apply Tuple2Sym0 arg_6989586621679876777) arg_6989586621679876779) 

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

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

Equations

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

Predicates

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

Equations

IsPrefixOf '[] '[] = TrueSym0 
IsPrefixOf '[] ((:) _z_6989586621679460566 _z_6989586621679460569) = TrueSym0 
IsPrefixOf ((:) _z_6989586621679460572 _z_6989586621679460575) '[] = 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_6989586621679460503 '[] = 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_6989586621679460488 '[] = 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_6989586621679459077 key x y xys (Let6989586621679459058Scrutinee_6989586621679458732Sym4 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_6989586621679459547 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FilterSym0 p)) a_6989586621679459547 

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

Equations

Filter _p '[] = '[] 
Filter p ((:) x xs) = Case_6989586621679459535 p x xs (Let6989586621679459522Scrutinee_6989586621679458698Sym3 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_6989586621679458892 = Apply ErrorSym0 "Data.Singletons.List.!!: index too large" 
((:) x xs) :!! n = Case_6989586621679458911 x xs n (Let6989586621679458898Scrutinee_6989586621679458738Sym3 x xs n) 

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

Equations

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

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

Equations

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

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

Equations

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

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_6989586621679460417Sym0 p) xs)) (Apply (Apply ZipSym0 xs) (Apply (Apply (Let6989586621679460388BuildListSym2 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_6989586621679460365 _z_6989586621679460368) '[] = '[] 
Zip '[] ((:) _z_6989586621679460371 _z_6989586621679460374) = '[] 

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_6989586621679460298 _z_6989586621679460301) = '[] 
Zip3 '[] ((:) _z_6989586621679460304 _z_6989586621679460307) '[] = '[] 
Zip3 '[] ((:) _z_6989586621679460310 _z_6989586621679460313) ((:) _z_6989586621679460316 _z_6989586621679460319) = '[] 
Zip3 ((:) _z_6989586621679460322 _z_6989586621679460325) '[] '[] = '[] 
Zip3 ((:) _z_6989586621679460328 _z_6989586621679460331) '[] ((:) _z_6989586621679460334 _z_6989586621679460337) = '[] 
Zip3 ((:) _z_6989586621679460340 _z_6989586621679460343) ((:) _z_6989586621679460346 _z_6989586621679460349) '[] = '[] 

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

Equations

Zip4 a_6989586621679877342 a_6989586621679877344 a_6989586621679877346 a_6989586621679877348 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621679877342) a_6989586621679877344) a_6989586621679877346) a_6989586621679877348 

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

Equations

Zip5 a_6989586621679877297 a_6989586621679877299 a_6989586621679877301 a_6989586621679877303 a_6989586621679877305 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621679877297) a_6989586621679877299) a_6989586621679877301) a_6989586621679877303) a_6989586621679877305 

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_6989586621679877240 a_6989586621679877242 a_6989586621679877244 a_6989586621679877246 a_6989586621679877248 a_6989586621679877250 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621679877240) a_6989586621679877242) a_6989586621679877244) a_6989586621679877246) a_6989586621679877248) a_6989586621679877250 

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_6989586621679877170 a_6989586621679877172 a_6989586621679877174 a_6989586621679877176 a_6989586621679877178 a_6989586621679877180 a_6989586621679877182 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621679877170) a_6989586621679877172) a_6989586621679877174) a_6989586621679877176) a_6989586621679877178) a_6989586621679877180) a_6989586621679877182 

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_6989586621679460256 '[] '[] = '[] 
ZipWith _z_6989586621679460259 ((:) _z_6989586621679460262 _z_6989586621679460265) '[] = '[] 
ZipWith _z_6989586621679460268 '[] ((:) _z_6989586621679460271 _z_6989586621679460274) = '[] 

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_6989586621679460161 '[] '[] '[] = '[] 
ZipWith3 _z_6989586621679460164 '[] '[] ((:) _z_6989586621679460167 _z_6989586621679460170) = '[] 
ZipWith3 _z_6989586621679460173 '[] ((:) _z_6989586621679460176 _z_6989586621679460179) '[] = '[] 
ZipWith3 _z_6989586621679460182 '[] ((:) _z_6989586621679460185 _z_6989586621679460188) ((:) _z_6989586621679460191 _z_6989586621679460194) = '[] 
ZipWith3 _z_6989586621679460197 ((:) _z_6989586621679460200 _z_6989586621679460203) '[] '[] = '[] 
ZipWith3 _z_6989586621679460206 ((:) _z_6989586621679460209 _z_6989586621679460212) '[] ((:) _z_6989586621679460215 _z_6989586621679460218) = '[] 
ZipWith3 _z_6989586621679460221 ((:) _z_6989586621679460224 _z_6989586621679460227) ((:) _z_6989586621679460230 _z_6989586621679460233) '[] = '[] 

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_6989586621679877155 _z_6989586621679877158 _z_6989586621679877161 _z_6989586621679877164 _z_6989586621679877167 = '[] 

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_6989586621679877098 _z_6989586621679877101 _z_6989586621679877104 _z_6989586621679877107 _z_6989586621679877110 _z_6989586621679877113 = '[] 

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_6989586621679877027 _z_6989586621679877030 _z_6989586621679877033 _z_6989586621679877036 _z_6989586621679877039 _z_6989586621679877042 _z_6989586621679877045 = '[] 

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_6989586621679876941 _z_6989586621679876944 _z_6989586621679876947 _z_6989586621679876950 _z_6989586621679876953 _z_6989586621679876956 _z_6989586621679876959 _z_6989586621679876962 = '[] 

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

Equations

Unzip xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679460107Sym0 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_6989586621679460075Sym0 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_6989586621679460041Sym0 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_6989586621679460005Sym0 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_6989586621679459967Sym0 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_6989586621679459927Sym0 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 (Let6989586621679460514Nub'Sym1 l) l) '[] 

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

Equations

Delete a_6989586621679459892 a_6989586621679459894 = Apply (Apply (Apply DeleteBySym0 (:==$)) a_6989586621679459892) a_6989586621679459894 

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

Equations

a_6989586621679459907 :\\ a_6989586621679459909 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 DeleteSym0)) a_6989586621679459907) a_6989586621679459909 

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

Equations

Union a_6989586621679459877 a_6989586621679459879 = Apply (Apply (Apply UnionBySym0 (:==$)) a_6989586621679459877) a_6989586621679459879 

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

Equations

Intersect a_6989586621679459680 a_6989586621679459682 = Apply (Apply (Apply IntersectBySym0 (:==$)) a_6989586621679459680) a_6989586621679459682 

Ordered lists

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

Equations

Sort a_6989586621679459783 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679459783 

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 (Let6989586621679458827NubBy'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_6989586621679459805 _z_6989586621679459808 '[] = '[] 
DeleteBy eq x ((:) y ys) = Case_6989586621679459834 eq x y ys (Let6989586621679459815Scrutinee_6989586621679458682Sym4 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_6989586621679459852 a_6989586621679459854 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679459852) a_6989586621679459854 

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_6989586621679459366 '[] = '[] 
GroupBy eq ((:) x xs) = Apply (Apply (:$) (Apply (Apply (:$) x) (Let6989586621679459372YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621679459372ZsSym3 eq x xs)) 

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

Equations

IntersectBy _z_6989586621679459566 '[] '[] = '[] 
IntersectBy _z_6989586621679459569 '[] ((:) _z_6989586621679459572 _z_6989586621679459575) = '[] 
IntersectBy _z_6989586621679459578 ((:) _z_6989586621679459581 _z_6989586621679459584) '[] = '[] 
IntersectBy eq ((:) wild_6989586621679458702 wild_6989586621679458704) ((:) wild_6989586621679458706 wild_6989586621679458708) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679459643Sym0 eq) wild_6989586621679458702) wild_6989586621679458704) wild_6989586621679458706) wild_6989586621679458708)) (Let6989586621679459592XsSym5 eq wild_6989586621679458702 wild_6989586621679458704 wild_6989586621679458706 wild_6989586621679458708) 

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_6989586621679459779 = Apply (Apply (Apply FoldrSym0 (Apply InsertBySym0 cmp)) '[]) a_6989586621679459779 

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

Equations

InsertBy _z_6989586621679459710 x '[] = Apply (Apply (:$) x) '[] 
InsertBy cmp x ((:) y ys') = Case_6989586621679459756 cmp x y ys' (Let6989586621679459737Scrutinee_6989586621679458684Sym4 cmp x y ys') 

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

Equations

MaximumBy _z_6989586621679461241 '[] = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" 
MaximumBy cmp ((:) wild_6989586621679458688 wild_6989586621679458690) = Apply (Apply Foldl1Sym0 (Let6989586621679461260MaxBySym3 cmp wild_6989586621679458688 wild_6989586621679458690)) (Let6989586621679461247XsSym3 cmp wild_6989586621679458688 wild_6989586621679458690) 

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

Equations

MinimumBy _z_6989586621679461328 '[] = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" 
MinimumBy cmp ((:) wild_6989586621679458694 wild_6989586621679458696) = Apply (Apply Foldl1Sym0 (Let6989586621679461347MinBySym3 cmp wild_6989586621679458694 wild_6989586621679458696)) (Let6989586621679461334XsSym3 cmp wild_6989586621679458694 wild_6989586621679458696) 

The "generic" operations

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

Equations

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

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

Equations

GenericTake a_6989586621679876851 a_6989586621679876853 = Apply (Apply TakeSym0 a_6989586621679876851) a_6989586621679876853 

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

Equations

GenericDrop a_6989586621679876836 a_6989586621679876838 = Apply (Apply DropSym0 a_6989586621679876836) a_6989586621679876838 

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

Equations

GenericSplitAt a_6989586621679876821 a_6989586621679876823 = Apply (Apply SplitAtSym0 a_6989586621679876821) a_6989586621679876823 

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

Equations

GenericIndex a_6989586621679876806 a_6989586621679876808 = Apply (Apply (:!!$) a_6989586621679876806) a_6989586621679876808 

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

Equations

GenericReplicate a_6989586621679876791 a_6989586621679876793 = Apply (Apply ReplicateSym0 a_6989586621679876791) a_6989586621679876793 

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 :: [a6989586621679281045]) (t :: [a6989586621679281045]) = (:++) t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

data MapSym0 (l :: TyFun (TyFun a6989586621679281046 b6989586621679281047 -> Type) (TyFun [a6989586621679281046] [b6989586621679281047] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679281046 b6989586621679281047 -> Type) (TyFun [a6989586621679281046] [b6989586621679281047] -> Type) -> *) (MapSym0 a6989586621679281046 b6989586621679281047) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a6989586621679281046 b6989586621679281047) t -> () Source #

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

data MapSym1 (l :: TyFun a6989586621679281046 b6989586621679281047 -> Type) (l :: TyFun [a6989586621679281046] [b6989586621679281047]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679281046 b6989586621679281047 -> Type) -> TyFun [a6989586621679281046] [b6989586621679281047] -> *) (MapSym1 a6989586621679281046 b6989586621679281047) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a6989586621679281046 b6989586621679281047) 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 a6989586621679281046 b6989586621679281047 -> Type) (t :: [a6989586621679281046]) = Map t t Source #

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym1 a6989586621679458190) 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 :: a6989586621679458190) (t :: [a6989586621679458190]) = Intersperse t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (IntercalateSym1 a6989586621679458189) 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 :: [a6989586621679458189]) (t :: [[a6989586621679458189]]) = Intercalate t t Source #

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (FoldlSym2 a6989586621679242245 b6989586621679242246) 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 b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (t :: b6989586621679242246) (t :: [a6989586621679242245]) = Foldl t t t Source #

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

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (TyFun b6989586621679458184 (TyFun [a6989586621679458183] b6989586621679458184 -> Type) -> Type) -> *) (Foldl'Sym0 a6989586621679458183 b6989586621679458184) Source # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym0 a6989586621679458183 b6989586621679458184) t -> () Source #

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

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

Instances

SuppressUnusedWarnings ((TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) -> TyFun b6989586621679458184 (TyFun [a6989586621679458183] b6989586621679458184 -> Type) -> *) (Foldl'Sym1 a6989586621679458183 b6989586621679458184) Source # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym1 a6989586621679458183 b6989586621679458184) t -> () Source #

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

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

Instances

SuppressUnusedWarnings ((TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) -> b6989586621679458184 -> TyFun [a6989586621679458183] b6989586621679458184 -> *) (Foldl'Sym2 a6989586621679458183 b6989586621679458184) Source # 

Methods

suppressUnusedWarnings :: Proxy (Foldl'Sym2 a6989586621679458183 b6989586621679458184) t -> () Source #

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 b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (t :: b6989586621679458184) (t :: [a6989586621679458183]) = Foldl' t t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Foldl1Sym1 a6989586621679458182) 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 a6989586621679458182 (TyFun a6989586621679458182 a6989586621679458182 -> Type) -> Type) (t :: [a6989586621679458182]) = Foldl1 t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Foldl1'Sym1 a6989586621679458181) 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 a6989586621679458181 (TyFun a6989586621679458181 a6989586621679458181 -> Type) -> Type) (t :: [a6989586621679458181]) = Foldl1' t t Source #

data FoldrSym0 (l :: TyFun (TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type) -> Type) -> *) (FoldrSym0 a6989586621679281048 b6989586621679281049) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym0 a6989586621679281048 b6989586621679281049) t -> () Source #

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

data FoldrSym1 (l :: TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (l :: TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) -> TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type) -> *) (FoldrSym1 a6989586621679281048 b6989586621679281049) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym1 a6989586621679281048 b6989586621679281049) t -> () Source #

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

data FoldrSym2 (l :: TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (l :: b6989586621679281049) (l :: TyFun [a6989586621679281048] b6989586621679281049) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) -> b6989586621679281049 -> TyFun [a6989586621679281048] b6989586621679281049 -> *) (FoldrSym2 a6989586621679281048 b6989586621679281049) Source # 

Methods

suppressUnusedWarnings :: Proxy (FoldrSym2 a6989586621679281048 b6989586621679281049) 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 a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (t :: b6989586621679281049) (t :: [a6989586621679281048]) = Foldr t t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Foldr1Sym1 a6989586621679458180) 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 a6989586621679458180 (TyFun a6989586621679458180 a6989586621679458180 -> Type) -> Type) (t :: [a6989586621679458180]) = Foldr1 t t Source #

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

Instances

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

Methods

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

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

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

data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679458177 [b6989586621679458178] -> Type) (TyFun [a6989586621679458177] [b6989586621679458178] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679458177 [b6989586621679458178] -> Type) (TyFun [a6989586621679458177] [b6989586621679458178] -> Type) -> *) (ConcatMapSym0 a6989586621679458177 b6989586621679458178) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym0 a6989586621679458177 b6989586621679458178) t -> () Source #

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

data ConcatMapSym1 (l :: TyFun a6989586621679458177 [b6989586621679458178] -> Type) (l :: TyFun [a6989586621679458177] [b6989586621679458178]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679458177 [b6989586621679458178] -> Type) -> TyFun [a6989586621679458177] [b6989586621679458178] -> *) (ConcatMapSym1 a6989586621679458177 b6989586621679458178) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConcatMapSym1 a6989586621679458177 b6989586621679458178) 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 a6989586621679458177 [b6989586621679458178] -> Type) (t :: [a6989586621679458177]) = ConcatMap t t Source #

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Any_Sym1 a6989586621679447960) 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 a6989586621679447960 Bool -> Type) (t :: [a6989586621679447960]) = Any_ t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (AllSym1 a6989586621679458176) 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 a6989586621679458176 Bool -> Type) (t :: [a6989586621679458176]) = All t t Source #

data ScanlSym0 (l :: TyFun (TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type) -> Type) -> *) (ScanlSym0 a6989586621679458175 b6989586621679458174) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a6989586621679458175 b6989586621679458174) t -> () Source #

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

data ScanlSym1 (l :: TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (l :: TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) -> TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type) -> *) (ScanlSym1 a6989586621679458175 b6989586621679458174) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a6989586621679458175 b6989586621679458174) t -> () Source #

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

data ScanlSym2 (l :: TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (l :: b6989586621679458174) (l :: TyFun [a6989586621679458175] [b6989586621679458174]) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) -> b6989586621679458174 -> TyFun [a6989586621679458175] [b6989586621679458174] -> *) (ScanlSym2 a6989586621679458175 b6989586621679458174) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a6989586621679458175 b6989586621679458174) 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 b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (t :: b6989586621679458174) (t :: [a6989586621679458175]) = Scanl t t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Scanl1Sym1 a6989586621679458173) 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 a6989586621679458173 (TyFun a6989586621679458173 a6989586621679458173 -> Type) -> Type) (t :: [a6989586621679458173]) = Scanl1 t t Source #

data ScanrSym0 (l :: TyFun (TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type) -> Type) -> *) (ScanrSym0 a6989586621679458171 b6989586621679458172) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a6989586621679458171 b6989586621679458172) t -> () Source #

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

data ScanrSym1 (l :: TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (l :: TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) -> TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type) -> *) (ScanrSym1 a6989586621679458171 b6989586621679458172) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a6989586621679458171 b6989586621679458172) t -> () Source #

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

data ScanrSym2 (l :: TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (l :: b6989586621679458172) (l :: TyFun [a6989586621679458171] [b6989586621679458172]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) -> b6989586621679458172 -> TyFun [a6989586621679458171] [b6989586621679458172] -> *) (ScanrSym2 a6989586621679458171 b6989586621679458172) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a6989586621679458171 b6989586621679458172) 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 a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (t :: b6989586621679458172) (t :: [a6989586621679458171]) = Scanr t t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Scanr1Sym1 a6989586621679458170) 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 a6989586621679458170 (TyFun a6989586621679458170 a6989586621679458170 -> Type) -> Type) (t :: [a6989586621679458170]) = Scanr1 t t Source #

data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) -> Type) -> *) (MapAccumLSym0 x6989586621679458168 acc6989586621679458167 y6989586621679458169) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym0 x6989586621679458168 acc6989586621679458167 y6989586621679458169) t -> () Source #

type Apply (TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) -> Type) (MapAccumLSym0 x6989586621679458168 acc6989586621679458167 y6989586621679458169) l Source # 
type Apply (TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) -> Type) (MapAccumLSym0 x6989586621679458168 acc6989586621679458167 y6989586621679458169) l = MapAccumLSym1 x6989586621679458168 acc6989586621679458167 y6989586621679458169 l

data MapAccumLSym1 (l :: TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (l :: TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) -> TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) -> *) (MapAccumLSym1 x6989586621679458168 acc6989586621679458167 y6989586621679458169) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym1 x6989586621679458168 acc6989586621679458167 y6989586621679458169) t -> () Source #

type Apply acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) (MapAccumLSym1 x6989586621679458168 acc6989586621679458167 y6989586621679458169 l1) l2 Source # 
type Apply acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) (MapAccumLSym1 x6989586621679458168 acc6989586621679458167 y6989586621679458169 l1) l2 = MapAccumLSym2 x6989586621679458168 acc6989586621679458167 y6989586621679458169 l1 l2

data MapAccumLSym2 (l :: TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (l :: acc6989586621679458167) (l :: TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169])) Source #

Instances

SuppressUnusedWarnings ((TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) -> acc6989586621679458167 -> TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> *) (MapAccumLSym2 x6989586621679458168 acc6989586621679458167 y6989586621679458169) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumLSym2 x6989586621679458168 acc6989586621679458167 y6989586621679458169) t -> () Source #

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 acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (t :: acc6989586621679458167) (t :: [x6989586621679458168]) = MapAccumL t t t Source #

data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) -> Type) -> *) (MapAccumRSym0 x6989586621679458165 acc6989586621679458164 y6989586621679458166) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym0 x6989586621679458165 acc6989586621679458164 y6989586621679458166) t -> () Source #

type Apply (TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) -> Type) (MapAccumRSym0 x6989586621679458165 acc6989586621679458164 y6989586621679458166) l Source # 
type Apply (TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) -> Type) (MapAccumRSym0 x6989586621679458165 acc6989586621679458164 y6989586621679458166) l = MapAccumRSym1 x6989586621679458165 acc6989586621679458164 y6989586621679458166 l

data MapAccumRSym1 (l :: TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (l :: TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) -> TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) -> *) (MapAccumRSym1 x6989586621679458165 acc6989586621679458164 y6989586621679458166) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym1 x6989586621679458165 acc6989586621679458164 y6989586621679458166) t -> () Source #

type Apply acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) (MapAccumRSym1 x6989586621679458165 acc6989586621679458164 y6989586621679458166 l1) l2 Source # 
type Apply acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) (MapAccumRSym1 x6989586621679458165 acc6989586621679458164 y6989586621679458166 l1) l2 = MapAccumRSym2 x6989586621679458165 acc6989586621679458164 y6989586621679458166 l1 l2

data MapAccumRSym2 (l :: TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (l :: acc6989586621679458164) (l :: TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166])) Source #

Instances

SuppressUnusedWarnings ((TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) -> acc6989586621679458164 -> TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> *) (MapAccumRSym2 x6989586621679458165 acc6989586621679458164 y6989586621679458166) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapAccumRSym2 x6989586621679458165 acc6989586621679458164 y6989586621679458166) t -> () Source #

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 acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (t :: acc6989586621679458164) (t :: [x6989586621679458165]) = MapAccumR t t t Source #

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

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) (TyFun b6989586621679458162 [a6989586621679458163] -> Type) -> *) (UnfoldrSym0 b6989586621679458162 a6989586621679458163) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 b6989586621679458162 a6989586621679458163) t -> () Source #

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

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

Instances

SuppressUnusedWarnings ((TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) -> TyFun b6989586621679458162 [a6989586621679458163] -> *) (UnfoldrSym1 b6989586621679458162 a6989586621679458163) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 b6989586621679458162 a6989586621679458163) 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 b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) (t :: b6989586621679458162) = Unfoldr t t Source #

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (IsPrefixOfSym1 a6989586621679458159) 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 :: [a6989586621679458159]) (t :: [a6989586621679458159]) = IsPrefixOf t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (IsSuffixOfSym1 a6989586621679458158) 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 :: [a6989586621679458158]) (t :: [a6989586621679458158]) = IsSuffixOf t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (IsInfixOfSym1 a6989586621679458157) 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 :: [a6989586621679458157]) (t :: [a6989586621679458157]) = IsInfixOf t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (ElemSym1 a6989586621679458156) 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 :: a6989586621679458156) (t :: [a6989586621679458156]) = Elem t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (NotElemSym1 a6989586621679458155) 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 :: a6989586621679458155) (t :: [a6989586621679458155]) = NotElem t t Source #

data ZipSym0 (l :: TyFun [a6989586621679458153] (TyFun [b6989586621679458154] [(a6989586621679458153, b6989586621679458154)] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679458153] (TyFun [b6989586621679458154] [(a6989586621679458153, b6989586621679458154)] -> Type) -> *) (ZipSym0 a6989586621679458153 b6989586621679458154) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a6989586621679458153 b6989586621679458154) t -> () Source #

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

data ZipSym1 (l :: [a6989586621679458153]) (l :: TyFun [b6989586621679458154] [(a6989586621679458153, b6989586621679458154)]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679458153] -> TyFun [b6989586621679458154] [(a6989586621679458153, b6989586621679458154)] -> *) (ZipSym1 a6989586621679458153 b6989586621679458154) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 a6989586621679458153 b6989586621679458154) 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 :: [a6989586621679458153]) (t :: [b6989586621679458154]) = Zip t t Source #

data Zip3Sym0 (l :: TyFun [a6989586621679458150] (TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679458150] (TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) -> Type) -> *) (Zip3Sym0 a6989586621679458150 b6989586621679458151 c6989586621679458152) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym0 a6989586621679458150 b6989586621679458151 c6989586621679458152) t -> () Source #

type Apply [a6989586621679458150] (TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) -> Type) (Zip3Sym0 a6989586621679458150 b6989586621679458151 c6989586621679458152) l Source # 
type Apply [a6989586621679458150] (TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) -> Type) (Zip3Sym0 a6989586621679458150 b6989586621679458151 c6989586621679458152) l = Zip3Sym1 a6989586621679458150 b6989586621679458151 c6989586621679458152 l

data Zip3Sym1 (l :: [a6989586621679458150]) (l :: TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679458150] -> TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) -> *) (Zip3Sym1 a6989586621679458150 b6989586621679458151 c6989586621679458152) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym1 a6989586621679458150 b6989586621679458151 c6989586621679458152) t -> () Source #

type Apply [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) (Zip3Sym1 a6989586621679458150 b6989586621679458151 c6989586621679458152 l1) l2 Source # 
type Apply [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) (Zip3Sym1 a6989586621679458150 b6989586621679458151 c6989586621679458152 l1) l2 = Zip3Sym2 a6989586621679458150 b6989586621679458151 c6989586621679458152 l1 l2

data Zip3Sym2 (l :: [a6989586621679458150]) (l :: [b6989586621679458151]) (l :: TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679458150] -> [b6989586621679458151] -> TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> *) (Zip3Sym2 a6989586621679458150 b6989586621679458151 c6989586621679458152) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip3Sym2 a6989586621679458150 b6989586621679458151 c6989586621679458152) 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 :: [a6989586621679458150]) (t :: [b6989586621679458151]) (t :: [c6989586621679458152]) = Zip3 t t t Source #

data ZipWithSym0 (l :: TyFun (TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679458147 b6989586621679458148 c6989586621679458149) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a6989586621679458147 b6989586621679458148 c6989586621679458149) t -> () Source #

type Apply (TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) -> Type) (ZipWithSym0 a6989586621679458147 b6989586621679458148 c6989586621679458149) l Source # 
type Apply (TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) -> Type) (ZipWithSym0 a6989586621679458147 b6989586621679458148 c6989586621679458149) l = ZipWithSym1 a6989586621679458147 b6989586621679458148 c6989586621679458149 l

data ZipWithSym1 (l :: TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (l :: TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) -> TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) -> *) (ZipWithSym1 a6989586621679458147 b6989586621679458148 c6989586621679458149) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a6989586621679458147 b6989586621679458148 c6989586621679458149) t -> () Source #

type Apply [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) (ZipWithSym1 a6989586621679458147 b6989586621679458148 c6989586621679458149 l1) l2 Source # 
type Apply [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) (ZipWithSym1 a6989586621679458147 b6989586621679458148 c6989586621679458149 l1) l2 = ZipWithSym2 a6989586621679458147 b6989586621679458148 c6989586621679458149 l1 l2

data ZipWithSym2 (l :: TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (l :: [a6989586621679458147]) (l :: TyFun [b6989586621679458148] [c6989586621679458149]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) -> [a6989586621679458147] -> TyFun [b6989586621679458148] [c6989586621679458149] -> *) (ZipWithSym2 a6989586621679458147 b6989586621679458148 c6989586621679458149) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a6989586621679458147 b6989586621679458148 c6989586621679458149) t -> () Source #

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 a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (t :: [a6989586621679458147]) (t :: [b6989586621679458148]) = ZipWith t t t Source #

data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym0 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) t -> () Source #

type Apply (TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) -> Type) (ZipWith3Sym0 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) l Source # 
type Apply (TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) -> Type) (ZipWith3Sym0 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) l = ZipWith3Sym1 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146 l

data ZipWith3Sym1 (l :: TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) -> TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) -> *) (ZipWith3Sym1 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym1 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) t -> () Source #

type Apply [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) (ZipWith3Sym1 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146 l1) l2 Source # 
type Apply [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) (ZipWith3Sym1 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146 l1) l2 = ZipWith3Sym2 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146 l1 l2

data ZipWith3Sym2 (l :: TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (l :: [a6989586621679458143]) (l :: TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) -> [a6989586621679458143] -> TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> *) (ZipWith3Sym2 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym2 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) t -> () Source #

type Apply [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) (ZipWith3Sym2 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146 l1 l2) l3 Source # 
type Apply [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) (ZipWith3Sym2 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146 l1 l2) l3 = ZipWith3Sym3 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146 l1 l2 l3

data ZipWith3Sym3 (l :: TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (l :: [a6989586621679458143]) (l :: [b6989586621679458144]) (l :: TyFun [c6989586621679458145] [d6989586621679458146]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) -> [a6989586621679458143] -> [b6989586621679458144] -> TyFun [c6989586621679458145] [d6989586621679458146] -> *) (ZipWith3Sym3 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith3Sym3 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) t -> () Source #

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 a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (t :: [a6989586621679458143]) (t :: [b6989586621679458144]) (t :: [c6989586621679458145]) = ZipWith3 t t t t Source #

data UnzipSym0 (l :: TyFun [(a6989586621679458141, b6989586621679458142)] ([a6989586621679458141], [b6989586621679458142])) Source #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679458141, b6989586621679458142)] ([a6989586621679458141], [b6989586621679458142]) -> *) (UnzipSym0 a6989586621679458141 b6989586621679458142) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a6989586621679458141 b6989586621679458142) 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 :: [(a6989586621679458141, b6989586621679458142)]) = Unzip t Source #

data Unzip3Sym0 (l :: TyFun [(a6989586621679458138, b6989586621679458139, c6989586621679458140)] ([a6989586621679458138], [b6989586621679458139], [c6989586621679458140])) Source #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679458138, b6989586621679458139, c6989586621679458140)] ([a6989586621679458138], [b6989586621679458139], [c6989586621679458140]) -> *) (Unzip3Sym0 a6989586621679458138 b6989586621679458139 c6989586621679458140) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip3Sym0 a6989586621679458138 b6989586621679458139 c6989586621679458140) 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 :: [(a6989586621679458138, b6989586621679458139, c6989586621679458140)]) = Unzip3 t Source #

data Unzip4Sym0 (l :: TyFun [(a6989586621679458134, b6989586621679458135, c6989586621679458136, d6989586621679458137)] ([a6989586621679458134], [b6989586621679458135], [c6989586621679458136], [d6989586621679458137])) Source #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679458134, b6989586621679458135, c6989586621679458136, d6989586621679458137)] ([a6989586621679458134], [b6989586621679458135], [c6989586621679458136], [d6989586621679458137]) -> *) (Unzip4Sym0 a6989586621679458134 b6989586621679458135 c6989586621679458136 d6989586621679458137) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip4Sym0 a6989586621679458134 b6989586621679458135 c6989586621679458136 d6989586621679458137) t -> () Source #

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 :: [(a6989586621679458134, b6989586621679458135, c6989586621679458136, d6989586621679458137)]) = Unzip4 t Source #

data Unzip5Sym0 (l :: TyFun [(a6989586621679458129, b6989586621679458130, c6989586621679458131, d6989586621679458132, e6989586621679458133)] ([a6989586621679458129], [b6989586621679458130], [c6989586621679458131], [d6989586621679458132], [e6989586621679458133])) Source #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679458129, b6989586621679458130, c6989586621679458131, d6989586621679458132, e6989586621679458133)] ([a6989586621679458129], [b6989586621679458130], [c6989586621679458131], [d6989586621679458132], [e6989586621679458133]) -> *) (Unzip5Sym0 a6989586621679458129 b6989586621679458130 c6989586621679458131 d6989586621679458132 e6989586621679458133) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip5Sym0 a6989586621679458129 b6989586621679458130 c6989586621679458131 d6989586621679458132 e6989586621679458133) t -> () Source #

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 :: [(a6989586621679458129, b6989586621679458130, c6989586621679458131, d6989586621679458132, e6989586621679458133)]) = Unzip5 t Source #

data Unzip6Sym0 (l :: TyFun [(a6989586621679458123, b6989586621679458124, c6989586621679458125, d6989586621679458126, e6989586621679458127, f6989586621679458128)] ([a6989586621679458123], [b6989586621679458124], [c6989586621679458125], [d6989586621679458126], [e6989586621679458127], [f6989586621679458128])) Source #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679458123, b6989586621679458124, c6989586621679458125, d6989586621679458126, e6989586621679458127, f6989586621679458128)] ([a6989586621679458123], [b6989586621679458124], [c6989586621679458125], [d6989586621679458126], [e6989586621679458127], [f6989586621679458128]) -> *) (Unzip6Sym0 a6989586621679458123 b6989586621679458124 c6989586621679458125 d6989586621679458126 e6989586621679458127 f6989586621679458128) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip6Sym0 a6989586621679458123 b6989586621679458124 c6989586621679458125 d6989586621679458126 e6989586621679458127 f6989586621679458128) t -> () Source #

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 :: [(a6989586621679458123, b6989586621679458124, c6989586621679458125, d6989586621679458126, e6989586621679458127, f6989586621679458128)]) = Unzip6 t Source #

data Unzip7Sym0 (l :: TyFun [(a6989586621679458116, b6989586621679458117, c6989586621679458118, d6989586621679458119, e6989586621679458120, f6989586621679458121, g6989586621679458122)] ([a6989586621679458116], [b6989586621679458117], [c6989586621679458118], [d6989586621679458119], [e6989586621679458120], [f6989586621679458121], [g6989586621679458122])) Source #

Instances

SuppressUnusedWarnings (TyFun [(a6989586621679458116, b6989586621679458117, c6989586621679458118, d6989586621679458119, e6989586621679458120, f6989586621679458121, g6989586621679458122)] ([a6989586621679458116], [b6989586621679458117], [c6989586621679458118], [d6989586621679458119], [e6989586621679458120], [f6989586621679458121], [g6989586621679458122]) -> *) (Unzip7Sym0 a6989586621679458116 b6989586621679458117 c6989586621679458118 d6989586621679458119 e6989586621679458120 f6989586621679458121 g6989586621679458122) Source # 

Methods

suppressUnusedWarnings :: Proxy (Unzip7Sym0 a6989586621679458116 b6989586621679458117 c6989586621679458118 d6989586621679458119 e6989586621679458120 f6989586621679458121 g6989586621679458122) t -> () Source #

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 :: [(a6989586621679458116, b6989586621679458117, c6989586621679458118, d6989586621679458119, e6989586621679458120, f6989586621679458121, g6989586621679458122)]) = Unzip7 t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DeleteSym1 a6989586621679458115) 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 :: a6989586621679458115) (t :: [a6989586621679458115]) = Delete t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (IntersectSym1 a6989586621679458101) 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 :: [a6989586621679458101]) (t :: [a6989586621679458101]) = Intersect t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (InsertSym1 a6989586621679458088) 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 :: a6989586621679458088) (t :: [a6989586621679458088]) = Insert t t Source #

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DeleteBySym2 a6989586621679458113) 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 a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) (t :: a6989586621679458113) (t :: [a6989586621679458113]) = DeleteBy t t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DeleteFirstsBySym2 a6989586621679458112) 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 a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) (t :: [a6989586621679458112]) (t :: [a6989586621679458112]) = DeleteFirstsBy t t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (IntersectBySym2 a6989586621679458100) 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 a6989586621679458111 (TyFun a6989586621679458111 Ordering -> Type) -> Type) (TyFun [a6989586621679458111] [a6989586621679458111] -> Type)) Source #

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SortBySym1 a6989586621679458111) 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 a6989586621679458111 (TyFun a6989586621679458111 Ordering -> Type) -> Type) (t :: [a6989586621679458111]) = SortBy t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (InsertBySym2 a6989586621679458110) 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 a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) (t :: a6989586621679458110) (t :: [a6989586621679458110]) = InsertBy t t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (MaximumBySym1 a6989586621679458109) 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 a6989586621679458109 (TyFun a6989586621679458109 Ordering -> Type) -> Type) (t :: [a6989586621679458109]) = MaximumBy t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (MinimumBySym1 a6989586621679458108) 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 a6989586621679458108 (TyFun a6989586621679458108 Ordering -> Type) -> Type) (t :: [a6989586621679458108]) = MinimumBy t t Source #

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (ReplicateSym1 a6989586621679458078) 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 :: a6989586621679458078) = Replicate t t Source #

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (TakeSym1 a6989586621679458094) 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 :: [a6989586621679458094]) = Take t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DropSym1 a6989586621679458093) 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 :: [a6989586621679458093]) = Drop t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym1 a6989586621679458092) 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 :: [a6989586621679458092]) = SplitAt t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (TakeWhileSym1 a6989586621679458099) 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 a6989586621679458099 Bool -> Type) (t :: [a6989586621679458099]) = TakeWhile t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DropWhileSym1 a6989586621679458098) 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 a6989586621679458098 Bool -> Type) (t :: [a6989586621679458098]) = DropWhile t t Source #

data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679458097 Bool -> Type) (TyFun [a6989586621679458097] [a6989586621679458097] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679458097 Bool -> Type) (TyFun [a6989586621679458097] [a6989586621679458097] -> Type) (DropWhileEndSym0 a6989586621679458097) l Source # 
type Apply (TyFun a6989586621679458097 Bool -> Type) (TyFun [a6989586621679458097] [a6989586621679458097] -> Type) (DropWhileEndSym0 a6989586621679458097) l = DropWhileEndSym1 a6989586621679458097 l

data DropWhileEndSym1 (l :: TyFun a6989586621679458097 Bool -> Type) (l :: TyFun [a6989586621679458097] [a6989586621679458097]) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DropWhileEndSym1 a6989586621679458097) 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 a6989586621679458097 Bool -> Type) (t :: [a6989586621679458097]) = DropWhileEnd t t Source #

data SpanSym0 (l :: TyFun (TyFun a6989586621679458096 Bool -> Type) (TyFun [a6989586621679458096] ([a6989586621679458096], [a6989586621679458096]) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679458096 Bool -> Type) (TyFun [a6989586621679458096] ([a6989586621679458096], [a6989586621679458096]) -> Type) (SpanSym0 a6989586621679458096) l Source # 
type Apply (TyFun a6989586621679458096 Bool -> Type) (TyFun [a6989586621679458096] ([a6989586621679458096], [a6989586621679458096]) -> Type) (SpanSym0 a6989586621679458096) l = SpanSym1 a6989586621679458096 l

data SpanSym1 (l :: TyFun a6989586621679458096 Bool -> Type) (l :: TyFun [a6989586621679458096] ([a6989586621679458096], [a6989586621679458096])) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SpanSym1 a6989586621679458096) 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 a6989586621679458096 Bool -> Type) (t :: [a6989586621679458096]) = Span t t Source #

data BreakSym0 (l :: TyFun (TyFun a6989586621679458095 Bool -> Type) (TyFun [a6989586621679458095] ([a6989586621679458095], [a6989586621679458095]) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679458095 Bool -> Type) (TyFun [a6989586621679458095] ([a6989586621679458095], [a6989586621679458095]) -> Type) (BreakSym0 a6989586621679458095) l Source # 
type Apply (TyFun a6989586621679458095 Bool -> Type) (TyFun [a6989586621679458095] ([a6989586621679458095], [a6989586621679458095]) -> Type) (BreakSym0 a6989586621679458095) l = BreakSym1 a6989586621679458095 l

data BreakSym1 (l :: TyFun a6989586621679458095 Bool -> Type) (l :: TyFun [a6989586621679458095] ([a6989586621679458095], [a6989586621679458095])) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (BreakSym1 a6989586621679458095) 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 a6989586621679458095 Bool -> Type) (t :: [a6989586621679458095]) = Break t t Source #

data StripPrefixSym0 (l :: TyFun [a6989586621679876709] (TyFun [a6989586621679876709] (Maybe [a6989586621679876709]) -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679876709] (TyFun [a6989586621679876709] (Maybe [a6989586621679876709]) -> Type) (StripPrefixSym0 a6989586621679876709) l Source # 
type Apply [a6989586621679876709] (TyFun [a6989586621679876709] (Maybe [a6989586621679876709]) -> Type) (StripPrefixSym0 a6989586621679876709) l = StripPrefixSym1 a6989586621679876709 l

data StripPrefixSym1 (l :: [a6989586621679876709]) (l :: TyFun [a6989586621679876709] (Maybe [a6989586621679876709])) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (StripPrefixSym1 a6989586621679876709) 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 :: [a6989586621679876709]) (t :: [a6989586621679876709]) = StripPrefix t t Source #

data MaximumSym0 (l :: TyFun [a6989586621679458090] a6989586621679458090) Source #

Instances

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

Methods

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

type Apply [a] a (MaximumSym0 a) l Source # 
type Apply [a] a (MaximumSym0 a) l = Maximum a l

type MaximumSym1 (t :: [a6989586621679458090]) = Maximum t Source #

data MinimumSym0 (l :: TyFun [a6989586621679458089] a6989586621679458089) Source #

Instances

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

Methods

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

type Apply [a] a (MinimumSym0 a) l Source # 
type Apply [a] a (MinimumSym0 a) l = Minimum a l

type MinimumSym1 (t :: [a6989586621679458089]) = Minimum t Source #

data GroupSym0 (l :: TyFun [a6989586621679458091] [[a6989586621679458091]]) Source #

Instances

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

Methods

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

type Apply [a] [[a]] (GroupSym0 a) l Source # 
type Apply [a] [[a]] (GroupSym0 a) l = Group a l

type GroupSym1 (t :: [a6989586621679458091]) = Group t Source #

data GroupBySym0 (l :: TyFun (TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (TyFun [a6989586621679458086] [[a6989586621679458086]] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (TyFun [a6989586621679458086] [[a6989586621679458086]] -> Type) (GroupBySym0 a6989586621679458086) l Source # 
type Apply (TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (TyFun [a6989586621679458086] [[a6989586621679458086]] -> Type) (GroupBySym0 a6989586621679458086) l = GroupBySym1 a6989586621679458086 l

data GroupBySym1 (l :: TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458086] [[a6989586621679458086]]) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (GroupBySym1 a6989586621679458086) 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 a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (t :: [a6989586621679458086]) = GroupBy t t Source #

data LookupSym0 (l :: TyFun a6989586621679458084 (TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun a6989586621679458084 (TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085) -> Type) -> *) (LookupSym0 a6989586621679458084 b6989586621679458085) Source # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym0 a6989586621679458084 b6989586621679458085) t -> () Source #

type Apply a6989586621679458084 (TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085) -> Type) (LookupSym0 a6989586621679458084 b6989586621679458085) l Source # 
type Apply a6989586621679458084 (TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085) -> Type) (LookupSym0 a6989586621679458084 b6989586621679458085) l = LookupSym1 a6989586621679458084 b6989586621679458085 l

data LookupSym1 (l :: a6989586621679458084) (l :: TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085)) Source #

Instances

SuppressUnusedWarnings (a6989586621679458084 -> TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085) -> *) (LookupSym1 a6989586621679458084 b6989586621679458085) Source # 

Methods

suppressUnusedWarnings :: Proxy (LookupSym1 a6989586621679458084 b6989586621679458085) 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 :: a6989586621679458084) (t :: [(a6989586621679458084, b6989586621679458085)]) = Lookup t t Source #

data FindSym0 (l :: TyFun (TyFun a6989586621679458106 Bool -> Type) (TyFun [a6989586621679458106] (Maybe a6989586621679458106) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679458106 Bool -> Type) (TyFun [a6989586621679458106] (Maybe a6989586621679458106) -> Type) (FindSym0 a6989586621679458106) l Source # 
type Apply (TyFun a6989586621679458106 Bool -> Type) (TyFun [a6989586621679458106] (Maybe a6989586621679458106) -> Type) (FindSym0 a6989586621679458106) l = FindSym1 a6989586621679458106 l

data FindSym1 (l :: TyFun a6989586621679458106 Bool -> Type) (l :: TyFun [a6989586621679458106] (Maybe a6989586621679458106)) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (FindSym1 a6989586621679458106) 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 a6989586621679458106 Bool -> Type) (t :: [a6989586621679458106]) = Find t t Source #

data FilterSym0 (l :: TyFun (TyFun a6989586621679458107 Bool -> Type) (TyFun [a6989586621679458107] [a6989586621679458107] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679458107 Bool -> Type) (TyFun [a6989586621679458107] [a6989586621679458107] -> Type) (FilterSym0 a6989586621679458107) l Source # 
type Apply (TyFun a6989586621679458107 Bool -> Type) (TyFun [a6989586621679458107] [a6989586621679458107] -> Type) (FilterSym0 a6989586621679458107) l = FilterSym1 a6989586621679458107 l

data FilterSym1 (l :: TyFun a6989586621679458107 Bool -> Type) (l :: TyFun [a6989586621679458107] [a6989586621679458107]) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (FilterSym1 a6989586621679458107) 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 a6989586621679458107 Bool -> Type) (t :: [a6989586621679458107]) = Filter t t Source #

data PartitionSym0 (l :: TyFun (TyFun a6989586621679458083 Bool -> Type) (TyFun [a6989586621679458083] ([a6989586621679458083], [a6989586621679458083]) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679458083 Bool -> Type) (TyFun [a6989586621679458083] ([a6989586621679458083], [a6989586621679458083]) -> Type) (PartitionSym0 a6989586621679458083) l Source # 
type Apply (TyFun a6989586621679458083 Bool -> Type) (TyFun [a6989586621679458083] ([a6989586621679458083], [a6989586621679458083]) -> Type) (PartitionSym0 a6989586621679458083) l = PartitionSym1 a6989586621679458083 l

data PartitionSym1 (l :: TyFun a6989586621679458083 Bool -> Type) (l :: TyFun [a6989586621679458083] ([a6989586621679458083], [a6989586621679458083])) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (PartitionSym1 a6989586621679458083) 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 a6989586621679458083 Bool -> Type) (t :: [a6989586621679458083]) = Partition t t Source #

data (:!!$) (l :: TyFun [a6989586621679458076] (TyFun Nat a6989586621679458076 -> Type)) Source #

Instances

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

Methods

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

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

data (l :: [a6989586621679458076]) :!!$$ (l :: TyFun Nat a6989586621679458076) Source #

Instances

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

Methods

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

type Apply Nat a ((:!!$$) a l1) l2 Source # 
type Apply Nat a ((:!!$$) a l1) l2 = (:!!) a l1 l2

type (:!!$$$) (t :: [a6989586621679458076]) (t :: Nat) = (:!!) t t Source #

data ElemIndexSym0 (l :: TyFun a6989586621679458105 (TyFun [a6989586621679458105] (Maybe Nat) -> Type)) Source #

Instances

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

Methods

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

type Apply a6989586621679458105 (TyFun [a6989586621679458105] (Maybe Nat) -> Type) (ElemIndexSym0 a6989586621679458105) l Source # 
type Apply a6989586621679458105 (TyFun [a6989586621679458105] (Maybe Nat) -> Type) (ElemIndexSym0 a6989586621679458105) l = ElemIndexSym1 a6989586621679458105 l

data ElemIndexSym1 (l :: a6989586621679458105) (l :: TyFun [a6989586621679458105] (Maybe Nat)) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (ElemIndexSym1 a6989586621679458105) 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 :: a6989586621679458105) (t :: [a6989586621679458105]) = ElemIndex t t Source #

data ElemIndicesSym0 (l :: TyFun a6989586621679458104 (TyFun [a6989586621679458104] [Nat] -> Type)) Source #

Instances

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

Methods

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

type Apply a6989586621679458104 (TyFun [a6989586621679458104] [Nat] -> Type) (ElemIndicesSym0 a6989586621679458104) l Source # 
type Apply a6989586621679458104 (TyFun [a6989586621679458104] [Nat] -> Type) (ElemIndicesSym0 a6989586621679458104) l = ElemIndicesSym1 a6989586621679458104 l

data ElemIndicesSym1 (l :: a6989586621679458104) (l :: TyFun [a6989586621679458104] [Nat]) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (ElemIndicesSym1 a6989586621679458104) 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 :: a6989586621679458104) (t :: [a6989586621679458104]) = ElemIndices t t Source #

data FindIndexSym0 (l :: TyFun (TyFun a6989586621679458103 Bool -> Type) (TyFun [a6989586621679458103] (Maybe Nat) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679458103 Bool -> Type) (TyFun [a6989586621679458103] (Maybe Nat) -> Type) (FindIndexSym0 a6989586621679458103) l Source # 
type Apply (TyFun a6989586621679458103 Bool -> Type) (TyFun [a6989586621679458103] (Maybe Nat) -> Type) (FindIndexSym0 a6989586621679458103) l = FindIndexSym1 a6989586621679458103 l

data FindIndexSym1 (l :: TyFun a6989586621679458103 Bool -> Type) (l :: TyFun [a6989586621679458103] (Maybe Nat)) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (FindIndexSym1 a6989586621679458103) 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 a6989586621679458103 Bool -> Type) (t :: [a6989586621679458103]) = FindIndex t t Source #

data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679458102 Bool -> Type) (TyFun [a6989586621679458102] [Nat] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679458102 Bool -> Type) (TyFun [a6989586621679458102] [Nat] -> Type) (FindIndicesSym0 a6989586621679458102) l Source # 
type Apply (TyFun a6989586621679458102 Bool -> Type) (TyFun [a6989586621679458102] [Nat] -> Type) (FindIndicesSym0 a6989586621679458102) l = FindIndicesSym1 a6989586621679458102 l

data FindIndicesSym1 (l :: TyFun a6989586621679458102 Bool -> Type) (l :: TyFun [a6989586621679458102] [Nat]) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (FindIndicesSym1 a6989586621679458102) 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 a6989586621679458102 Bool -> Type) (t :: [a6989586621679458102]) = FindIndices t t Source #

data Zip4Sym0 (l :: TyFun [a6989586621679876705] (TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679876705] (TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) -> Type) -> *) (Zip4Sym0 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym0 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) t -> () Source #

type Apply [a6989586621679876705] (TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) -> Type) (Zip4Sym0 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) l Source # 
type Apply [a6989586621679876705] (TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) -> Type) (Zip4Sym0 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) l = Zip4Sym1 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708 l

data Zip4Sym1 (l :: [a6989586621679876705]) (l :: TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876705] -> TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) -> *) (Zip4Sym1 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym1 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) t -> () Source #

type Apply [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) (Zip4Sym1 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708 l1) l2 Source # 
type Apply [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) (Zip4Sym1 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708 l1) l2 = Zip4Sym2 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708 l1 l2

data Zip4Sym2 (l :: [a6989586621679876705]) (l :: [b6989586621679876706]) (l :: TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876705] -> [b6989586621679876706] -> TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> *) (Zip4Sym2 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym2 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) t -> () Source #

type Apply [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) (Zip4Sym2 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708 l1 l2) l3 Source # 
type Apply [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) (Zip4Sym2 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708 l1 l2) l3 = Zip4Sym3 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708 l1 l2 l3

data Zip4Sym3 (l :: [a6989586621679876705]) (l :: [b6989586621679876706]) (l :: [c6989586621679876707]) (l :: TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876705] -> [b6989586621679876706] -> [c6989586621679876707] -> TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> *) (Zip4Sym3 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip4Sym3 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) t -> () Source #

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 :: [a6989586621679876705]) (t :: [b6989586621679876706]) (t :: [c6989586621679876707]) (t :: [d6989586621679876708]) = Zip4 t t t t Source #

data Zip5Sym0 (l :: TyFun [a6989586621679876700] (TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679876700] (TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip5Sym0 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym0 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) t -> () Source #

type Apply [a6989586621679876700] (TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) -> Type) (Zip5Sym0 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) l Source # 
type Apply [a6989586621679876700] (TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) -> Type) (Zip5Sym0 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) l = Zip5Sym1 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l

data Zip5Sym1 (l :: [a6989586621679876700]) (l :: TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876700] -> TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) -> *) (Zip5Sym1 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym1 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) t -> () Source #

type Apply [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) (Zip5Sym1 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l1) l2 Source # 
type Apply [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) (Zip5Sym1 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l1) l2 = Zip5Sym2 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l1 l2

data Zip5Sym2 (l :: [a6989586621679876700]) (l :: [b6989586621679876701]) (l :: TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876700] -> [b6989586621679876701] -> TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> *) (Zip5Sym2 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym2 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) t -> () Source #

type Apply [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) (Zip5Sym2 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l1 l2) l3 Source # 
type Apply [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) (Zip5Sym2 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l1 l2) l3 = Zip5Sym3 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l1 l2 l3

data Zip5Sym3 (l :: [a6989586621679876700]) (l :: [b6989586621679876701]) (l :: [c6989586621679876702]) (l :: TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876700] -> [b6989586621679876701] -> [c6989586621679876702] -> TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> *) (Zip5Sym3 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym3 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) t -> () Source #

type Apply [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) (Zip5Sym3 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l1 l2 l3) l4 Source # 
type Apply [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) (Zip5Sym3 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l1 l2 l3) l4 = Zip5Sym4 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l1 l2 l3 l4

data Zip5Sym4 (l :: [a6989586621679876700]) (l :: [b6989586621679876701]) (l :: [c6989586621679876702]) (l :: [d6989586621679876703]) (l :: TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876700] -> [b6989586621679876701] -> [c6989586621679876702] -> [d6989586621679876703] -> TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> *) (Zip5Sym4 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip5Sym4 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) t -> () Source #

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 :: [a6989586621679876700]) (t :: [b6989586621679876701]) (t :: [c6989586621679876702]) (t :: [d6989586621679876703]) (t :: [e6989586621679876704]) = Zip5 t t t t t Source #

data Zip6Sym0 (l :: TyFun [a6989586621679876694] (TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679876694] (TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym0 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym0 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) t -> () Source #

type Apply [a6989586621679876694] (TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip6Sym0 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) l Source # 
type Apply [a6989586621679876694] (TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip6Sym0 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) l = Zip6Sym1 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l

data Zip6Sym1 (l :: [a6989586621679876694]) (l :: TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876694] -> TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym1 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym1 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) t -> () Source #

type Apply [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) (Zip6Sym1 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1) l2 Source # 
type Apply [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) (Zip6Sym1 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1) l2 = Zip6Sym2 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2

data Zip6Sym2 (l :: [a6989586621679876694]) (l :: [b6989586621679876695]) (l :: TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876694] -> [b6989586621679876695] -> TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> *) (Zip6Sym2 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym2 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) t -> () Source #

type Apply [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) (Zip6Sym2 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2) l3 Source # 
type Apply [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) (Zip6Sym2 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2) l3 = Zip6Sym3 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2 l3

data Zip6Sym3 (l :: [a6989586621679876694]) (l :: [b6989586621679876695]) (l :: [c6989586621679876696]) (l :: TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876694] -> [b6989586621679876695] -> [c6989586621679876696] -> TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> *) (Zip6Sym3 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym3 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) t -> () Source #

type Apply [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) (Zip6Sym3 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2 l3) l4 Source # 
type Apply [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) (Zip6Sym3 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2 l3) l4 = Zip6Sym4 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2 l3 l4

data Zip6Sym4 (l :: [a6989586621679876694]) (l :: [b6989586621679876695]) (l :: [c6989586621679876696]) (l :: [d6989586621679876697]) (l :: TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876694] -> [b6989586621679876695] -> [c6989586621679876696] -> [d6989586621679876697] -> TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> *) (Zip6Sym4 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym4 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) t -> () Source #

type Apply [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) (Zip6Sym4 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2 l3 l4) l5 Source # 
type Apply [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) (Zip6Sym4 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2 l3 l4) l5 = Zip6Sym5 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2 l3 l4 l5

data Zip6Sym5 (l :: [a6989586621679876694]) (l :: [b6989586621679876695]) (l :: [c6989586621679876696]) (l :: [d6989586621679876697]) (l :: [e6989586621679876698]) (l :: TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876694] -> [b6989586621679876695] -> [c6989586621679876696] -> [d6989586621679876697] -> [e6989586621679876698] -> TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> *) (Zip6Sym5 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip6Sym5 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) t -> () Source #

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 :: [a6989586621679876694]) (t :: [b6989586621679876695]) (t :: [c6989586621679876696]) (t :: [d6989586621679876697]) (t :: [e6989586621679876698]) (t :: [f6989586621679876699]) = Zip6 t t t t t t Source #

data Zip7Sym0 (l :: TyFun [a6989586621679876687] (TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679876687] (TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym0 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym0 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

type Apply [a6989586621679876687] (TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym0 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) l Source # 
type Apply [a6989586621679876687] (TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym0 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) l = Zip7Sym1 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l

data Zip7Sym1 (l :: [a6989586621679876687]) (l :: TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876687] -> TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym1 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym1 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

type Apply [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym1 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1) l2 Source # 
type Apply [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym1 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1) l2 = Zip7Sym2 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2

data Zip7Sym2 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym2 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym2 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

type Apply [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) (Zip7Sym2 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2) l3 Source # 
type Apply [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) (Zip7Sym2 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2) l3 = Zip7Sym3 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3

data Zip7Sym3 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: [c6989586621679876689]) (l :: TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> [c6989586621679876689] -> TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> *) (Zip7Sym3 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym3 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

type Apply [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) (Zip7Sym3 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3) l4 Source # 
type Apply [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) (Zip7Sym3 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3) l4 = Zip7Sym4 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3 l4

data Zip7Sym4 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: [c6989586621679876689]) (l :: [d6989586621679876690]) (l :: TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> [c6989586621679876689] -> [d6989586621679876690] -> TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> *) (Zip7Sym4 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym4 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

type Apply [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) (Zip7Sym4 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3 l4) l5 Source # 
type Apply [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) (Zip7Sym4 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3 l4) l5 = Zip7Sym5 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3 l4 l5

data Zip7Sym5 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: [c6989586621679876689]) (l :: [d6989586621679876690]) (l :: [e6989586621679876691]) (l :: TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type)) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> [c6989586621679876689] -> [d6989586621679876690] -> [e6989586621679876691] -> TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> *) (Zip7Sym5 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym5 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

type Apply [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) (Zip7Sym5 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3 l4 l5) l6 Source # 
type Apply [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) (Zip7Sym5 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3 l4 l5) l6 = Zip7Sym6 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3 l4 l5 l6

data Zip7Sym6 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: [c6989586621679876689]) (l :: [d6989586621679876690]) (l :: [e6989586621679876691]) (l :: [f6989586621679876692]) (l :: TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> [c6989586621679876689] -> [d6989586621679876690] -> [e6989586621679876691] -> [f6989586621679876692] -> TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> *) (Zip7Sym6 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # 

Methods

suppressUnusedWarnings :: Proxy (Zip7Sym6 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) t -> () Source #

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 :: [a6989586621679876687]) (t :: [b6989586621679876688]) (t :: [c6989586621679876689]) (t :: [d6989586621679876690]) (t :: [e6989586621679876691]) (t :: [f6989586621679876692]) (t :: [g6989586621679876693]) = Zip7 t t t t t t t Source #

data ZipWith4Sym0 (l :: TyFun (TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith4Sym0 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym0 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) t -> () Source #

type Apply (TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) -> Type) (ZipWith4Sym0 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) l Source # 
type Apply (TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) -> Type) (ZipWith4Sym0 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) l = ZipWith4Sym1 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l

data ZipWith4Sym1 (l :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) -> *) (ZipWith4Sym1 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym1 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) t -> () Source #

type Apply [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) (ZipWith4Sym1 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l1) l2 Source # 
type Apply [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) (ZipWith4Sym1 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l1) l2 = ZipWith4Sym2 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l1 l2

data ZipWith4Sym2 (l :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876682]) (l :: TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876682] -> TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> *) (ZipWith4Sym2 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym2 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) t -> () Source #

type Apply [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) (ZipWith4Sym2 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l1 l2) l3 Source # 
type Apply [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) (ZipWith4Sym2 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l1 l2) l3 = ZipWith4Sym3 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l1 l2 l3

data ZipWith4Sym3 (l :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876682]) (l :: [b6989586621679876683]) (l :: TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876682] -> [b6989586621679876683] -> TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> *) (ZipWith4Sym3 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym3 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) t -> () Source #

type Apply [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) (ZipWith4Sym3 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l1 l2 l3) l4 Source # 
type Apply [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) (ZipWith4Sym3 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l1 l2 l3) l4 = ZipWith4Sym4 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l1 l2 l3 l4

data ZipWith4Sym4 (l :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876682]) (l :: [b6989586621679876683]) (l :: [c6989586621679876684]) (l :: TyFun [d6989586621679876685] [e6989586621679876686]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876682] -> [b6989586621679876683] -> [c6989586621679876684] -> TyFun [d6989586621679876685] [e6989586621679876686] -> *) (ZipWith4Sym4 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith4Sym4 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) t -> () Source #

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 a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679876682]) (t :: [b6989586621679876683]) (t :: [c6989586621679876684]) (t :: [d6989586621679876685]) = ZipWith4 t t t t t Source #

data ZipWith5Sym0 (l :: TyFun (TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym0 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym0 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) t -> () Source #

type Apply (TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym0 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) l Source # 
type Apply (TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym0 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) l = ZipWith5Sym1 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l

data ZipWith5Sym1 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym1 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym1 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) t -> () Source #

type Apply [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym1 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1) l2 Source # 
type Apply [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym1 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1) l2 = ZipWith5Sym2 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2

data ZipWith5Sym2 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876676]) (l :: TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876676] -> TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> *) (ZipWith5Sym2 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym2 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) t -> () Source #

type Apply [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) (ZipWith5Sym2 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2) l3 Source # 
type Apply [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) (ZipWith5Sym2 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2) l3 = ZipWith5Sym3 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2 l3

data ZipWith5Sym3 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876676]) (l :: [b6989586621679876677]) (l :: TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876676] -> [b6989586621679876677] -> TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> *) (ZipWith5Sym3 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym3 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) t -> () Source #

type Apply [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) (ZipWith5Sym3 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2 l3) l4 Source # 
type Apply [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) (ZipWith5Sym3 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2 l3) l4 = ZipWith5Sym4 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2 l3 l4

data ZipWith5Sym4 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876676]) (l :: [b6989586621679876677]) (l :: [c6989586621679876678]) (l :: TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876676] -> [b6989586621679876677] -> [c6989586621679876678] -> TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> *) (ZipWith5Sym4 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym4 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) t -> () Source #

type Apply [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) (ZipWith5Sym4 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2 l3 l4) l5 Source # 
type Apply [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) (ZipWith5Sym4 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2 l3 l4) l5 = ZipWith5Sym5 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2 l3 l4 l5

data ZipWith5Sym5 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876676]) (l :: [b6989586621679876677]) (l :: [c6989586621679876678]) (l :: [d6989586621679876679]) (l :: TyFun [e6989586621679876680] [f6989586621679876681]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876676] -> [b6989586621679876677] -> [c6989586621679876678] -> [d6989586621679876679] -> TyFun [e6989586621679876680] [f6989586621679876681] -> *) (ZipWith5Sym5 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith5Sym5 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) t -> () Source #

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 a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679876676]) (t :: [b6989586621679876677]) (t :: [c6989586621679876678]) (t :: [d6989586621679876679]) (t :: [e6989586621679876680]) = ZipWith5 t t t t t t Source #

data ZipWith6Sym0 (l :: TyFun (TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym0 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym0 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

type Apply (TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym0 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) l Source # 
type Apply (TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym0 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) l = ZipWith6Sym1 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l

data ZipWith6Sym1 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym1 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym1 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

type Apply [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym1 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1) l2 Source # 
type Apply [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym1 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1) l2 = ZipWith6Sym2 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2

data ZipWith6Sym2 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym2 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym2 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

type Apply [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym2 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2) l3 Source # 
type Apply [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym2 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2) l3 = ZipWith6Sym3 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3

data ZipWith6Sym3 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: [b6989586621679876670]) (l :: TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> [b6989586621679876670] -> TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> *) (ZipWith6Sym3 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym3 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

type Apply [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) (ZipWith6Sym3 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3) l4 Source # 
type Apply [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) (ZipWith6Sym3 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3) l4 = ZipWith6Sym4 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3 l4

data ZipWith6Sym4 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: [b6989586621679876670]) (l :: [c6989586621679876671]) (l :: TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> [b6989586621679876670] -> [c6989586621679876671] -> TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> *) (ZipWith6Sym4 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym4 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

type Apply [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) (ZipWith6Sym4 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3 l4) l5 Source # 
type Apply [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) (ZipWith6Sym4 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3 l4) l5 = ZipWith6Sym5 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3 l4 l5

data ZipWith6Sym5 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: [b6989586621679876670]) (l :: [c6989586621679876671]) (l :: [d6989586621679876672]) (l :: TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> [b6989586621679876670] -> [c6989586621679876671] -> [d6989586621679876672] -> TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> *) (ZipWith6Sym5 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym5 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

type Apply [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) (ZipWith6Sym5 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3 l4 l5) l6 Source # 
type Apply [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) (ZipWith6Sym5 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3 l4 l5) l6 = ZipWith6Sym6 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3 l4 l5 l6

data ZipWith6Sym6 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: [b6989586621679876670]) (l :: [c6989586621679876671]) (l :: [d6989586621679876672]) (l :: [e6989586621679876673]) (l :: TyFun [f6989586621679876674] [g6989586621679876675]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> [b6989586621679876670] -> [c6989586621679876671] -> [d6989586621679876672] -> [e6989586621679876673] -> TyFun [f6989586621679876674] [g6989586621679876675] -> *) (ZipWith6Sym6 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith6Sym6 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) t -> () Source #

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 a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679876669]) (t :: [b6989586621679876670]) (t :: [c6989586621679876671]) (t :: [d6989586621679876672]) (t :: [e6989586621679876673]) (t :: [f6989586621679876674]) = ZipWith6 t t t t t t t Source #

data ZipWith7Sym0 (l :: TyFun (TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym0 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym0 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

type Apply (TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym0 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) l Source # 
type Apply (TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym0 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) l = ZipWith7Sym1 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l

data ZipWith7Sym1 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym1 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym1 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

type Apply [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym1 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1) l2 Source # 
type Apply [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym1 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1) l2 = ZipWith7Sym2 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2

data ZipWith7Sym2 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym2 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym2 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

type Apply [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym2 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2) l3 Source # 
type Apply [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym2 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2) l3 = ZipWith7Sym3 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3

data ZipWith7Sym3 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym3 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym3 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

type Apply [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym3 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3) l4 Source # 
type Apply [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym3 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3) l4 = ZipWith7Sym4 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4

data ZipWith7Sym4 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: [c6989586621679876663]) (l :: TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> [c6989586621679876663] -> TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> *) (ZipWith7Sym4 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym4 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

type Apply [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) (ZipWith7Sym4 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4) l5 Source # 
type Apply [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) (ZipWith7Sym4 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4) l5 = ZipWith7Sym5 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4 l5

data ZipWith7Sym5 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: [c6989586621679876663]) (l :: [d6989586621679876664]) (l :: TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> [c6989586621679876663] -> [d6989586621679876664] -> TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> *) (ZipWith7Sym5 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym5 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

type Apply [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) (ZipWith7Sym5 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4 l5) l6 Source # 
type Apply [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) (ZipWith7Sym5 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4 l5) l6 = ZipWith7Sym6 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4 l5 l6

data ZipWith7Sym6 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: [c6989586621679876663]) (l :: [d6989586621679876664]) (l :: [e6989586621679876665]) (l :: TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> [c6989586621679876663] -> [d6989586621679876664] -> [e6989586621679876665] -> TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> *) (ZipWith7Sym6 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym6 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

type Apply [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) (ZipWith7Sym6 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4 l5 l6) l7 Source # 
type Apply [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) (ZipWith7Sym6 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4 l5 l6) l7 = ZipWith7Sym7 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4 l5 l6 l7

data ZipWith7Sym7 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: [c6989586621679876663]) (l :: [d6989586621679876664]) (l :: [e6989586621679876665]) (l :: [f6989586621679876666]) (l :: TyFun [g6989586621679876667] [h6989586621679876668]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> [c6989586621679876663] -> [d6989586621679876664] -> [e6989586621679876665] -> [f6989586621679876666] -> TyFun [g6989586621679876667] [h6989586621679876668] -> *) (ZipWith7Sym7 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWith7Sym7 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) t -> () Source #

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 a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679876661]) (t :: [b6989586621679876662]) (t :: [c6989586621679876663]) (t :: [d6989586621679876664]) (t :: [e6989586621679876665]) (t :: [f6989586621679876666]) (t :: [g6989586621679876667]) = ZipWith7 t t t t t t t t Source #

data NubSym0 (l :: TyFun [a6989586621679458075] [a6989586621679458075]) Source #

Instances

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

Methods

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

type Apply [a] [a] (NubSym0 a) l Source # 
type Apply [a] [a] (NubSym0 a) l = Nub a l

type NubSym1 (t :: [a6989586621679458075]) = Nub t Source #

data NubBySym0 (l :: TyFun (TyFun a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (TyFun [a6989586621679458074] [a6989586621679458074] -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (TyFun [a6989586621679458074] [a6989586621679458074] -> Type) (NubBySym0 a6989586621679458074) l Source # 
type Apply (TyFun a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (TyFun [a6989586621679458074] [a6989586621679458074] -> Type) (NubBySym0 a6989586621679458074) l = NubBySym1 a6989586621679458074 l

data NubBySym1 (l :: TyFun a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458074] [a6989586621679458074]) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (NubBySym1 a6989586621679458074) 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 a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (t :: [a6989586621679458074]) = NubBy t t Source #

data UnionSym0 (l :: TyFun [a6989586621679458071] (TyFun [a6989586621679458071] [a6989586621679458071] -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679458071] (TyFun [a6989586621679458071] [a6989586621679458071] -> Type) (UnionSym0 a6989586621679458071) l Source # 
type Apply [a6989586621679458071] (TyFun [a6989586621679458071] [a6989586621679458071] -> Type) (UnionSym0 a6989586621679458071) l = UnionSym1 a6989586621679458071 l

data UnionSym1 (l :: [a6989586621679458071]) (l :: TyFun [a6989586621679458071] [a6989586621679458071]) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (UnionSym1 a6989586621679458071) 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 :: [a6989586621679458071]) (t :: [a6989586621679458071]) = Union t t Source #

data UnionBySym0 (l :: TyFun (TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (TyFun [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type) -> Type)) Source #

Instances

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

Methods

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

type Apply (TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (TyFun [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type) -> Type) (UnionBySym0 a6989586621679458072) l Source # 
type Apply (TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (TyFun [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type) -> Type) (UnionBySym0 a6989586621679458072) l = UnionBySym1 a6989586621679458072 l

data UnionBySym1 (l :: TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type)) Source #

Instances

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

Methods

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

type Apply [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type) (UnionBySym1 a6989586621679458072 l1) l2 Source # 
type Apply [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type) (UnionBySym1 a6989586621679458072 l1) l2 = UnionBySym2 a6989586621679458072 l1 l2

data UnionBySym2 (l :: TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (l :: [a6989586621679458072]) (l :: TyFun [a6989586621679458072] [a6989586621679458072]) Source #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (UnionBySym2 a6989586621679458072) 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 a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (t :: [a6989586621679458072]) (t :: [a6989586621679458072]) = UnionBy t t t Source #

data GenericLengthSym0 (l :: TyFun [a6989586621679458070] i6989586621679458069) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679458070] i6989586621679458069 -> *) (GenericLengthSym0 a6989586621679458070 i6989586621679458069) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericLengthSym0 a6989586621679458070 i6989586621679458069) 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 :: [a6989586621679458070]) = GenericLength t Source #

data GenericTakeSym0 (l :: TyFun i6989586621679876659 (TyFun [a6989586621679876660] [a6989586621679876660] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun i6989586621679876659 (TyFun [a6989586621679876660] [a6989586621679876660] -> Type) -> *) (GenericTakeSym0 i6989586621679876659 a6989586621679876660) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym0 i6989586621679876659 a6989586621679876660) t -> () Source #

type Apply i6989586621679876659 (TyFun [a6989586621679876660] [a6989586621679876660] -> Type) (GenericTakeSym0 i6989586621679876659 a6989586621679876660) l Source # 
type Apply i6989586621679876659 (TyFun [a6989586621679876660] [a6989586621679876660] -> Type) (GenericTakeSym0 i6989586621679876659 a6989586621679876660) l = GenericTakeSym1 i6989586621679876659 a6989586621679876660 l

data GenericTakeSym1 (l :: i6989586621679876659) (l :: TyFun [a6989586621679876660] [a6989586621679876660]) Source #

Instances

SuppressUnusedWarnings (i6989586621679876659 -> TyFun [a6989586621679876660] [a6989586621679876660] -> *) (GenericTakeSym1 i6989586621679876659 a6989586621679876660) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericTakeSym1 i6989586621679876659 a6989586621679876660) 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 :: i6989586621679876659) (t :: [a6989586621679876660]) = GenericTake t t Source #

data GenericDropSym0 (l :: TyFun i6989586621679876657 (TyFun [a6989586621679876658] [a6989586621679876658] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun i6989586621679876657 (TyFun [a6989586621679876658] [a6989586621679876658] -> Type) -> *) (GenericDropSym0 i6989586621679876657 a6989586621679876658) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym0 i6989586621679876657 a6989586621679876658) t -> () Source #

type Apply i6989586621679876657 (TyFun [a6989586621679876658] [a6989586621679876658] -> Type) (GenericDropSym0 i6989586621679876657 a6989586621679876658) l Source # 
type Apply i6989586621679876657 (TyFun [a6989586621679876658] [a6989586621679876658] -> Type) (GenericDropSym0 i6989586621679876657 a6989586621679876658) l = GenericDropSym1 i6989586621679876657 a6989586621679876658 l

data GenericDropSym1 (l :: i6989586621679876657) (l :: TyFun [a6989586621679876658] [a6989586621679876658]) Source #

Instances

SuppressUnusedWarnings (i6989586621679876657 -> TyFun [a6989586621679876658] [a6989586621679876658] -> *) (GenericDropSym1 i6989586621679876657 a6989586621679876658) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericDropSym1 i6989586621679876657 a6989586621679876658) 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 :: i6989586621679876657) (t :: [a6989586621679876658]) = GenericDrop t t Source #

data GenericSplitAtSym0 (l :: TyFun i6989586621679876655 (TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun i6989586621679876655 (TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]) -> Type) -> *) (GenericSplitAtSym0 i6989586621679876655 a6989586621679876656) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym0 i6989586621679876655 a6989586621679876656) t -> () Source #

type Apply i6989586621679876655 (TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]) -> Type) (GenericSplitAtSym0 i6989586621679876655 a6989586621679876656) l Source # 
type Apply i6989586621679876655 (TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]) -> Type) (GenericSplitAtSym0 i6989586621679876655 a6989586621679876656) l = GenericSplitAtSym1 i6989586621679876655 a6989586621679876656 l

data GenericSplitAtSym1 (l :: i6989586621679876655) (l :: TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656])) Source #

Instances

SuppressUnusedWarnings (i6989586621679876655 -> TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]) -> *) (GenericSplitAtSym1 i6989586621679876655 a6989586621679876656) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericSplitAtSym1 i6989586621679876655 a6989586621679876656) 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 :: i6989586621679876655) (t :: [a6989586621679876656]) = GenericSplitAt t t Source #

data GenericIndexSym0 (l :: TyFun [a6989586621679876654] (TyFun i6989586621679876653 a6989586621679876654 -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679876654] (TyFun i6989586621679876653 a6989586621679876654 -> Type) -> *) (GenericIndexSym0 i6989586621679876653 a6989586621679876654) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym0 i6989586621679876653 a6989586621679876654) t -> () Source #

type Apply [a6989586621679876654] (TyFun i6989586621679876653 a6989586621679876654 -> Type) (GenericIndexSym0 i6989586621679876653 a6989586621679876654) l Source # 
type Apply [a6989586621679876654] (TyFun i6989586621679876653 a6989586621679876654 -> Type) (GenericIndexSym0 i6989586621679876653 a6989586621679876654) l = GenericIndexSym1 i6989586621679876653 a6989586621679876654 l

data GenericIndexSym1 (l :: [a6989586621679876654]) (l :: TyFun i6989586621679876653 a6989586621679876654) Source #

Instances

SuppressUnusedWarnings ([a6989586621679876654] -> TyFun i6989586621679876653 a6989586621679876654 -> *) (GenericIndexSym1 i6989586621679876653 a6989586621679876654) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericIndexSym1 i6989586621679876653 a6989586621679876654) 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 :: [a6989586621679876654]) (t :: i6989586621679876653) = GenericIndex t t Source #

data GenericReplicateSym0 (l :: TyFun i6989586621679876651 (TyFun a6989586621679876652 [a6989586621679876652] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun i6989586621679876651 (TyFun a6989586621679876652 [a6989586621679876652] -> Type) -> *) (GenericReplicateSym0 i6989586621679876651 a6989586621679876652) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym0 i6989586621679876651 a6989586621679876652) t -> () Source #

type Apply i6989586621679876651 (TyFun a6989586621679876652 [a6989586621679876652] -> Type) (GenericReplicateSym0 i6989586621679876651 a6989586621679876652) l Source # 
type Apply i6989586621679876651 (TyFun a6989586621679876652 [a6989586621679876652] -> Type) (GenericReplicateSym0 i6989586621679876651 a6989586621679876652) l = GenericReplicateSym1 i6989586621679876651 a6989586621679876652 l

data GenericReplicateSym1 (l :: i6989586621679876651) (l :: TyFun a6989586621679876652 [a6989586621679876652]) Source #

Instances

SuppressUnusedWarnings (i6989586621679876651 -> TyFun a6989586621679876652 [a6989586621679876652] -> *) (GenericReplicateSym1 i6989586621679876651 a6989586621679876652) Source # 

Methods

suppressUnusedWarnings :: Proxy (GenericReplicateSym1 i6989586621679876651 a6989586621679876652) 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 :: i6989586621679876651) (t :: a6989586621679876652) = GenericReplicate t t Source #