singletons-2.0.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] infixr 5 Source

Equations

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

type family Head a :: a Source

Equations

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

type family Last a :: a Source

Equations

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

type family Tail a :: [a] Source

Equations

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

type family Init a :: [a] Source

Equations

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

type family Null a :: Bool Source

Equations

Null `[]` = TrueSym0 
Null ((:) _z_1627752514 _z_1627752517) = FalseSym0 

type family Length a :: Nat Source

Equations

Length `[]` = FromInteger 0 
Length ((:) _z_1627749408 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply LengthSym0 xs) 

List transformations

type family Map a a :: [b] Source

Equations

Map _z_1627631698 `[]` = `[]` 
Map f ((:) x xs) = Apply (Apply (:$) (Apply f x)) (Apply (Apply MapSym0 f) xs) 

type family Reverse a :: [a] Source

Equations

Reverse l = Apply (Apply (Let1627752480RevSym1 l) l) `[]` 

type family Intersperse a a :: [a] Source

Equations

Intersperse _z_1627752458 `[]` = `[]` 
Intersperse sep ((:) x xs) = Apply (Apply (:$) x) (Apply (Apply PrependToAllSym0 sep) xs) 

type family Intercalate a a :: [a] Source

Equations

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

type family Transpose a :: [[a]] 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]] Source

Equations

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

type family Permutations a :: [[a]] Source

Equations

Permutations xs0 = Apply (Apply (:$) xs0) (Apply (Apply (Let1627752033PermsSym1 xs0) xs0) `[]`) 

Reducing lists (folds)

type family Foldl a a a :: b Source

Equations

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

type family Foldl' a a a :: b Source

Equations

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

type family Foldl1 a a :: a Source

Equations

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

type family Foldl1' a a :: a Source

Equations

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

type family Foldr a a a :: b Source

Equations

Foldr k z a_1627631719 = Apply (Let1627631724GoSym3 k z a_1627631719) a_1627631719 

type family Foldr1 a a :: a Source

Equations

Foldr1 _z_1627751682 `[x]` = x 
Foldr1 f ((:) x ((:) wild_1627749139 wild_1627749141)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let1627751690XsSym4 f x wild_1627749139 wild_1627749141)) 
Foldr1 _z_1627751709 `[]` = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" 

Special folds

type family Concat a :: [a] Source

Equations

Concat a_1627751666 = Apply (Apply (Apply FoldrSym0 (:++$)) `[]`) a_1627751666 

type family ConcatMap a a :: [b] Source

Equations

ConcatMap f a_1627751662 = Apply (Apply (Apply FoldrSym0 (Apply (Apply (:.$) (:++$)) f)) `[]`) a_1627751662 

type family And a :: Bool Source

Equations

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

type family Or a :: Bool Source

Equations

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

type family Any_ a a :: Bool Source

Equations

Any_ _z_1627737930 `[]` = FalseSym0 
Any_ p ((:) x xs) = Apply (Apply (:||$) (Apply p x)) (Apply (Apply Any_Sym0 p) xs) 

type family All a a :: Bool Source

Equations

All _z_1627751635 `[]` = TrueSym0 
All p ((:) x xs) = Apply (Apply (:&&$) (Apply p x)) (Apply (Apply AllSym0 p) xs) 

type family Sum a :: a Source

Equations

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

type family Product a :: a Source

Equations

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

type family Maximum a :: a Source

Equations

Maximum `[]` = Apply ErrorSym0 "Data.Singletons.List.maximum: empty list" 
Maximum ((:) wild_1627749225 wild_1627749227) = Apply (Apply Foldl1Sym0 MaxSym0) (Let1627751907XsSym2 wild_1627749225 wild_1627749227) 

type family Minimum a :: a Source

Equations

Minimum `[]` = Apply ErrorSym0 "Data.Singletons.List.minimum: empty list" 
Minimum ((:) wild_1627749229 wild_1627749231) = Apply (Apply Foldl1Sym0 MinSym0) (Let1627751921XsSym2 wild_1627749229 wild_1627749231) 

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

Building lists

Scans

type family Scanl a a a :: [b] Source

Equations

Scanl f q ls = Apply (Apply (:$) q) (Case_1627751606 f q ls (Let1627751593Scrutinee_1627749143Sym3 f q ls)) 

type family Scanl1 a a :: [a] Source

Equations

Scanl1 f ((:) x xs) = Apply (Apply (Apply ScanlSym0 f) x) xs 
Scanl1 _z_1627751623 `[]` = `[]` 

type family Scanr a a a :: [b] Source

Equations

Scanr _z_1627751543 q0 `[]` = Apply (Apply (:$) q0) `[]` 
Scanr f q0 ((:) x xs) = Case_1627751570 f q0 x xs (Let1627751551Scrutinee_1627749145Sym4 f q0 x xs) 

type family Scanr1 a a :: [a] Source

Equations

Scanr1 _z_1627751474 `[]` = `[]` 
Scanr1 _z_1627751477 `[x]` = Apply (Apply (:$) x) `[]` 
Scanr1 f ((:) x ((:) wild_1627749149 wild_1627749151)) = Case_1627751523 f x wild_1627749149 wild_1627749151 (Let1627751504Scrutinee_1627749147Sym4 f x wild_1627749149 wild_1627749151) 

Accumulating maps

type family MapAccumL a a a :: (acc, [y]) Source

Equations

MapAccumL _z_1627751308 s `[]` = Apply (Apply Tuple2Sym0 s) `[]` 
MapAccumL f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let1627751316S''Sym4 f s x xs)) (Apply (Apply (:$) (Let1627751316YSym4 f s x xs)) (Let1627751316YsSym4 f s x xs)) 

type family MapAccumR a a a :: (acc, [y]) Source

Equations

MapAccumR _z_1627751136 s `[]` = Apply (Apply Tuple2Sym0 s) `[]` 
MapAccumR f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let1627751144S''Sym4 f s x xs)) (Apply (Apply (:$) (Let1627751144YSym4 f s x xs)) (Let1627751144YsSym4 f s x xs)) 

Infinite lists

type family Replicate a a :: [a] Source

Equations

Replicate n x = Case_1627749401 n x (Let1627749393Scrutinee_1627749237Sym2 n x) 

Unfolding

type family Unfoldr a a :: [a] Source

Equations

Unfoldr f b = Case_1627751116 f b (Let1627751108Scrutinee_1627749153Sym2 f b) 

Sublists

Extracting sublists

type family Take a a :: [a] Source

Equations

Take _z_1627749588 `[]` = `[]` 
Take n ((:) x xs) = Case_1627749607 n x xs (Let1627749594Scrutinee_1627749221Sym3 n x xs) 

type family Drop a a :: [a] Source

Equations

Drop _z_1627749557 `[]` = `[]` 
Drop n ((:) x xs) = Case_1627749576 n x xs (Let1627749563Scrutinee_1627749223Sym3 n x xs) 

type family SplitAt a a :: ([a], [a]) Source

Equations

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

type family TakeWhile a a :: [a] Source

Equations

TakeWhile _z_1627749961 `[]` = `[]` 
TakeWhile p ((:) x xs) = Case_1627749980 p x xs (Let1627749967Scrutinee_1627749211Sym3 p x xs) 

type family DropWhile a a :: [a] Source

Equations

DropWhile _z_1627749917 `[]` = `[]` 
DropWhile p ((:) x xs') = Case_1627749949 p x xs' (Let1627749936Scrutinee_1627749213Sym3 p x xs') 

type family DropWhileEnd a a :: [a] Source

Equations

DropWhileEnd p a_1627752529 = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_1627752533Sym0 p) a_1627752529)) `[]`) a_1627752529 

type family Span a a :: ([a], [a]) Source

Equations

Span _z_1627749735 `[]` = Apply (Apply Tuple2Sym0 (Let1627749738XsSym1 _z_1627749735)) (Let1627749738XsSym1 _z_1627749735) 
Span p ((:) x xs') = Case_1627749771 p x xs' (Let1627749758Scrutinee_1627749217Sym3 p x xs') 

type family Break a a :: ([a], [a]) Source

Equations

Break _z_1627749630 `[]` = Apply (Apply Tuple2Sym0 (Let1627749633XsSym1 _z_1627749630)) (Let1627749633XsSym1 _z_1627749630) 
Break p ((:) x xs') = Case_1627749666 p x xs' (Let1627749653Scrutinee_1627749219Sym3 p x xs') 

type family StripPrefix a a :: Maybe [a] Source

Equations

StripPrefix `[]` ys = Apply JustSym0 ys 
StripPrefix arg_1627971870 arg_1627971872 = Case_1627972479 arg_1627971870 arg_1627971872 (Apply (Apply Tuple2Sym0 arg_1627971870) arg_1627971872) 

type family Group a :: [[a]] Source

Equations

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

type family Inits a :: [[a]] Source

Equations

Inits xs = Apply (Apply (:$) `[]`) (Case_1627751092 xs (Let1627751088Scrutinee_1627749155Sym1 xs)) 

type family Tails a :: [[a]] Source

Equations

Tails xs = Apply (Apply (:$) xs) (Case_1627751065 xs (Let1627751061Scrutinee_1627749157Sym1 xs)) 

Predicates

type family IsPrefixOf a a :: Bool Source

Equations

IsPrefixOf `[]` `[]` = TrueSym0 
IsPrefixOf `[]` ((:) _z_1627751040 _z_1627751043) = TrueSym0 
IsPrefixOf ((:) _z_1627751046 _z_1627751049) `[]` = FalseSym0 
IsPrefixOf ((:) x xs) ((:) y ys) = Apply (Apply (:&&$) (Apply (Apply (:==$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) 

type family IsInfixOf a a :: Bool 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 :: Bool Source

Equations

Elem _z_1627750977 `[]` = FalseSym0 
Elem x ((:) y ys) = Apply (Apply (:||$) (Apply (Apply (:==$) x) y)) (Apply (Apply ElemSym0 x) ys) 

type family NotElem a a :: Bool Source

Equations

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

type family Lookup a a :: Maybe b Source

Equations

Lookup _key `[]` = NothingSym0 
Lookup key ((:) `(x, y)` xys) = Case_1627749545 key x y xys (Let1627749526Scrutinee_1627749233Sym4 key x y xys) 

Searching with a predicate

type family Find a a :: Maybe a Source

Equations

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

type family Filter a a :: [a] Source

Equations

Filter _p `[]` = `[]` 
Filter p ((:) x xs) = Case_1627750009 p x xs (Let1627749996Scrutinee_1627749199Sym3 p x xs) 

type family Partition a a :: ([a], [a]) Source

Equations

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

Indexing lists

type family a :!! a :: a Source

Equations

`[]` :!! _z_1627749360 = Apply ErrorSym0 "Data.Singletons.List.!!: index too large" 
((:) x xs) :!! n = Case_1627749379 x xs n (Let1627749366Scrutinee_1627749239Sym3 x xs n) 

type family ElemIndex a a :: Maybe Nat Source

Equations

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

type family ElemIndices a a :: [Nat] Source

Equations

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

type family FindIndex a a :: Maybe Nat Source

Equations

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

type family FindIndices a a :: [Nat] Source

Equations

FindIndices p xs = Apply (Apply MapSym0 SndSym0) (Apply (Apply FilterSym0 (Apply (Apply Lambda_1627750891Sym0 p) xs)) (Apply (Apply ZipSym0 xs) (Apply (Apply (Let1627750862BuildListSym2 p xs) (FromInteger 0)) xs))) 

Zipping and unzipping lists

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

Equations

Zip ((:) x xs) ((:) y ys) = Apply (Apply (:$) (Apply (Apply Tuple2Sym0 x) y)) (Apply (Apply ZipSym0 xs) ys) 
Zip `[]` `[]` = `[]` 
Zip ((:) _z_1627750839 _z_1627750842) `[]` = `[]` 
Zip `[]` ((:) _z_1627750845 _z_1627750848) = `[]` 

type family Zip3 a a a :: [(a, b, c)] 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_1627750772 _z_1627750775) = `[]` 
Zip3 `[]` ((:) _z_1627750778 _z_1627750781) `[]` = `[]` 
Zip3 `[]` ((:) _z_1627750784 _z_1627750787) ((:) _z_1627750790 _z_1627750793) = `[]` 
Zip3 ((:) _z_1627750796 _z_1627750799) `[]` `[]` = `[]` 
Zip3 ((:) _z_1627750802 _z_1627750805) `[]` ((:) _z_1627750808 _z_1627750811) = `[]` 
Zip3 ((:) _z_1627750814 _z_1627750817) ((:) _z_1627750820 _z_1627750823) `[]` = `[]` 

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

Equations

Zip4 a_1627972433 a_1627972435 a_1627972437 a_1627972439 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_1627972433) a_1627972435) a_1627972437) a_1627972439 

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

Equations

Zip5 a_1627972388 a_1627972390 a_1627972392 a_1627972394 a_1627972396 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_1627972388) a_1627972390) a_1627972392) a_1627972394) a_1627972396 

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

Equations

Zip6 a_1627972331 a_1627972333 a_1627972335 a_1627972337 a_1627972339 a_1627972341 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_1627972331) a_1627972333) a_1627972335) a_1627972337) a_1627972339) a_1627972341 

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

Equations

Zip7 a_1627972261 a_1627972263 a_1627972265 a_1627972267 a_1627972269 a_1627972271 a_1627972273 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_1627972261) a_1627972263) a_1627972265) a_1627972267) a_1627972269) a_1627972271) a_1627972273 

type family ZipWith a a a :: [c] Source

Equations

ZipWith f ((:) x xs) ((:) y ys) = Apply (Apply (:$) (Apply (Apply f x) y)) (Apply (Apply (Apply ZipWithSym0 f) xs) ys) 
ZipWith _z_1627750730 `[]` `[]` = `[]` 
ZipWith _z_1627750733 ((:) _z_1627750736 _z_1627750739) `[]` = `[]` 
ZipWith _z_1627750742 `[]` ((:) _z_1627750745 _z_1627750748) = `[]` 

type family ZipWith3 a a a a :: [d] 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_1627750635 `[]` `[]` `[]` = `[]` 
ZipWith3 _z_1627750638 `[]` `[]` ((:) _z_1627750641 _z_1627750644) = `[]` 
ZipWith3 _z_1627750647 `[]` ((:) _z_1627750650 _z_1627750653) `[]` = `[]` 
ZipWith3 _z_1627750656 `[]` ((:) _z_1627750659 _z_1627750662) ((:) _z_1627750665 _z_1627750668) = `[]` 
ZipWith3 _z_1627750671 ((:) _z_1627750674 _z_1627750677) `[]` `[]` = `[]` 
ZipWith3 _z_1627750680 ((:) _z_1627750683 _z_1627750686) `[]` ((:) _z_1627750689 _z_1627750692) = `[]` 
ZipWith3 _z_1627750695 ((:) _z_1627750698 _z_1627750701) ((:) _z_1627750704 _z_1627750707) `[]` = `[]` 

type family ZipWith4 a a a a a :: [e] 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_1627972246 _z_1627972249 _z_1627972252 _z_1627972255 _z_1627972258 = `[]` 

type family ZipWith5 a a a a a a :: [f] 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_1627972189 _z_1627972192 _z_1627972195 _z_1627972198 _z_1627972201 _z_1627972204 = `[]` 

type family ZipWith6 a a a a a a a :: [g] 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_1627972118 _z_1627972121 _z_1627972124 _z_1627972127 _z_1627972130 _z_1627972133 _z_1627972136 = `[]` 

type family ZipWith7 a a a a a a a a :: [h] 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_1627972032 _z_1627972035 _z_1627972038 _z_1627972041 _z_1627972044 _z_1627972047 _z_1627972050 _z_1627972053 = `[]` 

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

Equations

Unzip xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_1627750581Sym0 xs)) (Apply (Apply Tuple2Sym0 `[]`) `[]`)) xs 

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

Equations

Unzip3 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_1627750549Sym0 xs)) (Apply (Apply (Apply Tuple3Sym0 `[]`) `[]`) `[]`)) xs 

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

Equations

Unzip4 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_1627750515Sym0 xs)) (Apply (Apply (Apply (Apply Tuple4Sym0 `[]`) `[]`) `[]`) `[]`)) xs 

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

Equations

Unzip5 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_1627750479Sym0 xs)) (Apply (Apply (Apply (Apply (Apply Tuple5Sym0 `[]`) `[]`) `[]`) `[]`) `[]`)) xs 

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

Equations

Unzip6 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_1627750441Sym0 xs)) (Apply (Apply (Apply (Apply (Apply (Apply Tuple6Sym0 `[]`) `[]`) `[]`) `[]`) `[]`) `[]`)) xs 

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

Equations

Unzip7 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_1627750401Sym0 xs)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply Tuple7Sym0 `[]`) `[]`) `[]`) `[]`) `[]`) `[]`) `[]`)) xs 

Special lists

"Set" operations

type family Nub a :: [a] Source

Equations

Nub l = Apply (Apply (Let1627750988Nub'Sym1 l) l) `[]` 

type family Delete a a :: [a] Source

Equations

Delete a_1627750366 a_1627750368 = Apply (Apply (Apply DeleteBySym0 (:==$)) a_1627750366) a_1627750368 

type family a :\\ a :: [a] infix 5 Source

Equations

a_1627750381 :\\ a_1627750383 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 DeleteSym0)) a_1627750381) a_1627750383 

type family Union a a :: [a] Source

Equations

Union a_1627750351 a_1627750353 = Apply (Apply (Apply UnionBySym0 (:==$)) a_1627750351) a_1627750353 

type family Intersect a a :: [a] Source

Equations

Intersect a_1627750154 a_1627750156 = Apply (Apply (Apply IntersectBySym0 (:==$)) a_1627750154) a_1627750156 

Ordered lists

type family Sort a :: [a] Source

Equations

Sort a_1627750257 = Apply (Apply SortBySym0 CompareSym0) a_1627750257 

type family Insert a a :: [a] 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 a :: [a] Source

Equations

NubBy eq l = Apply (Apply (Let1627749295NubBy'Sym2 eq l) l) `[]` 

type family DeleteBy a a a :: [a] Source

Equations

DeleteBy _z_1627750279 _z_1627750282 `[]` = `[]` 
DeleteBy eq x ((:) y ys) = Case_1627750308 eq x y ys (Let1627750289Scrutinee_1627749183Sym4 eq x y ys) 

type family DeleteFirstsBy a a a :: [a] Source

Equations

DeleteFirstsBy eq a_1627750326 a_1627750328 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_1627750326) a_1627750328 

type family UnionBy a a a :: [a] 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 a :: [[a]] Source

Equations

GroupBy _z_1627749840 `[]` = `[]` 
GroupBy eq ((:) x xs) = Apply (Apply (:$) (Apply (Apply (:$) x) (Let1627749846YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let1627749846ZsSym3 eq x xs)) 

type family IntersectBy a a a :: [a] Source

Equations

IntersectBy _z_1627750040 `[]` `[]` = `[]` 
IntersectBy _z_1627750043 `[]` ((:) _z_1627750046 _z_1627750049) = `[]` 
IntersectBy _z_1627750052 ((:) _z_1627750055 _z_1627750058) `[]` = `[]` 
IntersectBy eq ((:) wild_1627749203 wild_1627749205) ((:) wild_1627749207 wild_1627749209) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_1627750117Sym0 eq) wild_1627749203) wild_1627749205) wild_1627749207) wild_1627749209)) (Let1627750066XsSym5 eq wild_1627749203 wild_1627749205 wild_1627749207 wild_1627749209) 

User-supplied comparison (replacing an Ord context)

type family SortBy a a :: [a] Source

Equations

SortBy cmp a_1627750253 = Apply (Apply (Apply FoldrSym0 (Apply InsertBySym0 cmp)) `[]`) a_1627750253 

type family InsertBy a a a :: [a] Source

Equations

InsertBy _z_1627750184 x `[]` = Apply (Apply (:$) x) `[]` 
InsertBy cmp x ((:) y ys') = Case_1627750230 cmp x y ys' (Let1627750211Scrutinee_1627749185Sym4 cmp x y ys') 

type family MaximumBy a a :: a Source

Equations

MaximumBy _z_1627751736 `[]` = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" 
MaximumBy cmp ((:) wild_1627749189 wild_1627749191) = Apply (Apply Foldl1Sym0 (Let1627751755MaxBySym3 cmp wild_1627749189 wild_1627749191)) (Let1627751742XsSym3 cmp wild_1627749189 wild_1627749191) 

type family MinimumBy a a :: a Source

Equations

MinimumBy _z_1627751823 `[]` = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" 
MinimumBy cmp ((:) wild_1627749195 wild_1627749197) = Apply (Apply Foldl1Sym0 (Let1627751842MinBySym3 cmp wild_1627749195 wild_1627749197)) (Let1627751829XsSym3 cmp wild_1627749195 wild_1627749197) 

The "generic" operations

type family GenericLength a :: i Source

Equations

GenericLength `[]` = FromInteger 0 
GenericLength ((:) _z_1627749255 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply GenericLengthSym0 xs) 

type family GenericTake a a :: [a] Source

Equations

GenericTake a_1627971942 a_1627971944 = Apply (Apply TakeSym0 a_1627971942) a_1627971944 

type family GenericDrop a a :: [a] Source

Equations

GenericDrop a_1627971927 a_1627971929 = Apply (Apply DropSym0 a_1627971927) a_1627971929 

type family GenericSplitAt a a :: ([a], [a]) Source

Equations

GenericSplitAt a_1627971912 a_1627971914 = Apply (Apply SplitAtSym0 a_1627971912) a_1627971914 

type family GenericIndex a a :: a Source

Equations

GenericIndex a_1627971897 a_1627971899 = Apply (Apply (:!!$) a_1627971897) a_1627971899 

type family GenericReplicate a a :: [a] Source

Equations

GenericReplicate a_1627971882 a_1627971884 = Apply (Apply ReplicateSym0 a_1627971882) a_1627971884 

Defunctionalization symbols

type NilSym0 = `[]` Source

data (:$) l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun [k] [k] -> *) -> *) ((:$) k) Source 
type Apply (TyFun [k] [k] -> *) k ((:$) k) l0 = (:$$) k l0 Source 

data l :$$ l Source

Instances

SuppressUnusedWarnings (k -> TyFun [k] [k] -> *) ((:$$) k) Source 
type Apply [k] [k] ((:$$) k l1) l0 = (:$$$) k l1 l0 Source 

type (:$$$) t t = (:) t t Source

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

data l :++$$ l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] [k] -> *) ((:++$$) k) Source 
type Apply [k] [k] ((:++$$) k l1) l0 = (:++$$$) k l1 l0 Source 

data (:++$) l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] [k] -> *) -> *) ((:++$) k) Source 
type Apply (TyFun [k] [k] -> *) [k] ((:++$) k) l0 = (:++$$) k l0 Source 

data HeadSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] k -> *) (HeadSym0 k) Source 
type Apply k [k] (HeadSym0 k) l0 = HeadSym1 k l0 Source 

type HeadSym1 t = Head t Source

data LastSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] k -> *) (LastSym0 k) Source 
type Apply k [k] (LastSym0 k) l0 = LastSym1 k l0 Source 

type LastSym1 t = Last t Source

data TailSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] [k] -> *) (TailSym0 k) Source 
type Apply [k] [k] (TailSym0 k) l0 = TailSym1 k l0 Source 

type TailSym1 t = Tail t Source

data InitSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] [k] -> *) (InitSym0 k) Source 
type Apply [k] [k] (InitSym0 k) l0 = InitSym1 k l0 Source 

type InitSym1 t = Init t Source

data NullSym0 l Source

Instances

type NullSym1 t = Null t Source

data MapSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k k -> *) (TyFun [k] [k] -> *) -> *) (MapSym0 k k) Source 
type Apply (TyFun [k] [k1] -> *) (TyFun k k1 -> *) (MapSym0 k k1) l0 = MapSym1 k k1 l0 Source 

data MapSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k k -> *) -> TyFun [k] [k] -> *) (MapSym1 k k) Source 
type Apply [k1] [k] (MapSym1 k k1 l1) l0 = MapSym2 k k1 l1 l0 Source 

type MapSym2 t t = Map t t Source

data ReverseSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] [k] -> *) (ReverseSym0 k) Source 
type Apply [k] [k] (ReverseSym0 k) l0 = ReverseSym1 k l0 Source 

data IntersperseSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun [k] [k] -> *) -> *) (IntersperseSym0 k) Source 
type Apply (TyFun [k] [k] -> *) k (IntersperseSym0 k) l0 = IntersperseSym1 k l0 Source 

data IntersperseSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun [k] [k] -> *) (IntersperseSym1 k) Source 
type Apply [k] [k] (IntersperseSym1 k l1) l0 = IntersperseSym2 k l1 l0 Source 

data IntercalateSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [[k]] [k] -> *) -> *) (IntercalateSym0 k) Source 
type Apply (TyFun [[k]] [k] -> *) [k] (IntercalateSym0 k) l0 = IntercalateSym1 k l0 Source 

data IntercalateSym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [[k]] [k] -> *) (IntercalateSym1 k) Source 
type Apply [k] [[k]] (IntercalateSym1 k l1) l0 = IntercalateSym2 k l1 l0 Source 

data SubsequencesSym0 l Source

Instances

data PermutationsSym0 l Source

Instances

data FoldlSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k k -> *) -> *) (TyFun k (TyFun [k] k -> *) -> *) -> *) (FoldlSym0 k k) Source 
type Apply (TyFun k1 (TyFun [k] k1 -> *) -> *) (TyFun k1 (TyFun k k1 -> *) -> *) (FoldlSym0 k k1) l0 = FoldlSym1 k k1 l0 Source 

data FoldlSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> TyFun k (TyFun [k] k -> *) -> *) (FoldlSym1 k k) Source 
type Apply (TyFun [k1] k -> *) k (FoldlSym1 k1 k l1) l0 = FoldlSym2 k1 k l1 l0 Source 

data FoldlSym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> k -> TyFun [k] k -> *) (FoldlSym2 k k) Source 
type Apply k1 [k] (FoldlSym2 k k1 l1 l2) l0 = FoldlSym3 k1 k l1 l2 l0 Source 

type FoldlSym3 t t t = Foldl t t t Source

data Foldl'Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k k -> *) -> *) (TyFun k (TyFun [k] k -> *) -> *) -> *) (Foldl'Sym0 k k) Source 
type Apply (TyFun k1 (TyFun [k] k1 -> *) -> *) (TyFun k1 (TyFun k k1 -> *) -> *) (Foldl'Sym0 k k1) l0 = Foldl'Sym1 k k1 l0 Source 

data Foldl'Sym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> TyFun k (TyFun [k] k -> *) -> *) (Foldl'Sym1 k k) Source 
type Apply (TyFun [k1] k -> *) k (Foldl'Sym1 k1 k l1) l0 = Foldl'Sym2 k1 k l1 l0 Source 

data Foldl'Sym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> k -> TyFun [k] k -> *) (Foldl'Sym2 k k) Source 
type Apply k1 [k] (Foldl'Sym2 k k1 l1 l2) l0 = Foldl'Sym3 k1 k l1 l2 l0 Source 

type Foldl'Sym3 t t t = Foldl' t t t Source

data Foldl1Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k k -> *) -> *) (TyFun [k] k -> *) -> *) (Foldl1Sym0 k) Source 
type Apply (TyFun [k] k -> *) (TyFun k (TyFun k k -> *) -> *) (Foldl1Sym0 k) l0 = Foldl1Sym1 k l0 Source 

data Foldl1Sym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> TyFun [k] k -> *) (Foldl1Sym1 k) Source 
type Apply k [k] (Foldl1Sym1 k l1) l0 = Foldl1Sym2 k l1 l0 Source 

type Foldl1Sym2 t t = Foldl1 t t Source

data Foldl1'Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k k -> *) -> *) (TyFun [k] k -> *) -> *) (Foldl1'Sym0 k) Source 
type Apply (TyFun [k] k -> *) (TyFun k (TyFun k k -> *) -> *) (Foldl1'Sym0 k) l0 = Foldl1'Sym1 k l0 Source 

data Foldl1'Sym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> TyFun [k] k -> *) (Foldl1'Sym1 k) Source 
type Apply k [k] (Foldl1'Sym1 k l1) l0 = Foldl1'Sym2 k l1 l0 Source 

type Foldl1'Sym2 t t = Foldl1' t t Source

data FoldrSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k k -> *) -> *) (TyFun k (TyFun [k] k -> *) -> *) -> *) (FoldrSym0 k k) Source 
type Apply (TyFun k1 (TyFun [k] k1 -> *) -> *) (TyFun k (TyFun k1 k1 -> *) -> *) (FoldrSym0 k k1) l0 = FoldrSym1 k k1 l0 Source 

data FoldrSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> TyFun k (TyFun [k] k -> *) -> *) (FoldrSym1 k k) Source 
type Apply (TyFun [k1] k -> *) k (FoldrSym1 k1 k l1) l0 = FoldrSym2 k1 k l1 l0 Source 

data FoldrSym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> k -> TyFun [k] k -> *) (FoldrSym2 k k) Source 
type Apply k1 [k] (FoldrSym2 k k1 l1 l2) l0 = FoldrSym3 k k1 l1 l2 l0 Source 

type FoldrSym3 t t t = Foldr t t t Source

data Foldr1Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k k -> *) -> *) (TyFun [k] k -> *) -> *) (Foldr1Sym0 k) Source 
type Apply (TyFun [k] k -> *) (TyFun k (TyFun k k -> *) -> *) (Foldr1Sym0 k) l0 = Foldr1Sym1 k l0 Source 

data Foldr1Sym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> TyFun [k] k -> *) (Foldr1Sym1 k) Source 
type Apply k [k] (Foldr1Sym1 k l1) l0 = Foldr1Sym2 k l1 l0 Source 

type Foldr1Sym2 t t = Foldr1 t t Source

data ConcatSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [[k]] [k] -> *) (ConcatSym0 k) Source 
type Apply [k] [[k]] (ConcatSym0 k) l0 = ConcatSym1 k l0 Source 

data ConcatMapSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k [k] -> *) (TyFun [k] [k] -> *) -> *) (ConcatMapSym0 k k) Source 
type Apply (TyFun [k] [k1] -> *) (TyFun k [k1] -> *) (ConcatMapSym0 k k1) l0 = ConcatMapSym1 k k1 l0 Source 

data ConcatMapSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k [k] -> *) -> TyFun [k] [k] -> *) (ConcatMapSym1 k k) Source 
type Apply [k1] [k] (ConcatMapSym1 k k1 l1) l0 = ConcatMapSym2 k k1 l1 l0 Source 

type AndSym1 t = And t Source

type OrSym1 t = Or t Source

data Any_Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k Bool -> *) (TyFun [k] Bool -> *) -> *) (Any_Sym0 k) Source 
type Apply (TyFun [k] Bool -> *) (TyFun k Bool -> *) (Any_Sym0 k) l0 = Any_Sym1 k l0 Source 

data Any_Sym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] Bool -> *) (Any_Sym1 k) Source 
type Apply Bool [k] (Any_Sym1 k l1) l0 = Any_Sym2 k l1 l0 Source 

type Any_Sym2 t t = Any_ t t Source

data AllSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k Bool -> *) (TyFun [k] Bool -> *) -> *) (AllSym0 k) Source 
type Apply (TyFun [k] Bool -> *) (TyFun k Bool -> *) (AllSym0 k) l0 = AllSym1 k l0 Source 

data AllSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] Bool -> *) (AllSym1 k) Source 
type Apply Bool [k] (AllSym1 k l1) l0 = AllSym2 k l1 l0 Source 

type AllSym2 t t = All t t Source

data ScanlSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k k -> *) -> *) (TyFun k (TyFun [k] [k] -> *) -> *) -> *) (ScanlSym0 k k) Source 
type Apply (TyFun k (TyFun [k1] [k] -> *) -> *) (TyFun k (TyFun k1 k -> *) -> *) (ScanlSym0 k k1) l0 = ScanlSym1 k k1 l0 Source 

data ScanlSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> TyFun k (TyFun [k] [k] -> *) -> *) (ScanlSym1 k k) Source 
type Apply (TyFun [k1] [k] -> *) k (ScanlSym1 k k1 l1) l0 = ScanlSym2 k k1 l1 l0 Source 

data ScanlSym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> k -> TyFun [k] [k] -> *) (ScanlSym2 k k) Source 
type Apply [k] [k1] (ScanlSym2 k k1 l1 l2) l0 = ScanlSym3 k k1 l1 l2 l0 Source 

type ScanlSym3 t t t = Scanl t t t Source

data Scanl1Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k k -> *) -> *) (TyFun [k] [k] -> *) -> *) (Scanl1Sym0 k) Source 
type Apply (TyFun [k] [k] -> *) (TyFun k (TyFun k k -> *) -> *) (Scanl1Sym0 k) l0 = Scanl1Sym1 k l0 Source 

data Scanl1Sym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> TyFun [k] [k] -> *) (Scanl1Sym1 k) Source 
type Apply [k] [k] (Scanl1Sym1 k l1) l0 = Scanl1Sym2 k l1 l0 Source 

type Scanl1Sym2 t t = Scanl1 t t Source

data ScanrSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k k -> *) -> *) (TyFun k (TyFun [k] [k] -> *) -> *) -> *) (ScanrSym0 k k) Source 
type Apply (TyFun k1 (TyFun [k] [k1] -> *) -> *) (TyFun k (TyFun k1 k1 -> *) -> *) (ScanrSym0 k k1) l0 = ScanrSym1 k k1 l0 Source 

data ScanrSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> TyFun k (TyFun [k] [k] -> *) -> *) (ScanrSym1 k k) Source 
type Apply (TyFun [k1] [k] -> *) k (ScanrSym1 k1 k l1) l0 = ScanrSym2 k1 k l1 l0 Source 

data ScanrSym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> k -> TyFun [k] [k] -> *) (ScanrSym2 k k) Source 
type Apply [k1] [k] (ScanrSym2 k k1 l1 l2) l0 = ScanrSym3 k k1 l1 l2 l0 Source 

type ScanrSym3 t t t = Scanr t t t Source

data Scanr1Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k k -> *) -> *) (TyFun [k] [k] -> *) -> *) (Scanr1Sym0 k) Source 
type Apply (TyFun [k] [k] -> *) (TyFun k (TyFun k k -> *) -> *) (Scanr1Sym0 k) l0 = Scanr1Sym1 k l0 Source 

data Scanr1Sym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> TyFun [k] [k] -> *) (Scanr1Sym1 k) Source 
type Apply [k] [k] (Scanr1Sym1 k l1) l0 = Scanr1Sym2 k l1 l0 Source 

type Scanr1Sym2 t t = Scanr1 t t Source

data MapAccumLSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k ((,) k k) -> *) -> *) (TyFun k (TyFun [k] ((,) k [k]) -> *) -> *) -> *) (MapAccumLSym0 k k k) Source 
type Apply (TyFun k (TyFun [k1] ((,) k [k2]) -> *) -> *) (TyFun k (TyFun k1 ((,) k k2) -> *) -> *) (MapAccumLSym0 k k1 k2) l0 = MapAccumLSym1 k k1 k2 l0 Source 

data MapAccumLSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k ((,) k k) -> *) -> *) -> TyFun k (TyFun [k] ((,) k [k]) -> *) -> *) (MapAccumLSym1 k k k) Source 
type Apply (TyFun [k1] ((,) k [k2]) -> *) k (MapAccumLSym1 k k1 k2 l1) l0 = MapAccumLSym2 k k1 k2 l1 l0 Source 

data MapAccumLSym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k ((,) k k) -> *) -> *) -> k -> TyFun [k] ((,) k [k]) -> *) (MapAccumLSym2 k k k) Source 
type Apply ((,) k [k2]) [k1] (MapAccumLSym2 k k1 k2 l1 l2) l0 = MapAccumLSym3 k k1 k2 l1 l2 l0 Source 

type MapAccumLSym3 t t t = MapAccumL t t t Source

data MapAccumRSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k ((,) k k) -> *) -> *) (TyFun k (TyFun [k] ((,) k [k]) -> *) -> *) -> *) (MapAccumRSym0 k k k) Source 
type Apply (TyFun k (TyFun [k1] ((,) k [k2]) -> *) -> *) (TyFun k (TyFun k1 ((,) k k2) -> *) -> *) (MapAccumRSym0 k k1 k2) l0 = MapAccumRSym1 k k1 k2 l0 Source 

data MapAccumRSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k ((,) k k) -> *) -> *) -> TyFun k (TyFun [k] ((,) k [k]) -> *) -> *) (MapAccumRSym1 k k k) Source 
type Apply (TyFun [k1] ((,) k [k2]) -> *) k (MapAccumRSym1 k k1 k2 l1) l0 = MapAccumRSym2 k k1 k2 l1 l0 Source 

data MapAccumRSym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k ((,) k k) -> *) -> *) -> k -> TyFun [k] ((,) k [k]) -> *) (MapAccumRSym2 k k k) Source 
type Apply ((,) k [k2]) [k1] (MapAccumRSym2 k k1 k2 l1 l2) l0 = MapAccumRSym3 k k1 k2 l1 l2 l0 Source 

type MapAccumRSym3 t t t = MapAccumR t t t Source

data UnfoldrSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (Maybe ((,) k k)) -> *) (TyFun k [k] -> *) -> *) (UnfoldrSym0 k k) Source 
type Apply (TyFun k [k1] -> *) (TyFun k (Maybe ((,) k1 k)) -> *) (UnfoldrSym0 k k1) l0 = UnfoldrSym1 k k1 l0 Source 

data UnfoldrSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (Maybe ((,) k k)) -> *) -> TyFun k [k] -> *) (UnfoldrSym1 k k) Source 
type Apply [k1] k (UnfoldrSym1 k k1 l1) l0 = UnfoldrSym2 k k1 l1 l0 Source 

type UnfoldrSym2 t t = Unfoldr t t Source

data InitsSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] [[k]] -> *) (InitsSym0 k) Source 
type Apply [[k]] [k] (InitsSym0 k) l0 = InitsSym1 k l0 Source 

data TailsSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] [[k]] -> *) (TailsSym0 k) Source 
type Apply [[k]] [k] (TailsSym0 k) l0 = TailsSym1 k l0 Source 

data IsPrefixOfSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] Bool -> *) -> *) (IsPrefixOfSym0 k) Source 
type Apply (TyFun [k] Bool -> *) [k] (IsPrefixOfSym0 k) l0 = IsPrefixOfSym1 k l0 Source 

data IsPrefixOfSym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] Bool -> *) (IsPrefixOfSym1 k) Source 
type Apply Bool [k] (IsPrefixOfSym1 k l1) l0 = IsPrefixOfSym2 k l1 l0 Source 

data IsSuffixOfSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] Bool -> *) -> *) (IsSuffixOfSym0 k) Source 
type Apply (TyFun [k] Bool -> *) [k] (IsSuffixOfSym0 k) l0 = IsSuffixOfSym1 k l0 Source 

data IsSuffixOfSym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] Bool -> *) (IsSuffixOfSym1 k) Source 
type Apply Bool [k] (IsSuffixOfSym1 k l1) l0 = IsSuffixOfSym2 k l1 l0 Source 

data IsInfixOfSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] Bool -> *) -> *) (IsInfixOfSym0 k) Source 
type Apply (TyFun [k] Bool -> *) [k] (IsInfixOfSym0 k) l0 = IsInfixOfSym1 k l0 Source 

data IsInfixOfSym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] Bool -> *) (IsInfixOfSym1 k) Source 
type Apply Bool [k] (IsInfixOfSym1 k l1) l0 = IsInfixOfSym2 k l1 l0 Source 

data ElemSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun [k] Bool -> *) -> *) (ElemSym0 k) Source 
type Apply (TyFun [k] Bool -> *) k (ElemSym0 k) l0 = ElemSym1 k l0 Source 

data ElemSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun [k] Bool -> *) (ElemSym1 k) Source 
type Apply Bool [k] (ElemSym1 k l1) l0 = ElemSym2 k l1 l0 Source 

type ElemSym2 t t = Elem t t Source

data NotElemSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun [k] Bool -> *) -> *) (NotElemSym0 k) Source 
type Apply (TyFun [k] Bool -> *) k (NotElemSym0 k) l0 = NotElemSym1 k l0 Source 

data NotElemSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun [k] Bool -> *) (NotElemSym1 k) Source 
type Apply Bool [k] (NotElemSym1 k l1) l0 = NotElemSym2 k l1 l0 Source 

type NotElemSym2 t t = NotElem t t Source

data ZipSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] [(,) k k] -> *) -> *) (ZipSym0 k k) Source 
type Apply (TyFun [k1] [(,) k k1] -> *) [k] (ZipSym0 k k1) l0 = ZipSym1 k k1 l0 Source 

data ZipSym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] [(,) k k] -> *) (ZipSym1 k k) Source 
type Apply [(,) k1 k] [k] (ZipSym1 k1 k l1) l0 = ZipSym2 k1 k l1 l0 Source 

type ZipSym2 t t = Zip t t Source

data Zip3Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] (TyFun [k] [(,,) k k k] -> *) -> *) -> *) (Zip3Sym0 k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] [(,,) k k1 k2] -> *) -> *) [k] (Zip3Sym0 k k1 k2) l0 = Zip3Sym1 k k1 k2 l0 Source 

data Zip3Sym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] (TyFun [k] [(,,) k k k] -> *) -> *) (Zip3Sym1 k k k) Source 
type Apply (TyFun [k1] [(,,) k2 k k1] -> *) [k] (Zip3Sym1 k2 k k1 l1) l0 = Zip3Sym2 k2 k k1 l1 l0 Source 

data Zip3Sym2 l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> TyFun [k] [(,,) k k k] -> *) (Zip3Sym2 k k k) Source 
type Apply [(,,) k1 k2 k] [k] (Zip3Sym2 k1 k2 k l1 l2) l0 = Zip3Sym3 k1 k2 k l1 l2 l0 Source 

type Zip3Sym3 t t t = Zip3 t t t Source

data ZipWithSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k k -> *) -> *) (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) (ZipWithSym0 k k k) Source 
type Apply (TyFun [k] (TyFun [k1] [k2] -> *) -> *) (TyFun k (TyFun k1 k2 -> *) -> *) (ZipWithSym0 k k1 k2) l0 = ZipWithSym1 k k1 k2 l0 Source 

data ZipWithSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> TyFun [k] (TyFun [k] [k] -> *) -> *) (ZipWithSym1 k k k) Source 
type Apply (TyFun [k1] [k2] -> *) [k] (ZipWithSym1 k k1 k2 l1) l0 = ZipWithSym2 k k1 k2 l1 l0 Source 

data ZipWithSym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k k -> *) -> *) -> [k] -> TyFun [k] [k] -> *) (ZipWithSym2 k k k) Source 
type Apply [k2] [k1] (ZipWithSym2 k k1 k2 l1 l2) l0 = ZipWithSym3 k k1 k2 l1 l2 l0 Source 

type ZipWithSym3 t t t = ZipWith t t t Source

data ZipWith3Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) (ZipWith3Sym0 k k k k) Source 
type Apply (TyFun [k] (TyFun [k1] (TyFun [k2] [k3] -> *) -> *) -> *) (TyFun k (TyFun k1 (TyFun k2 k3 -> *) -> *) -> *) (ZipWith3Sym0 k k1 k2 k3) l0 = ZipWith3Sym1 k k1 k2 k3 l0 Source 

data ZipWith3Sym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) (ZipWith3Sym1 k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] [k3] -> *) -> *) [k] (ZipWith3Sym1 k k1 k2 k3 l1) l0 = ZipWith3Sym2 k k1 k2 k3 l1 l0 Source 

data ZipWith3Sym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> [k] -> TyFun [k] (TyFun [k] [k] -> *) -> *) (ZipWith3Sym2 k k k k) Source 
type Apply (TyFun [k2] [k3] -> *) [k1] (ZipWith3Sym2 k k1 k2 k3 l1 l2) l0 = ZipWith3Sym3 k k1 k2 k3 l1 l2 l0 Source 

data ZipWith3Sym3 l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> [k] -> [k] -> TyFun [k] [k] -> *) (ZipWith3Sym3 k k k k) Source 
type Apply [k3] [k2] (ZipWith3Sym3 k k1 k2 k3 l1 l2 l3) l0 = ZipWith3Sym4 k k1 k2 k3 l1 l2 l3 l0 Source 

type ZipWith3Sym4 t t t t = ZipWith3 t t t t Source

data UnzipSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [(,) k k] ((,) [k] [k]) -> *) (UnzipSym0 k k) Source 
type Apply ((,) [k] [k1]) [(,) k k1] (UnzipSym0 k k1) l0 = UnzipSym1 k k1 l0 Source 

data Unzip3Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun [(,,) k k k] ((,,) [k] [k] [k]) -> *) (Unzip3Sym0 k k k) Source 
type Apply ((,,) [k] [k1] [k2]) [(,,) k k1 k2] (Unzip3Sym0 k k1 k2) l0 = Unzip3Sym1 k k1 k2 l0 Source 

data Unzip4Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun [(,,,) k k k k] ((,,,) [k] [k] [k] [k]) -> *) (Unzip4Sym0 k k k k) Source 
type Apply ((,,,) [k] [k1] [k2] [k3]) [(,,,) k k1 k2 k3] (Unzip4Sym0 k k1 k2 k3) l0 = Unzip4Sym1 k k1 k2 k3 l0 Source 

data Unzip5Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun [(,,,,) k k k k k] ((,,,,) [k] [k] [k] [k] [k]) -> *) (Unzip5Sym0 k k k k k) Source 
type Apply ((,,,,) [k] [k1] [k2] [k3] [k4]) [(,,,,) k k1 k2 k3 k4] (Unzip5Sym0 k k1 k2 k3 k4) l0 = Unzip5Sym1 k k1 k2 k3 k4 l0 Source 

data Unzip6Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun [(,,,,,) k k k k k k] ((,,,,,) [k] [k] [k] [k] [k] [k]) -> *) (Unzip6Sym0 k k k k k k) Source 
type Apply ((,,,,,) [k] [k1] [k2] [k3] [k4] [k5]) [(,,,,,) k k1 k2 k3 k4 k5] (Unzip6Sym0 k k1 k2 k3 k4 k5) l0 = Unzip6Sym1 k k1 k2 k3 k4 k5 l0 Source 

data Unzip7Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun [(,,,,,,) k k k k k k k] ((,,,,,,) [k] [k] [k] [k] [k] [k] [k]) -> *) (Unzip7Sym0 k k k k k k k) Source 
type Apply ((,,,,,,) [k] [k1] [k2] [k3] [k4] [k5] [k6]) [(,,,,,,) k k1 k2 k3 k4 k5 k6] (Unzip7Sym0 k k1 k2 k3 k4 k5 k6) l0 = Unzip7Sym1 k k1 k2 k3 k4 k5 k6 l0 Source 

data DeleteSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun [k] [k] -> *) -> *) (DeleteSym0 k) Source 
type Apply (TyFun [k] [k] -> *) k (DeleteSym0 k) l0 = DeleteSym1 k l0 Source 

data DeleteSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun [k] [k] -> *) (DeleteSym1 k) Source 
type Apply [k] [k] (DeleteSym1 k l1) l0 = DeleteSym2 k l1 l0 Source 

type DeleteSym2 t t = Delete t t Source

data (:\\$) l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] [k] -> *) -> *) ((:\\$) k) Source 
type Apply (TyFun [k] [k] -> *) [k] ((:\\$) k) l0 = (:\\$$) k l0 Source 

data l :\\$$ l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] [k] -> *) ((:\\$$) k) Source 
type Apply [k] [k] ((:\\$$) k l1) l0 = (:\\$$$) k l1 l0 Source 

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

data IntersectSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] [k] -> *) -> *) (IntersectSym0 k) Source 
type Apply (TyFun [k] [k] -> *) [k] (IntersectSym0 k) l0 = IntersectSym1 k l0 Source 

data IntersectSym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] [k] -> *) (IntersectSym1 k) Source 
type Apply [k] [k] (IntersectSym1 k l1) l0 = IntersectSym2 k l1 l0 Source 

data InsertSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun [k] [k] -> *) -> *) (InsertSym0 k) Source 
type Apply (TyFun [k] [k] -> *) k (InsertSym0 k) l0 = InsertSym1 k l0 Source 

data InsertSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun [k] [k] -> *) (InsertSym1 k) Source 
type Apply [k] [k] (InsertSym1 k l1) l0 = InsertSym2 k l1 l0 Source 

type InsertSym2 t t = Insert t t Source

data SortSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] [k] -> *) (SortSym0 k) Source 
type Apply [k] [k] (SortSym0 k) l0 = SortSym1 k l0 Source 

type SortSym1 t = Sort t Source

data DeleteBySym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k Bool -> *) -> *) (TyFun k (TyFun [k] [k] -> *) -> *) -> *) (DeleteBySym0 k) Source 
type Apply (TyFun k (TyFun [k] [k] -> *) -> *) (TyFun k (TyFun k Bool -> *) -> *) (DeleteBySym0 k) l0 = DeleteBySym1 k l0 Source 

data DeleteBySym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Bool -> *) -> *) -> TyFun k (TyFun [k] [k] -> *) -> *) (DeleteBySym1 k) Source 
type Apply (TyFun [k] [k] -> *) k (DeleteBySym1 k l1) l0 = DeleteBySym2 k l1 l0 Source 

data DeleteBySym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Bool -> *) -> *) -> k -> TyFun [k] [k] -> *) (DeleteBySym2 k) Source 
type Apply [k] [k] (DeleteBySym2 k l1 l2) l0 = DeleteBySym3 k l1 l2 l0 Source 

type DeleteBySym3 t t t = DeleteBy t t t Source

data DeleteFirstsBySym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k Bool -> *) -> *) (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) (DeleteFirstsBySym0 k) Source 
type Apply (TyFun [k] (TyFun [k] [k] -> *) -> *) (TyFun k (TyFun k Bool -> *) -> *) (DeleteFirstsBySym0 k) l0 = DeleteFirstsBySym1 k l0 Source 

data DeleteFirstsBySym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Bool -> *) -> *) -> TyFun [k] (TyFun [k] [k] -> *) -> *) (DeleteFirstsBySym1 k) Source 
type Apply (TyFun [k] [k] -> *) [k] (DeleteFirstsBySym1 k l1) l0 = DeleteFirstsBySym2 k l1 l0 Source 

data DeleteFirstsBySym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Bool -> *) -> *) -> [k] -> TyFun [k] [k] -> *) (DeleteFirstsBySym2 k) Source 
type Apply [k] [k] (DeleteFirstsBySym2 k l1 l2) l0 = DeleteFirstsBySym3 k l1 l2 l0 Source 

data IntersectBySym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k Bool -> *) -> *) (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) (IntersectBySym0 k) Source 
type Apply (TyFun [k] (TyFun [k] [k] -> *) -> *) (TyFun k (TyFun k Bool -> *) -> *) (IntersectBySym0 k) l0 = IntersectBySym1 k l0 Source 

data IntersectBySym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Bool -> *) -> *) -> TyFun [k] (TyFun [k] [k] -> *) -> *) (IntersectBySym1 k) Source 
type Apply (TyFun [k] [k] -> *) [k] (IntersectBySym1 k l1) l0 = IntersectBySym2 k l1 l0 Source 

data IntersectBySym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Bool -> *) -> *) -> [k] -> TyFun [k] [k] -> *) (IntersectBySym2 k) Source 
type Apply [k] [k] (IntersectBySym2 k l1 l2) l0 = IntersectBySym3 k l1 l2 l0 Source 

data SortBySym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k Ordering -> *) -> *) (TyFun [k] [k] -> *) -> *) (SortBySym0 k) Source 
type Apply (TyFun [k] [k] -> *) (TyFun k (TyFun k Ordering -> *) -> *) (SortBySym0 k) l0 = SortBySym1 k l0 Source 

data SortBySym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Ordering -> *) -> *) -> TyFun [k] [k] -> *) (SortBySym1 k) Source 
type Apply [k] [k] (SortBySym1 k l1) l0 = SortBySym2 k l1 l0 Source 

type SortBySym2 t t = SortBy t t Source

data InsertBySym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k Ordering -> *) -> *) (TyFun k (TyFun [k] [k] -> *) -> *) -> *) (InsertBySym0 k) Source 
type Apply (TyFun k (TyFun [k] [k] -> *) -> *) (TyFun k (TyFun k Ordering -> *) -> *) (InsertBySym0 k) l0 = InsertBySym1 k l0 Source 

data InsertBySym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Ordering -> *) -> *) -> TyFun k (TyFun [k] [k] -> *) -> *) (InsertBySym1 k) Source 
type Apply (TyFun [k] [k] -> *) k (InsertBySym1 k l1) l0 = InsertBySym2 k l1 l0 Source 

data InsertBySym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Ordering -> *) -> *) -> k -> TyFun [k] [k] -> *) (InsertBySym2 k) Source 
type Apply [k] [k] (InsertBySym2 k l1 l2) l0 = InsertBySym3 k l1 l2 l0 Source 

type InsertBySym3 t t t = InsertBy t t t Source

data MaximumBySym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k Ordering -> *) -> *) (TyFun [k] k -> *) -> *) (MaximumBySym0 k) Source 
type Apply (TyFun [k] k -> *) (TyFun k (TyFun k Ordering -> *) -> *) (MaximumBySym0 k) l0 = MaximumBySym1 k l0 Source 

data MaximumBySym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Ordering -> *) -> *) -> TyFun [k] k -> *) (MaximumBySym1 k) Source 
type Apply k [k] (MaximumBySym1 k l1) l0 = MaximumBySym2 k l1 l0 Source 

data MinimumBySym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k Ordering -> *) -> *) (TyFun [k] k -> *) -> *) (MinimumBySym0 k) Source 
type Apply (TyFun [k] k -> *) (TyFun k (TyFun k Ordering -> *) -> *) (MinimumBySym0 k) l0 = MinimumBySym1 k l0 Source 

data MinimumBySym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Ordering -> *) -> *) -> TyFun [k] k -> *) (MinimumBySym1 k) Source 
type Apply k [k] (MinimumBySym1 k l1) l0 = MinimumBySym2 k l1 l0 Source 

data LengthSym0 l Source

Instances

data SumSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] k -> *) (SumSym0 k) Source 
type Apply k [k] (SumSym0 k) l0 = SumSym1 k l0 Source 

type SumSym1 t = Sum t Source

data ProductSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] k -> *) (ProductSym0 k) Source 
type Apply k [k] (ProductSym0 k) l0 = ProductSym1 k l0 Source 

data ReplicateSym0 l Source

Instances

SuppressUnusedWarnings (TyFun Nat (TyFun k [k] -> *) -> *) (ReplicateSym0 k) Source 
type Apply (TyFun k [k] -> *) Nat (ReplicateSym0 k) l0 = ReplicateSym1 k l0 Source 

data ReplicateSym1 l l Source

Instances

SuppressUnusedWarnings (Nat -> TyFun k [k] -> *) (ReplicateSym1 k) Source 
type Apply [k] k (ReplicateSym1 k l1) l0 = ReplicateSym2 k l1 l0 Source 

data TransposeSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [[k]] [[k]] -> *) (TransposeSym0 k) Source 
type Apply [[k]] [[k]] (TransposeSym0 k) l0 = TransposeSym1 k l0 Source 

data TakeSym0 l Source

Instances

SuppressUnusedWarnings (TyFun Nat (TyFun [k] [k] -> *) -> *) (TakeSym0 k) Source 
type Apply (TyFun [k] [k] -> *) Nat (TakeSym0 k) l0 = TakeSym1 k l0 Source 

data TakeSym1 l l Source

Instances

SuppressUnusedWarnings (Nat -> TyFun [k] [k] -> *) (TakeSym1 k) Source 
type Apply [k] [k] (TakeSym1 k l1) l0 = TakeSym2 k l1 l0 Source 

type TakeSym2 t t = Take t t Source

data DropSym0 l Source

Instances

SuppressUnusedWarnings (TyFun Nat (TyFun [k] [k] -> *) -> *) (DropSym0 k) Source 
type Apply (TyFun [k] [k] -> *) Nat (DropSym0 k) l0 = DropSym1 k l0 Source 

data DropSym1 l l Source

Instances

SuppressUnusedWarnings (Nat -> TyFun [k] [k] -> *) (DropSym1 k) Source 
type Apply [k] [k] (DropSym1 k l1) l0 = DropSym2 k l1 l0 Source 

type DropSym2 t t = Drop t t Source

data SplitAtSym0 l Source

Instances

SuppressUnusedWarnings (TyFun Nat (TyFun [k] ((,) [k] [k]) -> *) -> *) (SplitAtSym0 k) Source 
type Apply (TyFun [k] ((,) [k] [k]) -> *) Nat (SplitAtSym0 k) l0 = SplitAtSym1 k l0 Source 

data SplitAtSym1 l l Source

Instances

SuppressUnusedWarnings (Nat -> TyFun [k] ((,) [k] [k]) -> *) (SplitAtSym1 k) Source 
type Apply ((,) [k] [k]) [k] (SplitAtSym1 k l1) l0 = SplitAtSym2 k l1 l0 Source 

type SplitAtSym2 t t = SplitAt t t Source

data TakeWhileSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k Bool -> *) (TyFun [k] [k] -> *) -> *) (TakeWhileSym0 k) Source 
type Apply (TyFun [k] [k] -> *) (TyFun k Bool -> *) (TakeWhileSym0 k) l0 = TakeWhileSym1 k l0 Source 

data TakeWhileSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] [k] -> *) (TakeWhileSym1 k) Source 
type Apply [k] [k] (TakeWhileSym1 k l1) l0 = TakeWhileSym2 k l1 l0 Source 

data DropWhileSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k Bool -> *) (TyFun [k] [k] -> *) -> *) (DropWhileSym0 k) Source 
type Apply (TyFun [k] [k] -> *) (TyFun k Bool -> *) (DropWhileSym0 k) l0 = DropWhileSym1 k l0 Source 

data DropWhileSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] [k] -> *) (DropWhileSym1 k) Source 
type Apply [k] [k] (DropWhileSym1 k l1) l0 = DropWhileSym2 k l1 l0 Source 

data DropWhileEndSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k Bool -> *) (TyFun [k] [k] -> *) -> *) (DropWhileEndSym0 k) Source 
type Apply (TyFun [k] [k] -> *) (TyFun k Bool -> *) (DropWhileEndSym0 k) l0 = DropWhileEndSym1 k l0 Source 

data DropWhileEndSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] [k] -> *) (DropWhileEndSym1 k) Source 
type Apply [k] [k] (DropWhileEndSym1 k l1) l0 = DropWhileEndSym2 k l1 l0 Source 

data SpanSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k Bool -> *) (TyFun [k] ((,) [k] [k]) -> *) -> *) (SpanSym0 k) Source 
type Apply (TyFun [k] ((,) [k] [k]) -> *) (TyFun k Bool -> *) (SpanSym0 k) l0 = SpanSym1 k l0 Source 

data SpanSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] ((,) [k] [k]) -> *) (SpanSym1 k) Source 
type Apply ((,) [k] [k]) [k] (SpanSym1 k l1) l0 = SpanSym2 k l1 l0 Source 

type SpanSym2 t t = Span t t Source

data BreakSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k Bool -> *) (TyFun [k] ((,) [k] [k]) -> *) -> *) (BreakSym0 k) Source 
type Apply (TyFun [k] ((,) [k] [k]) -> *) (TyFun k Bool -> *) (BreakSym0 k) l0 = BreakSym1 k l0 Source 

data BreakSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] ((,) [k] [k]) -> *) (BreakSym1 k) Source 
type Apply ((,) [k] [k]) [k] (BreakSym1 k l1) l0 = BreakSym2 k l1 l0 Source 

type BreakSym2 t t = Break t t Source

data StripPrefixSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] (Maybe [k]) -> *) -> *) (StripPrefixSym0 k) Source 
type Apply (TyFun [k] (Maybe [k]) -> *) [k] (StripPrefixSym0 k) l0 = StripPrefixSym1 k l0 Source 

data StripPrefixSym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] (Maybe [k]) -> *) (StripPrefixSym1 k) Source 
type Apply (Maybe [k]) [k] (StripPrefixSym1 k l1) l0 = StripPrefixSym2 k l1 l0 Source 

data MaximumSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] k -> *) (MaximumSym0 k) Source 
type Apply k [k] (MaximumSym0 k) l0 = MaximumSym1 k l0 Source 

data MinimumSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] k -> *) (MinimumSym0 k) Source 
type Apply k [k] (MinimumSym0 k) l0 = MinimumSym1 k l0 Source 

data GroupSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] [[k]] -> *) (GroupSym0 k) Source 
type Apply [[k]] [k] (GroupSym0 k) l0 = GroupSym1 k l0 Source 

data GroupBySym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k Bool -> *) -> *) (TyFun [k] [[k]] -> *) -> *) (GroupBySym0 k) Source 
type Apply (TyFun [k] [[k]] -> *) (TyFun k (TyFun k Bool -> *) -> *) (GroupBySym0 k) l0 = GroupBySym1 k l0 Source 

data GroupBySym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Bool -> *) -> *) -> TyFun [k] [[k]] -> *) (GroupBySym1 k) Source 
type Apply [[k]] [k] (GroupBySym1 k l1) l0 = GroupBySym2 k l1 l0 Source 

type GroupBySym2 t t = GroupBy t t Source

data LookupSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun [(,) k k] (Maybe k) -> *) -> *) (LookupSym0 k k) Source 
type Apply (TyFun [(,) k k1] (Maybe k1) -> *) k (LookupSym0 k k1) l0 = LookupSym1 k k1 l0 Source 

data LookupSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun [(,) k k] (Maybe k) -> *) (LookupSym1 k k) Source 
type Apply (Maybe k) [(,) k1 k] (LookupSym1 k1 k l1) l0 = LookupSym2 k1 k l1 l0 Source 

type LookupSym2 t t = Lookup t t Source

data FindSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k Bool -> *) (TyFun [k] (Maybe k) -> *) -> *) (FindSym0 k) Source 
type Apply (TyFun [k] (Maybe k) -> *) (TyFun k Bool -> *) (FindSym0 k) l0 = FindSym1 k l0 Source 

data FindSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] (Maybe k) -> *) (FindSym1 k) Source 
type Apply (Maybe k) [k] (FindSym1 k l1) l0 = FindSym2 k l1 l0 Source 

type FindSym2 t t = Find t t Source

data FilterSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k Bool -> *) (TyFun [k] [k] -> *) -> *) (FilterSym0 k) Source 
type Apply (TyFun [k] [k] -> *) (TyFun k Bool -> *) (FilterSym0 k) l0 = FilterSym1 k l0 Source 

data FilterSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] [k] -> *) (FilterSym1 k) Source 
type Apply [k] [k] (FilterSym1 k l1) l0 = FilterSym2 k l1 l0 Source 

type FilterSym2 t t = Filter t t Source

data PartitionSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k Bool -> *) (TyFun [k] ((,) [k] [k]) -> *) -> *) (PartitionSym0 k) Source 
type Apply (TyFun [k] ((,) [k] [k]) -> *) (TyFun k Bool -> *) (PartitionSym0 k) l0 = PartitionSym1 k l0 Source 

data PartitionSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] ((,) [k] [k]) -> *) (PartitionSym1 k) Source 
type Apply ((,) [k] [k]) [k] (PartitionSym1 k l1) l0 = PartitionSym2 k l1 l0 Source 

data (:!!$) l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun Nat k -> *) -> *) ((:!!$) k) Source 
type Apply (TyFun Nat k -> *) [k] ((:!!$) k) l0 = (:!!$$) k l0 Source 

data l :!!$$ l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun Nat k -> *) ((:!!$$) k) Source 
type Apply k Nat ((:!!$$) k l1) l0 = (:!!$$$) k l1 l0 Source 

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

data ElemIndexSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun [k] (Maybe Nat) -> *) -> *) (ElemIndexSym0 k) Source 
type Apply (TyFun [k] (Maybe Nat) -> *) k (ElemIndexSym0 k) l0 = ElemIndexSym1 k l0 Source 

data ElemIndexSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun [k] (Maybe Nat) -> *) (ElemIndexSym1 k) Source 
type Apply (Maybe Nat) [k] (ElemIndexSym1 k l1) l0 = ElemIndexSym2 k l1 l0 Source 

data ElemIndicesSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun [k] [Nat] -> *) -> *) (ElemIndicesSym0 k) Source 
type Apply (TyFun [k] [Nat] -> *) k (ElemIndicesSym0 k) l0 = ElemIndicesSym1 k l0 Source 

data ElemIndicesSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun [k] [Nat] -> *) (ElemIndicesSym1 k) Source 
type Apply [Nat] [k] (ElemIndicesSym1 k l1) l0 = ElemIndicesSym2 k l1 l0 Source 

data FindIndexSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k Bool -> *) (TyFun [k] (Maybe Nat) -> *) -> *) (FindIndexSym0 k) Source 
type Apply (TyFun [k] (Maybe Nat) -> *) (TyFun k Bool -> *) (FindIndexSym0 k) l0 = FindIndexSym1 k l0 Source 

data FindIndexSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] (Maybe Nat) -> *) (FindIndexSym1 k) Source 
type Apply (Maybe Nat) [k] (FindIndexSym1 k l1) l0 = FindIndexSym2 k l1 l0 Source 

data FindIndicesSym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k Bool -> *) (TyFun [k] [Nat] -> *) -> *) (FindIndicesSym0 k) Source 
type Apply (TyFun [k] [Nat] -> *) (TyFun k Bool -> *) (FindIndicesSym0 k) l0 = FindIndicesSym1 k l0 Source 

data FindIndicesSym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] [Nat] -> *) (FindIndicesSym1 k) Source 
type Apply [Nat] [k] (FindIndicesSym1 k l1) l0 = FindIndicesSym2 k l1 l0 Source 

data Zip4Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [(,,,) k k k k] -> *) -> *) -> *) -> *) (Zip4Sym0 k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] [(,,,) k k1 k2 k3] -> *) -> *) -> *) [k] (Zip4Sym0 k k1 k2 k3) l0 = Zip4Sym1 k k1 k2 k3 l0 Source 

data Zip4Sym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] (TyFun [k] (TyFun [k] [(,,,) k k k k] -> *) -> *) -> *) (Zip4Sym1 k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] [(,,,) k3 k k1 k2] -> *) -> *) [k] (Zip4Sym1 k3 k k1 k2 l1) l0 = Zip4Sym2 k3 k k1 k2 l1 l0 Source 

data Zip4Sym2 l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> TyFun [k] (TyFun [k] [(,,,) k k k k] -> *) -> *) (Zip4Sym2 k k k k) Source 
type Apply (TyFun [k1] [(,,,) k2 k3 k k1] -> *) [k] (Zip4Sym2 k2 k3 k k1 l1 l2) l0 = Zip4Sym3 k2 k3 k k1 l1 l2 l0 Source 

data Zip4Sym3 l l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> [k] -> TyFun [k] [(,,,) k k k k] -> *) (Zip4Sym3 k k k k) Source 
type Apply [(,,,) k1 k2 k3 k] [k] (Zip4Sym3 k1 k2 k3 k l1 l2 l3) l0 = Zip4Sym4 k1 k2 k3 k l1 l2 l3 l0 Source 

type Zip4Sym4 t t t t = Zip4 t t t t Source

data Zip5Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [(,,,,) k k k k k] -> *) -> *) -> *) -> *) -> *) (Zip5Sym0 k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] (TyFun [k4] [(,,,,) k k1 k2 k3 k4] -> *) -> *) -> *) -> *) [k] (Zip5Sym0 k k1 k2 k3 k4) l0 = Zip5Sym1 k k1 k2 k3 k4 l0 Source 

data Zip5Sym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [(,,,,) k k k k k] -> *) -> *) -> *) -> *) (Zip5Sym1 k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] [(,,,,) k4 k k1 k2 k3] -> *) -> *) -> *) [k] (Zip5Sym1 k4 k k1 k2 k3 l1) l0 = Zip5Sym2 k4 k k1 k2 k3 l1 l0 Source 

data Zip5Sym2 l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] [(,,,,) k k k k k] -> *) -> *) -> *) (Zip5Sym2 k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] [(,,,,) k3 k4 k k1 k2] -> *) -> *) [k] (Zip5Sym2 k3 k4 k k1 k2 l1 l2) l0 = Zip5Sym3 k3 k4 k k1 k2 l1 l2 l0 Source 

data Zip5Sym3 l l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> [k] -> TyFun [k] (TyFun [k] [(,,,,) k k k k k] -> *) -> *) (Zip5Sym3 k k k k k) Source 
type Apply (TyFun [k1] [(,,,,) k2 k3 k4 k k1] -> *) [k] (Zip5Sym3 k2 k3 k4 k k1 l1 l2 l3) l0 = Zip5Sym4 k2 k3 k4 k k1 l1 l2 l3 l0 Source 

data Zip5Sym4 l l l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> [k] -> [k] -> TyFun [k] [(,,,,) k k k k k] -> *) (Zip5Sym4 k k k k k) Source 
type Apply [(,,,,) k1 k2 k3 k4 k] [k] (Zip5Sym4 k1 k2 k3 k4 k l1 l2 l3 l4) l0 = Zip5Sym5 k1 k2 k3 k4 k l1 l2 l3 l4 l0 Source 

type Zip5Sym5 t t t t t = Zip5 t t t t t Source

data Zip6Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [(,,,,,) k k k k k k] -> *) -> *) -> *) -> *) -> *) -> *) (Zip6Sym0 k k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] (TyFun [k4] (TyFun [k5] [(,,,,,) k k1 k2 k3 k4 k5] -> *) -> *) -> *) -> *) -> *) [k] (Zip6Sym0 k k1 k2 k3 k4 k5) l0 = Zip6Sym1 k k1 k2 k3 k4 k5 l0 Source 

data Zip6Sym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [(,,,,,) k k k k k k] -> *) -> *) -> *) -> *) -> *) (Zip6Sym1 k k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] (TyFun [k4] [(,,,,,) k5 k k1 k2 k3 k4] -> *) -> *) -> *) -> *) [k] (Zip6Sym1 k5 k k1 k2 k3 k4 l1) l0 = Zip6Sym2 k5 k k1 k2 k3 k4 l1 l0 Source 

data Zip6Sym2 l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [(,,,,,) k k k k k k] -> *) -> *) -> *) -> *) (Zip6Sym2 k k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] [(,,,,,) k4 k5 k k1 k2 k3] -> *) -> *) -> *) [k] (Zip6Sym2 k4 k5 k k1 k2 k3 l1 l2) l0 = Zip6Sym3 k4 k5 k k1 k2 k3 l1 l2 l0 Source 

data Zip6Sym3 l l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] [(,,,,,) k k k k k k] -> *) -> *) -> *) (Zip6Sym3 k k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] [(,,,,,) k3 k4 k5 k k1 k2] -> *) -> *) [k] (Zip6Sym3 k3 k4 k5 k k1 k2 l1 l2 l3) l0 = Zip6Sym4 k3 k4 k5 k k1 k2 l1 l2 l3 l0 Source 

data Zip6Sym4 l l l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> [k] -> [k] -> TyFun [k] (TyFun [k] [(,,,,,) k k k k k k] -> *) -> *) (Zip6Sym4 k k k k k k) Source 
type Apply (TyFun [k1] [(,,,,,) k2 k3 k4 k5 k k1] -> *) [k] (Zip6Sym4 k2 k3 k4 k5 k k1 l1 l2 l3 l4) l0 = Zip6Sym5 k2 k3 k4 k5 k k1 l1 l2 l3 l4 l0 Source 

data Zip6Sym5 l l l l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> [k] -> [k] -> [k] -> TyFun [k] [(,,,,,) k k k k k k] -> *) (Zip6Sym5 k k k k k k) Source 
type Apply [(,,,,,) k1 k2 k3 k4 k5 k] [k] (Zip6Sym5 k1 k2 k3 k4 k5 k l1 l2 l3 l4 l5) l0 = Zip6Sym6 k1 k2 k3 k4 k5 k l1 l2 l3 l4 l5 l0 Source 

type Zip6Sym6 t t t t t t = Zip6 t t t t t t Source

data Zip7Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [(,,,,,,) k k k k k k k] -> *) -> *) -> *) -> *) -> *) -> *) -> *) (Zip7Sym0 k k k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] (TyFun [k4] (TyFun [k5] (TyFun [k6] [(,,,,,,) k k1 k2 k3 k4 k5 k6] -> *) -> *) -> *) -> *) -> *) -> *) [k] (Zip7Sym0 k k1 k2 k3 k4 k5 k6) l0 = Zip7Sym1 k k1 k2 k3 k4 k5 k6 l0 Source 

data Zip7Sym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [(,,,,,,) k k k k k k k] -> *) -> *) -> *) -> *) -> *) -> *) (Zip7Sym1 k k k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] (TyFun [k4] (TyFun [k5] [(,,,,,,) k6 k k1 k2 k3 k4 k5] -> *) -> *) -> *) -> *) -> *) [k] (Zip7Sym1 k6 k k1 k2 k3 k4 k5 l1) l0 = Zip7Sym2 k6 k k1 k2 k3 k4 k5 l1 l0 Source 

data Zip7Sym2 l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [(,,,,,,) k k k k k k k] -> *) -> *) -> *) -> *) -> *) (Zip7Sym2 k k k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] (TyFun [k4] [(,,,,,,) k5 k6 k k1 k2 k3 k4] -> *) -> *) -> *) -> *) [k] (Zip7Sym2 k5 k6 k k1 k2 k3 k4 l1 l2) l0 = Zip7Sym3 k5 k6 k k1 k2 k3 k4 l1 l2 l0 Source 

data Zip7Sym3 l l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [(,,,,,,) k k k k k k k] -> *) -> *) -> *) -> *) (Zip7Sym3 k k k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] [(,,,,,,) k4 k5 k6 k k1 k2 k3] -> *) -> *) -> *) [k] (Zip7Sym3 k4 k5 k6 k k1 k2 k3 l1 l2 l3) l0 = Zip7Sym4 k4 k5 k6 k k1 k2 k3 l1 l2 l3 l0 Source 

data Zip7Sym4 l l l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> [k] -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] [(,,,,,,) k k k k k k k] -> *) -> *) -> *) (Zip7Sym4 k k k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] [(,,,,,,) k3 k4 k5 k6 k k1 k2] -> *) -> *) [k] (Zip7Sym4 k3 k4 k5 k6 k k1 k2 l1 l2 l3 l4) l0 = Zip7Sym5 k3 k4 k5 k6 k k1 k2 l1 l2 l3 l4 l0 Source 

data Zip7Sym5 l l l l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> [k] -> [k] -> [k] -> TyFun [k] (TyFun [k] [(,,,,,,) k k k k k k k] -> *) -> *) (Zip7Sym5 k k k k k k k) Source 
type Apply (TyFun [k1] [(,,,,,,) k2 k3 k4 k5 k6 k k1] -> *) [k] (Zip7Sym5 k2 k3 k4 k5 k6 k k1 l1 l2 l3 l4 l5) l0 = Zip7Sym6 k2 k3 k4 k5 k6 k k1 l1 l2 l3 l4 l5 l0 Source 

data Zip7Sym6 l l l l l l l Source

Instances

SuppressUnusedWarnings ([k] -> [k] -> [k] -> [k] -> [k] -> [k] -> TyFun [k] [(,,,,,,) k k k k k k k] -> *) (Zip7Sym6 k k k k k k k) Source 
type Apply [(,,,,,,) k1 k2 k3 k4 k5 k6 k] [k] (Zip7Sym6 k1 k2 k3 k4 k5 k6 k l1 l2 l3 l4 l5 l6) l0 = Zip7Sym7 k1 k2 k3 k4 k5 k6 k l1 l2 l3 l4 l5 l6 l0 Source 

type Zip7Sym7 t t t t t t t = Zip7 t t t t t t t Source

data ZipWith4Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) -> *) (ZipWith4Sym0 k k k k k) Source 
type Apply (TyFun [k] (TyFun [k1] (TyFun [k2] (TyFun [k3] [k4] -> *) -> *) -> *) -> *) (TyFun k (TyFun k1 (TyFun k2 (TyFun k3 k4 -> *) -> *) -> *) -> *) (ZipWith4Sym0 k k1 k2 k3 k4) l0 = ZipWith4Sym1 k k1 k2 k3 k4 l0 Source 

data ZipWith4Sym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) (ZipWith4Sym1 k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] [k4] -> *) -> *) -> *) [k] (ZipWith4Sym1 k k1 k2 k3 k4 l1) l0 = ZipWith4Sym2 k k1 k2 k3 k4 l1 l0 Source 

data ZipWith4Sym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) (ZipWith4Sym2 k k k k k) Source 
type Apply (TyFun [k2] (TyFun [k3] [k4] -> *) -> *) [k1] (ZipWith4Sym2 k k1 k2 k3 k4 l1 l2) l0 = ZipWith4Sym3 k k1 k2 k3 k4 l1 l2 l0 Source 

data ZipWith4Sym3 l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> [k] -> [k] -> TyFun [k] (TyFun [k] [k] -> *) -> *) (ZipWith4Sym3 k k k k k) Source 
type Apply (TyFun [k3] [k4] -> *) [k2] (ZipWith4Sym3 k k1 k2 k3 k4 l1 l2 l3) l0 = ZipWith4Sym4 k k1 k2 k3 k4 l1 l2 l3 l0 Source 

data ZipWith4Sym4 l l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> [k] -> [k] -> [k] -> TyFun [k] [k] -> *) (ZipWith4Sym4 k k k k k) Source 
type Apply [k4] [k3] (ZipWith4Sym4 k k1 k2 k3 k4 l1 l2 l3 l4) l0 = ZipWith4Sym5 k k1 k2 k3 k4 l1 l2 l3 l4 l0 Source 

type ZipWith4Sym5 t t t t t = ZipWith4 t t t t t Source

data ZipWith5Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) -> *) -> *) (ZipWith5Sym0 k k k k k k) Source 
type Apply (TyFun [k] (TyFun [k1] (TyFun [k2] (TyFun [k3] (TyFun [k4] [k5] -> *) -> *) -> *) -> *) -> *) (TyFun k (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 k5 -> *) -> *) -> *) -> *) -> *) (ZipWith5Sym0 k k1 k2 k3 k4 k5) l0 = ZipWith5Sym1 k k1 k2 k3 k4 k5 l0 Source 

data ZipWith5Sym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) -> *) (ZipWith5Sym1 k k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] (TyFun [k4] [k5] -> *) -> *) -> *) -> *) [k] (ZipWith5Sym1 k k1 k2 k3 k4 k5 l1) l0 = ZipWith5Sym2 k k1 k2 k3 k4 k5 l1 l0 Source 

data ZipWith5Sym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) (ZipWith5Sym2 k k k k k k) Source 
type Apply (TyFun [k2] (TyFun [k3] (TyFun [k4] [k5] -> *) -> *) -> *) [k1] (ZipWith5Sym2 k k1 k2 k3 k4 k5 l1 l2) l0 = ZipWith5Sym3 k k1 k2 k3 k4 k5 l1 l2 l0 Source 

data ZipWith5Sym3 l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> [k] -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) (ZipWith5Sym3 k k k k k k) Source 
type Apply (TyFun [k3] (TyFun [k4] [k5] -> *) -> *) [k2] (ZipWith5Sym3 k k1 k2 k3 k4 k5 l1 l2 l3) l0 = ZipWith5Sym4 k k1 k2 k3 k4 k5 l1 l2 l3 l0 Source 

data ZipWith5Sym4 l l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> [k] -> [k] -> [k] -> TyFun [k] (TyFun [k] [k] -> *) -> *) (ZipWith5Sym4 k k k k k k) Source 
type Apply (TyFun [k4] [k5] -> *) [k3] (ZipWith5Sym4 k k1 k2 k3 k4 k5 l1 l2 l3 l4) l0 = ZipWith5Sym5 k k1 k2 k3 k4 k5 l1 l2 l3 l4 l0 Source 

data ZipWith5Sym5 l l l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> [k] -> [k] -> [k] -> [k] -> TyFun [k] [k] -> *) (ZipWith5Sym5 k k k k k k) Source 
type Apply [k5] [k4] (ZipWith5Sym5 k k1 k2 k3 k4 k5 l1 l2 l3 l4 l5) l0 = ZipWith5Sym6 k k1 k2 k3 k4 k5 l1 l2 l3 l4 l5 l0 Source 

type ZipWith5Sym6 t t t t t t = ZipWith5 t t t t t t Source

data ZipWith6Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) -> *) -> *) -> *) (ZipWith6Sym0 k k k k k k k) Source 
type Apply (TyFun [k] (TyFun [k1] (TyFun [k2] (TyFun [k3] (TyFun [k4] (TyFun [k5] [k6] -> *) -> *) -> *) -> *) -> *) -> *) (TyFun k (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 k6 -> *) -> *) -> *) -> *) -> *) -> *) (ZipWith6Sym0 k k1 k2 k3 k4 k5 k6) l0 = ZipWith6Sym1 k k1 k2 k3 k4 k5 k6 l0 Source 

data ZipWith6Sym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) -> *) -> *) (ZipWith6Sym1 k k k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] (TyFun [k4] (TyFun [k5] [k6] -> *) -> *) -> *) -> *) -> *) [k] (ZipWith6Sym1 k k1 k2 k3 k4 k5 k6 l1) l0 = ZipWith6Sym2 k k1 k2 k3 k4 k5 k6 l1 l0 Source 

data ZipWith6Sym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) -> *) (ZipWith6Sym2 k k k k k k k) Source 
type Apply (TyFun [k2] (TyFun [k3] (TyFun [k4] (TyFun [k5] [k6] -> *) -> *) -> *) -> *) [k1] (ZipWith6Sym2 k k1 k2 k3 k4 k5 k6 l1 l2) l0 = ZipWith6Sym3 k k1 k2 k3 k4 k5 k6 l1 l2 l0 Source 

data ZipWith6Sym3 l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> [k] -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) (ZipWith6Sym3 k k k k k k k) Source 
type Apply (TyFun [k3] (TyFun [k4] (TyFun [k5] [k6] -> *) -> *) -> *) [k2] (ZipWith6Sym3 k k1 k2 k3 k4 k5 k6 l1 l2 l3) l0 = ZipWith6Sym4 k k1 k2 k3 k4 k5 k6 l1 l2 l3 l0 Source 

data ZipWith6Sym4 l l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> [k] -> [k] -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) (ZipWith6Sym4 k k k k k k k) Source 
type Apply (TyFun [k4] (TyFun [k5] [k6] -> *) -> *) [k3] (ZipWith6Sym4 k k1 k2 k3 k4 k5 k6 l1 l2 l3 l4) l0 = ZipWith6Sym5 k k1 k2 k3 k4 k5 k6 l1 l2 l3 l4 l0 Source 

data ZipWith6Sym5 l l l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> [k] -> [k] -> [k] -> [k] -> TyFun [k] (TyFun [k] [k] -> *) -> *) (ZipWith6Sym5 k k k k k k k) Source 
type Apply (TyFun [k5] [k6] -> *) [k4] (ZipWith6Sym5 k k1 k2 k3 k4 k5 k6 l1 l2 l3 l4 l5) l0 = ZipWith6Sym6 k k1 k2 k3 k4 k5 k6 l1 l2 l3 l4 l5 l0 Source 

data ZipWith6Sym6 l l l l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> [k] -> [k] -> [k] -> [k] -> [k] -> TyFun [k] [k] -> *) (ZipWith6Sym6 k k k k k k k) Source 
type Apply [k6] [k5] (ZipWith6Sym6 k k1 k2 k3 k4 k5 k6 l1 l2 l3 l4 l5 l6) l0 = ZipWith6Sym7 k k1 k2 k3 k4 k5 k6 l1 l2 l3 l4 l5 l6 l0 Source 

type ZipWith6Sym7 t t t t t t t = ZipWith6 t t t t t t t Source

data ZipWith7Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> *) (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) -> *) -> *) -> *) -> *) (ZipWith7Sym0 k k k k k k k k) Source 
type Apply (TyFun [k] (TyFun [k1] (TyFun [k2] (TyFun [k3] (TyFun [k4] (TyFun [k5] (TyFun [k6] [k7] -> *) -> *) -> *) -> *) -> *) -> *) -> *) (TyFun k (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 (TyFun k6 k7 -> *) -> *) -> *) -> *) -> *) -> *) -> *) (ZipWith7Sym0 k k1 k2 k3 k4 k5 k6 k7) l0 = ZipWith7Sym1 k k1 k2 k3 k4 k5 k6 k7 l0 Source 

data ZipWith7Sym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> *) -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) -> *) -> *) -> *) (ZipWith7Sym1 k k k k k k k k) Source 
type Apply (TyFun [k1] (TyFun [k2] (TyFun [k3] (TyFun [k4] (TyFun [k5] (TyFun [k6] [k7] -> *) -> *) -> *) -> *) -> *) -> *) [k] (ZipWith7Sym1 k k1 k2 k3 k4 k5 k6 k7 l1) l0 = ZipWith7Sym2 k k1 k2 k3 k4 k5 k6 k7 l1 l0 Source 

data ZipWith7Sym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> *) -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) -> *) -> *) (ZipWith7Sym2 k k k k k k k k) Source 
type Apply (TyFun [k2] (TyFun [k3] (TyFun [k4] (TyFun [k5] (TyFun [k6] [k7] -> *) -> *) -> *) -> *) -> *) [k1] (ZipWith7Sym2 k k1 k2 k3 k4 k5 k6 k7 l1 l2) l0 = ZipWith7Sym3 k k1 k2 k3 k4 k5 k6 k7 l1 l2 l0 Source 

data ZipWith7Sym3 l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> *) -> [k] -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) -> *) (ZipWith7Sym3 k k k k k k k k) Source 
type Apply (TyFun [k3] (TyFun [k4] (TyFun [k5] (TyFun [k6] [k7] -> *) -> *) -> *) -> *) [k2] (ZipWith7Sym3 k k1 k2 k3 k4 k5 k6 k7 l1 l2 l3) l0 = ZipWith7Sym4 k k1 k2 k3 k4 k5 k6 k7 l1 l2 l3 l0 Source 

data ZipWith7Sym4 l l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> *) -> [k] -> [k] -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) -> *) (ZipWith7Sym4 k k k k k k k k) Source 
type Apply (TyFun [k4] (TyFun [k5] (TyFun [k6] [k7] -> *) -> *) -> *) [k3] (ZipWith7Sym4 k k1 k2 k3 k4 k5 k6 k7 l1 l2 l3 l4) l0 = ZipWith7Sym5 k k1 k2 k3 k4 k5 k6 k7 l1 l2 l3 l4 l0 Source 

data ZipWith7Sym5 l l l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> *) -> [k] -> [k] -> [k] -> [k] -> TyFun [k] (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) (ZipWith7Sym5 k k k k k k k k) Source 
type Apply (TyFun [k5] (TyFun [k6] [k7] -> *) -> *) [k4] (ZipWith7Sym5 k k1 k2 k3 k4 k5 k6 k7 l1 l2 l3 l4 l5) l0 = ZipWith7Sym6 k k1 k2 k3 k4 k5 k6 k7 l1 l2 l3 l4 l5 l0 Source 

data ZipWith7Sym6 l l l l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> *) -> [k] -> [k] -> [k] -> [k] -> [k] -> TyFun [k] (TyFun [k] [k] -> *) -> *) (ZipWith7Sym6 k k k k k k k k) Source 
type Apply (TyFun [k6] [k7] -> *) [k5] (ZipWith7Sym6 k k1 k2 k3 k4 k5 k6 k7 l1 l2 l3 l4 l5 l6) l0 = ZipWith7Sym7 k k1 k2 k3 k4 k5 k6 k7 l1 l2 l3 l4 l5 l6 l0 Source 

data ZipWith7Sym7 l l l l l l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k (TyFun k k -> *) -> *) -> *) -> *) -> *) -> *) -> *) -> [k] -> [k] -> [k] -> [k] -> [k] -> [k] -> TyFun [k] [k] -> *) (ZipWith7Sym7 k k k k k k k k) Source 
type Apply [k7] [k6] (ZipWith7Sym7 k k1 k2 k3 k4 k5 k6 k7 l1 l2 l3 l4 l5 l6 l7) l0 = ZipWith7Sym8 k k1 k2 k3 k4 k5 k6 k7 l1 l2 l3 l4 l5 l6 l7 l0 Source 

type ZipWith7Sym8 t t t t t t t t = ZipWith7 t t t t t t t t Source

data NubSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] [k] -> *) (NubSym0 k) Source 
type Apply [k] [k] (NubSym0 k) l0 = NubSym1 k l0 Source 

type NubSym1 t = Nub t Source

data NubBySym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k Bool -> *) -> *) (TyFun [k] [k] -> *) -> *) (NubBySym0 k) Source 
type Apply (TyFun [k] [k] -> *) (TyFun k (TyFun k Bool -> *) -> *) (NubBySym0 k) l0 = NubBySym1 k l0 Source 

data NubBySym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Bool -> *) -> *) -> TyFun [k] [k] -> *) (NubBySym1 k) Source 
type Apply [k] [k] (NubBySym1 k l1) l0 = NubBySym2 k l1 l0 Source 

type NubBySym2 t t = NubBy t t Source

data UnionSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun [k] [k] -> *) -> *) (UnionSym0 k) Source 
type Apply (TyFun [k] [k] -> *) [k] (UnionSym0 k) l0 = UnionSym1 k l0 Source 

data UnionSym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun [k] [k] -> *) (UnionSym1 k) Source 
type Apply [k] [k] (UnionSym1 k l1) l0 = UnionSym2 k l1 l0 Source 

type UnionSym2 t t = Union t t Source

data UnionBySym0 l Source

Instances

SuppressUnusedWarnings (TyFun (TyFun k (TyFun k Bool -> *) -> *) (TyFun [k] (TyFun [k] [k] -> *) -> *) -> *) (UnionBySym0 k) Source 
type Apply (TyFun [k] (TyFun [k] [k] -> *) -> *) (TyFun k (TyFun k Bool -> *) -> *) (UnionBySym0 k) l0 = UnionBySym1 k l0 Source 

data UnionBySym1 l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Bool -> *) -> *) -> TyFun [k] (TyFun [k] [k] -> *) -> *) (UnionBySym1 k) Source 
type Apply (TyFun [k] [k] -> *) [k] (UnionBySym1 k l1) l0 = UnionBySym2 k l1 l0 Source 

data UnionBySym2 l l l Source

Instances

SuppressUnusedWarnings ((TyFun k (TyFun k Bool -> *) -> *) -> [k] -> TyFun [k] [k] -> *) (UnionBySym2 k) Source 
type Apply [k] [k] (UnionBySym2 k l1 l2) l0 = UnionBySym3 k l1 l2 l0 Source 

type UnionBySym3 t t t = UnionBy t t t Source

data GenericTakeSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun [k] [k] -> *) -> *) (GenericTakeSym0 k k) Source 
type Apply (TyFun [k1] [k1] -> *) k (GenericTakeSym0 k k1) l0 = GenericTakeSym1 k k1 l0 Source 

data GenericTakeSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun [k] [k] -> *) (GenericTakeSym1 k k) Source 
type Apply [k] [k] (GenericTakeSym1 k1 k l1) l0 = GenericTakeSym2 k1 k l1 l0 Source 

data GenericDropSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun [k] [k] -> *) -> *) (GenericDropSym0 k k) Source 
type Apply (TyFun [k1] [k1] -> *) k (GenericDropSym0 k k1) l0 = GenericDropSym1 k k1 l0 Source 

data GenericDropSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun [k] [k] -> *) (GenericDropSym1 k k) Source 
type Apply [k] [k] (GenericDropSym1 k1 k l1) l0 = GenericDropSym2 k1 k l1 l0 Source 

data GenericSplitAtSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun [k] ((,) [k] [k]) -> *) -> *) (GenericSplitAtSym0 k k) Source 
type Apply (TyFun [k1] ((,) [k1] [k1]) -> *) k (GenericSplitAtSym0 k k1) l0 = GenericSplitAtSym1 k k1 l0 Source 

data GenericSplitAtSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun [k] ((,) [k] [k]) -> *) (GenericSplitAtSym1 k k) Source 
type Apply ((,) [k] [k]) [k] (GenericSplitAtSym1 k1 k l1) l0 = GenericSplitAtSym2 k1 k l1 l0 Source 

data GenericIndexSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] (TyFun k k -> *) -> *) (GenericIndexSym0 k k) Source 
type Apply (TyFun k1 k -> *) [k] (GenericIndexSym0 k k1) l0 = GenericIndexSym1 k k1 l0 Source 

data GenericIndexSym1 l l Source

Instances

SuppressUnusedWarnings ([k] -> TyFun k k -> *) (GenericIndexSym1 k k) Source 
type Apply k1 k (GenericIndexSym1 k1 k l1) l0 = GenericIndexSym2 k1 k l1 l0 Source 

data GenericReplicateSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun k [k] -> *) -> *) (GenericReplicateSym0 k k) Source 
type Apply (TyFun k1 [k1] -> *) k (GenericReplicateSym0 k k1) l0 = GenericReplicateSym1 k k1 l0 Source 

data GenericReplicateSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun k [k] -> *) (GenericReplicateSym1 k k) Source 
type Apply [k] k (GenericReplicateSym1 k1 k l1) l0 = GenericReplicateSym2 k1 k l1 l0 Source