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 |
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 :: [a6989586621679448469]) (t :: [a6989586621679448469]) = (++) t t
- data (l :: [a6989586621679448469]) ++@#@$$ (l :: TyFun [a6989586621679448469] [a6989586621679448469])
- data (++@#@$) (l :: TyFun [a6989586621679448469] (TyFun [a6989586621679448469] [a6989586621679448469] -> Type))
- data HeadSym0 (l :: TyFun [a6989586621679473042] a6989586621679473042)
- type HeadSym1 (t :: [a6989586621679473042]) = Head t
- data LastSym0 (l :: TyFun [a6989586621679473041] a6989586621679473041)
- type LastSym1 (t :: [a6989586621679473041]) = Last t
- data TailSym0 (l :: TyFun [a6989586621679473040] [a6989586621679473040])
- type TailSym1 (t :: [a6989586621679473040]) = Tail t
- data InitSym0 (l :: TyFun [a6989586621679473039] [a6989586621679473039])
- type InitSym1 (t :: [a6989586621679473039]) = Init t
- data NullSym0 (l :: TyFun [a6989586621679473038] Bool)
- type NullSym1 (t :: [a6989586621679473038]) = Null t
- data LengthSym0 (l :: TyFun [a6989586621679472924] Nat)
- type LengthSym1 (t :: [a6989586621679472924]) = Length t
- data MapSym0 (l :: TyFun (TyFun a6989586621679448470 b6989586621679448471 -> Type) (TyFun [a6989586621679448470] [b6989586621679448471] -> Type))
- data MapSym1 (l :: TyFun a6989586621679448470 b6989586621679448471 -> Type) (l :: TyFun [a6989586621679448470] [b6989586621679448471])
- type MapSym2 (t :: TyFun a6989586621679448470 b6989586621679448471 -> Type) (t :: [a6989586621679448470]) = Map t t
- data ReverseSym0 (l :: TyFun [a6989586621679473037] [a6989586621679473037])
- type ReverseSym1 (t :: [a6989586621679473037]) = Reverse t
- data IntersperseSym0 (l :: TyFun a6989586621679473036 (TyFun [a6989586621679473036] [a6989586621679473036] -> Type))
- data IntersperseSym1 (l :: a6989586621679473036) (l :: TyFun [a6989586621679473036] [a6989586621679473036])
- type IntersperseSym2 (t :: a6989586621679473036) (t :: [a6989586621679473036]) = Intersperse t t
- data IntercalateSym0 (l :: TyFun [a6989586621679473035] (TyFun [[a6989586621679473035]] [a6989586621679473035] -> Type))
- data IntercalateSym1 (l :: [a6989586621679473035]) (l :: TyFun [[a6989586621679473035]] [a6989586621679473035])
- type IntercalateSym2 (t :: [a6989586621679473035]) (t :: [[a6989586621679473035]]) = Intercalate t t
- data TransposeSym0 (l :: TyFun [[a6989586621679472922]] [[a6989586621679472922]])
- type TransposeSym1 (t :: [[a6989586621679472922]]) = Transpose t
- data SubsequencesSym0 (l :: TyFun [a6989586621679473034] [[a6989586621679473034]])
- type SubsequencesSym1 (t :: [a6989586621679473034]) = Subsequences t
- data PermutationsSym0 (l :: TyFun [a6989586621679473031] [[a6989586621679473031]])
- type PermutationsSym1 (t :: [a6989586621679473031]) = Permutations t
- data FoldlSym0 (l :: TyFun (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> Type))
- data FoldlSym1 (l :: TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (l :: TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type))
- data FoldlSym2 (l :: TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (l :: b6989586621679273480) (l :: TyFun [a6989586621679273479] b6989586621679273480)
- type FoldlSym3 (t :: TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (t :: b6989586621679273480) (t :: [a6989586621679273479]) = Foldl t t t
- data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) (TyFun b6989586621679473030 (TyFun [a6989586621679473029] b6989586621679473030 -> Type) -> Type))
- data Foldl'Sym1 (l :: TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) (l :: TyFun b6989586621679473030 (TyFun [a6989586621679473029] b6989586621679473030 -> Type))
- data Foldl'Sym2 (l :: TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) (l :: b6989586621679473030) (l :: TyFun [a6989586621679473029] b6989586621679473030)
- type Foldl'Sym3 (t :: TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) (t :: b6989586621679473030) (t :: [a6989586621679473029]) = Foldl' t t t
- data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) (TyFun [a6989586621679473028] a6989586621679473028 -> Type))
- data Foldl1Sym1 (l :: TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) (l :: TyFun [a6989586621679473028] a6989586621679473028)
- type Foldl1Sym2 (t :: TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) (t :: [a6989586621679473028]) = Foldl1 t t
- data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) (TyFun [a6989586621679473027] a6989586621679473027 -> Type))
- data Foldl1'Sym1 (l :: TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) (l :: TyFun [a6989586621679473027] a6989586621679473027)
- type Foldl1'Sym2 (t :: TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) (t :: [a6989586621679473027]) = Foldl1' t t
- data FoldrSym0 (l :: TyFun (TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) (TyFun b6989586621679448473 (TyFun [a6989586621679448472] b6989586621679448473 -> Type) -> Type))
- data FoldrSym1 (l :: TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) (l :: TyFun b6989586621679448473 (TyFun [a6989586621679448472] b6989586621679448473 -> Type))
- data FoldrSym2 (l :: TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) (l :: b6989586621679448473) (l :: TyFun [a6989586621679448472] b6989586621679448473)
- type FoldrSym3 (t :: TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) (t :: b6989586621679448473) (t :: [a6989586621679448472]) = Foldr t t t
- data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) (TyFun [a6989586621679473026] a6989586621679473026 -> Type))
- data Foldr1Sym1 (l :: TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) (l :: TyFun [a6989586621679473026] a6989586621679473026)
- type Foldr1Sym2 (t :: TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) (t :: [a6989586621679473026]) = Foldr1 t t
- data ConcatSym0 (l :: TyFun [[a6989586621679473025]] [a6989586621679473025])
- type ConcatSym1 (t :: [[a6989586621679473025]]) = Concat t
- data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679473023 [b6989586621679473024] -> Type) (TyFun [a6989586621679473023] [b6989586621679473024] -> Type))
- data ConcatMapSym1 (l :: TyFun a6989586621679473023 [b6989586621679473024] -> Type) (l :: TyFun [a6989586621679473023] [b6989586621679473024])
- type ConcatMapSym2 (t :: TyFun a6989586621679473023 [b6989586621679473024] -> Type) (t :: [a6989586621679473023]) = 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 a6989586621679473021 Bool -> Type) (TyFun [a6989586621679473021] Bool -> Type))
- data AnySym1 (l :: TyFun a6989586621679473021 Bool -> Type) (l :: TyFun [a6989586621679473021] Bool)
- type AnySym2 (t :: TyFun a6989586621679473021 Bool -> Type) (t :: [a6989586621679473021]) = Any t t
- data AllSym0 (l :: TyFun (TyFun a6989586621679473022 Bool -> Type) (TyFun [a6989586621679473022] Bool -> Type))
- data AllSym1 (l :: TyFun a6989586621679473022 Bool -> Type) (l :: TyFun [a6989586621679473022] Bool)
- type AllSym2 (t :: TyFun a6989586621679473022 Bool -> Type) (t :: [a6989586621679473022]) = All t t
- data SumSym0 (l :: TyFun [a6989586621679472926] a6989586621679472926)
- type SumSym1 (t :: [a6989586621679472926]) = Sum t
- data ProductSym0 (l :: TyFun [a6989586621679472925] a6989586621679472925)
- type ProductSym1 (t :: [a6989586621679472925]) = Product t
- data MaximumSym0 (l :: TyFun [a6989586621679472935] a6989586621679472935)
- type MaximumSym1 (t :: [a6989586621679472935]) = Maximum t
- data MinimumSym0 (l :: TyFun [a6989586621679472934] a6989586621679472934)
- type MinimumSym1 (t :: [a6989586621679472934]) = Minimum t
- data ScanlSym0 (l :: TyFun (TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) (TyFun b6989586621679473019 (TyFun [a6989586621679473020] [b6989586621679473019] -> Type) -> Type))
- data ScanlSym1 (l :: TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) (l :: TyFun b6989586621679473019 (TyFun [a6989586621679473020] [b6989586621679473019] -> Type))
- data ScanlSym2 (l :: TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) (l :: b6989586621679473019) (l :: TyFun [a6989586621679473020] [b6989586621679473019])
- type ScanlSym3 (t :: TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) (t :: b6989586621679473019) (t :: [a6989586621679473020]) = Scanl t t t
- data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) (TyFun [a6989586621679473018] [a6989586621679473018] -> Type))
- data Scanl1Sym1 (l :: TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) (l :: TyFun [a6989586621679473018] [a6989586621679473018])
- type Scanl1Sym2 (t :: TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) (t :: [a6989586621679473018]) = Scanl1 t t
- data ScanrSym0 (l :: TyFun (TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) (TyFun b6989586621679473017 (TyFun [a6989586621679473016] [b6989586621679473017] -> Type) -> Type))
- data ScanrSym1 (l :: TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) (l :: TyFun b6989586621679473017 (TyFun [a6989586621679473016] [b6989586621679473017] -> Type))
- data ScanrSym2 (l :: TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) (l :: b6989586621679473017) (l :: TyFun [a6989586621679473016] [b6989586621679473017])
- type ScanrSym3 (t :: TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) (t :: b6989586621679473017) (t :: [a6989586621679473016]) = Scanr t t t
- data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) (TyFun [a6989586621679473015] [a6989586621679473015] -> Type))
- data Scanr1Sym1 (l :: TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) (l :: TyFun [a6989586621679473015] [a6989586621679473015])
- type Scanr1Sym2 (t :: TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) (t :: [a6989586621679473015]) = Scanr1 t t
- data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) (TyFun acc6989586621679473012 (TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> Type) -> Type))
- data MapAccumLSym1 (l :: TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) (l :: TyFun acc6989586621679473012 (TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> Type))
- data MapAccumLSym2 (l :: TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) (l :: acc6989586621679473012) (l :: TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]))
- type MapAccumLSym3 (t :: TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) (t :: acc6989586621679473012) (t :: [x6989586621679473013]) = MapAccumL t t t
- data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) (TyFun acc6989586621679473009 (TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> Type) -> Type))
- data MapAccumRSym1 (l :: TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) (l :: TyFun acc6989586621679473009 (TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> Type))
- data MapAccumRSym2 (l :: TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) (l :: acc6989586621679473009) (l :: TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]))
- type MapAccumRSym3 (t :: TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) (t :: acc6989586621679473009) (t :: [x6989586621679473010]) = MapAccumR t t t
- data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679472923 [a6989586621679472923] -> Type))
- data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679472923 [a6989586621679472923])
- type ReplicateSym2 (t :: Nat) (t :: a6989586621679472923) = Replicate t t
- data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679473007 (Maybe (a6989586621679473008, b6989586621679473007)) -> Type) (TyFun b6989586621679473007 [a6989586621679473008] -> Type))
- data UnfoldrSym1 (l :: TyFun b6989586621679473007 (Maybe (a6989586621679473008, b6989586621679473007)) -> Type) (l :: TyFun b6989586621679473007 [a6989586621679473008])
- type UnfoldrSym2 (t :: TyFun b6989586621679473007 (Maybe (a6989586621679473008, b6989586621679473007)) -> Type) (t :: b6989586621679473007) = Unfoldr t t
- data TakeSym0 (l :: TyFun Nat (TyFun [a6989586621679472939] [a6989586621679472939] -> Type))
- data TakeSym1 (l :: Nat) (l :: TyFun [a6989586621679472939] [a6989586621679472939])
- type TakeSym2 (t :: Nat) (t :: [a6989586621679472939]) = Take t t
- data DropSym0 (l :: TyFun Nat (TyFun [a6989586621679472938] [a6989586621679472938] -> Type))
- data DropSym1 (l :: Nat) (l :: TyFun [a6989586621679472938] [a6989586621679472938])
- type DropSym2 (t :: Nat) (t :: [a6989586621679472938]) = Drop t t
- data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679472937] ([a6989586621679472937], [a6989586621679472937]) -> Type))
- data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679472937] ([a6989586621679472937], [a6989586621679472937]))
- type SplitAtSym2 (t :: Nat) (t :: [a6989586621679472937]) = SplitAt t t
- data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679472944 Bool -> Type) (TyFun [a6989586621679472944] [a6989586621679472944] -> Type))
- data TakeWhileSym1 (l :: TyFun a6989586621679472944 Bool -> Type) (l :: TyFun [a6989586621679472944] [a6989586621679472944])
- type TakeWhileSym2 (t :: TyFun a6989586621679472944 Bool -> Type) (t :: [a6989586621679472944]) = TakeWhile t t
- data DropWhileSym0 (l :: TyFun (TyFun a6989586621679472943 Bool -> Type) (TyFun [a6989586621679472943] [a6989586621679472943] -> Type))
- data DropWhileSym1 (l :: TyFun a6989586621679472943 Bool -> Type) (l :: TyFun [a6989586621679472943] [a6989586621679472943])
- type DropWhileSym2 (t :: TyFun a6989586621679472943 Bool -> Type) (t :: [a6989586621679472943]) = DropWhile t t
- data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679472942 Bool -> Type) (TyFun [a6989586621679472942] [a6989586621679472942] -> Type))
- data DropWhileEndSym1 (l :: TyFun a6989586621679472942 Bool -> Type) (l :: TyFun [a6989586621679472942] [a6989586621679472942])
- type DropWhileEndSym2 (t :: TyFun a6989586621679472942 Bool -> Type) (t :: [a6989586621679472942]) = DropWhileEnd t t
- data SpanSym0 (l :: TyFun (TyFun a6989586621679472941 Bool -> Type) (TyFun [a6989586621679472941] ([a6989586621679472941], [a6989586621679472941]) -> Type))
- data SpanSym1 (l :: TyFun a6989586621679472941 Bool -> Type) (l :: TyFun [a6989586621679472941] ([a6989586621679472941], [a6989586621679472941]))
- type SpanSym2 (t :: TyFun a6989586621679472941 Bool -> Type) (t :: [a6989586621679472941]) = Span t t
- data BreakSym0 (l :: TyFun (TyFun a6989586621679472940 Bool -> Type) (TyFun [a6989586621679472940] ([a6989586621679472940], [a6989586621679472940]) -> Type))
- data BreakSym1 (l :: TyFun a6989586621679472940 Bool -> Type) (l :: TyFun [a6989586621679472940] ([a6989586621679472940], [a6989586621679472940]))
- type BreakSym2 (t :: TyFun a6989586621679472940 Bool -> Type) (t :: [a6989586621679472940]) = Break t t
- data GroupSym0 (l :: TyFun [a6989586621679472936] [[a6989586621679472936]])
- type GroupSym1 (t :: [a6989586621679472936]) = Group t
- data InitsSym0 (l :: TyFun [a6989586621679473006] [[a6989586621679473006]])
- type InitsSym1 (t :: [a6989586621679473006]) = Inits t
- data TailsSym0 (l :: TyFun [a6989586621679473005] [[a6989586621679473005]])
- type TailsSym1 (t :: [a6989586621679473005]) = Tails t
- data IsPrefixOfSym0 (l :: TyFun [a6989586621679473004] (TyFun [a6989586621679473004] Bool -> Type))
- data IsPrefixOfSym1 (l :: [a6989586621679473004]) (l :: TyFun [a6989586621679473004] Bool)
- type IsPrefixOfSym2 (t :: [a6989586621679473004]) (t :: [a6989586621679473004]) = IsPrefixOf t t
- data IsSuffixOfSym0 (l :: TyFun [a6989586621679473003] (TyFun [a6989586621679473003] Bool -> Type))
- data IsSuffixOfSym1 (l :: [a6989586621679473003]) (l :: TyFun [a6989586621679473003] Bool)
- type IsSuffixOfSym2 (t :: [a6989586621679473003]) (t :: [a6989586621679473003]) = IsSuffixOf t t
- data IsInfixOfSym0 (l :: TyFun [a6989586621679473002] (TyFun [a6989586621679473002] Bool -> Type))
- data IsInfixOfSym1 (l :: [a6989586621679473002]) (l :: TyFun [a6989586621679473002] Bool)
- type IsInfixOfSym2 (t :: [a6989586621679473002]) (t :: [a6989586621679473002]) = IsInfixOf t t
- data ElemSym0 (l :: TyFun a6989586621679473001 (TyFun [a6989586621679473001] Bool -> Type))
- data ElemSym1 (l :: a6989586621679473001) (l :: TyFun [a6989586621679473001] Bool)
- type ElemSym2 (t :: a6989586621679473001) (t :: [a6989586621679473001]) = Elem t t
- data NotElemSym0 (l :: TyFun a6989586621679473000 (TyFun [a6989586621679473000] Bool -> Type))
- data NotElemSym1 (l :: a6989586621679473000) (l :: TyFun [a6989586621679473000] Bool)
- type NotElemSym2 (t :: a6989586621679473000) (t :: [a6989586621679473000]) = NotElem t t
- data LookupSym0 (l :: TyFun a6989586621679472929 (TyFun [(a6989586621679472929, b6989586621679472930)] (Maybe b6989586621679472930) -> Type))
- data LookupSym1 (l :: a6989586621679472929) (l :: TyFun [(a6989586621679472929, b6989586621679472930)] (Maybe b6989586621679472930))
- type LookupSym2 (t :: a6989586621679472929) (t :: [(a6989586621679472929, b6989586621679472930)]) = Lookup t t
- data FindSym0 (l :: TyFun (TyFun a6989586621679472951 Bool -> Type) (TyFun [a6989586621679472951] (Maybe a6989586621679472951) -> Type))
- data FindSym1 (l :: TyFun a6989586621679472951 Bool -> Type) (l :: TyFun [a6989586621679472951] (Maybe a6989586621679472951))
- type FindSym2 (t :: TyFun a6989586621679472951 Bool -> Type) (t :: [a6989586621679472951]) = Find t t
- data FilterSym0 (l :: TyFun (TyFun a6989586621679472952 Bool -> Type) (TyFun [a6989586621679472952] [a6989586621679472952] -> Type))
- data FilterSym1 (l :: TyFun a6989586621679472952 Bool -> Type) (l :: TyFun [a6989586621679472952] [a6989586621679472952])
- type FilterSym2 (t :: TyFun a6989586621679472952 Bool -> Type) (t :: [a6989586621679472952]) = Filter t t
- data PartitionSym0 (l :: TyFun (TyFun a6989586621679472928 Bool -> Type) (TyFun [a6989586621679472928] ([a6989586621679472928], [a6989586621679472928]) -> Type))
- data PartitionSym1 (l :: TyFun a6989586621679472928 Bool -> Type) (l :: TyFun [a6989586621679472928] ([a6989586621679472928], [a6989586621679472928]))
- type PartitionSym2 (t :: TyFun a6989586621679472928 Bool -> Type) (t :: [a6989586621679472928]) = Partition t t
- data (!!@#@$) (l :: TyFun [a6989586621679472921] (TyFun Nat a6989586621679472921 -> Type))
- data (l :: [a6989586621679472921]) !!@#@$$ (l :: TyFun Nat a6989586621679472921)
- type (!!@#@$$$) (t :: [a6989586621679472921]) (t :: Nat) = (!!) t t
- data ElemIndexSym0 (l :: TyFun a6989586621679472950 (TyFun [a6989586621679472950] (Maybe Nat) -> Type))
- data ElemIndexSym1 (l :: a6989586621679472950) (l :: TyFun [a6989586621679472950] (Maybe Nat))
- type ElemIndexSym2 (t :: a6989586621679472950) (t :: [a6989586621679472950]) = ElemIndex t t
- data ElemIndicesSym0 (l :: TyFun a6989586621679472949 (TyFun [a6989586621679472949] [Nat] -> Type))
- data ElemIndicesSym1 (l :: a6989586621679472949) (l :: TyFun [a6989586621679472949] [Nat])
- type ElemIndicesSym2 (t :: a6989586621679472949) (t :: [a6989586621679472949]) = ElemIndices t t
- data FindIndexSym0 (l :: TyFun (TyFun a6989586621679472948 Bool -> Type) (TyFun [a6989586621679472948] (Maybe Nat) -> Type))
- data FindIndexSym1 (l :: TyFun a6989586621679472948 Bool -> Type) (l :: TyFun [a6989586621679472948] (Maybe Nat))
- type FindIndexSym2 (t :: TyFun a6989586621679472948 Bool -> Type) (t :: [a6989586621679472948]) = FindIndex t t
- data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679472947 Bool -> Type) (TyFun [a6989586621679472947] [Nat] -> Type))
- data FindIndicesSym1 (l :: TyFun a6989586621679472947 Bool -> Type) (l :: TyFun [a6989586621679472947] [Nat])
- type FindIndicesSym2 (t :: TyFun a6989586621679472947 Bool -> Type) (t :: [a6989586621679472947]) = FindIndices t t
- data ZipSym0 (l :: TyFun [a6989586621679472998] (TyFun [b6989586621679472999] [(a6989586621679472998, b6989586621679472999)] -> Type))
- data ZipSym1 (l :: [a6989586621679472998]) (l :: TyFun [b6989586621679472999] [(a6989586621679472998, b6989586621679472999)])
- type ZipSym2 (t :: [a6989586621679472998]) (t :: [b6989586621679472999]) = Zip t t
- data Zip3Sym0 (l :: TyFun [a6989586621679472995] (TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type) -> Type))
- data Zip3Sym1 (l :: [a6989586621679472995]) (l :: TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type))
- data Zip3Sym2 (l :: [a6989586621679472995]) (l :: [b6989586621679472996]) (l :: TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)])
- type Zip3Sym3 (t :: [a6989586621679472995]) (t :: [b6989586621679472996]) (t :: [c6989586621679472997]) = Zip3 t t t
- data ZipWithSym0 (l :: TyFun (TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) (TyFun [a6989586621679472992] (TyFun [b6989586621679472993] [c6989586621679472994] -> Type) -> Type))
- data ZipWithSym1 (l :: TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) (l :: TyFun [a6989586621679472992] (TyFun [b6989586621679472993] [c6989586621679472994] -> Type))
- data ZipWithSym2 (l :: TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) (l :: [a6989586621679472992]) (l :: TyFun [b6989586621679472993] [c6989586621679472994])
- type ZipWithSym3 (t :: TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) (t :: [a6989586621679472992]) (t :: [b6989586621679472993]) = ZipWith t t t
- data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (TyFun [a6989586621679472988] (TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> Type) -> Type))
- data ZipWith3Sym1 (l :: TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679472988] (TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> Type))
- data ZipWith3Sym2 (l :: TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (l :: [a6989586621679472988]) (l :: TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type))
- data ZipWith3Sym3 (l :: TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (l :: [a6989586621679472988]) (l :: [b6989586621679472989]) (l :: TyFun [c6989586621679472990] [d6989586621679472991])
- type ZipWith3Sym4 (t :: TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (t :: [a6989586621679472988]) (t :: [b6989586621679472989]) (t :: [c6989586621679472990]) = ZipWith3 t t t t
- data UnzipSym0 (l :: TyFun [(a6989586621679472986, b6989586621679472987)] ([a6989586621679472986], [b6989586621679472987]))
- type UnzipSym1 (t :: [(a6989586621679472986, b6989586621679472987)]) = Unzip t
- data Unzip3Sym0 (l :: TyFun [(a6989586621679472983, b6989586621679472984, c6989586621679472985)] ([a6989586621679472983], [b6989586621679472984], [c6989586621679472985]))
- type Unzip3Sym1 (t :: [(a6989586621679472983, b6989586621679472984, c6989586621679472985)]) = Unzip3 t
- data Unzip4Sym0 (l :: TyFun [(a6989586621679472979, b6989586621679472980, c6989586621679472981, d6989586621679472982)] ([a6989586621679472979], [b6989586621679472980], [c6989586621679472981], [d6989586621679472982]))
- type Unzip4Sym1 (t :: [(a6989586621679472979, b6989586621679472980, c6989586621679472981, d6989586621679472982)]) = Unzip4 t
- data Unzip5Sym0 (l :: TyFun [(a6989586621679472974, b6989586621679472975, c6989586621679472976, d6989586621679472977, e6989586621679472978)] ([a6989586621679472974], [b6989586621679472975], [c6989586621679472976], [d6989586621679472977], [e6989586621679472978]))
- type Unzip5Sym1 (t :: [(a6989586621679472974, b6989586621679472975, c6989586621679472976, d6989586621679472977, e6989586621679472978)]) = Unzip5 t
- data Unzip6Sym0 (l :: TyFun [(a6989586621679472968, b6989586621679472969, c6989586621679472970, d6989586621679472971, e6989586621679472972, f6989586621679472973)] ([a6989586621679472968], [b6989586621679472969], [c6989586621679472970], [d6989586621679472971], [e6989586621679472972], [f6989586621679472973]))
- type Unzip6Sym1 (t :: [(a6989586621679472968, b6989586621679472969, c6989586621679472970, d6989586621679472971, e6989586621679472972, f6989586621679472973)]) = Unzip6 t
- data Unzip7Sym0 (l :: TyFun [(a6989586621679472961, b6989586621679472962, c6989586621679472963, d6989586621679472964, e6989586621679472965, f6989586621679472966, g6989586621679472967)] ([a6989586621679472961], [b6989586621679472962], [c6989586621679472963], [d6989586621679472964], [e6989586621679472965], [f6989586621679472966], [g6989586621679472967]))
- type Unzip7Sym1 (t :: [(a6989586621679472961, b6989586621679472962, c6989586621679472963, d6989586621679472964, e6989586621679472965, f6989586621679472966, g6989586621679472967)]) = 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 [a6989586621679472920] [a6989586621679472920])
- type NubSym1 (t :: [a6989586621679472920]) = Nub t
- data DeleteSym0 (l :: TyFun a6989586621679472960 (TyFun [a6989586621679472960] [a6989586621679472960] -> Type))
- data DeleteSym1 (l :: a6989586621679472960) (l :: TyFun [a6989586621679472960] [a6989586621679472960])
- type DeleteSym2 (t :: a6989586621679472960) (t :: [a6989586621679472960]) = Delete t t
- data (\\@#@$) (l :: TyFun [a6989586621679472959] (TyFun [a6989586621679472959] [a6989586621679472959] -> Type))
- data (l :: [a6989586621679472959]) \\@#@$$ (l :: TyFun [a6989586621679472959] [a6989586621679472959])
- type (\\@#@$$$) (t :: [a6989586621679472959]) (t :: [a6989586621679472959]) = (\\) t t
- data UnionSym0 (l :: TyFun [a6989586621679472916] (TyFun [a6989586621679472916] [a6989586621679472916] -> Type))
- data UnionSym1 (l :: [a6989586621679472916]) (l :: TyFun [a6989586621679472916] [a6989586621679472916])
- type UnionSym2 (t :: [a6989586621679472916]) (t :: [a6989586621679472916]) = Union t t
- data IntersectSym0 (l :: TyFun [a6989586621679472946] (TyFun [a6989586621679472946] [a6989586621679472946] -> Type))
- data IntersectSym1 (l :: [a6989586621679472946]) (l :: TyFun [a6989586621679472946] [a6989586621679472946])
- type IntersectSym2 (t :: [a6989586621679472946]) (t :: [a6989586621679472946]) = Intersect t t
- data InsertSym0 (l :: TyFun a6989586621679472933 (TyFun [a6989586621679472933] [a6989586621679472933] -> Type))
- data InsertSym1 (l :: a6989586621679472933) (l :: TyFun [a6989586621679472933] [a6989586621679472933])
- type InsertSym2 (t :: a6989586621679472933) (t :: [a6989586621679472933]) = Insert t t
- data SortSym0 (l :: TyFun [a6989586621679472932] [a6989586621679472932])
- type SortSym1 (t :: [a6989586621679472932]) = Sort t
- data NubBySym0 (l :: TyFun (TyFun a6989586621679472919 (TyFun a6989586621679472919 Bool -> Type) -> Type) (TyFun [a6989586621679472919] [a6989586621679472919] -> Type))
- data NubBySym1 (l :: TyFun a6989586621679472919 (TyFun a6989586621679472919 Bool -> Type) -> Type) (l :: TyFun [a6989586621679472919] [a6989586621679472919])
- type NubBySym2 (t :: TyFun a6989586621679472919 (TyFun a6989586621679472919 Bool -> Type) -> Type) (t :: [a6989586621679472919]) = NubBy t t
- data DeleteBySym0 (l :: TyFun (TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) (TyFun a6989586621679472958 (TyFun [a6989586621679472958] [a6989586621679472958] -> Type) -> Type))
- data DeleteBySym1 (l :: TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) (l :: TyFun a6989586621679472958 (TyFun [a6989586621679472958] [a6989586621679472958] -> Type))
- data DeleteBySym2 (l :: TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) (l :: a6989586621679472958) (l :: TyFun [a6989586621679472958] [a6989586621679472958])
- type DeleteBySym3 (t :: TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) (t :: a6989586621679472958) (t :: [a6989586621679472958]) = DeleteBy t t t
- data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) (TyFun [a6989586621679472957] (TyFun [a6989586621679472957] [a6989586621679472957] -> Type) -> Type))
- data DeleteFirstsBySym1 (l :: TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) (l :: TyFun [a6989586621679472957] (TyFun [a6989586621679472957] [a6989586621679472957] -> Type))
- data DeleteFirstsBySym2 (l :: TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) (l :: [a6989586621679472957]) (l :: TyFun [a6989586621679472957] [a6989586621679472957])
- type DeleteFirstsBySym3 (t :: TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) (t :: [a6989586621679472957]) (t :: [a6989586621679472957]) = DeleteFirstsBy t t t
- data UnionBySym0 (l :: TyFun (TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) (TyFun [a6989586621679472917] (TyFun [a6989586621679472917] [a6989586621679472917] -> Type) -> Type))
- data UnionBySym1 (l :: TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) (l :: TyFun [a6989586621679472917] (TyFun [a6989586621679472917] [a6989586621679472917] -> Type))
- data UnionBySym2 (l :: TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) (l :: [a6989586621679472917]) (l :: TyFun [a6989586621679472917] [a6989586621679472917])
- type UnionBySym3 (t :: TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) (t :: [a6989586621679472917]) (t :: [a6989586621679472917]) = UnionBy t t t
- data IntersectBySym0 (l :: TyFun (TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) (TyFun [a6989586621679472945] (TyFun [a6989586621679472945] [a6989586621679472945] -> Type) -> Type))
- data IntersectBySym1 (l :: TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) (l :: TyFun [a6989586621679472945] (TyFun [a6989586621679472945] [a6989586621679472945] -> Type))
- data IntersectBySym2 (l :: TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) (l :: [a6989586621679472945]) (l :: TyFun [a6989586621679472945] [a6989586621679472945])
- type IntersectBySym3 (t :: TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) (t :: [a6989586621679472945]) (t :: [a6989586621679472945]) = IntersectBy t t t
- data GroupBySym0 (l :: TyFun (TyFun a6989586621679472931 (TyFun a6989586621679472931 Bool -> Type) -> Type) (TyFun [a6989586621679472931] [[a6989586621679472931]] -> Type))
- data GroupBySym1 (l :: TyFun a6989586621679472931 (TyFun a6989586621679472931 Bool -> Type) -> Type) (l :: TyFun [a6989586621679472931] [[a6989586621679472931]])
- type GroupBySym2 (t :: TyFun a6989586621679472931 (TyFun a6989586621679472931 Bool -> Type) -> Type) (t :: [a6989586621679472931]) = GroupBy t t
- data SortBySym0 (l :: TyFun (TyFun a6989586621679472956 (TyFun a6989586621679472956 Ordering -> Type) -> Type) (TyFun [a6989586621679472956] [a6989586621679472956] -> Type))
- data SortBySym1 (l :: TyFun a6989586621679472956 (TyFun a6989586621679472956 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679472956] [a6989586621679472956])
- type SortBySym2 (t :: TyFun a6989586621679472956 (TyFun a6989586621679472956 Ordering -> Type) -> Type) (t :: [a6989586621679472956]) = SortBy t t
- data InsertBySym0 (l :: TyFun (TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) (TyFun a6989586621679472955 (TyFun [a6989586621679472955] [a6989586621679472955] -> Type) -> Type))
- data InsertBySym1 (l :: TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) (l :: TyFun a6989586621679472955 (TyFun [a6989586621679472955] [a6989586621679472955] -> Type))
- data InsertBySym2 (l :: TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) (l :: a6989586621679472955) (l :: TyFun [a6989586621679472955] [a6989586621679472955])
- type InsertBySym3 (t :: TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) (t :: a6989586621679472955) (t :: [a6989586621679472955]) = InsertBy t t t
- data MaximumBySym0 (l :: TyFun (TyFun a6989586621679472954 (TyFun a6989586621679472954 Ordering -> Type) -> Type) (TyFun [a6989586621679472954] a6989586621679472954 -> Type))
- data MaximumBySym1 (l :: TyFun a6989586621679472954 (TyFun a6989586621679472954 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679472954] a6989586621679472954)
- type MaximumBySym2 (t :: TyFun a6989586621679472954 (TyFun a6989586621679472954 Ordering -> Type) -> Type) (t :: [a6989586621679472954]) = MaximumBy t t
- data MinimumBySym0 (l :: TyFun (TyFun a6989586621679472953 (TyFun a6989586621679472953 Ordering -> Type) -> Type) (TyFun [a6989586621679472953] a6989586621679472953 -> Type))
- data MinimumBySym1 (l :: TyFun a6989586621679472953 (TyFun a6989586621679472953 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679472953] a6989586621679472953)
- type MinimumBySym2 (t :: TyFun a6989586621679472953 (TyFun a6989586621679472953 Ordering -> Type) -> Type) (t :: [a6989586621679472953]) = MinimumBy t t
- data GenericLengthSym0 (l :: TyFun [a6989586621679472915] i6989586621679472914)
- type GenericLengthSym1 (t :: [a6989586621679472915]) = GenericLength t
The singleton for lists
data family Sing (a :: k) infixr 5 Source #
The singleton kind-indexed data family.
Instances
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 #
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 #
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 #
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 #
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 #
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 #
Sum l = Apply (Apply (Let6989586621679482351Sum'Sym1 l) l) (FromInteger 0) |
type family Product (a :: [a]) :: a where ... Source #
Product l = Apply (Apply (Let6989586621679482327ProdSym1 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 #
Scanr1 _ '[] = '[] | |
Scanr1 _ '[x] = Apply (Apply (:@#@$) x) '[] | |
Scanr1 f ((:) x ((:) wild_6989586621679473523 wild_6989586621679473525)) = Case_6989586621679484013 f x wild_6989586621679473523 wild_6989586621679473525 (Let6989586621679483994Scrutinee_6989586621679473517Sym4 f x wild_6989586621679473523 wild_6989586621679473525) |
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 #
Replicate n x = Case_6989586621679482314 n x (Let6989586621679482306Scrutinee_6989586621679473619Sym2 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 #
Unfoldr f b = Case_6989586621679483642 f b (Let6989586621679483634Scrutinee_6989586621679473527Sym2 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 #
Span _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679482627XsSym0) Let6989586621679482627XsSym0 | |
Span p ((:) x xs') = Case_6989586621679482657 p x xs' (Let6989586621679482644Scrutinee_6989586621679473599Sym3 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 #
Break _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679482534XsSym0) Let6989586621679482534XsSym0 | |
Break p ((:) x xs') = Case_6989586621679482564 p x xs' (Let6989586621679482551Scrutinee_6989586621679473601Sym3 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 #
Group xs = Apply (Apply GroupBySym0 (==@#@$)) xs |
Predicates
type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
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 #
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 #
Lookup _key '[] = NothingSym0 | |
Lookup key ((:) '(x, y) xys) = Case_6989586621679482455 key x y xys (Let6989586621679482436Scrutinee_6989586621679473615Sym4 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 #
Find p a_6989586621679482886 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FilterSym0 p)) a_6989586621679482886 |
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 #
ElemIndices x a_6989586621679483492 = Apply (Apply FindIndicesSym0 (Apply (==@#@$) x)) a_6989586621679483492 |
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 #
FindIndex p a_6989586621679483505 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679483505 |
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 #
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 #
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 Symbol
s
"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 #
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 #
Sort a_6989586621679482975 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679482975 |
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 #
DeleteFirstsBy eq a_6989586621679483038 a_6989586621679483040 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679483038) a_6989586621679483040 |
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 #
IntersectBy _ '[] '[] = '[] | |
IntersectBy _ '[] ((:) _ _) = '[] | |
IntersectBy _ ((:) _ _) '[] = '[] | |
IntersectBy eq ((:) wild_6989586621679473585 wild_6989586621679473587) ((:) wild_6989586621679473589 wild_6989586621679473591) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679484191Sym0 eq) wild_6989586621679473585) wild_6989586621679473587) wild_6989586621679473589) wild_6989586621679473591)) (Let6989586621679484140XsSym5 eq wild_6989586621679473585 wild_6989586621679473587 wild_6989586621679473589 wild_6989586621679473591) |
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 #
MaximumBy _ '[] = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" | |
MaximumBy cmp ((:) wild_6989586621679473571 wild_6989586621679473573) = Apply (Apply Foldl1Sym0 (Let6989586621679484357MaxBySym3 cmp wild_6989586621679473571 wild_6989586621679473573)) (Let6989586621679484344XsSym3 cmp wild_6989586621679473571 wild_6989586621679473573) |
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 #
MinimumBy _ '[] = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" | |
MinimumBy cmp ((:) wild_6989586621679473577 wild_6989586621679473579) = Apply (Apply Foldl1Sym0 (Let6989586621679484441MinBySym3 cmp wild_6989586621679473577 wild_6989586621679473579)) (Let6989586621679484428XsSym3 cmp wild_6989586621679473577 wild_6989586621679473579) |
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 #
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 # | |
Defined in Data.Singletons.Prelude.Instances suppressUnusedWarnings :: () Source # | |
type Apply ((:@#@$) :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type) -> *) (l :: a3530822107858468865) Source # | |
data (l :: a3530822107858468865) :@#@$$ (l :: TyFun [a3530822107858468865] [a3530822107858468865]) Source #
Instances
SuppressUnusedWarnings ((:@#@$$) :: a3530822107858468865 -> TyFun [a3530822107858468865] [a3530822107858468865] -> *) Source # | |
Defined in Data.Singletons.Prelude.Instances suppressUnusedWarnings :: () Source # | |
type Apply ((:@#@$$) l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Instances |
type (++@#@$$$) (t :: [a6989586621679448469]) (t :: [a6989586621679448469]) = (++) t t Source #
data (l :: [a6989586621679448469]) ++@#@$$ (l :: TyFun [a6989586621679448469] [a6989586621679448469]) Source #
data (++@#@$) (l :: TyFun [a6989586621679448469] (TyFun [a6989586621679448469] [a6989586621679448469] -> Type)) Source #
Instances
SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679448469] (TyFun [a6989586621679448469] [a6989586621679448469] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$) :: TyFun [a6989586621679448469] (TyFun [a6989586621679448469] [a6989586621679448469] -> Type) -> *) (l :: [a6989586621679448469]) Source # | |
data HeadSym0 (l :: TyFun [a6989586621679473042] a6989586621679473042) Source #
data LastSym0 (l :: TyFun [a6989586621679473041] a6989586621679473041) Source #
data TailSym0 (l :: TyFun [a6989586621679473040] [a6989586621679473040]) Source #
data InitSym0 (l :: TyFun [a6989586621679473039] [a6989586621679473039]) Source #
data NullSym0 (l :: TyFun [a6989586621679473038] Bool) Source #
data LengthSym0 (l :: TyFun [a6989586621679472924] Nat) Source #
Instances
SuppressUnusedWarnings (LengthSym0 :: TyFun [a6989586621679472924] Nat -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (LengthSym0 :: TyFun [a] Nat -> *) (l :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type LengthSym1 (t :: [a6989586621679472924]) = Length t Source #
data MapSym0 (l :: TyFun (TyFun a6989586621679448470 b6989586621679448471 -> Type) (TyFun [a6989586621679448470] [b6989586621679448471] -> Type)) Source #
Instances
SuppressUnusedWarnings (MapSym0 :: TyFun (TyFun a6989586621679448470 b6989586621679448471 -> Type) (TyFun [a6989586621679448470] [b6989586621679448471] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply (MapSym0 :: TyFun (TyFun a6989586621679448470 b6989586621679448471 -> Type) (TyFun [a6989586621679448470] [b6989586621679448471] -> Type) -> *) (l :: TyFun a6989586621679448470 b6989586621679448471 -> Type) Source # | |
data MapSym1 (l :: TyFun a6989586621679448470 b6989586621679448471 -> Type) (l :: TyFun [a6989586621679448470] [b6989586621679448471]) Source #
Instances
SuppressUnusedWarnings (MapSym1 :: (TyFun a6989586621679448470 b6989586621679448471 -> Type) -> TyFun [a6989586621679448470] [b6989586621679448471] -> *) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply (MapSym1 l1 :: TyFun [a] [b] -> *) (l2 :: [a]) Source # | |
type MapSym2 (t :: TyFun a6989586621679448470 b6989586621679448471 -> Type) (t :: [a6989586621679448470]) = Map t t Source #
data ReverseSym0 (l :: TyFun [a6989586621679473037] [a6989586621679473037]) Source #
Instances
SuppressUnusedWarnings (ReverseSym0 :: TyFun [a6989586621679473037] [a6989586621679473037] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ReverseSym0 :: TyFun [a] [a] -> *) (l :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type ReverseSym1 (t :: [a6989586621679473037]) = Reverse t Source #
data IntersperseSym0 (l :: TyFun a6989586621679473036 (TyFun [a6989586621679473036] [a6989586621679473036] -> Type)) Source #
Instances
SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679473036 (TyFun [a6989586621679473036] [a6989586621679473036] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym0 :: TyFun a6989586621679473036 (TyFun [a6989586621679473036] [a6989586621679473036] -> Type) -> *) (l :: a6989586621679473036) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (IntersperseSym0 :: TyFun a6989586621679473036 (TyFun [a6989586621679473036] [a6989586621679473036] -> Type) -> *) (l :: a6989586621679473036) = IntersperseSym1 l |
data IntersperseSym1 (l :: a6989586621679473036) (l :: TyFun [a6989586621679473036] [a6989586621679473036]) Source #
Instances
SuppressUnusedWarnings (IntersperseSym1 :: a6989586621679473036 -> TyFun [a6989586621679473036] [a6989586621679473036] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type IntersperseSym2 (t :: a6989586621679473036) (t :: [a6989586621679473036]) = Intersperse t t Source #
data IntercalateSym0 (l :: TyFun [a6989586621679473035] (TyFun [[a6989586621679473035]] [a6989586621679473035] -> Type)) Source #
Instances
SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a6989586621679473035] (TyFun [[a6989586621679473035]] [a6989586621679473035] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym0 :: TyFun [a6989586621679473035] (TyFun [[a6989586621679473035]] [a6989586621679473035] -> Type) -> *) (l :: [a6989586621679473035]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (IntercalateSym0 :: TyFun [a6989586621679473035] (TyFun [[a6989586621679473035]] [a6989586621679473035] -> Type) -> *) (l :: [a6989586621679473035]) = IntercalateSym1 l |
data IntercalateSym1 (l :: [a6989586621679473035]) (l :: TyFun [[a6989586621679473035]] [a6989586621679473035]) Source #
Instances
SuppressUnusedWarnings (IntercalateSym1 :: [a6989586621679473035] -> TyFun [[a6989586621679473035]] [a6989586621679473035] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym1 l1 :: TyFun [[a]] [a] -> *) (l2 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List |
type IntercalateSym2 (t :: [a6989586621679473035]) (t :: [[a6989586621679473035]]) = Intercalate t t Source #
data TransposeSym0 (l :: TyFun [[a6989586621679472922]] [[a6989586621679472922]]) Source #
Instances
SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a6989586621679472922]] [[a6989586621679472922]] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> *) (l :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List |
type TransposeSym1 (t :: [[a6989586621679472922]]) = Transpose t Source #
data SubsequencesSym0 (l :: TyFun [a6989586621679473034] [[a6989586621679473034]]) Source #
Instances
SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a6989586621679473034] [[a6989586621679473034]] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> *) (l :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type SubsequencesSym1 (t :: [a6989586621679473034]) = Subsequences t Source #
data PermutationsSym0 (l :: TyFun [a6989586621679473031] [[a6989586621679473031]]) Source #
Instances
SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a6989586621679473031] [[a6989586621679473031]] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> *) (l :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type PermutationsSym1 (t :: [a6989586621679473031]) = Permutations t Source #
data FoldlSym0 (l :: TyFun (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (FoldlSym0 :: TyFun (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.Instances suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym0 :: TyFun (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> Type) -> *) (l :: TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (FoldlSym0 :: TyFun (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> Type) -> *) (l :: TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) = FoldlSym1 l |
data FoldlSym1 (l :: TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (l :: TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type)) Source #
Instances
SuppressUnusedWarnings (FoldlSym1 :: (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) -> TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.Instances suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym1 l1 :: TyFun b6989586621679273480 (TyFun [a6989586621679273479] b6989586621679273480 -> Type) -> *) (l2 :: b6989586621679273480) Source # | |
data FoldlSym2 (l :: TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (l :: b6989586621679273480) (l :: TyFun [a6989586621679273479] b6989586621679273480) Source #
Instances
SuppressUnusedWarnings (FoldlSym2 :: (TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) -> b6989586621679273480 -> TyFun [a6989586621679273479] b6989586621679273480 -> *) Source # | |
Defined in Data.Singletons.Prelude.Instances suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) Source # | |
type FoldlSym3 (t :: TyFun b6989586621679273480 (TyFun a6989586621679273479 b6989586621679273480 -> Type) -> Type) (t :: b6989586621679273480) (t :: [a6989586621679273479]) = Foldl t t t Source #
data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) (TyFun b6989586621679473030 (TyFun [a6989586621679473029] b6989586621679473030 -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) (TyFun b6989586621679473030 (TyFun [a6989586621679473029] b6989586621679473030 -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym0 :: TyFun (TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) (TyFun b6989586621679473030 (TyFun [a6989586621679473029] b6989586621679473030 -> Type) -> Type) -> *) (l :: TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (Foldl'Sym0 :: TyFun (TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) (TyFun b6989586621679473030 (TyFun [a6989586621679473029] b6989586621679473030 -> Type) -> Type) -> *) (l :: TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) = Foldl'Sym1 l |
data Foldl'Sym1 (l :: TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) (l :: TyFun b6989586621679473030 (TyFun [a6989586621679473029] b6989586621679473030 -> Type)) Source #
Instances
SuppressUnusedWarnings (Foldl'Sym1 :: (TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) -> TyFun b6989586621679473030 (TyFun [a6989586621679473029] b6989586621679473030 -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym1 l1 :: TyFun b6989586621679473030 (TyFun [a6989586621679473029] b6989586621679473030 -> Type) -> *) (l2 :: b6989586621679473030) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (Foldl'Sym1 l1 :: TyFun b6989586621679473030 (TyFun [a6989586621679473029] b6989586621679473030 -> Type) -> *) (l2 :: b6989586621679473030) = Foldl'Sym2 l1 l2 |
data Foldl'Sym2 (l :: TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) (l :: b6989586621679473030) (l :: TyFun [a6989586621679473029] b6989586621679473030) Source #
Instances
SuppressUnusedWarnings (Foldl'Sym2 :: (TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) -> b6989586621679473030 -> TyFun [a6989586621679473029] b6989586621679473030 -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type Foldl'Sym3 (t :: TyFun b6989586621679473030 (TyFun a6989586621679473029 b6989586621679473030 -> Type) -> Type) (t :: b6989586621679473030) (t :: [a6989586621679473029]) = Foldl' t t t Source #
data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) (TyFun [a6989586621679473028] a6989586621679473028 -> Type)) Source #
Instances
SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) (TyFun [a6989586621679473028] a6989586621679473028 -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym0 :: TyFun (TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) (TyFun [a6989586621679473028] a6989586621679473028 -> Type) -> *) (l :: TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (Foldl1Sym0 :: TyFun (TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) (TyFun [a6989586621679473028] a6989586621679473028 -> Type) -> *) (l :: TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) = Foldl1Sym1 l |
data Foldl1Sym1 (l :: TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) (l :: TyFun [a6989586621679473028] a6989586621679473028) Source #
Instances
SuppressUnusedWarnings (Foldl1Sym1 :: (TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) -> TyFun [a6989586621679473028] a6989586621679473028 -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type Foldl1Sym2 (t :: TyFun a6989586621679473028 (TyFun a6989586621679473028 a6989586621679473028 -> Type) -> Type) (t :: [a6989586621679473028]) = Foldl1 t t Source #
data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) (TyFun [a6989586621679473027] a6989586621679473027 -> Type)) Source #
Instances
SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) (TyFun [a6989586621679473027] a6989586621679473027 -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym0 :: TyFun (TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) (TyFun [a6989586621679473027] a6989586621679473027 -> Type) -> *) (l :: TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (Foldl1'Sym0 :: TyFun (TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) (TyFun [a6989586621679473027] a6989586621679473027 -> Type) -> *) (l :: TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) = Foldl1'Sym1 l |
data Foldl1'Sym1 (l :: TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) (l :: TyFun [a6989586621679473027] a6989586621679473027) Source #
Instances
SuppressUnusedWarnings (Foldl1'Sym1 :: (TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) -> TyFun [a6989586621679473027] a6989586621679473027 -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type Foldl1'Sym2 (t :: TyFun a6989586621679473027 (TyFun a6989586621679473027 a6989586621679473027 -> Type) -> Type) (t :: [a6989586621679473027]) = Foldl1' t t Source #
data FoldrSym0 (l :: TyFun (TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) (TyFun b6989586621679448473 (TyFun [a6989586621679448472] b6989586621679448473 -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (FoldrSym0 :: TyFun (TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) (TyFun b6989586621679448473 (TyFun [a6989586621679448472] b6989586621679448473 -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym0 :: TyFun (TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) (TyFun b6989586621679448473 (TyFun [a6989586621679448472] b6989586621679448473 -> Type) -> Type) -> *) (l :: TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base type Apply (FoldrSym0 :: TyFun (TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) (TyFun b6989586621679448473 (TyFun [a6989586621679448472] b6989586621679448473 -> Type) -> Type) -> *) (l :: TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) = FoldrSym1 l |
data FoldrSym1 (l :: TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) (l :: TyFun b6989586621679448473 (TyFun [a6989586621679448472] b6989586621679448473 -> Type)) Source #
Instances
SuppressUnusedWarnings (FoldrSym1 :: (TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) -> TyFun b6989586621679448473 (TyFun [a6989586621679448472] b6989586621679448473 -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym1 l1 :: TyFun b6989586621679448473 (TyFun [a6989586621679448472] b6989586621679448473 -> Type) -> *) (l2 :: b6989586621679448473) Source # | |
data FoldrSym2 (l :: TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) (l :: b6989586621679448473) (l :: TyFun [a6989586621679448472] b6989586621679448473) Source #
Instances
SuppressUnusedWarnings (FoldrSym2 :: (TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) -> b6989586621679448473 -> TyFun [a6989586621679448472] b6989586621679448473 -> *) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) Source # | |
type FoldrSym3 (t :: TyFun a6989586621679448472 (TyFun b6989586621679448473 b6989586621679448473 -> Type) -> Type) (t :: b6989586621679448473) (t :: [a6989586621679448472]) = Foldr t t t Source #
data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) (TyFun [a6989586621679473026] a6989586621679473026 -> Type)) Source #
Instances
SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) (TyFun [a6989586621679473026] a6989586621679473026 -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym0 :: TyFun (TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) (TyFun [a6989586621679473026] a6989586621679473026 -> Type) -> *) (l :: TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (Foldr1Sym0 :: TyFun (TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) (TyFun [a6989586621679473026] a6989586621679473026 -> Type) -> *) (l :: TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) = Foldr1Sym1 l |
data Foldr1Sym1 (l :: TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) (l :: TyFun [a6989586621679473026] a6989586621679473026) Source #
Instances
SuppressUnusedWarnings (Foldr1Sym1 :: (TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) -> TyFun [a6989586621679473026] a6989586621679473026 -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type Foldr1Sym2 (t :: TyFun a6989586621679473026 (TyFun a6989586621679473026 a6989586621679473026 -> Type) -> Type) (t :: [a6989586621679473026]) = Foldr1 t t Source #
data ConcatSym0 (l :: TyFun [[a6989586621679473025]] [a6989586621679473025]) Source #
Instances
SuppressUnusedWarnings (ConcatSym0 :: TyFun [[a6989586621679473025]] [a6989586621679473025] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ConcatSym0 :: TyFun [[a]] [a] -> *) (l :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List |
type ConcatSym1 (t :: [[a6989586621679473025]]) = Concat t Source #
data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679473023 [b6989586621679473024] -> Type) (TyFun [a6989586621679473023] [b6989586621679473024] -> Type)) Source #
Instances
SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (TyFun a6989586621679473023 [b6989586621679473024] -> Type) (TyFun [a6989586621679473023] [b6989586621679473024] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym0 :: TyFun (TyFun a6989586621679473023 [b6989586621679473024] -> Type) (TyFun [a6989586621679473023] [b6989586621679473024] -> Type) -> *) (l :: TyFun a6989586621679473023 [b6989586621679473024] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data ConcatMapSym1 (l :: TyFun a6989586621679473023 [b6989586621679473024] -> Type) (l :: TyFun [a6989586621679473023] [b6989586621679473024]) Source #
Instances
SuppressUnusedWarnings (ConcatMapSym1 :: (TyFun a6989586621679473023 [b6989586621679473024] -> Type) -> TyFun [a6989586621679473023] [b6989586621679473024] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym1 l1 :: TyFun [a] [b] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type ConcatMapSym2 (t :: TyFun a6989586621679473023 [b6989586621679473024] -> Type) (t :: [a6989586621679473023]) = ConcatMap t t Source #
data AndSym0 (l :: TyFun [Bool] Bool) Source #
Instances
SuppressUnusedWarnings AndSym0 Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply AndSym0 (l :: [Bool]) Source # | |
Defined in Data.Singletons.Prelude.List |
data OrSym0 (l :: TyFun [Bool] Bool) Source #
Instances
SuppressUnusedWarnings OrSym0 Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply OrSym0 (l :: [Bool]) Source # | |
Defined in Data.Singletons.Prelude.List |
data AnySym0 (l :: TyFun (TyFun a6989586621679473021 Bool -> Type) (TyFun [a6989586621679473021] Bool -> Type)) Source #
Instances
SuppressUnusedWarnings (AnySym0 :: TyFun (TyFun a6989586621679473021 Bool -> Type) (TyFun [a6989586621679473021] Bool -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (AnySym0 :: TyFun (TyFun a6989586621679473021 Bool -> Type) (TyFun [a6989586621679473021] Bool -> Type) -> *) (l :: TyFun a6989586621679473021 Bool -> Type) Source # | |
data AnySym1 (l :: TyFun a6989586621679473021 Bool -> Type) (l :: TyFun [a6989586621679473021] Bool) Source #
type AnySym2 (t :: TyFun a6989586621679473021 Bool -> Type) (t :: [a6989586621679473021]) = Any t t Source #
data AllSym0 (l :: TyFun (TyFun a6989586621679473022 Bool -> Type) (TyFun [a6989586621679473022] Bool -> Type)) Source #
Instances
SuppressUnusedWarnings (AllSym0 :: TyFun (TyFun a6989586621679473022 Bool -> Type) (TyFun [a6989586621679473022] Bool -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (AllSym0 :: TyFun (TyFun a6989586621679473022 Bool -> Type) (TyFun [a6989586621679473022] Bool -> Type) -> *) (l :: TyFun a6989586621679473022 Bool -> Type) Source # | |
data AllSym1 (l :: TyFun a6989586621679473022 Bool -> Type) (l :: TyFun [a6989586621679473022] Bool) Source #
type AllSym2 (t :: TyFun a6989586621679473022 Bool -> Type) (t :: [a6989586621679473022]) = All t t Source #
data SumSym0 (l :: TyFun [a6989586621679472926] a6989586621679472926) Source #
data ProductSym0 (l :: TyFun [a6989586621679472925] a6989586621679472925) Source #
Instances
SuppressUnusedWarnings (ProductSym0 :: TyFun [a6989586621679472925] a6989586621679472925 -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ProductSym0 :: TyFun [a] a -> *) (l :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type ProductSym1 (t :: [a6989586621679472925]) = Product t Source #
data MaximumSym0 (l :: TyFun [a6989586621679472935] a6989586621679472935) Source #
Instances
SuppressUnusedWarnings (MaximumSym0 :: TyFun [a6989586621679472935] a6989586621679472935 -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (MaximumSym0 :: TyFun [a] a -> *) (l :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type MaximumSym1 (t :: [a6989586621679472935]) = Maximum t Source #
data MinimumSym0 (l :: TyFun [a6989586621679472934] a6989586621679472934) Source #
Instances
SuppressUnusedWarnings (MinimumSym0 :: TyFun [a6989586621679472934] a6989586621679472934 -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (MinimumSym0 :: TyFun [a] a -> *) (l :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type MinimumSym1 (t :: [a6989586621679472934]) = Minimum t Source #
data ScanlSym0 (l :: TyFun (TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) (TyFun b6989586621679473019 (TyFun [a6989586621679473020] [b6989586621679473019] -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (ScanlSym0 :: TyFun (TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) (TyFun b6989586621679473019 (TyFun [a6989586621679473020] [b6989586621679473019] -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym0 :: TyFun (TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) (TyFun b6989586621679473019 (TyFun [a6989586621679473020] [b6989586621679473019] -> Type) -> Type) -> *) (l :: TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (ScanlSym0 :: TyFun (TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) (TyFun b6989586621679473019 (TyFun [a6989586621679473020] [b6989586621679473019] -> Type) -> Type) -> *) (l :: TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) = ScanlSym1 l |
data ScanlSym1 (l :: TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) (l :: TyFun b6989586621679473019 (TyFun [a6989586621679473020] [b6989586621679473019] -> Type)) Source #
Instances
SuppressUnusedWarnings (ScanlSym1 :: (TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) -> TyFun b6989586621679473019 (TyFun [a6989586621679473020] [b6989586621679473019] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym1 l1 :: TyFun b6989586621679473019 (TyFun [a6989586621679473020] [b6989586621679473019] -> Type) -> *) (l2 :: b6989586621679473019) Source # | |
data ScanlSym2 (l :: TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) (l :: b6989586621679473019) (l :: TyFun [a6989586621679473020] [b6989586621679473019]) Source #
Instances
SuppressUnusedWarnings (ScanlSym2 :: (TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) -> b6989586621679473019 -> TyFun [a6989586621679473020] [b6989586621679473019] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym2 l1 l2 :: TyFun [a] [b] -> *) (l3 :: [a]) Source # | |
type ScanlSym3 (t :: TyFun b6989586621679473019 (TyFun a6989586621679473020 b6989586621679473019 -> Type) -> Type) (t :: b6989586621679473019) (t :: [a6989586621679473020]) = Scanl t t t Source #
data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) (TyFun [a6989586621679473018] [a6989586621679473018] -> Type)) Source #
Instances
SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) (TyFun [a6989586621679473018] [a6989586621679473018] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym0 :: TyFun (TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) (TyFun [a6989586621679473018] [a6989586621679473018] -> Type) -> *) (l :: TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (Scanl1Sym0 :: TyFun (TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) (TyFun [a6989586621679473018] [a6989586621679473018] -> Type) -> *) (l :: TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) = Scanl1Sym1 l |
data Scanl1Sym1 (l :: TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) (l :: TyFun [a6989586621679473018] [a6989586621679473018]) Source #
Instances
SuppressUnusedWarnings (Scanl1Sym1 :: (TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) -> TyFun [a6989586621679473018] [a6989586621679473018] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type Scanl1Sym2 (t :: TyFun a6989586621679473018 (TyFun a6989586621679473018 a6989586621679473018 -> Type) -> Type) (t :: [a6989586621679473018]) = Scanl1 t t Source #
data ScanrSym0 (l :: TyFun (TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) (TyFun b6989586621679473017 (TyFun [a6989586621679473016] [b6989586621679473017] -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (ScanrSym0 :: TyFun (TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) (TyFun b6989586621679473017 (TyFun [a6989586621679473016] [b6989586621679473017] -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym0 :: TyFun (TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) (TyFun b6989586621679473017 (TyFun [a6989586621679473016] [b6989586621679473017] -> Type) -> Type) -> *) (l :: TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (ScanrSym0 :: TyFun (TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) (TyFun b6989586621679473017 (TyFun [a6989586621679473016] [b6989586621679473017] -> Type) -> Type) -> *) (l :: TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) = ScanrSym1 l |
data ScanrSym1 (l :: TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) (l :: TyFun b6989586621679473017 (TyFun [a6989586621679473016] [b6989586621679473017] -> Type)) Source #
Instances
SuppressUnusedWarnings (ScanrSym1 :: (TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) -> TyFun b6989586621679473017 (TyFun [a6989586621679473016] [b6989586621679473017] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym1 l1 :: TyFun b6989586621679473017 (TyFun [a6989586621679473016] [b6989586621679473017] -> Type) -> *) (l2 :: b6989586621679473017) Source # | |
data ScanrSym2 (l :: TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) (l :: b6989586621679473017) (l :: TyFun [a6989586621679473016] [b6989586621679473017]) Source #
Instances
SuppressUnusedWarnings (ScanrSym2 :: (TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) -> b6989586621679473017 -> TyFun [a6989586621679473016] [b6989586621679473017] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym2 l1 l2 :: TyFun [a] [b] -> *) (l3 :: [a]) Source # | |
type ScanrSym3 (t :: TyFun a6989586621679473016 (TyFun b6989586621679473017 b6989586621679473017 -> Type) -> Type) (t :: b6989586621679473017) (t :: [a6989586621679473016]) = Scanr t t t Source #
data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) (TyFun [a6989586621679473015] [a6989586621679473015] -> Type)) Source #
Instances
SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) (TyFun [a6989586621679473015] [a6989586621679473015] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym0 :: TyFun (TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) (TyFun [a6989586621679473015] [a6989586621679473015] -> Type) -> *) (l :: TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (Scanr1Sym0 :: TyFun (TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) (TyFun [a6989586621679473015] [a6989586621679473015] -> Type) -> *) (l :: TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) = Scanr1Sym1 l |
data Scanr1Sym1 (l :: TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) (l :: TyFun [a6989586621679473015] [a6989586621679473015]) Source #
Instances
SuppressUnusedWarnings (Scanr1Sym1 :: (TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) -> TyFun [a6989586621679473015] [a6989586621679473015] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type Scanr1Sym2 (t :: TyFun a6989586621679473015 (TyFun a6989586621679473015 a6989586621679473015 -> Type) -> Type) (t :: [a6989586621679473015]) = Scanr1 t t Source #
data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) (TyFun acc6989586621679473012 (TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) (TyFun acc6989586621679473012 (TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym0 :: TyFun (TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) (TyFun acc6989586621679473012 (TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> Type) -> Type) -> *) (l :: TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (MapAccumLSym0 :: TyFun (TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) (TyFun acc6989586621679473012 (TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> Type) -> Type) -> *) (l :: TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) = MapAccumLSym1 l |
data MapAccumLSym1 (l :: TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) (l :: TyFun acc6989586621679473012 (TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> Type)) Source #
Instances
SuppressUnusedWarnings (MapAccumLSym1 :: (TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) -> TyFun acc6989586621679473012 (TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym1 l1 :: TyFun acc6989586621679473012 (TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> Type) -> *) (l2 :: acc6989586621679473012) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (MapAccumLSym1 l1 :: TyFun acc6989586621679473012 (TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> Type) -> *) (l2 :: acc6989586621679473012) = MapAccumLSym2 l1 l2 |
data MapAccumLSym2 (l :: TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) (l :: acc6989586621679473012) (l :: TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014])) Source #
Instances
SuppressUnusedWarnings (MapAccumLSym2 :: (TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) -> acc6989586621679473012 -> TyFun [x6989586621679473013] (acc6989586621679473012, [y6989586621679473014]) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym2 l1 l2 :: TyFun [x] (acc, [y]) -> *) (l3 :: [x]) Source # | |
Defined in Data.Singletons.Prelude.List |
type MapAccumLSym3 (t :: TyFun acc6989586621679473012 (TyFun x6989586621679473013 (acc6989586621679473012, y6989586621679473014) -> Type) -> Type) (t :: acc6989586621679473012) (t :: [x6989586621679473013]) = MapAccumL t t t Source #
data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) (TyFun acc6989586621679473009 (TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) (TyFun acc6989586621679473009 (TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym0 :: TyFun (TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) (TyFun acc6989586621679473009 (TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> Type) -> Type) -> *) (l :: TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (MapAccumRSym0 :: TyFun (TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) (TyFun acc6989586621679473009 (TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> Type) -> Type) -> *) (l :: TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) = MapAccumRSym1 l |
data MapAccumRSym1 (l :: TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) (l :: TyFun acc6989586621679473009 (TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> Type)) Source #
Instances
SuppressUnusedWarnings (MapAccumRSym1 :: (TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) -> TyFun acc6989586621679473009 (TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym1 l1 :: TyFun acc6989586621679473009 (TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> Type) -> *) (l2 :: acc6989586621679473009) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (MapAccumRSym1 l1 :: TyFun acc6989586621679473009 (TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> Type) -> *) (l2 :: acc6989586621679473009) = MapAccumRSym2 l1 l2 |
data MapAccumRSym2 (l :: TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) (l :: acc6989586621679473009) (l :: TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011])) Source #
Instances
SuppressUnusedWarnings (MapAccumRSym2 :: (TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) -> acc6989586621679473009 -> TyFun [x6989586621679473010] (acc6989586621679473009, [y6989586621679473011]) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym2 l1 l2 :: TyFun [x] (acc, [y]) -> *) (l3 :: [x]) Source # | |
Defined in Data.Singletons.Prelude.List |
type MapAccumRSym3 (t :: TyFun acc6989586621679473009 (TyFun x6989586621679473010 (acc6989586621679473009, y6989586621679473011) -> Type) -> Type) (t :: acc6989586621679473009) (t :: [x6989586621679473010]) = MapAccumR t t t Source #
data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679472923 [a6989586621679472923] -> Type)) Source #
Instances
SuppressUnusedWarnings (ReplicateSym0 :: TyFun Nat (TyFun a6989586621679472923 [a6989586621679472923] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym0 :: TyFun Nat (TyFun a6989586621679472923 [a6989586621679472923] -> Type) -> *) (l :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List |
data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679472923 [a6989586621679472923]) Source #
Instances
SuppressUnusedWarnings (ReplicateSym1 :: Nat -> TyFun a6989586621679472923 [a6989586621679472923] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym1 l1 :: TyFun a [a] -> *) (l2 :: a) Source # | |
Defined in Data.Singletons.Prelude.List |
type ReplicateSym2 (t :: Nat) (t :: a6989586621679472923) = Replicate t t Source #
data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679473007 (Maybe (a6989586621679473008, b6989586621679473007)) -> Type) (TyFun b6989586621679473007 [a6989586621679473008] -> Type)) Source #
Instances
SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (TyFun b6989586621679473007 (Maybe (a6989586621679473008, b6989586621679473007)) -> Type) (TyFun b6989586621679473007 [a6989586621679473008] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym0 :: TyFun (TyFun b6989586621679473007 (Maybe (a6989586621679473008, b6989586621679473007)) -> Type) (TyFun b6989586621679473007 [a6989586621679473008] -> Type) -> *) (l :: TyFun b6989586621679473007 (Maybe (a6989586621679473008, b6989586621679473007)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data UnfoldrSym1 (l :: TyFun b6989586621679473007 (Maybe (a6989586621679473008, b6989586621679473007)) -> Type) (l :: TyFun b6989586621679473007 [a6989586621679473008]) Source #
Instances
SuppressUnusedWarnings (UnfoldrSym1 :: (TyFun b6989586621679473007 (Maybe (a6989586621679473008, b6989586621679473007)) -> Type) -> TyFun b6989586621679473007 [a6989586621679473008] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym1 l1 :: TyFun b [a] -> *) (l2 :: b) Source # | |
Defined in Data.Singletons.Prelude.List |
type UnfoldrSym2 (t :: TyFun b6989586621679473007 (Maybe (a6989586621679473008, b6989586621679473007)) -> Type) (t :: b6989586621679473007) = Unfoldr t t Source #
data TakeSym0 (l :: TyFun Nat (TyFun [a6989586621679472939] [a6989586621679472939] -> Type)) Source #
Instances
SuppressUnusedWarnings (TakeSym0 :: TyFun Nat (TyFun [a6989586621679472939] [a6989586621679472939] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym0 :: TyFun Nat (TyFun [a6989586621679472939] [a6989586621679472939] -> Type) -> *) (l :: Nat) Source # | |
data TakeSym1 (l :: Nat) (l :: TyFun [a6989586621679472939] [a6989586621679472939]) Source #
data DropSym0 (l :: TyFun Nat (TyFun [a6989586621679472938] [a6989586621679472938] -> Type)) Source #
Instances
SuppressUnusedWarnings (DropSym0 :: TyFun Nat (TyFun [a6989586621679472938] [a6989586621679472938] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DropSym0 :: TyFun Nat (TyFun [a6989586621679472938] [a6989586621679472938] -> Type) -> *) (l :: Nat) Source # | |
data DropSym1 (l :: Nat) (l :: TyFun [a6989586621679472938] [a6989586621679472938]) Source #
data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679472937] ([a6989586621679472937], [a6989586621679472937]) -> Type)) Source #
Instances
SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat (TyFun [a6989586621679472937] ([a6989586621679472937], [a6989586621679472937]) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym0 :: TyFun Nat (TyFun [a6989586621679472937] ([a6989586621679472937], [a6989586621679472937]) -> Type) -> *) (l :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List |
data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679472937] ([a6989586621679472937], [a6989586621679472937])) Source #
Instances
SuppressUnusedWarnings (SplitAtSym1 :: Nat -> TyFun [a6989586621679472937] ([a6989586621679472937], [a6989586621679472937]) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type SplitAtSym2 (t :: Nat) (t :: [a6989586621679472937]) = SplitAt t t Source #
data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679472944 Bool -> Type) (TyFun [a6989586621679472944] [a6989586621679472944] -> Type)) Source #
Instances
SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (TyFun a6989586621679472944 Bool -> Type) (TyFun [a6989586621679472944] [a6989586621679472944] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym0 :: TyFun (TyFun a6989586621679472944 Bool -> Type) (TyFun [a6989586621679472944] [a6989586621679472944] -> Type) -> *) (l :: TyFun a6989586621679472944 Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data TakeWhileSym1 (l :: TyFun a6989586621679472944 Bool -> Type) (l :: TyFun [a6989586621679472944] [a6989586621679472944]) Source #
Instances
SuppressUnusedWarnings (TakeWhileSym1 :: (TyFun a6989586621679472944 Bool -> Type) -> TyFun [a6989586621679472944] [a6989586621679472944] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type TakeWhileSym2 (t :: TyFun a6989586621679472944 Bool -> Type) (t :: [a6989586621679472944]) = TakeWhile t t Source #
data DropWhileSym0 (l :: TyFun (TyFun a6989586621679472943 Bool -> Type) (TyFun [a6989586621679472943] [a6989586621679472943] -> Type)) Source #
Instances
SuppressUnusedWarnings (DropWhileSym0 :: TyFun (TyFun a6989586621679472943 Bool -> Type) (TyFun [a6989586621679472943] [a6989586621679472943] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym0 :: TyFun (TyFun a6989586621679472943 Bool -> Type) (TyFun [a6989586621679472943] [a6989586621679472943] -> Type) -> *) (l :: TyFun a6989586621679472943 Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data DropWhileSym1 (l :: TyFun a6989586621679472943 Bool -> Type) (l :: TyFun [a6989586621679472943] [a6989586621679472943]) Source #
Instances
SuppressUnusedWarnings (DropWhileSym1 :: (TyFun a6989586621679472943 Bool -> Type) -> TyFun [a6989586621679472943] [a6989586621679472943] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type DropWhileSym2 (t :: TyFun a6989586621679472943 Bool -> Type) (t :: [a6989586621679472943]) = DropWhile t t Source #
data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679472942 Bool -> Type) (TyFun [a6989586621679472942] [a6989586621679472942] -> Type)) Source #
Instances
SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (TyFun a6989586621679472942 Bool -> Type) (TyFun [a6989586621679472942] [a6989586621679472942] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym0 :: TyFun (TyFun a6989586621679472942 Bool -> Type) (TyFun [a6989586621679472942] [a6989586621679472942] -> Type) -> *) (l :: TyFun a6989586621679472942 Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data DropWhileEndSym1 (l :: TyFun a6989586621679472942 Bool -> Type) (l :: TyFun [a6989586621679472942] [a6989586621679472942]) Source #
Instances
SuppressUnusedWarnings (DropWhileEndSym1 :: (TyFun a6989586621679472942 Bool -> Type) -> TyFun [a6989586621679472942] [a6989586621679472942] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type DropWhileEndSym2 (t :: TyFun a6989586621679472942 Bool -> Type) (t :: [a6989586621679472942]) = DropWhileEnd t t Source #
data SpanSym0 (l :: TyFun (TyFun a6989586621679472941 Bool -> Type) (TyFun [a6989586621679472941] ([a6989586621679472941], [a6989586621679472941]) -> Type)) Source #
Instances
SuppressUnusedWarnings (SpanSym0 :: TyFun (TyFun a6989586621679472941 Bool -> Type) (TyFun [a6989586621679472941] ([a6989586621679472941], [a6989586621679472941]) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym0 :: TyFun (TyFun a6989586621679472941 Bool -> Type) (TyFun [a6989586621679472941] ([a6989586621679472941], [a6989586621679472941]) -> Type) -> *) (l :: TyFun a6989586621679472941 Bool -> Type) Source # | |
data SpanSym1 (l :: TyFun a6989586621679472941 Bool -> Type) (l :: TyFun [a6989586621679472941] ([a6989586621679472941], [a6989586621679472941])) Source #
Instances
SuppressUnusedWarnings (SpanSym1 :: (TyFun a6989586621679472941 Bool -> Type) -> TyFun [a6989586621679472941] ([a6989586621679472941], [a6989586621679472941]) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # | |
type SpanSym2 (t :: TyFun a6989586621679472941 Bool -> Type) (t :: [a6989586621679472941]) = Span t t Source #
data BreakSym0 (l :: TyFun (TyFun a6989586621679472940 Bool -> Type) (TyFun [a6989586621679472940] ([a6989586621679472940], [a6989586621679472940]) -> Type)) Source #
Instances
SuppressUnusedWarnings (BreakSym0 :: TyFun (TyFun a6989586621679472940 Bool -> Type) (TyFun [a6989586621679472940] ([a6989586621679472940], [a6989586621679472940]) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym0 :: TyFun (TyFun a6989586621679472940 Bool -> Type) (TyFun [a6989586621679472940] ([a6989586621679472940], [a6989586621679472940]) -> Type) -> *) (l :: TyFun a6989586621679472940 Bool -> Type) Source # | |
data BreakSym1 (l :: TyFun a6989586621679472940 Bool -> Type) (l :: TyFun [a6989586621679472940] ([a6989586621679472940], [a6989586621679472940])) Source #
Instances
SuppressUnusedWarnings (BreakSym1 :: (TyFun a6989586621679472940 Bool -> Type) -> TyFun [a6989586621679472940] ([a6989586621679472940], [a6989586621679472940]) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # | |
type BreakSym2 (t :: TyFun a6989586621679472940 Bool -> Type) (t :: [a6989586621679472940]) = Break t t Source #
data GroupSym0 (l :: TyFun [a6989586621679472936] [[a6989586621679472936]]) Source #
data InitsSym0 (l :: TyFun [a6989586621679473006] [[a6989586621679473006]]) Source #
data TailsSym0 (l :: TyFun [a6989586621679473005] [[a6989586621679473005]]) Source #
data IsPrefixOfSym0 (l :: TyFun [a6989586621679473004] (TyFun [a6989586621679473004] Bool -> Type)) Source #
Instances
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679473004] (TyFun [a6989586621679473004] Bool -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679473004] (TyFun [a6989586621679473004] Bool -> Type) -> *) (l :: [a6989586621679473004]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679473004] (TyFun [a6989586621679473004] Bool -> Type) -> *) (l :: [a6989586621679473004]) = IsPrefixOfSym1 l |
data IsPrefixOfSym1 (l :: [a6989586621679473004]) (l :: TyFun [a6989586621679473004] Bool) Source #
Instances
SuppressUnusedWarnings (IsPrefixOfSym1 :: [a6989586621679473004] -> TyFun [a6989586621679473004] Bool -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type IsPrefixOfSym2 (t :: [a6989586621679473004]) (t :: [a6989586621679473004]) = IsPrefixOf t t Source #
data IsSuffixOfSym0 (l :: TyFun [a6989586621679473003] (TyFun [a6989586621679473003] Bool -> Type)) Source #
Instances
SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679473003] (TyFun [a6989586621679473003] Bool -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679473003] (TyFun [a6989586621679473003] Bool -> Type) -> *) (l :: [a6989586621679473003]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679473003] (TyFun [a6989586621679473003] Bool -> Type) -> *) (l :: [a6989586621679473003]) = IsSuffixOfSym1 l |
data IsSuffixOfSym1 (l :: [a6989586621679473003]) (l :: TyFun [a6989586621679473003] Bool) Source #
Instances
SuppressUnusedWarnings (IsSuffixOfSym1 :: [a6989586621679473003] -> TyFun [a6989586621679473003] Bool -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type IsSuffixOfSym2 (t :: [a6989586621679473003]) (t :: [a6989586621679473003]) = IsSuffixOf t t Source #
data IsInfixOfSym0 (l :: TyFun [a6989586621679473002] (TyFun [a6989586621679473002] Bool -> Type)) Source #
Instances
SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a6989586621679473002] (TyFun [a6989586621679473002] Bool -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym0 :: TyFun [a6989586621679473002] (TyFun [a6989586621679473002] Bool -> Type) -> *) (l :: [a6989586621679473002]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (IsInfixOfSym0 :: TyFun [a6989586621679473002] (TyFun [a6989586621679473002] Bool -> Type) -> *) (l :: [a6989586621679473002]) = IsInfixOfSym1 l |
data IsInfixOfSym1 (l :: [a6989586621679473002]) (l :: TyFun [a6989586621679473002] Bool) Source #
Instances
SuppressUnusedWarnings (IsInfixOfSym1 :: [a6989586621679473002] -> TyFun [a6989586621679473002] Bool -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type IsInfixOfSym2 (t :: [a6989586621679473002]) (t :: [a6989586621679473002]) = IsInfixOf t t Source #
data ElemSym0 (l :: TyFun a6989586621679473001 (TyFun [a6989586621679473001] Bool -> Type)) Source #
Instances
SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621679473001 (TyFun [a6989586621679473001] Bool -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym0 :: TyFun a6989586621679473001 (TyFun [a6989586621679473001] Bool -> Type) -> *) (l :: a6989586621679473001) Source # | |
data ElemSym1 (l :: a6989586621679473001) (l :: TyFun [a6989586621679473001] Bool) Source #
data NotElemSym0 (l :: TyFun a6989586621679473000 (TyFun [a6989586621679473000] Bool -> Type)) Source #
Instances
SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621679473000 (TyFun [a6989586621679473000] Bool -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym0 :: TyFun a6989586621679473000 (TyFun [a6989586621679473000] Bool -> Type) -> *) (l :: a6989586621679473000) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (NotElemSym0 :: TyFun a6989586621679473000 (TyFun [a6989586621679473000] Bool -> Type) -> *) (l :: a6989586621679473000) = NotElemSym1 l |
data NotElemSym1 (l :: a6989586621679473000) (l :: TyFun [a6989586621679473000] Bool) Source #
Instances
SuppressUnusedWarnings (NotElemSym1 :: a6989586621679473000 -> TyFun [a6989586621679473000] Bool -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type NotElemSym2 (t :: a6989586621679473000) (t :: [a6989586621679473000]) = NotElem t t Source #
data LookupSym0 (l :: TyFun a6989586621679472929 (TyFun [(a6989586621679472929, b6989586621679472930)] (Maybe b6989586621679472930) -> Type)) Source #
Instances
SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679472929 (TyFun [(a6989586621679472929, b6989586621679472930)] (Maybe b6989586621679472930) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym0 :: TyFun a6989586621679472929 (TyFun [(a6989586621679472929, b6989586621679472930)] (Maybe b6989586621679472930) -> Type) -> *) (l :: a6989586621679472929) Source # | |
Defined in Data.Singletons.Prelude.List |
data LookupSym1 (l :: a6989586621679472929) (l :: TyFun [(a6989586621679472929, b6989586621679472930)] (Maybe b6989586621679472930)) Source #
Instances
SuppressUnusedWarnings (LookupSym1 :: a6989586621679472929 -> TyFun [(a6989586621679472929, b6989586621679472930)] (Maybe b6989586621679472930) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym1 l1 :: TyFun [(a, b)] (Maybe b) -> *) (l2 :: [(a, b)]) Source # | |
Defined in Data.Singletons.Prelude.List |
type LookupSym2 (t :: a6989586621679472929) (t :: [(a6989586621679472929, b6989586621679472930)]) = Lookup t t Source #
data FindSym0 (l :: TyFun (TyFun a6989586621679472951 Bool -> Type) (TyFun [a6989586621679472951] (Maybe a6989586621679472951) -> Type)) Source #
Instances
SuppressUnusedWarnings (FindSym0 :: TyFun (TyFun a6989586621679472951 Bool -> Type) (TyFun [a6989586621679472951] (Maybe a6989586621679472951) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (FindSym0 :: TyFun (TyFun a6989586621679472951 Bool -> Type) (TyFun [a6989586621679472951] (Maybe a6989586621679472951) -> Type) -> *) (l :: TyFun a6989586621679472951 Bool -> Type) Source # | |
data FindSym1 (l :: TyFun a6989586621679472951 Bool -> Type) (l :: TyFun [a6989586621679472951] (Maybe a6989586621679472951)) Source #
Instances
SuppressUnusedWarnings (FindSym1 :: (TyFun a6989586621679472951 Bool -> Type) -> TyFun [a6989586621679472951] (Maybe a6989586621679472951) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (FindSym1 l1 :: TyFun [a] (Maybe a) -> *) (l2 :: [a]) Source # | |
type FindSym2 (t :: TyFun a6989586621679472951 Bool -> Type) (t :: [a6989586621679472951]) = Find t t Source #
data FilterSym0 (l :: TyFun (TyFun a6989586621679472952 Bool -> Type) (TyFun [a6989586621679472952] [a6989586621679472952] -> Type)) Source #
Instances
SuppressUnusedWarnings (FilterSym0 :: TyFun (TyFun a6989586621679472952 Bool -> Type) (TyFun [a6989586621679472952] [a6989586621679472952] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym0 :: TyFun (TyFun a6989586621679472952 Bool -> Type) (TyFun [a6989586621679472952] [a6989586621679472952] -> Type) -> *) (l :: TyFun a6989586621679472952 Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data FilterSym1 (l :: TyFun a6989586621679472952 Bool -> Type) (l :: TyFun [a6989586621679472952] [a6989586621679472952]) Source #
Instances
SuppressUnusedWarnings (FilterSym1 :: (TyFun a6989586621679472952 Bool -> Type) -> TyFun [a6989586621679472952] [a6989586621679472952] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type FilterSym2 (t :: TyFun a6989586621679472952 Bool -> Type) (t :: [a6989586621679472952]) = Filter t t Source #
data PartitionSym0 (l :: TyFun (TyFun a6989586621679472928 Bool -> Type) (TyFun [a6989586621679472928] ([a6989586621679472928], [a6989586621679472928]) -> Type)) Source #
Instances
SuppressUnusedWarnings (PartitionSym0 :: TyFun (TyFun a6989586621679472928 Bool -> Type) (TyFun [a6989586621679472928] ([a6989586621679472928], [a6989586621679472928]) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym0 :: TyFun (TyFun a6989586621679472928 Bool -> Type) (TyFun [a6989586621679472928] ([a6989586621679472928], [a6989586621679472928]) -> Type) -> *) (l :: TyFun a6989586621679472928 Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data PartitionSym1 (l :: TyFun a6989586621679472928 Bool -> Type) (l :: TyFun [a6989586621679472928] ([a6989586621679472928], [a6989586621679472928])) Source #
Instances
SuppressUnusedWarnings (PartitionSym1 :: (TyFun a6989586621679472928 Bool -> Type) -> TyFun [a6989586621679472928] ([a6989586621679472928], [a6989586621679472928]) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type PartitionSym2 (t :: TyFun a6989586621679472928 Bool -> Type) (t :: [a6989586621679472928]) = Partition t t Source #
data (!!@#@$) (l :: TyFun [a6989586621679472921] (TyFun Nat a6989586621679472921 -> Type)) Source #
Instances
SuppressUnusedWarnings ((!!@#@$) :: TyFun [a6989586621679472921] (TyFun Nat a6989586621679472921 -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$) :: TyFun [a6989586621679472921] (TyFun Nat a6989586621679472921 -> Type) -> *) (l :: [a6989586621679472921]) Source # | |
data (l :: [a6989586621679472921]) !!@#@$$ (l :: TyFun Nat a6989586621679472921) Source #
type (!!@#@$$$) (t :: [a6989586621679472921]) (t :: Nat) = (!!) t t Source #
data ElemIndexSym0 (l :: TyFun a6989586621679472950 (TyFun [a6989586621679472950] (Maybe Nat) -> Type)) Source #
Instances
SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679472950 (TyFun [a6989586621679472950] (Maybe Nat) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym0 :: TyFun a6989586621679472950 (TyFun [a6989586621679472950] (Maybe Nat) -> Type) -> *) (l :: a6989586621679472950) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (ElemIndexSym0 :: TyFun a6989586621679472950 (TyFun [a6989586621679472950] (Maybe Nat) -> Type) -> *) (l :: a6989586621679472950) = ElemIndexSym1 l |
data ElemIndexSym1 (l :: a6989586621679472950) (l :: TyFun [a6989586621679472950] (Maybe Nat)) Source #
Instances
SuppressUnusedWarnings (ElemIndexSym1 :: a6989586621679472950 -> TyFun [a6989586621679472950] (Maybe Nat) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym1 l1 :: TyFun [a] (Maybe Nat) -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type ElemIndexSym2 (t :: a6989586621679472950) (t :: [a6989586621679472950]) = ElemIndex t t Source #
data ElemIndicesSym0 (l :: TyFun a6989586621679472949 (TyFun [a6989586621679472949] [Nat] -> Type)) Source #
Instances
SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a6989586621679472949 (TyFun [a6989586621679472949] [Nat] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym0 :: TyFun a6989586621679472949 (TyFun [a6989586621679472949] [Nat] -> Type) -> *) (l :: a6989586621679472949) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (ElemIndicesSym0 :: TyFun a6989586621679472949 (TyFun [a6989586621679472949] [Nat] -> Type) -> *) (l :: a6989586621679472949) = ElemIndicesSym1 l |
data ElemIndicesSym1 (l :: a6989586621679472949) (l :: TyFun [a6989586621679472949] [Nat]) Source #
Instances
SuppressUnusedWarnings (ElemIndicesSym1 :: a6989586621679472949 -> TyFun [a6989586621679472949] [Nat] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym1 l1 :: TyFun [a] [Nat] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type ElemIndicesSym2 (t :: a6989586621679472949) (t :: [a6989586621679472949]) = ElemIndices t t Source #
data FindIndexSym0 (l :: TyFun (TyFun a6989586621679472948 Bool -> Type) (TyFun [a6989586621679472948] (Maybe Nat) -> Type)) Source #
Instances
SuppressUnusedWarnings (FindIndexSym0 :: TyFun (TyFun a6989586621679472948 Bool -> Type) (TyFun [a6989586621679472948] (Maybe Nat) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym0 :: TyFun (TyFun a6989586621679472948 Bool -> Type) (TyFun [a6989586621679472948] (Maybe Nat) -> Type) -> *) (l :: TyFun a6989586621679472948 Bool -> Type) Source # | |
data FindIndexSym1 (l :: TyFun a6989586621679472948 Bool -> Type) (l :: TyFun [a6989586621679472948] (Maybe Nat)) Source #
Instances
SuppressUnusedWarnings (FindIndexSym1 :: (TyFun a6989586621679472948 Bool -> Type) -> TyFun [a6989586621679472948] (Maybe Nat) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym1 l1 :: TyFun [a] (Maybe Nat) -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type FindIndexSym2 (t :: TyFun a6989586621679472948 Bool -> Type) (t :: [a6989586621679472948]) = FindIndex t t Source #
data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679472947 Bool -> Type) (TyFun [a6989586621679472947] [Nat] -> Type)) Source #
Instances
SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (TyFun a6989586621679472947 Bool -> Type) (TyFun [a6989586621679472947] [Nat] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym0 :: TyFun (TyFun a6989586621679472947 Bool -> Type) (TyFun [a6989586621679472947] [Nat] -> Type) -> *) (l :: TyFun a6989586621679472947 Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data FindIndicesSym1 (l :: TyFun a6989586621679472947 Bool -> Type) (l :: TyFun [a6989586621679472947] [Nat]) Source #
Instances
SuppressUnusedWarnings (FindIndicesSym1 :: (TyFun a6989586621679472947 Bool -> Type) -> TyFun [a6989586621679472947] [Nat] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym1 l1 :: TyFun [a] [Nat] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type FindIndicesSym2 (t :: TyFun a6989586621679472947 Bool -> Type) (t :: [a6989586621679472947]) = FindIndices t t Source #
data ZipSym0 (l :: TyFun [a6989586621679472998] (TyFun [b6989586621679472999] [(a6989586621679472998, b6989586621679472999)] -> Type)) Source #
Instances
SuppressUnusedWarnings (ZipSym0 :: TyFun [a6989586621679472998] (TyFun [b6989586621679472999] [(a6989586621679472998, b6989586621679472999)] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym0 :: TyFun [a6989586621679472998] (TyFun [b6989586621679472999] [(a6989586621679472998, b6989586621679472999)] -> Type) -> *) (l :: [a6989586621679472998]) Source # | |
Defined in Data.Singletons.Prelude.List |
data ZipSym1 (l :: [a6989586621679472998]) (l :: TyFun [b6989586621679472999] [(a6989586621679472998, b6989586621679472999)]) Source #
Instances
SuppressUnusedWarnings (ZipSym1 :: [a6989586621679472998] -> TyFun [b6989586621679472999] [(a6989586621679472998, b6989586621679472999)] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym1 l1 :: TyFun [b] [(a, b)] -> *) (l2 :: [b]) Source # | |
data Zip3Sym0 (l :: TyFun [a6989586621679472995] (TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a6989586621679472995] (TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym0 :: TyFun [a6989586621679472995] (TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type) -> Type) -> *) (l :: [a6989586621679472995]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (Zip3Sym0 :: TyFun [a6989586621679472995] (TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type) -> Type) -> *) (l :: [a6989586621679472995]) = (Zip3Sym1 l :: TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type) -> *) |
data Zip3Sym1 (l :: [a6989586621679472995]) (l :: TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type)) Source #
Instances
SuppressUnusedWarnings (Zip3Sym1 :: [a6989586621679472995] -> TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym1 l1 :: TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type) -> *) (l2 :: [b6989586621679472996]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (Zip3Sym1 l1 :: TyFun [b6989586621679472996] (TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> Type) -> *) (l2 :: [b6989586621679472996]) = (Zip3Sym2 l1 l2 :: TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> *) |
data Zip3Sym2 (l :: [a6989586621679472995]) (l :: [b6989586621679472996]) (l :: TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)]) Source #
Instances
SuppressUnusedWarnings (Zip3Sym2 :: [a6989586621679472995] -> [b6989586621679472996] -> TyFun [c6989586621679472997] [(a6989586621679472995, b6989586621679472996, c6989586621679472997)] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym2 l1 l2 :: TyFun [c] [(a, b, c)] -> *) (l3 :: [c]) Source # | |
type Zip3Sym3 (t :: [a6989586621679472995]) (t :: [b6989586621679472996]) (t :: [c6989586621679472997]) = Zip3 t t t Source #
data ZipWithSym0 (l :: TyFun (TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) (TyFun [a6989586621679472992] (TyFun [b6989586621679472993] [c6989586621679472994] -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (ZipWithSym0 :: TyFun (TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) (TyFun [a6989586621679472992] (TyFun [b6989586621679472993] [c6989586621679472994] -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym0 :: TyFun (TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) (TyFun [a6989586621679472992] (TyFun [b6989586621679472993] [c6989586621679472994] -> Type) -> Type) -> *) (l :: TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (ZipWithSym0 :: TyFun (TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) (TyFun [a6989586621679472992] (TyFun [b6989586621679472993] [c6989586621679472994] -> Type) -> Type) -> *) (l :: TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) = ZipWithSym1 l |
data ZipWithSym1 (l :: TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) (l :: TyFun [a6989586621679472992] (TyFun [b6989586621679472993] [c6989586621679472994] -> Type)) Source #
Instances
SuppressUnusedWarnings (ZipWithSym1 :: (TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) -> TyFun [a6989586621679472992] (TyFun [b6989586621679472993] [c6989586621679472994] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym1 l1 :: TyFun [a6989586621679472992] (TyFun [b6989586621679472993] [c6989586621679472994] -> Type) -> *) (l2 :: [a6989586621679472992]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (ZipWithSym1 l1 :: TyFun [a6989586621679472992] (TyFun [b6989586621679472993] [c6989586621679472994] -> Type) -> *) (l2 :: [a6989586621679472992]) = ZipWithSym2 l1 l2 |
data ZipWithSym2 (l :: TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) (l :: [a6989586621679472992]) (l :: TyFun [b6989586621679472993] [c6989586621679472994]) Source #
Instances
SuppressUnusedWarnings (ZipWithSym2 :: (TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) -> [a6989586621679472992] -> TyFun [b6989586621679472993] [c6989586621679472994] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym2 l1 l2 :: TyFun [b] [c] -> *) (l3 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List |
type ZipWithSym3 (t :: TyFun a6989586621679472992 (TyFun b6989586621679472993 c6989586621679472994 -> Type) -> Type) (t :: [a6989586621679472992]) (t :: [b6989586621679472993]) = ZipWith t t t Source #
data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (TyFun [a6989586621679472988] (TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (TyFun [a6989586621679472988] (TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym0 :: TyFun (TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (TyFun [a6989586621679472988] (TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (ZipWith3Sym0 :: TyFun (TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (TyFun [a6989586621679472988] (TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) = ZipWith3Sym1 l |
data ZipWith3Sym1 (l :: TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679472988] (TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (ZipWith3Sym1 :: (TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) -> TyFun [a6989586621679472988] (TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym1 l1 :: TyFun [a6989586621679472988] (TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> Type) -> *) (l2 :: [a6989586621679472988]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (ZipWith3Sym1 l1 :: TyFun [a6989586621679472988] (TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> Type) -> *) (l2 :: [a6989586621679472988]) = ZipWith3Sym2 l1 l2 |
data ZipWith3Sym2 (l :: TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (l :: [a6989586621679472988]) (l :: TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type)) Source #
Instances
SuppressUnusedWarnings (ZipWith3Sym2 :: (TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) -> [a6989586621679472988] -> TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym2 l1 l2 :: TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> *) (l3 :: [b6989586621679472989]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (ZipWith3Sym2 l1 l2 :: TyFun [b6989586621679472989] (TyFun [c6989586621679472990] [d6989586621679472991] -> Type) -> *) (l3 :: [b6989586621679472989]) = ZipWith3Sym3 l1 l2 l3 |
data ZipWith3Sym3 (l :: TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (l :: [a6989586621679472988]) (l :: [b6989586621679472989]) (l :: TyFun [c6989586621679472990] [d6989586621679472991]) Source #
Instances
SuppressUnusedWarnings (ZipWith3Sym3 :: (TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) -> [a6989586621679472988] -> [b6989586621679472989] -> TyFun [c6989586621679472990] [d6989586621679472991] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym3 l1 l2 l3 :: TyFun [c] [d] -> *) (l4 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List |
type ZipWith3Sym4 (t :: TyFun a6989586621679472988 (TyFun b6989586621679472989 (TyFun c6989586621679472990 d6989586621679472991 -> Type) -> Type) -> Type) (t :: [a6989586621679472988]) (t :: [b6989586621679472989]) (t :: [c6989586621679472990]) = ZipWith3 t t t t Source #
data UnzipSym0 (l :: TyFun [(a6989586621679472986, b6989586621679472987)] ([a6989586621679472986], [b6989586621679472987])) Source #
Instances
SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a6989586621679472986, b6989586621679472987)] ([a6989586621679472986], [b6989586621679472987]) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> *) (l :: [(a, b)]) Source # | |
data Unzip3Sym0 (l :: TyFun [(a6989586621679472983, b6989586621679472984, c6989586621679472985)] ([a6989586621679472983], [b6989586621679472984], [c6989586621679472985])) Source #
Instances
SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a6989586621679472983, b6989586621679472984, c6989586621679472985)] ([a6989586621679472983], [b6989586621679472984], [c6989586621679472985]) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> *) (l :: [(a, b, c)]) Source # | |
Defined in Data.Singletons.Prelude.List |
type Unzip3Sym1 (t :: [(a6989586621679472983, b6989586621679472984, c6989586621679472985)]) = Unzip3 t Source #
data Unzip4Sym0 (l :: TyFun [(a6989586621679472979, b6989586621679472980, c6989586621679472981, d6989586621679472982)] ([a6989586621679472979], [b6989586621679472980], [c6989586621679472981], [d6989586621679472982])) Source #
Instances
SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a6989586621679472979, b6989586621679472980, c6989586621679472981, d6989586621679472982)] ([a6989586621679472979], [b6989586621679472980], [c6989586621679472981], [d6989586621679472982]) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> *) (l :: [(a, b, c, d)]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> *) (l :: [(a, b, c, d)]) = Unzip4 l |
type Unzip4Sym1 (t :: [(a6989586621679472979, b6989586621679472980, c6989586621679472981, d6989586621679472982)]) = Unzip4 t Source #
data Unzip5Sym0 (l :: TyFun [(a6989586621679472974, b6989586621679472975, c6989586621679472976, d6989586621679472977, e6989586621679472978)] ([a6989586621679472974], [b6989586621679472975], [c6989586621679472976], [d6989586621679472977], [e6989586621679472978])) Source #
Instances
SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a6989586621679472974, b6989586621679472975, c6989586621679472976, d6989586621679472977, e6989586621679472978)] ([a6989586621679472974], [b6989586621679472975], [c6989586621679472976], [d6989586621679472977], [e6989586621679472978]) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> *) (l :: [(a, b, c, d, e)]) Source # | |
Defined in Data.Singletons.Prelude.List 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 :: [(a6989586621679472974, b6989586621679472975, c6989586621679472976, d6989586621679472977, e6989586621679472978)]) = Unzip5 t Source #
data Unzip6Sym0 (l :: TyFun [(a6989586621679472968, b6989586621679472969, c6989586621679472970, d6989586621679472971, e6989586621679472972, f6989586621679472973)] ([a6989586621679472968], [b6989586621679472969], [c6989586621679472970], [d6989586621679472971], [e6989586621679472972], [f6989586621679472973])) Source #
Instances
SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a6989586621679472968, b6989586621679472969, c6989586621679472970, d6989586621679472971, e6989586621679472972, f6989586621679472973)] ([a6989586621679472968], [b6989586621679472969], [c6989586621679472970], [d6989586621679472971], [e6989586621679472972], [f6989586621679472973]) -> *) Source # | |
Defined in Data.Singletons.Prelude.List 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 # | |
Defined in Data.Singletons.Prelude.List 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 :: [(a6989586621679472968, b6989586621679472969, c6989586621679472970, d6989586621679472971, e6989586621679472972, f6989586621679472973)]) = Unzip6 t Source #
data Unzip7Sym0 (l :: TyFun [(a6989586621679472961, b6989586621679472962, c6989586621679472963, d6989586621679472964, e6989586621679472965, f6989586621679472966, g6989586621679472967)] ([a6989586621679472961], [b6989586621679472962], [c6989586621679472963], [d6989586621679472964], [e6989586621679472965], [f6989586621679472966], [g6989586621679472967])) Source #
Instances
SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a6989586621679472961, b6989586621679472962, c6989586621679472963, d6989586621679472964, e6989586621679472965, f6989586621679472966, g6989586621679472967)] ([a6989586621679472961], [b6989586621679472962], [c6989586621679472963], [d6989586621679472964], [e6989586621679472965], [f6989586621679472966], [g6989586621679472967]) -> *) Source # | |
Defined in Data.Singletons.Prelude.List 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 # | |
Defined in Data.Singletons.Prelude.List 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 :: [(a6989586621679472961, b6989586621679472962, c6989586621679472963, d6989586621679472964, e6989586621679472965, f6989586621679472966, g6989586621679472967)]) = Unzip7 t Source #
data UnlinesSym0 (l :: TyFun [Symbol] Symbol) Source #
Instances
SuppressUnusedWarnings UnlinesSym0 Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply UnlinesSym0 (l :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List |
type UnlinesSym1 (t :: [Symbol]) = Unlines t Source #
data UnwordsSym0 (l :: TyFun [Symbol] Symbol) Source #
Instances
SuppressUnusedWarnings UnwordsSym0 Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply UnwordsSym0 (l :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List |
type UnwordsSym1 (t :: [Symbol]) = Unwords t Source #
data NubSym0 (l :: TyFun [a6989586621679472920] [a6989586621679472920]) Source #
data DeleteSym0 (l :: TyFun a6989586621679472960 (TyFun [a6989586621679472960] [a6989586621679472960] -> Type)) Source #
Instances
SuppressUnusedWarnings (DeleteSym0 :: TyFun a6989586621679472960 (TyFun [a6989586621679472960] [a6989586621679472960] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym0 :: TyFun a6989586621679472960 (TyFun [a6989586621679472960] [a6989586621679472960] -> Type) -> *) (l :: a6989586621679472960) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (DeleteSym0 :: TyFun a6989586621679472960 (TyFun [a6989586621679472960] [a6989586621679472960] -> Type) -> *) (l :: a6989586621679472960) = DeleteSym1 l |
data DeleteSym1 (l :: a6989586621679472960) (l :: TyFun [a6989586621679472960] [a6989586621679472960]) Source #
Instances
SuppressUnusedWarnings (DeleteSym1 :: a6989586621679472960 -> TyFun [a6989586621679472960] [a6989586621679472960] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type DeleteSym2 (t :: a6989586621679472960) (t :: [a6989586621679472960]) = Delete t t Source #
data (\\@#@$) (l :: TyFun [a6989586621679472959] (TyFun [a6989586621679472959] [a6989586621679472959] -> Type)) Source #
Instances
SuppressUnusedWarnings ((\\@#@$) :: TyFun [a6989586621679472959] (TyFun [a6989586621679472959] [a6989586621679472959] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$) :: TyFun [a6989586621679472959] (TyFun [a6989586621679472959] [a6989586621679472959] -> Type) -> *) (l :: [a6989586621679472959]) Source # | |
data (l :: [a6989586621679472959]) \\@#@$$ (l :: TyFun [a6989586621679472959] [a6989586621679472959]) Source #
type (\\@#@$$$) (t :: [a6989586621679472959]) (t :: [a6989586621679472959]) = (\\) t t Source #
data UnionSym0 (l :: TyFun [a6989586621679472916] (TyFun [a6989586621679472916] [a6989586621679472916] -> Type)) Source #
Instances
SuppressUnusedWarnings (UnionSym0 :: TyFun [a6989586621679472916] (TyFun [a6989586621679472916] [a6989586621679472916] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym0 :: TyFun [a6989586621679472916] (TyFun [a6989586621679472916] [a6989586621679472916] -> Type) -> *) (l :: [a6989586621679472916]) Source # | |
data UnionSym1 (l :: [a6989586621679472916]) (l :: TyFun [a6989586621679472916] [a6989586621679472916]) Source #
data IntersectSym0 (l :: TyFun [a6989586621679472946] (TyFun [a6989586621679472946] [a6989586621679472946] -> Type)) Source #
Instances
SuppressUnusedWarnings (IntersectSym0 :: TyFun [a6989586621679472946] (TyFun [a6989586621679472946] [a6989586621679472946] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym0 :: TyFun [a6989586621679472946] (TyFun [a6989586621679472946] [a6989586621679472946] -> Type) -> *) (l :: [a6989586621679472946]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (IntersectSym0 :: TyFun [a6989586621679472946] (TyFun [a6989586621679472946] [a6989586621679472946] -> Type) -> *) (l :: [a6989586621679472946]) = IntersectSym1 l |
data IntersectSym1 (l :: [a6989586621679472946]) (l :: TyFun [a6989586621679472946] [a6989586621679472946]) Source #
Instances
SuppressUnusedWarnings (IntersectSym1 :: [a6989586621679472946] -> TyFun [a6989586621679472946] [a6989586621679472946] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type IntersectSym2 (t :: [a6989586621679472946]) (t :: [a6989586621679472946]) = Intersect t t Source #
data InsertSym0 (l :: TyFun a6989586621679472933 (TyFun [a6989586621679472933] [a6989586621679472933] -> Type)) Source #
Instances
SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621679472933 (TyFun [a6989586621679472933] [a6989586621679472933] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym0 :: TyFun a6989586621679472933 (TyFun [a6989586621679472933] [a6989586621679472933] -> Type) -> *) (l :: a6989586621679472933) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (InsertSym0 :: TyFun a6989586621679472933 (TyFun [a6989586621679472933] [a6989586621679472933] -> Type) -> *) (l :: a6989586621679472933) = InsertSym1 l |
data InsertSym1 (l :: a6989586621679472933) (l :: TyFun [a6989586621679472933] [a6989586621679472933]) Source #
Instances
SuppressUnusedWarnings (InsertSym1 :: a6989586621679472933 -> TyFun [a6989586621679472933] [a6989586621679472933] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type InsertSym2 (t :: a6989586621679472933) (t :: [a6989586621679472933]) = Insert t t Source #
data SortSym0 (l :: TyFun [a6989586621679472932] [a6989586621679472932]) Source #
data NubBySym0 (l :: TyFun (TyFun a6989586621679472919 (TyFun a6989586621679472919 Bool -> Type) -> Type) (TyFun [a6989586621679472919] [a6989586621679472919] -> Type)) Source #
Instances
SuppressUnusedWarnings (NubBySym0 :: TyFun (TyFun a6989586621679472919 (TyFun a6989586621679472919 Bool -> Type) -> Type) (TyFun [a6989586621679472919] [a6989586621679472919] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym0 :: TyFun (TyFun a6989586621679472919 (TyFun a6989586621679472919 Bool -> Type) -> Type) (TyFun [a6989586621679472919] [a6989586621679472919] -> Type) -> *) (l :: TyFun a6989586621679472919 (TyFun a6989586621679472919 Bool -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data NubBySym1 (l :: TyFun a6989586621679472919 (TyFun a6989586621679472919 Bool -> Type) -> Type) (l :: TyFun [a6989586621679472919] [a6989586621679472919]) Source #
Instances
SuppressUnusedWarnings (NubBySym1 :: (TyFun a6989586621679472919 (TyFun a6989586621679472919 Bool -> Type) -> Type) -> TyFun [a6989586621679472919] [a6989586621679472919] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
type NubBySym2 (t :: TyFun a6989586621679472919 (TyFun a6989586621679472919 Bool -> Type) -> Type) (t :: [a6989586621679472919]) = NubBy t t Source #
data DeleteBySym0 (l :: TyFun (TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) (TyFun a6989586621679472958 (TyFun [a6989586621679472958] [a6989586621679472958] -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (DeleteBySym0 :: TyFun (TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) (TyFun a6989586621679472958 (TyFun [a6989586621679472958] [a6989586621679472958] -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym0 :: TyFun (TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) (TyFun a6989586621679472958 (TyFun [a6989586621679472958] [a6989586621679472958] -> Type) -> Type) -> *) (l :: TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (DeleteBySym0 :: TyFun (TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) (TyFun a6989586621679472958 (TyFun [a6989586621679472958] [a6989586621679472958] -> Type) -> Type) -> *) (l :: TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) = DeleteBySym1 l |
data DeleteBySym1 (l :: TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) (l :: TyFun a6989586621679472958 (TyFun [a6989586621679472958] [a6989586621679472958] -> Type)) Source #
Instances
SuppressUnusedWarnings (DeleteBySym1 :: (TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) -> TyFun a6989586621679472958 (TyFun [a6989586621679472958] [a6989586621679472958] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym1 l1 :: TyFun a6989586621679472958 (TyFun [a6989586621679472958] [a6989586621679472958] -> Type) -> *) (l2 :: a6989586621679472958) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (DeleteBySym1 l1 :: TyFun a6989586621679472958 (TyFun [a6989586621679472958] [a6989586621679472958] -> Type) -> *) (l2 :: a6989586621679472958) = DeleteBySym2 l1 l2 |
data DeleteBySym2 (l :: TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) (l :: a6989586621679472958) (l :: TyFun [a6989586621679472958] [a6989586621679472958]) Source #
Instances
SuppressUnusedWarnings (DeleteBySym2 :: (TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) -> a6989586621679472958 -> TyFun [a6989586621679472958] [a6989586621679472958] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type DeleteBySym3 (t :: TyFun a6989586621679472958 (TyFun a6989586621679472958 Bool -> Type) -> Type) (t :: a6989586621679472958) (t :: [a6989586621679472958]) = DeleteBy t t t Source #
data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) (TyFun [a6989586621679472957] (TyFun [a6989586621679472957] [a6989586621679472957] -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) (TyFun [a6989586621679472957] (TyFun [a6989586621679472957] [a6989586621679472957] -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) (TyFun [a6989586621679472957] (TyFun [a6989586621679472957] [a6989586621679472957] -> Type) -> Type) -> *) (l :: TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) (TyFun [a6989586621679472957] (TyFun [a6989586621679472957] [a6989586621679472957] -> Type) -> Type) -> *) (l :: TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) = DeleteFirstsBySym1 l |
data DeleteFirstsBySym1 (l :: TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) (l :: TyFun [a6989586621679472957] (TyFun [a6989586621679472957] [a6989586621679472957] -> Type)) Source #
Instances
SuppressUnusedWarnings (DeleteFirstsBySym1 :: (TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) -> TyFun [a6989586621679472957] (TyFun [a6989586621679472957] [a6989586621679472957] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym1 l1 :: TyFun [a6989586621679472957] (TyFun [a6989586621679472957] [a6989586621679472957] -> Type) -> *) (l2 :: [a6989586621679472957]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (DeleteFirstsBySym1 l1 :: TyFun [a6989586621679472957] (TyFun [a6989586621679472957] [a6989586621679472957] -> Type) -> *) (l2 :: [a6989586621679472957]) = DeleteFirstsBySym2 l1 l2 |
data DeleteFirstsBySym2 (l :: TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) (l :: [a6989586621679472957]) (l :: TyFun [a6989586621679472957] [a6989586621679472957]) Source #
Instances
SuppressUnusedWarnings (DeleteFirstsBySym2 :: (TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) -> [a6989586621679472957] -> TyFun [a6989586621679472957] [a6989586621679472957] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type DeleteFirstsBySym3 (t :: TyFun a6989586621679472957 (TyFun a6989586621679472957 Bool -> Type) -> Type) (t :: [a6989586621679472957]) (t :: [a6989586621679472957]) = DeleteFirstsBy t t t Source #
data UnionBySym0 (l :: TyFun (TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) (TyFun [a6989586621679472917] (TyFun [a6989586621679472917] [a6989586621679472917] -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (UnionBySym0 :: TyFun (TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) (TyFun [a6989586621679472917] (TyFun [a6989586621679472917] [a6989586621679472917] -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym0 :: TyFun (TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) (TyFun [a6989586621679472917] (TyFun [a6989586621679472917] [a6989586621679472917] -> Type) -> Type) -> *) (l :: TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (UnionBySym0 :: TyFun (TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) (TyFun [a6989586621679472917] (TyFun [a6989586621679472917] [a6989586621679472917] -> Type) -> Type) -> *) (l :: TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) = UnionBySym1 l |
data UnionBySym1 (l :: TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) (l :: TyFun [a6989586621679472917] (TyFun [a6989586621679472917] [a6989586621679472917] -> Type)) Source #
Instances
SuppressUnusedWarnings (UnionBySym1 :: (TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) -> TyFun [a6989586621679472917] (TyFun [a6989586621679472917] [a6989586621679472917] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym1 l1 :: TyFun [a6989586621679472917] (TyFun [a6989586621679472917] [a6989586621679472917] -> Type) -> *) (l2 :: [a6989586621679472917]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (UnionBySym1 l1 :: TyFun [a6989586621679472917] (TyFun [a6989586621679472917] [a6989586621679472917] -> Type) -> *) (l2 :: [a6989586621679472917]) = UnionBySym2 l1 l2 |
data UnionBySym2 (l :: TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) (l :: [a6989586621679472917]) (l :: TyFun [a6989586621679472917] [a6989586621679472917]) Source #
Instances
SuppressUnusedWarnings (UnionBySym2 :: (TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) -> [a6989586621679472917] -> TyFun [a6989586621679472917] [a6989586621679472917] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type UnionBySym3 (t :: TyFun a6989586621679472917 (TyFun a6989586621679472917 Bool -> Type) -> Type) (t :: [a6989586621679472917]) (t :: [a6989586621679472917]) = UnionBy t t t Source #
data IntersectBySym0 (l :: TyFun (TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) (TyFun [a6989586621679472945] (TyFun [a6989586621679472945] [a6989586621679472945] -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (IntersectBySym0 :: TyFun (TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) (TyFun [a6989586621679472945] (TyFun [a6989586621679472945] [a6989586621679472945] -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym0 :: TyFun (TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) (TyFun [a6989586621679472945] (TyFun [a6989586621679472945] [a6989586621679472945] -> Type) -> Type) -> *) (l :: TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (IntersectBySym0 :: TyFun (TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) (TyFun [a6989586621679472945] (TyFun [a6989586621679472945] [a6989586621679472945] -> Type) -> Type) -> *) (l :: TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) = IntersectBySym1 l |
data IntersectBySym1 (l :: TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) (l :: TyFun [a6989586621679472945] (TyFun [a6989586621679472945] [a6989586621679472945] -> Type)) Source #
Instances
SuppressUnusedWarnings (IntersectBySym1 :: (TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) -> TyFun [a6989586621679472945] (TyFun [a6989586621679472945] [a6989586621679472945] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym1 l1 :: TyFun [a6989586621679472945] (TyFun [a6989586621679472945] [a6989586621679472945] -> Type) -> *) (l2 :: [a6989586621679472945]) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (IntersectBySym1 l1 :: TyFun [a6989586621679472945] (TyFun [a6989586621679472945] [a6989586621679472945] -> Type) -> *) (l2 :: [a6989586621679472945]) = IntersectBySym2 l1 l2 |
data IntersectBySym2 (l :: TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) (l :: [a6989586621679472945]) (l :: TyFun [a6989586621679472945] [a6989586621679472945]) Source #
Instances
SuppressUnusedWarnings (IntersectBySym2 :: (TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) -> [a6989586621679472945] -> TyFun [a6989586621679472945] [a6989586621679472945] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type IntersectBySym3 (t :: TyFun a6989586621679472945 (TyFun a6989586621679472945 Bool -> Type) -> Type) (t :: [a6989586621679472945]) (t :: [a6989586621679472945]) = IntersectBy t t t Source #
data GroupBySym0 (l :: TyFun (TyFun a6989586621679472931 (TyFun a6989586621679472931 Bool -> Type) -> Type) (TyFun [a6989586621679472931] [[a6989586621679472931]] -> Type)) Source #
Instances
SuppressUnusedWarnings (GroupBySym0 :: TyFun (TyFun a6989586621679472931 (TyFun a6989586621679472931 Bool -> Type) -> Type) (TyFun [a6989586621679472931] [[a6989586621679472931]] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym0 :: TyFun (TyFun a6989586621679472931 (TyFun a6989586621679472931 Bool -> Type) -> Type) (TyFun [a6989586621679472931] [[a6989586621679472931]] -> Type) -> *) (l :: TyFun a6989586621679472931 (TyFun a6989586621679472931 Bool -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data GroupBySym1 (l :: TyFun a6989586621679472931 (TyFun a6989586621679472931 Bool -> Type) -> Type) (l :: TyFun [a6989586621679472931] [[a6989586621679472931]]) Source #
Instances
SuppressUnusedWarnings (GroupBySym1 :: (TyFun a6989586621679472931 (TyFun a6989586621679472931 Bool -> Type) -> Type) -> TyFun [a6989586621679472931] [[a6989586621679472931]] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym1 l1 :: TyFun [a] [[a]] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type GroupBySym2 (t :: TyFun a6989586621679472931 (TyFun a6989586621679472931 Bool -> Type) -> Type) (t :: [a6989586621679472931]) = GroupBy t t Source #
data SortBySym0 (l :: TyFun (TyFun a6989586621679472956 (TyFun a6989586621679472956 Ordering -> Type) -> Type) (TyFun [a6989586621679472956] [a6989586621679472956] -> Type)) Source #
Instances
SuppressUnusedWarnings (SortBySym0 :: TyFun (TyFun a6989586621679472956 (TyFun a6989586621679472956 Ordering -> Type) -> Type) (TyFun [a6989586621679472956] [a6989586621679472956] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym0 :: TyFun (TyFun a6989586621679472956 (TyFun a6989586621679472956 Ordering -> Type) -> Type) (TyFun [a6989586621679472956] [a6989586621679472956] -> Type) -> *) (l :: TyFun a6989586621679472956 (TyFun a6989586621679472956 Ordering -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data SortBySym1 (l :: TyFun a6989586621679472956 (TyFun a6989586621679472956 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679472956] [a6989586621679472956]) Source #
Instances
SuppressUnusedWarnings (SortBySym1 :: (TyFun a6989586621679472956 (TyFun a6989586621679472956 Ordering -> Type) -> Type) -> TyFun [a6989586621679472956] [a6989586621679472956] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type SortBySym2 (t :: TyFun a6989586621679472956 (TyFun a6989586621679472956 Ordering -> Type) -> Type) (t :: [a6989586621679472956]) = SortBy t t Source #
data InsertBySym0 (l :: TyFun (TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) (TyFun a6989586621679472955 (TyFun [a6989586621679472955] [a6989586621679472955] -> Type) -> Type)) Source #
Instances
SuppressUnusedWarnings (InsertBySym0 :: TyFun (TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) (TyFun a6989586621679472955 (TyFun [a6989586621679472955] [a6989586621679472955] -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym0 :: TyFun (TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) (TyFun a6989586621679472955 (TyFun [a6989586621679472955] [a6989586621679472955] -> Type) -> Type) -> *) (l :: TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (InsertBySym0 :: TyFun (TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) (TyFun a6989586621679472955 (TyFun [a6989586621679472955] [a6989586621679472955] -> Type) -> Type) -> *) (l :: TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) = InsertBySym1 l |
data InsertBySym1 (l :: TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) (l :: TyFun a6989586621679472955 (TyFun [a6989586621679472955] [a6989586621679472955] -> Type)) Source #
Instances
SuppressUnusedWarnings (InsertBySym1 :: (TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) -> TyFun a6989586621679472955 (TyFun [a6989586621679472955] [a6989586621679472955] -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym1 l1 :: TyFun a6989586621679472955 (TyFun [a6989586621679472955] [a6989586621679472955] -> Type) -> *) (l2 :: a6989586621679472955) Source # | |
Defined in Data.Singletons.Prelude.List type Apply (InsertBySym1 l1 :: TyFun a6989586621679472955 (TyFun [a6989586621679472955] [a6989586621679472955] -> Type) -> *) (l2 :: a6989586621679472955) = InsertBySym2 l1 l2 |
data InsertBySym2 (l :: TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) (l :: a6989586621679472955) (l :: TyFun [a6989586621679472955] [a6989586621679472955]) Source #
Instances
SuppressUnusedWarnings (InsertBySym2 :: (TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) -> a6989586621679472955 -> TyFun [a6989586621679472955] [a6989586621679472955] -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type InsertBySym3 (t :: TyFun a6989586621679472955 (TyFun a6989586621679472955 Ordering -> Type) -> Type) (t :: a6989586621679472955) (t :: [a6989586621679472955]) = InsertBy t t t Source #
data MaximumBySym0 (l :: TyFun (TyFun a6989586621679472954 (TyFun a6989586621679472954 Ordering -> Type) -> Type) (TyFun [a6989586621679472954] a6989586621679472954 -> Type)) Source #
Instances
SuppressUnusedWarnings (MaximumBySym0 :: TyFun (TyFun a6989586621679472954 (TyFun a6989586621679472954 Ordering -> Type) -> Type) (TyFun [a6989586621679472954] a6989586621679472954 -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym0 :: TyFun (TyFun a6989586621679472954 (TyFun a6989586621679472954 Ordering -> Type) -> Type) (TyFun [a6989586621679472954] a6989586621679472954 -> Type) -> *) (l :: TyFun a6989586621679472954 (TyFun a6989586621679472954 Ordering -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data MaximumBySym1 (l :: TyFun a6989586621679472954 (TyFun a6989586621679472954 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679472954] a6989586621679472954) Source #
Instances
SuppressUnusedWarnings (MaximumBySym1 :: (TyFun a6989586621679472954 (TyFun a6989586621679472954 Ordering -> Type) -> Type) -> TyFun [a6989586621679472954] a6989586621679472954 -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type MaximumBySym2 (t :: TyFun a6989586621679472954 (TyFun a6989586621679472954 Ordering -> Type) -> Type) (t :: [a6989586621679472954]) = MaximumBy t t Source #
data MinimumBySym0 (l :: TyFun (TyFun a6989586621679472953 (TyFun a6989586621679472953 Ordering -> Type) -> Type) (TyFun [a6989586621679472953] a6989586621679472953 -> Type)) Source #
Instances
SuppressUnusedWarnings (MinimumBySym0 :: TyFun (TyFun a6989586621679472953 (TyFun a6989586621679472953 Ordering -> Type) -> Type) (TyFun [a6989586621679472953] a6989586621679472953 -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym0 :: TyFun (TyFun a6989586621679472953 (TyFun a6989586621679472953 Ordering -> Type) -> Type) (TyFun [a6989586621679472953] a6989586621679472953 -> Type) -> *) (l :: TyFun a6989586621679472953 (TyFun a6989586621679472953 Ordering -> Type) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List |
data MinimumBySym1 (l :: TyFun a6989586621679472953 (TyFun a6989586621679472953 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679472953] a6989586621679472953) Source #
Instances
SuppressUnusedWarnings (MinimumBySym1 :: (TyFun a6989586621679472953 (TyFun a6989586621679472953 Ordering -> Type) -> Type) -> TyFun [a6989586621679472953] a6989586621679472953 -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type MinimumBySym2 (t :: TyFun a6989586621679472953 (TyFun a6989586621679472953 Ordering -> Type) -> Type) (t :: [a6989586621679472953]) = MinimumBy t t Source #
data GenericLengthSym0 (l :: TyFun [a6989586621679472915] i6989586621679472914) Source #
Instances
SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a6989586621679472915] i6989586621679472914 -> *) Source # | |
Defined in Data.Singletons.Prelude.List suppressUnusedWarnings :: () Source # | |
type Apply (GenericLengthSym0 :: TyFun [a] k2 -> *) (l :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List |
type GenericLengthSym1 (t :: [a6989586621679472915]) = GenericLength t Source #