| Copyright | (C) 2013-2014 Richard Eisenberg Jan Stolarek |
|---|---|
| License | BSD-style (see LICENSE) |
| Maintainer | Ryan Scott |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.List.Singletons
Description
Defines functions and datatypes relating to the singleton for '[]',
including singled versions 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
- type family Sing :: k -> Type
- data SList :: forall (a :: Type). [a] -> Type where
- type family (a :: [a]) ++ (a :: [a]) :: [a] where ...
- (%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a])
- type family Head (a :: [a]) :: a where ...
- sHead :: forall a (t :: [a]). Sing t -> Sing (Apply HeadSym0 t :: a)
- type family Last (a :: [a]) :: a where ...
- sLast :: forall a (t :: [a]). Sing t -> Sing (Apply LastSym0 t :: a)
- type family Tail (a :: [a]) :: [a] where ...
- sTail :: forall a (t :: [a]). Sing t -> Sing (Apply TailSym0 t :: [a])
- type family Init (a :: [a]) :: [a] where ...
- sInit :: forall a (t :: [a]). Sing t -> Sing (Apply InitSym0 t :: [a])
- type family Null (arg :: t a) :: Bool
- sNull :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply NullSym0 t :: Bool)
- type family Length (arg :: t a) :: Natural
- sLength :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply LengthSym0 t :: Natural)
- type family Map (a :: (~>) a b) (a :: [a]) :: [b] where ...
- sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b])
- type family Reverse (a :: [a]) :: [a] where ...
- sReverse :: forall a (t :: [a]). Sing t -> Sing (Apply ReverseSym0 t :: [a])
- type family Intersperse (a :: a) (a :: [a]) :: [a] where ...
- sIntersperse :: forall a (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 a (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a])
- type family Transpose (a :: [[a]]) :: [[a]] where ...
- sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]])
- type family Subsequences (a :: [a]) :: [[a]] where ...
- sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]])
- type family Permutations (a :: [a]) :: [[a]] where ...
- sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]])
- type family Foldl (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
- sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b)
- type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
- sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b)
- type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
- sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a)
- type family Foldl1' (a :: (~>) a ((~>) a a)) (a :: [a]) :: a where ...
- sFoldl1' :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a)
- type family Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b
- sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b)
- type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
- sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a)
- type family Concat (a :: t [a]) :: [a] where ...
- sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a])
- type family ConcatMap (a :: (~>) a [b]) (a :: t a) :: [b] where ...
- sConcatMap :: forall a b t (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b])
- type family And (a :: t Bool) :: Bool where ...
- sAnd :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool)
- type family Or (a :: t Bool) :: Bool where ...
- sOr :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool)
- type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ...
- sAny :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool)
- type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ...
- sAll :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool)
- type family Sum (arg :: t a) :: a
- sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a)
- type family Product (arg :: t a) :: a
- sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a)
- type family Maximum (arg :: t a) :: a
- sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a)
- type family Minimum (arg :: t a) :: a
- sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a)
- type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: [b] where ...
- sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b])
- type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
- sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a])
- type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: [b] where ...
- sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b])
- type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
- sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a])
- type family MapAccumL (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
- sMapAccumL :: forall t a b c (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (a, t c))
- type family MapAccumR (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
- sMapAccumR :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c))
- type family Replicate (a :: Natural) (a :: a) :: [a] where ...
- sReplicate :: forall a (t :: Natural) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a])
- type family Unfoldr (a :: (~>) b (Maybe (a, b))) (a :: b) :: [a] where ...
- sUnfoldr :: forall b a (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a])
- type family Take (a :: Natural) (a :: [a]) :: [a] where ...
- sTake :: forall a (t :: Natural) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a])
- type family Drop (a :: Natural) (a :: [a]) :: [a] where ...
- sDrop :: forall a (t :: Natural) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a])
- type family SplitAt (a :: Natural) (a :: [a]) :: ([a], [a]) where ...
- sSplitAt :: forall a (t :: Natural) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a]))
- type family TakeWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sTakeWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a])
- type family DropWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sDropWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a])
- type family DropWhileEnd (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sDropWhileEnd :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a])
- type family Span (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sSpan :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a]))
- type family Break (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sBreak :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a]))
- type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ...
- type family Group (a :: [a]) :: [[a]] where ...
- sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [[a]])
- type family Inits (a :: [a]) :: [[a]] where ...
- sInits :: forall a (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: [[a]])
- type family Tails (a :: [a]) :: [[a]] where ...
- sTails :: forall a (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: [[a]])
- type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsPrefixOf :: forall a (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 a (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 a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool)
- type family Elem (arg :: a) (arg :: t a) :: Bool
- sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool)
- type family NotElem (a :: a) (a :: t a) :: Bool where ...
- sNotElem :: forall a t (t :: a) (t :: t a). (SFoldable t, 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 a b (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b)
- type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ...
- sFind :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a)
- type family Filter (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
- type family Partition (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
- type family (a :: [a]) !! (a :: Natural) :: a where ...
- (%!!) :: forall a (t :: [a]) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a)
- type family ElemIndex (a :: a) (a :: [a]) :: Maybe Natural where ...
- sElemIndex :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Natural)
- type family ElemIndices (a :: a) (a :: [a]) :: [Natural] where ...
- sElemIndices :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Natural])
- type family FindIndex (a :: (~>) a Bool) (a :: [a]) :: Maybe Natural where ...
- sFindIndex :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Natural)
- type family FindIndices (a :: (~>) a Bool) (a :: [a]) :: [Natural] where ...
- sFindIndices :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Natural])
- type family Zip (a :: [a]) (a :: [b]) :: [(a, b)] where ...
- sZip :: forall a b (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 a b c (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 Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ...
- type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ...
- type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ...
- type family Zip7 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [(a, b, c, d, e, f, g)] where ...
- type family ZipWith (a :: (~>) a ((~>) b c)) (a :: [a]) (a :: [b]) :: [c] where ...
- sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c])
- type family ZipWith3 (a :: (~>) a ((~>) b ((~>) c d))) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ...
- sZipWith3 :: forall a b c d (t :: (~>) a ((~>) b ((~>) c d))) (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 ZipWith4 (a :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ...
- type family ZipWith5 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ...
- type family ZipWith6 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ...
- type family ZipWith7 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ...
- type family Unzip (a :: [(a, b)]) :: ([a], [b]) where ...
- sUnzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b]))
- type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ...
- sUnzip3 :: forall a b c (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 a b c d (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 a b c d e (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 a b c d e f (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 a b c d e f g (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 a (t :: [a]). SEq a => Sing t -> Sing (Apply NubSym0 t :: [a])
- type family Delete (a :: a) (a :: [a]) :: [a] where ...
- sDelete :: forall a (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 a (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 a (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 a (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 a (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 a (t :: [a]). SOrd a => Sing t -> Sing (Apply SortSym0 t :: [a])
- type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [a] where ...
- sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a])
- type family DeleteBy (a :: (~>) a ((~>) a Bool)) (a :: a) (a :: [a]) :: [a] where ...
- sDeleteBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a])
- type family DeleteFirstsBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sDeleteFirstsBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a])
- type family UnionBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sUnionBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a])
- type family IntersectBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersectBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a])
- type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [[a]] where ...
- sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]])
- type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: [a]) :: [a] where ...
- sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a])
- type family InsertBy (a :: (~>) a ((~>) a Ordering)) (a :: a) (a :: [a]) :: [a] where ...
- sInsertBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a])
- type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
- sMaximumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a)
- type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
- sMinimumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a)
- type family GenericLength (a :: [a]) :: i where ...
- sGenericLength :: forall a i (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i)
- type family NilSym0 :: [a :: Type] where ...
- data (:@#@$) :: (~>) a ((~>) [a] [a :: Type])
- data (:@#@$$) (a6989586621679042108 :: a) :: (~>) [a] [a :: Type]
- type family (a6989586621679042108 :: a) :@#@$$$ (a6989586621679042109 :: [a]) :: [a :: Type] where ...
- type family (a6989586621679287772 :: [a]) ++@#@$$$ (a6989586621679287773 :: [a]) :: [a] where ...
- data (++@#@$$) (a6989586621679287772 :: [a]) :: (~>) [a] [a]
- data (++@#@$) :: (~>) [a] ((~>) [a] [a])
- data HeadSym0 :: (~>) [a] a
- type family HeadSym1 (a6989586621679849189 :: [a]) :: a where ...
- data LastSym0 :: (~>) [a] a
- type family LastSym1 (a6989586621679849183 :: [a]) :: a where ...
- data TailSym0 :: (~>) [a] [a]
- type family TailSym1 (a6989586621679849179 :: [a]) :: [a] where ...
- data InitSym0 :: (~>) [a] [a]
- type family InitSym1 (a6989586621679849167 :: [a]) :: [a] where ...
- data NullSym0 :: (~>) (t a) Bool
- type family NullSym1 (a6989586621680427279 :: t a) :: Bool where ...
- data LengthSym0 :: (~>) (t a) Natural
- type family LengthSym1 (a6989586621680427282 :: t a) :: Natural where ...
- data MapSym0 :: (~>) ((~>) a b) ((~>) [a] [b])
- data MapSym1 (a6989586621679287781 :: (~>) a b) :: (~>) [a] [b]
- type family MapSym2 (a6989586621679287781 :: (~>) a b) (a6989586621679287782 :: [a]) :: [b] where ...
- data ReverseSym0 :: (~>) [a] [a]
- type family ReverseSym1 (a6989586621679849152 :: [a]) :: [a] where ...
- data IntersperseSym0 :: (~>) a ((~>) [a] [a])
- data IntersperseSym1 (a6989586621679849145 :: a) :: (~>) [a] [a]
- type family IntersperseSym2 (a6989586621679849145 :: a) (a6989586621679849146 :: [a]) :: [a] where ...
- data IntercalateSym0 :: (~>) [a] ((~>) [[a]] [a])
- data IntercalateSym1 (a6989586621679849138 :: [a]) :: (~>) [[a]] [a]
- type family IntercalateSym2 (a6989586621679849138 :: [a]) (a6989586621679849139 :: [[a]]) :: [a] where ...
- data TransposeSym0 :: (~>) [[a]] [[a]]
- type family TransposeSym1 (a6989586621679848039 :: [[a]]) :: [[a]] where ...
- data SubsequencesSym0 :: (~>) [a] [[a]]
- type family SubsequencesSym1 (a6989586621679849133 :: [a]) :: [[a]] where ...
- data PermutationsSym0 :: (~>) [a] [[a]]
- type family PermutationsSym1 (a6989586621679849059 :: [a]) :: [[a]] where ...
- data FoldlSym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) (t a) b))
- data FoldlSym1 (a6989586621680427254 :: (~>) b ((~>) a b)) :: (~>) b ((~>) (t a) b)
- data FoldlSym2 (a6989586621680427254 :: (~>) b ((~>) a b)) (a6989586621680427255 :: b) :: (~>) (t a) b
- type family FoldlSym3 (a6989586621680427254 :: (~>) b ((~>) a b)) (a6989586621680427255 :: b) (a6989586621680427256 :: t a) :: b where ...
- data Foldl'Sym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) (t a) b))
- data Foldl'Sym1 (a6989586621680427261 :: (~>) b ((~>) a b)) :: (~>) b ((~>) (t a) b)
- data Foldl'Sym2 (a6989586621680427261 :: (~>) b ((~>) a b)) (a6989586621680427262 :: b) :: (~>) (t a) b
- type family Foldl'Sym3 (a6989586621680427261 :: (~>) b ((~>) a b)) (a6989586621680427262 :: b) (a6989586621680427263 :: t a) :: b where ...
- data Foldl1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (t a) a)
- data Foldl1Sym1 (a6989586621680427272 :: (~>) a ((~>) a a)) :: (~>) (t a) a
- type family Foldl1Sym2 (a6989586621680427272 :: (~>) a ((~>) a a)) (a6989586621680427273 :: t a) :: a where ...
- data Foldl1'Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) [a] a)
- data Foldl1'Sym1 (a6989586621679849024 :: (~>) a ((~>) a a)) :: (~>) [a] a
- type family Foldl1'Sym2 (a6989586621679849024 :: (~>) a ((~>) a a)) (a6989586621679849025 :: [a]) :: a where ...
- data FoldrSym0 :: (~>) ((~>) a ((~>) b b)) ((~>) b ((~>) (t a) b))
- data FoldrSym1 (a6989586621680427240 :: (~>) a ((~>) b b)) :: (~>) b ((~>) (t a) b)
- data FoldrSym2 (a6989586621680427240 :: (~>) a ((~>) b b)) (a6989586621680427241 :: b) :: (~>) (t a) b
- type family FoldrSym3 (a6989586621680427240 :: (~>) a ((~>) b b)) (a6989586621680427241 :: b) (a6989586621680427242 :: t a) :: b where ...
- data Foldr1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (t a) a)
- data Foldr1Sym1 (a6989586621680427267 :: (~>) a ((~>) a a)) :: (~>) (t a) a
- type family Foldr1Sym2 (a6989586621680427267 :: (~>) a ((~>) a a)) (a6989586621680427268 :: t a) :: a where ...
- data ConcatSym0 :: (~>) (t [a]) [a]
- type family ConcatSym1 (a6989586621680427121 :: t [a]) :: [a] where ...
- data ConcatMapSym0 :: (~>) ((~>) a [b]) ((~>) (t a) [b])
- data ConcatMapSym1 (a6989586621680427110 :: (~>) a [b]) :: (~>) (t a) [b]
- type family ConcatMapSym2 (a6989586621680427110 :: (~>) a [b]) (a6989586621680427111 :: t a) :: [b] where ...
- data AndSym0 :: (~>) (t Bool) Bool
- type family AndSym1 (a6989586621680427105 :: t Bool) :: Bool where ...
- data OrSym0 :: (~>) (t Bool) Bool
- type family OrSym1 (a6989586621680427099 :: t Bool) :: Bool where ...
- data AnySym0 :: (~>) ((~>) a Bool) ((~>) (t a) Bool)
- data AnySym1 (a6989586621680427091 :: (~>) a Bool) :: (~>) (t a) Bool
- type family AnySym2 (a6989586621680427091 :: (~>) a Bool) (a6989586621680427092 :: t a) :: Bool where ...
- data AllSym0 :: (~>) ((~>) a Bool) ((~>) (t a) Bool)
- data AllSym1 (a6989586621680427082 :: (~>) a Bool) :: (~>) (t a) Bool
- type family AllSym2 (a6989586621680427082 :: (~>) a Bool) (a6989586621680427083 :: t a) :: Bool where ...
- data SumSym0 :: (~>) (t a) a
- type family SumSym1 (a6989586621680427296 :: t a) :: a where ...
- data ProductSym0 :: (~>) (t a) a
- type family ProductSym1 (a6989586621680427299 :: t a) :: a where ...
- data MaximumSym0 :: (~>) (t a) a
- type family MaximumSym1 (a6989586621680427290 :: t a) :: a where ...
- data MinimumSym0 :: (~>) (t a) a
- type family MinimumSym1 (a6989586621680427293 :: t a) :: a where ...
- data ScanlSym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) [a] [b]))
- data ScanlSym1 (a6989586621679848957 :: (~>) b ((~>) a b)) :: (~>) b ((~>) [a] [b])
- data ScanlSym2 (a6989586621679848957 :: (~>) b ((~>) a b)) (a6989586621679848958 :: b) :: (~>) [a] [b]
- type family ScanlSym3 (a6989586621679848957 :: (~>) b ((~>) a b)) (a6989586621679848958 :: b) (a6989586621679848959 :: [a]) :: [b] where ...
- data Scanl1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) [a] [a])
- data Scanl1Sym1 (a6989586621679848948 :: (~>) a ((~>) a a)) :: (~>) [a] [a]
- type family Scanl1Sym2 (a6989586621679848948 :: (~>) a ((~>) a a)) (a6989586621679848949 :: [a]) :: [a] where ...
- data ScanrSym0 :: (~>) ((~>) a ((~>) b b)) ((~>) b ((~>) [a] [b]))
- data ScanrSym1 (a6989586621679848930 :: (~>) a ((~>) b b)) :: (~>) b ((~>) [a] [b])
- data ScanrSym2 (a6989586621679848930 :: (~>) a ((~>) b b)) (a6989586621679848931 :: b) :: (~>) [a] [b]
- type family ScanrSym3 (a6989586621679848930 :: (~>) a ((~>) b b)) (a6989586621679848931 :: b) (a6989586621679848932 :: [a]) :: [b] where ...
- data Scanr1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) [a] [a])
- data Scanr1Sym1 (a6989586621679848910 :: (~>) a ((~>) a a)) :: (~>) [a] [a]
- type family Scanr1Sym2 (a6989586621679848910 :: (~>) a ((~>) a a)) (a6989586621679848911 :: [a]) :: [a] where ...
- data MapAccumLSym0 :: (~>) ((~>) a ((~>) b (a, c))) ((~>) a ((~>) (t b) (a, t c)))
- data MapAccumLSym1 (a6989586621680784594 :: (~>) a ((~>) b (a, c))) :: (~>) a ((~>) (t b) (a, t c))
- data MapAccumLSym2 (a6989586621680784594 :: (~>) a ((~>) b (a, c))) (a6989586621680784595 :: a) :: (~>) (t b) (a, t c)
- type family MapAccumLSym3 (a6989586621680784594 :: (~>) a ((~>) b (a, c))) (a6989586621680784595 :: a) (a6989586621680784596 :: t b) :: (a, t c) where ...
- data MapAccumRSym0 :: (~>) ((~>) a ((~>) b (a, c))) ((~>) a ((~>) (t b) (a, t c)))
- data MapAccumRSym1 (a6989586621680784584 :: (~>) a ((~>) b (a, c))) :: (~>) a ((~>) (t b) (a, t c))
- data MapAccumRSym2 (a6989586621680784584 :: (~>) a ((~>) b (a, c))) (a6989586621680784585 :: a) :: (~>) (t b) (a, t c)
- type family MapAccumRSym3 (a6989586621680784584 :: (~>) a ((~>) b (a, c))) (a6989586621680784585 :: a) (a6989586621680784586 :: t b) :: (a, t c) where ...
- data ReplicateSym0 :: (~>) Natural ((~>) a [a])
- data ReplicateSym1 (a6989586621679848047 :: Natural) :: (~>) a [a]
- type family ReplicateSym2 (a6989586621679848047 :: Natural) (a6989586621679848048 :: a) :: [a] where ...
- data UnfoldrSym0 :: (~>) ((~>) b (Maybe (a, b))) ((~>) b [a])
- data UnfoldrSym1 (a6989586621679848802 :: (~>) b (Maybe (a, b))) :: (~>) b [a]
- type family UnfoldrSym2 (a6989586621679848802 :: (~>) b (Maybe (a, b))) (a6989586621679848803 :: b) :: [a] where ...
- data TakeSym0 :: (~>) Natural ((~>) [a] [a])
- data TakeSym1 (a6989586621679848202 :: Natural) :: (~>) [a] [a]
- type family TakeSym2 (a6989586621679848202 :: Natural) (a6989586621679848203 :: [a]) :: [a] where ...
- data DropSym0 :: (~>) Natural ((~>) [a] [a])
- data DropSym1 (a6989586621679848189 :: Natural) :: (~>) [a] [a]
- type family DropSym2 (a6989586621679848189 :: Natural) (a6989586621679848190 :: [a]) :: [a] where ...
- data SplitAtSym0 :: (~>) Natural ((~>) [a] ([a], [a]))
- data SplitAtSym1 (a6989586621679848182 :: Natural) :: (~>) [a] ([a], [a])
- type family SplitAtSym2 (a6989586621679848182 :: Natural) (a6989586621679848183 :: [a]) :: ([a], [a]) where ...
- data TakeWhileSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a])
- data TakeWhileSym1 (a6989586621679848319 :: (~>) a Bool) :: (~>) [a] [a]
- type family TakeWhileSym2 (a6989586621679848319 :: (~>) a Bool) (a6989586621679848320 :: [a]) :: [a] where ...
- data DropWhileSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a])
- data DropWhileSym1 (a6989586621679848304 :: (~>) a Bool) :: (~>) [a] [a]
- type family DropWhileSym2 (a6989586621679848304 :: (~>) a Bool) (a6989586621679848305 :: [a]) :: [a] where ...
- data DropWhileEndSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a])
- data DropWhileEndSym1 (a6989586621679848287 :: (~>) a Bool) :: (~>) [a] [a]
- type family DropWhileEndSym2 (a6989586621679848287 :: (~>) a Bool) (a6989586621679848288 :: [a]) :: [a] where ...
- data SpanSym0 :: (~>) ((~>) a Bool) ((~>) [a] ([a], [a]))
- data SpanSym1 (a6989586621679848250 :: (~>) a Bool) :: (~>) [a] ([a], [a])
- type family SpanSym2 (a6989586621679848250 :: (~>) a Bool) (a6989586621679848251 :: [a]) :: ([a], [a]) where ...
- data BreakSym0 :: (~>) ((~>) a Bool) ((~>) [a] ([a], [a]))
- data BreakSym1 (a6989586621679848215 :: (~>) a Bool) :: (~>) [a] ([a], [a])
- type family BreakSym2 (a6989586621679848215 :: (~>) a Bool) (a6989586621679848216 :: [a]) :: ([a], [a]) where ...
- data StripPrefixSym0 :: (~>) [a] ((~>) [a] (Maybe [a]))
- data StripPrefixSym1 (a6989586621679997490 :: [a]) :: (~>) [a] (Maybe [a])
- type family StripPrefixSym2 (a6989586621679997490 :: [a]) (a6989586621679997491 :: [a]) :: Maybe [a] where ...
- data GroupSym0 :: (~>) [a] [[a]]
- type family GroupSym1 (a6989586621679848177 :: [a]) :: [[a]] where ...
- data InitsSym0 :: (~>) [a] [[a]]
- type family InitsSym1 (a6989586621679848792 :: [a]) :: [[a]] where ...
- data TailsSym0 :: (~>) [a] [[a]]
- type family TailsSym1 (a6989586621679848784 :: [a]) :: [[a]] where ...
- data IsPrefixOfSym0 :: (~>) [a] ((~>) [a] Bool)
- data IsPrefixOfSym1 (a6989586621679848776 :: [a]) :: (~>) [a] Bool
- type family IsPrefixOfSym2 (a6989586621679848776 :: [a]) (a6989586621679848777 :: [a]) :: Bool where ...
- data IsSuffixOfSym0 :: (~>) [a] ((~>) [a] Bool)
- data IsSuffixOfSym1 (a6989586621679848769 :: [a]) :: (~>) [a] Bool
- type family IsSuffixOfSym2 (a6989586621679848769 :: [a]) (a6989586621679848770 :: [a]) :: Bool where ...
- data IsInfixOfSym0 :: (~>) [a] ((~>) [a] Bool)
- data IsInfixOfSym1 (a6989586621679848762 :: [a]) :: (~>) [a] Bool
- type family IsInfixOfSym2 (a6989586621679848762 :: [a]) (a6989586621679848763 :: [a]) :: Bool where ...
- data ElemSym0 :: (~>) a ((~>) (t a) Bool)
- data ElemSym1 (a6989586621680427286 :: a) :: (~>) (t a) Bool
- type family ElemSym2 (a6989586621680427286 :: a) (a6989586621680427287 :: t a) :: Bool where ...
- data NotElemSym0 :: (~>) a ((~>) (t a) Bool)
- data NotElemSym1 (a6989586621680427033 :: a) :: (~>) (t a) Bool
- type family NotElemSym2 (a6989586621680427033 :: a) (a6989586621680427034 :: t a) :: Bool where ...
- data LookupSym0 :: (~>) a ((~>) [(a, b)] (Maybe b))
- data LookupSym1 (a6989586621679848110 :: a) :: (~>) [(a, b)] (Maybe b)
- type family LookupSym2 (a6989586621679848110 :: a) (a6989586621679848111 :: [(a, b)]) :: Maybe b where ...
- data FindSym0 :: (~>) ((~>) a Bool) ((~>) (t a) (Maybe a))
- data FindSym1 (a6989586621680427015 :: (~>) a Bool) :: (~>) (t a) (Maybe a)
- type family FindSym2 (a6989586621680427015 :: (~>) a Bool) (a6989586621680427016 :: t a) :: Maybe a where ...
- data FilterSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a])
- data FilterSym1 (a6989586621679848419 :: (~>) a Bool) :: (~>) [a] [a]
- type family FilterSym2 (a6989586621679848419 :: (~>) a Bool) (a6989586621679848420 :: [a]) :: [a] where ...
- data PartitionSym0 :: (~>) ((~>) a Bool) ((~>) [a] ([a], [a]))
- data PartitionSym1 (a6989586621679848103 :: (~>) a Bool) :: (~>) [a] ([a], [a])
- type family PartitionSym2 (a6989586621679848103 :: (~>) a Bool) (a6989586621679848104 :: [a]) :: ([a], [a]) where ...
- data (!!@#@$) :: (~>) [a] ((~>) Natural a)
- data (!!@#@$$) (a6989586621679848027 :: [a]) :: (~>) Natural a
- type family (a6989586621679848027 :: [a]) !!@#@$$$ (a6989586621679848028 :: Natural) :: a where ...
- data ElemIndexSym0 :: (~>) a ((~>) [a] (Maybe Natural))
- data ElemIndexSym1 (a6989586621679848403 :: a) :: (~>) [a] (Maybe Natural)
- type family ElemIndexSym2 (a6989586621679848403 :: a) (a6989586621679848404 :: [a]) :: Maybe Natural where ...
- data ElemIndicesSym0 :: (~>) a ((~>) [a] [Natural])
- data ElemIndicesSym1 (a6989586621679848394 :: a) :: (~>) [a] [Natural]
- type family ElemIndicesSym2 (a6989586621679848394 :: a) (a6989586621679848395 :: [a]) :: [Natural] where ...
- data FindIndexSym0 :: (~>) ((~>) a Bool) ((~>) [a] (Maybe Natural))
- data FindIndexSym1 (a6989586621679848385 :: (~>) a Bool) :: (~>) [a] (Maybe Natural)
- type family FindIndexSym2 (a6989586621679848385 :: (~>) a Bool) (a6989586621679848386 :: [a]) :: Maybe Natural where ...
- data FindIndicesSym0 :: (~>) ((~>) a Bool) ((~>) [a] [Natural])
- data FindIndicesSym1 (a6989586621679848362 :: (~>) a Bool) :: (~>) [a] [Natural]
- type family FindIndicesSym2 (a6989586621679848362 :: (~>) a Bool) (a6989586621679848363 :: [a]) :: [Natural] where ...
- data ZipSym0 :: (~>) [a] ((~>) [b] [(a, b)])
- data ZipSym1 (a6989586621679848737 :: [a]) :: (~>) [b] [(a, b)]
- type family ZipSym2 (a6989586621679848737 :: [a]) (a6989586621679848738 :: [b]) :: [(a, b)] where ...
- data Zip3Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] [(a, b, c)]))
- data Zip3Sym1 (a6989586621679848725 :: [a]) :: (~>) [b] ((~>) [c] [(a, b, c)])
- data Zip3Sym2 (a6989586621679848725 :: [a]) (a6989586621679848726 :: [b]) :: (~>) [c] [(a, b, c)]
- type family Zip3Sym3 (a6989586621679848725 :: [a]) (a6989586621679848726 :: [b]) (a6989586621679848727 :: [c]) :: [(a, b, c)] where ...
- data Zip4Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] [(a, b, c, d)])))
- data Zip4Sym1 (a6989586621679997479 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] [(a, b, c, d)]))
- data Zip4Sym2 (a6989586621679997479 :: [a]) (a6989586621679997480 :: [b]) :: (~>) [c] ((~>) [d] [(a, b, c, d)])
- data Zip4Sym3 (a6989586621679997479 :: [a]) (a6989586621679997480 :: [b]) (a6989586621679997481 :: [c]) :: (~>) [d] [(a, b, c, d)]
- type family Zip4Sym4 (a6989586621679997479 :: [a]) (a6989586621679997480 :: [b]) (a6989586621679997481 :: [c]) (a6989586621679997482 :: [d]) :: [(a, b, c, d)] where ...
- data Zip5Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [(a, b, c, d, e)]))))
- data Zip5Sym1 (a6989586621679997456 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [(a, b, c, d, e)])))
- data Zip5Sym2 (a6989586621679997456 :: [a]) (a6989586621679997457 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] [(a, b, c, d, e)]))
- data Zip5Sym3 (a6989586621679997456 :: [a]) (a6989586621679997457 :: [b]) (a6989586621679997458 :: [c]) :: (~>) [d] ((~>) [e] [(a, b, c, d, e)])
- data Zip5Sym4 (a6989586621679997456 :: [a]) (a6989586621679997457 :: [b]) (a6989586621679997458 :: [c]) (a6989586621679997459 :: [d]) :: (~>) [e] [(a, b, c, d, e)]
- type family Zip5Sym5 (a6989586621679997456 :: [a]) (a6989586621679997457 :: [b]) (a6989586621679997458 :: [c]) (a6989586621679997459 :: [d]) (a6989586621679997460 :: [e]) :: [(a, b, c, d, e)] where ...
- data Zip6Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)])))))
- data Zip6Sym1 (a6989586621679997428 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)]))))
- data Zip6Sym2 (a6989586621679997428 :: [a]) (a6989586621679997429 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)])))
- data Zip6Sym3 (a6989586621679997428 :: [a]) (a6989586621679997429 :: [b]) (a6989586621679997430 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)]))
- data Zip6Sym4 (a6989586621679997428 :: [a]) (a6989586621679997429 :: [b]) (a6989586621679997430 :: [c]) (a6989586621679997431 :: [d]) :: (~>) [e] ((~>) [f] [(a, b, c, d, e, f)])
- data Zip6Sym5 (a6989586621679997428 :: [a]) (a6989586621679997429 :: [b]) (a6989586621679997430 :: [c]) (a6989586621679997431 :: [d]) (a6989586621679997432 :: [e]) :: (~>) [f] [(a, b, c, d, e, f)]
- type family Zip6Sym6 (a6989586621679997428 :: [a]) (a6989586621679997429 :: [b]) (a6989586621679997430 :: [c]) (a6989586621679997431 :: [d]) (a6989586621679997432 :: [e]) (a6989586621679997433 :: [f]) :: [(a, b, c, d, e, f)] where ...
- data Zip7Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)]))))))
- data Zip7Sym1 (a6989586621679997395 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)])))))
- data Zip7Sym2 (a6989586621679997395 :: [a]) (a6989586621679997396 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)]))))
- data Zip7Sym3 (a6989586621679997395 :: [a]) (a6989586621679997396 :: [b]) (a6989586621679997397 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)])))
- data Zip7Sym4 (a6989586621679997395 :: [a]) (a6989586621679997396 :: [b]) (a6989586621679997397 :: [c]) (a6989586621679997398 :: [d]) :: (~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)]))
- data Zip7Sym5 (a6989586621679997395 :: [a]) (a6989586621679997396 :: [b]) (a6989586621679997397 :: [c]) (a6989586621679997398 :: [d]) (a6989586621679997399 :: [e]) :: (~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)])
- data Zip7Sym6 (a6989586621679997395 :: [a]) (a6989586621679997396 :: [b]) (a6989586621679997397 :: [c]) (a6989586621679997398 :: [d]) (a6989586621679997399 :: [e]) (a6989586621679997400 :: [f]) :: (~>) [g] [(a, b, c, d, e, f, g)]
- type family Zip7Sym7 (a6989586621679997395 :: [a]) (a6989586621679997396 :: [b]) (a6989586621679997397 :: [c]) (a6989586621679997398 :: [d]) (a6989586621679997399 :: [e]) (a6989586621679997400 :: [f]) (a6989586621679997401 :: [g]) :: [(a, b, c, d, e, f, g)] where ...
- data ZipWithSym0 :: (~>) ((~>) a ((~>) b c)) ((~>) [a] ((~>) [b] [c]))
- data ZipWithSym1 (a6989586621679848713 :: (~>) a ((~>) b c)) :: (~>) [a] ((~>) [b] [c])
- data ZipWithSym2 (a6989586621679848713 :: (~>) a ((~>) b c)) (a6989586621679848714 :: [a]) :: (~>) [b] [c]
- type family ZipWithSym3 (a6989586621679848713 :: (~>) a ((~>) b c)) (a6989586621679848714 :: [a]) (a6989586621679848715 :: [b]) :: [c] where ...
- data ZipWith3Sym0 :: (~>) ((~>) a ((~>) b ((~>) c d))) ((~>) [a] ((~>) [b] ((~>) [c] [d])))
- data ZipWith3Sym1 (a6989586621679848698 :: (~>) a ((~>) b ((~>) c d))) :: (~>) [a] ((~>) [b] ((~>) [c] [d]))
- data ZipWith3Sym2 (a6989586621679848698 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679848699 :: [a]) :: (~>) [b] ((~>) [c] [d])
- data ZipWith3Sym3 (a6989586621679848698 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679848699 :: [a]) (a6989586621679848700 :: [b]) :: (~>) [c] [d]
- type family ZipWith3Sym4 (a6989586621679848698 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679848699 :: [a]) (a6989586621679848700 :: [b]) (a6989586621679848701 :: [c]) :: [d] where ...
- data ZipWith4Sym0 :: (~>) ((~>) a ((~>) b ((~>) c ((~>) d e)))) ((~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] [e]))))
- data ZipWith4Sym1 (a6989586621679997359 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] [e])))
- data ZipWith4Sym2 (a6989586621679997359 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679997360 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] [e]))
- data ZipWith4Sym3 (a6989586621679997359 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679997360 :: [a]) (a6989586621679997361 :: [b]) :: (~>) [c] ((~>) [d] [e])
- data ZipWith4Sym4 (a6989586621679997359 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679997360 :: [a]) (a6989586621679997361 :: [b]) (a6989586621679997362 :: [c]) :: (~>) [d] [e]
- type family ZipWith4Sym5 (a6989586621679997359 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679997360 :: [a]) (a6989586621679997361 :: [b]) (a6989586621679997362 :: [c]) (a6989586621679997363 :: [d]) :: [e] where ...
- data ZipWith5Sym0 :: (~>) ((~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) ((~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [f])))))
- data ZipWith5Sym1 (a6989586621679997336 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [f]))))
- data ZipWith5Sym2 (a6989586621679997336 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679997337 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [f])))
- data ZipWith5Sym3 (a6989586621679997336 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679997337 :: [a]) (a6989586621679997338 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] [f]))
- data ZipWith5Sym4 (a6989586621679997336 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679997337 :: [a]) (a6989586621679997338 :: [b]) (a6989586621679997339 :: [c]) :: (~>) [d] ((~>) [e] [f])
- data ZipWith5Sym5 (a6989586621679997336 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679997337 :: [a]) (a6989586621679997338 :: [b]) (a6989586621679997339 :: [c]) (a6989586621679997340 :: [d]) :: (~>) [e] [f]
- type family ZipWith5Sym6 (a6989586621679997336 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679997337 :: [a]) (a6989586621679997338 :: [b]) (a6989586621679997339 :: [c]) (a6989586621679997340 :: [d]) (a6989586621679997341 :: [e]) :: [f] where ...
- data ZipWith6Sym0 :: (~>) ((~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) ((~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g]))))))
- data ZipWith6Sym1 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g])))))
- data ZipWith6Sym2 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679997310 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g]))))
- data ZipWith6Sym3 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679997310 :: [a]) (a6989586621679997311 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g])))
- data ZipWith6Sym4 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679997310 :: [a]) (a6989586621679997311 :: [b]) (a6989586621679997312 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] [g]))
- data ZipWith6Sym5 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679997310 :: [a]) (a6989586621679997311 :: [b]) (a6989586621679997312 :: [c]) (a6989586621679997313 :: [d]) :: (~>) [e] ((~>) [f] [g])
- data ZipWith6Sym6 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679997310 :: [a]) (a6989586621679997311 :: [b]) (a6989586621679997312 :: [c]) (a6989586621679997313 :: [d]) (a6989586621679997314 :: [e]) :: (~>) [f] [g]
- type family ZipWith6Sym7 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679997310 :: [a]) (a6989586621679997311 :: [b]) (a6989586621679997312 :: [c]) (a6989586621679997313 :: [d]) (a6989586621679997314 :: [e]) (a6989586621679997315 :: [f]) :: [g] where ...
- data ZipWith7Sym0 :: (~>) ((~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) ((~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h])))))))
- data ZipWith7Sym1 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h]))))))
- data ZipWith7Sym2 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h])))))
- data ZipWith7Sym3 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) (a6989586621679997280 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h]))))
- data ZipWith7Sym4 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) (a6989586621679997280 :: [b]) (a6989586621679997281 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h])))
- data ZipWith7Sym5 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) (a6989586621679997280 :: [b]) (a6989586621679997281 :: [c]) (a6989586621679997282 :: [d]) :: (~>) [e] ((~>) [f] ((~>) [g] [h]))
- data ZipWith7Sym6 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) (a6989586621679997280 :: [b]) (a6989586621679997281 :: [c]) (a6989586621679997282 :: [d]) (a6989586621679997283 :: [e]) :: (~>) [f] ((~>) [g] [h])
- data ZipWith7Sym7 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) (a6989586621679997280 :: [b]) (a6989586621679997281 :: [c]) (a6989586621679997282 :: [d]) (a6989586621679997283 :: [e]) (a6989586621679997284 :: [f]) :: (~>) [g] [h]
- type family ZipWith7Sym8 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) (a6989586621679997280 :: [b]) (a6989586621679997281 :: [c]) (a6989586621679997282 :: [d]) (a6989586621679997283 :: [e]) (a6989586621679997284 :: [f]) (a6989586621679997285 :: [g]) :: [h] where ...
- data UnzipSym0 :: (~>) [(a, b)] ([a], [b])
- type family UnzipSym1 (a6989586621679848679 :: [(a, b)]) :: ([a], [b]) where ...
- data Unzip3Sym0 :: (~>) [(a, b, c)] ([a], [b], [c])
- type family Unzip3Sym1 (a6989586621679848661 :: [(a, b, c)]) :: ([a], [b], [c]) where ...
- data Unzip4Sym0 :: (~>) [(a, b, c, d)] ([a], [b], [c], [d])
- type family Unzip4Sym1 (a6989586621679848641 :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
- data Unzip5Sym0 :: (~>) [(a, b, c, d, e)] ([a], [b], [c], [d], [e])
- type family Unzip5Sym1 (a6989586621679848619 :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ...
- data Unzip6Sym0 :: (~>) [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f])
- type family Unzip6Sym1 (a6989586621679848595 :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ...
- data Unzip7Sym0 :: (~>) [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g])
- type family Unzip7Sym1 (a6989586621679848569 :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
- data UnlinesSym0 :: (~>) [Symbol] Symbol
- type family UnlinesSym1 (a6989586621679848564 :: [Symbol]) :: Symbol where ...
- data UnwordsSym0 :: (~>) [Symbol] Symbol
- type family UnwordsSym1 (a6989586621679848554 :: [Symbol]) :: Symbol where ...
- data NubSym0 :: (~>) [a] [a]
- type family NubSym1 (a6989586621679848010 :: [a]) :: [a] where ...
- data DeleteSym0 :: (~>) a ((~>) [a] [a])
- data DeleteSym1 (a6989586621679848548 :: a) :: (~>) [a] [a]
- type family DeleteSym2 (a6989586621679848548 :: a) (a6989586621679848549 :: [a]) :: [a] where ...
- data (\\@#@$) :: (~>) [a] ((~>) [a] [a])
- data (\\@#@$$) (a6989586621679848537 :: [a]) :: (~>) [a] [a]
- type family (a6989586621679848537 :: [a]) \\@#@$$$ (a6989586621679848538 :: [a]) :: [a] where ...
- data UnionSym0 :: (~>) [a] ((~>) [a] [a])
- data UnionSym1 (a6989586621679847964 :: [a]) :: (~>) [a] [a]
- type family UnionSym2 (a6989586621679847964 :: [a]) (a6989586621679847965 :: [a]) :: [a] where ...
- data IntersectSym0 :: (~>) [a] ((~>) [a] [a])
- data IntersectSym1 (a6989586621679848355 :: [a]) :: (~>) [a] [a]
- type family IntersectSym2 (a6989586621679848355 :: [a]) (a6989586621679848356 :: [a]) :: [a] where ...
- data InsertSym0 :: (~>) a ((~>) [a] [a])
- data InsertSym1 (a6989586621679848157 :: a) :: (~>) [a] [a]
- type family InsertSym2 (a6989586621679848157 :: a) (a6989586621679848158 :: [a]) :: [a] where ...
- data SortSym0 :: (~>) [a] [a]
- type family SortSym1 (a6989586621679848152 :: [a]) :: [a] where ...
- data NubBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] [a])
- data NubBySym1 (a6989586621679847992 :: (~>) a ((~>) a Bool)) :: (~>) [a] [a]
- type family NubBySym2 (a6989586621679847992 :: (~>) a ((~>) a Bool)) (a6989586621679847993 :: [a]) :: [a] where ...
- data DeleteBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) a ((~>) [a] [a]))
- data DeleteBySym1 (a6989586621679848518 :: (~>) a ((~>) a Bool)) :: (~>) a ((~>) [a] [a])
- data DeleteBySym2 (a6989586621679848518 :: (~>) a ((~>) a Bool)) (a6989586621679848519 :: a) :: (~>) [a] [a]
- type family DeleteBySym3 (a6989586621679848518 :: (~>) a ((~>) a Bool)) (a6989586621679848519 :: a) (a6989586621679848520 :: [a]) :: [a] where ...
- data DeleteFirstsBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] ((~>) [a] [a]))
- data DeleteFirstsBySym1 (a6989586621679848508 :: (~>) a ((~>) a Bool)) :: (~>) [a] ((~>) [a] [a])
- data DeleteFirstsBySym2 (a6989586621679848508 :: (~>) a ((~>) a Bool)) (a6989586621679848509 :: [a]) :: (~>) [a] [a]
- type family DeleteFirstsBySym3 (a6989586621679848508 :: (~>) a ((~>) a Bool)) (a6989586621679848509 :: [a]) (a6989586621679848510 :: [a]) :: [a] where ...
- data UnionBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] ((~>) [a] [a]))
- data UnionBySym1 (a6989586621679847972 :: (~>) a ((~>) a Bool)) :: (~>) [a] ((~>) [a] [a])
- data UnionBySym2 (a6989586621679847972 :: (~>) a ((~>) a Bool)) (a6989586621679847973 :: [a]) :: (~>) [a] [a]
- type family UnionBySym3 (a6989586621679847972 :: (~>) a ((~>) a Bool)) (a6989586621679847973 :: [a]) (a6989586621679847974 :: [a]) :: [a] where ...
- data IntersectBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] ((~>) [a] [a]))
- data IntersectBySym1 (a6989586621679848333 :: (~>) a ((~>) a Bool)) :: (~>) [a] ((~>) [a] [a])
- data IntersectBySym2 (a6989586621679848333 :: (~>) a ((~>) a Bool)) (a6989586621679848334 :: [a]) :: (~>) [a] [a]
- type family IntersectBySym3 (a6989586621679848333 :: (~>) a ((~>) a Bool)) (a6989586621679848334 :: [a]) (a6989586621679848335 :: [a]) :: [a] where ...
- data GroupBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] [[a]])
- data GroupBySym1 (a6989586621679848125 :: (~>) a ((~>) a Bool)) :: (~>) [a] [[a]]
- type family GroupBySym2 (a6989586621679848125 :: (~>) a ((~>) a Bool)) (a6989586621679848126 :: [a]) :: [[a]] where ...
- data SortBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) [a] [a])
- data SortBySym1 (a6989586621679848496 :: (~>) a ((~>) a Ordering)) :: (~>) [a] [a]
- type family SortBySym2 (a6989586621679848496 :: (~>) a ((~>) a Ordering)) (a6989586621679848497 :: [a]) :: [a] where ...
- data InsertBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) a ((~>) [a] [a]))
- data InsertBySym1 (a6989586621679848476 :: (~>) a ((~>) a Ordering)) :: (~>) a ((~>) [a] [a])
- data InsertBySym2 (a6989586621679848476 :: (~>) a ((~>) a Ordering)) (a6989586621679848477 :: a) :: (~>) [a] [a]
- type family InsertBySym3 (a6989586621679848476 :: (~>) a ((~>) a Ordering)) (a6989586621679848477 :: a) (a6989586621679848478 :: [a]) :: [a] where ...
- data MaximumBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (t a) a)
- data MaximumBySym1 (a6989586621680427062 :: (~>) a ((~>) a Ordering)) :: (~>) (t a) a
- type family MaximumBySym2 (a6989586621680427062 :: (~>) a ((~>) a Ordering)) (a6989586621680427063 :: t a) :: a where ...
- data MinimumBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (t a) a)
- data MinimumBySym1 (a6989586621680427042 :: (~>) a ((~>) a Ordering)) :: (~>) (t a) a
- type family MinimumBySym2 (a6989586621680427042 :: (~>) a ((~>) a Ordering)) (a6989586621680427043 :: t a) :: a where ...
- data GenericLengthSym0 :: (~>) [a] i
- type family GenericLengthSym1 (a6989586621679847955 :: [a]) :: i where ...
The singleton for lists
type family Sing :: k -> Type #
Instances
data SList :: forall (a :: Type). [a] -> Type where Source #
Constructors
| SNil :: forall (a :: Type). SList ('[] :: [a :: Type]) | |
| SCons :: forall (a :: Type) (n :: a) (n :: [a]). (Sing n) -> (Sing n) -> SList ('(:) n n :: [a :: Type]) infixr 5 |
Instances
| (SDecide a, SDecide [a]) => TestCoercion (SList :: [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| (SDecide a, SDecide [a]) => TestEquality (SList :: [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| (ShowSing a, ShowSing [a]) => Show (SList z) Source # | |
Basic functions
(%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a]) infixr 5 Source #
type family Null (arg :: t a) :: Bool Source #
Instances
type family Length (arg :: t a) :: Natural Source #
Instances
sLength :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply LengthSym0 t :: Natural) Source #
List transformations
sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b]) Source #
type family Intersperse (a :: a) (a :: [a]) :: [a] where ... Source #
Equations
| Intersperse _ '[] = NilSym0 | |
| Intersperse sep ('(:) x xs) = Apply (Apply (:@#@$) x) (Apply (Apply PrependToAllSym0 sep) xs) |
sIntersperse :: forall a (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a]) Source #
type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ... Source #
Equations
| Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) |
sIntercalate :: forall a (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a]) Source #
sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]]) Source #
type family Subsequences (a :: [a]) :: [[a]] where ... Source #
Equations
| Subsequences xs = Apply (Apply (:@#@$) NilSym0) (Apply NonEmptySubsequencesSym0 xs) |
sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]]) Source #
type family Permutations (a :: [a]) :: [[a]] where ... Source #
Equations
| Permutations xs0 = Apply (Apply (:@#@$) xs0) (Apply (Apply (Let6989586621679849061PermsSym1 xs0) xs0) NilSym0) |
sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]]) Source #
Reducing lists (folds)
type family Foldl (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #
Instances
| type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Min a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Identity a1) Source # | |
Defined in Data.Functor.Identity.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Dual a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Product a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Sum a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: NonEmpty a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: [a1]) Source # | |
Defined in Data.Foldable.Singletons type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: [a1]) | |
| type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1)) Source # | |
Defined in Data.Foldable.Singletons type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1)) | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Proxy a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source #
type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #
Instances
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Min a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: NonEmpty a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Identity a1) Source # | |
Defined in Data.Functor.Identity.Singletons | |
| type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Dual a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Product a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Sum a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: [a1]) Source # | |
Defined in Data.Foldable.Singletons type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: [a1]) | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Proxy a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1)) Source # | |
Defined in Data.Foldable.Singletons type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1)) | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) Source #
type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #
Instances
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Min a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Functor.Identity.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Foldable.Singletons type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) | |
| type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1)) Source # | |
Defined in Data.Foldable.Singletons type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1)) | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) Source #
sFoldl1' :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a) Source #
type family Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b Source #
Instances
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Identity a1) Source # | |
Defined in Data.Functor.Identity.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: First a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Last a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: First a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Last a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Max a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Min a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Dual a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Product a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Sum a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: NonEmpty a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: [a1]) Source # | |
Defined in Data.Foldable.Singletons type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: [a1]) | |
| type Foldr (a3 :: a1 ~> (k2 ~> k2)) (a4 :: k2) (a5 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Proxy a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a3 :: a1 ~> (k2 ~> k2)) (a4 :: k2) (a5 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr (a3 :: a1 ~> (k2 ~> k2)) (a4 :: k2) (a5 :: (a2, a1)) Source # | |
Defined in Data.Foldable.Singletons type Foldr (a3 :: a1 ~> (k2 ~> k2)) (a4 :: k2) (a5 :: (a2, a1)) | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Const m a1) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldr (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldr (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldr (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source #
type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #
Instances
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Min a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Functor.Identity.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Foldable.Singletons type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) | |
| type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1)) Source # | |
Defined in Data.Foldable.Singletons type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1)) | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) Source #
Special folds
sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a]) Source #
sConcatMap :: forall a b t (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) Source #
type family And (a :: t Bool) :: Bool where ... Source #
Equations
| And a_6989586621680427101 = Apply (Apply (Apply (.@#@$) GetAllSym0) (Apply FoldMapSym0 All_Sym0)) a_6989586621680427101 |
type family Or (a :: t Bool) :: Bool where ... Source #
Equations
| Or a_6989586621680427095 = Apply (Apply (Apply (.@#@$) GetAnySym0) (Apply FoldMapSym0 Any_Sym0)) a_6989586621680427095 |
type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #
Equations
| Any p a_6989586621680427086 = Apply (Apply (Apply (.@#@$) GetAnySym0) (Apply FoldMapSym0 (Apply (Apply (.@#@$) Any_Sym0) p))) a_6989586621680427086 |
sAny :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool) Source #
type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #
Equations
| All p a_6989586621680427077 = Apply (Apply (Apply (.@#@$) GetAllSym0) (Apply FoldMapSym0 (Apply (Apply (.@#@$) All_Sym0) p))) a_6989586621680427077 |
sAll :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) Source #
type family Sum (arg :: t a) :: a Source #
Instances
sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a) Source #
type family Product (arg :: t a) :: a Source #
Instances
sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a) Source #
type family Maximum (arg :: t a) :: a Source #
Instances
sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a) Source #
type family Minimum (arg :: t a) :: a Source #
Instances
sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a) Source #
Building lists
Scans
sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b]) Source #
sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a]) Source #
sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b]) Source #
type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ... Source #
Equations
| Scanr1 _ '[] = NilSym0 | |
| Scanr1 _ '[x] = Apply (Apply (:@#@$) x) NilSym0 | |
| Scanr1 f ('(:) x ('(:) wild_6989586621679844400 wild_6989586621679844402)) = Case_6989586621679848921 f x wild_6989586621679844400 wild_6989586621679844402 (Let6989586621679848919Scrutinee_6989586621679844394Sym4 f x wild_6989586621679844400 wild_6989586621679844402) |
sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a]) Source #
Accumulating maps
type family MapAccumL (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ... Source #
Equations
| MapAccumL f s t = Apply (Apply RunStateLSym0 (Apply (Apply TraverseSym0 (Apply (Apply (.@#@$) StateLSym0) (Apply FlipSym0 f))) t)) s |
sMapAccumL :: forall t a b c (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (a, t c)) Source #
type family MapAccumR (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ... Source #
Equations
| MapAccumR f s t = Apply (Apply RunStateRSym0 (Apply (Apply TraverseSym0 (Apply (Apply (.@#@$) StateRSym0) (Apply FlipSym0 f))) t)) s |
sMapAccumR :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c)) Source #
Cyclical lists
type family Replicate (a :: Natural) (a :: a) :: [a] where ... Source #
Equations
| Replicate n x = Case_6989586621679848053 n x (Let6989586621679848051Scrutinee_6989586621679844496Sym2 n x) |
sReplicate :: forall a (t :: Natural) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a]) Source #
Unfolding
type family Unfoldr (a :: (~>) b (Maybe (a, b))) (a :: b) :: [a] where ... Source #
Equations
| Unfoldr f b = Case_6989586621679848808 f b (Let6989586621679848806Scrutinee_6989586621679844404Sym2 f b) |
sUnfoldr :: forall b a (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a]) Source #
Sublists
Extracting sublists
sTake :: forall a (t :: Natural) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) Source #
sDrop :: forall a (t :: Natural) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) Source #
type family SplitAt (a :: Natural) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
| SplitAt n xs = Apply (Apply Tuple2Sym0 (Apply (Apply TakeSym0 n) xs)) (Apply (Apply DropSym0 n) xs) |
sSplitAt :: forall a (t :: Natural) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) Source #
sTakeWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) Source #
sDropWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) Source #
type family DropWhileEnd (a :: (~>) a Bool) (a :: [a]) :: [a] where ... Source #
Equations
| DropWhileEnd p a_6989586621679848282 = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_6989586621679848291Sym0 p) a_6989586621679848282)) NilSym0) a_6989586621679848282 |
sDropWhileEnd :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a]) Source #
type family Span (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
| Span _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679848252XsSym0) Let6989586621679848252XsSym0 | |
| Span p ('(:) x xs') = Case_6989586621679848261 p x xs' (Let6989586621679848259Scrutinee_6989586621679844476Sym3 p x xs') |
sSpan :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) Source #
type family Break (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
| Break _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679848217XsSym0) Let6989586621679848217XsSym0 | |
| Break p ('(:) x xs') = Case_6989586621679848226 p x xs' (Let6989586621679848224Scrutinee_6989586621679844478Sym3 p x xs') |
sBreak :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) Source #
type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ... Source #
Equations
| StripPrefix '[] ys = Apply JustSym0 ys | |
| StripPrefix arg_6989586621679996023 arg_6989586621679996025 = Case_6989586621679997495 arg_6989586621679996023 arg_6989586621679996025 (Apply (Apply Tuple2Sym0 arg_6989586621679996023) arg_6989586621679996025) |
type family Group (a :: [a]) :: [[a]] where ... Source #
Equations
| Group xs = Apply (Apply GroupBySym0 (==@#@$)) xs |
Predicates
type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
Equations
| IsPrefixOf '[] '[] = TrueSym0 | |
| IsPrefixOf '[] ('(:) _ _) = TrueSym0 | |
| IsPrefixOf ('(:) _ _) '[] = FalseSym0 | |
| IsPrefixOf ('(:) x xs) ('(:) y ys) = Apply (Apply (&&@#@$) (Apply (Apply (==@#@$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) |
sIsPrefixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) Source #
type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
Equations
| IsSuffixOf x y = Apply (Apply IsPrefixOfSym0 (Apply ReverseSym0 x)) (Apply ReverseSym0 y) |
sIsSuffixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) Source #
type family IsInfixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
Equations
| IsInfixOf needle haystack = Apply (Apply AnySym0 (Apply IsPrefixOfSym0 needle)) (Apply TailsSym0 haystack) |
sIsInfixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool) Source #
Searching lists
Searching by equality
type family Elem (arg :: a) (arg :: t a) :: Bool Source #
Instances
| type Elem (arg1 :: a) (arg2 :: First a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (arg1 :: a) (arg2 :: Last a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (arg1 :: a) (arg2 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Elem (arg1 :: a) (arg2 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Elem (arg1 :: a) (arg2 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Elem (arg1 :: a) (arg2 :: Min a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Elem (arg1 :: a) (arg2 :: NonEmpty a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (arg1 :: a) (arg2 :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (a1 :: k1) (a2 :: Identity k1) Source # | |
Defined in Data.Functor.Identity.Singletons | |
| type Elem (a1 :: k1) (a2 :: Dual k1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (a1 :: k1) (a2 :: Product k1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (a1 :: k1) (a2 :: Sum k1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (a1 :: k1) (a2 :: [k1]) Source # | |
Defined in Data.Foldable.Singletons type Elem (a1 :: k1) (a2 :: [k1]) | |
| type Elem (arg1 :: a1) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (arg1 :: a1) (arg2 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Elem (arg1 :: a1) (arg2 :: (a2, a1)) Source # | |
Defined in Data.Foldable.Singletons type Elem (arg1 :: a1) (arg2 :: (a2, a1)) | |
| type Elem (a1 :: k1) (a2 :: Proxy k1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (arg1 :: a) (arg2 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Elem (arg1 :: a) (arg2 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Elem (arg1 :: a) (arg2 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Elem (arg1 :: a) (arg2 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) Source #
sNotElem :: forall a t (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) Source #
type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... Source #
Equations
| Lookup _key '[] = NothingSym0 | |
| Lookup key ('(:) '(x, y) xys) = Case_6989586621679848119 key x y xys (Let6989586621679848117Scrutinee_6989586621679844492Sym4 key x y xys) |
sLookup :: forall a b (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 :: (~>) a Bool) (a :: t a) :: Maybe a where ... Source #
Equations
| Find p a_6989586621680427010 = Apply (Apply (Apply (.@#@$) GetFirstSym0) (Apply FoldMapSym0 (Apply (Apply Lambda_6989586621680427019Sym0 p) a_6989586621680427010))) a_6989586621680427010 |
sFind :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a) Source #
sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) Source #
type family Partition (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
| Partition p xs = Apply (Apply (Apply FoldrSym0 (Apply SelectSym0 p)) (Apply (Apply Tuple2Sym0 NilSym0) NilSym0)) xs |
sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) Source #
Indexing lists
(%!!) :: forall a (t :: [a]) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) infixl 9 Source #
type family ElemIndex (a :: a) (a :: [a]) :: Maybe Natural where ... Source #
Equations
| ElemIndex x a_6989586621679848398 = Apply (Apply FindIndexSym0 (Apply (==@#@$) x)) a_6989586621679848398 |
sElemIndex :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Natural) Source #
type family ElemIndices (a :: a) (a :: [a]) :: [Natural] where ... Source #
Equations
| ElemIndices x a_6989586621679848389 = Apply (Apply FindIndicesSym0 (Apply (==@#@$) x)) a_6989586621679848389 |
sElemIndices :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Natural]) Source #
type family FindIndex (a :: (~>) a Bool) (a :: [a]) :: Maybe Natural where ... Source #
Equations
| FindIndex p a_6989586621679848380 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679848380 |
sFindIndex :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Natural) Source #
type family FindIndices (a :: (~>) a Bool) (a :: [a]) :: [Natural] where ... Source #
Equations
| FindIndices p xs = Apply (Apply MapSym0 SndSym0) (Apply (Apply FilterSym0 (Apply (Apply Lambda_6989586621679848372Sym0 p) xs)) (Apply (Apply ZipSym0 xs) (Apply (Apply (Let6989586621679848366BuildListSym2 p xs) (FromInteger 0)) xs))) |
sFindIndices :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Natural]) Source #
Zipping and unzipping lists
sZip :: forall a b (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)]) Source #
type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ... Source #
Equations
| Zip3 ('(:) a as) ('(:) b bs) ('(:) c cs) = Apply (Apply (:@#@$) (Apply (Apply (Apply Tuple3Sym0 a) b) c)) (Apply (Apply (Apply Zip3Sym0 as) bs) cs) | |
| Zip3 '[] '[] '[] = NilSym0 | |
| Zip3 '[] '[] ('(:) _ _) = NilSym0 | |
| Zip3 '[] ('(:) _ _) '[] = NilSym0 | |
| Zip3 '[] ('(:) _ _) ('(:) _ _) = NilSym0 | |
| Zip3 ('(:) _ _) '[] '[] = NilSym0 | |
| Zip3 ('(:) _ _) '[] ('(:) _ _) = NilSym0 | |
| Zip3 ('(:) _ _) ('(:) _ _) '[] = NilSym0 |
sZip3 :: forall a b c (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 Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ... Source #
Equations
| Zip4 a_6989586621679997466 a_6989586621679997468 a_6989586621679997470 a_6989586621679997472 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621679997466) a_6989586621679997468) a_6989586621679997470) a_6989586621679997472 |
type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ... Source #
Equations
| Zip5 a_6989586621679997440 a_6989586621679997442 a_6989586621679997444 a_6989586621679997446 a_6989586621679997448 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621679997440) a_6989586621679997442) a_6989586621679997444) a_6989586621679997446) a_6989586621679997448 |
type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ... Source #
Equations
| Zip6 a_6989586621679997409 a_6989586621679997411 a_6989586621679997413 a_6989586621679997415 a_6989586621679997417 a_6989586621679997419 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621679997409) a_6989586621679997411) a_6989586621679997413) a_6989586621679997415) a_6989586621679997417) a_6989586621679997419 |
type family Zip7 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [(a, b, c, d, e, f, g)] where ... Source #
Equations
| Zip7 a_6989586621679997373 a_6989586621679997375 a_6989586621679997377 a_6989586621679997379 a_6989586621679997381 a_6989586621679997383 a_6989586621679997385 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621679997373) a_6989586621679997375) a_6989586621679997377) a_6989586621679997379) a_6989586621679997381) a_6989586621679997383) a_6989586621679997385 |
sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c]) Source #
type family ZipWith3 (a :: (~>) a ((~>) b ((~>) c d))) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ... Source #
Equations
| ZipWith3 z ('(:) a as) ('(:) b bs) ('(:) c cs) = Apply (Apply (:@#@$) (Apply (Apply (Apply z a) b) c)) (Apply (Apply (Apply (Apply ZipWith3Sym0 z) as) bs) cs) | |
| ZipWith3 _ '[] '[] '[] = NilSym0 | |
| ZipWith3 _ '[] '[] ('(:) _ _) = NilSym0 | |
| ZipWith3 _ '[] ('(:) _ _) '[] = NilSym0 | |
| ZipWith3 _ '[] ('(:) _ _) ('(:) _ _) = NilSym0 | |
| ZipWith3 _ ('(:) _ _) '[] '[] = NilSym0 | |
| ZipWith3 _ ('(:) _ _) '[] ('(:) _ _) = NilSym0 | |
| ZipWith3 _ ('(:) _ _) ('(:) _ _) '[] = NilSym0 |
sZipWith3 :: forall a b c d (t :: (~>) a ((~>) b ((~>) c d))) (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 #
type family ZipWith4 (a :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ... Source #
Equations
| ZipWith4 z ('(:) a as) ('(:) b bs) ('(:) c cs) ('(:) d ds) = Apply (Apply (:@#@$) (Apply (Apply (Apply (Apply z a) b) c) d)) (Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 z) as) bs) cs) ds) | |
| ZipWith4 _ _ _ _ _ = NilSym0 |
type family ZipWith5 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ... Source #
Equations
| ZipWith5 z ('(:) a as) ('(:) b bs) ('(:) c cs) ('(:) d ds) ('(:) e es) = Apply (Apply (:@#@$) (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e)) (Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 z) as) bs) cs) ds) es) | |
| ZipWith5 _ _ _ _ _ _ = NilSym0 |
type family ZipWith6 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ... Source #
Equations
| ZipWith6 z ('(:) a as) ('(:) b bs) ('(:) c cs) ('(:) d ds) ('(:) e es) ('(:) f fs) = Apply (Apply (:@#@$) (Apply (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e) f)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 z) as) bs) cs) ds) es) fs) | |
| ZipWith6 _ _ _ _ _ _ _ = NilSym0 |
type family ZipWith7 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ... Source #
Equations
| ZipWith7 z ('(:) a as) ('(:) b bs) ('(:) c cs) ('(:) d ds) ('(:) e es) ('(:) f fs) ('(:) g gs) = Apply (Apply (:@#@$) (Apply (Apply (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e) f) g)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 z) as) bs) cs) ds) es) fs) gs) | |
| ZipWith7 _ _ _ _ _ _ _ _ = NilSym0 |
type family Unzip (a :: [(a, b)]) :: ([a], [b]) where ... Source #
Equations
| Unzip xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679848681Sym0 xs)) (Apply (Apply Tuple2Sym0 NilSym0) NilSym0)) xs |
type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ... Source #
Equations
| Unzip3 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679848663Sym0 xs)) (Apply (Apply (Apply Tuple3Sym0 NilSym0) NilSym0) NilSym0)) xs |
sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c])) Source #
sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d])) Source #
sUnzip5 :: forall a b c d e (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e])) Source #
sUnzip6 :: forall a b c d e f (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 a b c d e f g (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g])) Source #
Special lists
Functions on Symbols
type family Unlines (a :: [Symbol]) :: Symbol where ... Source #
Equations
| Unlines '[] = "" | |
| Unlines ('(:) l ls) = Apply (Apply (<>@#@$) l) (Apply (Apply (<>@#@$) "\n") (Apply UnlinesSym0 ls)) |
"Set" operations
type family Delete (a :: a) (a :: [a]) :: [a] where ... Source #
Equations
| Delete a_6989586621679848541 a_6989586621679848543 = Apply (Apply (Apply DeleteBySym0 (==@#@$)) a_6989586621679848541) a_6989586621679848543 |
sDelete :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a]) Source #
type family (a :: [a]) \\ (a :: [a]) :: [a] where ... infix 5 Source #
Equations
| a_6989586621679848530 \\ a_6989586621679848532 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 DeleteSym0)) a_6989586621679848530) a_6989586621679848532 |
(%\\) :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (\\@#@$) t) t :: [a]) infix 5 Source #
type family Union (a :: [a]) (a :: [a]) :: [a] where ... Source #
Equations
| Union a_6989586621679847957 a_6989586621679847959 = Apply (Apply (Apply UnionBySym0 (==@#@$)) a_6989586621679847957) a_6989586621679847959 |
sUnion :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a]) Source #
type family Intersect (a :: [a]) (a :: [a]) :: [a] where ... Source #
Equations
| Intersect a_6989586621679848348 a_6989586621679848350 = Apply (Apply (Apply IntersectBySym0 (==@#@$)) a_6989586621679848348) a_6989586621679848350 |
sIntersect :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a]) Source #
Ordered lists
type family Insert (a :: a) (a :: [a]) :: [a] where ... Source #
Equations
| Insert e ls = Apply (Apply (Apply InsertBySym0 CompareSym0) e) ls |
sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a]) Source #
type family Sort (a :: [a]) :: [a] where ... Source #
Equations
| Sort a_6989586621679848148 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679848148 |
Generalized functions
The "By" operations
User-supplied equality (replacing an Eq context)
The predicate is assumed to define an equivalence.
sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a]) Source #
sDeleteBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a]) Source #
type family DeleteFirstsBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ... Source #
Equations
| DeleteFirstsBy eq a_6989586621679848500 a_6989586621679848502 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679848500) a_6989586621679848502 |
sDeleteFirstsBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a]) Source #
type family UnionBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ... Source #
Equations
| UnionBy eq xs ys = Apply (Apply (++@#@$) xs) (Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) (Apply (Apply NubBySym0 eq) ys)) xs) |
sUnionBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a]) Source #
type family IntersectBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ... Source #
Equations
| IntersectBy _ '[] '[] = NilSym0 | |
| IntersectBy _ '[] ('(:) _ _) = NilSym0 | |
| IntersectBy _ ('(:) _ _) '[] = NilSym0 | |
| IntersectBy eq ('(:) wild_6989586621679844462 wild_6989586621679844464) ('(:) wild_6989586621679844466 wild_6989586621679844468) = Apply (Apply (>>=@#@$) (Let6989586621679848341XsSym5 eq wild_6989586621679844462 wild_6989586621679844464 wild_6989586621679844466 wild_6989586621679844468)) (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679848344Sym0 eq) wild_6989586621679844462) wild_6989586621679844464) wild_6989586621679844466) wild_6989586621679844468) |
sIntersectBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a]) Source #
sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (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 :: (~>) a ((~>) a Ordering)) (a :: [a]) :: [a] where ... Source #
Equations
| SortBy cmp a_6989586621679848491 = Apply (Apply (Apply FoldrSym0 (Apply InsertBySym0 cmp)) NilSym0) a_6989586621679848491 |
sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a]) Source #
sInsertBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a]) Source #
type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #
Equations
| MaximumBy cmp a_6989586621680427057 = Apply (Apply Foldl1Sym0 (Let6989586621680427066Max'Sym2 cmp a_6989586621680427057)) a_6989586621680427057 |
sMaximumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) Source #
type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #
Equations
| MinimumBy cmp a_6989586621680427037 = Apply (Apply Foldl1Sym0 (Let6989586621680427046Min'Sym2 cmp a_6989586621680427037)) a_6989586621680427037 |
sMinimumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) Source #
The "generic" operations
The prefix `generic' indicates an overloaded function that
is a generalized version of a Prelude function.
type family GenericLength (a :: [a]) :: i where ... Source #
Equations
| GenericLength '[] = FromInteger 0 | |
| GenericLength ('(:) _ xs) = Apply (Apply (+@#@$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
sGenericLength :: forall a i (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i) Source #
Defunctionalization symbols
data (:@#@$) :: (~>) a ((~>) [a] [a :: Type]) infixr 5 Source #
Instances
| SingI ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| SuppressUnusedWarnings ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods suppressUnusedWarnings :: () # | |
| type Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679042108 :: a) Source # | |
Defined in Data.Singletons.Base.Instances | |
data (:@#@$$) (a6989586621679042108 :: a) :: (~>) [a] [a :: Type] infixr 5 Source #
Instances
| SingI1 ((:@#@$$) :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| SuppressUnusedWarnings ((:@#@$$) a6989586621679042108 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods suppressUnusedWarnings :: () # | |
| type Apply ((:@#@$$) a6989586621679042108 :: TyFun [a] [a] -> Type) (a6989586621679042109 :: [a]) Source # | |
Defined in Data.Singletons.Base.Instances | |
type family (a6989586621679042108 :: a) :@#@$$$ (a6989586621679042109 :: [a]) :: [a :: Type] where ... infixr 5 Source #
Equations
| a6989586621679042108 :@#@$$$ a6989586621679042109 = '(:) a6989586621679042108 a6989586621679042109 |
type family (a6989586621679287772 :: [a]) ++@#@$$$ (a6989586621679287773 :: [a]) :: [a] where ... infixr 5 Source #
data (++@#@$$) (a6989586621679287772 :: [a]) :: (~>) [a] [a] infixr 5 Source #
Instances
| SingI1 ((++@#@$$) :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in GHC.Base.Singletons | |
| SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
Defined in GHC.Base.Singletons | |
| SuppressUnusedWarnings ((++@#@$$) a6989586621679287772 :: TyFun [a] [a] -> Type) Source # | |
Defined in GHC.Base.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((++@#@$$) a6989586621679287772 :: TyFun [a] [a] -> Type) (a6989586621679287773 :: [a]) Source # | |
Defined in GHC.Base.Singletons | |
data (++@#@$) :: (~>) [a] ((~>) [a] [a]) infixr 5 Source #
Instances
| SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in GHC.Base.Singletons | |
| SuppressUnusedWarnings ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in GHC.Base.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679287772 :: [a]) Source # | |
Defined in GHC.Base.Singletons | |
data HeadSym0 :: (~>) [a] a Source #
Instances
| SingI (HeadSym0 :: TyFun [a] a -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (HeadSym0 :: TyFun [a] a -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679849189 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data LastSym0 :: (~>) [a] a Source #
Instances
| SingI (LastSym0 :: TyFun [a] a -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (LastSym0 :: TyFun [a] a -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679849183 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data TailSym0 :: (~>) [a] [a] Source #
Instances
| SingI (TailSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (TailSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679849179 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data InitSym0 :: (~>) [a] [a] Source #
Instances
| SingI (InitSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (InitSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679849167 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data NullSym0 :: (~>) (t a) Bool Source #
Instances
| SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (NullSym0 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680427279 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
data LengthSym0 :: (~>) (t a) Natural Source #
Instances
| SFoldable t => SingI (LengthSym0 :: TyFun (t a) Natural -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing LengthSym0 | |
| SuppressUnusedWarnings (LengthSym0 :: TyFun (t a) Natural -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621680427282 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621680427282 :: t a) = Length a6989586621680427282 | |
type family LengthSym1 (a6989586621680427282 :: t a) :: Natural where ... Source #
Equations
| LengthSym1 a6989586621680427282 = Length a6989586621680427282 |
data MapSym0 :: (~>) ((~>) a b) ((~>) [a] [b]) Source #
Instances
| SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # | |
Defined in GHC.Base.Singletons | |
| SuppressUnusedWarnings (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # | |
Defined in GHC.Base.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679287781 :: a ~> b) Source # | |
Defined in GHC.Base.Singletons | |
data MapSym1 (a6989586621679287781 :: (~>) a b) :: (~>) [a] [b] Source #
Instances
| SingI1 (MapSym1 :: (a ~> b) -> TyFun [a] [b] -> Type) Source # | |
Defined in GHC.Base.Singletons | |
| SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # | |
Defined in GHC.Base.Singletons | |
| SuppressUnusedWarnings (MapSym1 a6989586621679287781 :: TyFun [a] [b] -> Type) Source # | |
Defined in GHC.Base.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapSym1 a6989586621679287781 :: TyFun [a] [b] -> Type) (a6989586621679287782 :: [a]) Source # | |
Defined in GHC.Base.Singletons | |
type family MapSym2 (a6989586621679287781 :: (~>) a b) (a6989586621679287782 :: [a]) :: [b] where ... Source #
data ReverseSym0 :: (~>) [a] [a] Source #
Instances
| SingI (ReverseSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing ReverseSym0 | |
| SuppressUnusedWarnings (ReverseSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679849152 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679849152 :: [a]) = Reverse a6989586621679849152 | |
type family ReverseSym1 (a6989586621679849152 :: [a]) :: [a] where ... Source #
Equations
| ReverseSym1 a6989586621679849152 = Reverse a6989586621679849152 |
data IntersperseSym0 :: (~>) a ((~>) [a] [a]) Source #
Instances
| SingI (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679849145 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679849145 :: a) = IntersperseSym1 a6989586621679849145 | |
data IntersperseSym1 (a6989586621679849145 :: a) :: (~>) [a] [a] Source #
Instances
| SingI1 (IntersperseSym1 :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (IntersperseSym1 x) | |
| SingI d => SingI (IntersperseSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IntersperseSym1 d) | |
| SuppressUnusedWarnings (IntersperseSym1 a6989586621679849145 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersperseSym1 a6989586621679849145 :: TyFun [a] [a] -> Type) (a6989586621679849146 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersperseSym1 a6989586621679849145 :: TyFun [a] [a] -> Type) (a6989586621679849146 :: [a]) = Intersperse a6989586621679849145 a6989586621679849146 | |
type family IntersperseSym2 (a6989586621679849145 :: a) (a6989586621679849146 :: [a]) :: [a] where ... Source #
Equations
| IntersperseSym2 a6989586621679849145 a6989586621679849146 = Intersperse a6989586621679849145 a6989586621679849146 |
data IntercalateSym0 :: (~>) [a] ((~>) [[a]] [a]) Source #
Instances
| SingI (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679849138 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679849138 :: [a]) = IntercalateSym1 a6989586621679849138 | |
data IntercalateSym1 (a6989586621679849138 :: [a]) :: (~>) [[a]] [a] Source #
Instances
| SingI1 (IntercalateSym1 :: [a] -> TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (IntercalateSym1 x) | |
| SingI d => SingI (IntercalateSym1 d :: TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IntercalateSym1 d) | |
| SuppressUnusedWarnings (IntercalateSym1 a6989586621679849138 :: TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntercalateSym1 a6989586621679849138 :: TyFun [[a]] [a] -> Type) (a6989586621679849139 :: [[a]]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntercalateSym1 a6989586621679849138 :: TyFun [[a]] [a] -> Type) (a6989586621679849139 :: [[a]]) = Intercalate a6989586621679849138 a6989586621679849139 | |
type family IntercalateSym2 (a6989586621679849138 :: [a]) (a6989586621679849139 :: [[a]]) :: [a] where ... Source #
Equations
| IntercalateSym2 a6989586621679849138 a6989586621679849139 = Intercalate a6989586621679849138 a6989586621679849139 |
data TransposeSym0 :: (~>) [[a]] [[a]] Source #
Instances
| SingI (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679848039 :: [[a]]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679848039 :: [[a]]) = Transpose a6989586621679848039 | |
type family TransposeSym1 (a6989586621679848039 :: [[a]]) :: [[a]] where ... Source #
Equations
| TransposeSym1 a6989586621679848039 = Transpose a6989586621679848039 |
data SubsequencesSym0 :: (~>) [a] [[a]] Source #
Instances
| SingI (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679849133 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679849133 :: [a]) = Subsequences a6989586621679849133 | |
type family SubsequencesSym1 (a6989586621679849133 :: [a]) :: [[a]] where ... Source #
Equations
| SubsequencesSym1 a6989586621679849133 = Subsequences a6989586621679849133 |
data PermutationsSym0 :: (~>) [a] [[a]] Source #
Instances
| SingI (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679849059 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679849059 :: [a]) = Permutations a6989586621679849059 | |
type family PermutationsSym1 (a6989586621679849059 :: [a]) :: [[a]] where ... Source #
Equations
| PermutationsSym1 a6989586621679849059 = Permutations a6989586621679849059 |
data FoldlSym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) (t a) b)) Source #
Instances
| SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680427254 :: b ~> (a ~> b)) Source # | |
Defined in Data.Foldable.Singletons | |
data FoldlSym1 (a6989586621680427254 :: (~>) b ((~>) a b)) :: (~>) b ((~>) (t a) b) Source #
Instances
| SFoldable t => SingI1 (FoldlSym1 :: (b ~> (a ~> b)) -> TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| (SFoldable t, SingI d) => SingI (FoldlSym1 d :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (FoldlSym1 a6989586621680427254 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldlSym1 a6989586621680427254 :: TyFun b (t a ~> b) -> Type) (a6989586621680427255 :: b) Source # | |
Defined in Data.Foldable.Singletons | |
data FoldlSym2 (a6989586621680427254 :: (~>) b ((~>) a b)) (a6989586621680427255 :: b) :: (~>) (t a) b Source #
Instances
| (SFoldable t, SingI d) => SingI1 (FoldlSym2 d :: b -> TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SFoldable t => SingI2 (FoldlSym2 :: (b ~> (a ~> b)) -> b -> TyFun (t a) b -> Type) Source # | |
| (SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (FoldlSym2 a6989586621680427254 a6989586621680427255 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldlSym2 a6989586621680427254 a6989586621680427255 :: TyFun (t a) b -> Type) (a6989586621680427256 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family FoldlSym3 (a6989586621680427254 :: (~>) b ((~>) a b)) (a6989586621680427255 :: b) (a6989586621680427256 :: t a) :: b where ... Source #
data Foldl'Sym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) (t a) b)) Source #
Instances
| SFoldable t => SingI (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing Foldl'Sym0 | |
| SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680427261 :: b ~> (a ~> b)) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680427261 :: b ~> (a ~> b)) = Foldl'Sym1 a6989586621680427261 :: TyFun b (t a ~> b) -> Type | |
data Foldl'Sym1 (a6989586621680427261 :: (~>) b ((~>) a b)) :: (~>) b ((~>) (t a) b) Source #
Instances
| SFoldable t => SingI1 (Foldl'Sym1 :: (b ~> (a ~> b)) -> TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (Foldl'Sym1 x) | |
| (SFoldable t, SingI d) => SingI (Foldl'Sym1 d :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing (Foldl'Sym1 d) | |
| SuppressUnusedWarnings (Foldl'Sym1 a6989586621680427261 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl'Sym1 a6989586621680427261 :: TyFun b (t a ~> b) -> Type) (a6989586621680427262 :: b) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl'Sym1 a6989586621680427261 :: TyFun b (t a ~> b) -> Type) (a6989586621680427262 :: b) = Foldl'Sym2 a6989586621680427261 a6989586621680427262 :: TyFun (t a) b -> Type | |
data Foldl'Sym2 (a6989586621680427261 :: (~>) b ((~>) a b)) (a6989586621680427262 :: b) :: (~>) (t a) b Source #
Instances
| (SFoldable t, SingI d) => SingI1 (Foldl'Sym2 d :: b -> TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (Foldl'Sym2 d x) | |
| SFoldable t => SingI2 (Foldl'Sym2 :: (b ~> (a ~> b)) -> b -> TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (Foldl'Sym2 x y) | |
| (SFoldable t, SingI d1, SingI d2) => SingI (Foldl'Sym2 d1 d2 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing (Foldl'Sym2 d1 d2) | |
| SuppressUnusedWarnings (Foldl'Sym2 a6989586621680427261 a6989586621680427262 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl'Sym2 a6989586621680427261 a6989586621680427262 :: TyFun (t a) b -> Type) (a6989586621680427263 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl'Sym2 a6989586621680427261 a6989586621680427262 :: TyFun (t a) b -> Type) (a6989586621680427263 :: t a) = Foldl' a6989586621680427261 a6989586621680427262 a6989586621680427263 | |
type family Foldl'Sym3 (a6989586621680427261 :: (~>) b ((~>) a b)) (a6989586621680427262 :: b) (a6989586621680427263 :: t a) :: b where ... Source #
Equations
| Foldl'Sym3 a6989586621680427261 a6989586621680427262 a6989586621680427263 = Foldl' a6989586621680427261 a6989586621680427262 a6989586621680427263 |
data Foldl1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (t a) a) Source #
Instances
| SFoldable t => SingI (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing Foldl1Sym0 | |
| SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680427272 :: a ~> (a ~> a)) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680427272 :: a ~> (a ~> a)) = Foldl1Sym1 a6989586621680427272 :: TyFun (t a) a -> Type | |
data Foldl1Sym1 (a6989586621680427272 :: (~>) a ((~>) a a)) :: (~>) (t a) a Source #
Instances
| SFoldable t => SingI1 (Foldl1Sym1 :: (a ~> (a ~> a)) -> TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (Foldl1Sym1 x) | |
| (SFoldable t, SingI d) => SingI (Foldl1Sym1 d :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing (Foldl1Sym1 d) | |
| SuppressUnusedWarnings (Foldl1Sym1 a6989586621680427272 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl1Sym1 a6989586621680427272 :: TyFun (t a) a -> Type) (a6989586621680427273 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl1Sym1 a6989586621680427272 :: TyFun (t a) a -> Type) (a6989586621680427273 :: t a) = Foldl1 a6989586621680427272 a6989586621680427273 | |
type family Foldl1Sym2 (a6989586621680427272 :: (~>) a ((~>) a a)) (a6989586621680427273 :: t a) :: a where ... Source #
Equations
| Foldl1Sym2 a6989586621680427272 a6989586621680427273 = Foldl1 a6989586621680427272 a6989586621680427273 |
data Foldl1'Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) [a] a) Source #
Instances
| SingI (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing Foldl1'Sym0 | |
| SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679849024 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679849024 :: a ~> (a ~> a)) = Foldl1'Sym1 a6989586621679849024 | |
data Foldl1'Sym1 (a6989586621679849024 :: (~>) a ((~>) a a)) :: (~>) [a] a Source #
Instances
| SingI d => SingI (Foldl1'Sym1 d :: TyFun [a] a -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (Foldl1'Sym1 d) | |
| SuppressUnusedWarnings (Foldl1'Sym1 a6989586621679849024 :: TyFun [a] a -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (Foldl1'Sym1 :: (a ~> (a ~> a)) -> TyFun [a] a -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (Foldl1'Sym1 x) | |
| type Apply (Foldl1'Sym1 a6989586621679849024 :: TyFun [a] a -> Type) (a6989586621679849025 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Foldl1'Sym1 a6989586621679849024 :: TyFun [a] a -> Type) (a6989586621679849025 :: [a]) = Foldl1' a6989586621679849024 a6989586621679849025 | |
type family Foldl1'Sym2 (a6989586621679849024 :: (~>) a ((~>) a a)) (a6989586621679849025 :: [a]) :: a where ... Source #
Equations
| Foldl1'Sym2 a6989586621679849024 a6989586621679849025 = Foldl1' a6989586621679849024 a6989586621679849025 |
data FoldrSym0 :: (~>) ((~>) a ((~>) b b)) ((~>) b ((~>) (t a) b)) Source #
Instances
| SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680427240 :: a ~> (b ~> b)) Source # | |
Defined in Data.Foldable.Singletons | |
data FoldrSym1 (a6989586621680427240 :: (~>) a ((~>) b b)) :: (~>) b ((~>) (t a) b) Source #
Instances
| SFoldable t => SingI1 (FoldrSym1 :: (a ~> (b ~> b)) -> TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| (SFoldable t, SingI d) => SingI (FoldrSym1 d :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (FoldrSym1 a6989586621680427240 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldrSym1 a6989586621680427240 :: TyFun b (t a ~> b) -> Type) (a6989586621680427241 :: b) Source # | |
Defined in Data.Foldable.Singletons | |
data FoldrSym2 (a6989586621680427240 :: (~>) a ((~>) b b)) (a6989586621680427241 :: b) :: (~>) (t a) b Source #
Instances
| (SFoldable t, SingI d) => SingI1 (FoldrSym2 d :: b -> TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SFoldable t => SingI2 (FoldrSym2 :: (a ~> (b ~> b)) -> b -> TyFun (t a) b -> Type) Source # | |
| (SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (FoldrSym2 a6989586621680427240 a6989586621680427241 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldrSym2 a6989586621680427240 a6989586621680427241 :: TyFun (t a) b -> Type) (a6989586621680427242 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family FoldrSym3 (a6989586621680427240 :: (~>) a ((~>) b b)) (a6989586621680427241 :: b) (a6989586621680427242 :: t a) :: b where ... Source #
data Foldr1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (t a) a) Source #
Instances
| SFoldable t => SingI (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing Foldr1Sym0 | |
| SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680427267 :: a ~> (a ~> a)) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680427267 :: a ~> (a ~> a)) = Foldr1Sym1 a6989586621680427267 :: TyFun (t a) a -> Type | |
data Foldr1Sym1 (a6989586621680427267 :: (~>) a ((~>) a a)) :: (~>) (t a) a Source #
Instances
| SFoldable t => SingI1 (Foldr1Sym1 :: (a ~> (a ~> a)) -> TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (Foldr1Sym1 x) | |
| (SFoldable t, SingI d) => SingI (Foldr1Sym1 d :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing (Foldr1Sym1 d) | |
| SuppressUnusedWarnings (Foldr1Sym1 a6989586621680427267 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldr1Sym1 a6989586621680427267 :: TyFun (t a) a -> Type) (a6989586621680427268 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldr1Sym1 a6989586621680427267 :: TyFun (t a) a -> Type) (a6989586621680427268 :: t a) = Foldr1 a6989586621680427267 a6989586621680427268 | |
type family Foldr1Sym2 (a6989586621680427267 :: (~>) a ((~>) a a)) (a6989586621680427268 :: t a) :: a where ... Source #
Equations
| Foldr1Sym2 a6989586621680427267 a6989586621680427268 = Foldr1 a6989586621680427267 a6989586621680427268 |
data ConcatSym0 :: (~>) (t [a]) [a] Source #
Instances
| SFoldable t => SingI (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing ConcatSym0 | |
| SuppressUnusedWarnings (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680427121 :: t [a]) Source # | |
Defined in Data.Foldable.Singletons type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680427121 :: t [a]) = Concat a6989586621680427121 | |
type family ConcatSym1 (a6989586621680427121 :: t [a]) :: [a] where ... Source #
Equations
| ConcatSym1 a6989586621680427121 = Concat a6989586621680427121 |
data ConcatMapSym0 :: (~>) ((~>) a [b]) ((~>) (t a) [b]) Source #
Instances
| SFoldable t => SingI (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods | |
| SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680427110 :: a ~> [b]) Source # | |
Defined in Data.Foldable.Singletons type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680427110 :: a ~> [b]) = ConcatMapSym1 a6989586621680427110 :: TyFun (t a) [b] -> Type | |
data ConcatMapSym1 (a6989586621680427110 :: (~>) a [b]) :: (~>) (t a) [b] Source #
Instances
| SFoldable t => SingI1 (ConcatMapSym1 :: (a ~> [b]) -> TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (ConcatMapSym1 x) | |
| (SFoldable t, SingI d) => SingI (ConcatMapSym1 d :: TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing (ConcatMapSym1 d) | |
| SuppressUnusedWarnings (ConcatMapSym1 a6989586621680427110 :: TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ConcatMapSym1 a6989586621680427110 :: TyFun (t a) [b] -> Type) (a6989586621680427111 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (ConcatMapSym1 a6989586621680427110 :: TyFun (t a) [b] -> Type) (a6989586621680427111 :: t a) = ConcatMap a6989586621680427110 a6989586621680427111 | |
type family ConcatMapSym2 (a6989586621680427110 :: (~>) a [b]) (a6989586621680427111 :: t a) :: [b] where ... Source #
Equations
| ConcatMapSym2 a6989586621680427110 a6989586621680427111 = ConcatMap a6989586621680427110 a6989586621680427111 |
data AndSym0 :: (~>) (t Bool) Bool Source #
Instances
| SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680427105 :: t Bool) Source # | |
data OrSym0 :: (~>) (t Bool) Bool Source #
Instances
| SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680427099 :: t Bool) Source # | |
data AnySym0 :: (~>) ((~>) a Bool) ((~>) (t a) Bool) Source #
Instances
| SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680427091 :: a ~> Bool) Source # | |
data AnySym1 (a6989586621680427091 :: (~>) a Bool) :: (~>) (t a) Bool Source #
Instances
| SFoldable t => SingI1 (AnySym1 :: (a ~> Bool) -> TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| (SFoldable t, SingI d) => SingI (AnySym1 d :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (AnySym1 a6989586621680427091 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (AnySym1 a6989586621680427091 :: TyFun (t a) Bool -> Type) (a6989586621680427092 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family AnySym2 (a6989586621680427091 :: (~>) a Bool) (a6989586621680427092 :: t a) :: Bool where ... Source #
data AllSym0 :: (~>) ((~>) a Bool) ((~>) (t a) Bool) Source #
Instances
| SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680427082 :: a ~> Bool) Source # | |
data AllSym1 (a6989586621680427082 :: (~>) a Bool) :: (~>) (t a) Bool Source #
Instances
| SFoldable t => SingI1 (AllSym1 :: (a ~> Bool) -> TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| (SFoldable t, SingI d) => SingI (AllSym1 d :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (AllSym1 a6989586621680427082 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (AllSym1 a6989586621680427082 :: TyFun (t a) Bool -> Type) (a6989586621680427083 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family AllSym2 (a6989586621680427082 :: (~>) a Bool) (a6989586621680427083 :: t a) :: Bool where ... Source #
data SumSym0 :: (~>) (t a) a Source #
Instances
| (SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (SumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (SumSym0 :: TyFun (t a) a -> Type) (a6989586621680427296 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
data ProductSym0 :: (~>) (t a) a Source #
Instances
| (SFoldable t, SNum a) => SingI (ProductSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing ProductSym0 | |
| SuppressUnusedWarnings (ProductSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680427299 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680427299 :: t a) = Product a6989586621680427299 | |
type family ProductSym1 (a6989586621680427299 :: t a) :: a where ... Source #
Equations
| ProductSym1 a6989586621680427299 = Product a6989586621680427299 |
data MaximumSym0 :: (~>) (t a) a Source #
Instances
| (SFoldable t, SOrd a) => SingI (MaximumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing MaximumSym0 | |
| SuppressUnusedWarnings (MaximumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680427290 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680427290 :: t a) = Maximum a6989586621680427290 | |
type family MaximumSym1 (a6989586621680427290 :: t a) :: a where ... Source #
Equations
| MaximumSym1 a6989586621680427290 = Maximum a6989586621680427290 |
data MinimumSym0 :: (~>) (t a) a Source #
Instances
| (SFoldable t, SOrd a) => SingI (MinimumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing MinimumSym0 | |
| SuppressUnusedWarnings (MinimumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680427293 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680427293 :: t a) = Minimum a6989586621680427293 | |
type family MinimumSym1 (a6989586621680427293 :: t a) :: a where ... Source #
Equations
| MinimumSym1 a6989586621680427293 = Minimum a6989586621680427293 |
data ScanlSym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) [a] [b])) Source #
Instances
| SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679848957 :: b ~> (a ~> b)) Source # | |
Defined in Data.List.Singletons.Internal | |
data ScanlSym1 (a6989586621679848957 :: (~>) b ((~>) a b)) :: (~>) b ((~>) [a] [b]) Source #
Instances
| SingI1 (ScanlSym1 :: (b ~> (a ~> b)) -> TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ScanlSym1 a6989586621679848957 :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym1 a6989586621679848957 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679848958 :: b) Source # | |
Defined in Data.List.Singletons.Internal | |
data ScanlSym2 (a6989586621679848957 :: (~>) b ((~>) a b)) (a6989586621679848958 :: b) :: (~>) [a] [b] Source #
Instances
| SingI d => SingI1 (ScanlSym2 d :: b -> TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI2 (ScanlSym2 :: (b ~> (a ~> b)) -> b -> TyFun [a] [b] -> Type) Source # | |
| (SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ScanlSym2 a6989586621679848957 a6989586621679848958 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym2 a6989586621679848957 a6989586621679848958 :: TyFun [a] [b] -> Type) (a6989586621679848959 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family ScanlSym3 (a6989586621679848957 :: (~>) b ((~>) a b)) (a6989586621679848958 :: b) (a6989586621679848959 :: [a]) :: [b] where ... Source #
data Scanl1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) [a] [a]) Source #
Instances
| SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing Scanl1Sym0 | |
| SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679848948 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679848948 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621679848948 | |
data Scanl1Sym1 (a6989586621679848948 :: (~>) a ((~>) a a)) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI (Scanl1Sym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (Scanl1Sym1 d) | |
| SuppressUnusedWarnings (Scanl1Sym1 a6989586621679848948 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (Scanl1Sym1 :: (a ~> (a ~> a)) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (Scanl1Sym1 x) | |
| type Apply (Scanl1Sym1 a6989586621679848948 :: TyFun [a] [a] -> Type) (a6989586621679848949 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanl1Sym1 a6989586621679848948 :: TyFun [a] [a] -> Type) (a6989586621679848949 :: [a]) = Scanl1 a6989586621679848948 a6989586621679848949 | |
type family Scanl1Sym2 (a6989586621679848948 :: (~>) a ((~>) a a)) (a6989586621679848949 :: [a]) :: [a] where ... Source #
Equations
| Scanl1Sym2 a6989586621679848948 a6989586621679848949 = Scanl1 a6989586621679848948 a6989586621679848949 |
data ScanrSym0 :: (~>) ((~>) a ((~>) b b)) ((~>) b ((~>) [a] [b])) Source #
Instances
| SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679848930 :: a ~> (b ~> b)) Source # | |
Defined in Data.List.Singletons.Internal | |
data ScanrSym1 (a6989586621679848930 :: (~>) a ((~>) b b)) :: (~>) b ((~>) [a] [b]) Source #
Instances
| SingI1 (ScanrSym1 :: (a ~> (b ~> b)) -> TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ScanrSym1 a6989586621679848930 :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym1 a6989586621679848930 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679848931 :: b) Source # | |
Defined in Data.List.Singletons.Internal | |
data ScanrSym2 (a6989586621679848930 :: (~>) a ((~>) b b)) (a6989586621679848931 :: b) :: (~>) [a] [b] Source #
Instances
| SingI d => SingI1 (ScanrSym2 d :: b -> TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI2 (ScanrSym2 :: (a ~> (b ~> b)) -> b -> TyFun [a] [b] -> Type) Source # | |
| (SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ScanrSym2 a6989586621679848930 a6989586621679848931 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym2 a6989586621679848930 a6989586621679848931 :: TyFun [a] [b] -> Type) (a6989586621679848932 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family ScanrSym3 (a6989586621679848930 :: (~>) a ((~>) b b)) (a6989586621679848931 :: b) (a6989586621679848932 :: [a]) :: [b] where ... Source #
data Scanr1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) [a] [a]) Source #
Instances
| SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing Scanr1Sym0 | |
| SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679848910 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679848910 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621679848910 | |
data Scanr1Sym1 (a6989586621679848910 :: (~>) a ((~>) a a)) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI (Scanr1Sym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (Scanr1Sym1 d) | |
| SuppressUnusedWarnings (Scanr1Sym1 a6989586621679848910 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (Scanr1Sym1 :: (a ~> (a ~> a)) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (Scanr1Sym1 x) | |
| type Apply (Scanr1Sym1 a6989586621679848910 :: TyFun [a] [a] -> Type) (a6989586621679848911 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanr1Sym1 a6989586621679848910 :: TyFun [a] [a] -> Type) (a6989586621679848911 :: [a]) = Scanr1 a6989586621679848910 a6989586621679848911 | |
type family Scanr1Sym2 (a6989586621679848910 :: (~>) a ((~>) a a)) (a6989586621679848911 :: [a]) :: [a] where ... Source #
Equations
| Scanr1Sym2 a6989586621679848910 a6989586621679848911 = Scanr1 a6989586621679848910 a6989586621679848911 |
data MapAccumLSym0 :: (~>) ((~>) a ((~>) b (a, c))) ((~>) a ((~>) (t b) (a, t c))) Source #
Instances
| STraversable t => SingI (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods | |
| SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680784594 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680784594 :: a ~> (b ~> (a, c))) = MapAccumLSym1 a6989586621680784594 :: TyFun a (t b ~> (a, t c)) -> Type | |
data MapAccumLSym1 (a6989586621680784594 :: (~>) a ((~>) b (a, c))) :: (~>) a ((~>) (t b) (a, t c)) Source #
Instances
| STraversable t => SingI1 (MapAccumLSym1 :: (a ~> (b ~> (a, c))) -> TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (MapAccumLSym1 x) | |
| (STraversable t, SingI d) => SingI (MapAccumLSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods sing :: Sing (MapAccumLSym1 d) | |
| SuppressUnusedWarnings (MapAccumLSym1 a6989586621680784594 :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumLSym1 a6989586621680784594 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680784595 :: a) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumLSym1 a6989586621680784594 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680784595 :: a) = MapAccumLSym2 a6989586621680784594 a6989586621680784595 :: TyFun (t b) (a, t c) -> Type | |
data MapAccumLSym2 (a6989586621680784594 :: (~>) a ((~>) b (a, c))) (a6989586621680784595 :: a) :: (~>) (t b) (a, t c) Source #
Instances
| (STraversable t, SingI d) => SingI1 (MapAccumLSym2 d :: a -> TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (MapAccumLSym2 d x) | |
| STraversable t => SingI2 (MapAccumLSym2 :: (a ~> (b ~> (a, c))) -> a -> TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (MapAccumLSym2 x y) | |
| (STraversable t, SingI d1, SingI d2) => SingI (MapAccumLSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods sing :: Sing (MapAccumLSym2 d1 d2) | |
| SuppressUnusedWarnings (MapAccumLSym2 a6989586621680784594 a6989586621680784595 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumLSym2 a6989586621680784594 a6989586621680784595 :: TyFun (t b) (a, t c) -> Type) (a6989586621680784596 :: t b) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumLSym2 a6989586621680784594 a6989586621680784595 :: TyFun (t b) (a, t c) -> Type) (a6989586621680784596 :: t b) = MapAccumL a6989586621680784594 a6989586621680784595 a6989586621680784596 | |
type family MapAccumLSym3 (a6989586621680784594 :: (~>) a ((~>) b (a, c))) (a6989586621680784595 :: a) (a6989586621680784596 :: t b) :: (a, t c) where ... Source #
Equations
| MapAccumLSym3 a6989586621680784594 a6989586621680784595 a6989586621680784596 = MapAccumL a6989586621680784594 a6989586621680784595 a6989586621680784596 |
data MapAccumRSym0 :: (~>) ((~>) a ((~>) b (a, c))) ((~>) a ((~>) (t b) (a, t c))) Source #
Instances
| STraversable t => SingI (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods | |
| SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680784584 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680784584 :: a ~> (b ~> (a, c))) = MapAccumRSym1 a6989586621680784584 :: TyFun a (t b ~> (a, t c)) -> Type | |
data MapAccumRSym1 (a6989586621680784584 :: (~>) a ((~>) b (a, c))) :: (~>) a ((~>) (t b) (a, t c)) Source #
Instances
| STraversable t => SingI1 (MapAccumRSym1 :: (a ~> (b ~> (a, c))) -> TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (MapAccumRSym1 x) | |
| (STraversable t, SingI d) => SingI (MapAccumRSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods sing :: Sing (MapAccumRSym1 d) | |
| SuppressUnusedWarnings (MapAccumRSym1 a6989586621680784584 :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumRSym1 a6989586621680784584 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680784585 :: a) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumRSym1 a6989586621680784584 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680784585 :: a) = MapAccumRSym2 a6989586621680784584 a6989586621680784585 :: TyFun (t b) (a, t c) -> Type | |
data MapAccumRSym2 (a6989586621680784584 :: (~>) a ((~>) b (a, c))) (a6989586621680784585 :: a) :: (~>) (t b) (a, t c) Source #
Instances
| (STraversable t, SingI d) => SingI1 (MapAccumRSym2 d :: a -> TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (MapAccumRSym2 d x) | |
| STraversable t => SingI2 (MapAccumRSym2 :: (a ~> (b ~> (a, c))) -> a -> TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (MapAccumRSym2 x y) | |
| (STraversable t, SingI d1, SingI d2) => SingI (MapAccumRSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods sing :: Sing (MapAccumRSym2 d1 d2) | |
| SuppressUnusedWarnings (MapAccumRSym2 a6989586621680784584 a6989586621680784585 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumRSym2 a6989586621680784584 a6989586621680784585 :: TyFun (t b) (a, t c) -> Type) (a6989586621680784586 :: t b) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumRSym2 a6989586621680784584 a6989586621680784585 :: TyFun (t b) (a, t c) -> Type) (a6989586621680784586 :: t b) = MapAccumR a6989586621680784584 a6989586621680784585 a6989586621680784586 | |
type family MapAccumRSym3 (a6989586621680784584 :: (~>) a ((~>) b (a, c))) (a6989586621680784585 :: a) (a6989586621680784586 :: t b) :: (a, t c) where ... Source #
Equations
| MapAccumRSym3 a6989586621680784584 a6989586621680784585 a6989586621680784586 = MapAccumR a6989586621680784584 a6989586621680784585 a6989586621680784586 |
data ReplicateSym0 :: (~>) Natural ((~>) a [a]) Source #
Instances
| SingI (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679848047 :: Natural) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679848047 :: Natural) = ReplicateSym1 a6989586621679848047 :: TyFun a [a] -> Type | |
data ReplicateSym1 (a6989586621679848047 :: Natural) :: (~>) a [a] Source #
Instances
| SingI1 (ReplicateSym1 :: Natural -> TyFun a [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (ReplicateSym1 x) | |
| SingI d => SingI (ReplicateSym1 d :: TyFun a [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ReplicateSym1 d) | |
| SuppressUnusedWarnings (ReplicateSym1 a6989586621679848047 :: TyFun a [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ReplicateSym1 a6989586621679848047 :: TyFun a [a] -> Type) (a6989586621679848048 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ReplicateSym1 a6989586621679848047 :: TyFun a [a] -> Type) (a6989586621679848048 :: a) = Replicate a6989586621679848047 a6989586621679848048 | |
type family ReplicateSym2 (a6989586621679848047 :: Natural) (a6989586621679848048 :: a) :: [a] where ... Source #
Equations
| ReplicateSym2 a6989586621679848047 a6989586621679848048 = Replicate a6989586621679848047 a6989586621679848048 |
data UnfoldrSym0 :: (~>) ((~>) b (Maybe (a, b))) ((~>) b [a]) Source #
Instances
| SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing UnfoldrSym0 | |
| SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679848802 :: b ~> Maybe (a, b)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679848802 :: b ~> Maybe (a, b)) = UnfoldrSym1 a6989586621679848802 | |
data UnfoldrSym1 (a6989586621679848802 :: (~>) b (Maybe (a, b))) :: (~>) b [a] Source #
Instances
| SingI1 (UnfoldrSym1 :: (b ~> Maybe (a, b)) -> TyFun b [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (UnfoldrSym1 x) | |
| SingI d => SingI (UnfoldrSym1 d :: TyFun b [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (UnfoldrSym1 d) | |
| SuppressUnusedWarnings (UnfoldrSym1 a6989586621679848802 :: TyFun b [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnfoldrSym1 a6989586621679848802 :: TyFun b [a] -> Type) (a6989586621679848803 :: b) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnfoldrSym1 a6989586621679848802 :: TyFun b [a] -> Type) (a6989586621679848803 :: b) = Unfoldr a6989586621679848802 a6989586621679848803 | |
type family UnfoldrSym2 (a6989586621679848802 :: (~>) b (Maybe (a, b))) (a6989586621679848803 :: b) :: [a] where ... Source #
Equations
| UnfoldrSym2 a6989586621679848802 a6989586621679848803 = Unfoldr a6989586621679848802 a6989586621679848803 |
data TakeSym0 :: (~>) Natural ((~>) [a] [a]) Source #
Instances
| SingI (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679848202 :: Natural) Source # | |
data TakeSym1 (a6989586621679848202 :: Natural) :: (~>) [a] [a] Source #
Instances
| SingI1 (TakeSym1 :: Natural -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI d => SingI (TakeSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (TakeSym1 a6989586621679848202 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeSym1 a6989586621679848202 :: TyFun [a] [a] -> Type) (a6989586621679848203 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family TakeSym2 (a6989586621679848202 :: Natural) (a6989586621679848203 :: [a]) :: [a] where ... Source #
data DropSym0 :: (~>) Natural ((~>) [a] [a]) Source #
Instances
| SingI (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679848189 :: Natural) Source # | |
data DropSym1 (a6989586621679848189 :: Natural) :: (~>) [a] [a] Source #
Instances
| SingI1 (DropSym1 :: Natural -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI d => SingI (DropSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (DropSym1 a6989586621679848189 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DropSym1 a6989586621679848189 :: TyFun [a] [a] -> Type) (a6989586621679848190 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family DropSym2 (a6989586621679848189 :: Natural) (a6989586621679848190 :: [a]) :: [a] where ... Source #
data SplitAtSym0 :: (~>) Natural ((~>) [a] ([a], [a])) Source #
Instances
| SingI (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing SplitAtSym0 | |
| SuppressUnusedWarnings (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679848182 :: Natural) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679848182 :: Natural) = SplitAtSym1 a6989586621679848182 :: TyFun [a] ([a], [a]) -> Type | |
data SplitAtSym1 (a6989586621679848182 :: Natural) :: (~>) [a] ([a], [a]) Source #
Instances
| SingI1 (SplitAtSym1 :: Natural -> TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (SplitAtSym1 x) | |
| SingI d => SingI (SplitAtSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (SplitAtSym1 d) | |
| SuppressUnusedWarnings (SplitAtSym1 a6989586621679848182 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (SplitAtSym1 a6989586621679848182 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679848183 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SplitAtSym1 a6989586621679848182 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679848183 :: [a]) = SplitAt a6989586621679848182 a6989586621679848183 | |
type family SplitAtSym2 (a6989586621679848182 :: Natural) (a6989586621679848183 :: [a]) :: ([a], [a]) where ... Source #
Equations
| SplitAtSym2 a6989586621679848182 a6989586621679848183 = SplitAt a6989586621679848182 a6989586621679848183 |
data TakeWhileSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a]) Source #
Instances
| SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679848319 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679848319 :: a ~> Bool) = TakeWhileSym1 a6989586621679848319 | |
data TakeWhileSym1 (a6989586621679848319 :: (~>) a Bool) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI (TakeWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (TakeWhileSym1 d) | |
| SuppressUnusedWarnings (TakeWhileSym1 a6989586621679848319 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (TakeWhileSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (TakeWhileSym1 x) | |
| type Apply (TakeWhileSym1 a6989586621679848319 :: TyFun [a] [a] -> Type) (a6989586621679848320 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (TakeWhileSym1 a6989586621679848319 :: TyFun [a] [a] -> Type) (a6989586621679848320 :: [a]) = TakeWhile a6989586621679848319 a6989586621679848320 | |
type family TakeWhileSym2 (a6989586621679848319 :: (~>) a Bool) (a6989586621679848320 :: [a]) :: [a] where ... Source #
Equations
| TakeWhileSym2 a6989586621679848319 a6989586621679848320 = TakeWhile a6989586621679848319 a6989586621679848320 |
data DropWhileSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a]) Source #
Instances
| SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679848304 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679848304 :: a ~> Bool) = DropWhileSym1 a6989586621679848304 | |
data DropWhileSym1 (a6989586621679848304 :: (~>) a Bool) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI (DropWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DropWhileSym1 d) | |
| SuppressUnusedWarnings (DropWhileSym1 a6989586621679848304 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (DropWhileSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (DropWhileSym1 x) | |
| type Apply (DropWhileSym1 a6989586621679848304 :: TyFun [a] [a] -> Type) (a6989586621679848305 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileSym1 a6989586621679848304 :: TyFun [a] [a] -> Type) (a6989586621679848305 :: [a]) = DropWhile a6989586621679848304 a6989586621679848305 | |
type family DropWhileSym2 (a6989586621679848304 :: (~>) a Bool) (a6989586621679848305 :: [a]) :: [a] where ... Source #
Equations
| DropWhileSym2 a6989586621679848304 a6989586621679848305 = DropWhile a6989586621679848304 a6989586621679848305 |
data DropWhileEndSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a]) Source #
Instances
| SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679848287 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679848287 :: a ~> Bool) = DropWhileEndSym1 a6989586621679848287 | |
data DropWhileEndSym1 (a6989586621679848287 :: (~>) a Bool) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI (DropWhileEndSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DropWhileEndSym1 d) | |
| SuppressUnusedWarnings (DropWhileEndSym1 a6989586621679848287 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (DropWhileEndSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (DropWhileEndSym1 x) | |
| type Apply (DropWhileEndSym1 a6989586621679848287 :: TyFun [a] [a] -> Type) (a6989586621679848288 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileEndSym1 a6989586621679848287 :: TyFun [a] [a] -> Type) (a6989586621679848288 :: [a]) = DropWhileEnd a6989586621679848287 a6989586621679848288 | |
type family DropWhileEndSym2 (a6989586621679848287 :: (~>) a Bool) (a6989586621679848288 :: [a]) :: [a] where ... Source #
Equations
| DropWhileEndSym2 a6989586621679848287 a6989586621679848288 = DropWhileEnd a6989586621679848287 a6989586621679848288 |
data SpanSym0 :: (~>) ((~>) a Bool) ((~>) [a] ([a], [a])) Source #
Instances
| SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679848250 :: a ~> Bool) Source # | |
data SpanSym1 (a6989586621679848250 :: (~>) a Bool) :: (~>) [a] ([a], [a]) Source #
Instances
| SingI d => SingI (SpanSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (SpanSym1 a6989586621679848250 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (SpanSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (SpanSym1 a6989586621679848250 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679848251 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family SpanSym2 (a6989586621679848250 :: (~>) a Bool) (a6989586621679848251 :: [a]) :: ([a], [a]) where ... Source #
data BreakSym0 :: (~>) ((~>) a Bool) ((~>) [a] ([a], [a])) Source #
Instances
| SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679848215 :: a ~> Bool) Source # | |
data BreakSym1 (a6989586621679848215 :: (~>) a Bool) :: (~>) [a] ([a], [a]) Source #
Instances
| SingI d => SingI (BreakSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (BreakSym1 a6989586621679848215 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (BreakSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (BreakSym1 a6989586621679848215 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679848216 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family BreakSym2 (a6989586621679848215 :: (~>) a Bool) (a6989586621679848216 :: [a]) :: ([a], [a]) where ... Source #
data StripPrefixSym0 :: (~>) [a] ((~>) [a] (Maybe [a])) Source #
Instances
| SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679997490 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679997490 :: [a]) = StripPrefixSym1 a6989586621679997490 | |
data StripPrefixSym1 (a6989586621679997490 :: [a]) :: (~>) [a] (Maybe [a]) Source #
Instances
| SuppressUnusedWarnings (StripPrefixSym1 a6989586621679997490 :: TyFun [a] (Maybe [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (StripPrefixSym1 a6989586621679997490 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679997491 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (StripPrefixSym1 a6989586621679997490 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679997491 :: [a]) = StripPrefix a6989586621679997490 a6989586621679997491 | |
type family StripPrefixSym2 (a6989586621679997490 :: [a]) (a6989586621679997491 :: [a]) :: Maybe [a] where ... Source #
Equations
| StripPrefixSym2 a6989586621679997490 a6989586621679997491 = StripPrefix a6989586621679997490 a6989586621679997491 |
data GroupSym0 :: (~>) [a] [[a]] Source #
Instances
| SEq a => SingI (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679848177 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data InitsSym0 :: (~>) [a] [[a]] Source #
Instances
| SingI (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679848792 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data TailsSym0 :: (~>) [a] [[a]] Source #
Instances
| SingI (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679848784 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data IsPrefixOfSym0 :: (~>) [a] ((~>) [a] Bool) Source #
Instances
| SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679848776 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679848776 :: [a]) = IsPrefixOfSym1 a6989586621679848776 | |
data IsPrefixOfSym1 (a6989586621679848776 :: [a]) :: (~>) [a] Bool Source #
Instances
| SEq a => SingI1 (IsPrefixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (IsPrefixOfSym1 x) | |
| (SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IsPrefixOfSym1 d) | |
| SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679848776 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsPrefixOfSym1 a6989586621679848776 :: TyFun [a] Bool -> Type) (a6989586621679848777 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsPrefixOfSym1 a6989586621679848776 :: TyFun [a] Bool -> Type) (a6989586621679848777 :: [a]) = IsPrefixOf a6989586621679848776 a6989586621679848777 | |
type family IsPrefixOfSym2 (a6989586621679848776 :: [a]) (a6989586621679848777 :: [a]) :: Bool where ... Source #
Equations
| IsPrefixOfSym2 a6989586621679848776 a6989586621679848777 = IsPrefixOf a6989586621679848776 a6989586621679848777 |
data IsSuffixOfSym0 :: (~>) [a] ((~>) [a] Bool) Source #
Instances
| SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679848769 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679848769 :: [a]) = IsSuffixOfSym1 a6989586621679848769 | |
data IsSuffixOfSym1 (a6989586621679848769 :: [a]) :: (~>) [a] Bool Source #
Instances
| SEq a => SingI1 (IsSuffixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (IsSuffixOfSym1 x) | |
| (SEq a, SingI d) => SingI (IsSuffixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IsSuffixOfSym1 d) | |
| SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679848769 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsSuffixOfSym1 a6989586621679848769 :: TyFun [a] Bool -> Type) (a6989586621679848770 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsSuffixOfSym1 a6989586621679848769 :: TyFun [a] Bool -> Type) (a6989586621679848770 :: [a]) = IsSuffixOf a6989586621679848769 a6989586621679848770 | |
type family IsSuffixOfSym2 (a6989586621679848769 :: [a]) (a6989586621679848770 :: [a]) :: Bool where ... Source #
Equations
| IsSuffixOfSym2 a6989586621679848769 a6989586621679848770 = IsSuffixOf a6989586621679848769 a6989586621679848770 |
data IsInfixOfSym0 :: (~>) [a] ((~>) [a] Bool) Source #
Instances
| SEq a => SingI (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679848762 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679848762 :: [a]) = IsInfixOfSym1 a6989586621679848762 | |
data IsInfixOfSym1 (a6989586621679848762 :: [a]) :: (~>) [a] Bool Source #
Instances
| SEq a => SingI1 (IsInfixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (IsInfixOfSym1 x) | |
| (SEq a, SingI d) => SingI (IsInfixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IsInfixOfSym1 d) | |
| SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679848762 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsInfixOfSym1 a6989586621679848762 :: TyFun [a] Bool -> Type) (a6989586621679848763 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsInfixOfSym1 a6989586621679848762 :: TyFun [a] Bool -> Type) (a6989586621679848763 :: [a]) = IsInfixOf a6989586621679848762 a6989586621679848763 | |
type family IsInfixOfSym2 (a6989586621679848762 :: [a]) (a6989586621679848763 :: [a]) :: Bool where ... Source #
Equations
| IsInfixOfSym2 a6989586621679848762 a6989586621679848763 = IsInfixOf a6989586621679848762 a6989586621679848763 |
data ElemSym0 :: (~>) a ((~>) (t a) Bool) Source #
Instances
| (SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680427286 :: a) Source # | |
data ElemSym1 (a6989586621680427286 :: a) :: (~>) (t a) Bool Source #
Instances
| (SFoldable t, SEq a) => SingI1 (ElemSym1 :: a -> TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| (SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (ElemSym1 a6989586621680427286 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemSym1 a6989586621680427286 :: TyFun (t a) Bool -> Type) (a6989586621680427287 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family ElemSym2 (a6989586621680427286 :: a) (a6989586621680427287 :: t a) :: Bool where ... Source #
data NotElemSym0 :: (~>) a ((~>) (t a) Bool) Source #
Instances
| (SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing NotElemSym0 | |
| SuppressUnusedWarnings (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680427033 :: a) Source # | |
Defined in Data.Foldable.Singletons type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680427033 :: a) = NotElemSym1 a6989586621680427033 :: TyFun (t a) Bool -> Type | |
data NotElemSym1 (a6989586621680427033 :: a) :: (~>) (t a) Bool Source #
Instances
| (SFoldable t, SEq a) => SingI1 (NotElemSym1 :: a -> TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (NotElemSym1 x) | |
| (SFoldable t, SEq a, SingI d) => SingI (NotElemSym1 d :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing (NotElemSym1 d) | |
| SuppressUnusedWarnings (NotElemSym1 a6989586621680427033 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (NotElemSym1 a6989586621680427033 :: TyFun (t a) Bool -> Type) (a6989586621680427034 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (NotElemSym1 a6989586621680427033 :: TyFun (t a) Bool -> Type) (a6989586621680427034 :: t a) = NotElem a6989586621680427033 a6989586621680427034 | |
type family NotElemSym2 (a6989586621680427033 :: a) (a6989586621680427034 :: t a) :: Bool where ... Source #
Equations
| NotElemSym2 a6989586621680427033 a6989586621680427034 = NotElem a6989586621680427033 a6989586621680427034 |
data LookupSym0 :: (~>) a ((~>) [(a, b)] (Maybe b)) Source #
Instances
| SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing LookupSym0 | |
| SuppressUnusedWarnings (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679848110 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679848110 :: a) = LookupSym1 a6989586621679848110 :: TyFun [(a, b)] (Maybe b) -> Type | |
data LookupSym1 (a6989586621679848110 :: a) :: (~>) [(a, b)] (Maybe b) Source #
Instances
| SEq a => SingI1 (LookupSym1 :: a -> TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (LookupSym1 x) | |
| (SEq a, SingI d) => SingI (LookupSym1 d :: TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (LookupSym1 d) | |
| SuppressUnusedWarnings (LookupSym1 a6989586621679848110 :: TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (LookupSym1 a6989586621679848110 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679848111 :: [(a, b)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (LookupSym1 a6989586621679848110 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679848111 :: [(a, b)]) = Lookup a6989586621679848110 a6989586621679848111 | |
type family LookupSym2 (a6989586621679848110 :: a) (a6989586621679848111 :: [(a, b)]) :: Maybe b where ... Source #
Equations
| LookupSym2 a6989586621679848110 a6989586621679848111 = Lookup a6989586621679848110 a6989586621679848111 |
data FindSym0 :: (~>) ((~>) a Bool) ((~>) (t a) (Maybe a)) Source #
Instances
| SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680427015 :: a ~> Bool) Source # | |
data FindSym1 (a6989586621680427015 :: (~>) a Bool) :: (~>) (t a) (Maybe a) Source #
Instances
| SFoldable t => SingI1 (FindSym1 :: (a ~> Bool) -> TyFun (t a) (Maybe a) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| (SFoldable t, SingI d) => SingI (FindSym1 d :: TyFun (t a) (Maybe a) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (FindSym1 a6989586621680427015 :: TyFun (t a) (Maybe a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FindSym1 a6989586621680427015 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680427016 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family FindSym2 (a6989586621680427015 :: (~>) a Bool) (a6989586621680427016 :: t a) :: Maybe a where ... Source #
data FilterSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a]) Source #
Instances
| SingI (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing FilterSym0 | |
| SuppressUnusedWarnings (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679848419 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679848419 :: a ~> Bool) = FilterSym1 a6989586621679848419 | |
data FilterSym1 (a6989586621679848419 :: (~>) a Bool) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI (FilterSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (FilterSym1 d) | |
| SuppressUnusedWarnings (FilterSym1 a6989586621679848419 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (FilterSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (FilterSym1 x) | |
| type Apply (FilterSym1 a6989586621679848419 :: TyFun [a] [a] -> Type) (a6989586621679848420 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FilterSym1 a6989586621679848419 :: TyFun [a] [a] -> Type) (a6989586621679848420 :: [a]) = Filter a6989586621679848419 a6989586621679848420 | |
type family FilterSym2 (a6989586621679848419 :: (~>) a Bool) (a6989586621679848420 :: [a]) :: [a] where ... Source #
Equations
| FilterSym2 a6989586621679848419 a6989586621679848420 = Filter a6989586621679848419 a6989586621679848420 |
data PartitionSym0 :: (~>) ((~>) a Bool) ((~>) [a] ([a], [a])) Source #
Instances
| SingI (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679848103 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679848103 :: a ~> Bool) = PartitionSym1 a6989586621679848103 | |
data PartitionSym1 (a6989586621679848103 :: (~>) a Bool) :: (~>) [a] ([a], [a]) Source #
Instances
| SingI d => SingI (PartitionSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (PartitionSym1 d) | |
| SuppressUnusedWarnings (PartitionSym1 a6989586621679848103 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (PartitionSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (PartitionSym1 x) | |
| type Apply (PartitionSym1 a6989586621679848103 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679848104 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (PartitionSym1 a6989586621679848103 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679848104 :: [a]) = Partition a6989586621679848103 a6989586621679848104 | |
type family PartitionSym2 (a6989586621679848103 :: (~>) a Bool) (a6989586621679848104 :: [a]) :: ([a], [a]) where ... Source #
Equations
| PartitionSym2 a6989586621679848103 a6989586621679848104 = Partition a6989586621679848103 a6989586621679848104 |
data (!!@#@$) :: (~>) [a] ((~>) Natural a) infixl 9 Source #
Instances
| SingI ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) (a6989586621679848027 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data (!!@#@$$) (a6989586621679848027 :: [a]) :: (~>) Natural a infixl 9 Source #
Instances
| SingI1 ((!!@#@$$) :: [a] -> TyFun Natural a -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI d => SingI ((!!@#@$$) d :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings ((!!@#@$$) a6989586621679848027 :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply ((!!@#@$$) a6989586621679848027 :: TyFun Natural a -> Type) (a6989586621679848028 :: Natural) Source # | |
type family (a6989586621679848027 :: [a]) !!@#@$$$ (a6989586621679848028 :: Natural) :: a where ... infixl 9 Source #
data ElemIndexSym0 :: (~>) a ((~>) [a] (Maybe Natural)) Source #
Instances
| SEq a => SingI (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) (a6989586621679848403 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) (a6989586621679848403 :: a) = ElemIndexSym1 a6989586621679848403 | |
data ElemIndexSym1 (a6989586621679848403 :: a) :: (~>) [a] (Maybe Natural) Source #
Instances
| SEq a => SingI1 (ElemIndexSym1 :: a -> TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (ElemIndexSym1 x) | |
| (SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ElemIndexSym1 d) | |
| SuppressUnusedWarnings (ElemIndexSym1 a6989586621679848403 :: TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemIndexSym1 a6989586621679848403 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679848404 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndexSym1 a6989586621679848403 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679848404 :: [a]) = ElemIndex a6989586621679848403 a6989586621679848404 | |
type family ElemIndexSym2 (a6989586621679848403 :: a) (a6989586621679848404 :: [a]) :: Maybe Natural where ... Source #
Equations
| ElemIndexSym2 a6989586621679848403 a6989586621679848404 = ElemIndex a6989586621679848403 a6989586621679848404 |
data ElemIndicesSym0 :: (~>) a ((~>) [a] [Natural]) Source #
Instances
| SEq a => SingI (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) (a6989586621679848394 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) (a6989586621679848394 :: a) = ElemIndicesSym1 a6989586621679848394 | |
data ElemIndicesSym1 (a6989586621679848394 :: a) :: (~>) [a] [Natural] Source #
Instances
| SEq a => SingI1 (ElemIndicesSym1 :: a -> TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (ElemIndicesSym1 x) | |
| (SEq a, SingI d) => SingI (ElemIndicesSym1 d :: TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ElemIndicesSym1 d) | |
| SuppressUnusedWarnings (ElemIndicesSym1 a6989586621679848394 :: TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemIndicesSym1 a6989586621679848394 :: TyFun [a] [Natural] -> Type) (a6989586621679848395 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndicesSym1 a6989586621679848394 :: TyFun [a] [Natural] -> Type) (a6989586621679848395 :: [a]) = ElemIndices a6989586621679848394 a6989586621679848395 | |
type family ElemIndicesSym2 (a6989586621679848394 :: a) (a6989586621679848395 :: [a]) :: [Natural] where ... Source #
Equations
| ElemIndicesSym2 a6989586621679848394 a6989586621679848395 = ElemIndices a6989586621679848394 a6989586621679848395 |
data FindIndexSym0 :: (~>) ((~>) a Bool) ((~>) [a] (Maybe Natural)) Source #
Instances
| SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679848385 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679848385 :: a ~> Bool) = FindIndexSym1 a6989586621679848385 | |
data FindIndexSym1 (a6989586621679848385 :: (~>) a Bool) :: (~>) [a] (Maybe Natural) Source #
Instances
| SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (FindIndexSym1 d) | |
| SuppressUnusedWarnings (FindIndexSym1 a6989586621679848385 :: TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (FindIndexSym1 :: (a ~> Bool) -> TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (FindIndexSym1 x) | |
| type Apply (FindIndexSym1 a6989586621679848385 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679848386 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FindIndexSym1 a6989586621679848385 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679848386 :: [a]) = FindIndex a6989586621679848385 a6989586621679848386 | |
type family FindIndexSym2 (a6989586621679848385 :: (~>) a Bool) (a6989586621679848386 :: [a]) :: Maybe Natural where ... Source #
Equations
| FindIndexSym2 a6989586621679848385 a6989586621679848386 = FindIndex a6989586621679848385 a6989586621679848386 |
data FindIndicesSym0 :: (~>) ((~>) a Bool) ((~>) [a] [Natural]) Source #
Instances
| SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679848362 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679848362 :: a ~> Bool) = FindIndicesSym1 a6989586621679848362 | |
data FindIndicesSym1 (a6989586621679848362 :: (~>) a Bool) :: (~>) [a] [Natural] Source #
Instances
| SingI d => SingI (FindIndicesSym1 d :: TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (FindIndicesSym1 d) | |
| SuppressUnusedWarnings (FindIndicesSym1 a6989586621679848362 :: TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (FindIndicesSym1 :: (a ~> Bool) -> TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (FindIndicesSym1 x) | |
| type Apply (FindIndicesSym1 a6989586621679848362 :: TyFun [a] [Natural] -> Type) (a6989586621679848363 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FindIndicesSym1 a6989586621679848362 :: TyFun [a] [Natural] -> Type) (a6989586621679848363 :: [a]) = FindIndices a6989586621679848362 a6989586621679848363 | |
type family FindIndicesSym2 (a6989586621679848362 :: (~>) a Bool) (a6989586621679848363 :: [a]) :: [Natural] where ... Source #
Equations
| FindIndicesSym2 a6989586621679848362 a6989586621679848363 = FindIndices a6989586621679848362 a6989586621679848363 |
data ZipSym0 :: (~>) [a] ((~>) [b] [(a, b)]) Source #
Instances
| SingI (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679848737 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data ZipSym1 (a6989586621679848737 :: [a]) :: (~>) [b] [(a, b)] Source #
Instances
| SingI1 (ZipSym1 :: [a] -> TyFun [b] [(a, b)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI d => SingI (ZipSym1 d :: TyFun [b] [(a, b)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ZipSym1 a6989586621679848737 :: TyFun [b] [(a, b)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipSym1 a6989586621679848737 :: TyFun [b] [(a, b)] -> Type) (a6989586621679848738 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family ZipSym2 (a6989586621679848737 :: [a]) (a6989586621679848738 :: [b]) :: [(a, b)] where ... Source #
data Zip3Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] [(a, b, c)])) Source #
Instances
| SingI (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679848725 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip3Sym1 (a6989586621679848725 :: [a]) :: (~>) [b] ((~>) [c] [(a, b, c)]) Source #
Instances
| SingI1 (Zip3Sym1 :: [a] -> TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI d => SingI (Zip3Sym1 d :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Zip3Sym1 a6989586621679848725 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip3Sym1 a6989586621679848725 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679848726 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip3Sym2 (a6989586621679848725 :: [a]) (a6989586621679848726 :: [b]) :: (~>) [c] [(a, b, c)] Source #
Instances
| SingI2 (Zip3Sym2 :: [a] -> [b] -> TyFun [c] [(a, b, c)] -> Type) Source # | |
| SingI d => SingI1 (Zip3Sym2 d :: [b] -> TyFun [c] [(a, b, c)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 :: TyFun [c] [(a, b, c)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Zip3Sym2 a6989586621679848725 a6989586621679848726 :: TyFun [c] [(a, b, c)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip3Sym2 a6989586621679848725 a6989586621679848726 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679848727 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family Zip3Sym3 (a6989586621679848725 :: [a]) (a6989586621679848726 :: [b]) (a6989586621679848727 :: [c]) :: [(a, b, c)] where ... Source #
data Zip4Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] [(a, b, c, d)]))) Source #
Instances
| SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621679997479 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip4Sym1 (a6989586621679997479 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] [(a, b, c, d)])) Source #
Instances
| SuppressUnusedWarnings (Zip4Sym1 a6989586621679997479 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip4Sym1 a6989586621679997479 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621679997480 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip4Sym2 (a6989586621679997479 :: [a]) (a6989586621679997480 :: [b]) :: (~>) [c] ((~>) [d] [(a, b, c, d)]) Source #
Instances
| SuppressUnusedWarnings (Zip4Sym2 a6989586621679997479 a6989586621679997480 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip4Sym2 a6989586621679997479 a6989586621679997480 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621679997481 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip4Sym3 (a6989586621679997479 :: [a]) (a6989586621679997480 :: [b]) (a6989586621679997481 :: [c]) :: (~>) [d] [(a, b, c, d)] Source #
Instances
| SuppressUnusedWarnings (Zip4Sym3 a6989586621679997479 a6989586621679997480 a6989586621679997481 :: TyFun [d] [(a, b, c, d)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip4Sym3 a6989586621679997479 a6989586621679997480 a6989586621679997481 :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621679997482 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family Zip4Sym4 (a6989586621679997479 :: [a]) (a6989586621679997480 :: [b]) (a6989586621679997481 :: [c]) (a6989586621679997482 :: [d]) :: [(a, b, c, d)] where ... Source #
data Zip5Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [(a, b, c, d, e)])))) Source #
Instances
| SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) (a6989586621679997456 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip5Sym1 (a6989586621679997456 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [(a, b, c, d, e)]))) Source #
Instances
| SuppressUnusedWarnings (Zip5Sym1 a6989586621679997456 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym1 a6989586621679997456 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621679997457 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip5Sym2 (a6989586621679997456 :: [a]) (a6989586621679997457 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] [(a, b, c, d, e)])) Source #
Instances
| SuppressUnusedWarnings (Zip5Sym2 a6989586621679997456 a6989586621679997457 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym2 a6989586621679997456 a6989586621679997457 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621679997458 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip5Sym3 (a6989586621679997456 :: [a]) (a6989586621679997457 :: [b]) (a6989586621679997458 :: [c]) :: (~>) [d] ((~>) [e] [(a, b, c, d, e)]) Source #
Instances
| SuppressUnusedWarnings (Zip5Sym3 a6989586621679997456 a6989586621679997457 a6989586621679997458 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym3 a6989586621679997456 a6989586621679997457 a6989586621679997458 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621679997459 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip5Sym4 (a6989586621679997456 :: [a]) (a6989586621679997457 :: [b]) (a6989586621679997458 :: [c]) (a6989586621679997459 :: [d]) :: (~>) [e] [(a, b, c, d, e)] Source #
Instances
| SuppressUnusedWarnings (Zip5Sym4 a6989586621679997456 a6989586621679997457 a6989586621679997458 a6989586621679997459 :: TyFun [e] [(a, b, c, d, e)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym4 a6989586621679997456 a6989586621679997457 a6989586621679997458 a6989586621679997459 :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621679997460 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family Zip5Sym5 (a6989586621679997456 :: [a]) (a6989586621679997457 :: [b]) (a6989586621679997458 :: [c]) (a6989586621679997459 :: [d]) (a6989586621679997460 :: [e]) :: [(a, b, c, d, e)] where ... Source #
data Zip6Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)]))))) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) (a6989586621679997428 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip6Sym1 (a6989586621679997428 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)])))) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym1 a6989586621679997428 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym1 a6989586621679997428 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621679997429 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip6Sym2 (a6989586621679997428 :: [a]) (a6989586621679997429 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)]))) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym2 a6989586621679997428 a6989586621679997429 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym2 a6989586621679997428 a6989586621679997429 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621679997430 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip6Sym3 (a6989586621679997428 :: [a]) (a6989586621679997429 :: [b]) (a6989586621679997430 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)])) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym3 a6989586621679997428 a6989586621679997429 a6989586621679997430 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym3 a6989586621679997428 a6989586621679997429 a6989586621679997430 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679997431 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip6Sym3 a6989586621679997428 a6989586621679997429 a6989586621679997430 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679997431 :: [d]) = Zip6Sym4 a6989586621679997428 a6989586621679997429 a6989586621679997430 a6989586621679997431 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type | |
data Zip6Sym4 (a6989586621679997428 :: [a]) (a6989586621679997429 :: [b]) (a6989586621679997430 :: [c]) (a6989586621679997431 :: [d]) :: (~>) [e] ((~>) [f] [(a, b, c, d, e, f)]) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym4 a6989586621679997428 a6989586621679997429 a6989586621679997430 a6989586621679997431 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym4 a6989586621679997428 a6989586621679997429 a6989586621679997430 a6989586621679997431 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679997432 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip6Sym4 a6989586621679997428 a6989586621679997429 a6989586621679997430 a6989586621679997431 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679997432 :: [e]) = Zip6Sym5 a6989586621679997428 a6989586621679997429 a6989586621679997430 a6989586621679997431 a6989586621679997432 :: TyFun [f] [(a, b, c, d, e, f)] -> Type | |
data Zip6Sym5 (a6989586621679997428 :: [a]) (a6989586621679997429 :: [b]) (a6989586621679997430 :: [c]) (a6989586621679997431 :: [d]) (a6989586621679997432 :: [e]) :: (~>) [f] [(a, b, c, d, e, f)] Source #
Instances
| SuppressUnusedWarnings (Zip6Sym5 a6989586621679997428 a6989586621679997429 a6989586621679997430 a6989586621679997431 a6989586621679997432 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym5 a6989586621679997428 a6989586621679997429 a6989586621679997430 a6989586621679997431 a6989586621679997432 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621679997433 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip6Sym5 a6989586621679997428 a6989586621679997429 a6989586621679997430 a6989586621679997431 a6989586621679997432 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621679997433 :: [f]) = Zip6 a6989586621679997428 a6989586621679997429 a6989586621679997430 a6989586621679997431 a6989586621679997432 a6989586621679997433 | |
type family Zip6Sym6 (a6989586621679997428 :: [a]) (a6989586621679997429 :: [b]) (a6989586621679997430 :: [c]) (a6989586621679997431 :: [d]) (a6989586621679997432 :: [e]) (a6989586621679997433 :: [f]) :: [(a, b, c, d, e, f)] where ... Source #
data Zip7Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)])))))) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) (a6989586621679997395 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip7Sym1 (a6989586621679997395 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)]))))) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym1 a6989586621679997395 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym1 a6989586621679997395 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621679997396 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip7Sym2 (a6989586621679997395 :: [a]) (a6989586621679997396 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)])))) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym2 a6989586621679997395 a6989586621679997396 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym2 a6989586621679997395 a6989586621679997396 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679997397 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym2 a6989586621679997395 a6989586621679997396 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679997397 :: [c]) = Zip7Sym3 a6989586621679997395 a6989586621679997396 a6989586621679997397 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type | |
data Zip7Sym3 (a6989586621679997395 :: [a]) (a6989586621679997396 :: [b]) (a6989586621679997397 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)]))) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym3 a6989586621679997395 a6989586621679997396 a6989586621679997397 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym3 a6989586621679997395 a6989586621679997396 a6989586621679997397 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679997398 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym3 a6989586621679997395 a6989586621679997396 a6989586621679997397 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679997398 :: [d]) = Zip7Sym4 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type | |
data Zip7Sym4 (a6989586621679997395 :: [a]) (a6989586621679997396 :: [b]) (a6989586621679997397 :: [c]) (a6989586621679997398 :: [d]) :: (~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)])) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym4 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym4 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679997399 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym4 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679997399 :: [e]) = Zip7Sym5 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 a6989586621679997399 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type | |
data Zip7Sym5 (a6989586621679997395 :: [a]) (a6989586621679997396 :: [b]) (a6989586621679997397 :: [c]) (a6989586621679997398 :: [d]) (a6989586621679997399 :: [e]) :: (~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)]) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym5 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 a6989586621679997399 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym5 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 a6989586621679997399 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679997400 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym5 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 a6989586621679997399 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679997400 :: [f]) = Zip7Sym6 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 a6989586621679997399 a6989586621679997400 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type | |
data Zip7Sym6 (a6989586621679997395 :: [a]) (a6989586621679997396 :: [b]) (a6989586621679997397 :: [c]) (a6989586621679997398 :: [d]) (a6989586621679997399 :: [e]) (a6989586621679997400 :: [f]) :: (~>) [g] [(a, b, c, d, e, f, g)] Source #
Instances
| SuppressUnusedWarnings (Zip7Sym6 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 a6989586621679997399 a6989586621679997400 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym6 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 a6989586621679997399 a6989586621679997400 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621679997401 :: [g]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym6 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 a6989586621679997399 a6989586621679997400 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621679997401 :: [g]) = Zip7 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 a6989586621679997399 a6989586621679997400 a6989586621679997401 | |
type family Zip7Sym7 (a6989586621679997395 :: [a]) (a6989586621679997396 :: [b]) (a6989586621679997397 :: [c]) (a6989586621679997398 :: [d]) (a6989586621679997399 :: [e]) (a6989586621679997400 :: [f]) (a6989586621679997401 :: [g]) :: [(a, b, c, d, e, f, g)] where ... Source #
Equations
| Zip7Sym7 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 a6989586621679997399 a6989586621679997400 a6989586621679997401 = Zip7 a6989586621679997395 a6989586621679997396 a6989586621679997397 a6989586621679997398 a6989586621679997399 a6989586621679997400 a6989586621679997401 |
data ZipWithSym0 :: (~>) ((~>) a ((~>) b c)) ((~>) [a] ((~>) [b] [c])) Source #
Instances
| SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing ZipWithSym0 | |
| SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679848713 :: a ~> (b ~> c)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679848713 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621679848713 | |
data ZipWithSym1 (a6989586621679848713 :: (~>) a ((~>) b c)) :: (~>) [a] ((~>) [b] [c]) Source #
Instances
| SingI1 (ZipWithSym1 :: (a ~> (b ~> c)) -> TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (ZipWithSym1 x) | |
| SingI d => SingI (ZipWithSym1 d :: TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ZipWithSym1 d) | |
| SuppressUnusedWarnings (ZipWithSym1 a6989586621679848713 :: TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym1 a6989586621679848713 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679848714 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWithSym1 a6989586621679848713 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679848714 :: [a]) = ZipWithSym2 a6989586621679848713 a6989586621679848714 | |
data ZipWithSym2 (a6989586621679848713 :: (~>) a ((~>) b c)) (a6989586621679848714 :: [a]) :: (~>) [b] [c] Source #
Instances
| SingI d => SingI1 (ZipWithSym2 d :: [a] -> TyFun [b] [c] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (ZipWithSym2 d x) | |
| SingI2 (ZipWithSym2 :: (a ~> (b ~> c)) -> [a] -> TyFun [b] [c] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (ZipWithSym2 x y) | |
| (SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun [b] [c] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ZipWithSym2 d1 d2) | |
| SuppressUnusedWarnings (ZipWithSym2 a6989586621679848713 a6989586621679848714 :: TyFun [b] [c] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym2 a6989586621679848713 a6989586621679848714 :: TyFun [b] [c] -> Type) (a6989586621679848715 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWithSym2 a6989586621679848713 a6989586621679848714 :: TyFun [b] [c] -> Type) (a6989586621679848715 :: [b]) = ZipWith a6989586621679848713 a6989586621679848714 a6989586621679848715 | |
type family ZipWithSym3 (a6989586621679848713 :: (~>) a ((~>) b c)) (a6989586621679848714 :: [a]) (a6989586621679848715 :: [b]) :: [c] where ... Source #
Equations
| ZipWithSym3 a6989586621679848713 a6989586621679848714 a6989586621679848715 = ZipWith a6989586621679848713 a6989586621679848714 a6989586621679848715 |
data ZipWith3Sym0 :: (~>) ((~>) a ((~>) b ((~>) c d))) ((~>) [a] ((~>) [b] ((~>) [c] [d]))) Source #
Instances
| SingI (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing ZipWith3Sym0 | |
| SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679848698 :: a ~> (b ~> (c ~> d))) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679848698 :: a ~> (b ~> (c ~> d))) = ZipWith3Sym1 a6989586621679848698 | |
data ZipWith3Sym1 (a6989586621679848698 :: (~>) a ((~>) b ((~>) c d))) :: (~>) [a] ((~>) [b] ((~>) [c] [d])) Source #
Instances
| SingI1 (ZipWith3Sym1 :: (a ~> (b ~> (c ~> d))) -> TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (ZipWith3Sym1 x) | |
| SingI d2 => SingI (ZipWith3Sym1 d2 :: TyFun [a] ([b] ~> ([c] ~> [d1])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ZipWith3Sym1 d2) | |
| SuppressUnusedWarnings (ZipWith3Sym1 a6989586621679848698 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith3Sym1 a6989586621679848698 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679848699 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym1 a6989586621679848698 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679848699 :: [a]) = ZipWith3Sym2 a6989586621679848698 a6989586621679848699 | |
data ZipWith3Sym2 (a6989586621679848698 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679848699 :: [a]) :: (~>) [b] ((~>) [c] [d]) Source #
Instances
| SingI d2 => SingI1 (ZipWith3Sym2 d2 :: [a] -> TyFun [b] ([c] ~> [d1]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (ZipWith3Sym2 d2 x) | |
| SingI2 (ZipWith3Sym2 :: (a ~> (b ~> (c ~> d))) -> [a] -> TyFun [b] ([c] ~> [d]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (ZipWith3Sym2 x y) | |
| (SingI d2, SingI d3) => SingI (ZipWith3Sym2 d2 d3 :: TyFun [b] ([c] ~> [d1]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ZipWith3Sym2 d2 d3) | |
| SuppressUnusedWarnings (ZipWith3Sym2 a6989586621679848698 a6989586621679848699 :: TyFun [b] ([c] ~> [d]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith3Sym2 a6989586621679848698 a6989586621679848699 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679848700 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym2 a6989586621679848698 a6989586621679848699 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679848700 :: [b]) = ZipWith3Sym3 a6989586621679848698 a6989586621679848699 a6989586621679848700 | |
data ZipWith3Sym3 (a6989586621679848698 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679848699 :: [a]) (a6989586621679848700 :: [b]) :: (~>) [c] [d] Source #
Instances
| SingI d2 => SingI2 (ZipWith3Sym3 d2 :: [a] -> [b] -> TyFun [c] [d1] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (ZipWith3Sym3 d2 x y) | |
| (SingI d2, SingI d3) => SingI1 (ZipWith3Sym3 d2 d3 :: [b] -> TyFun [c] [d1] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (ZipWith3Sym3 d2 d3 x) | |
| (SingI d2, SingI d3, SingI d4) => SingI (ZipWith3Sym3 d2 d3 d4 :: TyFun [c] [d1] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ZipWith3Sym3 d2 d3 d4) | |
| SuppressUnusedWarnings (ZipWith3Sym3 a6989586621679848698 a6989586621679848699 a6989586621679848700 :: TyFun [c] [d] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith3Sym3 a6989586621679848698 a6989586621679848699 a6989586621679848700 :: TyFun [c] [d] -> Type) (a6989586621679848701 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym3 a6989586621679848698 a6989586621679848699 a6989586621679848700 :: TyFun [c] [d] -> Type) (a6989586621679848701 :: [c]) = ZipWith3 a6989586621679848698 a6989586621679848699 a6989586621679848700 a6989586621679848701 | |
type family ZipWith3Sym4 (a6989586621679848698 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679848699 :: [a]) (a6989586621679848700 :: [b]) (a6989586621679848701 :: [c]) :: [d] where ... Source #
Equations
| ZipWith3Sym4 a6989586621679848698 a6989586621679848699 a6989586621679848700 a6989586621679848701 = ZipWith3 a6989586621679848698 a6989586621679848699 a6989586621679848700 a6989586621679848701 |
data ZipWith4Sym0 :: (~>) ((~>) a ((~>) b ((~>) c ((~>) d e)))) ((~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] [e])))) Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) (a6989586621679997359 :: a ~> (b ~> (c ~> (d ~> e)))) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) (a6989586621679997359 :: a ~> (b ~> (c ~> (d ~> e)))) = ZipWith4Sym1 a6989586621679997359 | |
data ZipWith4Sym1 (a6989586621679997359 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] [e]))) Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym1 a6989586621679997359 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym1 a6989586621679997359 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679997360 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym1 a6989586621679997359 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679997360 :: [a]) = ZipWith4Sym2 a6989586621679997359 a6989586621679997360 | |
data ZipWith4Sym2 (a6989586621679997359 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679997360 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] [e])) Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym2 a6989586621679997359 a6989586621679997360 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym2 a6989586621679997359 a6989586621679997360 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679997361 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym2 a6989586621679997359 a6989586621679997360 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679997361 :: [b]) = ZipWith4Sym3 a6989586621679997359 a6989586621679997360 a6989586621679997361 | |
data ZipWith4Sym3 (a6989586621679997359 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679997360 :: [a]) (a6989586621679997361 :: [b]) :: (~>) [c] ((~>) [d] [e]) Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym3 a6989586621679997359 a6989586621679997360 a6989586621679997361 :: TyFun [c] ([d] ~> [e]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym3 a6989586621679997359 a6989586621679997360 a6989586621679997361 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679997362 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym3 a6989586621679997359 a6989586621679997360 a6989586621679997361 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679997362 :: [c]) = ZipWith4Sym4 a6989586621679997359 a6989586621679997360 a6989586621679997361 a6989586621679997362 | |
data ZipWith4Sym4 (a6989586621679997359 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679997360 :: [a]) (a6989586621679997361 :: [b]) (a6989586621679997362 :: [c]) :: (~>) [d] [e] Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym4 a6989586621679997359 a6989586621679997360 a6989586621679997361 a6989586621679997362 :: TyFun [d] [e] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym4 a6989586621679997359 a6989586621679997360 a6989586621679997361 a6989586621679997362 :: TyFun [d] [e] -> Type) (a6989586621679997363 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym4 a6989586621679997359 a6989586621679997360 a6989586621679997361 a6989586621679997362 :: TyFun [d] [e] -> Type) (a6989586621679997363 :: [d]) = ZipWith4 a6989586621679997359 a6989586621679997360 a6989586621679997361 a6989586621679997362 a6989586621679997363 | |
type family ZipWith4Sym5 (a6989586621679997359 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679997360 :: [a]) (a6989586621679997361 :: [b]) (a6989586621679997362 :: [c]) (a6989586621679997363 :: [d]) :: [e] where ... Source #
Equations
| ZipWith4Sym5 a6989586621679997359 a6989586621679997360 a6989586621679997361 a6989586621679997362 a6989586621679997363 = ZipWith4 a6989586621679997359 a6989586621679997360 a6989586621679997361 a6989586621679997362 a6989586621679997363 |
data ZipWith5Sym0 :: (~>) ((~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) ((~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [f]))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) (a6989586621679997336 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) (a6989586621679997336 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) = ZipWith5Sym1 a6989586621679997336 | |
data ZipWith5Sym1 (a6989586621679997336 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [f])))) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym1 a6989586621679997336 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym1 a6989586621679997336 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679997337 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym1 a6989586621679997336 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679997337 :: [a]) = ZipWith5Sym2 a6989586621679997336 a6989586621679997337 | |
data ZipWith5Sym2 (a6989586621679997336 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679997337 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [f]))) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym2 a6989586621679997336 a6989586621679997337 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym2 a6989586621679997336 a6989586621679997337 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679997338 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym2 a6989586621679997336 a6989586621679997337 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679997338 :: [b]) = ZipWith5Sym3 a6989586621679997336 a6989586621679997337 a6989586621679997338 | |
data ZipWith5Sym3 (a6989586621679997336 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679997337 :: [a]) (a6989586621679997338 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] [f])) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym3 a6989586621679997336 a6989586621679997337 a6989586621679997338 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym3 a6989586621679997336 a6989586621679997337 a6989586621679997338 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679997339 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym3 a6989586621679997336 a6989586621679997337 a6989586621679997338 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679997339 :: [c]) = ZipWith5Sym4 a6989586621679997336 a6989586621679997337 a6989586621679997338 a6989586621679997339 | |
data ZipWith5Sym4 (a6989586621679997336 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679997337 :: [a]) (a6989586621679997338 :: [b]) (a6989586621679997339 :: [c]) :: (~>) [d] ((~>) [e] [f]) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym4 a6989586621679997336 a6989586621679997337 a6989586621679997338 a6989586621679997339 :: TyFun [d] ([e] ~> [f]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym4 a6989586621679997336 a6989586621679997337 a6989586621679997338 a6989586621679997339 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679997340 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym4 a6989586621679997336 a6989586621679997337 a6989586621679997338 a6989586621679997339 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679997340 :: [d]) = ZipWith5Sym5 a6989586621679997336 a6989586621679997337 a6989586621679997338 a6989586621679997339 a6989586621679997340 | |
data ZipWith5Sym5 (a6989586621679997336 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679997337 :: [a]) (a6989586621679997338 :: [b]) (a6989586621679997339 :: [c]) (a6989586621679997340 :: [d]) :: (~>) [e] [f] Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym5 a6989586621679997336 a6989586621679997337 a6989586621679997338 a6989586621679997339 a6989586621679997340 :: TyFun [e] [f] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym5 a6989586621679997336 a6989586621679997337 a6989586621679997338 a6989586621679997339 a6989586621679997340 :: TyFun [e] [f] -> Type) (a6989586621679997341 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym5 a6989586621679997336 a6989586621679997337 a6989586621679997338 a6989586621679997339 a6989586621679997340 :: TyFun [e] [f] -> Type) (a6989586621679997341 :: [e]) = ZipWith5 a6989586621679997336 a6989586621679997337 a6989586621679997338 a6989586621679997339 a6989586621679997340 a6989586621679997341 | |
type family ZipWith5Sym6 (a6989586621679997336 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679997337 :: [a]) (a6989586621679997338 :: [b]) (a6989586621679997339 :: [c]) (a6989586621679997340 :: [d]) (a6989586621679997341 :: [e]) :: [f] where ... Source #
Equations
| ZipWith5Sym6 a6989586621679997336 a6989586621679997337 a6989586621679997338 a6989586621679997339 a6989586621679997340 a6989586621679997341 = ZipWith5 a6989586621679997336 a6989586621679997337 a6989586621679997338 a6989586621679997339 a6989586621679997340 a6989586621679997341 |
data ZipWith6Sym0 :: (~>) ((~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) ((~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g])))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) (a6989586621679997309 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) (a6989586621679997309 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) = ZipWith6Sym1 a6989586621679997309 | |
data ZipWith6Sym1 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g]))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym1 a6989586621679997309 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym1 a6989586621679997309 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679997310 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym1 a6989586621679997309 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679997310 :: [a]) = ZipWith6Sym2 a6989586621679997309 a6989586621679997310 | |
data ZipWith6Sym2 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679997310 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g])))) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym2 a6989586621679997309 a6989586621679997310 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym2 a6989586621679997309 a6989586621679997310 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679997311 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym2 a6989586621679997309 a6989586621679997310 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679997311 :: [b]) = ZipWith6Sym3 a6989586621679997309 a6989586621679997310 a6989586621679997311 | |
data ZipWith6Sym3 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679997310 :: [a]) (a6989586621679997311 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g]))) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym3 a6989586621679997309 a6989586621679997310 a6989586621679997311 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym3 a6989586621679997309 a6989586621679997310 a6989586621679997311 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679997312 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym3 a6989586621679997309 a6989586621679997310 a6989586621679997311 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679997312 :: [c]) = ZipWith6Sym4 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 | |
data ZipWith6Sym4 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679997310 :: [a]) (a6989586621679997311 :: [b]) (a6989586621679997312 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] [g])) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym4 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym4 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679997313 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym4 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679997313 :: [d]) = ZipWith6Sym5 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 a6989586621679997313 | |
data ZipWith6Sym5 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679997310 :: [a]) (a6989586621679997311 :: [b]) (a6989586621679997312 :: [c]) (a6989586621679997313 :: [d]) :: (~>) [e] ((~>) [f] [g]) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym5 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 a6989586621679997313 :: TyFun [e] ([f] ~> [g]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym5 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 a6989586621679997313 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679997314 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym5 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 a6989586621679997313 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679997314 :: [e]) = ZipWith6Sym6 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 a6989586621679997313 a6989586621679997314 | |
data ZipWith6Sym6 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679997310 :: [a]) (a6989586621679997311 :: [b]) (a6989586621679997312 :: [c]) (a6989586621679997313 :: [d]) (a6989586621679997314 :: [e]) :: (~>) [f] [g] Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym6 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 a6989586621679997313 a6989586621679997314 :: TyFun [f] [g] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym6 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 a6989586621679997313 a6989586621679997314 :: TyFun [f] [g] -> Type) (a6989586621679997315 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym6 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 a6989586621679997313 a6989586621679997314 :: TyFun [f] [g] -> Type) (a6989586621679997315 :: [f]) = ZipWith6 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 a6989586621679997313 a6989586621679997314 a6989586621679997315 | |
type family ZipWith6Sym7 (a6989586621679997309 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679997310 :: [a]) (a6989586621679997311 :: [b]) (a6989586621679997312 :: [c]) (a6989586621679997313 :: [d]) (a6989586621679997314 :: [e]) (a6989586621679997315 :: [f]) :: [g] where ... Source #
Equations
| ZipWith6Sym7 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 a6989586621679997313 a6989586621679997314 a6989586621679997315 = ZipWith6 a6989586621679997309 a6989586621679997310 a6989586621679997311 a6989586621679997312 a6989586621679997313 a6989586621679997314 a6989586621679997315 |
data ZipWith7Sym0 :: (~>) ((~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) ((~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h]))))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) (a6989586621679997278 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) (a6989586621679997278 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) = ZipWith7Sym1 a6989586621679997278 | |
data ZipWith7Sym1 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h])))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym1 a6989586621679997278 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym1 a6989586621679997278 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679997279 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym1 a6989586621679997278 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679997279 :: [a]) = ZipWith7Sym2 a6989586621679997278 a6989586621679997279 | |
data ZipWith7Sym2 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h]))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym2 a6989586621679997278 a6989586621679997279 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym2 a6989586621679997278 a6989586621679997279 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679997280 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym2 a6989586621679997278 a6989586621679997279 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679997280 :: [b]) = ZipWith7Sym3 a6989586621679997278 a6989586621679997279 a6989586621679997280 | |
data ZipWith7Sym3 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) (a6989586621679997280 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h])))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym3 a6989586621679997278 a6989586621679997279 a6989586621679997280 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym3 a6989586621679997278 a6989586621679997279 a6989586621679997280 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679997281 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym3 a6989586621679997278 a6989586621679997279 a6989586621679997280 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679997281 :: [c]) = ZipWith7Sym4 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 | |
data ZipWith7Sym4 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) (a6989586621679997280 :: [b]) (a6989586621679997281 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h]))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym4 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym4 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679997282 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym4 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679997282 :: [d]) = ZipWith7Sym5 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 | |
data ZipWith7Sym5 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) (a6989586621679997280 :: [b]) (a6989586621679997281 :: [c]) (a6989586621679997282 :: [d]) :: (~>) [e] ((~>) [f] ((~>) [g] [h])) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym5 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym5 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679997283 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym5 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679997283 :: [e]) = ZipWith7Sym6 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 a6989586621679997283 | |
data ZipWith7Sym6 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) (a6989586621679997280 :: [b]) (a6989586621679997281 :: [c]) (a6989586621679997282 :: [d]) (a6989586621679997283 :: [e]) :: (~>) [f] ((~>) [g] [h]) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym6 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 a6989586621679997283 :: TyFun [f] ([g] ~> [h]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym6 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 a6989586621679997283 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679997284 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym6 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 a6989586621679997283 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679997284 :: [f]) = ZipWith7Sym7 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 a6989586621679997283 a6989586621679997284 | |
data ZipWith7Sym7 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) (a6989586621679997280 :: [b]) (a6989586621679997281 :: [c]) (a6989586621679997282 :: [d]) (a6989586621679997283 :: [e]) (a6989586621679997284 :: [f]) :: (~>) [g] [h] Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym7 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 a6989586621679997283 a6989586621679997284 :: TyFun [g] [h] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym7 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 a6989586621679997283 a6989586621679997284 :: TyFun [g] [h] -> Type) (a6989586621679997285 :: [g]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym7 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 a6989586621679997283 a6989586621679997284 :: TyFun [g] [h] -> Type) (a6989586621679997285 :: [g]) = ZipWith7 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 a6989586621679997283 a6989586621679997284 a6989586621679997285 | |
type family ZipWith7Sym8 (a6989586621679997278 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679997279 :: [a]) (a6989586621679997280 :: [b]) (a6989586621679997281 :: [c]) (a6989586621679997282 :: [d]) (a6989586621679997283 :: [e]) (a6989586621679997284 :: [f]) (a6989586621679997285 :: [g]) :: [h] where ... Source #
Equations
| ZipWith7Sym8 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 a6989586621679997283 a6989586621679997284 a6989586621679997285 = ZipWith7 a6989586621679997278 a6989586621679997279 a6989586621679997280 a6989586621679997281 a6989586621679997282 a6989586621679997283 a6989586621679997284 a6989586621679997285 |
data UnzipSym0 :: (~>) [(a, b)] ([a], [b]) Source #
Instances
| SingI (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679848679 :: [(a, b)]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Unzip3Sym0 :: (~>) [(a, b, c)] ([a], [b], [c]) Source #
Instances
| SingI (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing Unzip3Sym0 | |
| SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679848661 :: [(a, b, c)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679848661 :: [(a, b, c)]) = Unzip3 a6989586621679848661 | |
type family Unzip3Sym1 (a6989586621679848661 :: [(a, b, c)]) :: ([a], [b], [c]) where ... Source #
Equations
| Unzip3Sym1 a6989586621679848661 = Unzip3 a6989586621679848661 |
data Unzip4Sym0 :: (~>) [(a, b, c, d)] ([a], [b], [c], [d]) Source #
Instances
| SingI (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing Unzip4Sym0 | |
| SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679848641 :: [(a, b, c, d)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679848641 :: [(a, b, c, d)]) = Unzip4 a6989586621679848641 | |
type family Unzip4Sym1 (a6989586621679848641 :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ... Source #
Equations
| Unzip4Sym1 a6989586621679848641 = Unzip4 a6989586621679848641 |
data Unzip5Sym0 :: (~>) [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) Source #
Instances
| SingI (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing Unzip5Sym0 | |
| SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679848619 :: [(a, b, c, d, e)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679848619 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679848619 | |
type family Unzip5Sym1 (a6989586621679848619 :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ... Source #
Equations
| Unzip5Sym1 a6989586621679848619 = Unzip5 a6989586621679848619 |
data Unzip6Sym0 :: (~>) [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) Source #
Instances
| SingI (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing Unzip6Sym0 | |
| SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679848595 :: [(a, b, c, d, e, f)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679848595 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679848595 | |
type family Unzip6Sym1 (a6989586621679848595 :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ... Source #
Equations
| Unzip6Sym1 a6989586621679848595 = Unzip6 a6989586621679848595 |
data Unzip7Sym0 :: (~>) [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) Source #
Instances
| SingI (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing Unzip7Sym0 | |
| SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679848569 :: [(a, b, c, d, e, f, g)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679848569 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679848569 | |
type family Unzip7Sym1 (a6989586621679848569 :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... Source #
Equations
| Unzip7Sym1 a6989586621679848569 = Unzip7 a6989586621679848569 |
data UnlinesSym0 :: (~>) [Symbol] Symbol Source #
Instances
| SingI UnlinesSym0 Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing UnlinesSym0 | |
| SuppressUnusedWarnings UnlinesSym0 Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply UnlinesSym0 (a6989586621679848564 :: [Symbol]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family UnlinesSym1 (a6989586621679848564 :: [Symbol]) :: Symbol where ... Source #
Equations
| UnlinesSym1 a6989586621679848564 = Unlines a6989586621679848564 |
data UnwordsSym0 :: (~>) [Symbol] Symbol Source #
Instances
| SingI UnwordsSym0 Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing UnwordsSym0 | |
| SuppressUnusedWarnings UnwordsSym0 Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply UnwordsSym0 (a6989586621679848554 :: [Symbol]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family UnwordsSym1 (a6989586621679848554 :: [Symbol]) :: Symbol where ... Source #
Equations
| UnwordsSym1 a6989586621679848554 = Unwords a6989586621679848554 |
data NubSym0 :: (~>) [a] [a] Source #
Instances
| SEq a => SingI (NubSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (NubSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (NubSym0 :: TyFun [a] [a] -> Type) (a6989586621679848010 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data DeleteSym0 :: (~>) a ((~>) [a] [a]) Source #
Instances
| SEq a => SingI (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing DeleteSym0 | |
| SuppressUnusedWarnings (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679848548 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679848548 :: a) = DeleteSym1 a6989586621679848548 | |
data DeleteSym1 (a6989586621679848548 :: a) :: (~>) [a] [a] Source #
Instances
| SEq a => SingI1 (DeleteSym1 :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (DeleteSym1 x) | |
| (SEq a, SingI d) => SingI (DeleteSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DeleteSym1 d) | |
| SuppressUnusedWarnings (DeleteSym1 a6989586621679848548 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteSym1 a6989586621679848548 :: TyFun [a] [a] -> Type) (a6989586621679848549 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteSym1 a6989586621679848548 :: TyFun [a] [a] -> Type) (a6989586621679848549 :: [a]) = Delete a6989586621679848548 a6989586621679848549 | |
type family DeleteSym2 (a6989586621679848548 :: a) (a6989586621679848549 :: [a]) :: [a] where ... Source #
Equations
| DeleteSym2 a6989586621679848548 a6989586621679848549 = Delete a6989586621679848548 a6989586621679848549 |
data (\\@#@$) :: (~>) [a] ((~>) [a] [a]) infix 5 Source #
Instances
| SEq a => SingI ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679848537 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data (\\@#@$$) (a6989586621679848537 :: [a]) :: (~>) [a] [a] infix 5 Source #
Instances
| SEq a => SingI1 ((\\@#@$$) :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (SEq a, SingI d) => SingI ((\\@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings ((\\@#@$$) a6989586621679848537 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply ((\\@#@$$) a6989586621679848537 :: TyFun [a] [a] -> Type) (a6989586621679848538 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family (a6989586621679848537 :: [a]) \\@#@$$$ (a6989586621679848538 :: [a]) :: [a] where ... infix 5 Source #
data UnionSym0 :: (~>) [a] ((~>) [a] [a]) Source #
Instances
| SEq a => SingI (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679847964 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data UnionSym1 (a6989586621679847964 :: [a]) :: (~>) [a] [a] Source #
Instances
| SEq a => SingI1 (UnionSym1 :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (SEq a, SingI d) => SingI (UnionSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (UnionSym1 a6989586621679847964 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnionSym1 a6989586621679847964 :: TyFun [a] [a] -> Type) (a6989586621679847965 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family UnionSym2 (a6989586621679847964 :: [a]) (a6989586621679847965 :: [a]) :: [a] where ... Source #
data IntersectSym0 :: (~>) [a] ((~>) [a] [a]) Source #
Instances
| SEq a => SingI (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679848355 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679848355 :: [a]) = IntersectSym1 a6989586621679848355 | |
data IntersectSym1 (a6989586621679848355 :: [a]) :: (~>) [a] [a] Source #
Instances
| SEq a => SingI1 (IntersectSym1 :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (IntersectSym1 x) | |
| (SEq a, SingI d) => SingI (IntersectSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IntersectSym1 d) | |
| SuppressUnusedWarnings (IntersectSym1 a6989586621679848355 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersectSym1 a6989586621679848355 :: TyFun [a] [a] -> Type) (a6989586621679848356 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectSym1 a6989586621679848355 :: TyFun [a] [a] -> Type) (a6989586621679848356 :: [a]) = Intersect a6989586621679848355 a6989586621679848356 | |
type family IntersectSym2 (a6989586621679848355 :: [a]) (a6989586621679848356 :: [a]) :: [a] where ... Source #
Equations
| IntersectSym2 a6989586621679848355 a6989586621679848356 = Intersect a6989586621679848355 a6989586621679848356 |
data InsertSym0 :: (~>) a ((~>) [a] [a]) Source #
Instances
| SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing InsertSym0 | |
| SuppressUnusedWarnings (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679848157 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679848157 :: a) = InsertSym1 a6989586621679848157 | |
data InsertSym1 (a6989586621679848157 :: a) :: (~>) [a] [a] Source #
Instances
| SOrd a => SingI1 (InsertSym1 :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (InsertSym1 x) | |
| (SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (InsertSym1 d) | |
| SuppressUnusedWarnings (InsertSym1 a6989586621679848157 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertSym1 a6989586621679848157 :: TyFun [a] [a] -> Type) (a6989586621679848158 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertSym1 a6989586621679848157 :: TyFun [a] [a] -> Type) (a6989586621679848158 :: [a]) = Insert a6989586621679848157 a6989586621679848158 | |
type family InsertSym2 (a6989586621679848157 :: a) (a6989586621679848158 :: [a]) :: [a] where ... Source #
Equations
| InsertSym2 a6989586621679848157 a6989586621679848158 = Insert a6989586621679848157 a6989586621679848158 |
data SortSym0 :: (~>) [a] [a] Source #
Instances
| SOrd a => SingI (SortSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (SortSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (SortSym0 :: TyFun [a] [a] -> Type) (a6989586621679848152 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data NubBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] [a]) Source #
Instances
| SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679847992 :: a ~> (a ~> Bool)) Source # | |
data NubBySym1 (a6989586621679847992 :: (~>) a ((~>) a Bool)) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI (NubBySym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (NubBySym1 a6989586621679847992 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (NubBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (NubBySym1 a6989586621679847992 :: TyFun [a] [a] -> Type) (a6989586621679847993 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family NubBySym2 (a6989586621679847992 :: (~>) a ((~>) a Bool)) (a6989586621679847993 :: [a]) :: [a] where ... Source #
data DeleteBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) a ((~>) [a] [a])) Source #
Instances
| SingI (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing DeleteBySym0 | |
| SuppressUnusedWarnings (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679848518 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679848518 :: a ~> (a ~> Bool)) = DeleteBySym1 a6989586621679848518 | |
data DeleteBySym1 (a6989586621679848518 :: (~>) a ((~>) a Bool)) :: (~>) a ((~>) [a] [a]) Source #
Instances
| SingI d => SingI (DeleteBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DeleteBySym1 d) | |
| SuppressUnusedWarnings (DeleteBySym1 a6989586621679848518 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (DeleteBySym1 :: (a ~> (a ~> Bool)) -> TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (DeleteBySym1 x) | |
| type Apply (DeleteBySym1 a6989586621679848518 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679848519 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteBySym1 a6989586621679848518 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679848519 :: a) = DeleteBySym2 a6989586621679848518 a6989586621679848519 | |
data DeleteBySym2 (a6989586621679848518 :: (~>) a ((~>) a Bool)) (a6989586621679848519 :: a) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI1 (DeleteBySym2 d :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (DeleteBySym2 d x) | |
| SingI2 (DeleteBySym2 :: (a ~> (a ~> Bool)) -> a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (DeleteBySym2 x y) | |
| (SingI d1, SingI d2) => SingI (DeleteBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DeleteBySym2 d1 d2) | |
| SuppressUnusedWarnings (DeleteBySym2 a6989586621679848518 a6989586621679848519 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteBySym2 a6989586621679848518 a6989586621679848519 :: TyFun [a] [a] -> Type) (a6989586621679848520 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteBySym2 a6989586621679848518 a6989586621679848519 :: TyFun [a] [a] -> Type) (a6989586621679848520 :: [a]) = DeleteBy a6989586621679848518 a6989586621679848519 a6989586621679848520 | |
type family DeleteBySym3 (a6989586621679848518 :: (~>) a ((~>) a Bool)) (a6989586621679848519 :: a) (a6989586621679848520 :: [a]) :: [a] where ... Source #
Equations
| DeleteBySym3 a6989586621679848518 a6989586621679848519 a6989586621679848520 = DeleteBy a6989586621679848518 a6989586621679848519 a6989586621679848520 |
data DeleteFirstsBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] ((~>) [a] [a])) Source #
Instances
| SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679848508 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679848508 :: a ~> (a ~> Bool)) = DeleteFirstsBySym1 a6989586621679848508 | |
data DeleteFirstsBySym1 (a6989586621679848508 :: (~>) a ((~>) a Bool)) :: (~>) [a] ((~>) [a] [a]) Source #
Instances
| SingI d => SingI (DeleteFirstsBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DeleteFirstsBySym1 d) | |
| SuppressUnusedWarnings (DeleteFirstsBySym1 a6989586621679848508 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (DeleteFirstsBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (DeleteFirstsBySym1 x) | |
| type Apply (DeleteFirstsBySym1 a6989586621679848508 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679848509 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteFirstsBySym1 a6989586621679848508 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679848509 :: [a]) = DeleteFirstsBySym2 a6989586621679848508 a6989586621679848509 | |
data DeleteFirstsBySym2 (a6989586621679848508 :: (~>) a ((~>) a Bool)) (a6989586621679848509 :: [a]) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI1 (DeleteFirstsBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (DeleteFirstsBySym2 d x) | |
| SingI2 (DeleteFirstsBySym2 :: (a ~> (a ~> Bool)) -> [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (DeleteFirstsBySym2 x y) | |
| (SingI d1, SingI d2) => SingI (DeleteFirstsBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DeleteFirstsBySym2 d1 d2) | |
| SuppressUnusedWarnings (DeleteFirstsBySym2 a6989586621679848508 a6989586621679848509 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteFirstsBySym2 a6989586621679848508 a6989586621679848509 :: TyFun [a] [a] -> Type) (a6989586621679848510 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteFirstsBySym2 a6989586621679848508 a6989586621679848509 :: TyFun [a] [a] -> Type) (a6989586621679848510 :: [a]) = DeleteFirstsBy a6989586621679848508 a6989586621679848509 a6989586621679848510 | |
type family DeleteFirstsBySym3 (a6989586621679848508 :: (~>) a ((~>) a Bool)) (a6989586621679848509 :: [a]) (a6989586621679848510 :: [a]) :: [a] where ... Source #
Equations
| DeleteFirstsBySym3 a6989586621679848508 a6989586621679848509 a6989586621679848510 = DeleteFirstsBy a6989586621679848508 a6989586621679848509 a6989586621679848510 |
data UnionBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] ((~>) [a] [a])) Source #
Instances
| SingI (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing UnionBySym0 | |
| SuppressUnusedWarnings (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679847972 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679847972 :: a ~> (a ~> Bool)) = UnionBySym1 a6989586621679847972 | |
data UnionBySym1 (a6989586621679847972 :: (~>) a ((~>) a Bool)) :: (~>) [a] ((~>) [a] [a]) Source #
Instances
| SingI d => SingI (UnionBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (UnionBySym1 d) | |
| SuppressUnusedWarnings (UnionBySym1 a6989586621679847972 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (UnionBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (UnionBySym1 x) | |
| type Apply (UnionBySym1 a6989586621679847972 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679847973 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnionBySym1 a6989586621679847972 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679847973 :: [a]) = UnionBySym2 a6989586621679847972 a6989586621679847973 | |
data UnionBySym2 (a6989586621679847972 :: (~>) a ((~>) a Bool)) (a6989586621679847973 :: [a]) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI1 (UnionBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (UnionBySym2 d x) | |
| SingI2 (UnionBySym2 :: (a ~> (a ~> Bool)) -> [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (UnionBySym2 x y) | |
| (SingI d1, SingI d2) => SingI (UnionBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (UnionBySym2 d1 d2) | |
| SuppressUnusedWarnings (UnionBySym2 a6989586621679847972 a6989586621679847973 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnionBySym2 a6989586621679847972 a6989586621679847973 :: TyFun [a] [a] -> Type) (a6989586621679847974 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnionBySym2 a6989586621679847972 a6989586621679847973 :: TyFun [a] [a] -> Type) (a6989586621679847974 :: [a]) = UnionBy a6989586621679847972 a6989586621679847973 a6989586621679847974 | |
type family UnionBySym3 (a6989586621679847972 :: (~>) a ((~>) a Bool)) (a6989586621679847973 :: [a]) (a6989586621679847974 :: [a]) :: [a] where ... Source #
Equations
| UnionBySym3 a6989586621679847972 a6989586621679847973 a6989586621679847974 = UnionBy a6989586621679847972 a6989586621679847973 a6989586621679847974 |
data IntersectBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] ((~>) [a] [a])) Source #
Instances
| SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679848333 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679848333 :: a ~> (a ~> Bool)) = IntersectBySym1 a6989586621679848333 | |
data IntersectBySym1 (a6989586621679848333 :: (~>) a ((~>) a Bool)) :: (~>) [a] ((~>) [a] [a]) Source #
Instances
| SingI d => SingI (IntersectBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IntersectBySym1 d) | |
| SuppressUnusedWarnings (IntersectBySym1 a6989586621679848333 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (IntersectBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (IntersectBySym1 x) | |
| type Apply (IntersectBySym1 a6989586621679848333 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679848334 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectBySym1 a6989586621679848333 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679848334 :: [a]) = IntersectBySym2 a6989586621679848333 a6989586621679848334 | |
data IntersectBySym2 (a6989586621679848333 :: (~>) a ((~>) a Bool)) (a6989586621679848334 :: [a]) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI1 (IntersectBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (IntersectBySym2 d x) | |
| SingI2 (IntersectBySym2 :: (a ~> (a ~> Bool)) -> [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (IntersectBySym2 x y) | |
| (SingI d1, SingI d2) => SingI (IntersectBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IntersectBySym2 d1 d2) | |
| SuppressUnusedWarnings (IntersectBySym2 a6989586621679848333 a6989586621679848334 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersectBySym2 a6989586621679848333 a6989586621679848334 :: TyFun [a] [a] -> Type) (a6989586621679848335 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectBySym2 a6989586621679848333 a6989586621679848334 :: TyFun [a] [a] -> Type) (a6989586621679848335 :: [a]) = IntersectBy a6989586621679848333 a6989586621679848334 a6989586621679848335 | |
type family IntersectBySym3 (a6989586621679848333 :: (~>) a ((~>) a Bool)) (a6989586621679848334 :: [a]) (a6989586621679848335 :: [a]) :: [a] where ... Source #
Equations
| IntersectBySym3 a6989586621679848333 a6989586621679848334 a6989586621679848335 = IntersectBy a6989586621679848333 a6989586621679848334 a6989586621679848335 |
data GroupBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] [[a]]) Source #
Instances
| SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing GroupBySym0 | |
| SuppressUnusedWarnings (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679848125 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679848125 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621679848125 | |
data GroupBySym1 (a6989586621679848125 :: (~>) a ((~>) a Bool)) :: (~>) [a] [[a]] Source #
Instances
| SingI d => SingI (GroupBySym1 d :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (GroupBySym1 d) | |
| SuppressUnusedWarnings (GroupBySym1 a6989586621679848125 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (GroupBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (GroupBySym1 x) | |
| type Apply (GroupBySym1 a6989586621679848125 :: TyFun [a] [[a]] -> Type) (a6989586621679848126 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (GroupBySym1 a6989586621679848125 :: TyFun [a] [[a]] -> Type) (a6989586621679848126 :: [a]) = GroupBy a6989586621679848125 a6989586621679848126 | |
type family GroupBySym2 (a6989586621679848125 :: (~>) a ((~>) a Bool)) (a6989586621679848126 :: [a]) :: [[a]] where ... Source #
Equations
| GroupBySym2 a6989586621679848125 a6989586621679848126 = GroupBy a6989586621679848125 a6989586621679848126 |
data SortBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) [a] [a]) Source #
Instances
| SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing SortBySym0 | |
| SuppressUnusedWarnings (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679848496 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679848496 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621679848496 | |
data SortBySym1 (a6989586621679848496 :: (~>) a ((~>) a Ordering)) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI (SortBySym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (SortBySym1 d) | |
| SuppressUnusedWarnings (SortBySym1 a6989586621679848496 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (SortBySym1 :: (a ~> (a ~> Ordering)) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (SortBySym1 x) | |
| type Apply (SortBySym1 a6989586621679848496 :: TyFun [a] [a] -> Type) (a6989586621679848497 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SortBySym1 a6989586621679848496 :: TyFun [a] [a] -> Type) (a6989586621679848497 :: [a]) = SortBy a6989586621679848496 a6989586621679848497 | |
type family SortBySym2 (a6989586621679848496 :: (~>) a ((~>) a Ordering)) (a6989586621679848497 :: [a]) :: [a] where ... Source #
Equations
| SortBySym2 a6989586621679848496 a6989586621679848497 = SortBy a6989586621679848496 a6989586621679848497 |
data InsertBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) a ((~>) [a] [a])) Source #
Instances
| SingI (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing InsertBySym0 | |
| SuppressUnusedWarnings (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679848476 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679848476 :: a ~> (a ~> Ordering)) = InsertBySym1 a6989586621679848476 | |
data InsertBySym1 (a6989586621679848476 :: (~>) a ((~>) a Ordering)) :: (~>) a ((~>) [a] [a]) Source #
Instances
| SingI d => SingI (InsertBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (InsertBySym1 d) | |
| SuppressUnusedWarnings (InsertBySym1 a6989586621679848476 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (InsertBySym1 :: (a ~> (a ~> Ordering)) -> TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (InsertBySym1 x) | |
| type Apply (InsertBySym1 a6989586621679848476 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679848477 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertBySym1 a6989586621679848476 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679848477 :: a) = InsertBySym2 a6989586621679848476 a6989586621679848477 | |
data InsertBySym2 (a6989586621679848476 :: (~>) a ((~>) a Ordering)) (a6989586621679848477 :: a) :: (~>) [a] [a] Source #
Instances
| SingI d => SingI1 (InsertBySym2 d :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: k1). Sing x -> Sing (InsertBySym2 d x) | |
| SingI2 (InsertBySym2 :: (a ~> (a ~> Ordering)) -> a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (InsertBySym2 x y) | |
| (SingI d1, SingI d2) => SingI (InsertBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (InsertBySym2 d1 d2) | |
| SuppressUnusedWarnings (InsertBySym2 a6989586621679848476 a6989586621679848477 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertBySym2 a6989586621679848476 a6989586621679848477 :: TyFun [a] [a] -> Type) (a6989586621679848478 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertBySym2 a6989586621679848476 a6989586621679848477 :: TyFun [a] [a] -> Type) (a6989586621679848478 :: [a]) = InsertBy a6989586621679848476 a6989586621679848477 a6989586621679848478 | |
type family InsertBySym3 (a6989586621679848476 :: (~>) a ((~>) a Ordering)) (a6989586621679848477 :: a) (a6989586621679848478 :: [a]) :: [a] where ... Source #
Equations
| InsertBySym3 a6989586621679848476 a6989586621679848477 a6989586621679848478 = InsertBy a6989586621679848476 a6989586621679848477 a6989586621679848478 |
data MaximumBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (t a) a) Source #
Instances
| SFoldable t => SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods | |
| SuppressUnusedWarnings (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680427062 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Foldable.Singletons type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680427062 :: a ~> (a ~> Ordering)) = MaximumBySym1 a6989586621680427062 :: TyFun (t a) a -> Type | |
data MaximumBySym1 (a6989586621680427062 :: (~>) a ((~>) a Ordering)) :: (~>) (t a) a Source #
Instances
| SFoldable t => SingI1 (MaximumBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (MaximumBySym1 x) | |
| (SFoldable t, SingI d) => SingI (MaximumBySym1 d :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing (MaximumBySym1 d) | |
| SuppressUnusedWarnings (MaximumBySym1 a6989586621680427062 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MaximumBySym1 a6989586621680427062 :: TyFun (t a) a -> Type) (a6989586621680427063 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MaximumBySym1 a6989586621680427062 :: TyFun (t a) a -> Type) (a6989586621680427063 :: t a) = MaximumBy a6989586621680427062 a6989586621680427063 | |
type family MaximumBySym2 (a6989586621680427062 :: (~>) a ((~>) a Ordering)) (a6989586621680427063 :: t a) :: a where ... Source #
Equations
| MaximumBySym2 a6989586621680427062 a6989586621680427063 = MaximumBy a6989586621680427062 a6989586621680427063 |
data MinimumBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (t a) a) Source #
Instances
| SFoldable t => SingI (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods | |
| SuppressUnusedWarnings (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680427042 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Foldable.Singletons type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680427042 :: a ~> (a ~> Ordering)) = MinimumBySym1 a6989586621680427042 :: TyFun (t a) a -> Type | |
data MinimumBySym1 (a6989586621680427042 :: (~>) a ((~>) a Ordering)) :: (~>) (t a) a Source #
Instances
| SFoldable t => SingI1 (MinimumBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (MinimumBySym1 x) | |
| (SFoldable t, SingI d) => SingI (MinimumBySym1 d :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods sing :: Sing (MinimumBySym1 d) | |
| SuppressUnusedWarnings (MinimumBySym1 a6989586621680427042 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MinimumBySym1 a6989586621680427042 :: TyFun (t a) a -> Type) (a6989586621680427043 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MinimumBySym1 a6989586621680427042 :: TyFun (t a) a -> Type) (a6989586621680427043 :: t a) = MinimumBy a6989586621680427042 a6989586621680427043 | |
type family MinimumBySym2 (a6989586621680427042 :: (~>) a ((~>) a Ordering)) (a6989586621680427043 :: t a) :: a where ... Source #
Equations
| MinimumBySym2 a6989586621680427042 a6989586621680427043 = MinimumBy a6989586621680427042 a6989586621680427043 |
data GenericLengthSym0 :: (~>) [a] i Source #
Instances
| SNum i => SingI (GenericLengthSym0 :: TyFun [a] i -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods | |
| SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a] i -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679847955 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679847955 :: [a]) = GenericLength a6989586621679847955 :: k2 | |
type family GenericLengthSym1 (a6989586621679847955 :: [a]) :: i where ... Source #
Equations
| GenericLengthSym1 a6989586621679847955 = GenericLength a6989586621679847955 |