singletons-2.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

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

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

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

type SList = (Sing :: [a] -> *) Source

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

Basic functions

type family a :++ a :: [a] infixr 5 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 :: [a]) infixr 5 Source

type family Head a :: a Source

Equations

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

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

type family Last a :: a Source

Equations

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

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

type family Tail a :: [a] Source

Equations

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

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

type family Init a :: [a] Source

Equations

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

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

type family Null a :: Bool Source

Equations

Null `[]` = TrueSym0 
Null ((:) _z_1627909034 _z_1627909037) = FalseSym0 

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

type family Length a :: Nat Source

Equations

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

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

List transformations

type family Map a a :: [b] Source

Equations

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

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

type family Reverse a :: [a] Source

Equations

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

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

type family Intersperse a a :: [a] Source

Equations

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

sIntersperse :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a]) 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 :: [a]) Source

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

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

type family Subsequences a :: [[a]] Source

Equations

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

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

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

Equations

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

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

Reducing lists (folds)

type family Foldl a a a :: b Source

Equations

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

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

type family Foldl' a a a :: b Source

Equations

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

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

type family Foldl1 a a :: a Source

Equations

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

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

type family Foldl1' a a :: a Source

Equations

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

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

type family Foldr a a a :: b Source

Equations

Foldr k z a_1627752769 = Apply (Let1627752774GoSym3 k z a_1627752769) a_1627752769 

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

type family Foldr1 a a :: a Source

Equations

Foldr1 _z_1627908202 `[x]` = x 
Foldr1 f ((:) x ((:) wild_1627905686 wild_1627905688)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let1627908210XsSym4 f x wild_1627905686 wild_1627905688)) 
Foldr1 _z_1627908229 `[]` = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" 

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

Special folds

type family Concat a :: [a] Source

Equations

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

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

type family ConcatMap a a :: [b] Source

Equations

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

sConcatMap :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) 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 :: Bool) 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 :: Bool) Source

type family Any_ a a :: Bool Source

Equations

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

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

type family All a a :: Bool Source

Equations

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

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

type family Sum a :: a Source

Equations

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

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

type family Product a :: a Source

Equations

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

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

type family Maximum a :: a Source

Equations

Maximum `[]` = Apply ErrorSym0 "Data.Singletons.List.maximum: empty list" 
Maximum ((:) wild_1627905766 wild_1627905768) = Apply (Apply Foldl1Sym0 MaxSym0) (Let1627908427XsSym2 wild_1627905766 wild_1627905768) 

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

type family Minimum a :: a Source

Equations

Minimum `[]` = Apply ErrorSym0 "Data.Singletons.List.minimum: empty list" 
Minimum ((:) wild_1627905770 wild_1627905772) = Apply (Apply Foldl1Sym0 MinSym0) (Let1627908441XsSym2 wild_1627905770 wild_1627905772) 

sMinimum :: forall t. SOrd (KProxy :: KProxy a) => Sing t -> Sing (Apply MinimumSym0 t :: a) 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_1627908126 f q ls ls) 

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

type family Scanl1 a a :: [a] Source

Equations

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

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

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

Equations

Scanr _z_1627908076 q0 `[]` = Apply (Apply (:$) q0) `[]` 
Scanr f q0 ((:) x xs) = Case_1627908103 f q0 x xs (Let1627908084Scrutinee_1627905690Sym4 f q0 x xs) 

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

type family Scanr1 a a :: [a] Source

Equations

Scanr1 _z_1627908007 `[]` = `[]` 
Scanr1 _z_1627908010 `[x]` = Apply (Apply (:$) x) `[]` 
Scanr1 f ((:) x ((:) wild_1627905694 wild_1627905696)) = Case_1627908056 f x wild_1627905694 wild_1627905696 (Let1627908037Scrutinee_1627905692Sym4 f x wild_1627905694 wild_1627905696) 

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

Accumulating maps

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

Equations

MapAccumL _z_1627907841 s `[]` = Apply (Apply Tuple2Sym0 s) `[]` 
MapAccumL f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let1627907849S''Sym4 f s x xs)) (Apply (Apply (:$) (Let1627907849YSym4 f s x xs)) (Let1627907849YsSym4 f s x xs)) 

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

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

Equations

MapAccumR _z_1627907669 s `[]` = Apply (Apply Tuple2Sym0 s) `[]` 
MapAccumR f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let1627907677S''Sym4 f s x xs)) (Apply (Apply (:$) (Let1627907677YSym4 f s x xs)) (Let1627907677YsSym4 f s x xs)) 

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

Cyclical lists

type family Replicate a a :: [a] Source

Equations

Replicate n x = Case_1627905942 n x (Let1627905934Scrutinee_1627905778Sym2 n x) 

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

Unfolding

type family Unfoldr a a :: [a] Source

Equations

Unfoldr f b = Case_1627907649 f b (Let1627907641Scrutinee_1627905698Sym2 f b) 

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

Sublists

Extracting sublists

type family Take a a :: [a] Source

Equations

Take _z_1627906129 `[]` = `[]` 
Take n ((:) x xs) = Case_1627906148 n x xs (Let1627906135Scrutinee_1627905762Sym3 n x xs) 

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

type family Drop a a :: [a] Source

Equations

Drop _z_1627906098 `[]` = `[]` 
Drop n ((:) x xs) = Case_1627906117 n x xs (Let1627906104Scrutinee_1627905764Sym3 n x xs) 

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

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) 

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

type family TakeWhile a a :: [a] Source

Equations

TakeWhile _z_1627906502 `[]` = `[]` 
TakeWhile p ((:) x xs) = Case_1627906521 p x xs (Let1627906508Scrutinee_1627905752Sym3 p x xs) 

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

type family DropWhile a a :: [a] Source

Equations

DropWhile _z_1627906458 `[]` = `[]` 
DropWhile p ((:) x xs') = Case_1627906490 p x xs' (Let1627906477Scrutinee_1627905754Sym3 p x xs') 

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

type family DropWhileEnd a a :: [a] Source

Equations

DropWhileEnd p a_1627909049 = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_1627909053Sym0 p) a_1627909049)) `[]`) a_1627909049 

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

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

Equations

Span _z_1627906276 `[]` = Apply (Apply Tuple2Sym0 (Let1627906279XsSym1 _z_1627906276)) (Let1627906279XsSym1 _z_1627906276) 
Span p ((:) x xs') = Case_1627906312 p x xs' (Let1627906299Scrutinee_1627905758Sym3 p x xs') 

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

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

Equations

Break _z_1627906171 `[]` = Apply (Apply Tuple2Sym0 (Let1627906174XsSym1 _z_1627906171)) (Let1627906174XsSym1 _z_1627906171) 
Break p ((:) x xs') = Case_1627906207 p x xs' (Let1627906194Scrutinee_1627905760Sym3 p x xs') 

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

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

Equations

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

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

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

Equations

Inits xs = Apply (Apply (:$) `[]`) (Case_1627907625 xs xs) 

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

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

Equations

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

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

Predicates

type family IsPrefixOf a a :: Bool Source

Equations

IsPrefixOf `[]` `[]` = TrueSym0 
IsPrefixOf `[]` ((:) _z_1627907581 _z_1627907584) = TrueSym0 
IsPrefixOf ((:) _z_1627907587 _z_1627907590) `[]` = 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 :: Bool) Source

sIsSuffixOf :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) 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 :: Bool) Source

Searching lists

Searching by equality

type family Elem a a :: Bool Source

Equations

Elem _z_1627907518 `[]` = 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 :: Bool) Source

type family NotElem a a :: Bool Source

Equations

NotElem _z_1627907503 `[]` = 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 :: Bool) Source

type family Lookup a a :: Maybe b Source

Equations

Lookup _key `[]` = NothingSym0 
Lookup key ((:) `(x, y)` xys) = Case_1627906086 key x y xys (Let1627906067Scrutinee_1627905774Sym4 key x y xys) 

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

Searching with a predicate

type family Find a a :: Maybe a Source

Equations

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

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

type family Filter a a :: [a] Source

Equations

Filter _p `[]` = `[]` 
Filter p ((:) x xs) = Case_1627906550 p x xs (Let1627906537Scrutinee_1627905740Sym3 p x xs) 

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

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

Equations

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

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

Indexing lists

type family a :!! a :: a Source

Equations

`[]` :!! _z_1627905901 = Apply ErrorSym0 "Data.Singletons.List.!!: index too large" 
((:) x xs) :!! n = Case_1627905920 x xs n (Let1627905907Scrutinee_1627905780Sym3 x xs n) 

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

type family ElemIndex a a :: Maybe Nat Source

Equations

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

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

type family ElemIndices a a :: [Nat] Source

Equations

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

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

type family FindIndex a a :: Maybe Nat Source

Equations

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

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

type family FindIndices a a :: [Nat] Source

Equations

FindIndices p xs = Apply (Apply MapSym0 SndSym0) (Apply (Apply FilterSym0 (Apply (Apply Lambda_1627907432Sym0 p) xs)) (Apply (Apply ZipSym0 xs) (Apply (Apply (Let1627907403BuildListSym2 p xs) (FromInteger 0)) xs))) 

sFindIndices :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat]) 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_1627907380 _z_1627907383) `[]` = `[]` 
Zip `[]` ((:) _z_1627907386 _z_1627907389) = `[]` 

sZip :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)]) 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_1627907313 _z_1627907316) = `[]` 
Zip3 `[]` ((:) _z_1627907319 _z_1627907322) `[]` = `[]` 
Zip3 `[]` ((:) _z_1627907325 _z_1627907328) ((:) _z_1627907331 _z_1627907334) = `[]` 
Zip3 ((:) _z_1627907337 _z_1627907340) `[]` `[]` = `[]` 
Zip3 ((:) _z_1627907343 _z_1627907346) `[]` ((:) _z_1627907349 _z_1627907352) = `[]` 
Zip3 ((:) _z_1627907355 _z_1627907358) ((:) _z_1627907361 _z_1627907364) `[]` = `[]` 

sZip3 :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)]) 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_1627907271 `[]` `[]` = `[]` 
ZipWith _z_1627907274 ((:) _z_1627907277 _z_1627907280) `[]` = `[]` 
ZipWith _z_1627907283 `[]` ((:) _z_1627907286 _z_1627907289) = `[]` 

sZipWith :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c]) 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_1627907176 `[]` `[]` `[]` = `[]` 
ZipWith3 _z_1627907179 `[]` `[]` ((:) _z_1627907182 _z_1627907185) = `[]` 
ZipWith3 _z_1627907188 `[]` ((:) _z_1627907191 _z_1627907194) `[]` = `[]` 
ZipWith3 _z_1627907197 `[]` ((:) _z_1627907200 _z_1627907203) ((:) _z_1627907206 _z_1627907209) = `[]` 
ZipWith3 _z_1627907212 ((:) _z_1627907215 _z_1627907218) `[]` `[]` = `[]` 
ZipWith3 _z_1627907221 ((:) _z_1627907224 _z_1627907227) `[]` ((:) _z_1627907230 _z_1627907233) = `[]` 
ZipWith3 _z_1627907236 ((:) _z_1627907239 _z_1627907242) ((:) _z_1627907245 _z_1627907248) `[]` = `[]` 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

Special lists

"Set" operations

type family Nub a :: [a] Source

Equations

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

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

type family Delete a a :: [a] Source

Equations

Delete a_1627906907 a_1627906909 = Apply (Apply (Apply DeleteBySym0 (:==$)) a_1627906907) a_1627906909 

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

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

Equations

a_1627906922 :\\ a_1627906924 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 DeleteSym0)) a_1627906922) a_1627906924 

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

type family Union a a :: [a] Source

Equations

Union a_1627906892 a_1627906894 = Apply (Apply (Apply UnionBySym0 (:==$)) a_1627906892) a_1627906894 

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

type family Intersect a a :: [a] Source

Equations

Intersect a_1627906695 a_1627906697 = Apply (Apply (Apply IntersectBySym0 (:==$)) a_1627906695) a_1627906697 

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

Ordered lists

type family Insert a a :: [a] Source

Equations

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

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

type family Sort a :: [a] Source

Equations

Sort a_1627906798 = Apply (Apply SortBySym0 CompareSym0) a_1627906798 

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

Generalized functions

The "By" operations

User-supplied equality (replacing an Eq context)

The predicate is assumed to define an equivalence.

type family NubBy a a :: [a] Source

Equations

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

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

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

Equations

DeleteBy _z_1627906820 _z_1627906823 `[]` = `[]` 
DeleteBy eq x ((:) y ys) = Case_1627906849 eq x y ys (Let1627906830Scrutinee_1627905724Sym4 eq x y ys) 

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

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

Equations

DeleteFirstsBy eq a_1627906867 a_1627906869 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_1627906867) a_1627906869 

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

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) 

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

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

Equations

IntersectBy _z_1627906581 `[]` `[]` = `[]` 
IntersectBy _z_1627906584 `[]` ((:) _z_1627906587 _z_1627906590) = `[]` 
IntersectBy _z_1627906593 ((:) _z_1627906596 _z_1627906599) `[]` = `[]` 
IntersectBy eq ((:) wild_1627905744 wild_1627905746) ((:) wild_1627905748 wild_1627905750) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_1627906658Sym0 eq) wild_1627905744) wild_1627905746) wild_1627905748) wild_1627905750)) (Let1627906607XsSym5 eq wild_1627905744 wild_1627905746 wild_1627905748 wild_1627905750) 

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

type family GroupBy a a :: [[a]] Source

Equations

GroupBy _z_1627906381 `[]` = `[]` 
GroupBy eq ((:) x xs) = Apply (Apply (:$) (Apply (Apply (:$) x) (Let1627906387YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let1627906387ZsSym3 eq x xs)) 

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

User-supplied comparison (replacing an Ord context)

The function is assumed to define a total ordering.

type family SortBy a a :: [a] Source

Equations

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

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

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

Equations

InsertBy _z_1627906725 x `[]` = Apply (Apply (:$) x) `[]` 
InsertBy cmp x ((:) y ys') = Case_1627906771 cmp x y ys' (Let1627906752Scrutinee_1627905726Sym4 cmp x y ys') 

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

type family MaximumBy a a :: a Source

Equations

MaximumBy _z_1627908256 `[]` = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" 
MaximumBy cmp ((:) wild_1627905730 wild_1627905732) = Apply (Apply Foldl1Sym0 (Let1627908275MaxBySym3 cmp wild_1627905730 wild_1627905732)) (Let1627908262XsSym3 cmp wild_1627905730 wild_1627905732) 

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

type family MinimumBy a a :: a Source

Equations

MinimumBy _z_1627908343 `[]` = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" 
MinimumBy cmp ((:) wild_1627905736 wild_1627905738) = Apply (Apply Foldl1Sym0 (Let1627908362MinBySym3 cmp wild_1627905736 wild_1627905738)) (Let1627908349XsSym3 cmp wild_1627905736 wild_1627905738) 

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

The "generic" operations

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

type family GenericLength a :: i Source

Equations

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

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

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 LengthSym0 l Source

Instances

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 TransposeSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [[k]] [[k]] -> *) (TransposeSym0 k) Source 
type Apply [[k]] [[k]] (TransposeSym0 k) l0 = TransposeSym1 k 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 k (TyFun [k1] k -> *) -> *) (TyFun k (TyFun k1 k -> *) -> *) (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 k k1 l1) l0 = FoldlSym2 k k1 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 k [k1] (FoldlSym2 k k1 l1 l2) l0 = FoldlSym3 k k1 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 k (TyFun [k1] k -> *) -> *) (TyFun k (TyFun k1 k -> *) -> *) (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 k k1 l1) l0 = Foldl'Sym2 k k1 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 k [k1] (Foldl'Sym2 k k1 l1 l2) l0 = Foldl'Sym3 k k1 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 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 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 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 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 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 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 GroupSym0 l Source

Instances

SuppressUnusedWarnings (TyFun [k] [[k]] -> *) (GroupSym0 k) Source 
type Apply [[k]] [k] (GroupSym0 k) l0 = GroupSym1 k l0 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 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 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 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 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 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 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 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 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 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 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 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 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