Copyright | (C) 2013-2014 Richard Eisenberg, Jan Stolarek |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Richard Eisenberg (eir@cis.upenn.edu) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
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.
- data family Sing a
- type SList = (Sing :: [a] -> *)
- type family a :++ a :: [a]
- (%:++) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:++$) t) t :: [a])
- type family Head a :: a
- sHead :: forall t. Sing t -> Sing (Apply HeadSym0 t :: a)
- type family Last a :: a
- sLast :: forall t. Sing t -> Sing (Apply LastSym0 t :: a)
- type family Tail a :: [a]
- sTail :: forall t. Sing t -> Sing (Apply TailSym0 t :: [a])
- type family Init a :: [a]
- sInit :: forall t. Sing t -> Sing (Apply InitSym0 t :: [a])
- type family Null a :: Bool
- sNull :: forall t. Sing t -> Sing (Apply NullSym0 t :: Bool)
- type family Length a :: Nat
- sLength :: forall t. Sing t -> Sing (Apply LengthSym0 t :: Nat)
- type family Map a a :: [b]
- sMap :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b])
- type family Reverse a :: [a]
- sReverse :: forall t. Sing t -> Sing (Apply ReverseSym0 t :: [a])
- type family Intersperse a a :: [a]
- sIntersperse :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a])
- type family Intercalate a a :: [a]
- sIntercalate :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a])
- type family Transpose a :: [[a]]
- sTranspose :: forall t. Sing t -> Sing (Apply TransposeSym0 t :: [[a]])
- type family Subsequences a :: [[a]]
- sSubsequences :: forall t. Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]])
- type family Permutations a :: [[a]]
- sPermutations :: forall t. Sing t -> Sing (Apply PermutationsSym0 t :: [[a]])
- type family Foldl a a a :: b
- sFoldl :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b)
- type family Foldl' a a a :: b
- sFoldl' :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b)
- type family Foldl1 a a :: a
- sFoldl1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a)
- type family Foldl1' a a :: a
- sFoldl1' :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a)
- type family Foldr a a a :: b
- sFoldr :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b)
- type family Foldr1 a a :: a
- sFoldr1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a)
- type family Concat a :: [a]
- sConcat :: forall t. Sing t -> Sing (Apply ConcatSym0 t :: [a])
- type family ConcatMap a a :: [b]
- sConcatMap :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b])
- type family And a :: Bool
- sAnd :: forall t. Sing t -> Sing (Apply AndSym0 t :: Bool)
- type family Or a :: Bool
- sOr :: forall t. Sing t -> Sing (Apply OrSym0 t :: Bool)
- type family Any_ a a :: Bool
- sAny_ :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Any_Sym0 t) t :: Bool)
- type family All a a :: Bool
- sAll :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool)
- type family Sum a :: a
- sSum :: forall t. SNum (KProxy :: KProxy a) => Sing t -> Sing (Apply SumSym0 t :: a)
- type family Product a :: a
- sProduct :: forall t. SNum (KProxy :: KProxy a) => Sing t -> Sing (Apply ProductSym0 t :: a)
- type family Maximum a :: a
- sMaximum :: forall t. SOrd (KProxy :: KProxy a) => Sing t -> Sing (Apply MaximumSym0 t :: a)
- type family Minimum a :: a
- sMinimum :: forall t. SOrd (KProxy :: KProxy a) => Sing t -> Sing (Apply MinimumSym0 t :: a)
- any_ :: forall a. (a -> Bool) -> [a] -> Bool
- type family Scanl a a a :: [b]
- sScanl :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b])
- type family Scanl1 a a :: [a]
- sScanl1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a])
- type family Scanr a a a :: [b]
- sScanr :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b])
- type family Scanr1 a a :: [a]
- sScanr1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a])
- type family MapAccumL a a a :: (acc, [y])
- sMapAccumL :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (acc, [y]))
- type family MapAccumR a a a :: (acc, [y])
- sMapAccumR :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (acc, [y]))
- type family Replicate a a :: [a]
- sReplicate :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a])
- type family Unfoldr a a :: [a]
- sUnfoldr :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a])
- type family Take a a :: [a]
- sTake :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a])
- type family Drop a a :: [a]
- sDrop :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a])
- type family SplitAt a a :: ([a], [a])
- sSplitAt :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a]))
- type family TakeWhile a a :: [a]
- sTakeWhile :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a])
- type family DropWhile a a :: [a]
- sDropWhile :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a])
- type family DropWhileEnd a a :: [a]
- sDropWhileEnd :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a])
- type family Span a a :: ([a], [a])
- sSpan :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a]))
- type family Break a a :: ([a], [a])
- sBreak :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a]))
- type family Group a :: [[a]]
- sGroup :: forall t. SEq (KProxy :: KProxy a) => Sing t -> Sing (Apply GroupSym0 t :: [[a]])
- type family Inits a :: [[a]]
- sInits :: forall t. Sing t -> Sing (Apply InitsSym0 t :: [[a]])
- type family Tails a :: [[a]]
- sTails :: forall t. Sing t -> Sing (Apply TailsSym0 t :: [[a]])
- type family IsPrefixOf a a :: Bool
- sIsPrefixOf :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool)
- type family IsSuffixOf a a :: Bool
- sIsSuffixOf :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool)
- type family IsInfixOf a a :: Bool
- sIsInfixOf :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool)
- type family Elem a a :: Bool
- sElem :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool)
- type family NotElem a a :: Bool
- sNotElem :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool)
- type family Lookup a a :: Maybe b
- sLookup :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b)
- type family Find a a :: Maybe a
- sFind :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a)
- type family Filter a a :: [a]
- sFilter :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
- type family Partition a a :: ([a], [a])
- sPartition :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
- type family a :!! a :: a
- (%:!!) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:!!$) t) t :: a)
- type family ElemIndex a a :: Maybe Nat
- sElemIndex :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat)
- type family ElemIndices a a :: [Nat]
- sElemIndices :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat])
- type family FindIndex a a :: Maybe Nat
- sFindIndex :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat)
- type family FindIndices a a :: [Nat]
- sFindIndices :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat])
- type family Zip a a :: [(a, b)]
- sZip :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)])
- type family Zip3 a a a :: [(a, b, c)]
- sZip3 :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)])
- type family ZipWith a a a :: [c]
- sZipWith :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c])
- type family ZipWith3 a a a a :: [d]
- 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])
- type family Unzip a :: ([a], [b])
- sUnzip :: forall t. Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b]))
- type family Unzip3 a :: ([a], [b], [c])
- sUnzip3 :: forall t. Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c]))
- type family Unzip4 a :: ([a], [b], [c], [d])
- sUnzip4 :: forall t. Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d]))
- type family Unzip5 a :: ([a], [b], [c], [d], [e])
- sUnzip5 :: forall t. Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e]))
- type family Unzip6 a :: ([a], [b], [c], [d], [e], [f])
- sUnzip6 :: forall t. Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f]))
- type family Unzip7 a :: ([a], [b], [c], [d], [e], [f], [g])
- sUnzip7 :: forall t. Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g]))
- type family Nub a :: [a]
- sNub :: forall t. SEq (KProxy :: KProxy a) => Sing t -> Sing (Apply NubSym0 t :: [a])
- type family Delete a a :: [a]
- sDelete :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a])
- type family a :\\ a :: [a]
- (%:\\) :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply (:\\$) t) t :: [a])
- type family Union a a :: [a]
- sUnion :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a])
- type family Intersect a a :: [a]
- sIntersect :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a])
- type family Insert a a :: [a]
- sInsert :: forall t t. SOrd (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a])
- type family Sort a :: [a]
- sSort :: forall t. SOrd (KProxy :: KProxy a) => Sing t -> Sing (Apply SortSym0 t :: [a])
- type family NubBy a a :: [a]
- sNubBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a])
- type family DeleteBy a a a :: [a]
- sDeleteBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a])
- type family DeleteFirstsBy a a a :: [a]
- sDeleteFirstsBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a])
- type family UnionBy a a a :: [a]
- sUnionBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a])
- type family IntersectBy a a a :: [a]
- sIntersectBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a])
- type family GroupBy a a :: [[a]]
- sGroupBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]])
- type family SortBy a a :: [a]
- sSortBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a])
- type family InsertBy a a a :: [a]
- sInsertBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a])
- type family MaximumBy a a :: a
- sMaximumBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a)
- type family MinimumBy a a :: a
- sMinimumBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a)
- type family GenericLength a :: i
- sGenericLength :: forall t. SNum (KProxy :: KProxy i) => Sing t -> Sing (Apply GenericLengthSym0 t :: i)
- type NilSym0 = `[]`
- data (:$) l
- data l :$$ l
- type (:$$$) t t = (:) t t
- type (:++$$$) t t = (:++) t t
- data l :++$$ l
- data (:++$) l
- data HeadSym0 l
- type HeadSym1 t = Head t
- data LastSym0 l
- type LastSym1 t = Last t
- data TailSym0 l
- type TailSym1 t = Tail t
- data InitSym0 l
- type InitSym1 t = Init t
- data NullSym0 l
- type NullSym1 t = Null t
- data LengthSym0 l
- type LengthSym1 t = Length t
- data MapSym0 l
- data MapSym1 l l
- type MapSym2 t t = Map t t
- data ReverseSym0 l
- type ReverseSym1 t = Reverse t
- data IntersperseSym0 l
- data IntersperseSym1 l l
- type IntersperseSym2 t t = Intersperse t t
- data IntercalateSym0 l
- data IntercalateSym1 l l
- type IntercalateSym2 t t = Intercalate t t
- data TransposeSym0 l
- type TransposeSym1 t = Transpose t
- data SubsequencesSym0 l
- type SubsequencesSym1 t = Subsequences t
- data PermutationsSym0 l
- type PermutationsSym1 t = Permutations t
- data FoldlSym0 l
- data FoldlSym1 l l
- data FoldlSym2 l l l
- type FoldlSym3 t t t = Foldl t t t
- data Foldl'Sym0 l
- data Foldl'Sym1 l l
- data Foldl'Sym2 l l l
- type Foldl'Sym3 t t t = Foldl' t t t
- data Foldl1Sym0 l
- data Foldl1Sym1 l l
- type Foldl1Sym2 t t = Foldl1 t t
- data Foldl1'Sym0 l
- data Foldl1'Sym1 l l
- type Foldl1'Sym2 t t = Foldl1' t t
- data FoldrSym0 l
- data FoldrSym1 l l
- data FoldrSym2 l l l
- type FoldrSym3 t t t = Foldr t t t
- data Foldr1Sym0 l
- data Foldr1Sym1 l l
- type Foldr1Sym2 t t = Foldr1 t t
- data ConcatSym0 l
- type ConcatSym1 t = Concat t
- data ConcatMapSym0 l
- data ConcatMapSym1 l l
- type ConcatMapSym2 t t = ConcatMap t t
- data AndSym0 l
- type AndSym1 t = And t
- data OrSym0 l
- type OrSym1 t = Or t
- data Any_Sym0 l
- data Any_Sym1 l l
- type Any_Sym2 t t = Any_ t t
- data AllSym0 l
- data AllSym1 l l
- type AllSym2 t t = All t t
- data SumSym0 l
- type SumSym1 t = Sum t
- data ProductSym0 l
- type ProductSym1 t = Product t
- data MaximumSym0 l
- type MaximumSym1 t = Maximum t
- data MinimumSym0 l
- type MinimumSym1 t = Minimum t
- data ScanlSym0 l
- data ScanlSym1 l l
- data ScanlSym2 l l l
- type ScanlSym3 t t t = Scanl t t t
- data Scanl1Sym0 l
- data Scanl1Sym1 l l
- type Scanl1Sym2 t t = Scanl1 t t
- data ScanrSym0 l
- data ScanrSym1 l l
- data ScanrSym2 l l l
- type ScanrSym3 t t t = Scanr t t t
- data Scanr1Sym0 l
- data Scanr1Sym1 l l
- type Scanr1Sym2 t t = Scanr1 t t
- data MapAccumLSym0 l
- data MapAccumLSym1 l l
- data MapAccumLSym2 l l l
- type MapAccumLSym3 t t t = MapAccumL t t t
- data MapAccumRSym0 l
- data MapAccumRSym1 l l
- data MapAccumRSym2 l l l
- type MapAccumRSym3 t t t = MapAccumR t t t
- data ReplicateSym0 l
- data ReplicateSym1 l l
- type ReplicateSym2 t t = Replicate t t
- data UnfoldrSym0 l
- data UnfoldrSym1 l l
- type UnfoldrSym2 t t = Unfoldr t t
- data TakeSym0 l
- data TakeSym1 l l
- type TakeSym2 t t = Take t t
- data DropSym0 l
- data DropSym1 l l
- type DropSym2 t t = Drop t t
- data SplitAtSym0 l
- data SplitAtSym1 l l
- type SplitAtSym2 t t = SplitAt t t
- data TakeWhileSym0 l
- data TakeWhileSym1 l l
- type TakeWhileSym2 t t = TakeWhile t t
- data DropWhileSym0 l
- data DropWhileSym1 l l
- type DropWhileSym2 t t = DropWhile t t
- data DropWhileEndSym0 l
- data DropWhileEndSym1 l l
- type DropWhileEndSym2 t t = DropWhileEnd t t
- data SpanSym0 l
- data SpanSym1 l l
- type SpanSym2 t t = Span t t
- data BreakSym0 l
- data BreakSym1 l l
- type BreakSym2 t t = Break t t
- data GroupSym0 l
- type GroupSym1 t = Group t
- data InitsSym0 l
- type InitsSym1 t = Inits t
- data TailsSym0 l
- type TailsSym1 t = Tails t
- data IsPrefixOfSym0 l
- data IsPrefixOfSym1 l l
- type IsPrefixOfSym2 t t = IsPrefixOf t t
- data IsSuffixOfSym0 l
- data IsSuffixOfSym1 l l
- type IsSuffixOfSym2 t t = IsSuffixOf t t
- data IsInfixOfSym0 l
- data IsInfixOfSym1 l l
- type IsInfixOfSym2 t t = IsInfixOf t t
- data ElemSym0 l
- data ElemSym1 l l
- type ElemSym2 t t = Elem t t
- data NotElemSym0 l
- data NotElemSym1 l l
- type NotElemSym2 t t = NotElem t t
- data LookupSym0 l
- data LookupSym1 l l
- type LookupSym2 t t = Lookup t t
- data FindSym0 l
- data FindSym1 l l
- type FindSym2 t t = Find t t
- data FilterSym0 l
- data FilterSym1 l l
- type FilterSym2 t t = Filter t t
- data PartitionSym0 l
- data PartitionSym1 l l
- type PartitionSym2 t t = Partition t t
- data (:!!$) l
- data l :!!$$ l
- type (:!!$$$) t t = (:!!) t t
- data ElemIndexSym0 l
- data ElemIndexSym1 l l
- type ElemIndexSym2 t t = ElemIndex t t
- data ElemIndicesSym0 l
- data ElemIndicesSym1 l l
- type ElemIndicesSym2 t t = ElemIndices t t
- data FindIndexSym0 l
- data FindIndexSym1 l l
- type FindIndexSym2 t t = FindIndex t t
- data FindIndicesSym0 l
- data FindIndicesSym1 l l
- type FindIndicesSym2 t t = FindIndices t t
- data ZipSym0 l
- data ZipSym1 l l
- type ZipSym2 t t = Zip t t
- data Zip3Sym0 l
- data Zip3Sym1 l l
- data Zip3Sym2 l l l
- type Zip3Sym3 t t t = Zip3 t t t
- data ZipWithSym0 l
- data ZipWithSym1 l l
- data ZipWithSym2 l l l
- type ZipWithSym3 t t t = ZipWith t t t
- data ZipWith3Sym0 l
- data ZipWith3Sym1 l l
- data ZipWith3Sym2 l l l
- data ZipWith3Sym3 l l l l
- type ZipWith3Sym4 t t t t = ZipWith3 t t t t
- data UnzipSym0 l
- type UnzipSym1 t = Unzip t
- data Unzip3Sym0 l
- type Unzip3Sym1 t = Unzip3 t
- data Unzip4Sym0 l
- type Unzip4Sym1 t = Unzip4 t
- data Unzip5Sym0 l
- type Unzip5Sym1 t = Unzip5 t
- data Unzip6Sym0 l
- type Unzip6Sym1 t = Unzip6 t
- data Unzip7Sym0 l
- type Unzip7Sym1 t = Unzip7 t
- data NubSym0 l
- type NubSym1 t = Nub t
- data DeleteSym0 l
- data DeleteSym1 l l
- type DeleteSym2 t t = Delete t t
- data (:\\$) l
- data l :\\$$ l
- type (:\\$$$) t t = (:\\) t t
- data UnionSym0 l
- data UnionSym1 l l
- type UnionSym2 t t = Union t t
- data IntersectSym0 l
- data IntersectSym1 l l
- type IntersectSym2 t t = Intersect t t
- data InsertSym0 l
- data InsertSym1 l l
- type InsertSym2 t t = Insert t t
- data SortSym0 l
- type SortSym1 t = Sort t
- data NubBySym0 l
- data NubBySym1 l l
- type NubBySym2 t t = NubBy t t
- data DeleteBySym0 l
- data DeleteBySym1 l l
- data DeleteBySym2 l l l
- type DeleteBySym3 t t t = DeleteBy t t t
- data DeleteFirstsBySym0 l
- data DeleteFirstsBySym1 l l
- data DeleteFirstsBySym2 l l l
- type DeleteFirstsBySym3 t t t = DeleteFirstsBy t t t
- data UnionBySym0 l
- data UnionBySym1 l l
- data UnionBySym2 l l l
- type UnionBySym3 t t t = UnionBy t t t
- data IntersectBySym0 l
- data IntersectBySym1 l l
- data IntersectBySym2 l l l
- type IntersectBySym3 t t t = IntersectBy t t t
- data GroupBySym0 l
- data GroupBySym1 l l
- type GroupBySym2 t t = GroupBy t t
- data SortBySym0 l
- data SortBySym1 l l
- type SortBySym2 t t = SortBy t t
- data InsertBySym0 l
- data InsertBySym1 l l
- data InsertBySym2 l l l
- type InsertBySym3 t t t = InsertBy t t t
- data MaximumBySym0 l
- data MaximumBySym1 l l
- type MaximumBySym2 t t = MaximumBy t t
- data MinimumBySym0 l
- data MinimumBySym1 l l
- type MinimumBySym2 t t = MinimumBy t t
- data GenericLengthSym0 l
- type GenericLengthSym1 t = GenericLength t
The singleton for lists
The singleton kind-indexed data family.
data Sing Bool where Source | |
data Sing Ordering where Source | |
data Sing * where Source | |
data Sing Nat where Source | |
data Sing Symbol where
| |
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)
Basic functions
type family Length a :: Nat Source
Length `[]` = FromInteger 0 | |
Length ((:) _z_1627905949 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply LengthSym0 xs) |
List transformations
type family Intersperse a a :: [a] Source
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
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
sTranspose :: forall t. Sing t -> Sing (Apply TransposeSym0 t :: [[a]]) Source
type family Subsequences a :: [[a]] Source
Subsequences xs = Apply (Apply (:$) `[]`) (Apply NonEmptySubsequencesSym0 xs) |
sSubsequences :: forall t. Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]]) Source
type family Permutations a :: [[a]] Source
sPermutations :: forall t. Sing t -> Sing (Apply PermutationsSym0 t :: [[a]]) Source
Reducing lists (folds)
sFoldl :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source
sFoldl' :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) Source
sFoldr :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source
Special folds
sConcatMap :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) Source
type family Product a :: a Source
Product l = Apply (Apply (Let1627905958ProdSym1 l) l) (FromInteger 1) |
Building lists
Scans
sScanl :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b]) Source
sScanr :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b]) Source
Accumulating maps
sMapAccumL :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (acc, [y])) Source
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
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
Unfoldr f b = Case_1627907649 f b (Let1627907641Scrutinee_1627905698Sym2 f b) |
Sublists
Extracting sublists
sSplitAt :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) Source
sTakeWhile :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) Source
sDropWhile :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) Source
type family DropWhileEnd a a :: [a] Source
sDropWhileEnd :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a]) Source
type family Span a a :: ([a], [a]) Source
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') |
type family Break a a :: ([a], [a]) Source
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') |
Predicates
type family IsPrefixOf a a :: Bool Source
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
type family IsSuffixOf a a :: Bool Source
IsSuffixOf x y = Apply (Apply IsPrefixOfSym0 (Apply ReverseSym0 x)) (Apply ReverseSym0 y) |
sIsSuffixOf :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) Source
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
sElem :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) Source
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
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
Find p a_1627906562 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FilterSym0 p)) a_1627906562 |
sPartition :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) Source
Indexing lists
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
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
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
sFindIndices :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat]) Source
Zipping and unzipping lists
type family Zip3 a a a :: [(a, b, c)] Source
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
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
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
sUnzip7 :: forall t. Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g])) Source
Special lists
"Set" operations
sDelete :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a]) Source
(%:\\) :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply (:\\$) t) t :: [a]) infix 5 Source
sUnion :: forall t t. SEq (KProxy :: KProxy a) => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a]) Source
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
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
Sort a_1627906798 = Apply (Apply SortBySym0 CompareSym0) a_1627906798 |
Generalized functions
The "By
" operations
User-supplied equality (replacing an Eq
context)
The predicate is assumed to define an equivalence.
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
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
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
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
User-supplied comparison (replacing an Ord
context)
The function is assumed to define a total ordering.
sInsertBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a]) Source
sMaximumBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) Source
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
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
data LengthSym0 l Source
SuppressUnusedWarnings (TyFun [k] Nat -> *) (LengthSym0 k) Source | |
type Apply Nat [k] (LengthSym0 k) l0 = LengthSym1 k l0 Source |
type LengthSym1 t = Length t Source
data ReverseSym0 l Source
SuppressUnusedWarnings (TyFun [k] [k] -> *) (ReverseSym0 k) Source | |
type Apply [k] [k] (ReverseSym0 k) l0 = ReverseSym1 k l0 Source |
type ReverseSym1 t = Reverse t Source
data IntersperseSym0 l Source
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
SuppressUnusedWarnings (k -> TyFun [k] [k] -> *) (IntersperseSym1 k) Source | |
type Apply [k] [k] (IntersperseSym1 k l1) l0 = IntersperseSym2 k l1 l0 Source |
type IntersperseSym2 t t = Intersperse t t Source
data IntercalateSym0 l Source
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
SuppressUnusedWarnings ([k] -> TyFun [[k]] [k] -> *) (IntercalateSym1 k) Source | |
type Apply [k] [[k]] (IntercalateSym1 k l1) l0 = IntercalateSym2 k l1 l0 Source |
type IntercalateSym2 t t = Intercalate t t Source
data TransposeSym0 l Source
SuppressUnusedWarnings (TyFun [[k]] [[k]] -> *) (TransposeSym0 k) Source | |
type Apply [[k]] [[k]] (TransposeSym0 k) l0 = TransposeSym1 k l0 Source |
type TransposeSym1 t = Transpose t Source
data SubsequencesSym0 l Source
SuppressUnusedWarnings (TyFun [k] [[k]] -> *) (SubsequencesSym0 k) Source | |
type Apply [[k]] [k] (SubsequencesSym0 k) l0 = SubsequencesSym1 k l0 Source |
type SubsequencesSym1 t = Subsequences t Source
data PermutationsSym0 l Source
SuppressUnusedWarnings (TyFun [k] [[k]] -> *) (PermutationsSym0 k) Source | |
type Apply [[k]] [k] (PermutationsSym0 k) l0 = PermutationsSym1 k l0 Source |
type PermutationsSym1 t = Permutations t Source
data Foldl'Sym0 l Source
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
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
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
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
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
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
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 Foldr1Sym0 l Source
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
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
SuppressUnusedWarnings (TyFun [[k]] [k] -> *) (ConcatSym0 k) Source | |
type Apply [k] [[k]] (ConcatSym0 k) l0 = ConcatSym1 k l0 Source |
type ConcatSym1 t = Concat t Source
data ConcatMapSym0 l Source
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
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 ConcatMapSym2 t t = ConcatMap t t Source
data ProductSym0 l Source
SuppressUnusedWarnings (TyFun [k] k -> *) (ProductSym0 k) Source | |
type Apply k [k] (ProductSym0 k) l0 = ProductSym1 k l0 Source |
type ProductSym1 t = Product t Source
data MaximumSym0 l Source
SuppressUnusedWarnings (TyFun [k] k -> *) (MaximumSym0 k) Source | |
type Apply k [k] (MaximumSym0 k) l0 = MaximumSym1 k l0 Source |
type MaximumSym1 t = Maximum t Source
data MinimumSym0 l Source
SuppressUnusedWarnings (TyFun [k] k -> *) (MinimumSym0 k) Source | |
type Apply k [k] (MinimumSym0 k) l0 = MinimumSym1 k l0 Source |
type MinimumSym1 t = Minimum t Source
data Scanl1Sym0 l Source
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
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 Scanr1Sym0 l Source
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
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
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
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
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
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
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
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
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
SuppressUnusedWarnings (Nat -> TyFun k [k] -> *) (ReplicateSym1 k) Source | |
type Apply [k] k (ReplicateSym1 k l1) l0 = ReplicateSym2 k l1 l0 Source |
type ReplicateSym2 t t = Replicate t t Source
data UnfoldrSym0 l Source
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
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 SplitAtSym0 l Source
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
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
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
SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] [k] -> *) (TakeWhileSym1 k) Source | |
type Apply [k] [k] (TakeWhileSym1 k l1) l0 = TakeWhileSym2 k l1 l0 Source |
type TakeWhileSym2 t t = TakeWhile t t Source
data DropWhileSym0 l Source
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
SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] [k] -> *) (DropWhileSym1 k) Source | |
type Apply [k] [k] (DropWhileSym1 k l1) l0 = DropWhileSym2 k l1 l0 Source |
type DropWhileSym2 t t = DropWhile t t Source
data DropWhileEndSym0 l Source
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
SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] [k] -> *) (DropWhileEndSym1 k) Source | |
type Apply [k] [k] (DropWhileEndSym1 k l1) l0 = DropWhileEndSym2 k l1 l0 Source |
type DropWhileEndSym2 t t = DropWhileEnd t t Source
data IsPrefixOfSym0 l Source
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
SuppressUnusedWarnings ([k] -> TyFun [k] Bool -> *) (IsPrefixOfSym1 k) Source | |
type Apply Bool [k] (IsPrefixOfSym1 k l1) l0 = IsPrefixOfSym2 k l1 l0 Source |
type IsPrefixOfSym2 t t = IsPrefixOf t t Source
data IsSuffixOfSym0 l Source
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
SuppressUnusedWarnings ([k] -> TyFun [k] Bool -> *) (IsSuffixOfSym1 k) Source | |
type Apply Bool [k] (IsSuffixOfSym1 k l1) l0 = IsSuffixOfSym2 k l1 l0 Source |
type IsSuffixOfSym2 t t = IsSuffixOf t t Source
data IsInfixOfSym0 l Source
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
SuppressUnusedWarnings ([k] -> TyFun [k] Bool -> *) (IsInfixOfSym1 k) Source | |
type Apply Bool [k] (IsInfixOfSym1 k l1) l0 = IsInfixOfSym2 k l1 l0 Source |
type IsInfixOfSym2 t t = IsInfixOf t t Source
data NotElemSym0 l Source
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
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
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
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 FilterSym0 l Source
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
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
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
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 |
type PartitionSym2 t t = Partition t t Source
data ElemIndexSym0 l Source
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
SuppressUnusedWarnings (k -> TyFun [k] (Maybe Nat) -> *) (ElemIndexSym1 k) Source | |
type Apply (Maybe Nat) [k] (ElemIndexSym1 k l1) l0 = ElemIndexSym2 k l1 l0 Source |
type ElemIndexSym2 t t = ElemIndex t t Source
data ElemIndicesSym0 l Source
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
SuppressUnusedWarnings (k -> TyFun [k] [Nat] -> *) (ElemIndicesSym1 k) Source | |
type Apply [Nat] [k] (ElemIndicesSym1 k l1) l0 = ElemIndicesSym2 k l1 l0 Source |
type ElemIndicesSym2 t t = ElemIndices t t Source
data FindIndexSym0 l Source
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
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 |
type FindIndexSym2 t t = FindIndex t t Source
data FindIndicesSym0 l Source
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
SuppressUnusedWarnings ((TyFun k Bool -> *) -> TyFun [k] [Nat] -> *) (FindIndicesSym1 k) Source | |
type Apply [Nat] [k] (FindIndicesSym1 k l1) l0 = FindIndicesSym2 k l1 l0 Source |
type FindIndicesSym2 t t = FindIndices t t Source
data ZipWithSym0 l Source
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
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
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
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
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
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
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 Unzip3Sym0 l Source
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 |
type Unzip3Sym1 t = Unzip3 t Source
data Unzip4Sym0 l Source
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 |
type Unzip4Sym1 t = Unzip4 t Source
data Unzip5Sym0 l Source
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 |
type Unzip5Sym1 t = Unzip5 t Source
data Unzip6Sym0 l Source
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 |
type Unzip6Sym1 t = Unzip6 t Source
data Unzip7Sym0 l Source
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 |
type Unzip7Sym1 t = Unzip7 t Source
data DeleteSym0 l Source
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
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 IntersectSym0 l Source
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
SuppressUnusedWarnings ([k] -> TyFun [k] [k] -> *) (IntersectSym1 k) Source | |
type Apply [k] [k] (IntersectSym1 k l1) l0 = IntersectSym2 k l1 l0 Source |
type IntersectSym2 t t = Intersect t t Source
data InsertSym0 l Source
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
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 DeleteBySym0 l Source
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
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
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
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
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
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 |
type DeleteFirstsBySym3 t t t = DeleteFirstsBy t t t Source
data UnionBySym0 l Source
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
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
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
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
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
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 |
type IntersectBySym3 t t t = IntersectBy t t t Source
data GroupBySym0 l Source
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
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
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
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
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
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
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
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
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 |
type MaximumBySym2 t t = MaximumBy t t Source
data MinimumBySym0 l Source
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
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 |
type MinimumBySym2 t t = MinimumBy t t Source
data GenericLengthSym0 l Source
SuppressUnusedWarnings (TyFun [k] k -> *) (GenericLengthSym0 k k) Source | |
type Apply k [k1] (GenericLengthSym0 k1 k) l0 = GenericLengthSym1 k1 k l0 Source |
type GenericLengthSym1 t = GenericLength t Source