| Copyright | (C) 2013-2014 Richard Eisenberg Jan Stolarek |
|---|---|
| License | BSD-style (see LICENSE) |
| Maintainer | Richard Eisenberg (rae@cs.brynmawr.edu) |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
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.
- data family Sing (a :: k)
- type SList = (Sing :: [a] -> Type)
- type family (a :: [a]) :++ (a :: [a]) :: [a] where ...
- (%:++) :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (:++$) t) t :: [a])
- type family Head (a :: [a]) :: a where ...
- sHead :: forall (t :: [a]). Sing t -> Sing (Apply HeadSym0 t :: a)
- type family Last (a :: [a]) :: a where ...
- sLast :: forall (t :: [a]). Sing t -> Sing (Apply LastSym0 t :: a)
- type family Tail (a :: [a]) :: [a] where ...
- sTail :: forall (t :: [a]). Sing t -> Sing (Apply TailSym0 t :: [a])
- type family Init (a :: [a]) :: [a] where ...
- sInit :: forall (t :: [a]). Sing t -> Sing (Apply InitSym0 t :: [a])
- type family Null (a :: [a]) :: Bool where ...
- sNull :: forall (t :: [a]). Sing t -> Sing (Apply NullSym0 t :: Bool)
- type family Length (a :: [a]) :: Nat where ...
- sLength :: forall (t :: [a]). Sing t -> Sing (Apply LengthSym0 t :: Nat)
- type family Map (a :: TyFun a b -> Type) (a :: [a]) :: [b] where ...
- sMap :: forall (t :: TyFun a b -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b])
- type family Reverse (a :: [a]) :: [a] where ...
- sReverse :: forall (t :: [a]). Sing t -> Sing (Apply ReverseSym0 t :: [a])
- type family Intersperse (a :: a) (a :: [a]) :: [a] where ...
- sIntersperse :: forall (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a])
- type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ...
- sIntercalate :: forall (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a])
- type family Transpose (a :: [[a]]) :: [[a]] where ...
- sTranspose :: forall (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]])
- type family Subsequences (a :: [a]) :: [[a]] where ...
- sSubsequences :: forall (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]])
- type family Permutations (a :: [a]) :: [[a]] where ...
- sPermutations :: forall (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]])
- type family Foldl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- sFoldl :: forall (t :: TyFun b (TyFun a b -> Type) -> Type) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b)
- type family Foldl' (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- sFoldl' :: forall (t :: TyFun b (TyFun a b -> Type) -> Type) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b)
- type family Foldl1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
- sFoldl1 :: forall (t :: TyFun a (TyFun a a -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a)
- type family Foldl1' (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
- sFoldl1' :: forall (t :: TyFun a (TyFun a a -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a)
- type family Foldr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- sFoldr :: forall (t :: TyFun a (TyFun b b -> Type) -> Type) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b)
- type family Foldr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
- sFoldr1 :: forall (t :: TyFun a (TyFun a a -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a)
- type family Concat (a :: [[a]]) :: [a] where ...
- sConcat :: forall (t :: [[a]]). Sing t -> Sing (Apply ConcatSym0 t :: [a])
- type family ConcatMap (a :: TyFun a [b] -> Type) (a :: [a]) :: [b] where ...
- sConcatMap :: forall (t :: TyFun a [b] -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b])
- type family And (a :: [Bool]) :: Bool where ...
- sAnd :: forall (t :: [Bool]). Sing t -> Sing (Apply AndSym0 t :: Bool)
- type family Or (a :: [Bool]) :: Bool where ...
- sOr :: forall (t :: [Bool]). Sing t -> Sing (Apply OrSym0 t :: Bool)
- type family Any_ (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ...
- sAny_ :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Any_Sym0 t) t :: Bool)
- type family All (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ...
- sAll :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool)
- type family Sum (a :: [a]) :: a where ...
- sSum :: forall (t :: [a]). SNum a => Sing t -> Sing (Apply SumSym0 t :: a)
- type family Product (a :: [a]) :: a where ...
- sProduct :: forall (t :: [a]). SNum a => Sing t -> Sing (Apply ProductSym0 t :: a)
- type family Maximum (a :: [a]) :: a where ...
- sMaximum :: forall (t :: [a]). SOrd a => Sing t -> Sing (Apply MaximumSym0 t :: a)
- type family Minimum (a :: [a]) :: a where ...
- sMinimum :: forall (t :: [a]). SOrd a => Sing t -> Sing (Apply MinimumSym0 t :: a)
- any_ :: (a -> Bool) -> [a] -> Bool
- type family Scanl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ...
- sScanl :: forall (t :: TyFun b (TyFun a b -> Type) -> Type) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b])
- type family Scanl1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ...
- sScanl1 :: forall (t :: TyFun a (TyFun a a -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a])
- type family Scanr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ...
- sScanr :: forall (t :: TyFun a (TyFun b b -> Type) -> Type) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b])
- type family Scanr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ...
- sScanr1 :: forall (t :: TyFun a (TyFun a a -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a])
- type family MapAccumL (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ...
- sMapAccumL :: forall (t :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (t :: acc) (t :: [x]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (acc, [y]))
- type family MapAccumR (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ...
- sMapAccumR :: forall (t :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (t :: acc) (t :: [x]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (acc, [y]))
- type family Replicate (a :: Nat) (a :: a) :: [a] where ...
- sReplicate :: forall (t :: Nat) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a])
- type family Unfoldr (a :: TyFun b (Maybe (a, b)) -> Type) (a :: b) :: [a] where ...
- sUnfoldr :: forall (t :: TyFun b (Maybe (a, b)) -> Type) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a])
- type family Take (a :: Nat) (a :: [a]) :: [a] where ...
- sTake :: forall (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a])
- type family Drop (a :: Nat) (a :: [a]) :: [a] where ...
- sDrop :: forall (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a])
- type family SplitAt (a :: Nat) (a :: [a]) :: ([a], [a]) where ...
- sSplitAt :: forall (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a]))
- type family TakeWhile (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ...
- sTakeWhile :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a])
- type family DropWhile (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ...
- sDropWhile :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a])
- type family DropWhileEnd (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ...
- sDropWhileEnd :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a])
- type family Span (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ...
- sSpan :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a]))
- type family Break (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ...
- sBreak :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a]))
- type family Group (a :: [a]) :: [[a]] where ...
- sGroup :: forall (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [[a]])
- type family Inits (a :: [a]) :: [[a]] where ...
- sInits :: forall (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: [[a]])
- type family Tails (a :: [a]) :: [[a]] where ...
- sTails :: forall (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: [[a]])
- type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsPrefixOf :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool)
- type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsSuffixOf :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool)
- type family IsInfixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsInfixOf :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool)
- type family Elem (a :: a) (a :: [a]) :: Bool where ...
- sElem :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool)
- type family NotElem (a :: a) (a :: [a]) :: Bool where ...
- sNotElem :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool)
- type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ...
- sLookup :: forall (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b)
- type family Find (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe a where ...
- sFind :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a)
- type family Filter (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ...
- sFilter :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
- type family Partition (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ...
- sPartition :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
- type family (a :: [a]) :!! (a :: Nat) :: a where ...
- (%:!!) :: forall (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (:!!$) t) t :: a)
- type family ElemIndex (a :: a) (a :: [a]) :: Maybe Nat where ...
- sElemIndex :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat)
- type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ...
- sElemIndices :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat])
- type family FindIndex (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe Nat where ...
- sFindIndex :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat)
- type family FindIndices (a :: TyFun a Bool -> Type) (a :: [a]) :: [Nat] where ...
- sFindIndices :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat])
- type family Zip (a :: [a]) (a :: [b]) :: [(a, b)] where ...
- sZip :: forall (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)])
- type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ...
- sZip3 :: forall (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)])
- type family ZipWith (a :: TyFun a (TyFun b c -> Type) -> Type) (a :: [a]) (a :: [b]) :: [c] where ...
- sZipWith :: forall (t :: TyFun a (TyFun b c -> Type) -> Type) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c])
- type family ZipWith3 (a :: TyFun a (TyFun b (TyFun c d -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ...
- sZipWith3 :: forall (t :: TyFun a (TyFun b (TyFun c d -> Type) -> Type) -> Type) (t :: [a]) (t :: [b]) (t :: [c]). 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)]) :: ([a], [b]) where ...
- sUnzip :: forall (t :: [(a, b)]). Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b]))
- type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ...
- sUnzip3 :: forall (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c]))
- type family Unzip4 (a :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
- sUnzip4 :: forall (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d]))
- type family Unzip5 (a :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ...
- sUnzip5 :: forall (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e]))
- type family Unzip6 (a :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ...
- sUnzip6 :: forall (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f]))
- type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
- sUnzip7 :: forall (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g]))
- type family Nub (a :: [a]) :: [a] where ...
- sNub :: forall (t :: [a]). SEq a => Sing t -> Sing (Apply NubSym0 t :: [a])
- type family Delete (a :: a) (a :: [a]) :: [a] where ...
- sDelete :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a])
- type family (a :: [a]) :\\ (a :: [a]) :: [a] where ...
- (%:\\) :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (:\\$) t) t :: [a])
- type family Union (a :: [a]) (a :: [a]) :: [a] where ...
- sUnion :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a])
- type family Intersect (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersect :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a])
- type family Insert (a :: a) (a :: [a]) :: [a] where ...
- sInsert :: forall (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a])
- type family Sort (a :: [a]) :: [a] where ...
- sSort :: forall (t :: [a]). SOrd a => Sing t -> Sing (Apply SortSym0 t :: [a])
- type family NubBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [a] where ...
- sNubBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a])
- type family DeleteBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ...
- sDeleteBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a])
- type family DeleteFirstsBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ...
- sDeleteFirstsBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a])
- type family UnionBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ...
- sUnionBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a])
- type family IntersectBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersectBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a])
- type family GroupBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [[a]] where ...
- sGroupBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]])
- type family SortBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: [a] where ...
- sSortBy :: forall (t :: TyFun a (TyFun a Ordering -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a])
- type family InsertBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ...
- sInsertBy :: forall (t :: TyFun a (TyFun a Ordering -> Type) -> Type) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a])
- type family MaximumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ...
- sMaximumBy :: forall (t :: TyFun a (TyFun a Ordering -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a)
- type family MinimumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ...
- sMinimumBy :: forall (t :: TyFun a (TyFun a Ordering -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a)
- type family GenericLength (a :: [a]) :: i where ...
- sGenericLength :: forall (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i)
- type NilSym0 = '[]
- data (:$) (l :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type))
- data (l :: a3530822107858468865) :$$ (l :: TyFun [a3530822107858468865] [a3530822107858468865])
- type (:$$$) (t :: a3530822107858468865) (t :: [a3530822107858468865]) = (:) t t
- type (:++$$$) (t :: [a6989586621679277916]) (t :: [a6989586621679277916]) = (:++) t t
- data (l :: [a6989586621679277916]) :++$$ (l :: TyFun [a6989586621679277916] [a6989586621679277916])
- data (:++$) (l :: TyFun [a6989586621679277916] (TyFun [a6989586621679277916] [a6989586621679277916] -> Type))
- data HeadSym0 (l :: TyFun [a6989586621679454963] a6989586621679454963)
- type HeadSym1 (t :: [a6989586621679454963]) = Head t
- data LastSym0 (l :: TyFun [a6989586621679454962] a6989586621679454962)
- type LastSym1 (t :: [a6989586621679454962]) = Last t
- data TailSym0 (l :: TyFun [a6989586621679454961] [a6989586621679454961])
- type TailSym1 (t :: [a6989586621679454961]) = Tail t
- data InitSym0 (l :: TyFun [a6989586621679454960] [a6989586621679454960])
- type InitSym1 (t :: [a6989586621679454960]) = Init t
- data NullSym0 (l :: TyFun [a6989586621679454959] Bool)
- type NullSym1 (t :: [a6989586621679454959]) = Null t
- data LengthSym0 (l :: TyFun [a6989586621679454846] Nat)
- type LengthSym1 (t :: [a6989586621679454846]) = Length t
- data MapSym0 (l :: TyFun (TyFun a6989586621679277917 b6989586621679277918 -> Type) (TyFun [a6989586621679277917] [b6989586621679277918] -> Type))
- data MapSym1 (l :: TyFun a6989586621679277917 b6989586621679277918 -> Type) (l :: TyFun [a6989586621679277917] [b6989586621679277918])
- type MapSym2 (t :: TyFun a6989586621679277917 b6989586621679277918 -> Type) (t :: [a6989586621679277917]) = Map t t
- data ReverseSym0 (l :: TyFun [a6989586621679454958] [a6989586621679454958])
- type ReverseSym1 (t :: [a6989586621679454958]) = Reverse t
- data IntersperseSym0 (l :: TyFun a6989586621679454957 (TyFun [a6989586621679454957] [a6989586621679454957] -> Type))
- data IntersperseSym1 (l :: a6989586621679454957) (l :: TyFun [a6989586621679454957] [a6989586621679454957])
- type IntersperseSym2 (t :: a6989586621679454957) (t :: [a6989586621679454957]) = Intersperse t t
- data IntercalateSym0 (l :: TyFun [a6989586621679454956] (TyFun [[a6989586621679454956]] [a6989586621679454956] -> Type))
- data IntercalateSym1 (l :: [a6989586621679454956]) (l :: TyFun [[a6989586621679454956]] [a6989586621679454956])
- type IntercalateSym2 (t :: [a6989586621679454956]) (t :: [[a6989586621679454956]]) = Intercalate t t
- data TransposeSym0 (l :: TyFun [[a6989586621679454844]] [[a6989586621679454844]])
- type TransposeSym1 (t :: [[a6989586621679454844]]) = Transpose t
- data SubsequencesSym0 (l :: TyFun [a6989586621679454955] [[a6989586621679454955]])
- type SubsequencesSym1 (t :: [a6989586621679454955]) = Subsequences t
- data PermutationsSym0 (l :: TyFun [a6989586621679454952] [[a6989586621679454952]])
- type PermutationsSym1 (t :: [a6989586621679454952]) = Permutations t
- data FoldlSym0 (l :: TyFun (TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (TyFun b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type) -> Type))
- data FoldlSym1 (l :: TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (l :: TyFun b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type))
- data FoldlSym2 (l :: TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (l :: b6989586621679240792) (l :: TyFun [a6989586621679240791] b6989586621679240792)
- type FoldlSym3 (t :: TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (t :: b6989586621679240792) (t :: [a6989586621679240791]) = Foldl t t t
- data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) -> Type))
- data Foldl'Sym1 (l :: TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (l :: TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type))
- data Foldl'Sym2 (l :: TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (l :: b6989586621679454951) (l :: TyFun [a6989586621679454950] b6989586621679454951)
- type Foldl'Sym3 (t :: TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (t :: b6989586621679454951) (t :: [a6989586621679454950]) = Foldl' t t t
- data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (TyFun [a6989586621679454949] a6989586621679454949 -> Type))
- data Foldl1Sym1 (l :: TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (l :: TyFun [a6989586621679454949] a6989586621679454949)
- type Foldl1Sym2 (t :: TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (t :: [a6989586621679454949]) = Foldl1 t t
- data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (TyFun [a6989586621679454948] a6989586621679454948 -> Type))
- data Foldl1'Sym1 (l :: TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (l :: TyFun [a6989586621679454948] a6989586621679454948)
- type Foldl1'Sym2 (t :: TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (t :: [a6989586621679454948]) = Foldl1' t t
- data FoldrSym0 (l :: TyFun (TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) -> Type))
- data FoldrSym1 (l :: TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (l :: TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type))
- data FoldrSym2 (l :: TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (l :: b6989586621679277920) (l :: TyFun [a6989586621679277919] b6989586621679277920)
- type FoldrSym3 (t :: TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (t :: b6989586621679277920) (t :: [a6989586621679277919]) = Foldr t t t
- data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (TyFun [a6989586621679454947] a6989586621679454947 -> Type))
- data Foldr1Sym1 (l :: TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (l :: TyFun [a6989586621679454947] a6989586621679454947)
- type Foldr1Sym2 (t :: TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (t :: [a6989586621679454947]) = Foldr1 t t
- data ConcatSym0 (l :: TyFun [[a6989586621679454946]] [a6989586621679454946])
- type ConcatSym1 (t :: [[a6989586621679454946]]) = Concat t
- data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679454944 [b6989586621679454945] -> Type) (TyFun [a6989586621679454944] [b6989586621679454945] -> Type))
- data ConcatMapSym1 (l :: TyFun a6989586621679454944 [b6989586621679454945] -> Type) (l :: TyFun [a6989586621679454944] [b6989586621679454945])
- type ConcatMapSym2 (t :: TyFun a6989586621679454944 [b6989586621679454945] -> Type) (t :: [a6989586621679454944]) = ConcatMap t t
- data AndSym0 (l :: TyFun [Bool] Bool)
- type AndSym1 (t :: [Bool]) = And t
- data OrSym0 (l :: TyFun [Bool] Bool)
- type OrSym1 (t :: [Bool]) = Or t
- data Any_Sym0 (l :: TyFun (TyFun a6989586621679444727 Bool -> Type) (TyFun [a6989586621679444727] Bool -> Type))
- data Any_Sym1 (l :: TyFun a6989586621679444727 Bool -> Type) (l :: TyFun [a6989586621679444727] Bool)
- type Any_Sym2 (t :: TyFun a6989586621679444727 Bool -> Type) (t :: [a6989586621679444727]) = Any_ t t
- data AllSym0 (l :: TyFun (TyFun a6989586621679454943 Bool -> Type) (TyFun [a6989586621679454943] Bool -> Type))
- data AllSym1 (l :: TyFun a6989586621679454943 Bool -> Type) (l :: TyFun [a6989586621679454943] Bool)
- type AllSym2 (t :: TyFun a6989586621679454943 Bool -> Type) (t :: [a6989586621679454943]) = All t t
- data SumSym0 (l :: TyFun [a6989586621679454848] a6989586621679454848)
- type SumSym1 (t :: [a6989586621679454848]) = Sum t
- data ProductSym0 (l :: TyFun [a6989586621679454847] a6989586621679454847)
- type ProductSym1 (t :: [a6989586621679454847]) = Product t
- data MaximumSym0 (l :: TyFun [a6989586621679454857] a6989586621679454857)
- type MaximumSym1 (t :: [a6989586621679454857]) = Maximum t
- data MinimumSym0 (l :: TyFun [a6989586621679454856] a6989586621679454856)
- type MinimumSym1 (t :: [a6989586621679454856]) = Minimum t
- data ScanlSym0 (l :: TyFun (TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) -> Type))
- data ScanlSym1 (l :: TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (l :: TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type))
- data ScanlSym2 (l :: TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (l :: b6989586621679454941) (l :: TyFun [a6989586621679454942] [b6989586621679454941])
- type ScanlSym3 (t :: TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (t :: b6989586621679454941) (t :: [a6989586621679454942]) = Scanl t t t
- data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (TyFun [a6989586621679454940] [a6989586621679454940] -> Type))
- data Scanl1Sym1 (l :: TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (l :: TyFun [a6989586621679454940] [a6989586621679454940])
- type Scanl1Sym2 (t :: TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (t :: [a6989586621679454940]) = Scanl1 t t
- data ScanrSym0 (l :: TyFun (TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) -> Type))
- data ScanrSym1 (l :: TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (l :: TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type))
- data ScanrSym2 (l :: TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (l :: b6989586621679454939) (l :: TyFun [a6989586621679454938] [b6989586621679454939])
- type ScanrSym3 (t :: TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (t :: b6989586621679454939) (t :: [a6989586621679454938]) = Scanr t t t
- data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (TyFun [a6989586621679454937] [a6989586621679454937] -> Type))
- data Scanr1Sym1 (l :: TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (l :: TyFun [a6989586621679454937] [a6989586621679454937])
- type Scanr1Sym2 (t :: TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (t :: [a6989586621679454937]) = Scanr1 t t
- data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) -> Type))
- data MapAccumLSym1 (l :: TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (l :: TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type))
- data MapAccumLSym2 (l :: TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (l :: acc6989586621679454934) (l :: TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]))
- type MapAccumLSym3 (t :: TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (t :: acc6989586621679454934) (t :: [x6989586621679454935]) = MapAccumL t t t
- data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) -> Type))
- data MapAccumRSym1 (l :: TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (l :: TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type))
- data MapAccumRSym2 (l :: TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (l :: acc6989586621679454931) (l :: TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]))
- type MapAccumRSym3 (t :: TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (t :: acc6989586621679454931) (t :: [x6989586621679454932]) = MapAccumR t t t
- data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679454845 [a6989586621679454845] -> Type))
- data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679454845 [a6989586621679454845])
- type ReplicateSym2 (t :: Nat) (t :: a6989586621679454845) = Replicate t t
- data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (TyFun b6989586621679454929 [a6989586621679454930] -> Type))
- data UnfoldrSym1 (l :: TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (l :: TyFun b6989586621679454929 [a6989586621679454930])
- type UnfoldrSym2 (t :: TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (t :: b6989586621679454929) = Unfoldr t t
- data TakeSym0 (l :: TyFun Nat (TyFun [a6989586621679454861] [a6989586621679454861] -> Type))
- data TakeSym1 (l :: Nat) (l :: TyFun [a6989586621679454861] [a6989586621679454861])
- type TakeSym2 (t :: Nat) (t :: [a6989586621679454861]) = Take t t
- data DropSym0 (l :: TyFun Nat (TyFun [a6989586621679454860] [a6989586621679454860] -> Type))
- data DropSym1 (l :: Nat) (l :: TyFun [a6989586621679454860] [a6989586621679454860])
- type DropSym2 (t :: Nat) (t :: [a6989586621679454860]) = Drop t t
- data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679454859] ([a6989586621679454859], [a6989586621679454859]) -> Type))
- data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679454859] ([a6989586621679454859], [a6989586621679454859]))
- type SplitAtSym2 (t :: Nat) (t :: [a6989586621679454859]) = SplitAt t t
- data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679454866 Bool -> Type) (TyFun [a6989586621679454866] [a6989586621679454866] -> Type))
- data TakeWhileSym1 (l :: TyFun a6989586621679454866 Bool -> Type) (l :: TyFun [a6989586621679454866] [a6989586621679454866])
- type TakeWhileSym2 (t :: TyFun a6989586621679454866 Bool -> Type) (t :: [a6989586621679454866]) = TakeWhile t t
- data DropWhileSym0 (l :: TyFun (TyFun a6989586621679454865 Bool -> Type) (TyFun [a6989586621679454865] [a6989586621679454865] -> Type))
- data DropWhileSym1 (l :: TyFun a6989586621679454865 Bool -> Type) (l :: TyFun [a6989586621679454865] [a6989586621679454865])
- type DropWhileSym2 (t :: TyFun a6989586621679454865 Bool -> Type) (t :: [a6989586621679454865]) = DropWhile t t
- data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679454864 Bool -> Type) (TyFun [a6989586621679454864] [a6989586621679454864] -> Type))
- data DropWhileEndSym1 (l :: TyFun a6989586621679454864 Bool -> Type) (l :: TyFun [a6989586621679454864] [a6989586621679454864])
- type DropWhileEndSym2 (t :: TyFun a6989586621679454864 Bool -> Type) (t :: [a6989586621679454864]) = DropWhileEnd t t
- data SpanSym0 (l :: TyFun (TyFun a6989586621679454863 Bool -> Type) (TyFun [a6989586621679454863] ([a6989586621679454863], [a6989586621679454863]) -> Type))
- data SpanSym1 (l :: TyFun a6989586621679454863 Bool -> Type) (l :: TyFun [a6989586621679454863] ([a6989586621679454863], [a6989586621679454863]))
- type SpanSym2 (t :: TyFun a6989586621679454863 Bool -> Type) (t :: [a6989586621679454863]) = Span t t
- data BreakSym0 (l :: TyFun (TyFun a6989586621679454862 Bool -> Type) (TyFun [a6989586621679454862] ([a6989586621679454862], [a6989586621679454862]) -> Type))
- data BreakSym1 (l :: TyFun a6989586621679454862 Bool -> Type) (l :: TyFun [a6989586621679454862] ([a6989586621679454862], [a6989586621679454862]))
- type BreakSym2 (t :: TyFun a6989586621679454862 Bool -> Type) (t :: [a6989586621679454862]) = Break t t
- data GroupSym0 (l :: TyFun [a6989586621679454858] [[a6989586621679454858]])
- type GroupSym1 (t :: [a6989586621679454858]) = Group t
- data InitsSym0 (l :: TyFun [a6989586621679454928] [[a6989586621679454928]])
- type InitsSym1 (t :: [a6989586621679454928]) = Inits t
- data TailsSym0 (l :: TyFun [a6989586621679454927] [[a6989586621679454927]])
- type TailsSym1 (t :: [a6989586621679454927]) = Tails t
- data IsPrefixOfSym0 (l :: TyFun [a6989586621679454926] (TyFun [a6989586621679454926] Bool -> Type))
- data IsPrefixOfSym1 (l :: [a6989586621679454926]) (l :: TyFun [a6989586621679454926] Bool)
- type IsPrefixOfSym2 (t :: [a6989586621679454926]) (t :: [a6989586621679454926]) = IsPrefixOf t t
- data IsSuffixOfSym0 (l :: TyFun [a6989586621679454925] (TyFun [a6989586621679454925] Bool -> Type))
- data IsSuffixOfSym1 (l :: [a6989586621679454925]) (l :: TyFun [a6989586621679454925] Bool)
- type IsSuffixOfSym2 (t :: [a6989586621679454925]) (t :: [a6989586621679454925]) = IsSuffixOf t t
- data IsInfixOfSym0 (l :: TyFun [a6989586621679454924] (TyFun [a6989586621679454924] Bool -> Type))
- data IsInfixOfSym1 (l :: [a6989586621679454924]) (l :: TyFun [a6989586621679454924] Bool)
- type IsInfixOfSym2 (t :: [a6989586621679454924]) (t :: [a6989586621679454924]) = IsInfixOf t t
- data ElemSym0 (l :: TyFun a6989586621679454923 (TyFun [a6989586621679454923] Bool -> Type))
- data ElemSym1 (l :: a6989586621679454923) (l :: TyFun [a6989586621679454923] Bool)
- type ElemSym2 (t :: a6989586621679454923) (t :: [a6989586621679454923]) = Elem t t
- data NotElemSym0 (l :: TyFun a6989586621679454922 (TyFun [a6989586621679454922] Bool -> Type))
- data NotElemSym1 (l :: a6989586621679454922) (l :: TyFun [a6989586621679454922] Bool)
- type NotElemSym2 (t :: a6989586621679454922) (t :: [a6989586621679454922]) = NotElem t t
- data LookupSym0 (l :: TyFun a6989586621679454851 (TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852) -> Type))
- data LookupSym1 (l :: a6989586621679454851) (l :: TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852))
- type LookupSym2 (t :: a6989586621679454851) (t :: [(a6989586621679454851, b6989586621679454852)]) = Lookup t t
- data FindSym0 (l :: TyFun (TyFun a6989586621679454873 Bool -> Type) (TyFun [a6989586621679454873] (Maybe a6989586621679454873) -> Type))
- data FindSym1 (l :: TyFun a6989586621679454873 Bool -> Type) (l :: TyFun [a6989586621679454873] (Maybe a6989586621679454873))
- type FindSym2 (t :: TyFun a6989586621679454873 Bool -> Type) (t :: [a6989586621679454873]) = Find t t
- data FilterSym0 (l :: TyFun (TyFun a6989586621679454874 Bool -> Type) (TyFun [a6989586621679454874] [a6989586621679454874] -> Type))
- data FilterSym1 (l :: TyFun a6989586621679454874 Bool -> Type) (l :: TyFun [a6989586621679454874] [a6989586621679454874])
- type FilterSym2 (t :: TyFun a6989586621679454874 Bool -> Type) (t :: [a6989586621679454874]) = Filter t t
- data PartitionSym0 (l :: TyFun (TyFun a6989586621679454850 Bool -> Type) (TyFun [a6989586621679454850] ([a6989586621679454850], [a6989586621679454850]) -> Type))
- data PartitionSym1 (l :: TyFun a6989586621679454850 Bool -> Type) (l :: TyFun [a6989586621679454850] ([a6989586621679454850], [a6989586621679454850]))
- type PartitionSym2 (t :: TyFun a6989586621679454850 Bool -> Type) (t :: [a6989586621679454850]) = Partition t t
- data (:!!$) (l :: TyFun [a6989586621679454843] (TyFun Nat a6989586621679454843 -> Type))
- data (l :: [a6989586621679454843]) :!!$$ (l :: TyFun Nat a6989586621679454843)
- type (:!!$$$) (t :: [a6989586621679454843]) (t :: Nat) = (:!!) t t
- data ElemIndexSym0 (l :: TyFun a6989586621679454872 (TyFun [a6989586621679454872] (Maybe Nat) -> Type))
- data ElemIndexSym1 (l :: a6989586621679454872) (l :: TyFun [a6989586621679454872] (Maybe Nat))
- type ElemIndexSym2 (t :: a6989586621679454872) (t :: [a6989586621679454872]) = ElemIndex t t
- data ElemIndicesSym0 (l :: TyFun a6989586621679454871 (TyFun [a6989586621679454871] [Nat] -> Type))
- data ElemIndicesSym1 (l :: a6989586621679454871) (l :: TyFun [a6989586621679454871] [Nat])
- type ElemIndicesSym2 (t :: a6989586621679454871) (t :: [a6989586621679454871]) = ElemIndices t t
- data FindIndexSym0 (l :: TyFun (TyFun a6989586621679454870 Bool -> Type) (TyFun [a6989586621679454870] (Maybe Nat) -> Type))
- data FindIndexSym1 (l :: TyFun a6989586621679454870 Bool -> Type) (l :: TyFun [a6989586621679454870] (Maybe Nat))
- type FindIndexSym2 (t :: TyFun a6989586621679454870 Bool -> Type) (t :: [a6989586621679454870]) = FindIndex t t
- data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679454869 Bool -> Type) (TyFun [a6989586621679454869] [Nat] -> Type))
- data FindIndicesSym1 (l :: TyFun a6989586621679454869 Bool -> Type) (l :: TyFun [a6989586621679454869] [Nat])
- type FindIndicesSym2 (t :: TyFun a6989586621679454869 Bool -> Type) (t :: [a6989586621679454869]) = FindIndices t t
- data ZipSym0 (l :: TyFun [a6989586621679454920] (TyFun [b6989586621679454921] [(a6989586621679454920, b6989586621679454921)] -> Type))
- data ZipSym1 (l :: [a6989586621679454920]) (l :: TyFun [b6989586621679454921] [(a6989586621679454920, b6989586621679454921)])
- type ZipSym2 (t :: [a6989586621679454920]) (t :: [b6989586621679454921]) = Zip t t
- data Zip3Sym0 (l :: TyFun [a6989586621679454917] (TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) -> Type))
- data Zip3Sym1 (l :: [a6989586621679454917]) (l :: TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type))
- data Zip3Sym2 (l :: [a6989586621679454917]) (l :: [b6989586621679454918]) (l :: TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)])
- type Zip3Sym3 (t :: [a6989586621679454917]) (t :: [b6989586621679454918]) (t :: [c6989586621679454919]) = Zip3 t t t
- data ZipWithSym0 (l :: TyFun (TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) -> Type))
- data ZipWithSym1 (l :: TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (l :: TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type))
- data ZipWithSym2 (l :: TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (l :: [a6989586621679454914]) (l :: TyFun [b6989586621679454915] [c6989586621679454916])
- type ZipWithSym3 (t :: TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (t :: [a6989586621679454914]) (t :: [b6989586621679454915]) = ZipWith t t t
- data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) -> Type))
- data ZipWith3Sym1 (l :: TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type))
- data ZipWith3Sym2 (l :: TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (l :: [a6989586621679454910]) (l :: TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type))
- data ZipWith3Sym3 (l :: TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (l :: [a6989586621679454910]) (l :: [b6989586621679454911]) (l :: TyFun [c6989586621679454912] [d6989586621679454913])
- type ZipWith3Sym4 (t :: TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (t :: [a6989586621679454910]) (t :: [b6989586621679454911]) (t :: [c6989586621679454912]) = ZipWith3 t t t t
- data UnzipSym0 (l :: TyFun [(a6989586621679454908, b6989586621679454909)] ([a6989586621679454908], [b6989586621679454909]))
- type UnzipSym1 (t :: [(a6989586621679454908, b6989586621679454909)]) = Unzip t
- data Unzip3Sym0 (l :: TyFun [(a6989586621679454905, b6989586621679454906, c6989586621679454907)] ([a6989586621679454905], [b6989586621679454906], [c6989586621679454907]))
- type Unzip3Sym1 (t :: [(a6989586621679454905, b6989586621679454906, c6989586621679454907)]) = Unzip3 t
- data Unzip4Sym0 (l :: TyFun [(a6989586621679454901, b6989586621679454902, c6989586621679454903, d6989586621679454904)] ([a6989586621679454901], [b6989586621679454902], [c6989586621679454903], [d6989586621679454904]))
- type Unzip4Sym1 (t :: [(a6989586621679454901, b6989586621679454902, c6989586621679454903, d6989586621679454904)]) = Unzip4 t
- data Unzip5Sym0 (l :: TyFun [(a6989586621679454896, b6989586621679454897, c6989586621679454898, d6989586621679454899, e6989586621679454900)] ([a6989586621679454896], [b6989586621679454897], [c6989586621679454898], [d6989586621679454899], [e6989586621679454900]))
- type Unzip5Sym1 (t :: [(a6989586621679454896, b6989586621679454897, c6989586621679454898, d6989586621679454899, e6989586621679454900)]) = Unzip5 t
- data Unzip6Sym0 (l :: TyFun [(a6989586621679454890, b6989586621679454891, c6989586621679454892, d6989586621679454893, e6989586621679454894, f6989586621679454895)] ([a6989586621679454890], [b6989586621679454891], [c6989586621679454892], [d6989586621679454893], [e6989586621679454894], [f6989586621679454895]))
- type Unzip6Sym1 (t :: [(a6989586621679454890, b6989586621679454891, c6989586621679454892, d6989586621679454893, e6989586621679454894, f6989586621679454895)]) = Unzip6 t
- data Unzip7Sym0 (l :: TyFun [(a6989586621679454883, b6989586621679454884, c6989586621679454885, d6989586621679454886, e6989586621679454887, f6989586621679454888, g6989586621679454889)] ([a6989586621679454883], [b6989586621679454884], [c6989586621679454885], [d6989586621679454886], [e6989586621679454887], [f6989586621679454888], [g6989586621679454889]))
- type Unzip7Sym1 (t :: [(a6989586621679454883, b6989586621679454884, c6989586621679454885, d6989586621679454886, e6989586621679454887, f6989586621679454888, g6989586621679454889)]) = Unzip7 t
- data NubSym0 (l :: TyFun [a6989586621679454842] [a6989586621679454842])
- type NubSym1 (t :: [a6989586621679454842]) = Nub t
- data DeleteSym0 (l :: TyFun a6989586621679454882 (TyFun [a6989586621679454882] [a6989586621679454882] -> Type))
- data DeleteSym1 (l :: a6989586621679454882) (l :: TyFun [a6989586621679454882] [a6989586621679454882])
- type DeleteSym2 (t :: a6989586621679454882) (t :: [a6989586621679454882]) = Delete t t
- data (:\\$) (l :: TyFun [a6989586621679454881] (TyFun [a6989586621679454881] [a6989586621679454881] -> Type))
- data (l :: [a6989586621679454881]) :\\$$ (l :: TyFun [a6989586621679454881] [a6989586621679454881])
- type (:\\$$$) (t :: [a6989586621679454881]) (t :: [a6989586621679454881]) = (:\\) t t
- data UnionSym0 (l :: TyFun [a6989586621679454838] (TyFun [a6989586621679454838] [a6989586621679454838] -> Type))
- data UnionSym1 (l :: [a6989586621679454838]) (l :: TyFun [a6989586621679454838] [a6989586621679454838])
- type UnionSym2 (t :: [a6989586621679454838]) (t :: [a6989586621679454838]) = Union t t
- data IntersectSym0 (l :: TyFun [a6989586621679454868] (TyFun [a6989586621679454868] [a6989586621679454868] -> Type))
- data IntersectSym1 (l :: [a6989586621679454868]) (l :: TyFun [a6989586621679454868] [a6989586621679454868])
- type IntersectSym2 (t :: [a6989586621679454868]) (t :: [a6989586621679454868]) = Intersect t t
- data InsertSym0 (l :: TyFun a6989586621679454855 (TyFun [a6989586621679454855] [a6989586621679454855] -> Type))
- data InsertSym1 (l :: a6989586621679454855) (l :: TyFun [a6989586621679454855] [a6989586621679454855])
- type InsertSym2 (t :: a6989586621679454855) (t :: [a6989586621679454855]) = Insert t t
- data SortSym0 (l :: TyFun [a6989586621679454854] [a6989586621679454854])
- type SortSym1 (t :: [a6989586621679454854]) = Sort t
- data NubBySym0 (l :: TyFun (TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (TyFun [a6989586621679454841] [a6989586621679454841] -> Type))
- data NubBySym1 (l :: TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454841] [a6989586621679454841])
- type NubBySym2 (t :: TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (t :: [a6989586621679454841]) = NubBy t t
- data DeleteBySym0 (l :: TyFun (TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (TyFun a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type) -> Type))
- data DeleteBySym1 (l :: TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (l :: TyFun a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type))
- data DeleteBySym2 (l :: TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (l :: a6989586621679454880) (l :: TyFun [a6989586621679454880] [a6989586621679454880])
- type DeleteBySym3 (t :: TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (t :: a6989586621679454880) (t :: [a6989586621679454880]) = DeleteBy t t t
- data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (TyFun [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type) -> Type))
- data DeleteFirstsBySym1 (l :: TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type))
- data DeleteFirstsBySym2 (l :: TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (l :: [a6989586621679454879]) (l :: TyFun [a6989586621679454879] [a6989586621679454879])
- type DeleteFirstsBySym3 (t :: TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (t :: [a6989586621679454879]) (t :: [a6989586621679454879]) = DeleteFirstsBy t t t
- data UnionBySym0 (l :: TyFun (TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (TyFun [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type) -> Type))
- data UnionBySym1 (l :: TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type))
- data UnionBySym2 (l :: TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (l :: [a6989586621679454839]) (l :: TyFun [a6989586621679454839] [a6989586621679454839])
- type UnionBySym3 (t :: TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (t :: [a6989586621679454839]) (t :: [a6989586621679454839]) = UnionBy t t t
- data IntersectBySym0 (l :: TyFun (TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (TyFun [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type) -> Type))
- data IntersectBySym1 (l :: TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type))
- data IntersectBySym2 (l :: TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (l :: [a6989586621679454867]) (l :: TyFun [a6989586621679454867] [a6989586621679454867])
- type IntersectBySym3 (t :: TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (t :: [a6989586621679454867]) (t :: [a6989586621679454867]) = IntersectBy t t t
- data GroupBySym0 (l :: TyFun (TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (TyFun [a6989586621679454853] [[a6989586621679454853]] -> Type))
- data GroupBySym1 (l :: TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454853] [[a6989586621679454853]])
- type GroupBySym2 (t :: TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (t :: [a6989586621679454853]) = GroupBy t t
- data SortBySym0 (l :: TyFun (TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (TyFun [a6989586621679454878] [a6989586621679454878] -> Type))
- data SortBySym1 (l :: TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679454878] [a6989586621679454878])
- type SortBySym2 (t :: TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (t :: [a6989586621679454878]) = SortBy t t
- data InsertBySym0 (l :: TyFun (TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (TyFun a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type) -> Type))
- data InsertBySym1 (l :: TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (l :: TyFun a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type))
- data InsertBySym2 (l :: TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (l :: a6989586621679454877) (l :: TyFun [a6989586621679454877] [a6989586621679454877])
- type InsertBySym3 (t :: TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (t :: a6989586621679454877) (t :: [a6989586621679454877]) = InsertBy t t t
- data MaximumBySym0 (l :: TyFun (TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (TyFun [a6989586621679454876] a6989586621679454876 -> Type))
- data MaximumBySym1 (l :: TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679454876] a6989586621679454876)
- type MaximumBySym2 (t :: TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (t :: [a6989586621679454876]) = MaximumBy t t
- data MinimumBySym0 (l :: TyFun (TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (TyFun [a6989586621679454875] a6989586621679454875 -> Type))
- data MinimumBySym1 (l :: TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679454875] a6989586621679454875)
- type MinimumBySym2 (t :: TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (t :: [a6989586621679454875]) = MinimumBy t t
- data GenericLengthSym0 (l :: TyFun [a6989586621679454837] i6989586621679454836)
- type GenericLengthSym1 (t :: [a6989586621679454837]) = GenericLength t
The singleton for lists
data family Sing (a :: k) Source #
The singleton kind-indexed data family.
Instances
| data Sing Bool Source # | |
| data Sing Ordering Source # | |
| data Sing * Source # | |
| data Sing Nat Source # | |
| data Sing Symbol Source # | |
| data Sing () Source # | |
| data Sing [a] Source # | |
| data Sing (Maybe a) Source # | |
| data Sing (NonEmpty a) Source # | |
| data Sing (Either a b) Source # | |
| data Sing (a, b) Source # | |
| data Sing ((~>) k1 k2) Source # | |
| data Sing (a, b, c) Source # | |
| data Sing (a, b, c, d) Source # | |
| data Sing (a, b, c, d, e) Source # | |
| data Sing (a, b, c, d, e, f) Source # | |
| data Sing (a, b, c, d, e, f, g) 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
(%:++) :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (:++$) t) t :: [a]) infixr 5 Source #
type family Length (a :: [a]) :: Nat where ... Source #
Equations
| Length '[] = FromInteger 0 | |
| Length ((:) _z_6989586621679455707 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply LengthSym0 xs) |
List transformations
sMap :: forall (t :: TyFun a b -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b]) Source #
type family Intersperse (a :: a) (a :: [a]) :: [a] where ... Source #
Equations
| Intersperse _z_6989586621679458730 '[] = '[] | |
| Intersperse sep ((:) x xs) = Apply (Apply (:$) x) (Apply (Apply PrependToAllSym0 sep) xs) |
sIntersperse :: forall (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a]) Source #
type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ... Source #
Equations
| Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) |
sIntercalate :: forall (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a]) Source #
sTranspose :: forall (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]]) Source #
type family Subsequences (a :: [a]) :: [[a]] where ... Source #
Equations
| Subsequences xs = Apply (Apply (:$) '[]) (Apply NonEmptySubsequencesSym0 xs) |
sSubsequences :: forall (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]]) Source #
type family Permutations (a :: [a]) :: [[a]] where ... Source #
sPermutations :: forall (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]]) Source #
Reducing lists (folds)
type family Foldl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #
sFoldl :: forall (t :: TyFun b (TyFun a b -> Type) -> Type) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source #
type family Foldl' (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #
sFoldl' :: forall (t :: TyFun b (TyFun a b -> Type) -> Type) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) Source #
sFoldl1 :: forall (t :: TyFun a (TyFun a a -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) Source #
sFoldl1' :: forall (t :: TyFun a (TyFun a a -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a) Source #
type family Foldr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #
sFoldr :: forall (t :: TyFun a (TyFun b b -> Type) -> Type) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source #
type family Foldr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ... Source #
Equations
| Foldr1 _z_6989586621679457954 '[x] = x | |
| Foldr1 f ((:) x ((:) wild_6989586621679455411 wild_6989586621679455413)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let6989586621679457962XsSym4 f x wild_6989586621679455411 wild_6989586621679455413)) | |
| Foldr1 _z_6989586621679457981 '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" |
sFoldr1 :: forall (t :: TyFun a (TyFun a a -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) Source #
Special folds
sConcatMap :: forall (t :: TyFun a [b] -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) Source #
sAny_ :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Any_Sym0 t) t :: Bool) Source #
sAll :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) Source #
type family Sum (a :: [a]) :: a where ... Source #
Equations
| Sum l = Apply (Apply (Let6989586621679455740Sum'Sym1 l) l) (FromInteger 0) |
type family Product (a :: [a]) :: a where ... Source #
Equations
| Product l = Apply (Apply (Let6989586621679455716ProdSym1 l) l) (FromInteger 1) |
Building lists
Scans
type family Scanl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ... Source #
sScanl :: forall (t :: TyFun b (TyFun a b -> Type) -> Type) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b]) Source #
sScanl1 :: forall (t :: TyFun a (TyFun a a -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a]) Source #
type family Scanr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ... Source #
sScanr :: forall (t :: TyFun a (TyFun b b -> Type) -> Type) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b]) Source #
type family Scanr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ... Source #
Equations
| Scanr1 _z_6989586621679457759 '[] = '[] | |
| Scanr1 _z_6989586621679457762 '[x] = Apply (Apply (:$) x) '[] | |
| Scanr1 f ((:) x ((:) wild_6989586621679455419 wild_6989586621679455421)) = Case_6989586621679457808 f x wild_6989586621679455419 wild_6989586621679455421 (Let6989586621679457789Scrutinee_6989586621679455417Sym4 f x wild_6989586621679455419 wild_6989586621679455421) |
sScanr1 :: forall (t :: TyFun a (TyFun a a -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a]) Source #
Accumulating maps
type family MapAccumL (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... Source #
sMapAccumL :: forall (t :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (t :: acc) (t :: [x]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (acc, [y])) Source #
type family MapAccumR (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... Source #
sMapAccumR :: forall (t :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (t :: acc) (t :: [x]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (acc, [y])) Source #
Cyclical lists
type family Replicate (a :: Nat) (a :: a) :: [a] where ... Source #
Equations
| Replicate n x = Case_6989586621679455700 n x (Let6989586621679455692Scrutinee_6989586621679455503Sym2 n x) |
sReplicate :: forall (t :: Nat) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a]) Source #
Unfolding
type family Unfoldr (a :: TyFun b (Maybe (a, b)) -> Type) (a :: b) :: [a] where ... Source #
Equations
| Unfoldr f b = Case_6989586621679457401 f b (Let6989586621679457393Scrutinee_6989586621679455423Sym2 f b) |
sUnfoldr :: forall (t :: TyFun b (Maybe (a, b)) -> Type) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a]) Source #
Sublists
Extracting sublists
sTake :: forall (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) Source #
sDrop :: forall (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) Source #
sSplitAt :: forall (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) Source #
sTakeWhile :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) Source #
sDropWhile :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) Source #
sDropWhileEnd :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a]) Source #
type family Span (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
| Span _z_6989586621679456031 '[] = Apply (Apply Tuple2Sym0 Let6989586621679456034XsSym0) Let6989586621679456034XsSym0 | |
| Span p ((:) x xs') = Case_6989586621679456064 p x xs' (Let6989586621679456051Scrutinee_6989586621679455483Sym3 p x xs') |
sSpan :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) Source #
type family Break (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
| Break _z_6989586621679455929 '[] = Apply (Apply Tuple2Sym0 Let6989586621679455932XsSym0) Let6989586621679455932XsSym0 | |
| Break p ((:) x xs') = Case_6989586621679455962 p x xs' (Let6989586621679455949Scrutinee_6989586621679455485Sym3 p x xs') |
sBreak :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) Source #
type family Group (a :: [a]) :: [[a]] where ... Source #
Equations
| Group xs = Apply (Apply GroupBySym0 (:==$)) xs |
Predicates
type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
Equations
| IsPrefixOf '[] '[] = TrueSym0 | |
| IsPrefixOf '[] ((:) _z_6989586621679457333 _z_6989586621679457336) = TrueSym0 | |
| IsPrefixOf ((:) _z_6989586621679457339 _z_6989586621679457342) '[] = FalseSym0 | |
| IsPrefixOf ((:) x xs) ((:) y ys) = Apply (Apply (:&&$) (Apply (Apply (:==$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) |
sIsPrefixOf :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) Source #
type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
Equations
| IsSuffixOf x y = Apply (Apply IsPrefixOfSym0 (Apply ReverseSym0 x)) (Apply ReverseSym0 y) |
sIsSuffixOf :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) Source #
sIsInfixOf :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool) Source #
Searching lists
Searching by equality
sElem :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) Source #
sNotElem :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) Source #
type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... Source #
Equations
| Lookup _key '[] = NothingSym0 | |
| Lookup key ((:) '(x, y) xys) = Case_6989586621679455844 key x y xys (Let6989586621679455825Scrutinee_6989586621679455499Sym4 key x y xys) |
sLookup :: forall (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b) Source #
Searching with a predicate
type family Find (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe a where ... Source #
Equations
| Find p a_6989586621679456314 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FilterSym0 p)) a_6989586621679456314 |
sFind :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a) Source #
sFilter :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) Source #
sPartition :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) Source #
Indexing lists
(%:!!) :: forall (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (:!!$) t) t :: a) Source #
sElemIndex :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat) Source #
type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ... Source #
Equations
| ElemIndices x a_6989586621679457216 = Apply (Apply FindIndicesSym0 (Apply (:==$) x)) a_6989586621679457216 |
sElemIndices :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat]) Source #
type family FindIndex (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe Nat where ... Source #
Equations
| FindIndex p a_6989586621679457229 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679457229 |
sFindIndex :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat) Source #
sFindIndices :: forall (t :: TyFun a Bool -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat]) Source #
Zipping and unzipping lists
sZip :: forall (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)]) Source #
type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ... Source #
Equations
| Zip3 ((:) a as) ((:) b bs) ((:) c cs) = Apply (Apply (:$) (Apply (Apply (Apply Tuple3Sym0 a) b) c)) (Apply (Apply (Apply Zip3Sym0 as) bs) cs) | |
| Zip3 '[] '[] '[] = '[] | |
| Zip3 '[] '[] ((:) _z_6989586621679457065 _z_6989586621679457068) = '[] | |
| Zip3 '[] ((:) _z_6989586621679457071 _z_6989586621679457074) '[] = '[] | |
| Zip3 '[] ((:) _z_6989586621679457077 _z_6989586621679457080) ((:) _z_6989586621679457083 _z_6989586621679457086) = '[] | |
| Zip3 ((:) _z_6989586621679457089 _z_6989586621679457092) '[] '[] = '[] | |
| Zip3 ((:) _z_6989586621679457095 _z_6989586621679457098) '[] ((:) _z_6989586621679457101 _z_6989586621679457104) = '[] | |
| Zip3 ((:) _z_6989586621679457107 _z_6989586621679457110) ((:) _z_6989586621679457113 _z_6989586621679457116) '[] = '[] |
sZip3 :: forall (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)]) Source #
type family ZipWith (a :: TyFun a (TyFun b c -> Type) -> Type) (a :: [a]) (a :: [b]) :: [c] where ... Source #
Equations
| ZipWith f ((:) x xs) ((:) y ys) = Apply (Apply (:$) (Apply (Apply f x) y)) (Apply (Apply (Apply ZipWithSym0 f) xs) ys) | |
| ZipWith _z_6989586621679457023 '[] '[] = '[] | |
| ZipWith _z_6989586621679457026 ((:) _z_6989586621679457029 _z_6989586621679457032) '[] = '[] | |
| ZipWith _z_6989586621679457035 '[] ((:) _z_6989586621679457038 _z_6989586621679457041) = '[] |
sZipWith :: forall (t :: TyFun a (TyFun b c -> Type) -> Type) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c]) Source #
type family ZipWith3 (a :: TyFun a (TyFun b (TyFun c d -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ... Source #
Equations
| ZipWith3 z ((:) a as) ((:) b bs) ((:) c cs) = Apply (Apply (:$) (Apply (Apply (Apply z a) b) c)) (Apply (Apply (Apply (Apply ZipWith3Sym0 z) as) bs) cs) | |
| ZipWith3 _z_6989586621679456928 '[] '[] '[] = '[] | |
| ZipWith3 _z_6989586621679456931 '[] '[] ((:) _z_6989586621679456934 _z_6989586621679456937) = '[] | |
| ZipWith3 _z_6989586621679456940 '[] ((:) _z_6989586621679456943 _z_6989586621679456946) '[] = '[] | |
| ZipWith3 _z_6989586621679456949 '[] ((:) _z_6989586621679456952 _z_6989586621679456955) ((:) _z_6989586621679456958 _z_6989586621679456961) = '[] | |
| ZipWith3 _z_6989586621679456964 ((:) _z_6989586621679456967 _z_6989586621679456970) '[] '[] = '[] | |
| ZipWith3 _z_6989586621679456973 ((:) _z_6989586621679456976 _z_6989586621679456979) '[] ((:) _z_6989586621679456982 _z_6989586621679456985) = '[] | |
| ZipWith3 _z_6989586621679456988 ((:) _z_6989586621679456991 _z_6989586621679456994) ((:) _z_6989586621679456997 _z_6989586621679457000) '[] = '[] |
sZipWith3 :: forall (t :: TyFun a (TyFun b (TyFun c d -> Type) -> Type) -> Type) (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d]) Source #
sUnzip3 :: forall (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c])) Source #
sUnzip4 :: forall (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d])) Source #
sUnzip5 :: forall (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e])) Source #
sUnzip6 :: forall (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f])) Source #
type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... Source #
sUnzip7 :: forall (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g])) Source #
Special lists
"Set" operations
sDelete :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a]) Source #
(%:\\) :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (:\\$) t) t :: [a]) infix 5 Source #
sUnion :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a]) Source #
sIntersect :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a]) Source #
Ordered lists
type family Insert (a :: a) (a :: [a]) :: [a] where ... Source #
Equations
| Insert e ls = Apply (Apply (Apply InsertBySym0 CompareSym0) e) ls |
sInsert :: forall (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a]) Source #
type family Sort (a :: [a]) :: [a] where ... Source #
Equations
| Sort a_6989586621679456550 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679456550 |
Generalized functions
The "By" operations
User-supplied equality (replacing an Eq context)
The predicate is assumed to define an equivalence.
type family NubBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [a] where ... Source #
sNubBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a]) Source #
type family DeleteBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... Source #
sDeleteBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a]) Source #
type family DeleteFirstsBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... Source #
Equations
| DeleteFirstsBy eq a_6989586621679456619 a_6989586621679456621 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679456619) a_6989586621679456621 |
sDeleteFirstsBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a]) Source #
type family UnionBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... Source #
sUnionBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a]) Source #
type family IntersectBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... Source #
Equations
| IntersectBy _z_6989586621679456333 '[] '[] = '[] | |
| IntersectBy _z_6989586621679456336 '[] ((:) _z_6989586621679456339 _z_6989586621679456342) = '[] | |
| IntersectBy _z_6989586621679456345 ((:) _z_6989586621679456348 _z_6989586621679456351) '[] = '[] | |
| IntersectBy eq ((:) wild_6989586621679455469 wild_6989586621679455471) ((:) wild_6989586621679455473 wild_6989586621679455475) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679456410Sym0 eq) wild_6989586621679455469) wild_6989586621679455471) wild_6989586621679455473) wild_6989586621679455475)) (Let6989586621679456359XsSym5 eq wild_6989586621679455469 wild_6989586621679455471 wild_6989586621679455473 wild_6989586621679455475) |
sIntersectBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a]) Source #
type family GroupBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [[a]] where ... Source #
sGroupBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (t :: [a]). 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 :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: [a] where ... Source #
sSortBy :: forall (t :: TyFun a (TyFun a Ordering -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a]) Source #
type family InsertBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... Source #
sInsertBy :: forall (t :: TyFun a (TyFun a Ordering -> Type) -> Type) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a]) Source #
type family MaximumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... Source #
Equations
| MaximumBy _z_6989586621679458008 '[] = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" | |
| MaximumBy cmp ((:) wild_6989586621679455455 wild_6989586621679455457) = Apply (Apply Foldl1Sym0 (Let6989586621679458027MaxBySym3 cmp wild_6989586621679455455 wild_6989586621679455457)) (Let6989586621679458014XsSym3 cmp wild_6989586621679455455 wild_6989586621679455457) |
sMaximumBy :: forall (t :: TyFun a (TyFun a Ordering -> Type) -> Type) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) Source #
type family MinimumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... Source #
Equations
| MinimumBy _z_6989586621679458095 '[] = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" | |
| MinimumBy cmp ((:) wild_6989586621679455461 wild_6989586621679455463) = Apply (Apply Foldl1Sym0 (Let6989586621679458114MinBySym3 cmp wild_6989586621679455461 wild_6989586621679455463)) (Let6989586621679458101XsSym3 cmp wild_6989586621679455461 wild_6989586621679455463) |
sMinimumBy :: forall (t :: TyFun a (TyFun a Ordering -> Type) -> Type) (t :: [a]). 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 :: [a]) :: i where ... Source #
Equations
| GenericLength '[] = FromInteger 0 | |
| GenericLength ((:) _z_6989586621679455554 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
sGenericLength :: forall (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i) Source #
Defunctionalization symbols
data (:$) (l :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type)) Source #
data (l :: a3530822107858468865) :$$ (l :: TyFun [a3530822107858468865] [a3530822107858468865]) Source #
data (l :: [a6989586621679277916]) :++$$ (l :: TyFun [a6989586621679277916] [a6989586621679277916]) Source #
data (:++$) (l :: TyFun [a6989586621679277916] (TyFun [a6989586621679277916] [a6989586621679277916] -> Type)) Source #
Instances
data LengthSym0 (l :: TyFun [a6989586621679454846] Nat) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454846] Nat -> *) (LengthSym0 a6989586621679454846) Source # | |
| type Apply [a] Nat (LengthSym0 a) l Source # | |
type LengthSym1 (t :: [a6989586621679454846]) = Length t Source #
data MapSym0 (l :: TyFun (TyFun a6989586621679277917 b6989586621679277918 -> Type) (TyFun [a6989586621679277917] [b6989586621679277918] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679277917 b6989586621679277918 -> Type) (TyFun [a6989586621679277917] [b6989586621679277918] -> Type) -> *) (MapSym0 a6989586621679277917 b6989586621679277918) Source # | |
| type Apply (TyFun a6989586621679277917 b6989586621679277918 -> Type) (TyFun [a6989586621679277917] [b6989586621679277918] -> Type) (MapSym0 a6989586621679277917 b6989586621679277918) l Source # | |
data MapSym1 (l :: TyFun a6989586621679277917 b6989586621679277918 -> Type) (l :: TyFun [a6989586621679277917] [b6989586621679277918]) Source #
type MapSym2 (t :: TyFun a6989586621679277917 b6989586621679277918 -> Type) (t :: [a6989586621679277917]) = Map t t Source #
data ReverseSym0 (l :: TyFun [a6989586621679454958] [a6989586621679454958]) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454958] [a6989586621679454958] -> *) (ReverseSym0 a6989586621679454958) Source # | |
| type Apply [a] [a] (ReverseSym0 a) l Source # | |
type ReverseSym1 (t :: [a6989586621679454958]) = Reverse t Source #
data IntersperseSym0 (l :: TyFun a6989586621679454957 (TyFun [a6989586621679454957] [a6989586621679454957] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun a6989586621679454957 (TyFun [a6989586621679454957] [a6989586621679454957] -> Type) -> *) (IntersperseSym0 a6989586621679454957) Source # | |
| type Apply a6989586621679454957 (TyFun [a6989586621679454957] [a6989586621679454957] -> Type) (IntersperseSym0 a6989586621679454957) l Source # | |
data IntersperseSym1 (l :: a6989586621679454957) (l :: TyFun [a6989586621679454957] [a6989586621679454957]) Source #
Instances
| SuppressUnusedWarnings (a6989586621679454957 -> TyFun [a6989586621679454957] [a6989586621679454957] -> *) (IntersperseSym1 a6989586621679454957) Source # | |
| type Apply [a] [a] (IntersperseSym1 a l1) l2 Source # | |
type IntersperseSym2 (t :: a6989586621679454957) (t :: [a6989586621679454957]) = Intersperse t t Source #
data IntercalateSym0 (l :: TyFun [a6989586621679454956] (TyFun [[a6989586621679454956]] [a6989586621679454956] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454956] (TyFun [[a6989586621679454956]] [a6989586621679454956] -> Type) -> *) (IntercalateSym0 a6989586621679454956) Source # | |
| type Apply [a6989586621679454956] (TyFun [[a6989586621679454956]] [a6989586621679454956] -> Type) (IntercalateSym0 a6989586621679454956) l Source # | |
data IntercalateSym1 (l :: [a6989586621679454956]) (l :: TyFun [[a6989586621679454956]] [a6989586621679454956]) Source #
Instances
| SuppressUnusedWarnings ([a6989586621679454956] -> TyFun [[a6989586621679454956]] [a6989586621679454956] -> *) (IntercalateSym1 a6989586621679454956) Source # | |
| type Apply [[a]] [a] (IntercalateSym1 a l1) l2 Source # | |
type IntercalateSym2 (t :: [a6989586621679454956]) (t :: [[a6989586621679454956]]) = Intercalate t t Source #
data TransposeSym0 (l :: TyFun [[a6989586621679454844]] [[a6989586621679454844]]) Source #
Instances
| SuppressUnusedWarnings (TyFun [[a6989586621679454844]] [[a6989586621679454844]] -> *) (TransposeSym0 a6989586621679454844) Source # | |
| type Apply [[a]] [[a]] (TransposeSym0 a) l Source # | |
type TransposeSym1 (t :: [[a6989586621679454844]]) = Transpose t Source #
data SubsequencesSym0 (l :: TyFun [a6989586621679454955] [[a6989586621679454955]]) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454955] [[a6989586621679454955]] -> *) (SubsequencesSym0 a6989586621679454955) Source # | |
| type Apply [a] [[a]] (SubsequencesSym0 a) l Source # | |
type SubsequencesSym1 (t :: [a6989586621679454955]) = Subsequences t Source #
data PermutationsSym0 (l :: TyFun [a6989586621679454952] [[a6989586621679454952]]) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454952] [[a6989586621679454952]] -> *) (PermutationsSym0 a6989586621679454952) Source # | |
| type Apply [a] [[a]] (PermutationsSym0 a) l Source # | |
type PermutationsSym1 (t :: [a6989586621679454952]) = Permutations t Source #
data FoldlSym0 (l :: TyFun (TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (TyFun b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (TyFun b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679240791 b6989586621679240792) Source # | |
| type Apply (TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (TyFun b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type) -> Type) (FoldlSym0 a6989586621679240791 b6989586621679240792) l Source # | |
data FoldlSym1 (l :: TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (l :: TyFun b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) -> TyFun b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type) -> *) (FoldlSym1 a6989586621679240791 b6989586621679240792) Source # | |
| type Apply b6989586621679240792 (TyFun [a6989586621679240791] b6989586621679240792 -> Type) (FoldlSym1 a6989586621679240791 b6989586621679240792 l1) l2 Source # | |
data FoldlSym2 (l :: TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (l :: b6989586621679240792) (l :: TyFun [a6989586621679240791] b6989586621679240792) Source #
Instances
| SuppressUnusedWarnings ((TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) -> b6989586621679240792 -> TyFun [a6989586621679240791] b6989586621679240792 -> *) (FoldlSym2 a6989586621679240791 b6989586621679240792) Source # | |
| type Apply [a] b (FoldlSym2 a b l1 l2) l3 Source # | |
type FoldlSym3 (t :: TyFun b6989586621679240792 (TyFun a6989586621679240791 b6989586621679240792 -> Type) -> Type) (t :: b6989586621679240792) (t :: [a6989586621679240791]) = Foldl t t t Source #
data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) -> Type) -> *) (Foldl'Sym0 a6989586621679454950 b6989586621679454951) Source # | |
| type Apply (TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) -> Type) (Foldl'Sym0 a6989586621679454950 b6989586621679454951) l Source # | |
data Foldl'Sym1 (l :: TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (l :: TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) -> TyFun b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) -> *) (Foldl'Sym1 a6989586621679454950 b6989586621679454951) Source # | |
| type Apply b6989586621679454951 (TyFun [a6989586621679454950] b6989586621679454951 -> Type) (Foldl'Sym1 a6989586621679454950 b6989586621679454951 l1) l2 Source # | |
data Foldl'Sym2 (l :: TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (l :: b6989586621679454951) (l :: TyFun [a6989586621679454950] b6989586621679454951) Source #
Instances
| SuppressUnusedWarnings ((TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) -> b6989586621679454951 -> TyFun [a6989586621679454950] b6989586621679454951 -> *) (Foldl'Sym2 a6989586621679454950 b6989586621679454951) Source # | |
| type Apply [a] b (Foldl'Sym2 a b l1 l2) l3 Source # | |
type Foldl'Sym3 (t :: TyFun b6989586621679454951 (TyFun a6989586621679454950 b6989586621679454951 -> Type) -> Type) (t :: b6989586621679454951) (t :: [a6989586621679454950]) = Foldl' t t t Source #
data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (TyFun [a6989586621679454949] a6989586621679454949 -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (TyFun [a6989586621679454949] a6989586621679454949 -> Type) -> *) (Foldl1Sym0 a6989586621679454949) Source # | |
| type Apply (TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (TyFun [a6989586621679454949] a6989586621679454949 -> Type) (Foldl1Sym0 a6989586621679454949) l Source # | |
data Foldl1Sym1 (l :: TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (l :: TyFun [a6989586621679454949] a6989586621679454949) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) -> TyFun [a6989586621679454949] a6989586621679454949 -> *) (Foldl1Sym1 a6989586621679454949) Source # | |
| type Apply [a] a (Foldl1Sym1 a l1) l2 Source # | |
type Foldl1Sym2 (t :: TyFun a6989586621679454949 (TyFun a6989586621679454949 a6989586621679454949 -> Type) -> Type) (t :: [a6989586621679454949]) = Foldl1 t t Source #
data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (TyFun [a6989586621679454948] a6989586621679454948 -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (TyFun [a6989586621679454948] a6989586621679454948 -> Type) -> *) (Foldl1'Sym0 a6989586621679454948) Source # | |
| type Apply (TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (TyFun [a6989586621679454948] a6989586621679454948 -> Type) (Foldl1'Sym0 a6989586621679454948) l Source # | |
data Foldl1'Sym1 (l :: TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (l :: TyFun [a6989586621679454948] a6989586621679454948) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) -> TyFun [a6989586621679454948] a6989586621679454948 -> *) (Foldl1'Sym1 a6989586621679454948) Source # | |
| type Apply [a] a (Foldl1'Sym1 a l1) l2 Source # | |
type Foldl1'Sym2 (t :: TyFun a6989586621679454948 (TyFun a6989586621679454948 a6989586621679454948 -> Type) -> Type) (t :: [a6989586621679454948]) = Foldl1' t t Source #
data FoldrSym0 (l :: TyFun (TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) -> Type) -> *) (FoldrSym0 a6989586621679277919 b6989586621679277920) Source # | |
| type Apply (TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) -> Type) (FoldrSym0 a6989586621679277919 b6989586621679277920) l Source # | |
data FoldrSym1 (l :: TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (l :: TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) -> TyFun b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) -> *) (FoldrSym1 a6989586621679277919 b6989586621679277920) Source # | |
| type Apply b6989586621679277920 (TyFun [a6989586621679277919] b6989586621679277920 -> Type) (FoldrSym1 a6989586621679277919 b6989586621679277920 l1) l2 Source # | |
data FoldrSym2 (l :: TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (l :: b6989586621679277920) (l :: TyFun [a6989586621679277919] b6989586621679277920) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) -> b6989586621679277920 -> TyFun [a6989586621679277919] b6989586621679277920 -> *) (FoldrSym2 a6989586621679277919 b6989586621679277920) Source # | |
| type Apply [a] b (FoldrSym2 a b l1 l2) l3 Source # | |
type FoldrSym3 (t :: TyFun a6989586621679277919 (TyFun b6989586621679277920 b6989586621679277920 -> Type) -> Type) (t :: b6989586621679277920) (t :: [a6989586621679277919]) = Foldr t t t Source #
data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (TyFun [a6989586621679454947] a6989586621679454947 -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (TyFun [a6989586621679454947] a6989586621679454947 -> Type) -> *) (Foldr1Sym0 a6989586621679454947) Source # | |
| type Apply (TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (TyFun [a6989586621679454947] a6989586621679454947 -> Type) (Foldr1Sym0 a6989586621679454947) l Source # | |
data Foldr1Sym1 (l :: TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (l :: TyFun [a6989586621679454947] a6989586621679454947) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) -> TyFun [a6989586621679454947] a6989586621679454947 -> *) (Foldr1Sym1 a6989586621679454947) Source # | |
| type Apply [a] a (Foldr1Sym1 a l1) l2 Source # | |
type Foldr1Sym2 (t :: TyFun a6989586621679454947 (TyFun a6989586621679454947 a6989586621679454947 -> Type) -> Type) (t :: [a6989586621679454947]) = Foldr1 t t Source #
data ConcatSym0 (l :: TyFun [[a6989586621679454946]] [a6989586621679454946]) Source #
Instances
| SuppressUnusedWarnings (TyFun [[a6989586621679454946]] [a6989586621679454946] -> *) (ConcatSym0 a6989586621679454946) Source # | |
| type Apply [[a]] [a] (ConcatSym0 a) l Source # | |
type ConcatSym1 (t :: [[a6989586621679454946]]) = Concat t Source #
data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679454944 [b6989586621679454945] -> Type) (TyFun [a6989586621679454944] [b6989586621679454945] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454944 [b6989586621679454945] -> Type) (TyFun [a6989586621679454944] [b6989586621679454945] -> Type) -> *) (ConcatMapSym0 a6989586621679454944 b6989586621679454945) Source # | |
| type Apply (TyFun a6989586621679454944 [b6989586621679454945] -> Type) (TyFun [a6989586621679454944] [b6989586621679454945] -> Type) (ConcatMapSym0 a6989586621679454944 b6989586621679454945) l Source # | |
data ConcatMapSym1 (l :: TyFun a6989586621679454944 [b6989586621679454945] -> Type) (l :: TyFun [a6989586621679454944] [b6989586621679454945]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454944 [b6989586621679454945] -> Type) -> TyFun [a6989586621679454944] [b6989586621679454945] -> *) (ConcatMapSym1 a6989586621679454944 b6989586621679454945) Source # | |
| type Apply [a] [b] (ConcatMapSym1 a b l1) l2 Source # | |
type ConcatMapSym2 (t :: TyFun a6989586621679454944 [b6989586621679454945] -> Type) (t :: [a6989586621679454944]) = ConcatMap t t Source #
data Any_Sym0 (l :: TyFun (TyFun a6989586621679444727 Bool -> Type) (TyFun [a6989586621679444727] Bool -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679444727 Bool -> Type) (TyFun [a6989586621679444727] Bool -> Type) -> *) (Any_Sym0 a6989586621679444727) Source # | |
| type Apply (TyFun a6989586621679444727 Bool -> Type) (TyFun [a6989586621679444727] Bool -> Type) (Any_Sym0 a6989586621679444727) l Source # | |
data Any_Sym1 (l :: TyFun a6989586621679444727 Bool -> Type) (l :: TyFun [a6989586621679444727] Bool) Source #
type Any_Sym2 (t :: TyFun a6989586621679444727 Bool -> Type) (t :: [a6989586621679444727]) = Any_ t t Source #
data AllSym0 (l :: TyFun (TyFun a6989586621679454943 Bool -> Type) (TyFun [a6989586621679454943] Bool -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454943 Bool -> Type) (TyFun [a6989586621679454943] Bool -> Type) -> *) (AllSym0 a6989586621679454943) Source # | |
| type Apply (TyFun a6989586621679454943 Bool -> Type) (TyFun [a6989586621679454943] Bool -> Type) (AllSym0 a6989586621679454943) l Source # | |
data AllSym1 (l :: TyFun a6989586621679454943 Bool -> Type) (l :: TyFun [a6989586621679454943] Bool) Source #
type AllSym2 (t :: TyFun a6989586621679454943 Bool -> Type) (t :: [a6989586621679454943]) = All t t Source #
data ProductSym0 (l :: TyFun [a6989586621679454847] a6989586621679454847) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454847] a6989586621679454847 -> *) (ProductSym0 a6989586621679454847) Source # | |
| type Apply [a] a (ProductSym0 a) l Source # | |
type ProductSym1 (t :: [a6989586621679454847]) = Product t Source #
data MaximumSym0 (l :: TyFun [a6989586621679454857] a6989586621679454857) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454857] a6989586621679454857 -> *) (MaximumSym0 a6989586621679454857) Source # | |
| type Apply [a] a (MaximumSym0 a) l Source # | |
type MaximumSym1 (t :: [a6989586621679454857]) = Maximum t Source #
data MinimumSym0 (l :: TyFun [a6989586621679454856] a6989586621679454856) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454856] a6989586621679454856 -> *) (MinimumSym0 a6989586621679454856) Source # | |
| type Apply [a] a (MinimumSym0 a) l Source # | |
type MinimumSym1 (t :: [a6989586621679454856]) = Minimum t Source #
data ScanlSym0 (l :: TyFun (TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) -> Type) -> *) (ScanlSym0 a6989586621679454942 b6989586621679454941) Source # | |
| type Apply (TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) -> Type) (ScanlSym0 a6989586621679454942 b6989586621679454941) l Source # | |
data ScanlSym1 (l :: TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (l :: TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) -> TyFun b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) -> *) (ScanlSym1 a6989586621679454942 b6989586621679454941) Source # | |
| type Apply b6989586621679454941 (TyFun [a6989586621679454942] [b6989586621679454941] -> Type) (ScanlSym1 a6989586621679454942 b6989586621679454941 l1) l2 Source # | |
data ScanlSym2 (l :: TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (l :: b6989586621679454941) (l :: TyFun [a6989586621679454942] [b6989586621679454941]) Source #
Instances
| SuppressUnusedWarnings ((TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) -> b6989586621679454941 -> TyFun [a6989586621679454942] [b6989586621679454941] -> *) (ScanlSym2 a6989586621679454942 b6989586621679454941) Source # | |
| type Apply [a] [b] (ScanlSym2 a b l1 l2) l3 Source # | |
type ScanlSym3 (t :: TyFun b6989586621679454941 (TyFun a6989586621679454942 b6989586621679454941 -> Type) -> Type) (t :: b6989586621679454941) (t :: [a6989586621679454942]) = Scanl t t t Source #
data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (TyFun [a6989586621679454940] [a6989586621679454940] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (TyFun [a6989586621679454940] [a6989586621679454940] -> Type) -> *) (Scanl1Sym0 a6989586621679454940) Source # | |
| type Apply (TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (TyFun [a6989586621679454940] [a6989586621679454940] -> Type) (Scanl1Sym0 a6989586621679454940) l Source # | |
data Scanl1Sym1 (l :: TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (l :: TyFun [a6989586621679454940] [a6989586621679454940]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) -> TyFun [a6989586621679454940] [a6989586621679454940] -> *) (Scanl1Sym1 a6989586621679454940) Source # | |
| type Apply [a] [a] (Scanl1Sym1 a l1) l2 Source # | |
type Scanl1Sym2 (t :: TyFun a6989586621679454940 (TyFun a6989586621679454940 a6989586621679454940 -> Type) -> Type) (t :: [a6989586621679454940]) = Scanl1 t t Source #
data ScanrSym0 (l :: TyFun (TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) -> Type) -> *) (ScanrSym0 a6989586621679454938 b6989586621679454939) Source # | |
| type Apply (TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) -> Type) (ScanrSym0 a6989586621679454938 b6989586621679454939) l Source # | |
data ScanrSym1 (l :: TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (l :: TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) -> TyFun b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) -> *) (ScanrSym1 a6989586621679454938 b6989586621679454939) Source # | |
| type Apply b6989586621679454939 (TyFun [a6989586621679454938] [b6989586621679454939] -> Type) (ScanrSym1 a6989586621679454938 b6989586621679454939 l1) l2 Source # | |
data ScanrSym2 (l :: TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (l :: b6989586621679454939) (l :: TyFun [a6989586621679454938] [b6989586621679454939]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) -> b6989586621679454939 -> TyFun [a6989586621679454938] [b6989586621679454939] -> *) (ScanrSym2 a6989586621679454938 b6989586621679454939) Source # | |
| type Apply [a] [b] (ScanrSym2 a b l1 l2) l3 Source # | |
type ScanrSym3 (t :: TyFun a6989586621679454938 (TyFun b6989586621679454939 b6989586621679454939 -> Type) -> Type) (t :: b6989586621679454939) (t :: [a6989586621679454938]) = Scanr t t t Source #
data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (TyFun [a6989586621679454937] [a6989586621679454937] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (TyFun [a6989586621679454937] [a6989586621679454937] -> Type) -> *) (Scanr1Sym0 a6989586621679454937) Source # | |
| type Apply (TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (TyFun [a6989586621679454937] [a6989586621679454937] -> Type) (Scanr1Sym0 a6989586621679454937) l Source # | |
data Scanr1Sym1 (l :: TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (l :: TyFun [a6989586621679454937] [a6989586621679454937]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) -> TyFun [a6989586621679454937] [a6989586621679454937] -> *) (Scanr1Sym1 a6989586621679454937) Source # | |
| type Apply [a] [a] (Scanr1Sym1 a l1) l2 Source # | |
type Scanr1Sym2 (t :: TyFun a6989586621679454937 (TyFun a6989586621679454937 a6989586621679454937 -> Type) -> Type) (t :: [a6989586621679454937]) = Scanr1 t t Source #
data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) -> Type) -> *) (MapAccumLSym0 x6989586621679454935 acc6989586621679454934 y6989586621679454936) Source # | |
| type Apply (TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) -> Type) (MapAccumLSym0 x6989586621679454935 acc6989586621679454934 y6989586621679454936) l Source # | |
data MapAccumLSym1 (l :: TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (l :: TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) -> TyFun acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) -> *) (MapAccumLSym1 x6989586621679454935 acc6989586621679454934 y6989586621679454936) Source # | |
| type Apply acc6989586621679454934 (TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> Type) (MapAccumLSym1 x6989586621679454935 acc6989586621679454934 y6989586621679454936 l1) l2 Source # | |
data MapAccumLSym2 (l :: TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (l :: acc6989586621679454934) (l :: TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936])) Source #
Instances
| SuppressUnusedWarnings ((TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) -> acc6989586621679454934 -> TyFun [x6989586621679454935] (acc6989586621679454934, [y6989586621679454936]) -> *) (MapAccumLSym2 x6989586621679454935 acc6989586621679454934 y6989586621679454936) Source # | |
| type Apply [x] (acc, [y]) (MapAccumLSym2 x acc y l1 l2) l3 Source # | |
type MapAccumLSym3 (t :: TyFun acc6989586621679454934 (TyFun x6989586621679454935 (acc6989586621679454934, y6989586621679454936) -> Type) -> Type) (t :: acc6989586621679454934) (t :: [x6989586621679454935]) = MapAccumL t t t Source #
data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) -> Type) -> *) (MapAccumRSym0 x6989586621679454932 acc6989586621679454931 y6989586621679454933) Source # | |
| type Apply (TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) -> Type) (MapAccumRSym0 x6989586621679454932 acc6989586621679454931 y6989586621679454933) l Source # | |
data MapAccumRSym1 (l :: TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (l :: TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) -> TyFun acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) -> *) (MapAccumRSym1 x6989586621679454932 acc6989586621679454931 y6989586621679454933) Source # | |
| type Apply acc6989586621679454931 (TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> Type) (MapAccumRSym1 x6989586621679454932 acc6989586621679454931 y6989586621679454933 l1) l2 Source # | |
data MapAccumRSym2 (l :: TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (l :: acc6989586621679454931) (l :: TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933])) Source #
Instances
| SuppressUnusedWarnings ((TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) -> acc6989586621679454931 -> TyFun [x6989586621679454932] (acc6989586621679454931, [y6989586621679454933]) -> *) (MapAccumRSym2 x6989586621679454932 acc6989586621679454931 y6989586621679454933) Source # | |
| type Apply [x] (acc, [y]) (MapAccumRSym2 x acc y l1 l2) l3 Source # | |
type MapAccumRSym3 (t :: TyFun acc6989586621679454931 (TyFun x6989586621679454932 (acc6989586621679454931, y6989586621679454933) -> Type) -> Type) (t :: acc6989586621679454931) (t :: [x6989586621679454932]) = MapAccumR t t t Source #
data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679454845 [a6989586621679454845] -> Type)) Source #
data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679454845 [a6989586621679454845]) Source #
Instances
| SuppressUnusedWarnings (Nat -> TyFun a6989586621679454845 [a6989586621679454845] -> *) (ReplicateSym1 a6989586621679454845) Source # | |
| type Apply a [a] (ReplicateSym1 a l1) l2 Source # | |
type ReplicateSym2 (t :: Nat) (t :: a6989586621679454845) = Replicate t t Source #
data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (TyFun b6989586621679454929 [a6989586621679454930] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (TyFun b6989586621679454929 [a6989586621679454930] -> Type) -> *) (UnfoldrSym0 b6989586621679454929 a6989586621679454930) Source # | |
| type Apply (TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (TyFun b6989586621679454929 [a6989586621679454930] -> Type) (UnfoldrSym0 b6989586621679454929 a6989586621679454930) l Source # | |
data UnfoldrSym1 (l :: TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (l :: TyFun b6989586621679454929 [a6989586621679454930]) Source #
Instances
| SuppressUnusedWarnings ((TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) -> TyFun b6989586621679454929 [a6989586621679454930] -> *) (UnfoldrSym1 b6989586621679454929 a6989586621679454930) Source # | |
| type Apply b [a] (UnfoldrSym1 b a l1) l2 Source # | |
type UnfoldrSym2 (t :: TyFun b6989586621679454929 (Maybe (a6989586621679454930, b6989586621679454929)) -> Type) (t :: b6989586621679454929) = Unfoldr t t Source #
data TakeSym0 (l :: TyFun Nat (TyFun [a6989586621679454861] [a6989586621679454861] -> Type)) Source #
data DropSym0 (l :: TyFun Nat (TyFun [a6989586621679454860] [a6989586621679454860] -> Type)) Source #
data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679454859] ([a6989586621679454859], [a6989586621679454859]) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679454859] ([a6989586621679454859], [a6989586621679454859]) -> Type) -> *) (SplitAtSym0 a6989586621679454859) Source # | |
| type Apply Nat (TyFun [a6989586621679454859] ([a6989586621679454859], [a6989586621679454859]) -> Type) (SplitAtSym0 a6989586621679454859) l Source # | |
data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679454859] ([a6989586621679454859], [a6989586621679454859])) Source #
Instances
| SuppressUnusedWarnings (Nat -> TyFun [a6989586621679454859] ([a6989586621679454859], [a6989586621679454859]) -> *) (SplitAtSym1 a6989586621679454859) Source # | |
| type Apply [a] ([a], [a]) (SplitAtSym1 a l1) l2 Source # | |
type SplitAtSym2 (t :: Nat) (t :: [a6989586621679454859]) = SplitAt t t Source #
data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679454866 Bool -> Type) (TyFun [a6989586621679454866] [a6989586621679454866] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454866 Bool -> Type) (TyFun [a6989586621679454866] [a6989586621679454866] -> Type) -> *) (TakeWhileSym0 a6989586621679454866) Source # | |
| type Apply (TyFun a6989586621679454866 Bool -> Type) (TyFun [a6989586621679454866] [a6989586621679454866] -> Type) (TakeWhileSym0 a6989586621679454866) l Source # | |
data TakeWhileSym1 (l :: TyFun a6989586621679454866 Bool -> Type) (l :: TyFun [a6989586621679454866] [a6989586621679454866]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454866 Bool -> Type) -> TyFun [a6989586621679454866] [a6989586621679454866] -> *) (TakeWhileSym1 a6989586621679454866) Source # | |
| type Apply [a] [a] (TakeWhileSym1 a l1) l2 Source # | |
type TakeWhileSym2 (t :: TyFun a6989586621679454866 Bool -> Type) (t :: [a6989586621679454866]) = TakeWhile t t Source #
data DropWhileSym0 (l :: TyFun (TyFun a6989586621679454865 Bool -> Type) (TyFun [a6989586621679454865] [a6989586621679454865] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454865 Bool -> Type) (TyFun [a6989586621679454865] [a6989586621679454865] -> Type) -> *) (DropWhileSym0 a6989586621679454865) Source # | |
| type Apply (TyFun a6989586621679454865 Bool -> Type) (TyFun [a6989586621679454865] [a6989586621679454865] -> Type) (DropWhileSym0 a6989586621679454865) l Source # | |
data DropWhileSym1 (l :: TyFun a6989586621679454865 Bool -> Type) (l :: TyFun [a6989586621679454865] [a6989586621679454865]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454865 Bool -> Type) -> TyFun [a6989586621679454865] [a6989586621679454865] -> *) (DropWhileSym1 a6989586621679454865) Source # | |
| type Apply [a] [a] (DropWhileSym1 a l1) l2 Source # | |
type DropWhileSym2 (t :: TyFun a6989586621679454865 Bool -> Type) (t :: [a6989586621679454865]) = DropWhile t t Source #
data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679454864 Bool -> Type) (TyFun [a6989586621679454864] [a6989586621679454864] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454864 Bool -> Type) (TyFun [a6989586621679454864] [a6989586621679454864] -> Type) -> *) (DropWhileEndSym0 a6989586621679454864) Source # | |
| type Apply (TyFun a6989586621679454864 Bool -> Type) (TyFun [a6989586621679454864] [a6989586621679454864] -> Type) (DropWhileEndSym0 a6989586621679454864) l Source # | |
data DropWhileEndSym1 (l :: TyFun a6989586621679454864 Bool -> Type) (l :: TyFun [a6989586621679454864] [a6989586621679454864]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454864 Bool -> Type) -> TyFun [a6989586621679454864] [a6989586621679454864] -> *) (DropWhileEndSym1 a6989586621679454864) Source # | |
| type Apply [a] [a] (DropWhileEndSym1 a l1) l2 Source # | |
type DropWhileEndSym2 (t :: TyFun a6989586621679454864 Bool -> Type) (t :: [a6989586621679454864]) = DropWhileEnd t t Source #
data SpanSym0 (l :: TyFun (TyFun a6989586621679454863 Bool -> Type) (TyFun [a6989586621679454863] ([a6989586621679454863], [a6989586621679454863]) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454863 Bool -> Type) (TyFun [a6989586621679454863] ([a6989586621679454863], [a6989586621679454863]) -> Type) -> *) (SpanSym0 a6989586621679454863) Source # | |
| type Apply (TyFun a6989586621679454863 Bool -> Type) (TyFun [a6989586621679454863] ([a6989586621679454863], [a6989586621679454863]) -> Type) (SpanSym0 a6989586621679454863) l Source # | |
data SpanSym1 (l :: TyFun a6989586621679454863 Bool -> Type) (l :: TyFun [a6989586621679454863] ([a6989586621679454863], [a6989586621679454863])) Source #
type SpanSym2 (t :: TyFun a6989586621679454863 Bool -> Type) (t :: [a6989586621679454863]) = Span t t Source #
data BreakSym0 (l :: TyFun (TyFun a6989586621679454862 Bool -> Type) (TyFun [a6989586621679454862] ([a6989586621679454862], [a6989586621679454862]) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454862 Bool -> Type) (TyFun [a6989586621679454862] ([a6989586621679454862], [a6989586621679454862]) -> Type) -> *) (BreakSym0 a6989586621679454862) Source # | |
| type Apply (TyFun a6989586621679454862 Bool -> Type) (TyFun [a6989586621679454862] ([a6989586621679454862], [a6989586621679454862]) -> Type) (BreakSym0 a6989586621679454862) l Source # | |
data BreakSym1 (l :: TyFun a6989586621679454862 Bool -> Type) (l :: TyFun [a6989586621679454862] ([a6989586621679454862], [a6989586621679454862])) Source #
type BreakSym2 (t :: TyFun a6989586621679454862 Bool -> Type) (t :: [a6989586621679454862]) = Break t t Source #
data IsPrefixOfSym0 (l :: TyFun [a6989586621679454926] (TyFun [a6989586621679454926] Bool -> Type)) Source #
data IsPrefixOfSym1 (l :: [a6989586621679454926]) (l :: TyFun [a6989586621679454926] Bool) Source #
Instances
| SuppressUnusedWarnings ([a6989586621679454926] -> TyFun [a6989586621679454926] Bool -> *) (IsPrefixOfSym1 a6989586621679454926) Source # | |
| type Apply [a] Bool (IsPrefixOfSym1 a l1) l2 Source # | |
type IsPrefixOfSym2 (t :: [a6989586621679454926]) (t :: [a6989586621679454926]) = IsPrefixOf t t Source #
data IsSuffixOfSym0 (l :: TyFun [a6989586621679454925] (TyFun [a6989586621679454925] Bool -> Type)) Source #
data IsSuffixOfSym1 (l :: [a6989586621679454925]) (l :: TyFun [a6989586621679454925] Bool) Source #
Instances
| SuppressUnusedWarnings ([a6989586621679454925] -> TyFun [a6989586621679454925] Bool -> *) (IsSuffixOfSym1 a6989586621679454925) Source # | |
| type Apply [a] Bool (IsSuffixOfSym1 a l1) l2 Source # | |
type IsSuffixOfSym2 (t :: [a6989586621679454925]) (t :: [a6989586621679454925]) = IsSuffixOf t t Source #
data IsInfixOfSym0 (l :: TyFun [a6989586621679454924] (TyFun [a6989586621679454924] Bool -> Type)) Source #
data IsInfixOfSym1 (l :: [a6989586621679454924]) (l :: TyFun [a6989586621679454924] Bool) Source #
Instances
| SuppressUnusedWarnings ([a6989586621679454924] -> TyFun [a6989586621679454924] Bool -> *) (IsInfixOfSym1 a6989586621679454924) Source # | |
| type Apply [a] Bool (IsInfixOfSym1 a l1) l2 Source # | |
type IsInfixOfSym2 (t :: [a6989586621679454924]) (t :: [a6989586621679454924]) = IsInfixOf t t Source #
data ElemSym0 (l :: TyFun a6989586621679454923 (TyFun [a6989586621679454923] Bool -> Type)) Source #
data NotElemSym0 (l :: TyFun a6989586621679454922 (TyFun [a6989586621679454922] Bool -> Type)) Source #
data NotElemSym1 (l :: a6989586621679454922) (l :: TyFun [a6989586621679454922] Bool) Source #
Instances
| SuppressUnusedWarnings (a6989586621679454922 -> TyFun [a6989586621679454922] Bool -> *) (NotElemSym1 a6989586621679454922) Source # | |
| type Apply [a] Bool (NotElemSym1 a l1) l2 Source # | |
type NotElemSym2 (t :: a6989586621679454922) (t :: [a6989586621679454922]) = NotElem t t Source #
data LookupSym0 (l :: TyFun a6989586621679454851 (TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun a6989586621679454851 (TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852) -> Type) -> *) (LookupSym0 a6989586621679454851 b6989586621679454852) Source # | |
| type Apply a6989586621679454851 (TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852) -> Type) (LookupSym0 a6989586621679454851 b6989586621679454852) l Source # | |
data LookupSym1 (l :: a6989586621679454851) (l :: TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852)) Source #
Instances
| SuppressUnusedWarnings (a6989586621679454851 -> TyFun [(a6989586621679454851, b6989586621679454852)] (Maybe b6989586621679454852) -> *) (LookupSym1 a6989586621679454851 b6989586621679454852) Source # | |
| type Apply [(a, b)] (Maybe b) (LookupSym1 a b l1) l2 Source # | |
type LookupSym2 (t :: a6989586621679454851) (t :: [(a6989586621679454851, b6989586621679454852)]) = Lookup t t Source #
data FindSym0 (l :: TyFun (TyFun a6989586621679454873 Bool -> Type) (TyFun [a6989586621679454873] (Maybe a6989586621679454873) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454873 Bool -> Type) (TyFun [a6989586621679454873] (Maybe a6989586621679454873) -> Type) -> *) (FindSym0 a6989586621679454873) Source # | |
| type Apply (TyFun a6989586621679454873 Bool -> Type) (TyFun [a6989586621679454873] (Maybe a6989586621679454873) -> Type) (FindSym0 a6989586621679454873) l Source # | |
data FindSym1 (l :: TyFun a6989586621679454873 Bool -> Type) (l :: TyFun [a6989586621679454873] (Maybe a6989586621679454873)) Source #
type FindSym2 (t :: TyFun a6989586621679454873 Bool -> Type) (t :: [a6989586621679454873]) = Find t t Source #
data FilterSym0 (l :: TyFun (TyFun a6989586621679454874 Bool -> Type) (TyFun [a6989586621679454874] [a6989586621679454874] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454874 Bool -> Type) (TyFun [a6989586621679454874] [a6989586621679454874] -> Type) -> *) (FilterSym0 a6989586621679454874) Source # | |
| type Apply (TyFun a6989586621679454874 Bool -> Type) (TyFun [a6989586621679454874] [a6989586621679454874] -> Type) (FilterSym0 a6989586621679454874) l Source # | |
data FilterSym1 (l :: TyFun a6989586621679454874 Bool -> Type) (l :: TyFun [a6989586621679454874] [a6989586621679454874]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454874 Bool -> Type) -> TyFun [a6989586621679454874] [a6989586621679454874] -> *) (FilterSym1 a6989586621679454874) Source # | |
| type Apply [a] [a] (FilterSym1 a l1) l2 Source # | |
type FilterSym2 (t :: TyFun a6989586621679454874 Bool -> Type) (t :: [a6989586621679454874]) = Filter t t Source #
data PartitionSym0 (l :: TyFun (TyFun a6989586621679454850 Bool -> Type) (TyFun [a6989586621679454850] ([a6989586621679454850], [a6989586621679454850]) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454850 Bool -> Type) (TyFun [a6989586621679454850] ([a6989586621679454850], [a6989586621679454850]) -> Type) -> *) (PartitionSym0 a6989586621679454850) Source # | |
| type Apply (TyFun a6989586621679454850 Bool -> Type) (TyFun [a6989586621679454850] ([a6989586621679454850], [a6989586621679454850]) -> Type) (PartitionSym0 a6989586621679454850) l Source # | |
data PartitionSym1 (l :: TyFun a6989586621679454850 Bool -> Type) (l :: TyFun [a6989586621679454850] ([a6989586621679454850], [a6989586621679454850])) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454850 Bool -> Type) -> TyFun [a6989586621679454850] ([a6989586621679454850], [a6989586621679454850]) -> *) (PartitionSym1 a6989586621679454850) Source # | |
| type Apply [a] ([a], [a]) (PartitionSym1 a l1) l2 Source # | |
type PartitionSym2 (t :: TyFun a6989586621679454850 Bool -> Type) (t :: [a6989586621679454850]) = Partition t t Source #
data ElemIndexSym0 (l :: TyFun a6989586621679454872 (TyFun [a6989586621679454872] (Maybe Nat) -> Type)) Source #
data ElemIndexSym1 (l :: a6989586621679454872) (l :: TyFun [a6989586621679454872] (Maybe Nat)) Source #
Instances
| SuppressUnusedWarnings (a6989586621679454872 -> TyFun [a6989586621679454872] (Maybe Nat) -> *) (ElemIndexSym1 a6989586621679454872) Source # | |
| type Apply [a] (Maybe Nat) (ElemIndexSym1 a l1) l2 Source # | |
type ElemIndexSym2 (t :: a6989586621679454872) (t :: [a6989586621679454872]) = ElemIndex t t Source #
data ElemIndicesSym0 (l :: TyFun a6989586621679454871 (TyFun [a6989586621679454871] [Nat] -> Type)) Source #
data ElemIndicesSym1 (l :: a6989586621679454871) (l :: TyFun [a6989586621679454871] [Nat]) Source #
Instances
| SuppressUnusedWarnings (a6989586621679454871 -> TyFun [a6989586621679454871] [Nat] -> *) (ElemIndicesSym1 a6989586621679454871) Source # | |
| type Apply [a] [Nat] (ElemIndicesSym1 a l1) l2 Source # | |
type ElemIndicesSym2 (t :: a6989586621679454871) (t :: [a6989586621679454871]) = ElemIndices t t Source #
data FindIndexSym0 (l :: TyFun (TyFun a6989586621679454870 Bool -> Type) (TyFun [a6989586621679454870] (Maybe Nat) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454870 Bool -> Type) (TyFun [a6989586621679454870] (Maybe Nat) -> Type) -> *) (FindIndexSym0 a6989586621679454870) Source # | |
| type Apply (TyFun a6989586621679454870 Bool -> Type) (TyFun [a6989586621679454870] (Maybe Nat) -> Type) (FindIndexSym0 a6989586621679454870) l Source # | |
data FindIndexSym1 (l :: TyFun a6989586621679454870 Bool -> Type) (l :: TyFun [a6989586621679454870] (Maybe Nat)) Source #
type FindIndexSym2 (t :: TyFun a6989586621679454870 Bool -> Type) (t :: [a6989586621679454870]) = FindIndex t t Source #
data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679454869 Bool -> Type) (TyFun [a6989586621679454869] [Nat] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454869 Bool -> Type) (TyFun [a6989586621679454869] [Nat] -> Type) -> *) (FindIndicesSym0 a6989586621679454869) Source # | |
| type Apply (TyFun a6989586621679454869 Bool -> Type) (TyFun [a6989586621679454869] [Nat] -> Type) (FindIndicesSym0 a6989586621679454869) l Source # | |
data FindIndicesSym1 (l :: TyFun a6989586621679454869 Bool -> Type) (l :: TyFun [a6989586621679454869] [Nat]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454869 Bool -> Type) -> TyFun [a6989586621679454869] [Nat] -> *) (FindIndicesSym1 a6989586621679454869) Source # | |
| type Apply [a] [Nat] (FindIndicesSym1 a l1) l2 Source # | |
type FindIndicesSym2 (t :: TyFun a6989586621679454869 Bool -> Type) (t :: [a6989586621679454869]) = FindIndices t t Source #
data ZipSym0 (l :: TyFun [a6989586621679454920] (TyFun [b6989586621679454921] [(a6989586621679454920, b6989586621679454921)] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454920] (TyFun [b6989586621679454921] [(a6989586621679454920, b6989586621679454921)] -> Type) -> *) (ZipSym0 a6989586621679454920 b6989586621679454921) Source # | |
| type Apply [a6989586621679454920] (TyFun [b6989586621679454921] [(a6989586621679454920, b6989586621679454921)] -> Type) (ZipSym0 a6989586621679454920 b6989586621679454921) l Source # | |
data ZipSym1 (l :: [a6989586621679454920]) (l :: TyFun [b6989586621679454921] [(a6989586621679454920, b6989586621679454921)]) Source #
data Zip3Sym0 (l :: TyFun [a6989586621679454917] (TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454917] (TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) -> Type) -> *) (Zip3Sym0 a6989586621679454917 b6989586621679454918 c6989586621679454919) Source # | |
| type Apply [a6989586621679454917] (TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) -> Type) (Zip3Sym0 a6989586621679454917 b6989586621679454918 c6989586621679454919) l Source # | |
data Zip3Sym1 (l :: [a6989586621679454917]) (l :: TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type)) Source #
Instances
| SuppressUnusedWarnings ([a6989586621679454917] -> TyFun [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) -> *) (Zip3Sym1 a6989586621679454917 b6989586621679454918 c6989586621679454919) Source # | |
| type Apply [b6989586621679454918] (TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> Type) (Zip3Sym1 a6989586621679454917 b6989586621679454918 c6989586621679454919 l1) l2 Source # | |
data Zip3Sym2 (l :: [a6989586621679454917]) (l :: [b6989586621679454918]) (l :: TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)]) Source #
Instances
| SuppressUnusedWarnings ([a6989586621679454917] -> [b6989586621679454918] -> TyFun [c6989586621679454919] [(a6989586621679454917, b6989586621679454918, c6989586621679454919)] -> *) (Zip3Sym2 a6989586621679454917 b6989586621679454918 c6989586621679454919) Source # | |
| type Apply [c] [(a, b, c)] (Zip3Sym2 a b c l1 l2) l3 Source # | |
type Zip3Sym3 (t :: [a6989586621679454917]) (t :: [b6989586621679454918]) (t :: [c6989586621679454919]) = Zip3 t t t Source #
data ZipWithSym0 (l :: TyFun (TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679454914 b6989586621679454915 c6989586621679454916) Source # | |
| type Apply (TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) -> Type) (ZipWithSym0 a6989586621679454914 b6989586621679454915 c6989586621679454916) l Source # | |
data ZipWithSym1 (l :: TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (l :: TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) -> TyFun [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) -> *) (ZipWithSym1 a6989586621679454914 b6989586621679454915 c6989586621679454916) Source # | |
| type Apply [a6989586621679454914] (TyFun [b6989586621679454915] [c6989586621679454916] -> Type) (ZipWithSym1 a6989586621679454914 b6989586621679454915 c6989586621679454916 l1) l2 Source # | |
data ZipWithSym2 (l :: TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (l :: [a6989586621679454914]) (l :: TyFun [b6989586621679454915] [c6989586621679454916]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) -> [a6989586621679454914] -> TyFun [b6989586621679454915] [c6989586621679454916] -> *) (ZipWithSym2 a6989586621679454914 b6989586621679454915 c6989586621679454916) Source # | |
| type Apply [b] [c] (ZipWithSym2 a b c l1 l2) l3 Source # | |
type ZipWithSym3 (t :: TyFun a6989586621679454914 (TyFun b6989586621679454915 c6989586621679454916 -> Type) -> Type) (t :: [a6989586621679454914]) (t :: [b6989586621679454915]) = ZipWith t t t Source #
data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) Source # | |
| type Apply (TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) -> Type) (ZipWith3Sym0 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) l Source # | |
data ZipWith3Sym1 (l :: TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) -> TyFun [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) -> *) (ZipWith3Sym1 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) Source # | |
| type Apply [a6989586621679454910] (TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> Type) (ZipWith3Sym1 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913 l1) l2 Source # | |
data ZipWith3Sym2 (l :: TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (l :: [a6989586621679454910]) (l :: TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) -> [a6989586621679454910] -> TyFun [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) -> *) (ZipWith3Sym2 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) Source # | |
| type Apply [b6989586621679454911] (TyFun [c6989586621679454912] [d6989586621679454913] -> Type) (ZipWith3Sym2 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913 l1 l2) l3 Source # | |
data ZipWith3Sym3 (l :: TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (l :: [a6989586621679454910]) (l :: [b6989586621679454911]) (l :: TyFun [c6989586621679454912] [d6989586621679454913]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) -> [a6989586621679454910] -> [b6989586621679454911] -> TyFun [c6989586621679454912] [d6989586621679454913] -> *) (ZipWith3Sym3 a6989586621679454910 b6989586621679454911 c6989586621679454912 d6989586621679454913) Source # | |
| type Apply [c] [d] (ZipWith3Sym3 a b c d l1 l2 l3) l4 Source # | |
type ZipWith3Sym4 (t :: TyFun a6989586621679454910 (TyFun b6989586621679454911 (TyFun c6989586621679454912 d6989586621679454913 -> Type) -> Type) -> Type) (t :: [a6989586621679454910]) (t :: [b6989586621679454911]) (t :: [c6989586621679454912]) = ZipWith3 t t t t Source #
data UnzipSym0 (l :: TyFun [(a6989586621679454908, b6989586621679454909)] ([a6989586621679454908], [b6989586621679454909])) Source #
data Unzip3Sym0 (l :: TyFun [(a6989586621679454905, b6989586621679454906, c6989586621679454907)] ([a6989586621679454905], [b6989586621679454906], [c6989586621679454907])) Source #
Instances
| SuppressUnusedWarnings (TyFun [(a6989586621679454905, b6989586621679454906, c6989586621679454907)] ([a6989586621679454905], [b6989586621679454906], [c6989586621679454907]) -> *) (Unzip3Sym0 a6989586621679454905 b6989586621679454906 c6989586621679454907) Source # | |
| type Apply [(a, b, c)] ([a], [b], [c]) (Unzip3Sym0 a b c) l Source # | |
type Unzip3Sym1 (t :: [(a6989586621679454905, b6989586621679454906, c6989586621679454907)]) = Unzip3 t Source #
data Unzip4Sym0 (l :: TyFun [(a6989586621679454901, b6989586621679454902, c6989586621679454903, d6989586621679454904)] ([a6989586621679454901], [b6989586621679454902], [c6989586621679454903], [d6989586621679454904])) Source #
Instances
| SuppressUnusedWarnings (TyFun [(a6989586621679454901, b6989586621679454902, c6989586621679454903, d6989586621679454904)] ([a6989586621679454901], [b6989586621679454902], [c6989586621679454903], [d6989586621679454904]) -> *) (Unzip4Sym0 a6989586621679454901 b6989586621679454902 c6989586621679454903 d6989586621679454904) Source # | |
| type Apply [(a, b, c, d)] ([a], [b], [c], [d]) (Unzip4Sym0 a b c d) l Source # | |
type Unzip4Sym1 (t :: [(a6989586621679454901, b6989586621679454902, c6989586621679454903, d6989586621679454904)]) = Unzip4 t Source #
data Unzip5Sym0 (l :: TyFun [(a6989586621679454896, b6989586621679454897, c6989586621679454898, d6989586621679454899, e6989586621679454900)] ([a6989586621679454896], [b6989586621679454897], [c6989586621679454898], [d6989586621679454899], [e6989586621679454900])) Source #
Instances
| SuppressUnusedWarnings (TyFun [(a6989586621679454896, b6989586621679454897, c6989586621679454898, d6989586621679454899, e6989586621679454900)] ([a6989586621679454896], [b6989586621679454897], [c6989586621679454898], [d6989586621679454899], [e6989586621679454900]) -> *) (Unzip5Sym0 a6989586621679454896 b6989586621679454897 c6989586621679454898 d6989586621679454899 e6989586621679454900) Source # | |
| type Apply [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) (Unzip5Sym0 a b c d e) l Source # | |
type Unzip5Sym1 (t :: [(a6989586621679454896, b6989586621679454897, c6989586621679454898, d6989586621679454899, e6989586621679454900)]) = Unzip5 t Source #
data Unzip6Sym0 (l :: TyFun [(a6989586621679454890, b6989586621679454891, c6989586621679454892, d6989586621679454893, e6989586621679454894, f6989586621679454895)] ([a6989586621679454890], [b6989586621679454891], [c6989586621679454892], [d6989586621679454893], [e6989586621679454894], [f6989586621679454895])) Source #
Instances
| SuppressUnusedWarnings (TyFun [(a6989586621679454890, b6989586621679454891, c6989586621679454892, d6989586621679454893, e6989586621679454894, f6989586621679454895)] ([a6989586621679454890], [b6989586621679454891], [c6989586621679454892], [d6989586621679454893], [e6989586621679454894], [f6989586621679454895]) -> *) (Unzip6Sym0 a6989586621679454890 b6989586621679454891 c6989586621679454892 d6989586621679454893 e6989586621679454894 f6989586621679454895) Source # | |
| type Apply [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) (Unzip6Sym0 a b c d e f) l Source # | |
type Unzip6Sym1 (t :: [(a6989586621679454890, b6989586621679454891, c6989586621679454892, d6989586621679454893, e6989586621679454894, f6989586621679454895)]) = Unzip6 t Source #
data Unzip7Sym0 (l :: TyFun [(a6989586621679454883, b6989586621679454884, c6989586621679454885, d6989586621679454886, e6989586621679454887, f6989586621679454888, g6989586621679454889)] ([a6989586621679454883], [b6989586621679454884], [c6989586621679454885], [d6989586621679454886], [e6989586621679454887], [f6989586621679454888], [g6989586621679454889])) Source #
Instances
| SuppressUnusedWarnings (TyFun [(a6989586621679454883, b6989586621679454884, c6989586621679454885, d6989586621679454886, e6989586621679454887, f6989586621679454888, g6989586621679454889)] ([a6989586621679454883], [b6989586621679454884], [c6989586621679454885], [d6989586621679454886], [e6989586621679454887], [f6989586621679454888], [g6989586621679454889]) -> *) (Unzip7Sym0 a6989586621679454883 b6989586621679454884 c6989586621679454885 d6989586621679454886 e6989586621679454887 f6989586621679454888 g6989586621679454889) Source # | |
| type Apply [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) (Unzip7Sym0 a b c d e f g) l Source # | |
type Unzip7Sym1 (t :: [(a6989586621679454883, b6989586621679454884, c6989586621679454885, d6989586621679454886, e6989586621679454887, f6989586621679454888, g6989586621679454889)]) = Unzip7 t Source #
data DeleteSym0 (l :: TyFun a6989586621679454882 (TyFun [a6989586621679454882] [a6989586621679454882] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun a6989586621679454882 (TyFun [a6989586621679454882] [a6989586621679454882] -> Type) -> *) (DeleteSym0 a6989586621679454882) Source # | |
| type Apply a6989586621679454882 (TyFun [a6989586621679454882] [a6989586621679454882] -> Type) (DeleteSym0 a6989586621679454882) l Source # | |
data DeleteSym1 (l :: a6989586621679454882) (l :: TyFun [a6989586621679454882] [a6989586621679454882]) Source #
Instances
| SuppressUnusedWarnings (a6989586621679454882 -> TyFun [a6989586621679454882] [a6989586621679454882] -> *) (DeleteSym1 a6989586621679454882) Source # | |
| type Apply [a] [a] (DeleteSym1 a l1) l2 Source # | |
type DeleteSym2 (t :: a6989586621679454882) (t :: [a6989586621679454882]) = Delete t t Source #
data (:\\$) (l :: TyFun [a6989586621679454881] (TyFun [a6989586621679454881] [a6989586621679454881] -> Type)) Source #
Instances
data (l :: [a6989586621679454881]) :\\$$ (l :: TyFun [a6989586621679454881] [a6989586621679454881]) Source #
data UnionSym0 (l :: TyFun [a6989586621679454838] (TyFun [a6989586621679454838] [a6989586621679454838] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454838] (TyFun [a6989586621679454838] [a6989586621679454838] -> Type) -> *) (UnionSym0 a6989586621679454838) Source # | |
| type Apply [a6989586621679454838] (TyFun [a6989586621679454838] [a6989586621679454838] -> Type) (UnionSym0 a6989586621679454838) l Source # | |
data UnionSym1 (l :: [a6989586621679454838]) (l :: TyFun [a6989586621679454838] [a6989586621679454838]) Source #
data IntersectSym0 (l :: TyFun [a6989586621679454868] (TyFun [a6989586621679454868] [a6989586621679454868] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454868] (TyFun [a6989586621679454868] [a6989586621679454868] -> Type) -> *) (IntersectSym0 a6989586621679454868) Source # | |
| type Apply [a6989586621679454868] (TyFun [a6989586621679454868] [a6989586621679454868] -> Type) (IntersectSym0 a6989586621679454868) l Source # | |
data IntersectSym1 (l :: [a6989586621679454868]) (l :: TyFun [a6989586621679454868] [a6989586621679454868]) Source #
Instances
| SuppressUnusedWarnings ([a6989586621679454868] -> TyFun [a6989586621679454868] [a6989586621679454868] -> *) (IntersectSym1 a6989586621679454868) Source # | |
| type Apply [a] [a] (IntersectSym1 a l1) l2 Source # | |
type IntersectSym2 (t :: [a6989586621679454868]) (t :: [a6989586621679454868]) = Intersect t t Source #
data InsertSym0 (l :: TyFun a6989586621679454855 (TyFun [a6989586621679454855] [a6989586621679454855] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun a6989586621679454855 (TyFun [a6989586621679454855] [a6989586621679454855] -> Type) -> *) (InsertSym0 a6989586621679454855) Source # | |
| type Apply a6989586621679454855 (TyFun [a6989586621679454855] [a6989586621679454855] -> Type) (InsertSym0 a6989586621679454855) l Source # | |
data InsertSym1 (l :: a6989586621679454855) (l :: TyFun [a6989586621679454855] [a6989586621679454855]) Source #
Instances
| SuppressUnusedWarnings (a6989586621679454855 -> TyFun [a6989586621679454855] [a6989586621679454855] -> *) (InsertSym1 a6989586621679454855) Source # | |
| type Apply [a] [a] (InsertSym1 a l1) l2 Source # | |
type InsertSym2 (t :: a6989586621679454855) (t :: [a6989586621679454855]) = Insert t t Source #
data NubBySym0 (l :: TyFun (TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (TyFun [a6989586621679454841] [a6989586621679454841] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (TyFun [a6989586621679454841] [a6989586621679454841] -> Type) -> *) (NubBySym0 a6989586621679454841) Source # | |
| type Apply (TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (TyFun [a6989586621679454841] [a6989586621679454841] -> Type) (NubBySym0 a6989586621679454841) l Source # | |
data NubBySym1 (l :: TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454841] [a6989586621679454841]) Source #
type NubBySym2 (t :: TyFun a6989586621679454841 (TyFun a6989586621679454841 Bool -> Type) -> Type) (t :: [a6989586621679454841]) = NubBy t t Source #
data DeleteBySym0 (l :: TyFun (TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (TyFun a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (TyFun a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type) -> Type) -> *) (DeleteBySym0 a6989586621679454880) Source # | |
| type Apply (TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (TyFun a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type) -> Type) (DeleteBySym0 a6989586621679454880) l Source # | |
data DeleteBySym1 (l :: TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (l :: TyFun a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) -> TyFun a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type) -> *) (DeleteBySym1 a6989586621679454880) Source # | |
| type Apply a6989586621679454880 (TyFun [a6989586621679454880] [a6989586621679454880] -> Type) (DeleteBySym1 a6989586621679454880 l1) l2 Source # | |
data DeleteBySym2 (l :: TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (l :: a6989586621679454880) (l :: TyFun [a6989586621679454880] [a6989586621679454880]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) -> a6989586621679454880 -> TyFun [a6989586621679454880] [a6989586621679454880] -> *) (DeleteBySym2 a6989586621679454880) Source # | |
| type Apply [a] [a] (DeleteBySym2 a l1 l2) l3 Source # | |
type DeleteBySym3 (t :: TyFun a6989586621679454880 (TyFun a6989586621679454880 Bool -> Type) -> Type) (t :: a6989586621679454880) (t :: [a6989586621679454880]) = DeleteBy t t t Source #
data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (TyFun [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (TyFun [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type) -> Type) -> *) (DeleteFirstsBySym0 a6989586621679454879) Source # | |
| type Apply (TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (TyFun [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type) -> Type) (DeleteFirstsBySym0 a6989586621679454879) l Source # | |
data DeleteFirstsBySym1 (l :: TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) -> TyFun [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type) -> *) (DeleteFirstsBySym1 a6989586621679454879) Source # | |
| type Apply [a6989586621679454879] (TyFun [a6989586621679454879] [a6989586621679454879] -> Type) (DeleteFirstsBySym1 a6989586621679454879 l1) l2 Source # | |
data DeleteFirstsBySym2 (l :: TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (l :: [a6989586621679454879]) (l :: TyFun [a6989586621679454879] [a6989586621679454879]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) -> [a6989586621679454879] -> TyFun [a6989586621679454879] [a6989586621679454879] -> *) (DeleteFirstsBySym2 a6989586621679454879) Source # | |
| type Apply [a] [a] (DeleteFirstsBySym2 a l1 l2) l3 Source # | |
type DeleteFirstsBySym3 (t :: TyFun a6989586621679454879 (TyFun a6989586621679454879 Bool -> Type) -> Type) (t :: [a6989586621679454879]) (t :: [a6989586621679454879]) = DeleteFirstsBy t t t Source #
data UnionBySym0 (l :: TyFun (TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (TyFun [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (TyFun [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type) -> Type) -> *) (UnionBySym0 a6989586621679454839) Source # | |
| type Apply (TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (TyFun [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type) -> Type) (UnionBySym0 a6989586621679454839) l Source # | |
data UnionBySym1 (l :: TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) -> TyFun [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type) -> *) (UnionBySym1 a6989586621679454839) Source # | |
| type Apply [a6989586621679454839] (TyFun [a6989586621679454839] [a6989586621679454839] -> Type) (UnionBySym1 a6989586621679454839 l1) l2 Source # | |
data UnionBySym2 (l :: TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (l :: [a6989586621679454839]) (l :: TyFun [a6989586621679454839] [a6989586621679454839]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) -> [a6989586621679454839] -> TyFun [a6989586621679454839] [a6989586621679454839] -> *) (UnionBySym2 a6989586621679454839) Source # | |
| type Apply [a] [a] (UnionBySym2 a l1 l2) l3 Source # | |
type UnionBySym3 (t :: TyFun a6989586621679454839 (TyFun a6989586621679454839 Bool -> Type) -> Type) (t :: [a6989586621679454839]) (t :: [a6989586621679454839]) = UnionBy t t t Source #
data IntersectBySym0 (l :: TyFun (TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (TyFun [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (TyFun [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type) -> Type) -> *) (IntersectBySym0 a6989586621679454867) Source # | |
| type Apply (TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (TyFun [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type) -> Type) (IntersectBySym0 a6989586621679454867) l Source # | |
data IntersectBySym1 (l :: TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) -> TyFun [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type) -> *) (IntersectBySym1 a6989586621679454867) Source # | |
| type Apply [a6989586621679454867] (TyFun [a6989586621679454867] [a6989586621679454867] -> Type) (IntersectBySym1 a6989586621679454867 l1) l2 Source # | |
data IntersectBySym2 (l :: TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (l :: [a6989586621679454867]) (l :: TyFun [a6989586621679454867] [a6989586621679454867]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) -> [a6989586621679454867] -> TyFun [a6989586621679454867] [a6989586621679454867] -> *) (IntersectBySym2 a6989586621679454867) Source # | |
| type Apply [a] [a] (IntersectBySym2 a l1 l2) l3 Source # | |
type IntersectBySym3 (t :: TyFun a6989586621679454867 (TyFun a6989586621679454867 Bool -> Type) -> Type) (t :: [a6989586621679454867]) (t :: [a6989586621679454867]) = IntersectBy t t t Source #
data GroupBySym0 (l :: TyFun (TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (TyFun [a6989586621679454853] [[a6989586621679454853]] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (TyFun [a6989586621679454853] [[a6989586621679454853]] -> Type) -> *) (GroupBySym0 a6989586621679454853) Source # | |
| type Apply (TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (TyFun [a6989586621679454853] [[a6989586621679454853]] -> Type) (GroupBySym0 a6989586621679454853) l Source # | |
data GroupBySym1 (l :: TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (l :: TyFun [a6989586621679454853] [[a6989586621679454853]]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) -> TyFun [a6989586621679454853] [[a6989586621679454853]] -> *) (GroupBySym1 a6989586621679454853) Source # | |
| type Apply [a] [[a]] (GroupBySym1 a l1) l2 Source # | |
type GroupBySym2 (t :: TyFun a6989586621679454853 (TyFun a6989586621679454853 Bool -> Type) -> Type) (t :: [a6989586621679454853]) = GroupBy t t Source #
data SortBySym0 (l :: TyFun (TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (TyFun [a6989586621679454878] [a6989586621679454878] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (TyFun [a6989586621679454878] [a6989586621679454878] -> Type) -> *) (SortBySym0 a6989586621679454878) Source # | |
| type Apply (TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (TyFun [a6989586621679454878] [a6989586621679454878] -> Type) (SortBySym0 a6989586621679454878) l Source # | |
data SortBySym1 (l :: TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679454878] [a6989586621679454878]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) -> TyFun [a6989586621679454878] [a6989586621679454878] -> *) (SortBySym1 a6989586621679454878) Source # | |
| type Apply [a] [a] (SortBySym1 a l1) l2 Source # | |
type SortBySym2 (t :: TyFun a6989586621679454878 (TyFun a6989586621679454878 Ordering -> Type) -> Type) (t :: [a6989586621679454878]) = SortBy t t Source #
data InsertBySym0 (l :: TyFun (TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (TyFun a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (TyFun a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type) -> Type) -> *) (InsertBySym0 a6989586621679454877) Source # | |
| type Apply (TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (TyFun a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type) -> Type) (InsertBySym0 a6989586621679454877) l Source # | |
data InsertBySym1 (l :: TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (l :: TyFun a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type)) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) -> TyFun a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type) -> *) (InsertBySym1 a6989586621679454877) Source # | |
| type Apply a6989586621679454877 (TyFun [a6989586621679454877] [a6989586621679454877] -> Type) (InsertBySym1 a6989586621679454877 l1) l2 Source # | |
data InsertBySym2 (l :: TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (l :: a6989586621679454877) (l :: TyFun [a6989586621679454877] [a6989586621679454877]) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) -> a6989586621679454877 -> TyFun [a6989586621679454877] [a6989586621679454877] -> *) (InsertBySym2 a6989586621679454877) Source # | |
| type Apply [a] [a] (InsertBySym2 a l1 l2) l3 Source # | |
type InsertBySym3 (t :: TyFun a6989586621679454877 (TyFun a6989586621679454877 Ordering -> Type) -> Type) (t :: a6989586621679454877) (t :: [a6989586621679454877]) = InsertBy t t t Source #
data MaximumBySym0 (l :: TyFun (TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (TyFun [a6989586621679454876] a6989586621679454876 -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (TyFun [a6989586621679454876] a6989586621679454876 -> Type) -> *) (MaximumBySym0 a6989586621679454876) Source # | |
| type Apply (TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (TyFun [a6989586621679454876] a6989586621679454876 -> Type) (MaximumBySym0 a6989586621679454876) l Source # | |
data MaximumBySym1 (l :: TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679454876] a6989586621679454876) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) -> TyFun [a6989586621679454876] a6989586621679454876 -> *) (MaximumBySym1 a6989586621679454876) Source # | |
| type Apply [a] a (MaximumBySym1 a l1) l2 Source # | |
type MaximumBySym2 (t :: TyFun a6989586621679454876 (TyFun a6989586621679454876 Ordering -> Type) -> Type) (t :: [a6989586621679454876]) = MaximumBy t t Source #
data MinimumBySym0 (l :: TyFun (TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (TyFun [a6989586621679454875] a6989586621679454875 -> Type)) Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (TyFun [a6989586621679454875] a6989586621679454875 -> Type) -> *) (MinimumBySym0 a6989586621679454875) Source # | |
| type Apply (TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (TyFun [a6989586621679454875] a6989586621679454875 -> Type) (MinimumBySym0 a6989586621679454875) l Source # | |
data MinimumBySym1 (l :: TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679454875] a6989586621679454875) Source #
Instances
| SuppressUnusedWarnings ((TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) -> TyFun [a6989586621679454875] a6989586621679454875 -> *) (MinimumBySym1 a6989586621679454875) Source # | |
| type Apply [a] a (MinimumBySym1 a l1) l2 Source # | |
type MinimumBySym2 (t :: TyFun a6989586621679454875 (TyFun a6989586621679454875 Ordering -> Type) -> Type) (t :: [a6989586621679454875]) = MinimumBy t t Source #
data GenericLengthSym0 (l :: TyFun [a6989586621679454837] i6989586621679454836) Source #
Instances
| SuppressUnusedWarnings (TyFun [a6989586621679454837] i6989586621679454836 -> *) (GenericLengthSym0 a6989586621679454837 i6989586621679454836) Source # | |
| type Apply [a] k2 (GenericLengthSym0 a k2) l Source # | |
type GenericLengthSym1 (t :: [a6989586621679454837]) = GenericLength t Source #