singletons-1.1.1: A framework for generating singleton types

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

Data.Singletons.Prelude.List

Contents

Description

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

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

Synopsis

The singleton for lists

data family Sing a Source

The singleton kind-indexed data family.

Instances

TestCoercion * (Sing *) 
SDecide k (KProxy k) => TestEquality k (Sing k) 
data Sing Bool where 
data Sing Ordering where 
data Sing * where 
data Sing Nat where 
data Sing Symbol where 
data Sing () where 
data Sing [a0] where 
data Sing (Maybe a0) where 
data Sing (TyFun k1 k2 -> *) = SLambda {} 
data Sing (Either a0 b0) where 
data Sing ((,) a0 b0) where 
data Sing ((,,) a0 b0 c0) where 
data Sing ((,,,) a0 b0 c0 d0) where 
data Sing ((,,,,) a0 b0 c0 d0 e0) where 
data Sing ((,,,,,) a0 b0 c0 d0 e0 f0) where 
data Sing ((,,,,,,) a0 b0 c0 d0 e0 f0 g0) where 

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

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

type SList z = Sing z Source

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

Basic functions

type family a :++ a :: [a] Source

Equations

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

(%:++) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:++$) t) t) Source

type family Head a :: a Source

Equations

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

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

type family Last a :: a Source

Equations

Last `[]` = Apply ErrorSym0 "Data.Singletons.List.last: empty list" 
Last ((:) x xs) = Apply (Apply (Let_1627596970Last'Sym2 x xs) x) xs 

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

type family Tail a :: [a] Source

Equations

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

sTail :: forall t. Sing t -> Sing (Apply TailSym0 t) Source

type family Init a :: [a] Source

Equations

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

sInit :: forall t. Sing t -> Sing (Apply InitSym0 t) Source

type family Null a :: Bool Source

Equations

Null `[]` = TrueSym0 
Null ((:) z z) = FalseSym0 

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

List transformations

type family Map a a :: [b] Source

Equations

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

sMap :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t) Source

type family Reverse a :: [a] Source

Equations

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

sReverse :: forall t. Sing t -> Sing (Apply ReverseSym0 t) Source

type family Intersperse a a :: [a] Source

Equations

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

sIntersperse :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t) Source

type family Intercalate a a :: [a] Source

Equations

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

sIntercalate :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t) Source

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 (Let_1627596448PermsSym1 xs0) xs0) `[]`) 

Reducing lists (folds)

type family Foldl a a a :: b Source

Equations

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

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

type family Foldl' a a a :: b Source

Equations

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

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

type family Foldl1 a a :: a Source

Equations

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

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

type family Foldl1' a a :: a Source

Equations

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

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

type family Foldr a a a :: b Source

Equations

Foldr k z a_1627559854 = Apply (Let_1627559859GoSym3 k z a_1627559854) a_1627559854 

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

type family Foldr1 a a :: a Source

Equations

Foldr1 z `[x]` = x 
Foldr1 f ((:) x ((:) wild_1627594821 wild_1627594823)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let_1627596044XsSym4 f x wild_1627594821 wild_1627594823)) 
Foldr1 z `[]` = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" 

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

Special folds

type family Concat a :: [a] Source

Equations

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

sConcat :: forall t. Sing t -> Sing (Apply ConcatSym0 t) Source

type family ConcatMap a a :: [b] Source

Equations

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

sConcatMap :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t) Source

type family And a :: Bool Source

Equations

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

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

type family Or a :: Bool Source

Equations

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

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

type family Any_ a a :: Bool Source

Equations

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

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

type family All a a :: Bool Source

Equations

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

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

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_1627595965 f q ls (Let_1627595951Scrutinee_1627594825Sym3 f q ls)) 

sScanl :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t) Source

type family Scanl1 a a :: [a] Source

Equations

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

sScanl1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t) Source

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

Equations

Scanr z q0 `[]` = Apply (Apply (:$) q0) `[]` 
Scanr f q0 ((:) x xs) = Case_1627595927 f q0 x xs (Let_1627595907Scrutinee_1627594827Sym4 f q0 x xs) 

sScanr :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t) Source

type family Scanr1 a a :: [a] Source

Equations

Scanr1 z `[]` = `[]` 
Scanr1 z `[x]` = Apply (Apply (:$) x) `[]` 
Scanr1 f ((:) x ((:) wild_1627594831 wild_1627594833)) = Case_1627595880 f x wild_1627594831 wild_1627594833 (Let_1627595860Scrutinee_1627594829Sym4 f x wild_1627594831 wild_1627594833) 

sScanr1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t) Source

Accumulating maps

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

Equations

MapAccumL z s `[]` = Apply (Apply Tuple2Sym0 s) `[]` 
MapAccumL f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let_1627595678S''Sym4 f s x xs)) (Apply (Apply (:$) (Let_1627595678YSym4 f s x xs)) (Let_1627595678YsSym4 f s x xs)) 

sMapAccumL :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t) Source

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

Equations

MapAccumR z s `[]` = Apply (Apply Tuple2Sym0 s) `[]` 
MapAccumR f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let_1627595511S''Sym4 f s x xs)) (Apply (Apply (:$) (Let_1627595511YSym4 f s x xs)) (Let_1627595511YsSym4 f s x xs)) 

sMapAccumR :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t) Source

Unfolding

type family Unfoldr a a :: [a] Source

Equations

Unfoldr f b = Case_1627595484 f b (Let_1627595475Scrutinee_1627594835Sym2 f b) 

sUnfoldr :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t) Source

Sublists

Extracting sublists

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

Equations

Inits xs = Apply (Apply (:$) `[]`) (Case_1627595458 xs (Let_1627595453Scrutinee_1627594837Sym1 xs)) 

sInits :: forall t. Sing t -> Sing (Apply InitsSym0 t) Source

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

Equations

Tails xs = Apply (Apply (:$) xs) (Case_1627595431 xs (Let_1627595426Scrutinee_1627594839Sym1 xs)) 

sTails :: forall t. Sing t -> Sing (Apply TailsSym0 t) Source

Predicates

type family IsPrefixOf a a :: Bool Source

Equations

IsPrefixOf `[]` `[]` = TrueSym0 
IsPrefixOf `[]` ((:) z z) = TrueSym0 
IsPrefixOf ((:) z z) `[]` = FalseSym0 
IsPrefixOf ((:) x xs) ((:) y ys) = Apply (Apply (:&&$) (Apply (Apply (:==$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) 

sIsPrefixOf :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t) Source

sIsSuffixOf :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t) Source

type family IsInfixOf a a :: Bool Source

Equations

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

sIsInfixOf :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t) Source

Searching lists

Searching by equality

type family Elem a a :: Bool Source

Equations

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

sElem :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t) Source

type family NotElem a a :: Bool Source

Equations

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

sNotElem :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t) Source

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 z) `[]` = `[]` 
Zip `[]` ((:) z z) = `[]` 

sZip :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t) Source

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 z) = `[]` 
Zip3 `[]` ((:) z z) `[]` = `[]` 
Zip3 `[]` ((:) z z) ((:) z z) = `[]` 
Zip3 ((:) z z) `[]` `[]` = `[]` 
Zip3 ((:) z z) `[]` ((:) z z) = `[]` 
Zip3 ((:) z z) ((:) z z) `[]` = `[]` 

sZip3 :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t) Source

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 `[]` `[]` = `[]` 
ZipWith z ((:) z z) `[]` = `[]` 
ZipWith z `[]` ((:) z z) = `[]` 

sZipWith :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t) Source

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 `[]` `[]` `[]` = `[]` 
ZipWith3 z `[]` `[]` ((:) z z) = `[]` 
ZipWith3 z `[]` ((:) z z) `[]` = `[]` 
ZipWith3 z `[]` ((:) z z) ((:) z z) = `[]` 
ZipWith3 z ((:) z z) `[]` `[]` = `[]` 
ZipWith3 z ((:) z z) `[]` ((:) z z) = `[]` 
ZipWith3 z ((:) z z) ((:) z z) `[]` = `[]` 

sZipWith3 :: forall t t t t. Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t) Source

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

Equations

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

sUnzip :: forall t. Sing t -> Sing (Apply UnzipSym0 t) Source

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

Equations

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

sUnzip3 :: forall t. Sing t -> Sing (Apply Unzip3Sym0 t) Source

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

Equations

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

sUnzip4 :: forall t. Sing t -> Sing (Apply Unzip4Sym0 t) Source

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

Equations

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

sUnzip5 :: forall t. Sing t -> Sing (Apply Unzip5Sym0 t) Source

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

Equations

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

sUnzip6 :: forall t. Sing t -> Sing (Apply Unzip6Sym0 t) Source

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

Equations

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

sUnzip7 :: forall t. Sing t -> Sing (Apply Unzip7Sym0 t) Source

Special lists

"Set" operations

type family Delete a a :: [a] Source

Equations

Delete a_1627595004 a_1627595006 = Apply (Apply (Apply DeleteBySym0 (:==$)) a_1627595004) a_1627595006 

sDelete :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t) Source

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

Equations

a_1627596406 :\\ a_1627596408 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 DeleteSym0)) a_1627596406) a_1627596408 

(%:\\) :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply (:\\$) t) t) Source

Ordered lists

Generalized functions

The "By" operations

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

Equations

DeleteBy z z `[]` = `[]` 
DeleteBy eq x ((:) y ys) = Case_1627595000 eq x y ys (Let_1627594980Scrutinee_1627594865Sym4 eq x y ys) 

sDeleteBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t) Source

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

Equations

DeleteFirstsBy eq a_1627596436 a_1627596438 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_1627596436) a_1627596438 

sDeleteFirstsBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t) Source

type family SortBy a a :: [a] Source

Equations

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

sSortBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t) Source

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

Equations

InsertBy z x `[]` = Apply (Apply (:$) x) `[]` 
InsertBy cmp x ((:) y ys') = Case_1627594942 cmp x y ys' (Let_1627594922Scrutinee_1627594867Sym4 cmp x y ys') 

sInsertBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t) Source

type family MaximumBy a a :: a Source

Equations

MaximumBy z `[]` = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" 
MaximumBy cmp ((:) wild_1627594871 wild_1627594873) = Apply (Apply Foldl1Sym0 (Let_1627596255MaxBySym3 cmp wild_1627594871 wild_1627594873)) (Let_1627596241XsSym3 cmp wild_1627594871 wild_1627594873) 

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

type family MinimumBy a a :: a Source

Equations

MinimumBy z `[]` = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" 
MinimumBy cmp ((:) wild_1627594877 wild_1627594879) = Apply (Apply Foldl1Sym0 (Let_1627596344MinBySym3 cmp wild_1627594877 wild_1627594879)) (Let_1627596330XsSym3 cmp wild_1627594877 wild_1627594879) 

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

Defunctionalization symbols

type NilSym0 = `[]` Source

data (:$) l Source

Instances

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

data l :$$ l Source

Instances

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

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

data l :++$$ l Source

Instances

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

data (:++$) l Source

Instances

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

data HeadSym0 l Source

Instances

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

type HeadSym1 t = Head t Source

data LastSym0 l Source

Instances

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

type LastSym1 t = Last t Source

data TailSym0 l Source

Instances

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

type TailSym1 t = Tail t Source

data InitSym0 l Source

Instances

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

type InitSym1 t = Init t Source

data NullSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] Bool -> *) (NullSym0 k) 
type Apply Bool [k] (NullSym0 k) l0 = NullSym1 k l0 

type NullSym1 t = Null t Source

data MapSym0 l Source

Instances

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

data MapSym1 l l Source

Instances

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

type MapSym2 t t = Map t t Source

data ReverseSym0 l Source

Instances

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

data IntersperseSym0 l Source

Instances

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

data IntersperseSym1 l l Source

Instances

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

data IntercalateSym0 l Source

Instances

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

data IntercalateSym1 l l Source

Instances

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

data SubsequencesSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] [[k]] -> *) (SubsequencesSym0 k) 
type Apply [[k]] [k] (SubsequencesSym0 k) l0 = SubsequencesSym1 k l0 

data PermutationsSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] [[k]] -> *) (PermutationsSym0 k) 
type Apply [[k]] [k] (PermutationsSym0 k) l0 = PermutationsSym1 k l0 

data FoldlSym0 l Source

Instances

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

data FoldlSym1 l l Source

Instances

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

data FoldlSym2 l l l Source

Instances

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

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) 
type Apply (TyFun k (TyFun [k1] k -> *) -> *) (TyFun k (TyFun k1 k -> *) -> *) (Foldl'Sym0 k k1) l0 = Foldl'Sym1 k k1 l0 

data Foldl'Sym1 l l Source

Instances

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

data Foldl'Sym2 l l l Source

Instances

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

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) 
type Apply (TyFun [k] k -> *) (TyFun k (TyFun k k -> *) -> *) (Foldl1Sym0 k) l0 = Foldl1Sym1 k l0 

data Foldl1Sym1 l l Source

Instances

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

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) 
type Apply (TyFun [k] k -> *) (TyFun k (TyFun k k -> *) -> *) (Foldl1'Sym0 k) l0 = Foldl1'Sym1 k l0 

data Foldl1'Sym1 l l Source

Instances

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

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) 
type Apply (TyFun k1 (TyFun [k] k1 -> *) -> *) (TyFun k (TyFun k1 k1 -> *) -> *) (FoldrSym0 k k1) l0 = FoldrSym1 k k1 l0 

data FoldrSym1 l l Source

Instances

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

data FoldrSym2 l l l Source

Instances

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

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) 
type Apply (TyFun [k] k -> *) (TyFun k (TyFun k k -> *) -> *) (Foldr1Sym0 k) l0 = Foldr1Sym1 k l0 

data Foldr1Sym1 l l Source

Instances

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

type Foldr1Sym2 t t = Foldr1 t t Source

data ConcatSym0 l Source

Instances

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

data ConcatMapSym0 l Source

Instances

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

data ConcatMapSym1 l l Source

Instances

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

type AndSym1 t = And t Source

data OrSym0 l Source

Instances

type OrSym1 t = Or t Source

data Any_Sym0 l Source

Instances

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

data Any_Sym1 l l Source

Instances

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

type Any_Sym2 t t = Any_ t t Source

data AllSym0 l Source

Instances

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

data AllSym1 l l Source

Instances

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

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) 
type Apply (TyFun k (TyFun [k1] [k] -> *) -> *) (TyFun k (TyFun k1 k -> *) -> *) (ScanlSym0 k k1) l0 = ScanlSym1 k k1 l0 

data ScanlSym1 l l Source

Instances

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

data ScanlSym2 l l l Source

Instances

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

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) 
type Apply (TyFun [k] [k] -> *) (TyFun k (TyFun k k -> *) -> *) (Scanl1Sym0 k) l0 = Scanl1Sym1 k l0 

data Scanl1Sym1 l l Source

Instances

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

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) 
type Apply (TyFun k1 (TyFun [k] [k1] -> *) -> *) (TyFun k (TyFun k1 k1 -> *) -> *) (ScanrSym0 k k1) l0 = ScanrSym1 k k1 l0 

data ScanrSym1 l l Source

Instances

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

data ScanrSym2 l l l Source

Instances

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

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) 
type Apply (TyFun [k] [k] -> *) (TyFun k (TyFun k k -> *) -> *) (Scanr1Sym0 k) l0 = Scanr1Sym1 k l0 

data Scanr1Sym1 l l Source

Instances

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

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) 
type Apply (TyFun k (TyFun [k1] ((,) k [k2]) -> *) -> *) (TyFun k (TyFun k1 ((,) k k2) -> *) -> *) (MapAccumLSym0 k k1 k2) l0 = MapAccumLSym1 k k1 k2 l0 

data MapAccumLSym1 l l Source

Instances

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

data MapAccumLSym2 l l l Source

Instances

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

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) 
type Apply (TyFun k (TyFun [k1] ((,) k [k2]) -> *) -> *) (TyFun k (TyFun k1 ((,) k k2) -> *) -> *) (MapAccumRSym0 k k1 k2) l0 = MapAccumRSym1 k k1 k2 l0 

data MapAccumRSym1 l l Source

Instances

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

data MapAccumRSym2 l l l Source

Instances

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

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) 
type Apply (TyFun k [k1] -> *) (TyFun k (Maybe ((,) k1 k)) -> *) (UnfoldrSym0 k k1) l0 = UnfoldrSym1 k k1 l0 

data UnfoldrSym1 l l Source

Instances

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

type UnfoldrSym2 t t = Unfoldr t t Source

data InitsSym0 l Source

Instances

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

data TailsSym0 l Source

Instances

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

data IsPrefixOfSym0 l Source

Instances

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

data IsPrefixOfSym1 l l Source

Instances

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

data IsSuffixOfSym0 l Source

Instances

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

data IsSuffixOfSym1 l l Source

Instances

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

data IsInfixOfSym0 l Source

Instances

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

data IsInfixOfSym1 l l Source

Instances

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

data ElemSym0 l Source

Instances

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

data ElemSym1 l l Source

Instances

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

type ElemSym2 t t = Elem t t Source

data NotElemSym0 l Source

Instances

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

data NotElemSym1 l l Source

Instances

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

type NotElemSym2 t t = NotElem t t Source

data ZipSym0 l Source

Instances

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

data ZipSym1 l l Source

Instances

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

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) 
type Apply (TyFun [k1] (TyFun [k2] [(,,) k k1 k2] -> *) -> *) [k] (Zip3Sym0 k k1 k2) l0 = Zip3Sym1 k k1 k2 l0 

data Zip3Sym1 l l Source

Instances

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

data Zip3Sym2 l l l Source

Instances

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

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) 
type Apply (TyFun [k] (TyFun [k1] [k2] -> *) -> *) (TyFun k (TyFun k1 k2 -> *) -> *) (ZipWithSym0 k k1 k2) l0 = ZipWithSym1 k k1 k2 l0 

data ZipWithSym1 l l Source

Instances

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

data ZipWithSym2 l l l Source

Instances

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

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

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) 
type Apply (TyFun [k1] (TyFun [k2] [k3] -> *) -> *) [k] (ZipWith3Sym1 k k1 k2 k3 l1) l0 = ZipWith3Sym2 k k1 k2 k3 l1 l0 

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) 
type Apply (TyFun [k2] [k3] -> *) [k1] (ZipWith3Sym2 k k1 k2 k3 l1 l2) l0 = ZipWith3Sym3 k k1 k2 k3 l1 l2 l0 

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) 
type Apply [k3] [k2] (ZipWith3Sym3 k k1 k2 k3 l1 l2 l3) l0 

data UnzipSym0 l Source

Instances

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

data Unzip3Sym0 l Source

Instances

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

data Unzip4Sym0 l Source

Instances

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

data Unzip5Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun [(,,,,) k k k k k] ((,,,,) [k] [k] [k] [k] [k]) -> *) (Unzip5Sym0 k k k k k) 
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 

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

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

data DeleteSym0 l Source

Instances

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

data DeleteSym1 l l Source

Instances

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

type DeleteSym2 t t = Delete t t Source

data (:\\$) l Source

Instances

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

data l :\\$$ l Source

Instances

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

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

data DeleteBySym0 l Source

Instances

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

data DeleteBySym1 l l Source

Instances

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

data DeleteBySym2 l l l Source

Instances

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

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) 
type Apply (TyFun [k] (TyFun [k] [k] -> *) -> *) (TyFun k (TyFun k Bool -> *) -> *) (DeleteFirstsBySym0 k) l0 = DeleteFirstsBySym1 k l0 

data DeleteFirstsBySym1 l l Source

Instances

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

data DeleteFirstsBySym2 l l l Source

Instances

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

data SortBySym0 l Source

Instances

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

data SortBySym1 l l Source

Instances

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

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) 
type Apply (TyFun k (TyFun [k] [k] -> *) -> *) (TyFun k (TyFun k Ordering -> *) -> *) (InsertBySym0 k) l0 = InsertBySym1 k l0 

data InsertBySym1 l l Source

Instances

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

data InsertBySym2 l l l Source

Instances

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

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) 
type Apply (TyFun [k] k -> *) (TyFun k (TyFun k Ordering -> *) -> *) (MaximumBySym0 k) l0 = MaximumBySym1 k l0 

data MaximumBySym1 l l Source

Instances

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

data MinimumBySym0 l Source

Instances

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

data MinimumBySym1 l l Source

Instances

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