| 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.
Synopsis
- 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 AnySym0 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)
- 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 Unlines (a :: [Symbol]) :: Symbol where ...
- sUnlines :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnlinesSym0 t :: Symbol)
- type family Unwords (a :: [Symbol]) :: Symbol where ...
- sUnwords :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnwordsSym0 t :: Symbol)
- 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 :: [a6989586621679419904]) (t :: [a6989586621679419904]) = (++) t t
- data (l :: [a6989586621679419904]) ++@#@$$ (l :: TyFun [a6989586621679419904] [a6989586621679419904])
- data (++@#@$) (l :: TyFun [a6989586621679419904] (TyFun [a6989586621679419904] [a6989586621679419904] -> Type))
- data HeadSym0 (l :: TyFun [a6989586621679442541] a6989586621679442541)
- type HeadSym1 (t :: [a6989586621679442541]) = Head t
- data LastSym0 (l :: TyFun [a6989586621679442540] a6989586621679442540)
- type LastSym1 (t :: [a6989586621679442540]) = Last t
- data TailSym0 (l :: TyFun [a6989586621679442539] [a6989586621679442539])
- type TailSym1 (t :: [a6989586621679442539]) = Tail t
- data InitSym0 (l :: TyFun [a6989586621679442538] [a6989586621679442538])
- type InitSym1 (t :: [a6989586621679442538]) = Init t
- data NullSym0 (l :: TyFun [a6989586621679442537] Bool)
- type NullSym1 (t :: [a6989586621679442537]) = Null t
- data LengthSym0 (l :: TyFun [a6989586621679442423] Nat)
- type LengthSym1 (t :: [a6989586621679442423]) = Length t
- data MapSym0 (l :: TyFun (TyFun a6989586621679419905 b6989586621679419906 -> Type) (TyFun [a6989586621679419905] [b6989586621679419906] -> Type))
- data MapSym1 (l :: TyFun a6989586621679419905 b6989586621679419906 -> Type) (l :: TyFun [a6989586621679419905] [b6989586621679419906])
- type MapSym2 (t :: TyFun a6989586621679419905 b6989586621679419906 -> Type) (t :: [a6989586621679419905]) = Map t t
- data ReverseSym0 (l :: TyFun [a6989586621679442536] [a6989586621679442536])
- type ReverseSym1 (t :: [a6989586621679442536]) = Reverse t
- data IntersperseSym0 (l :: TyFun a6989586621679442535 (TyFun [a6989586621679442535] [a6989586621679442535] -> Type))
- data IntersperseSym1 (l :: a6989586621679442535) (l :: TyFun [a6989586621679442535] [a6989586621679442535])
- type IntersperseSym2 (t :: a6989586621679442535) (t :: [a6989586621679442535]) = Intersperse t t
- data IntercalateSym0 (l :: TyFun [a6989586621679442534] (TyFun [[a6989586621679442534]] [a6989586621679442534] -> Type))
- data IntercalateSym1 (l :: [a6989586621679442534]) (l :: TyFun [[a6989586621679442534]] [a6989586621679442534])
- type IntercalateSym2 (t :: [a6989586621679442534]) (t :: [[a6989586621679442534]]) = Intercalate t t
- data TransposeSym0 (l :: TyFun [[a6989586621679442421]] [[a6989586621679442421]])
- type TransposeSym1 (t :: [[a6989586621679442421]]) = Transpose t
- data SubsequencesSym0 (l :: TyFun [a6989586621679442533] [[a6989586621679442533]])
- type SubsequencesSym1 (t :: [a6989586621679442533]) = Subsequences t
- data PermutationsSym0 (l :: TyFun [a6989586621679442530] [[a6989586621679442530]])
- type PermutationsSym1 (t :: [a6989586621679442530]) = Permutations t
- data FoldlSym0 (l :: TyFun (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> Type))
- data FoldlSym1 (l :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (l :: TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type))
- data FoldlSym2 (l :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (l :: b6989586621679259259) (l :: TyFun [a6989586621679259258] b6989586621679259259)
- type FoldlSym3 (t :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (t :: b6989586621679259259) (t :: [a6989586621679259258]) = Foldl t t t
- data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) (TyFun b6989586621679442529 (TyFun [a6989586621679442528] b6989586621679442529 -> Type) -> Type))
- data Foldl'Sym1 (l :: TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) (l :: TyFun b6989586621679442529 (TyFun [a6989586621679442528] b6989586621679442529 -> Type))
- data Foldl'Sym2 (l :: TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) (l :: b6989586621679442529) (l :: TyFun [a6989586621679442528] b6989586621679442529)
- type Foldl'Sym3 (t :: TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) (t :: b6989586621679442529) (t :: [a6989586621679442528]) = Foldl' t t t
- data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) (TyFun [a6989586621679442527] a6989586621679442527 -> Type))
- data Foldl1Sym1 (l :: TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) (l :: TyFun [a6989586621679442527] a6989586621679442527)
- type Foldl1Sym2 (t :: TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) (t :: [a6989586621679442527]) = Foldl1 t t
- data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) (TyFun [a6989586621679442526] a6989586621679442526 -> Type))
- data Foldl1'Sym1 (l :: TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) (l :: TyFun [a6989586621679442526] a6989586621679442526)
- type Foldl1'Sym2 (t :: TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) (t :: [a6989586621679442526]) = Foldl1' t t
- data FoldrSym0 (l :: TyFun (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> Type))
- data FoldrSym1 (l :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (l :: TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type))
- data FoldrSym2 (l :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (l :: b6989586621679419908) (l :: TyFun [a6989586621679419907] b6989586621679419908)
- type FoldrSym3 (t :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (t :: b6989586621679419908) (t :: [a6989586621679419907]) = Foldr t t t
- data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) (TyFun [a6989586621679442525] a6989586621679442525 -> Type))
- data Foldr1Sym1 (l :: TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) (l :: TyFun [a6989586621679442525] a6989586621679442525)
- type Foldr1Sym2 (t :: TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) (t :: [a6989586621679442525]) = Foldr1 t t
- data ConcatSym0 (l :: TyFun [[a6989586621679442524]] [a6989586621679442524])
- type ConcatSym1 (t :: [[a6989586621679442524]]) = Concat t
- data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679442522 [b6989586621679442523] -> Type) (TyFun [a6989586621679442522] [b6989586621679442523] -> Type))
- data ConcatMapSym1 (l :: TyFun a6989586621679442522 [b6989586621679442523] -> Type) (l :: TyFun [a6989586621679442522] [b6989586621679442523])
- type ConcatMapSym2 (t :: TyFun a6989586621679442522 [b6989586621679442523] -> Type) (t :: [a6989586621679442522]) = 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 AnySym0 (l :: TyFun (TyFun a6989586621679442520 Bool -> Type) (TyFun [a6989586621679442520] Bool -> Type))
- data AnySym1 (l :: TyFun a6989586621679442520 Bool -> Type) (l :: TyFun [a6989586621679442520] Bool)
- type AnySym2 (t :: TyFun a6989586621679442520 Bool -> Type) (t :: [a6989586621679442520]) = Any t t
- data AllSym0 (l :: TyFun (TyFun a6989586621679442521 Bool -> Type) (TyFun [a6989586621679442521] Bool -> Type))
- data AllSym1 (l :: TyFun a6989586621679442521 Bool -> Type) (l :: TyFun [a6989586621679442521] Bool)
- type AllSym2 (t :: TyFun a6989586621679442521 Bool -> Type) (t :: [a6989586621679442521]) = All t t
- data SumSym0 (l :: TyFun [a6989586621679442425] a6989586621679442425)
- type SumSym1 (t :: [a6989586621679442425]) = Sum t
- data ProductSym0 (l :: TyFun [a6989586621679442424] a6989586621679442424)
- type ProductSym1 (t :: [a6989586621679442424]) = Product t
- data MaximumSym0 (l :: TyFun [a6989586621679442434] a6989586621679442434)
- type MaximumSym1 (t :: [a6989586621679442434]) = Maximum t
- data MinimumSym0 (l :: TyFun [a6989586621679442433] a6989586621679442433)
- type MinimumSym1 (t :: [a6989586621679442433]) = Minimum t
- data ScanlSym0 (l :: TyFun (TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) (TyFun b6989586621679442518 (TyFun [a6989586621679442519] [b6989586621679442518] -> Type) -> Type))
- data ScanlSym1 (l :: TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) (l :: TyFun b6989586621679442518 (TyFun [a6989586621679442519] [b6989586621679442518] -> Type))
- data ScanlSym2 (l :: TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) (l :: b6989586621679442518) (l :: TyFun [a6989586621679442519] [b6989586621679442518])
- type ScanlSym3 (t :: TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) (t :: b6989586621679442518) (t :: [a6989586621679442519]) = Scanl t t t
- data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) (TyFun [a6989586621679442517] [a6989586621679442517] -> Type))
- data Scanl1Sym1 (l :: TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) (l :: TyFun [a6989586621679442517] [a6989586621679442517])
- type Scanl1Sym2 (t :: TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) (t :: [a6989586621679442517]) = Scanl1 t t
- data ScanrSym0 (l :: TyFun (TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) (TyFun b6989586621679442516 (TyFun [a6989586621679442515] [b6989586621679442516] -> Type) -> Type))
- data ScanrSym1 (l :: TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) (l :: TyFun b6989586621679442516 (TyFun [a6989586621679442515] [b6989586621679442516] -> Type))
- data ScanrSym2 (l :: TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) (l :: b6989586621679442516) (l :: TyFun [a6989586621679442515] [b6989586621679442516])
- type ScanrSym3 (t :: TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) (t :: b6989586621679442516) (t :: [a6989586621679442515]) = Scanr t t t
- data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) (TyFun [a6989586621679442514] [a6989586621679442514] -> Type))
- data Scanr1Sym1 (l :: TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) (l :: TyFun [a6989586621679442514] [a6989586621679442514])
- type Scanr1Sym2 (t :: TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) (t :: [a6989586621679442514]) = Scanr1 t t
- data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) (TyFun acc6989586621679442511 (TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> Type) -> Type))
- data MapAccumLSym1 (l :: TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) (l :: TyFun acc6989586621679442511 (TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> Type))
- data MapAccumLSym2 (l :: TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) (l :: acc6989586621679442511) (l :: TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]))
- type MapAccumLSym3 (t :: TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) (t :: acc6989586621679442511) (t :: [x6989586621679442512]) = MapAccumL t t t
- data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) (TyFun acc6989586621679442508 (TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> Type) -> Type))
- data MapAccumRSym1 (l :: TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) (l :: TyFun acc6989586621679442508 (TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> Type))
- data MapAccumRSym2 (l :: TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) (l :: acc6989586621679442508) (l :: TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]))
- type MapAccumRSym3 (t :: TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) (t :: acc6989586621679442508) (t :: [x6989586621679442509]) = MapAccumR t t t
- data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679442422 [a6989586621679442422] -> Type))
- data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679442422 [a6989586621679442422])
- type ReplicateSym2 (t :: Nat) (t :: a6989586621679442422) = Replicate t t
- data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679442506 (Maybe (a6989586621679442507, b6989586621679442506)) -> Type) (TyFun b6989586621679442506 [a6989586621679442507] -> Type))
- data UnfoldrSym1 (l :: TyFun b6989586621679442506 (Maybe (a6989586621679442507, b6989586621679442506)) -> Type) (l :: TyFun b6989586621679442506 [a6989586621679442507])
- type UnfoldrSym2 (t :: TyFun b6989586621679442506 (Maybe (a6989586621679442507, b6989586621679442506)) -> Type) (t :: b6989586621679442506) = Unfoldr t t
- data TakeSym0 (l :: TyFun Nat (TyFun [a6989586621679442438] [a6989586621679442438] -> Type))
- data TakeSym1 (l :: Nat) (l :: TyFun [a6989586621679442438] [a6989586621679442438])
- type TakeSym2 (t :: Nat) (t :: [a6989586621679442438]) = Take t t
- data DropSym0 (l :: TyFun Nat (TyFun [a6989586621679442437] [a6989586621679442437] -> Type))
- data DropSym1 (l :: Nat) (l :: TyFun [a6989586621679442437] [a6989586621679442437])
- type DropSym2 (t :: Nat) (t :: [a6989586621679442437]) = Drop t t
- data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679442436] ([a6989586621679442436], [a6989586621679442436]) -> Type))
- data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679442436] ([a6989586621679442436], [a6989586621679442436]))
- type SplitAtSym2 (t :: Nat) (t :: [a6989586621679442436]) = SplitAt t t
- data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679442443 Bool -> Type) (TyFun [a6989586621679442443] [a6989586621679442443] -> Type))
- data TakeWhileSym1 (l :: TyFun a6989586621679442443 Bool -> Type) (l :: TyFun [a6989586621679442443] [a6989586621679442443])
- type TakeWhileSym2 (t :: TyFun a6989586621679442443 Bool -> Type) (t :: [a6989586621679442443]) = TakeWhile t t
- data DropWhileSym0 (l :: TyFun (TyFun a6989586621679442442 Bool -> Type) (TyFun [a6989586621679442442] [a6989586621679442442] -> Type))
- data DropWhileSym1 (l :: TyFun a6989586621679442442 Bool -> Type) (l :: TyFun [a6989586621679442442] [a6989586621679442442])
- type DropWhileSym2 (t :: TyFun a6989586621679442442 Bool -> Type) (t :: [a6989586621679442442]) = DropWhile t t
- data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679442441 Bool -> Type) (TyFun [a6989586621679442441] [a6989586621679442441] -> Type))
- data DropWhileEndSym1 (l :: TyFun a6989586621679442441 Bool -> Type) (l :: TyFun [a6989586621679442441] [a6989586621679442441])
- type DropWhileEndSym2 (t :: TyFun a6989586621679442441 Bool -> Type) (t :: [a6989586621679442441]) = DropWhileEnd t t
- data SpanSym0 (l :: TyFun (TyFun a6989586621679442440 Bool -> Type) (TyFun [a6989586621679442440] ([a6989586621679442440], [a6989586621679442440]) -> Type))
- data SpanSym1 (l :: TyFun a6989586621679442440 Bool -> Type) (l :: TyFun [a6989586621679442440] ([a6989586621679442440], [a6989586621679442440]))
- type SpanSym2 (t :: TyFun a6989586621679442440 Bool -> Type) (t :: [a6989586621679442440]) = Span t t
- data BreakSym0 (l :: TyFun (TyFun a6989586621679442439 Bool -> Type) (TyFun [a6989586621679442439] ([a6989586621679442439], [a6989586621679442439]) -> Type))
- data BreakSym1 (l :: TyFun a6989586621679442439 Bool -> Type) (l :: TyFun [a6989586621679442439] ([a6989586621679442439], [a6989586621679442439]))
- type BreakSym2 (t :: TyFun a6989586621679442439 Bool -> Type) (t :: [a6989586621679442439]) = Break t t
- data GroupSym0 (l :: TyFun [a6989586621679442435] [[a6989586621679442435]])
- type GroupSym1 (t :: [a6989586621679442435]) = Group t
- data InitsSym0 (l :: TyFun [a6989586621679442505] [[a6989586621679442505]])
- type InitsSym1 (t :: [a6989586621679442505]) = Inits t
- data TailsSym0 (l :: TyFun [a6989586621679442504] [[a6989586621679442504]])
- type TailsSym1 (t :: [a6989586621679442504]) = Tails t
- data IsPrefixOfSym0 (l :: TyFun [a6989586621679442503] (TyFun [a6989586621679442503] Bool -> Type))
- data IsPrefixOfSym1 (l :: [a6989586621679442503]) (l :: TyFun [a6989586621679442503] Bool)
- type IsPrefixOfSym2 (t :: [a6989586621679442503]) (t :: [a6989586621679442503]) = IsPrefixOf t t
- data IsSuffixOfSym0 (l :: TyFun [a6989586621679442502] (TyFun [a6989586621679442502] Bool -> Type))
- data IsSuffixOfSym1 (l :: [a6989586621679442502]) (l :: TyFun [a6989586621679442502] Bool)
- type IsSuffixOfSym2 (t :: [a6989586621679442502]) (t :: [a6989586621679442502]) = IsSuffixOf t t
- data IsInfixOfSym0 (l :: TyFun [a6989586621679442501] (TyFun [a6989586621679442501] Bool -> Type))
- data IsInfixOfSym1 (l :: [a6989586621679442501]) (l :: TyFun [a6989586621679442501] Bool)
- type IsInfixOfSym2 (t :: [a6989586621679442501]) (t :: [a6989586621679442501]) = IsInfixOf t t
- data ElemSym0 (l :: TyFun a6989586621679442500 (TyFun [a6989586621679442500] Bool -> Type))
- data ElemSym1 (l :: a6989586621679442500) (l :: TyFun [a6989586621679442500] Bool)
- type ElemSym2 (t :: a6989586621679442500) (t :: [a6989586621679442500]) = Elem t t
- data NotElemSym0 (l :: TyFun a6989586621679442499 (TyFun [a6989586621679442499] Bool -> Type))
- data NotElemSym1 (l :: a6989586621679442499) (l :: TyFun [a6989586621679442499] Bool)
- type NotElemSym2 (t :: a6989586621679442499) (t :: [a6989586621679442499]) = NotElem t t
- data LookupSym0 (l :: TyFun a6989586621679442428 (TyFun [(a6989586621679442428, b6989586621679442429)] (Maybe b6989586621679442429) -> Type))
- data LookupSym1 (l :: a6989586621679442428) (l :: TyFun [(a6989586621679442428, b6989586621679442429)] (Maybe b6989586621679442429))
- type LookupSym2 (t :: a6989586621679442428) (t :: [(a6989586621679442428, b6989586621679442429)]) = Lookup t t
- data FindSym0 (l :: TyFun (TyFun a6989586621679442450 Bool -> Type) (TyFun [a6989586621679442450] (Maybe a6989586621679442450) -> Type))
- data FindSym1 (l :: TyFun a6989586621679442450 Bool -> Type) (l :: TyFun [a6989586621679442450] (Maybe a6989586621679442450))
- type FindSym2 (t :: TyFun a6989586621679442450 Bool -> Type) (t :: [a6989586621679442450]) = Find t t
- data FilterSym0 (l :: TyFun (TyFun a6989586621679442451 Bool -> Type) (TyFun [a6989586621679442451] [a6989586621679442451] -> Type))
- data FilterSym1 (l :: TyFun a6989586621679442451 Bool -> Type) (l :: TyFun [a6989586621679442451] [a6989586621679442451])
- type FilterSym2 (t :: TyFun a6989586621679442451 Bool -> Type) (t :: [a6989586621679442451]) = Filter t t
- data PartitionSym0 (l :: TyFun (TyFun a6989586621679442427 Bool -> Type) (TyFun [a6989586621679442427] ([a6989586621679442427], [a6989586621679442427]) -> Type))
- data PartitionSym1 (l :: TyFun a6989586621679442427 Bool -> Type) (l :: TyFun [a6989586621679442427] ([a6989586621679442427], [a6989586621679442427]))
- type PartitionSym2 (t :: TyFun a6989586621679442427 Bool -> Type) (t :: [a6989586621679442427]) = Partition t t
- data (!!@#@$) (l :: TyFun [a6989586621679442420] (TyFun Nat a6989586621679442420 -> Type))
- data (l :: [a6989586621679442420]) !!@#@$$ (l :: TyFun Nat a6989586621679442420)
- type (!!@#@$$$) (t :: [a6989586621679442420]) (t :: Nat) = (!!) t t
- data ElemIndexSym0 (l :: TyFun a6989586621679442449 (TyFun [a6989586621679442449] (Maybe Nat) -> Type))
- data ElemIndexSym1 (l :: a6989586621679442449) (l :: TyFun [a6989586621679442449] (Maybe Nat))
- type ElemIndexSym2 (t :: a6989586621679442449) (t :: [a6989586621679442449]) = ElemIndex t t
- data ElemIndicesSym0 (l :: TyFun a6989586621679442448 (TyFun [a6989586621679442448] [Nat] -> Type))
- data ElemIndicesSym1 (l :: a6989586621679442448) (l :: TyFun [a6989586621679442448] [Nat])
- type ElemIndicesSym2 (t :: a6989586621679442448) (t :: [a6989586621679442448]) = ElemIndices t t
- data FindIndexSym0 (l :: TyFun (TyFun a6989586621679442447 Bool -> Type) (TyFun [a6989586621679442447] (Maybe Nat) -> Type))
- data FindIndexSym1 (l :: TyFun a6989586621679442447 Bool -> Type) (l :: TyFun [a6989586621679442447] (Maybe Nat))
- type FindIndexSym2 (t :: TyFun a6989586621679442447 Bool -> Type) (t :: [a6989586621679442447]) = FindIndex t t
- data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679442446 Bool -> Type) (TyFun [a6989586621679442446] [Nat] -> Type))
- data FindIndicesSym1 (l :: TyFun a6989586621679442446 Bool -> Type) (l :: TyFun [a6989586621679442446] [Nat])
- type FindIndicesSym2 (t :: TyFun a6989586621679442446 Bool -> Type) (t :: [a6989586621679442446]) = FindIndices t t
- data ZipSym0 (l :: TyFun [a6989586621679442497] (TyFun [b6989586621679442498] [(a6989586621679442497, b6989586621679442498)] -> Type))
- data ZipSym1 (l :: [a6989586621679442497]) (l :: TyFun [b6989586621679442498] [(a6989586621679442497, b6989586621679442498)])
- type ZipSym2 (t :: [a6989586621679442497]) (t :: [b6989586621679442498]) = Zip t t
- data Zip3Sym0 (l :: TyFun [a6989586621679442494] (TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type) -> Type))
- data Zip3Sym1 (l :: [a6989586621679442494]) (l :: TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type))
- data Zip3Sym2 (l :: [a6989586621679442494]) (l :: [b6989586621679442495]) (l :: TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)])
- type Zip3Sym3 (t :: [a6989586621679442494]) (t :: [b6989586621679442495]) (t :: [c6989586621679442496]) = Zip3 t t t
- data ZipWithSym0 (l :: TyFun (TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) (TyFun [a6989586621679442491] (TyFun [b6989586621679442492] [c6989586621679442493] -> Type) -> Type))
- data ZipWithSym1 (l :: TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) (l :: TyFun [a6989586621679442491] (TyFun [b6989586621679442492] [c6989586621679442493] -> Type))
- data ZipWithSym2 (l :: TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) (l :: [a6989586621679442491]) (l :: TyFun [b6989586621679442492] [c6989586621679442493])
- type ZipWithSym3 (t :: TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) (t :: [a6989586621679442491]) (t :: [b6989586621679442492]) = ZipWith t t t
- data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (TyFun [a6989586621679442487] (TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> Type) -> Type))
- data ZipWith3Sym1 (l :: TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679442487] (TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> Type))
- data ZipWith3Sym2 (l :: TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (l :: [a6989586621679442487]) (l :: TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type))
- data ZipWith3Sym3 (l :: TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (l :: [a6989586621679442487]) (l :: [b6989586621679442488]) (l :: TyFun [c6989586621679442489] [d6989586621679442490])
- type ZipWith3Sym4 (t :: TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (t :: [a6989586621679442487]) (t :: [b6989586621679442488]) (t :: [c6989586621679442489]) = ZipWith3 t t t t
- data UnzipSym0 (l :: TyFun [(a6989586621679442485, b6989586621679442486)] ([a6989586621679442485], [b6989586621679442486]))
- type UnzipSym1 (t :: [(a6989586621679442485, b6989586621679442486)]) = Unzip t
- data Unzip3Sym0 (l :: TyFun [(a6989586621679442482, b6989586621679442483, c6989586621679442484)] ([a6989586621679442482], [b6989586621679442483], [c6989586621679442484]))
- type Unzip3Sym1 (t :: [(a6989586621679442482, b6989586621679442483, c6989586621679442484)]) = Unzip3 t
- data Unzip4Sym0 (l :: TyFun [(a6989586621679442478, b6989586621679442479, c6989586621679442480, d6989586621679442481)] ([a6989586621679442478], [b6989586621679442479], [c6989586621679442480], [d6989586621679442481]))
- type Unzip4Sym1 (t :: [(a6989586621679442478, b6989586621679442479, c6989586621679442480, d6989586621679442481)]) = Unzip4 t
- data Unzip5Sym0 (l :: TyFun [(a6989586621679442473, b6989586621679442474, c6989586621679442475, d6989586621679442476, e6989586621679442477)] ([a6989586621679442473], [b6989586621679442474], [c6989586621679442475], [d6989586621679442476], [e6989586621679442477]))
- type Unzip5Sym1 (t :: [(a6989586621679442473, b6989586621679442474, c6989586621679442475, d6989586621679442476, e6989586621679442477)]) = Unzip5 t
- data Unzip6Sym0 (l :: TyFun [(a6989586621679442467, b6989586621679442468, c6989586621679442469, d6989586621679442470, e6989586621679442471, f6989586621679442472)] ([a6989586621679442467], [b6989586621679442468], [c6989586621679442469], [d6989586621679442470], [e6989586621679442471], [f6989586621679442472]))
- type Unzip6Sym1 (t :: [(a6989586621679442467, b6989586621679442468, c6989586621679442469, d6989586621679442470, e6989586621679442471, f6989586621679442472)]) = Unzip6 t
- data Unzip7Sym0 (l :: TyFun [(a6989586621679442460, b6989586621679442461, c6989586621679442462, d6989586621679442463, e6989586621679442464, f6989586621679442465, g6989586621679442466)] ([a6989586621679442460], [b6989586621679442461], [c6989586621679442462], [d6989586621679442463], [e6989586621679442464], [f6989586621679442465], [g6989586621679442466]))
- type Unzip7Sym1 (t :: [(a6989586621679442460, b6989586621679442461, c6989586621679442462, d6989586621679442463, e6989586621679442464, f6989586621679442465, g6989586621679442466)]) = Unzip7 t
- data UnlinesSym0 (l :: TyFun [Symbol] Symbol)
- type UnlinesSym1 (t :: [Symbol]) = Unlines t
- data UnwordsSym0 (l :: TyFun [Symbol] Symbol)
- type UnwordsSym1 (t :: [Symbol]) = Unwords t
- data NubSym0 (l :: TyFun [a6989586621679442419] [a6989586621679442419])
- type NubSym1 (t :: [a6989586621679442419]) = Nub t
- data DeleteSym0 (l :: TyFun a6989586621679442459 (TyFun [a6989586621679442459] [a6989586621679442459] -> Type))
- data DeleteSym1 (l :: a6989586621679442459) (l :: TyFun [a6989586621679442459] [a6989586621679442459])
- type DeleteSym2 (t :: a6989586621679442459) (t :: [a6989586621679442459]) = Delete t t
- data (\\@#@$) (l :: TyFun [a6989586621679442458] (TyFun [a6989586621679442458] [a6989586621679442458] -> Type))
- data (l :: [a6989586621679442458]) \\@#@$$ (l :: TyFun [a6989586621679442458] [a6989586621679442458])
- type (\\@#@$$$) (t :: [a6989586621679442458]) (t :: [a6989586621679442458]) = (\\) t t
- data UnionSym0 (l :: TyFun [a6989586621679442415] (TyFun [a6989586621679442415] [a6989586621679442415] -> Type))
- data UnionSym1 (l :: [a6989586621679442415]) (l :: TyFun [a6989586621679442415] [a6989586621679442415])
- type UnionSym2 (t :: [a6989586621679442415]) (t :: [a6989586621679442415]) = Union t t
- data IntersectSym0 (l :: TyFun [a6989586621679442445] (TyFun [a6989586621679442445] [a6989586621679442445] -> Type))
- data IntersectSym1 (l :: [a6989586621679442445]) (l :: TyFun [a6989586621679442445] [a6989586621679442445])
- type IntersectSym2 (t :: [a6989586621679442445]) (t :: [a6989586621679442445]) = Intersect t t
- data InsertSym0 (l :: TyFun a6989586621679442432 (TyFun [a6989586621679442432] [a6989586621679442432] -> Type))
- data InsertSym1 (l :: a6989586621679442432) (l :: TyFun [a6989586621679442432] [a6989586621679442432])
- type InsertSym2 (t :: a6989586621679442432) (t :: [a6989586621679442432]) = Insert t t
- data SortSym0 (l :: TyFun [a6989586621679442431] [a6989586621679442431])
- type SortSym1 (t :: [a6989586621679442431]) = Sort t
- data NubBySym0 (l :: TyFun (TyFun a6989586621679442418 (TyFun a6989586621679442418 Bool -> Type) -> Type) (TyFun [a6989586621679442418] [a6989586621679442418] -> Type))
- data NubBySym1 (l :: TyFun a6989586621679442418 (TyFun a6989586621679442418 Bool -> Type) -> Type) (l :: TyFun [a6989586621679442418] [a6989586621679442418])
- type NubBySym2 (t :: TyFun a6989586621679442418 (TyFun a6989586621679442418 Bool -> Type) -> Type) (t :: [a6989586621679442418]) = NubBy t t
- data DeleteBySym0 (l :: TyFun (TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) (TyFun a6989586621679442457 (TyFun [a6989586621679442457] [a6989586621679442457] -> Type) -> Type))
- data DeleteBySym1 (l :: TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) (l :: TyFun a6989586621679442457 (TyFun [a6989586621679442457] [a6989586621679442457] -> Type))
- data DeleteBySym2 (l :: TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) (l :: a6989586621679442457) (l :: TyFun [a6989586621679442457] [a6989586621679442457])
- type DeleteBySym3 (t :: TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) (t :: a6989586621679442457) (t :: [a6989586621679442457]) = DeleteBy t t t
- data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) (TyFun [a6989586621679442456] (TyFun [a6989586621679442456] [a6989586621679442456] -> Type) -> Type))
- data DeleteFirstsBySym1 (l :: TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) (l :: TyFun [a6989586621679442456] (TyFun [a6989586621679442456] [a6989586621679442456] -> Type))
- data DeleteFirstsBySym2 (l :: TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) (l :: [a6989586621679442456]) (l :: TyFun [a6989586621679442456] [a6989586621679442456])
- type DeleteFirstsBySym3 (t :: TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) (t :: [a6989586621679442456]) (t :: [a6989586621679442456]) = DeleteFirstsBy t t t
- data UnionBySym0 (l :: TyFun (TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) (TyFun [a6989586621679442416] (TyFun [a6989586621679442416] [a6989586621679442416] -> Type) -> Type))
- data UnionBySym1 (l :: TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) (l :: TyFun [a6989586621679442416] (TyFun [a6989586621679442416] [a6989586621679442416] -> Type))
- data UnionBySym2 (l :: TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) (l :: [a6989586621679442416]) (l :: TyFun [a6989586621679442416] [a6989586621679442416])
- type UnionBySym3 (t :: TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) (t :: [a6989586621679442416]) (t :: [a6989586621679442416]) = UnionBy t t t
- data IntersectBySym0 (l :: TyFun (TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) (TyFun [a6989586621679442444] (TyFun [a6989586621679442444] [a6989586621679442444] -> Type) -> Type))
- data IntersectBySym1 (l :: TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) (l :: TyFun [a6989586621679442444] (TyFun [a6989586621679442444] [a6989586621679442444] -> Type))
- data IntersectBySym2 (l :: TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) (l :: [a6989586621679442444]) (l :: TyFun [a6989586621679442444] [a6989586621679442444])
- type IntersectBySym3 (t :: TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) (t :: [a6989586621679442444]) (t :: [a6989586621679442444]) = IntersectBy t t t
- data GroupBySym0 (l :: TyFun (TyFun a6989586621679442430 (TyFun a6989586621679442430 Bool -> Type) -> Type) (TyFun [a6989586621679442430] [[a6989586621679442430]] -> Type))
- data GroupBySym1 (l :: TyFun a6989586621679442430 (TyFun a6989586621679442430 Bool -> Type) -> Type) (l :: TyFun [a6989586621679442430] [[a6989586621679442430]])
- type GroupBySym2 (t :: TyFun a6989586621679442430 (TyFun a6989586621679442430 Bool -> Type) -> Type) (t :: [a6989586621679442430]) = GroupBy t t
- data SortBySym0 (l :: TyFun (TyFun a6989586621679442455 (TyFun a6989586621679442455 Ordering -> Type) -> Type) (TyFun [a6989586621679442455] [a6989586621679442455] -> Type))
- data SortBySym1 (l :: TyFun a6989586621679442455 (TyFun a6989586621679442455 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679442455] [a6989586621679442455])
- type SortBySym2 (t :: TyFun a6989586621679442455 (TyFun a6989586621679442455 Ordering -> Type) -> Type) (t :: [a6989586621679442455]) = SortBy t t
- data InsertBySym0 (l :: TyFun (TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) (TyFun a6989586621679442454 (TyFun [a6989586621679442454] [a6989586621679442454] -> Type) -> Type))
- data InsertBySym1 (l :: TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) (l :: TyFun a6989586621679442454 (TyFun [a6989586621679442454] [a6989586621679442454] -> Type))
- data InsertBySym2 (l :: TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) (l :: a6989586621679442454) (l :: TyFun [a6989586621679442454] [a6989586621679442454])
- type InsertBySym3 (t :: TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) (t :: a6989586621679442454) (t :: [a6989586621679442454]) = InsertBy t t t
- data MaximumBySym0 (l :: TyFun (TyFun a6989586621679442453 (TyFun a6989586621679442453 Ordering -> Type) -> Type) (TyFun [a6989586621679442453] a6989586621679442453 -> Type))
- data MaximumBySym1 (l :: TyFun a6989586621679442453 (TyFun a6989586621679442453 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679442453] a6989586621679442453)
- type MaximumBySym2 (t :: TyFun a6989586621679442453 (TyFun a6989586621679442453 Ordering -> Type) -> Type) (t :: [a6989586621679442453]) = MaximumBy t t
- data MinimumBySym0 (l :: TyFun (TyFun a6989586621679442452 (TyFun a6989586621679442452 Ordering -> Type) -> Type) (TyFun [a6989586621679442452] a6989586621679442452 -> Type))
- data MinimumBySym1 (l :: TyFun a6989586621679442452 (TyFun a6989586621679442452 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679442452] a6989586621679442452)
- type MinimumBySym2 (t :: TyFun a6989586621679442452 (TyFun a6989586621679442452 Ordering -> Type) -> Type) (t :: [a6989586621679442452]) = MinimumBy t t
- data GenericLengthSym0 (l :: TyFun [a6989586621679442414] i6989586621679442413)
- type GenericLengthSym1 (t :: [a6989586621679442414]) = GenericLength t
The singleton for lists
data family Sing (a :: k) infixr 5 Source #
The singleton kind-indexed data family.
Instances
| data Sing (z :: Bool) Source # | |
| data Sing (z :: Ordering) Source # | |
| data Sing (a :: Type) Source # | |
| data Sing (n :: Nat) Source # | |
| data Sing (n :: Symbol) Source # | |
| data Sing (z :: ()) Source # | |
| data Sing (z :: Void) Source # | |
| data Sing (z :: [a]) Source # | |
| data Sing (z :: Maybe a) Source # | |
| data Sing (z :: NonEmpty a) Source # | |
| data Sing (z :: Either a b) Source # | |
| data Sing (z :: (a, b)) Source # | |
| data Sing (f :: k1 ~> k2) Source # | |
| data Sing (z :: (a, b, c)) Source # | |
| data Sing (z :: (a, b, c, d)) Source # | |
| data Sing (z :: (a, b, c, d, e)) Source # | |
| data Sing (z :: (a, b, c, d, e, f)) Source # | |
| data Sing (z :: (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 ((:) _ 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 _ '[] = '[] | |
| 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 _ '[x] = x | |
| Foldr1 f ((:) x ((:) wild_6989586621679443002 wild_6989586621679443004)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let6989586621679453800XsSym4 f x wild_6989586621679443002 wild_6989586621679443004)) | |
| Foldr1 _ '[] = 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 AnySym0 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 (Let6989586621679451850Sum'Sym1 l) l) (FromInteger 0) |
type family Product (a :: [a]) :: a where ... Source #
Equations
| Product l = Apply (Apply (Let6989586621679451826ProdSym1 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 _ '[] = '[] | |
| Scanr1 _ '[x] = Apply (Apply (:@#@$) x) '[] | |
| Scanr1 f ((:) x ((:) wild_6989586621679443022 wild_6989586621679443024)) = Case_6989586621679453512 f x wild_6989586621679443022 wild_6989586621679443024 (Let6989586621679453493Scrutinee_6989586621679443016Sym4 f x wild_6989586621679443022 wild_6989586621679443024) |
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_6989586621679451813 n x (Let6989586621679451805Scrutinee_6989586621679443118Sym2 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_6989586621679453141 f b (Let6989586621679453133Scrutinee_6989586621679443026Sym2 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 _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679452126XsSym0) Let6989586621679452126XsSym0 | |
| Span p ((:) x xs') = Case_6989586621679452156 p x xs' (Let6989586621679452143Scrutinee_6989586621679443098Sym3 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 _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679452033XsSym0) Let6989586621679452033XsSym0 | |
| Break p ((:) x xs') = Case_6989586621679452063 p x xs' (Let6989586621679452050Scrutinee_6989586621679443100Sym3 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 '[] ((:) _ _) = TrueSym0 | |
| IsPrefixOf ((:) _ _) '[] = 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) infix 4 Source #
sNotElem :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) infix 4 Source #
type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... Source #
Equations
| Lookup _key '[] = NothingSym0 | |
| Lookup key ((:) '(x, y) xys) = Case_6989586621679451954 key x y xys (Let6989586621679451935Scrutinee_6989586621679443114Sym4 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_6989586621679452385 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FilterSym0 p)) a_6989586621679452385 |
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) infixl 9 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_6989586621679452991 = Apply (Apply FindIndicesSym0 (Apply (==@#@$) x)) a_6989586621679452991 |
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_6989586621679453004 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679453004 |
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 '[] '[] ((:) _ _) = '[] | |
| Zip3 '[] ((:) _ _) '[] = '[] | |
| Zip3 '[] ((:) _ _) ((:) _ _) = '[] | |
| Zip3 ((:) _ _) '[] '[] = '[] | |
| Zip3 ((:) _ _) '[] ((:) _ _) = '[] | |
| Zip3 ((:) _ _) ((:) _ _) '[] = '[] |
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 #
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 _ '[] '[] '[] = '[] | |
| ZipWith3 _ '[] '[] ((:) _ _) = '[] | |
| ZipWith3 _ '[] ((:) _ _) '[] = '[] | |
| ZipWith3 _ '[] ((:) _ _) ((:) _ _) = '[] | |
| ZipWith3 _ ((:) _ _) '[] '[] = '[] | |
| ZipWith3 _ ((:) _ _) '[] ((:) _ _) = '[] | |
| ZipWith3 _ ((:) _ _) ((:) _ _) '[] = '[] |
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
Functions on Symbols
"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_6989586621679452474 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679452474 |
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_6989586621679452537 a_6989586621679452539 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679452537) a_6989586621679452539 |
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 _ '[] '[] = '[] | |
| IntersectBy _ '[] ((:) _ _) = '[] | |
| IntersectBy _ ((:) _ _) '[] = '[] | |
| IntersectBy eq ((:) wild_6989586621679443084 wild_6989586621679443086) ((:) wild_6989586621679443088 wild_6989586621679443090) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679453690Sym0 eq) wild_6989586621679443084) wild_6989586621679443086) wild_6989586621679443088) wild_6989586621679443090)) (Let6989586621679453639XsSym5 eq wild_6989586621679443084 wild_6989586621679443086 wild_6989586621679443088 wild_6989586621679443090) |
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 _ '[] = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" | |
| MaximumBy cmp ((:) wild_6989586621679443070 wild_6989586621679443072) = Apply (Apply Foldl1Sym0 (Let6989586621679453856MaxBySym3 cmp wild_6989586621679443070 wild_6989586621679443072)) (Let6989586621679453843XsSym3 cmp wild_6989586621679443070 wild_6989586621679443072) |
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 _ '[] = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" | |
| MinimumBy cmp ((:) wild_6989586621679443076 wild_6989586621679443078) = Apply (Apply Foldl1Sym0 (Let6989586621679453940MinBySym3 cmp wild_6989586621679443076 wild_6989586621679443078)) (Let6989586621679453927XsSym3 cmp wild_6989586621679443076 wild_6989586621679443078) |
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 ((:) _ 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 #
Instances
| SuppressUnusedWarnings ((:@#@$) :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply ((:@#@$) :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type) -> *) (l :: a3530822107858468865) Source # | |
data (l :: a3530822107858468865) :@#@$$ (l :: TyFun [a3530822107858468865] [a3530822107858468865]) Source #
type (++@#@$$$) (t :: [a6989586621679419904]) (t :: [a6989586621679419904]) = (++) t t Source #
data (l :: [a6989586621679419904]) ++@#@$$ (l :: TyFun [a6989586621679419904] [a6989586621679419904]) Source #
data (++@#@$) (l :: TyFun [a6989586621679419904] (TyFun [a6989586621679419904] [a6989586621679419904] -> Type)) Source #
Instances
| SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679419904] (TyFun [a6989586621679419904] [a6989586621679419904] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply ((++@#@$) :: TyFun [a6989586621679419904] (TyFun [a6989586621679419904] [a6989586621679419904] -> Type) -> *) (l :: [a6989586621679419904]) Source # | |
data LengthSym0 (l :: TyFun [a6989586621679442423] Nat) Source #
Instances
| SuppressUnusedWarnings (LengthSym0 :: TyFun [a6989586621679442423] Nat -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (LengthSym0 :: TyFun [a] Nat -> *) (l :: [a]) Source # | |
type LengthSym1 (t :: [a6989586621679442423]) = Length t Source #
data MapSym0 (l :: TyFun (TyFun a6989586621679419905 b6989586621679419906 -> Type) (TyFun [a6989586621679419905] [b6989586621679419906] -> Type)) Source #
Instances
| SuppressUnusedWarnings (MapSym0 :: TyFun (TyFun a6989586621679419905 b6989586621679419906 -> Type) (TyFun [a6989586621679419905] [b6989586621679419906] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MapSym0 :: TyFun (TyFun a6989586621679419905 b6989586621679419906 -> Type) (TyFun [a6989586621679419905] [b6989586621679419906] -> Type) -> *) (l :: TyFun a6989586621679419905 b6989586621679419906 -> Type) Source # | |
data MapSym1 (l :: TyFun a6989586621679419905 b6989586621679419906 -> Type) (l :: TyFun [a6989586621679419905] [b6989586621679419906]) Source #
type MapSym2 (t :: TyFun a6989586621679419905 b6989586621679419906 -> Type) (t :: [a6989586621679419905]) = Map t t Source #
data ReverseSym0 (l :: TyFun [a6989586621679442536] [a6989586621679442536]) Source #
Instances
| SuppressUnusedWarnings (ReverseSym0 :: TyFun [a6989586621679442536] [a6989586621679442536] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ReverseSym0 :: TyFun [a] [a] -> *) (l :: [a]) Source # | |
type ReverseSym1 (t :: [a6989586621679442536]) = Reverse t Source #
data IntersperseSym0 (l :: TyFun a6989586621679442535 (TyFun [a6989586621679442535] [a6989586621679442535] -> Type)) Source #
Instances
| SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679442535 (TyFun [a6989586621679442535] [a6989586621679442535] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IntersperseSym0 :: TyFun a6989586621679442535 (TyFun [a6989586621679442535] [a6989586621679442535] -> Type) -> *) (l :: a6989586621679442535) Source # | |
type Apply (IntersperseSym0 :: TyFun a6989586621679442535 (TyFun [a6989586621679442535] [a6989586621679442535] -> Type) -> *) (l :: a6989586621679442535) = IntersperseSym1 l | |
data IntersperseSym1 (l :: a6989586621679442535) (l :: TyFun [a6989586621679442535] [a6989586621679442535]) Source #
Instances
| SuppressUnusedWarnings (IntersperseSym1 :: a6989586621679442535 -> TyFun [a6989586621679442535] [a6989586621679442535] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IntersperseSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type IntersperseSym2 (t :: a6989586621679442535) (t :: [a6989586621679442535]) = Intersperse t t Source #
data IntercalateSym0 (l :: TyFun [a6989586621679442534] (TyFun [[a6989586621679442534]] [a6989586621679442534] -> Type)) Source #
Instances
| SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a6989586621679442534] (TyFun [[a6989586621679442534]] [a6989586621679442534] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IntercalateSym0 :: TyFun [a6989586621679442534] (TyFun [[a6989586621679442534]] [a6989586621679442534] -> Type) -> *) (l :: [a6989586621679442534]) Source # | |
type Apply (IntercalateSym0 :: TyFun [a6989586621679442534] (TyFun [[a6989586621679442534]] [a6989586621679442534] -> Type) -> *) (l :: [a6989586621679442534]) = IntercalateSym1 l | |
data IntercalateSym1 (l :: [a6989586621679442534]) (l :: TyFun [[a6989586621679442534]] [a6989586621679442534]) Source #
Instances
| SuppressUnusedWarnings (IntercalateSym1 :: [a6989586621679442534] -> TyFun [[a6989586621679442534]] [a6989586621679442534] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IntercalateSym1 l1 :: TyFun [[a]] [a] -> *) (l2 :: [[a]]) Source # | |
type IntercalateSym2 (t :: [a6989586621679442534]) (t :: [[a6989586621679442534]]) = Intercalate t t Source #
data TransposeSym0 (l :: TyFun [[a6989586621679442421]] [[a6989586621679442421]]) Source #
Instances
| SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a6989586621679442421]] [[a6989586621679442421]] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> *) (l :: [[a]]) Source # | |
type TransposeSym1 (t :: [[a6989586621679442421]]) = Transpose t Source #
data SubsequencesSym0 (l :: TyFun [a6989586621679442533] [[a6989586621679442533]]) Source #
Instances
| SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a6989586621679442533] [[a6989586621679442533]] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> *) (l :: [a]) Source # | |
type SubsequencesSym1 (t :: [a6989586621679442533]) = Subsequences t Source #
data PermutationsSym0 (l :: TyFun [a6989586621679442530] [[a6989586621679442530]]) Source #
Instances
| SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a6989586621679442530] [[a6989586621679442530]] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> *) (l :: [a]) Source # | |
type PermutationsSym1 (t :: [a6989586621679442530]) = Permutations t Source #
data FoldlSym0 (l :: TyFun (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (FoldlSym0 :: TyFun (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FoldlSym0 :: TyFun (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> Type) -> *) (l :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) Source # | |
type Apply (FoldlSym0 :: TyFun (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> Type) -> *) (l :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) = FoldlSym1 l | |
data FoldlSym1 (l :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (l :: TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type)) Source #
Instances
| SuppressUnusedWarnings (FoldlSym1 :: (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) -> TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FoldlSym1 l1 :: TyFun b6989586621679259259 (TyFun [a6989586621679259258] b6989586621679259259 -> Type) -> *) (l2 :: b6989586621679259259) Source # | |
data FoldlSym2 (l :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (l :: b6989586621679259259) (l :: TyFun [a6989586621679259258] b6989586621679259259) Source #
Instances
| SuppressUnusedWarnings (FoldlSym2 :: (TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) -> b6989586621679259259 -> TyFun [a6989586621679259258] b6989586621679259259 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FoldlSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) Source # | |
type FoldlSym3 (t :: TyFun b6989586621679259259 (TyFun a6989586621679259258 b6989586621679259259 -> Type) -> Type) (t :: b6989586621679259259) (t :: [a6989586621679259258]) = Foldl t t t Source #
data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) (TyFun b6989586621679442529 (TyFun [a6989586621679442528] b6989586621679442529 -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) (TyFun b6989586621679442529 (TyFun [a6989586621679442528] b6989586621679442529 -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Foldl'Sym0 :: TyFun (TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) (TyFun b6989586621679442529 (TyFun [a6989586621679442528] b6989586621679442529 -> Type) -> Type) -> *) (l :: TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) Source # | |
type Apply (Foldl'Sym0 :: TyFun (TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) (TyFun b6989586621679442529 (TyFun [a6989586621679442528] b6989586621679442529 -> Type) -> Type) -> *) (l :: TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) = Foldl'Sym1 l | |
data Foldl'Sym1 (l :: TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) (l :: TyFun b6989586621679442529 (TyFun [a6989586621679442528] b6989586621679442529 -> Type)) Source #
Instances
| SuppressUnusedWarnings (Foldl'Sym1 :: (TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) -> TyFun b6989586621679442529 (TyFun [a6989586621679442528] b6989586621679442529 -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Foldl'Sym1 l1 :: TyFun b6989586621679442529 (TyFun [a6989586621679442528] b6989586621679442529 -> Type) -> *) (l2 :: b6989586621679442529) Source # | |
type Apply (Foldl'Sym1 l1 :: TyFun b6989586621679442529 (TyFun [a6989586621679442528] b6989586621679442529 -> Type) -> *) (l2 :: b6989586621679442529) = Foldl'Sym2 l1 l2 | |
data Foldl'Sym2 (l :: TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) (l :: b6989586621679442529) (l :: TyFun [a6989586621679442528] b6989586621679442529) Source #
Instances
| SuppressUnusedWarnings (Foldl'Sym2 :: (TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) -> b6989586621679442529 -> TyFun [a6989586621679442528] b6989586621679442529 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Foldl'Sym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) Source # | |
type Foldl'Sym3 (t :: TyFun b6989586621679442529 (TyFun a6989586621679442528 b6989586621679442529 -> Type) -> Type) (t :: b6989586621679442529) (t :: [a6989586621679442528]) = Foldl' t t t Source #
data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) (TyFun [a6989586621679442527] a6989586621679442527 -> Type)) Source #
Instances
| SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) (TyFun [a6989586621679442527] a6989586621679442527 -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Foldl1Sym0 :: TyFun (TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) (TyFun [a6989586621679442527] a6989586621679442527 -> Type) -> *) (l :: TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) Source # | |
type Apply (Foldl1Sym0 :: TyFun (TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) (TyFun [a6989586621679442527] a6989586621679442527 -> Type) -> *) (l :: TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) = Foldl1Sym1 l | |
data Foldl1Sym1 (l :: TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) (l :: TyFun [a6989586621679442527] a6989586621679442527) Source #
Instances
| SuppressUnusedWarnings (Foldl1Sym1 :: (TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) -> TyFun [a6989586621679442527] a6989586621679442527 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Foldl1Sym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # | |
type Foldl1Sym2 (t :: TyFun a6989586621679442527 (TyFun a6989586621679442527 a6989586621679442527 -> Type) -> Type) (t :: [a6989586621679442527]) = Foldl1 t t Source #
data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) (TyFun [a6989586621679442526] a6989586621679442526 -> Type)) Source #
Instances
| SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) (TyFun [a6989586621679442526] a6989586621679442526 -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Foldl1'Sym0 :: TyFun (TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) (TyFun [a6989586621679442526] a6989586621679442526 -> Type) -> *) (l :: TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) Source # | |
type Apply (Foldl1'Sym0 :: TyFun (TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) (TyFun [a6989586621679442526] a6989586621679442526 -> Type) -> *) (l :: TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) = Foldl1'Sym1 l | |
data Foldl1'Sym1 (l :: TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) (l :: TyFun [a6989586621679442526] a6989586621679442526) Source #
Instances
| SuppressUnusedWarnings (Foldl1'Sym1 :: (TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) -> TyFun [a6989586621679442526] a6989586621679442526 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Foldl1'Sym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # | |
type Foldl1'Sym2 (t :: TyFun a6989586621679442526 (TyFun a6989586621679442526 a6989586621679442526 -> Type) -> Type) (t :: [a6989586621679442526]) = Foldl1' t t Source #
data FoldrSym0 (l :: TyFun (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (FoldrSym0 :: TyFun (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FoldrSym0 :: TyFun (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> Type) -> *) (l :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) Source # | |
type Apply (FoldrSym0 :: TyFun (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> Type) -> *) (l :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) = FoldrSym1 l | |
data FoldrSym1 (l :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (l :: TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type)) Source #
Instances
| SuppressUnusedWarnings (FoldrSym1 :: (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) -> TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FoldrSym1 l1 :: TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> *) (l2 :: b6989586621679419908) Source # | |
data FoldrSym2 (l :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (l :: b6989586621679419908) (l :: TyFun [a6989586621679419907] b6989586621679419908) Source #
Instances
| SuppressUnusedWarnings (FoldrSym2 :: (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) -> b6989586621679419908 -> TyFun [a6989586621679419907] b6989586621679419908 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FoldrSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) Source # | |
type FoldrSym3 (t :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (t :: b6989586621679419908) (t :: [a6989586621679419907]) = Foldr t t t Source #
data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) (TyFun [a6989586621679442525] a6989586621679442525 -> Type)) Source #
Instances
| SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) (TyFun [a6989586621679442525] a6989586621679442525 -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Foldr1Sym0 :: TyFun (TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) (TyFun [a6989586621679442525] a6989586621679442525 -> Type) -> *) (l :: TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) Source # | |
type Apply (Foldr1Sym0 :: TyFun (TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) (TyFun [a6989586621679442525] a6989586621679442525 -> Type) -> *) (l :: TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) = Foldr1Sym1 l | |
data Foldr1Sym1 (l :: TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) (l :: TyFun [a6989586621679442525] a6989586621679442525) Source #
Instances
| SuppressUnusedWarnings (Foldr1Sym1 :: (TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) -> TyFun [a6989586621679442525] a6989586621679442525 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Foldr1Sym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # | |
type Foldr1Sym2 (t :: TyFun a6989586621679442525 (TyFun a6989586621679442525 a6989586621679442525 -> Type) -> Type) (t :: [a6989586621679442525]) = Foldr1 t t Source #
data ConcatSym0 (l :: TyFun [[a6989586621679442524]] [a6989586621679442524]) Source #
Instances
| SuppressUnusedWarnings (ConcatSym0 :: TyFun [[a6989586621679442524]] [a6989586621679442524] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ConcatSym0 :: TyFun [[a]] [a] -> *) (l :: [[a]]) Source # | |
type ConcatSym1 (t :: [[a6989586621679442524]]) = Concat t Source #
data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679442522 [b6989586621679442523] -> Type) (TyFun [a6989586621679442522] [b6989586621679442523] -> Type)) Source #
Instances
| SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (TyFun a6989586621679442522 [b6989586621679442523] -> Type) (TyFun [a6989586621679442522] [b6989586621679442523] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ConcatMapSym0 :: TyFun (TyFun a6989586621679442522 [b6989586621679442523] -> Type) (TyFun [a6989586621679442522] [b6989586621679442523] -> Type) -> *) (l :: TyFun a6989586621679442522 [b6989586621679442523] -> Type) Source # | |
data ConcatMapSym1 (l :: TyFun a6989586621679442522 [b6989586621679442523] -> Type) (l :: TyFun [a6989586621679442522] [b6989586621679442523]) Source #
Instances
| SuppressUnusedWarnings (ConcatMapSym1 :: (TyFun a6989586621679442522 [b6989586621679442523] -> Type) -> TyFun [a6989586621679442522] [b6989586621679442523] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ConcatMapSym1 l1 :: TyFun [a] [b] -> *) (l2 :: [a]) Source # | |
type ConcatMapSym2 (t :: TyFun a6989586621679442522 [b6989586621679442523] -> Type) (t :: [a6989586621679442522]) = ConcatMap t t Source #
data AnySym0 (l :: TyFun (TyFun a6989586621679442520 Bool -> Type) (TyFun [a6989586621679442520] Bool -> Type)) Source #
Instances
| SuppressUnusedWarnings (AnySym0 :: TyFun (TyFun a6989586621679442520 Bool -> Type) (TyFun [a6989586621679442520] Bool -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (AnySym0 :: TyFun (TyFun a6989586621679442520 Bool -> Type) (TyFun [a6989586621679442520] Bool -> Type) -> *) (l :: TyFun a6989586621679442520 Bool -> Type) Source # | |
data AnySym1 (l :: TyFun a6989586621679442520 Bool -> Type) (l :: TyFun [a6989586621679442520] Bool) Source #
type AnySym2 (t :: TyFun a6989586621679442520 Bool -> Type) (t :: [a6989586621679442520]) = Any t t Source #
data AllSym0 (l :: TyFun (TyFun a6989586621679442521 Bool -> Type) (TyFun [a6989586621679442521] Bool -> Type)) Source #
Instances
| SuppressUnusedWarnings (AllSym0 :: TyFun (TyFun a6989586621679442521 Bool -> Type) (TyFun [a6989586621679442521] Bool -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (AllSym0 :: TyFun (TyFun a6989586621679442521 Bool -> Type) (TyFun [a6989586621679442521] Bool -> Type) -> *) (l :: TyFun a6989586621679442521 Bool -> Type) Source # | |
data AllSym1 (l :: TyFun a6989586621679442521 Bool -> Type) (l :: TyFun [a6989586621679442521] Bool) Source #
type AllSym2 (t :: TyFun a6989586621679442521 Bool -> Type) (t :: [a6989586621679442521]) = All t t Source #
data ProductSym0 (l :: TyFun [a6989586621679442424] a6989586621679442424) Source #
Instances
| SuppressUnusedWarnings (ProductSym0 :: TyFun [a6989586621679442424] a6989586621679442424 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ProductSym0 :: TyFun [a] a -> *) (l :: [a]) Source # | |
type ProductSym1 (t :: [a6989586621679442424]) = Product t Source #
data MaximumSym0 (l :: TyFun [a6989586621679442434] a6989586621679442434) Source #
Instances
| SuppressUnusedWarnings (MaximumSym0 :: TyFun [a6989586621679442434] a6989586621679442434 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MaximumSym0 :: TyFun [a] a -> *) (l :: [a]) Source # | |
type MaximumSym1 (t :: [a6989586621679442434]) = Maximum t Source #
data MinimumSym0 (l :: TyFun [a6989586621679442433] a6989586621679442433) Source #
Instances
| SuppressUnusedWarnings (MinimumSym0 :: TyFun [a6989586621679442433] a6989586621679442433 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MinimumSym0 :: TyFun [a] a -> *) (l :: [a]) Source # | |
type MinimumSym1 (t :: [a6989586621679442433]) = Minimum t Source #
data ScanlSym0 (l :: TyFun (TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) (TyFun b6989586621679442518 (TyFun [a6989586621679442519] [b6989586621679442518] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (ScanlSym0 :: TyFun (TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) (TyFun b6989586621679442518 (TyFun [a6989586621679442519] [b6989586621679442518] -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ScanlSym0 :: TyFun (TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) (TyFun b6989586621679442518 (TyFun [a6989586621679442519] [b6989586621679442518] -> Type) -> Type) -> *) (l :: TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) Source # | |
type Apply (ScanlSym0 :: TyFun (TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) (TyFun b6989586621679442518 (TyFun [a6989586621679442519] [b6989586621679442518] -> Type) -> Type) -> *) (l :: TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) = ScanlSym1 l | |
data ScanlSym1 (l :: TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) (l :: TyFun b6989586621679442518 (TyFun [a6989586621679442519] [b6989586621679442518] -> Type)) Source #
Instances
| SuppressUnusedWarnings (ScanlSym1 :: (TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) -> TyFun b6989586621679442518 (TyFun [a6989586621679442519] [b6989586621679442518] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ScanlSym1 l1 :: TyFun b6989586621679442518 (TyFun [a6989586621679442519] [b6989586621679442518] -> Type) -> *) (l2 :: b6989586621679442518) Source # | |
data ScanlSym2 (l :: TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) (l :: b6989586621679442518) (l :: TyFun [a6989586621679442519] [b6989586621679442518]) Source #
Instances
| SuppressUnusedWarnings (ScanlSym2 :: (TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) -> b6989586621679442518 -> TyFun [a6989586621679442519] [b6989586621679442518] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ScanlSym2 l1 l2 :: TyFun [a] [b] -> *) (l3 :: [a]) Source # | |
type ScanlSym3 (t :: TyFun b6989586621679442518 (TyFun a6989586621679442519 b6989586621679442518 -> Type) -> Type) (t :: b6989586621679442518) (t :: [a6989586621679442519]) = Scanl t t t Source #
data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) (TyFun [a6989586621679442517] [a6989586621679442517] -> Type)) Source #
Instances
| SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) (TyFun [a6989586621679442517] [a6989586621679442517] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Scanl1Sym0 :: TyFun (TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) (TyFun [a6989586621679442517] [a6989586621679442517] -> Type) -> *) (l :: TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) Source # | |
type Apply (Scanl1Sym0 :: TyFun (TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) (TyFun [a6989586621679442517] [a6989586621679442517] -> Type) -> *) (l :: TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) = Scanl1Sym1 l | |
data Scanl1Sym1 (l :: TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) (l :: TyFun [a6989586621679442517] [a6989586621679442517]) Source #
Instances
| SuppressUnusedWarnings (Scanl1Sym1 :: (TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) -> TyFun [a6989586621679442517] [a6989586621679442517] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Scanl1Sym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type Scanl1Sym2 (t :: TyFun a6989586621679442517 (TyFun a6989586621679442517 a6989586621679442517 -> Type) -> Type) (t :: [a6989586621679442517]) = Scanl1 t t Source #
data ScanrSym0 (l :: TyFun (TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) (TyFun b6989586621679442516 (TyFun [a6989586621679442515] [b6989586621679442516] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (ScanrSym0 :: TyFun (TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) (TyFun b6989586621679442516 (TyFun [a6989586621679442515] [b6989586621679442516] -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ScanrSym0 :: TyFun (TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) (TyFun b6989586621679442516 (TyFun [a6989586621679442515] [b6989586621679442516] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) Source # | |
type Apply (ScanrSym0 :: TyFun (TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) (TyFun b6989586621679442516 (TyFun [a6989586621679442515] [b6989586621679442516] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) = ScanrSym1 l | |
data ScanrSym1 (l :: TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) (l :: TyFun b6989586621679442516 (TyFun [a6989586621679442515] [b6989586621679442516] -> Type)) Source #
Instances
| SuppressUnusedWarnings (ScanrSym1 :: (TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) -> TyFun b6989586621679442516 (TyFun [a6989586621679442515] [b6989586621679442516] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ScanrSym1 l1 :: TyFun b6989586621679442516 (TyFun [a6989586621679442515] [b6989586621679442516] -> Type) -> *) (l2 :: b6989586621679442516) Source # | |
data ScanrSym2 (l :: TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) (l :: b6989586621679442516) (l :: TyFun [a6989586621679442515] [b6989586621679442516]) Source #
Instances
| SuppressUnusedWarnings (ScanrSym2 :: (TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) -> b6989586621679442516 -> TyFun [a6989586621679442515] [b6989586621679442516] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ScanrSym2 l1 l2 :: TyFun [a] [b] -> *) (l3 :: [a]) Source # | |
type ScanrSym3 (t :: TyFun a6989586621679442515 (TyFun b6989586621679442516 b6989586621679442516 -> Type) -> Type) (t :: b6989586621679442516) (t :: [a6989586621679442515]) = Scanr t t t Source #
data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) (TyFun [a6989586621679442514] [a6989586621679442514] -> Type)) Source #
Instances
| SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) (TyFun [a6989586621679442514] [a6989586621679442514] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Scanr1Sym0 :: TyFun (TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) (TyFun [a6989586621679442514] [a6989586621679442514] -> Type) -> *) (l :: TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) Source # | |
type Apply (Scanr1Sym0 :: TyFun (TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) (TyFun [a6989586621679442514] [a6989586621679442514] -> Type) -> *) (l :: TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) = Scanr1Sym1 l | |
data Scanr1Sym1 (l :: TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) (l :: TyFun [a6989586621679442514] [a6989586621679442514]) Source #
Instances
| SuppressUnusedWarnings (Scanr1Sym1 :: (TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) -> TyFun [a6989586621679442514] [a6989586621679442514] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Scanr1Sym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type Scanr1Sym2 (t :: TyFun a6989586621679442514 (TyFun a6989586621679442514 a6989586621679442514 -> Type) -> Type) (t :: [a6989586621679442514]) = Scanr1 t t Source #
data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) (TyFun acc6989586621679442511 (TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) (TyFun acc6989586621679442511 (TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MapAccumLSym0 :: TyFun (TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) (TyFun acc6989586621679442511 (TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> Type) -> Type) -> *) (l :: TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) Source # | |
type Apply (MapAccumLSym0 :: TyFun (TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) (TyFun acc6989586621679442511 (TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> Type) -> Type) -> *) (l :: TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) = MapAccumLSym1 l | |
data MapAccumLSym1 (l :: TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) (l :: TyFun acc6989586621679442511 (TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> Type)) Source #
Instances
| SuppressUnusedWarnings (MapAccumLSym1 :: (TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) -> TyFun acc6989586621679442511 (TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MapAccumLSym1 l1 :: TyFun acc6989586621679442511 (TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> Type) -> *) (l2 :: acc6989586621679442511) Source # | |
type Apply (MapAccumLSym1 l1 :: TyFun acc6989586621679442511 (TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> Type) -> *) (l2 :: acc6989586621679442511) = MapAccumLSym2 l1 l2 | |
data MapAccumLSym2 (l :: TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) (l :: acc6989586621679442511) (l :: TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513])) Source #
Instances
| SuppressUnusedWarnings (MapAccumLSym2 :: (TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) -> acc6989586621679442511 -> TyFun [x6989586621679442512] (acc6989586621679442511, [y6989586621679442513]) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MapAccumLSym2 l1 l2 :: TyFun [x] (acc, [y]) -> *) (l3 :: [x]) Source # | |
type MapAccumLSym3 (t :: TyFun acc6989586621679442511 (TyFun x6989586621679442512 (acc6989586621679442511, y6989586621679442513) -> Type) -> Type) (t :: acc6989586621679442511) (t :: [x6989586621679442512]) = MapAccumL t t t Source #
data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) (TyFun acc6989586621679442508 (TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) (TyFun acc6989586621679442508 (TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MapAccumRSym0 :: TyFun (TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) (TyFun acc6989586621679442508 (TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> Type) -> Type) -> *) (l :: TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) Source # | |
type Apply (MapAccumRSym0 :: TyFun (TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) (TyFun acc6989586621679442508 (TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> Type) -> Type) -> *) (l :: TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) = MapAccumRSym1 l | |
data MapAccumRSym1 (l :: TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) (l :: TyFun acc6989586621679442508 (TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> Type)) Source #
Instances
| SuppressUnusedWarnings (MapAccumRSym1 :: (TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) -> TyFun acc6989586621679442508 (TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MapAccumRSym1 l1 :: TyFun acc6989586621679442508 (TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> Type) -> *) (l2 :: acc6989586621679442508) Source # | |
type Apply (MapAccumRSym1 l1 :: TyFun acc6989586621679442508 (TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> Type) -> *) (l2 :: acc6989586621679442508) = MapAccumRSym2 l1 l2 | |
data MapAccumRSym2 (l :: TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) (l :: acc6989586621679442508) (l :: TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510])) Source #
Instances
| SuppressUnusedWarnings (MapAccumRSym2 :: (TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) -> acc6989586621679442508 -> TyFun [x6989586621679442509] (acc6989586621679442508, [y6989586621679442510]) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MapAccumRSym2 l1 l2 :: TyFun [x] (acc, [y]) -> *) (l3 :: [x]) Source # | |
type MapAccumRSym3 (t :: TyFun acc6989586621679442508 (TyFun x6989586621679442509 (acc6989586621679442508, y6989586621679442510) -> Type) -> Type) (t :: acc6989586621679442508) (t :: [x6989586621679442509]) = MapAccumR t t t Source #
data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679442422 [a6989586621679442422] -> Type)) Source #
Instances
| SuppressUnusedWarnings (ReplicateSym0 :: TyFun Nat (TyFun a6989586621679442422 [a6989586621679442422] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ReplicateSym0 :: TyFun Nat (TyFun a6989586621679442422 [a6989586621679442422] -> Type) -> *) (l :: Nat) Source # | |
data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679442422 [a6989586621679442422]) Source #
Instances
| SuppressUnusedWarnings (ReplicateSym1 :: Nat -> TyFun a6989586621679442422 [a6989586621679442422] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ReplicateSym1 l1 :: TyFun a [a] -> *) (l2 :: a) Source # | |
type ReplicateSym2 (t :: Nat) (t :: a6989586621679442422) = Replicate t t Source #
data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679442506 (Maybe (a6989586621679442507, b6989586621679442506)) -> Type) (TyFun b6989586621679442506 [a6989586621679442507] -> Type)) Source #
Instances
| SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (TyFun b6989586621679442506 (Maybe (a6989586621679442507, b6989586621679442506)) -> Type) (TyFun b6989586621679442506 [a6989586621679442507] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (UnfoldrSym0 :: TyFun (TyFun b6989586621679442506 (Maybe (a6989586621679442507, b6989586621679442506)) -> Type) (TyFun b6989586621679442506 [a6989586621679442507] -> Type) -> *) (l :: TyFun b6989586621679442506 (Maybe (a6989586621679442507, b6989586621679442506)) -> Type) Source # | |
data UnfoldrSym1 (l :: TyFun b6989586621679442506 (Maybe (a6989586621679442507, b6989586621679442506)) -> Type) (l :: TyFun b6989586621679442506 [a6989586621679442507]) Source #
Instances
| SuppressUnusedWarnings (UnfoldrSym1 :: (TyFun b6989586621679442506 (Maybe (a6989586621679442507, b6989586621679442506)) -> Type) -> TyFun b6989586621679442506 [a6989586621679442507] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (UnfoldrSym1 l1 :: TyFun b [a] -> *) (l2 :: b) Source # | |
type UnfoldrSym2 (t :: TyFun b6989586621679442506 (Maybe (a6989586621679442507, b6989586621679442506)) -> Type) (t :: b6989586621679442506) = Unfoldr t t Source #
data TakeSym0 (l :: TyFun Nat (TyFun [a6989586621679442438] [a6989586621679442438] -> Type)) Source #
data TakeSym1 (l :: Nat) (l :: TyFun [a6989586621679442438] [a6989586621679442438]) Source #
data DropSym0 (l :: TyFun Nat (TyFun [a6989586621679442437] [a6989586621679442437] -> Type)) Source #
data DropSym1 (l :: Nat) (l :: TyFun [a6989586621679442437] [a6989586621679442437]) Source #
data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679442436] ([a6989586621679442436], [a6989586621679442436]) -> Type)) Source #
Instances
| SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat (TyFun [a6989586621679442436] ([a6989586621679442436], [a6989586621679442436]) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (SplitAtSym0 :: TyFun Nat (TyFun [a6989586621679442436] ([a6989586621679442436], [a6989586621679442436]) -> Type) -> *) (l :: Nat) Source # | |
data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679442436] ([a6989586621679442436], [a6989586621679442436])) Source #
Instances
| SuppressUnusedWarnings (SplitAtSym1 :: Nat -> TyFun [a6989586621679442436] ([a6989586621679442436], [a6989586621679442436]) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (SplitAtSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # | |
type SplitAtSym2 (t :: Nat) (t :: [a6989586621679442436]) = SplitAt t t Source #
data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679442443 Bool -> Type) (TyFun [a6989586621679442443] [a6989586621679442443] -> Type)) Source #
Instances
| SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (TyFun a6989586621679442443 Bool -> Type) (TyFun [a6989586621679442443] [a6989586621679442443] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (TakeWhileSym0 :: TyFun (TyFun a6989586621679442443 Bool -> Type) (TyFun [a6989586621679442443] [a6989586621679442443] -> Type) -> *) (l :: TyFun a6989586621679442443 Bool -> Type) Source # | |
data TakeWhileSym1 (l :: TyFun a6989586621679442443 Bool -> Type) (l :: TyFun [a6989586621679442443] [a6989586621679442443]) Source #
Instances
| SuppressUnusedWarnings (TakeWhileSym1 :: (TyFun a6989586621679442443 Bool -> Type) -> TyFun [a6989586621679442443] [a6989586621679442443] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (TakeWhileSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type TakeWhileSym2 (t :: TyFun a6989586621679442443 Bool -> Type) (t :: [a6989586621679442443]) = TakeWhile t t Source #
data DropWhileSym0 (l :: TyFun (TyFun a6989586621679442442 Bool -> Type) (TyFun [a6989586621679442442] [a6989586621679442442] -> Type)) Source #
Instances
| SuppressUnusedWarnings (DropWhileSym0 :: TyFun (TyFun a6989586621679442442 Bool -> Type) (TyFun [a6989586621679442442] [a6989586621679442442] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DropWhileSym0 :: TyFun (TyFun a6989586621679442442 Bool -> Type) (TyFun [a6989586621679442442] [a6989586621679442442] -> Type) -> *) (l :: TyFun a6989586621679442442 Bool -> Type) Source # | |
data DropWhileSym1 (l :: TyFun a6989586621679442442 Bool -> Type) (l :: TyFun [a6989586621679442442] [a6989586621679442442]) Source #
Instances
| SuppressUnusedWarnings (DropWhileSym1 :: (TyFun a6989586621679442442 Bool -> Type) -> TyFun [a6989586621679442442] [a6989586621679442442] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DropWhileSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type DropWhileSym2 (t :: TyFun a6989586621679442442 Bool -> Type) (t :: [a6989586621679442442]) = DropWhile t t Source #
data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679442441 Bool -> Type) (TyFun [a6989586621679442441] [a6989586621679442441] -> Type)) Source #
Instances
| SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (TyFun a6989586621679442441 Bool -> Type) (TyFun [a6989586621679442441] [a6989586621679442441] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DropWhileEndSym0 :: TyFun (TyFun a6989586621679442441 Bool -> Type) (TyFun [a6989586621679442441] [a6989586621679442441] -> Type) -> *) (l :: TyFun a6989586621679442441 Bool -> Type) Source # | |
data DropWhileEndSym1 (l :: TyFun a6989586621679442441 Bool -> Type) (l :: TyFun [a6989586621679442441] [a6989586621679442441]) Source #
Instances
| SuppressUnusedWarnings (DropWhileEndSym1 :: (TyFun a6989586621679442441 Bool -> Type) -> TyFun [a6989586621679442441] [a6989586621679442441] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DropWhileEndSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type DropWhileEndSym2 (t :: TyFun a6989586621679442441 Bool -> Type) (t :: [a6989586621679442441]) = DropWhileEnd t t Source #
data SpanSym0 (l :: TyFun (TyFun a6989586621679442440 Bool -> Type) (TyFun [a6989586621679442440] ([a6989586621679442440], [a6989586621679442440]) -> Type)) Source #
Instances
| SuppressUnusedWarnings (SpanSym0 :: TyFun (TyFun a6989586621679442440 Bool -> Type) (TyFun [a6989586621679442440] ([a6989586621679442440], [a6989586621679442440]) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (SpanSym0 :: TyFun (TyFun a6989586621679442440 Bool -> Type) (TyFun [a6989586621679442440] ([a6989586621679442440], [a6989586621679442440]) -> Type) -> *) (l :: TyFun a6989586621679442440 Bool -> Type) Source # | |
data SpanSym1 (l :: TyFun a6989586621679442440 Bool -> Type) (l :: TyFun [a6989586621679442440] ([a6989586621679442440], [a6989586621679442440])) Source #
Instances
| SuppressUnusedWarnings (SpanSym1 :: (TyFun a6989586621679442440 Bool -> Type) -> TyFun [a6989586621679442440] ([a6989586621679442440], [a6989586621679442440]) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (SpanSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # | |
type SpanSym2 (t :: TyFun a6989586621679442440 Bool -> Type) (t :: [a6989586621679442440]) = Span t t Source #
data BreakSym0 (l :: TyFun (TyFun a6989586621679442439 Bool -> Type) (TyFun [a6989586621679442439] ([a6989586621679442439], [a6989586621679442439]) -> Type)) Source #
Instances
| SuppressUnusedWarnings (BreakSym0 :: TyFun (TyFun a6989586621679442439 Bool -> Type) (TyFun [a6989586621679442439] ([a6989586621679442439], [a6989586621679442439]) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (BreakSym0 :: TyFun (TyFun a6989586621679442439 Bool -> Type) (TyFun [a6989586621679442439] ([a6989586621679442439], [a6989586621679442439]) -> Type) -> *) (l :: TyFun a6989586621679442439 Bool -> Type) Source # | |
data BreakSym1 (l :: TyFun a6989586621679442439 Bool -> Type) (l :: TyFun [a6989586621679442439] ([a6989586621679442439], [a6989586621679442439])) Source #
Instances
| SuppressUnusedWarnings (BreakSym1 :: (TyFun a6989586621679442439 Bool -> Type) -> TyFun [a6989586621679442439] ([a6989586621679442439], [a6989586621679442439]) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (BreakSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # | |
type BreakSym2 (t :: TyFun a6989586621679442439 Bool -> Type) (t :: [a6989586621679442439]) = Break t t Source #
data IsPrefixOfSym0 (l :: TyFun [a6989586621679442503] (TyFun [a6989586621679442503] Bool -> Type)) Source #
Instances
| SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679442503] (TyFun [a6989586621679442503] Bool -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679442503] (TyFun [a6989586621679442503] Bool -> Type) -> *) (l :: [a6989586621679442503]) Source # | |
type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679442503] (TyFun [a6989586621679442503] Bool -> Type) -> *) (l :: [a6989586621679442503]) = IsPrefixOfSym1 l | |
data IsPrefixOfSym1 (l :: [a6989586621679442503]) (l :: TyFun [a6989586621679442503] Bool) Source #
Instances
| SuppressUnusedWarnings (IsPrefixOfSym1 :: [a6989586621679442503] -> TyFun [a6989586621679442503] Bool -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IsPrefixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # | |
type IsPrefixOfSym2 (t :: [a6989586621679442503]) (t :: [a6989586621679442503]) = IsPrefixOf t t Source #
data IsSuffixOfSym0 (l :: TyFun [a6989586621679442502] (TyFun [a6989586621679442502] Bool -> Type)) Source #
Instances
| SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679442502] (TyFun [a6989586621679442502] Bool -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679442502] (TyFun [a6989586621679442502] Bool -> Type) -> *) (l :: [a6989586621679442502]) Source # | |
type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679442502] (TyFun [a6989586621679442502] Bool -> Type) -> *) (l :: [a6989586621679442502]) = IsSuffixOfSym1 l | |
data IsSuffixOfSym1 (l :: [a6989586621679442502]) (l :: TyFun [a6989586621679442502] Bool) Source #
Instances
| SuppressUnusedWarnings (IsSuffixOfSym1 :: [a6989586621679442502] -> TyFun [a6989586621679442502] Bool -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IsSuffixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # | |
type IsSuffixOfSym2 (t :: [a6989586621679442502]) (t :: [a6989586621679442502]) = IsSuffixOf t t Source #
data IsInfixOfSym0 (l :: TyFun [a6989586621679442501] (TyFun [a6989586621679442501] Bool -> Type)) Source #
Instances
| SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a6989586621679442501] (TyFun [a6989586621679442501] Bool -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IsInfixOfSym0 :: TyFun [a6989586621679442501] (TyFun [a6989586621679442501] Bool -> Type) -> *) (l :: [a6989586621679442501]) Source # | |
type Apply (IsInfixOfSym0 :: TyFun [a6989586621679442501] (TyFun [a6989586621679442501] Bool -> Type) -> *) (l :: [a6989586621679442501]) = IsInfixOfSym1 l | |
data IsInfixOfSym1 (l :: [a6989586621679442501]) (l :: TyFun [a6989586621679442501] Bool) Source #
Instances
| SuppressUnusedWarnings (IsInfixOfSym1 :: [a6989586621679442501] -> TyFun [a6989586621679442501] Bool -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IsInfixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # | |
type IsInfixOfSym2 (t :: [a6989586621679442501]) (t :: [a6989586621679442501]) = IsInfixOf t t Source #
data ElemSym0 (l :: TyFun a6989586621679442500 (TyFun [a6989586621679442500] Bool -> Type)) Source #
Instances
| SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621679442500 (TyFun [a6989586621679442500] Bool -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ElemSym0 :: TyFun a6989586621679442500 (TyFun [a6989586621679442500] Bool -> Type) -> *) (l :: a6989586621679442500) Source # | |
data ElemSym1 (l :: a6989586621679442500) (l :: TyFun [a6989586621679442500] Bool) Source #
data NotElemSym0 (l :: TyFun a6989586621679442499 (TyFun [a6989586621679442499] Bool -> Type)) Source #
Instances
| SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621679442499 (TyFun [a6989586621679442499] Bool -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (NotElemSym0 :: TyFun a6989586621679442499 (TyFun [a6989586621679442499] Bool -> Type) -> *) (l :: a6989586621679442499) Source # | |
type Apply (NotElemSym0 :: TyFun a6989586621679442499 (TyFun [a6989586621679442499] Bool -> Type) -> *) (l :: a6989586621679442499) = NotElemSym1 l | |
data NotElemSym1 (l :: a6989586621679442499) (l :: TyFun [a6989586621679442499] Bool) Source #
Instances
| SuppressUnusedWarnings (NotElemSym1 :: a6989586621679442499 -> TyFun [a6989586621679442499] Bool -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (NotElemSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # | |
type NotElemSym2 (t :: a6989586621679442499) (t :: [a6989586621679442499]) = NotElem t t Source #
data LookupSym0 (l :: TyFun a6989586621679442428 (TyFun [(a6989586621679442428, b6989586621679442429)] (Maybe b6989586621679442429) -> Type)) Source #
Instances
| SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679442428 (TyFun [(a6989586621679442428, b6989586621679442429)] (Maybe b6989586621679442429) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (LookupSym0 :: TyFun a6989586621679442428 (TyFun [(a6989586621679442428, b6989586621679442429)] (Maybe b6989586621679442429) -> Type) -> *) (l :: a6989586621679442428) Source # | |
data LookupSym1 (l :: a6989586621679442428) (l :: TyFun [(a6989586621679442428, b6989586621679442429)] (Maybe b6989586621679442429)) Source #
Instances
| SuppressUnusedWarnings (LookupSym1 :: a6989586621679442428 -> TyFun [(a6989586621679442428, b6989586621679442429)] (Maybe b6989586621679442429) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (LookupSym1 l1 :: TyFun [(a, b)] (Maybe b) -> *) (l2 :: [(a, b)]) Source # | |
type LookupSym2 (t :: a6989586621679442428) (t :: [(a6989586621679442428, b6989586621679442429)]) = Lookup t t Source #
data FindSym0 (l :: TyFun (TyFun a6989586621679442450 Bool -> Type) (TyFun [a6989586621679442450] (Maybe a6989586621679442450) -> Type)) Source #
Instances
| SuppressUnusedWarnings (FindSym0 :: TyFun (TyFun a6989586621679442450 Bool -> Type) (TyFun [a6989586621679442450] (Maybe a6989586621679442450) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FindSym0 :: TyFun (TyFun a6989586621679442450 Bool -> Type) (TyFun [a6989586621679442450] (Maybe a6989586621679442450) -> Type) -> *) (l :: TyFun a6989586621679442450 Bool -> Type) Source # | |
data FindSym1 (l :: TyFun a6989586621679442450 Bool -> Type) (l :: TyFun [a6989586621679442450] (Maybe a6989586621679442450)) Source #
type FindSym2 (t :: TyFun a6989586621679442450 Bool -> Type) (t :: [a6989586621679442450]) = Find t t Source #
data FilterSym0 (l :: TyFun (TyFun a6989586621679442451 Bool -> Type) (TyFun [a6989586621679442451] [a6989586621679442451] -> Type)) Source #
Instances
| SuppressUnusedWarnings (FilterSym0 :: TyFun (TyFun a6989586621679442451 Bool -> Type) (TyFun [a6989586621679442451] [a6989586621679442451] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FilterSym0 :: TyFun (TyFun a6989586621679442451 Bool -> Type) (TyFun [a6989586621679442451] [a6989586621679442451] -> Type) -> *) (l :: TyFun a6989586621679442451 Bool -> Type) Source # | |
data FilterSym1 (l :: TyFun a6989586621679442451 Bool -> Type) (l :: TyFun [a6989586621679442451] [a6989586621679442451]) Source #
Instances
| SuppressUnusedWarnings (FilterSym1 :: (TyFun a6989586621679442451 Bool -> Type) -> TyFun [a6989586621679442451] [a6989586621679442451] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FilterSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type FilterSym2 (t :: TyFun a6989586621679442451 Bool -> Type) (t :: [a6989586621679442451]) = Filter t t Source #
data PartitionSym0 (l :: TyFun (TyFun a6989586621679442427 Bool -> Type) (TyFun [a6989586621679442427] ([a6989586621679442427], [a6989586621679442427]) -> Type)) Source #
Instances
| SuppressUnusedWarnings (PartitionSym0 :: TyFun (TyFun a6989586621679442427 Bool -> Type) (TyFun [a6989586621679442427] ([a6989586621679442427], [a6989586621679442427]) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (PartitionSym0 :: TyFun (TyFun a6989586621679442427 Bool -> Type) (TyFun [a6989586621679442427] ([a6989586621679442427], [a6989586621679442427]) -> Type) -> *) (l :: TyFun a6989586621679442427 Bool -> Type) Source # | |
data PartitionSym1 (l :: TyFun a6989586621679442427 Bool -> Type) (l :: TyFun [a6989586621679442427] ([a6989586621679442427], [a6989586621679442427])) Source #
Instances
| SuppressUnusedWarnings (PartitionSym1 :: (TyFun a6989586621679442427 Bool -> Type) -> TyFun [a6989586621679442427] ([a6989586621679442427], [a6989586621679442427]) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (PartitionSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # | |
type PartitionSym2 (t :: TyFun a6989586621679442427 Bool -> Type) (t :: [a6989586621679442427]) = Partition t t Source #
data (!!@#@$) (l :: TyFun [a6989586621679442420] (TyFun Nat a6989586621679442420 -> Type)) Source #
Instances
| SuppressUnusedWarnings ((!!@#@$) :: TyFun [a6989586621679442420] (TyFun Nat a6989586621679442420 -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply ((!!@#@$) :: TyFun [a6989586621679442420] (TyFun Nat a6989586621679442420 -> Type) -> *) (l :: [a6989586621679442420]) Source # | |
type (!!@#@$$$) (t :: [a6989586621679442420]) (t :: Nat) = (!!) t t Source #
data ElemIndexSym0 (l :: TyFun a6989586621679442449 (TyFun [a6989586621679442449] (Maybe Nat) -> Type)) Source #
Instances
| SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679442449 (TyFun [a6989586621679442449] (Maybe Nat) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ElemIndexSym0 :: TyFun a6989586621679442449 (TyFun [a6989586621679442449] (Maybe Nat) -> Type) -> *) (l :: a6989586621679442449) Source # | |
type Apply (ElemIndexSym0 :: TyFun a6989586621679442449 (TyFun [a6989586621679442449] (Maybe Nat) -> Type) -> *) (l :: a6989586621679442449) = ElemIndexSym1 l | |
data ElemIndexSym1 (l :: a6989586621679442449) (l :: TyFun [a6989586621679442449] (Maybe Nat)) Source #
Instances
| SuppressUnusedWarnings (ElemIndexSym1 :: a6989586621679442449 -> TyFun [a6989586621679442449] (Maybe Nat) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ElemIndexSym1 l1 :: TyFun [a] (Maybe Nat) -> *) (l2 :: [a]) Source # | |
type ElemIndexSym2 (t :: a6989586621679442449) (t :: [a6989586621679442449]) = ElemIndex t t Source #
data ElemIndicesSym0 (l :: TyFun a6989586621679442448 (TyFun [a6989586621679442448] [Nat] -> Type)) Source #
Instances
| SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a6989586621679442448 (TyFun [a6989586621679442448] [Nat] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ElemIndicesSym0 :: TyFun a6989586621679442448 (TyFun [a6989586621679442448] [Nat] -> Type) -> *) (l :: a6989586621679442448) Source # | |
type Apply (ElemIndicesSym0 :: TyFun a6989586621679442448 (TyFun [a6989586621679442448] [Nat] -> Type) -> *) (l :: a6989586621679442448) = ElemIndicesSym1 l | |
data ElemIndicesSym1 (l :: a6989586621679442448) (l :: TyFun [a6989586621679442448] [Nat]) Source #
Instances
| SuppressUnusedWarnings (ElemIndicesSym1 :: a6989586621679442448 -> TyFun [a6989586621679442448] [Nat] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ElemIndicesSym1 l1 :: TyFun [a] [Nat] -> *) (l2 :: [a]) Source # | |
type ElemIndicesSym2 (t :: a6989586621679442448) (t :: [a6989586621679442448]) = ElemIndices t t Source #
data FindIndexSym0 (l :: TyFun (TyFun a6989586621679442447 Bool -> Type) (TyFun [a6989586621679442447] (Maybe Nat) -> Type)) Source #
Instances
| SuppressUnusedWarnings (FindIndexSym0 :: TyFun (TyFun a6989586621679442447 Bool -> Type) (TyFun [a6989586621679442447] (Maybe Nat) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FindIndexSym0 :: TyFun (TyFun a6989586621679442447 Bool -> Type) (TyFun [a6989586621679442447] (Maybe Nat) -> Type) -> *) (l :: TyFun a6989586621679442447 Bool -> Type) Source # | |
data FindIndexSym1 (l :: TyFun a6989586621679442447 Bool -> Type) (l :: TyFun [a6989586621679442447] (Maybe Nat)) Source #
type FindIndexSym2 (t :: TyFun a6989586621679442447 Bool -> Type) (t :: [a6989586621679442447]) = FindIndex t t Source #
data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679442446 Bool -> Type) (TyFun [a6989586621679442446] [Nat] -> Type)) Source #
Instances
| SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (TyFun a6989586621679442446 Bool -> Type) (TyFun [a6989586621679442446] [Nat] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FindIndicesSym0 :: TyFun (TyFun a6989586621679442446 Bool -> Type) (TyFun [a6989586621679442446] [Nat] -> Type) -> *) (l :: TyFun a6989586621679442446 Bool -> Type) Source # | |
data FindIndicesSym1 (l :: TyFun a6989586621679442446 Bool -> Type) (l :: TyFun [a6989586621679442446] [Nat]) Source #
Instances
| SuppressUnusedWarnings (FindIndicesSym1 :: (TyFun a6989586621679442446 Bool -> Type) -> TyFun [a6989586621679442446] [Nat] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FindIndicesSym1 l1 :: TyFun [a] [Nat] -> *) (l2 :: [a]) Source # | |
type FindIndicesSym2 (t :: TyFun a6989586621679442446 Bool -> Type) (t :: [a6989586621679442446]) = FindIndices t t Source #
data ZipSym0 (l :: TyFun [a6989586621679442497] (TyFun [b6989586621679442498] [(a6989586621679442497, b6989586621679442498)] -> Type)) Source #
Instances
| SuppressUnusedWarnings (ZipSym0 :: TyFun [a6989586621679442497] (TyFun [b6989586621679442498] [(a6989586621679442497, b6989586621679442498)] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ZipSym0 :: TyFun [a6989586621679442497] (TyFun [b6989586621679442498] [(a6989586621679442497, b6989586621679442498)] -> Type) -> *) (l :: [a6989586621679442497]) Source # | |
data ZipSym1 (l :: [a6989586621679442497]) (l :: TyFun [b6989586621679442498] [(a6989586621679442497, b6989586621679442498)]) Source #
data Zip3Sym0 (l :: TyFun [a6989586621679442494] (TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a6989586621679442494] (TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Zip3Sym0 :: TyFun [a6989586621679442494] (TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type) -> Type) -> *) (l :: [a6989586621679442494]) Source # | |
type Apply (Zip3Sym0 :: TyFun [a6989586621679442494] (TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type) -> Type) -> *) (l :: [a6989586621679442494]) = (Zip3Sym1 l :: TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type) -> *) | |
data Zip3Sym1 (l :: [a6989586621679442494]) (l :: TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type)) Source #
Instances
| SuppressUnusedWarnings (Zip3Sym1 :: [a6989586621679442494] -> TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Zip3Sym1 l1 :: TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type) -> *) (l2 :: [b6989586621679442495]) Source # | |
type Apply (Zip3Sym1 l1 :: TyFun [b6989586621679442495] (TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> Type) -> *) (l2 :: [b6989586621679442495]) = (Zip3Sym2 l1 l2 :: TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> *) | |
data Zip3Sym2 (l :: [a6989586621679442494]) (l :: [b6989586621679442495]) (l :: TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)]) Source #
Instances
| SuppressUnusedWarnings (Zip3Sym2 :: [a6989586621679442494] -> [b6989586621679442495] -> TyFun [c6989586621679442496] [(a6989586621679442494, b6989586621679442495, c6989586621679442496)] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Zip3Sym2 l1 l2 :: TyFun [c] [(a, b, c)] -> *) (l3 :: [c]) Source # | |
type Zip3Sym3 (t :: [a6989586621679442494]) (t :: [b6989586621679442495]) (t :: [c6989586621679442496]) = Zip3 t t t Source #
data ZipWithSym0 (l :: TyFun (TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) (TyFun [a6989586621679442491] (TyFun [b6989586621679442492] [c6989586621679442493] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (ZipWithSym0 :: TyFun (TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) (TyFun [a6989586621679442491] (TyFun [b6989586621679442492] [c6989586621679442493] -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ZipWithSym0 :: TyFun (TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) (TyFun [a6989586621679442491] (TyFun [b6989586621679442492] [c6989586621679442493] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) Source # | |
type Apply (ZipWithSym0 :: TyFun (TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) (TyFun [a6989586621679442491] (TyFun [b6989586621679442492] [c6989586621679442493] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) = ZipWithSym1 l | |
data ZipWithSym1 (l :: TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) (l :: TyFun [a6989586621679442491] (TyFun [b6989586621679442492] [c6989586621679442493] -> Type)) Source #
Instances
| SuppressUnusedWarnings (ZipWithSym1 :: (TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) -> TyFun [a6989586621679442491] (TyFun [b6989586621679442492] [c6989586621679442493] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ZipWithSym1 l1 :: TyFun [a6989586621679442491] (TyFun [b6989586621679442492] [c6989586621679442493] -> Type) -> *) (l2 :: [a6989586621679442491]) Source # | |
type Apply (ZipWithSym1 l1 :: TyFun [a6989586621679442491] (TyFun [b6989586621679442492] [c6989586621679442493] -> Type) -> *) (l2 :: [a6989586621679442491]) = ZipWithSym2 l1 l2 | |
data ZipWithSym2 (l :: TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) (l :: [a6989586621679442491]) (l :: TyFun [b6989586621679442492] [c6989586621679442493]) Source #
Instances
| SuppressUnusedWarnings (ZipWithSym2 :: (TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) -> [a6989586621679442491] -> TyFun [b6989586621679442492] [c6989586621679442493] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ZipWithSym2 l1 l2 :: TyFun [b] [c] -> *) (l3 :: [b]) Source # | |
type ZipWithSym3 (t :: TyFun a6989586621679442491 (TyFun b6989586621679442492 c6989586621679442493 -> Type) -> Type) (t :: [a6989586621679442491]) (t :: [b6989586621679442492]) = ZipWith t t t Source #
data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (TyFun [a6989586621679442487] (TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (TyFun [a6989586621679442487] (TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ZipWith3Sym0 :: TyFun (TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (TyFun [a6989586621679442487] (TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) Source # | |
type Apply (ZipWith3Sym0 :: TyFun (TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (TyFun [a6989586621679442487] (TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) = ZipWith3Sym1 l | |
data ZipWith3Sym1 (l :: TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679442487] (TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (ZipWith3Sym1 :: (TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) -> TyFun [a6989586621679442487] (TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ZipWith3Sym1 l1 :: TyFun [a6989586621679442487] (TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> Type) -> *) (l2 :: [a6989586621679442487]) Source # | |
type Apply (ZipWith3Sym1 l1 :: TyFun [a6989586621679442487] (TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> Type) -> *) (l2 :: [a6989586621679442487]) = ZipWith3Sym2 l1 l2 | |
data ZipWith3Sym2 (l :: TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (l :: [a6989586621679442487]) (l :: TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type)) Source #
Instances
| SuppressUnusedWarnings (ZipWith3Sym2 :: (TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) -> [a6989586621679442487] -> TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ZipWith3Sym2 l1 l2 :: TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> *) (l3 :: [b6989586621679442488]) Source # | |
type Apply (ZipWith3Sym2 l1 l2 :: TyFun [b6989586621679442488] (TyFun [c6989586621679442489] [d6989586621679442490] -> Type) -> *) (l3 :: [b6989586621679442488]) = ZipWith3Sym3 l1 l2 l3 | |
data ZipWith3Sym3 (l :: TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (l :: [a6989586621679442487]) (l :: [b6989586621679442488]) (l :: TyFun [c6989586621679442489] [d6989586621679442490]) Source #
Instances
| SuppressUnusedWarnings (ZipWith3Sym3 :: (TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) -> [a6989586621679442487] -> [b6989586621679442488] -> TyFun [c6989586621679442489] [d6989586621679442490] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ZipWith3Sym3 l1 l2 l3 :: TyFun [c] [d] -> *) (l4 :: [c]) Source # | |
type ZipWith3Sym4 (t :: TyFun a6989586621679442487 (TyFun b6989586621679442488 (TyFun c6989586621679442489 d6989586621679442490 -> Type) -> Type) -> Type) (t :: [a6989586621679442487]) (t :: [b6989586621679442488]) (t :: [c6989586621679442489]) = ZipWith3 t t t t Source #
data UnzipSym0 (l :: TyFun [(a6989586621679442485, b6989586621679442486)] ([a6989586621679442485], [b6989586621679442486])) Source #
data Unzip3Sym0 (l :: TyFun [(a6989586621679442482, b6989586621679442483, c6989586621679442484)] ([a6989586621679442482], [b6989586621679442483], [c6989586621679442484])) Source #
Instances
| SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a6989586621679442482, b6989586621679442483, c6989586621679442484)] ([a6989586621679442482], [b6989586621679442483], [c6989586621679442484]) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> *) (l :: [(a, b, c)]) Source # | |
type Unzip3Sym1 (t :: [(a6989586621679442482, b6989586621679442483, c6989586621679442484)]) = Unzip3 t Source #
data Unzip4Sym0 (l :: TyFun [(a6989586621679442478, b6989586621679442479, c6989586621679442480, d6989586621679442481)] ([a6989586621679442478], [b6989586621679442479], [c6989586621679442480], [d6989586621679442481])) Source #
Instances
| SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a6989586621679442478, b6989586621679442479, c6989586621679442480, d6989586621679442481)] ([a6989586621679442478], [b6989586621679442479], [c6989586621679442480], [d6989586621679442481]) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> *) (l :: [(a, b, c, d)]) Source # | |
type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> *) (l :: [(a, b, c, d)]) = Unzip4 l | |
type Unzip4Sym1 (t :: [(a6989586621679442478, b6989586621679442479, c6989586621679442480, d6989586621679442481)]) = Unzip4 t Source #
data Unzip5Sym0 (l :: TyFun [(a6989586621679442473, b6989586621679442474, c6989586621679442475, d6989586621679442476, e6989586621679442477)] ([a6989586621679442473], [b6989586621679442474], [c6989586621679442475], [d6989586621679442476], [e6989586621679442477])) Source #
Instances
| SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a6989586621679442473, b6989586621679442474, c6989586621679442475, d6989586621679442476, e6989586621679442477)] ([a6989586621679442473], [b6989586621679442474], [c6989586621679442475], [d6989586621679442476], [e6989586621679442477]) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> *) (l :: [(a, b, c, d, e)]) Source # | |
type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> *) (l :: [(a, b, c, d, e)]) = Unzip5 l | |
type Unzip5Sym1 (t :: [(a6989586621679442473, b6989586621679442474, c6989586621679442475, d6989586621679442476, e6989586621679442477)]) = Unzip5 t Source #
data Unzip6Sym0 (l :: TyFun [(a6989586621679442467, b6989586621679442468, c6989586621679442469, d6989586621679442470, e6989586621679442471, f6989586621679442472)] ([a6989586621679442467], [b6989586621679442468], [c6989586621679442469], [d6989586621679442470], [e6989586621679442471], [f6989586621679442472])) Source #
Instances
| SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a6989586621679442467, b6989586621679442468, c6989586621679442469, d6989586621679442470, e6989586621679442471, f6989586621679442472)] ([a6989586621679442467], [b6989586621679442468], [c6989586621679442469], [d6989586621679442470], [e6989586621679442471], [f6989586621679442472]) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> *) (l :: [(a, b, c, d, e, f)]) Source # | |
type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> *) (l :: [(a, b, c, d, e, f)]) = Unzip6 l | |
type Unzip6Sym1 (t :: [(a6989586621679442467, b6989586621679442468, c6989586621679442469, d6989586621679442470, e6989586621679442471, f6989586621679442472)]) = Unzip6 t Source #
data Unzip7Sym0 (l :: TyFun [(a6989586621679442460, b6989586621679442461, c6989586621679442462, d6989586621679442463, e6989586621679442464, f6989586621679442465, g6989586621679442466)] ([a6989586621679442460], [b6989586621679442461], [c6989586621679442462], [d6989586621679442463], [e6989586621679442464], [f6989586621679442465], [g6989586621679442466])) Source #
Instances
| SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a6989586621679442460, b6989586621679442461, c6989586621679442462, d6989586621679442463, e6989586621679442464, f6989586621679442465, g6989586621679442466)] ([a6989586621679442460], [b6989586621679442461], [c6989586621679442462], [d6989586621679442463], [e6989586621679442464], [f6989586621679442465], [g6989586621679442466]) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> *) (l :: [(a, b, c, d, e, f, g)]) Source # | |
type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> *) (l :: [(a, b, c, d, e, f, g)]) = Unzip7 l | |
type Unzip7Sym1 (t :: [(a6989586621679442460, b6989586621679442461, c6989586621679442462, d6989586621679442463, e6989586621679442464, f6989586621679442465, g6989586621679442466)]) = Unzip7 t Source #
data UnlinesSym0 (l :: TyFun [Symbol] Symbol) Source #
Instances
| SuppressUnusedWarnings UnlinesSym0 Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply UnlinesSym0 (l :: [Symbol]) Source # | |
type UnlinesSym1 (t :: [Symbol]) = Unlines t Source #
data UnwordsSym0 (l :: TyFun [Symbol] Symbol) Source #
Instances
| SuppressUnusedWarnings UnwordsSym0 Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply UnwordsSym0 (l :: [Symbol]) Source # | |
type UnwordsSym1 (t :: [Symbol]) = Unwords t Source #
data DeleteSym0 (l :: TyFun a6989586621679442459 (TyFun [a6989586621679442459] [a6989586621679442459] -> Type)) Source #
Instances
| SuppressUnusedWarnings (DeleteSym0 :: TyFun a6989586621679442459 (TyFun [a6989586621679442459] [a6989586621679442459] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DeleteSym0 :: TyFun a6989586621679442459 (TyFun [a6989586621679442459] [a6989586621679442459] -> Type) -> *) (l :: a6989586621679442459) Source # | |
type Apply (DeleteSym0 :: TyFun a6989586621679442459 (TyFun [a6989586621679442459] [a6989586621679442459] -> Type) -> *) (l :: a6989586621679442459) = DeleteSym1 l | |
data DeleteSym1 (l :: a6989586621679442459) (l :: TyFun [a6989586621679442459] [a6989586621679442459]) Source #
Instances
| SuppressUnusedWarnings (DeleteSym1 :: a6989586621679442459 -> TyFun [a6989586621679442459] [a6989586621679442459] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DeleteSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type DeleteSym2 (t :: a6989586621679442459) (t :: [a6989586621679442459]) = Delete t t Source #
data (\\@#@$) (l :: TyFun [a6989586621679442458] (TyFun [a6989586621679442458] [a6989586621679442458] -> Type)) Source #
Instances
| SuppressUnusedWarnings ((\\@#@$) :: TyFun [a6989586621679442458] (TyFun [a6989586621679442458] [a6989586621679442458] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply ((\\@#@$) :: TyFun [a6989586621679442458] (TyFun [a6989586621679442458] [a6989586621679442458] -> Type) -> *) (l :: [a6989586621679442458]) Source # | |
data (l :: [a6989586621679442458]) \\@#@$$ (l :: TyFun [a6989586621679442458] [a6989586621679442458]) Source #
type (\\@#@$$$) (t :: [a6989586621679442458]) (t :: [a6989586621679442458]) = (\\) t t Source #
data UnionSym0 (l :: TyFun [a6989586621679442415] (TyFun [a6989586621679442415] [a6989586621679442415] -> Type)) Source #
Instances
| SuppressUnusedWarnings (UnionSym0 :: TyFun [a6989586621679442415] (TyFun [a6989586621679442415] [a6989586621679442415] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (UnionSym0 :: TyFun [a6989586621679442415] (TyFun [a6989586621679442415] [a6989586621679442415] -> Type) -> *) (l :: [a6989586621679442415]) Source # | |
data UnionSym1 (l :: [a6989586621679442415]) (l :: TyFun [a6989586621679442415] [a6989586621679442415]) Source #
data IntersectSym0 (l :: TyFun [a6989586621679442445] (TyFun [a6989586621679442445] [a6989586621679442445] -> Type)) Source #
Instances
| SuppressUnusedWarnings (IntersectSym0 :: TyFun [a6989586621679442445] (TyFun [a6989586621679442445] [a6989586621679442445] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IntersectSym0 :: TyFun [a6989586621679442445] (TyFun [a6989586621679442445] [a6989586621679442445] -> Type) -> *) (l :: [a6989586621679442445]) Source # | |
type Apply (IntersectSym0 :: TyFun [a6989586621679442445] (TyFun [a6989586621679442445] [a6989586621679442445] -> Type) -> *) (l :: [a6989586621679442445]) = IntersectSym1 l | |
data IntersectSym1 (l :: [a6989586621679442445]) (l :: TyFun [a6989586621679442445] [a6989586621679442445]) Source #
Instances
| SuppressUnusedWarnings (IntersectSym1 :: [a6989586621679442445] -> TyFun [a6989586621679442445] [a6989586621679442445] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IntersectSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type IntersectSym2 (t :: [a6989586621679442445]) (t :: [a6989586621679442445]) = Intersect t t Source #
data InsertSym0 (l :: TyFun a6989586621679442432 (TyFun [a6989586621679442432] [a6989586621679442432] -> Type)) Source #
Instances
| SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621679442432 (TyFun [a6989586621679442432] [a6989586621679442432] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (InsertSym0 :: TyFun a6989586621679442432 (TyFun [a6989586621679442432] [a6989586621679442432] -> Type) -> *) (l :: a6989586621679442432) Source # | |
type Apply (InsertSym0 :: TyFun a6989586621679442432 (TyFun [a6989586621679442432] [a6989586621679442432] -> Type) -> *) (l :: a6989586621679442432) = InsertSym1 l | |
data InsertSym1 (l :: a6989586621679442432) (l :: TyFun [a6989586621679442432] [a6989586621679442432]) Source #
Instances
| SuppressUnusedWarnings (InsertSym1 :: a6989586621679442432 -> TyFun [a6989586621679442432] [a6989586621679442432] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (InsertSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type InsertSym2 (t :: a6989586621679442432) (t :: [a6989586621679442432]) = Insert t t Source #
data NubBySym0 (l :: TyFun (TyFun a6989586621679442418 (TyFun a6989586621679442418 Bool -> Type) -> Type) (TyFun [a6989586621679442418] [a6989586621679442418] -> Type)) Source #
Instances
| SuppressUnusedWarnings (NubBySym0 :: TyFun (TyFun a6989586621679442418 (TyFun a6989586621679442418 Bool -> Type) -> Type) (TyFun [a6989586621679442418] [a6989586621679442418] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (NubBySym0 :: TyFun (TyFun a6989586621679442418 (TyFun a6989586621679442418 Bool -> Type) -> Type) (TyFun [a6989586621679442418] [a6989586621679442418] -> Type) -> *) (l :: TyFun a6989586621679442418 (TyFun a6989586621679442418 Bool -> Type) -> Type) Source # | |
data NubBySym1 (l :: TyFun a6989586621679442418 (TyFun a6989586621679442418 Bool -> Type) -> Type) (l :: TyFun [a6989586621679442418] [a6989586621679442418]) Source #
Instances
| SuppressUnusedWarnings (NubBySym1 :: (TyFun a6989586621679442418 (TyFun a6989586621679442418 Bool -> Type) -> Type) -> TyFun [a6989586621679442418] [a6989586621679442418] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (NubBySym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type NubBySym2 (t :: TyFun a6989586621679442418 (TyFun a6989586621679442418 Bool -> Type) -> Type) (t :: [a6989586621679442418]) = NubBy t t Source #
data DeleteBySym0 (l :: TyFun (TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) (TyFun a6989586621679442457 (TyFun [a6989586621679442457] [a6989586621679442457] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (DeleteBySym0 :: TyFun (TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) (TyFun a6989586621679442457 (TyFun [a6989586621679442457] [a6989586621679442457] -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DeleteBySym0 :: TyFun (TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) (TyFun a6989586621679442457 (TyFun [a6989586621679442457] [a6989586621679442457] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) Source # | |
type Apply (DeleteBySym0 :: TyFun (TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) (TyFun a6989586621679442457 (TyFun [a6989586621679442457] [a6989586621679442457] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) = DeleteBySym1 l | |
data DeleteBySym1 (l :: TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) (l :: TyFun a6989586621679442457 (TyFun [a6989586621679442457] [a6989586621679442457] -> Type)) Source #
Instances
| SuppressUnusedWarnings (DeleteBySym1 :: (TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) -> TyFun a6989586621679442457 (TyFun [a6989586621679442457] [a6989586621679442457] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DeleteBySym1 l1 :: TyFun a6989586621679442457 (TyFun [a6989586621679442457] [a6989586621679442457] -> Type) -> *) (l2 :: a6989586621679442457) Source # | |
type Apply (DeleteBySym1 l1 :: TyFun a6989586621679442457 (TyFun [a6989586621679442457] [a6989586621679442457] -> Type) -> *) (l2 :: a6989586621679442457) = DeleteBySym2 l1 l2 | |
data DeleteBySym2 (l :: TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) (l :: a6989586621679442457) (l :: TyFun [a6989586621679442457] [a6989586621679442457]) Source #
Instances
| SuppressUnusedWarnings (DeleteBySym2 :: (TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) -> a6989586621679442457 -> TyFun [a6989586621679442457] [a6989586621679442457] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DeleteBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # | |
type DeleteBySym3 (t :: TyFun a6989586621679442457 (TyFun a6989586621679442457 Bool -> Type) -> Type) (t :: a6989586621679442457) (t :: [a6989586621679442457]) = DeleteBy t t t Source #
data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) (TyFun [a6989586621679442456] (TyFun [a6989586621679442456] [a6989586621679442456] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) (TyFun [a6989586621679442456] (TyFun [a6989586621679442456] [a6989586621679442456] -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) (TyFun [a6989586621679442456] (TyFun [a6989586621679442456] [a6989586621679442456] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) Source # | |
type Apply (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) (TyFun [a6989586621679442456] (TyFun [a6989586621679442456] [a6989586621679442456] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) = DeleteFirstsBySym1 l | |
data DeleteFirstsBySym1 (l :: TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) (l :: TyFun [a6989586621679442456] (TyFun [a6989586621679442456] [a6989586621679442456] -> Type)) Source #
Instances
| SuppressUnusedWarnings (DeleteFirstsBySym1 :: (TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) -> TyFun [a6989586621679442456] (TyFun [a6989586621679442456] [a6989586621679442456] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DeleteFirstsBySym1 l1 :: TyFun [a6989586621679442456] (TyFun [a6989586621679442456] [a6989586621679442456] -> Type) -> *) (l2 :: [a6989586621679442456]) Source # | |
type Apply (DeleteFirstsBySym1 l1 :: TyFun [a6989586621679442456] (TyFun [a6989586621679442456] [a6989586621679442456] -> Type) -> *) (l2 :: [a6989586621679442456]) = DeleteFirstsBySym2 l1 l2 | |
data DeleteFirstsBySym2 (l :: TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) (l :: [a6989586621679442456]) (l :: TyFun [a6989586621679442456] [a6989586621679442456]) Source #
Instances
| SuppressUnusedWarnings (DeleteFirstsBySym2 :: (TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) -> [a6989586621679442456] -> TyFun [a6989586621679442456] [a6989586621679442456] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DeleteFirstsBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # | |
type DeleteFirstsBySym3 (t :: TyFun a6989586621679442456 (TyFun a6989586621679442456 Bool -> Type) -> Type) (t :: [a6989586621679442456]) (t :: [a6989586621679442456]) = DeleteFirstsBy t t t Source #
data UnionBySym0 (l :: TyFun (TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) (TyFun [a6989586621679442416] (TyFun [a6989586621679442416] [a6989586621679442416] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (UnionBySym0 :: TyFun (TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) (TyFun [a6989586621679442416] (TyFun [a6989586621679442416] [a6989586621679442416] -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (UnionBySym0 :: TyFun (TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) (TyFun [a6989586621679442416] (TyFun [a6989586621679442416] [a6989586621679442416] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) Source # | |
type Apply (UnionBySym0 :: TyFun (TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) (TyFun [a6989586621679442416] (TyFun [a6989586621679442416] [a6989586621679442416] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) = UnionBySym1 l | |
data UnionBySym1 (l :: TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) (l :: TyFun [a6989586621679442416] (TyFun [a6989586621679442416] [a6989586621679442416] -> Type)) Source #
Instances
| SuppressUnusedWarnings (UnionBySym1 :: (TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) -> TyFun [a6989586621679442416] (TyFun [a6989586621679442416] [a6989586621679442416] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (UnionBySym1 l1 :: TyFun [a6989586621679442416] (TyFun [a6989586621679442416] [a6989586621679442416] -> Type) -> *) (l2 :: [a6989586621679442416]) Source # | |
type Apply (UnionBySym1 l1 :: TyFun [a6989586621679442416] (TyFun [a6989586621679442416] [a6989586621679442416] -> Type) -> *) (l2 :: [a6989586621679442416]) = UnionBySym2 l1 l2 | |
data UnionBySym2 (l :: TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) (l :: [a6989586621679442416]) (l :: TyFun [a6989586621679442416] [a6989586621679442416]) Source #
Instances
| SuppressUnusedWarnings (UnionBySym2 :: (TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) -> [a6989586621679442416] -> TyFun [a6989586621679442416] [a6989586621679442416] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (UnionBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # | |
type UnionBySym3 (t :: TyFun a6989586621679442416 (TyFun a6989586621679442416 Bool -> Type) -> Type) (t :: [a6989586621679442416]) (t :: [a6989586621679442416]) = UnionBy t t t Source #
data IntersectBySym0 (l :: TyFun (TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) (TyFun [a6989586621679442444] (TyFun [a6989586621679442444] [a6989586621679442444] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (IntersectBySym0 :: TyFun (TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) (TyFun [a6989586621679442444] (TyFun [a6989586621679442444] [a6989586621679442444] -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IntersectBySym0 :: TyFun (TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) (TyFun [a6989586621679442444] (TyFun [a6989586621679442444] [a6989586621679442444] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) Source # | |
type Apply (IntersectBySym0 :: TyFun (TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) (TyFun [a6989586621679442444] (TyFun [a6989586621679442444] [a6989586621679442444] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) = IntersectBySym1 l | |
data IntersectBySym1 (l :: TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) (l :: TyFun [a6989586621679442444] (TyFun [a6989586621679442444] [a6989586621679442444] -> Type)) Source #
Instances
| SuppressUnusedWarnings (IntersectBySym1 :: (TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) -> TyFun [a6989586621679442444] (TyFun [a6989586621679442444] [a6989586621679442444] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IntersectBySym1 l1 :: TyFun [a6989586621679442444] (TyFun [a6989586621679442444] [a6989586621679442444] -> Type) -> *) (l2 :: [a6989586621679442444]) Source # | |
type Apply (IntersectBySym1 l1 :: TyFun [a6989586621679442444] (TyFun [a6989586621679442444] [a6989586621679442444] -> Type) -> *) (l2 :: [a6989586621679442444]) = IntersectBySym2 l1 l2 | |
data IntersectBySym2 (l :: TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) (l :: [a6989586621679442444]) (l :: TyFun [a6989586621679442444] [a6989586621679442444]) Source #
Instances
| SuppressUnusedWarnings (IntersectBySym2 :: (TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) -> [a6989586621679442444] -> TyFun [a6989586621679442444] [a6989586621679442444] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IntersectBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # | |
type IntersectBySym3 (t :: TyFun a6989586621679442444 (TyFun a6989586621679442444 Bool -> Type) -> Type) (t :: [a6989586621679442444]) (t :: [a6989586621679442444]) = IntersectBy t t t Source #
data GroupBySym0 (l :: TyFun (TyFun a6989586621679442430 (TyFun a6989586621679442430 Bool -> Type) -> Type) (TyFun [a6989586621679442430] [[a6989586621679442430]] -> Type)) Source #
Instances
| SuppressUnusedWarnings (GroupBySym0 :: TyFun (TyFun a6989586621679442430 (TyFun a6989586621679442430 Bool -> Type) -> Type) (TyFun [a6989586621679442430] [[a6989586621679442430]] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (GroupBySym0 :: TyFun (TyFun a6989586621679442430 (TyFun a6989586621679442430 Bool -> Type) -> Type) (TyFun [a6989586621679442430] [[a6989586621679442430]] -> Type) -> *) (l :: TyFun a6989586621679442430 (TyFun a6989586621679442430 Bool -> Type) -> Type) Source # | |
data GroupBySym1 (l :: TyFun a6989586621679442430 (TyFun a6989586621679442430 Bool -> Type) -> Type) (l :: TyFun [a6989586621679442430] [[a6989586621679442430]]) Source #
Instances
| SuppressUnusedWarnings (GroupBySym1 :: (TyFun a6989586621679442430 (TyFun a6989586621679442430 Bool -> Type) -> Type) -> TyFun [a6989586621679442430] [[a6989586621679442430]] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (GroupBySym1 l1 :: TyFun [a] [[a]] -> *) (l2 :: [a]) Source # | |
type GroupBySym2 (t :: TyFun a6989586621679442430 (TyFun a6989586621679442430 Bool -> Type) -> Type) (t :: [a6989586621679442430]) = GroupBy t t Source #
data SortBySym0 (l :: TyFun (TyFun a6989586621679442455 (TyFun a6989586621679442455 Ordering -> Type) -> Type) (TyFun [a6989586621679442455] [a6989586621679442455] -> Type)) Source #
Instances
| SuppressUnusedWarnings (SortBySym0 :: TyFun (TyFun a6989586621679442455 (TyFun a6989586621679442455 Ordering -> Type) -> Type) (TyFun [a6989586621679442455] [a6989586621679442455] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (SortBySym0 :: TyFun (TyFun a6989586621679442455 (TyFun a6989586621679442455 Ordering -> Type) -> Type) (TyFun [a6989586621679442455] [a6989586621679442455] -> Type) -> *) (l :: TyFun a6989586621679442455 (TyFun a6989586621679442455 Ordering -> Type) -> Type) Source # | |
data SortBySym1 (l :: TyFun a6989586621679442455 (TyFun a6989586621679442455 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679442455] [a6989586621679442455]) Source #
Instances
| SuppressUnusedWarnings (SortBySym1 :: (TyFun a6989586621679442455 (TyFun a6989586621679442455 Ordering -> Type) -> Type) -> TyFun [a6989586621679442455] [a6989586621679442455] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (SortBySym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type SortBySym2 (t :: TyFun a6989586621679442455 (TyFun a6989586621679442455 Ordering -> Type) -> Type) (t :: [a6989586621679442455]) = SortBy t t Source #
data InsertBySym0 (l :: TyFun (TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) (TyFun a6989586621679442454 (TyFun [a6989586621679442454] [a6989586621679442454] -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (InsertBySym0 :: TyFun (TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) (TyFun a6989586621679442454 (TyFun [a6989586621679442454] [a6989586621679442454] -> Type) -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (InsertBySym0 :: TyFun (TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) (TyFun a6989586621679442454 (TyFun [a6989586621679442454] [a6989586621679442454] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) Source # | |
type Apply (InsertBySym0 :: TyFun (TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) (TyFun a6989586621679442454 (TyFun [a6989586621679442454] [a6989586621679442454] -> Type) -> Type) -> *) (l :: TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) = InsertBySym1 l | |
data InsertBySym1 (l :: TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) (l :: TyFun a6989586621679442454 (TyFun [a6989586621679442454] [a6989586621679442454] -> Type)) Source #
Instances
| SuppressUnusedWarnings (InsertBySym1 :: (TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) -> TyFun a6989586621679442454 (TyFun [a6989586621679442454] [a6989586621679442454] -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (InsertBySym1 l1 :: TyFun a6989586621679442454 (TyFun [a6989586621679442454] [a6989586621679442454] -> Type) -> *) (l2 :: a6989586621679442454) Source # | |
type Apply (InsertBySym1 l1 :: TyFun a6989586621679442454 (TyFun [a6989586621679442454] [a6989586621679442454] -> Type) -> *) (l2 :: a6989586621679442454) = InsertBySym2 l1 l2 | |
data InsertBySym2 (l :: TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) (l :: a6989586621679442454) (l :: TyFun [a6989586621679442454] [a6989586621679442454]) Source #
Instances
| SuppressUnusedWarnings (InsertBySym2 :: (TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) -> a6989586621679442454 -> TyFun [a6989586621679442454] [a6989586621679442454] -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (InsertBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # | |
type InsertBySym3 (t :: TyFun a6989586621679442454 (TyFun a6989586621679442454 Ordering -> Type) -> Type) (t :: a6989586621679442454) (t :: [a6989586621679442454]) = InsertBy t t t Source #
data MaximumBySym0 (l :: TyFun (TyFun a6989586621679442453 (TyFun a6989586621679442453 Ordering -> Type) -> Type) (TyFun [a6989586621679442453] a6989586621679442453 -> Type)) Source #
Instances
| SuppressUnusedWarnings (MaximumBySym0 :: TyFun (TyFun a6989586621679442453 (TyFun a6989586621679442453 Ordering -> Type) -> Type) (TyFun [a6989586621679442453] a6989586621679442453 -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MaximumBySym0 :: TyFun (TyFun a6989586621679442453 (TyFun a6989586621679442453 Ordering -> Type) -> Type) (TyFun [a6989586621679442453] a6989586621679442453 -> Type) -> *) (l :: TyFun a6989586621679442453 (TyFun a6989586621679442453 Ordering -> Type) -> Type) Source # | |
data MaximumBySym1 (l :: TyFun a6989586621679442453 (TyFun a6989586621679442453 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679442453] a6989586621679442453) Source #
Instances
| SuppressUnusedWarnings (MaximumBySym1 :: (TyFun a6989586621679442453 (TyFun a6989586621679442453 Ordering -> Type) -> Type) -> TyFun [a6989586621679442453] a6989586621679442453 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MaximumBySym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # | |
type MaximumBySym2 (t :: TyFun a6989586621679442453 (TyFun a6989586621679442453 Ordering -> Type) -> Type) (t :: [a6989586621679442453]) = MaximumBy t t Source #
data MinimumBySym0 (l :: TyFun (TyFun a6989586621679442452 (TyFun a6989586621679442452 Ordering -> Type) -> Type) (TyFun [a6989586621679442452] a6989586621679442452 -> Type)) Source #
Instances
| SuppressUnusedWarnings (MinimumBySym0 :: TyFun (TyFun a6989586621679442452 (TyFun a6989586621679442452 Ordering -> Type) -> Type) (TyFun [a6989586621679442452] a6989586621679442452 -> Type) -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MinimumBySym0 :: TyFun (TyFun a6989586621679442452 (TyFun a6989586621679442452 Ordering -> Type) -> Type) (TyFun [a6989586621679442452] a6989586621679442452 -> Type) -> *) (l :: TyFun a6989586621679442452 (TyFun a6989586621679442452 Ordering -> Type) -> Type) Source # | |
data MinimumBySym1 (l :: TyFun a6989586621679442452 (TyFun a6989586621679442452 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679442452] a6989586621679442452) Source #
Instances
| SuppressUnusedWarnings (MinimumBySym1 :: (TyFun a6989586621679442452 (TyFun a6989586621679442452 Ordering -> Type) -> Type) -> TyFun [a6989586621679442452] a6989586621679442452 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MinimumBySym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # | |
type MinimumBySym2 (t :: TyFun a6989586621679442452 (TyFun a6989586621679442452 Ordering -> Type) -> Type) (t :: [a6989586621679442452]) = MinimumBy t t Source #
data GenericLengthSym0 (l :: TyFun [a6989586621679442414] i6989586621679442413) Source #
Instances
| SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a6989586621679442414] i6989586621679442413 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
| type Apply (GenericLengthSym0 :: TyFun [a] k2 -> *) (l :: [a]) Source # | |
type GenericLengthSym1 (t :: [a6989586621679442414]) = GenericLength t Source #