| 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 | GHC2021 |
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 (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a]) :: Type
- type family Head (a :: [a]) :: a where ...
- sHead :: forall (t :: [a]). Sing t -> Sing (Apply HeadSym0 t :: a) :: Type
- type family Last (a :: [a]) :: a where ...
- sLast :: forall (t :: [a]). Sing t -> Sing (Apply LastSym0 t :: a) :: Type
- type family Tail (a :: [a]) :: [a] where ...
- sTail :: forall (t :: [a]). Sing t -> Sing (Apply TailSym0 t :: [a]) :: Type
- type family Init (a :: [a]) :: [a] where ...
- sInit :: forall (t :: [a]). Sing t -> Sing (Apply InitSym0 t :: [a]) :: Type
- type family Null (arg :: t a) :: Bool
- sNull :: SFoldable t => forall (t :: t a). Sing t -> Sing (Apply NullSym0 t :: Bool) :: Type
- type family Length (arg :: t a) :: Natural
- sLength :: SFoldable t => forall (t :: t a). Sing t -> Sing (Apply LengthSym0 t :: Natural) :: Type
- type family Map (a :: (~>) a b) (a :: [a]) :: [b] where ...
- sMap :: forall (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b]) :: Type
- type family Reverse (a :: [a]) :: [a] where ...
- sReverse :: forall (t :: [a]). Sing t -> Sing (Apply ReverseSym0 t :: [a]) :: Type
- type family Intersperse (a :: a) (a :: [a]) :: [a] where ...
- sIntersperse :: forall (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a]) :: Type
- type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ...
- sIntercalate :: forall (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a]) :: Type
- type family Transpose (a :: [[a]]) :: [[a]] where ...
- sTranspose :: forall (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]]) :: Type
- type family Subsequences (a :: [a]) :: [[a]] where ...
- sSubsequences :: forall (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]]) :: Type
- 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 :: SFoldable t => forall (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) :: Type
- type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
- sFoldl' :: SFoldable t => forall (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) :: Type
- type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
- sFoldl1 :: SFoldable t => forall (t :: (~>) a ((~>) a a)) (t :: t a). Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) :: Type
- type family Foldl1' (a :: (~>) a ((~>) a a)) (a :: [a]) :: a where ...
- sFoldl1' :: forall (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a) :: Type
- type family Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b
- sFoldr :: SFoldable t => forall (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) :: Type
- type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
- sFoldr1 :: SFoldable t => forall (t :: (~>) a ((~>) a a)) (t :: t a). Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) :: Type
- type family Concat (a :: t [a]) :: [a] where ...
- sConcat :: forall (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a]) :: Type
- type family ConcatMap (a :: (~>) a [b]) (a :: t a) :: [b] where ...
- sConcatMap :: forall (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) :: Type
- type family And (a :: t Bool) :: Bool where ...
- sAnd :: forall (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool) :: Type
- type family Or (a :: t Bool) :: Bool where ...
- sOr :: forall (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool) :: Type
- type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ...
- sAny :: forall (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool) :: Type
- type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ...
- sAll :: forall (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) :: Type
- type family Sum (arg :: t a) :: a
- sSum :: SFoldable t => forall (t :: t a). SNum a => Sing t -> Sing (Apply SumSym0 t :: a) :: Type
- type family Product (arg :: t a) :: a
- sProduct :: SFoldable t => forall (t :: t a). SNum a => Sing t -> Sing (Apply ProductSym0 t :: a) :: Type
- 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 (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b]) :: Type
- type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
- sScanl1 :: forall (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a]) :: Type
- type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: [b] where ...
- sScanr :: forall (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b]) :: Type
- type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
- sScanr1 :: forall (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a]) :: Type
- 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 (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
- type family Replicate (a :: Natural) (a :: a) :: [a] where ...
- sReplicate :: forall (t :: Natural) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a]) :: Type
- type family Unfoldr (a :: (~>) b (Maybe (a, b))) (a :: b) :: [a] where ...
- sUnfoldr :: forall (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a]) :: Type
- type family Take (a :: Natural) (a :: [a]) :: [a] where ...
- sTake :: forall (t :: Natural) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) :: Type
- type family Drop (a :: Natural) (a :: [a]) :: [a] where ...
- sDrop :: forall (t :: Natural) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) :: Type
- type family SplitAt (a :: Natural) (a :: [a]) :: ([a], [a]) where ...
- sSplitAt :: forall (t :: Natural) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) :: Type
- type family TakeWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sTakeWhile :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) :: Type
- type family DropWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sDropWhile :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) :: Type
- type family DropWhileEnd (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sDropWhileEnd :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a]) :: Type
- type family Span (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sSpan :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) :: Type
- type family Break (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sBreak :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) :: Type
- type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ...
- type family Group (a :: [a]) :: [[a]] where ...
- sGroup :: forall (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [[a]]) :: Type
- type family Inits (a :: [a]) :: [[a]] where ...
- sInits :: forall (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: [[a]]) :: Type
- type family Tails (a :: [a]) :: [[a]] where ...
- sTails :: forall (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: [[a]]) :: Type
- type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsPrefixOf :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) :: Type
- type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsSuffixOf :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) :: Type
- type family IsInfixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsInfixOf :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool) :: Type
- type family Elem (arg :: a) (arg :: t a) :: Bool
- sElem :: SFoldable t => forall (t :: a) (t :: t a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) :: Type
- type family NotElem (a :: a) (a :: t a) :: Bool where ...
- sNotElem :: forall (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) :: Type
- type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ...
- sLookup :: forall (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b) :: Type
- type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ...
- sFind :: forall (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a) :: Type
- type family Filter (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sFilter :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) :: Type
- type family Partition (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sPartition :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) :: Type
- type family (a :: [a]) !! (a :: Natural) :: a where ...
- (%!!) :: forall (t :: [a]) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) :: Type
- type family ElemIndex (a :: a) (a :: [a]) :: Maybe Natural where ...
- sElemIndex :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Natural) :: Type
- type family ElemIndices (a :: a) (a :: [a]) :: [Natural] where ...
- sElemIndices :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Natural]) :: Type
- type family FindIndex (a :: (~>) a Bool) (a :: [a]) :: Maybe Natural where ...
- sFindIndex :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Natural) :: Type
- type family FindIndices (a :: (~>) a Bool) (a :: [a]) :: [Natural] where ...
- sFindIndices :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Natural]) :: Type
- type family Zip (a :: [a]) (a :: [b]) :: [(a, b)] where ...
- sZip :: forall (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)]) :: Type
- type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ...
- sZip3 :: forall (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)]) :: Type
- 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 (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c]) :: Type
- type family ZipWith3 (a :: (~>) a ((~>) b ((~>) c d))) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ...
- sZipWith3 :: forall (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
- 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 (t :: [(a, b)]). Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b])) :: Type
- type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ...
- sUnzip3 :: forall (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c])) :: Type
- type family Unzip4 (a :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
- sUnzip4 :: forall (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d])) :: Type
- type family Unzip5 (a :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ...
- sUnzip5 :: forall (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e])) :: Type
- type family Unzip6 (a :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ...
- sUnzip6 :: forall (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f])) :: Type
- type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
- sUnzip7 :: forall (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g])) :: Type
- type family Unlines (a :: [Symbol]) :: Symbol where ...
- sUnlines :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnlinesSym0 t :: Symbol) :: Type
- type family Unwords (a :: [Symbol]) :: Symbol where ...
- sUnwords :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnwordsSym0 t :: Symbol) :: Type
- 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 (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a]) :: Type
- type family (a :: [a]) \\ (a :: [a]) :: [a] where ...
- (%\\) :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (\\@#@$) t) t :: [a]) :: Type
- type family Union (a :: [a]) (a :: [a]) :: [a] where ...
- sUnion :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a]) :: Type
- type family Intersect (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersect :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a]) :: Type
- type family Insert (a :: a) (a :: [a]) :: [a] where ...
- sInsert :: forall (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a]) :: Type
- type family Sort (a :: [a]) :: [a] where ...
- sSort :: forall (t :: [a]). SOrd a => Sing t -> Sing (Apply SortSym0 t :: [a]) :: Type
- type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [a] where ...
- sNubBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a]) :: Type
- type family DeleteBy (a :: (~>) a ((~>) a Bool)) (a :: a) (a :: [a]) :: [a] where ...
- sDeleteBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a]) :: Type
- type family DeleteFirstsBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sDeleteFirstsBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a]) :: Type
- type family UnionBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sUnionBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a]) :: Type
- type family IntersectBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersectBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a]) :: Type
- type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [[a]] where ...
- sGroupBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]]) :: Type
- type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: [a]) :: [a] where ...
- sSortBy :: forall (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a]) :: Type
- type family InsertBy (a :: (~>) a ((~>) a Ordering)) (a :: a) (a :: [a]) :: [a] where ...
- sInsertBy :: forall (t :: (~>) a ((~>) a Ordering)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a]) :: Type
- type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
- sMaximumBy :: forall (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) :: Type
- type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
- sMinimumBy :: forall (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) :: Type
- type family GenericLength (a :: [a]) :: i where ...
- sGenericLength :: forall (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i) :: Type
- type family NilSym0 :: [a :: Type] where ...
- data (:@#@$) :: (~>) a ((~>) [a] [a :: Type])
- data (:@#@$$) (a6989586621679037552 :: a) :: (~>) [a] [a :: Type]
- type family (a6989586621679037552 :: a) :@#@$$$ (a6989586621679037553 :: [a]) :: [a :: Type] where ...
- type family (a6989586621679144197 :: [a]) ++@#@$$$ (a6989586621679144198 :: [a]) :: [a] where ...
- data (++@#@$$) (a6989586621679144197 :: [a]) :: (~>) [a] [a]
- data (++@#@$) :: (~>) [a] ((~>) [a] [a])
- data HeadSym0 :: (~>) [a] a
- type family HeadSym1 (a6989586621679654300 :: [a]) :: a where ...
- data LastSym0 :: (~>) [a] a
- type family LastSym1 (a6989586621679654294 :: [a]) :: a where ...
- data TailSym0 :: (~>) [a] [a]
- type family TailSym1 (a6989586621679654290 :: [a]) :: [a] where ...
- data InitSym0 :: (~>) [a] [a]
- type family InitSym1 (a6989586621679654278 :: [a]) :: [a] where ...
- data NullSym0 :: (~>) (t a) Bool
- type family NullSym1 (a6989586621680110598 :: t a) :: Bool where ...
- data LengthSym0 :: (~>) (t a) Natural
- type family LengthSym1 (a6989586621680110601 :: t a) :: Natural where ...
- data MapSym0 :: (~>) ((~>) a b) ((~>) [a] [b])
- data MapSym1 (a6989586621679144206 :: (~>) a b) :: (~>) [a] [b]
- type family MapSym2 (a6989586621679144206 :: (~>) a b) (a6989586621679144207 :: [a]) :: [b] where ...
- data ReverseSym0 :: (~>) [a] [a]
- type family ReverseSym1 (a6989586621679654263 :: [a]) :: [a] where ...
- data IntersperseSym0 :: (~>) a ((~>) [a] [a])
- data IntersperseSym1 (a6989586621679654256 :: a) :: (~>) [a] [a]
- type family IntersperseSym2 (a6989586621679654256 :: a) (a6989586621679654257 :: [a]) :: [a] where ...
- data IntercalateSym0 :: (~>) [a] ((~>) [[a]] [a])
- data IntercalateSym1 (a6989586621679654249 :: [a]) :: (~>) [[a]] [a]
- type family IntercalateSym2 (a6989586621679654249 :: [a]) (a6989586621679654250 :: [[a]]) :: [a] where ...
- data TransposeSym0 :: (~>) [[a]] [[a]]
- type family TransposeSym1 (a6989586621679653150 :: [[a]]) :: [[a]] where ...
- data SubsequencesSym0 :: (~>) [a] [[a]]
- type family SubsequencesSym1 (a6989586621679654244 :: [a]) :: [[a]] where ...
- data PermutationsSym0 :: (~>) [a] [[a]]
- type family PermutationsSym1 (a6989586621679654170 :: [a]) :: [[a]] where ...
- data FoldlSym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) (t a) b))
- data FoldlSym1 (a6989586621680110573 :: (~>) b ((~>) a b)) :: (~>) b ((~>) (t a) b)
- data FoldlSym2 (a6989586621680110573 :: (~>) b ((~>) a b)) (a6989586621680110574 :: b) :: (~>) (t a) b
- type family FoldlSym3 (a6989586621680110573 :: (~>) b ((~>) a b)) (a6989586621680110574 :: b) (a6989586621680110575 :: t a) :: b where ...
- data Foldl'Sym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) (t a) b))
- data Foldl'Sym1 (a6989586621680110580 :: (~>) b ((~>) a b)) :: (~>) b ((~>) (t a) b)
- data Foldl'Sym2 (a6989586621680110580 :: (~>) b ((~>) a b)) (a6989586621680110581 :: b) :: (~>) (t a) b
- type family Foldl'Sym3 (a6989586621680110580 :: (~>) b ((~>) a b)) (a6989586621680110581 :: b) (a6989586621680110582 :: t a) :: b where ...
- data Foldl1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (t a) a)
- data Foldl1Sym1 (a6989586621680110591 :: (~>) a ((~>) a a)) :: (~>) (t a) a
- type family Foldl1Sym2 (a6989586621680110591 :: (~>) a ((~>) a a)) (a6989586621680110592 :: t a) :: a where ...
- data Foldl1'Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) [a] a)
- data Foldl1'Sym1 (a6989586621679654135 :: (~>) a ((~>) a a)) :: (~>) [a] a
- type family Foldl1'Sym2 (a6989586621679654135 :: (~>) a ((~>) a a)) (a6989586621679654136 :: [a]) :: a where ...
- data FoldrSym0 :: (~>) ((~>) a ((~>) b b)) ((~>) b ((~>) (t a) b))
- data FoldrSym1 (a6989586621680110559 :: (~>) a ((~>) b b)) :: (~>) b ((~>) (t a) b)
- data FoldrSym2 (a6989586621680110559 :: (~>) a ((~>) b b)) (a6989586621680110560 :: b) :: (~>) (t a) b
- type family FoldrSym3 (a6989586621680110559 :: (~>) a ((~>) b b)) (a6989586621680110560 :: b) (a6989586621680110561 :: t a) :: b where ...
- data Foldr1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (t a) a)
- data Foldr1Sym1 (a6989586621680110586 :: (~>) a ((~>) a a)) :: (~>) (t a) a
- type family Foldr1Sym2 (a6989586621680110586 :: (~>) a ((~>) a a)) (a6989586621680110587 :: t a) :: a where ...
- data ConcatSym0 :: (~>) (t [a]) [a]
- type family ConcatSym1 (a6989586621680110440 :: t [a]) :: [a] where ...
- data ConcatMapSym0 :: (~>) ((~>) a [b]) ((~>) (t a) [b])
- data ConcatMapSym1 (a6989586621680110429 :: (~>) a [b]) :: (~>) (t a) [b]
- type family ConcatMapSym2 (a6989586621680110429 :: (~>) a [b]) (a6989586621680110430 :: t a) :: [b] where ...
- data AndSym0 :: (~>) (t Bool) Bool
- type family AndSym1 (a6989586621680110424 :: t Bool) :: Bool where ...
- data OrSym0 :: (~>) (t Bool) Bool
- type family OrSym1 (a6989586621680110418 :: t Bool) :: Bool where ...
- data AnySym0 :: (~>) ((~>) a Bool) ((~>) (t a) Bool)
- data AnySym1 (a6989586621680110410 :: (~>) a Bool) :: (~>) (t a) Bool
- type family AnySym2 (a6989586621680110410 :: (~>) a Bool) (a6989586621680110411 :: t a) :: Bool where ...
- data AllSym0 :: (~>) ((~>) a Bool) ((~>) (t a) Bool)
- data AllSym1 (a6989586621680110401 :: (~>) a Bool) :: (~>) (t a) Bool
- type family AllSym2 (a6989586621680110401 :: (~>) a Bool) (a6989586621680110402 :: t a) :: Bool where ...
- data SumSym0 :: (~>) (t a) a
- type family SumSym1 (a6989586621680110615 :: t a) :: a where ...
- data ProductSym0 :: (~>) (t a) a
- type family ProductSym1 (a6989586621680110618 :: t a) :: a where ...
- data MaximumSym0 :: (~>) (t a) a
- type family MaximumSym1 (a6989586621680110609 :: t a) :: a where ...
- data MinimumSym0 :: (~>) (t a) a
- type family MinimumSym1 (a6989586621680110612 :: t a) :: a where ...
- data ScanlSym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) [a] [b]))
- data ScanlSym1 (a6989586621679654068 :: (~>) b ((~>) a b)) :: (~>) b ((~>) [a] [b])
- data ScanlSym2 (a6989586621679654068 :: (~>) b ((~>) a b)) (a6989586621679654069 :: b) :: (~>) [a] [b]
- type family ScanlSym3 (a6989586621679654068 :: (~>) b ((~>) a b)) (a6989586621679654069 :: b) (a6989586621679654070 :: [a]) :: [b] where ...
- data Scanl1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) [a] [a])
- data Scanl1Sym1 (a6989586621679654059 :: (~>) a ((~>) a a)) :: (~>) [a] [a]
- type family Scanl1Sym2 (a6989586621679654059 :: (~>) a ((~>) a a)) (a6989586621679654060 :: [a]) :: [a] where ...
- data ScanrSym0 :: (~>) ((~>) a ((~>) b b)) ((~>) b ((~>) [a] [b]))
- data ScanrSym1 (a6989586621679654041 :: (~>) a ((~>) b b)) :: (~>) b ((~>) [a] [b])
- data ScanrSym2 (a6989586621679654041 :: (~>) a ((~>) b b)) (a6989586621679654042 :: b) :: (~>) [a] [b]
- type family ScanrSym3 (a6989586621679654041 :: (~>) a ((~>) b b)) (a6989586621679654042 :: b) (a6989586621679654043 :: [a]) :: [b] where ...
- data Scanr1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) [a] [a])
- data Scanr1Sym1 (a6989586621679654021 :: (~>) a ((~>) a a)) :: (~>) [a] [a]
- type family Scanr1Sym2 (a6989586621679654021 :: (~>) a ((~>) a a)) (a6989586621679654022 :: [a]) :: [a] where ...
- data MapAccumLSym0 :: (~>) ((~>) a ((~>) b (a, c))) ((~>) a ((~>) (t b) (a, t c)))
- data MapAccumLSym1 (a6989586621680387583 :: (~>) a ((~>) b (a, c))) :: (~>) a ((~>) (t b) (a, t c))
- data MapAccumLSym2 (a6989586621680387583 :: (~>) a ((~>) b (a, c))) (a6989586621680387584 :: a) :: (~>) (t b) (a, t c)
- type family MapAccumLSym3 (a6989586621680387583 :: (~>) a ((~>) b (a, c))) (a6989586621680387584 :: a) (a6989586621680387585 :: t b) :: (a, t c) where ...
- data MapAccumRSym0 :: (~>) ((~>) a ((~>) b (a, c))) ((~>) a ((~>) (t b) (a, t c)))
- data MapAccumRSym1 (a6989586621680387573 :: (~>) a ((~>) b (a, c))) :: (~>) a ((~>) (t b) (a, t c))
- data MapAccumRSym2 (a6989586621680387573 :: (~>) a ((~>) b (a, c))) (a6989586621680387574 :: a) :: (~>) (t b) (a, t c)
- type family MapAccumRSym3 (a6989586621680387573 :: (~>) a ((~>) b (a, c))) (a6989586621680387574 :: a) (a6989586621680387575 :: t b) :: (a, t c) where ...
- data ReplicateSym0 :: (~>) Natural ((~>) a [a])
- data ReplicateSym1 (a6989586621679653158 :: Natural) :: (~>) a [a]
- type family ReplicateSym2 (a6989586621679653158 :: Natural) (a6989586621679653159 :: a) :: [a] where ...
- data UnfoldrSym0 :: (~>) ((~>) b (Maybe (a, b))) ((~>) b [a])
- data UnfoldrSym1 (a6989586621679653913 :: (~>) b (Maybe (a, b))) :: (~>) b [a]
- type family UnfoldrSym2 (a6989586621679653913 :: (~>) b (Maybe (a, b))) (a6989586621679653914 :: b) :: [a] where ...
- data TakeSym0 :: (~>) Natural ((~>) [a] [a])
- data TakeSym1 (a6989586621679653313 :: Natural) :: (~>) [a] [a]
- type family TakeSym2 (a6989586621679653313 :: Natural) (a6989586621679653314 :: [a]) :: [a] where ...
- data DropSym0 :: (~>) Natural ((~>) [a] [a])
- data DropSym1 (a6989586621679653300 :: Natural) :: (~>) [a] [a]
- type family DropSym2 (a6989586621679653300 :: Natural) (a6989586621679653301 :: [a]) :: [a] where ...
- data SplitAtSym0 :: (~>) Natural ((~>) [a] ([a], [a]))
- data SplitAtSym1 (a6989586621679653293 :: Natural) :: (~>) [a] ([a], [a])
- type family SplitAtSym2 (a6989586621679653293 :: Natural) (a6989586621679653294 :: [a]) :: ([a], [a]) where ...
- data TakeWhileSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a])
- data TakeWhileSym1 (a6989586621679653430 :: (~>) a Bool) :: (~>) [a] [a]
- type family TakeWhileSym2 (a6989586621679653430 :: (~>) a Bool) (a6989586621679653431 :: [a]) :: [a] where ...
- data DropWhileSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a])
- data DropWhileSym1 (a6989586621679653415 :: (~>) a Bool) :: (~>) [a] [a]
- type family DropWhileSym2 (a6989586621679653415 :: (~>) a Bool) (a6989586621679653416 :: [a]) :: [a] where ...
- data DropWhileEndSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a])
- data DropWhileEndSym1 (a6989586621679653398 :: (~>) a Bool) :: (~>) [a] [a]
- type family DropWhileEndSym2 (a6989586621679653398 :: (~>) a Bool) (a6989586621679653399 :: [a]) :: [a] where ...
- data SpanSym0 :: (~>) ((~>) a Bool) ((~>) [a] ([a], [a]))
- data SpanSym1 (a6989586621679653361 :: (~>) a Bool) :: (~>) [a] ([a], [a])
- type family SpanSym2 (a6989586621679653361 :: (~>) a Bool) (a6989586621679653362 :: [a]) :: ([a], [a]) where ...
- data BreakSym0 :: (~>) ((~>) a Bool) ((~>) [a] ([a], [a]))
- data BreakSym1 (a6989586621679653326 :: (~>) a Bool) :: (~>) [a] ([a], [a])
- type family BreakSym2 (a6989586621679653326 :: (~>) a Bool) (a6989586621679653327 :: [a]) :: ([a], [a]) where ...
- data StripPrefixSym0 :: (~>) [a] ((~>) [a] (Maybe [a]))
- data StripPrefixSym1 (a6989586621679805280 :: [a]) :: (~>) [a] (Maybe [a])
- type family StripPrefixSym2 (a6989586621679805280 :: [a]) (a6989586621679805281 :: [a]) :: Maybe [a] where ...
- data GroupSym0 :: (~>) [a] [[a]]
- type family GroupSym1 (a6989586621679653288 :: [a]) :: [[a]] where ...
- data InitsSym0 :: (~>) [a] [[a]]
- type family InitsSym1 (a6989586621679653903 :: [a]) :: [[a]] where ...
- data TailsSym0 :: (~>) [a] [[a]]
- type family TailsSym1 (a6989586621679653895 :: [a]) :: [[a]] where ...
- data IsPrefixOfSym0 :: (~>) [a] ((~>) [a] Bool)
- data IsPrefixOfSym1 (a6989586621679653887 :: [a]) :: (~>) [a] Bool
- type family IsPrefixOfSym2 (a6989586621679653887 :: [a]) (a6989586621679653888 :: [a]) :: Bool where ...
- data IsSuffixOfSym0 :: (~>) [a] ((~>) [a] Bool)
- data IsSuffixOfSym1 (a6989586621679653880 :: [a]) :: (~>) [a] Bool
- type family IsSuffixOfSym2 (a6989586621679653880 :: [a]) (a6989586621679653881 :: [a]) :: Bool where ...
- data IsInfixOfSym0 :: (~>) [a] ((~>) [a] Bool)
- data IsInfixOfSym1 (a6989586621679653873 :: [a]) :: (~>) [a] Bool
- type family IsInfixOfSym2 (a6989586621679653873 :: [a]) (a6989586621679653874 :: [a]) :: Bool where ...
- data ElemSym0 :: (~>) a ((~>) (t a) Bool)
- data ElemSym1 (a6989586621680110605 :: a) :: (~>) (t a) Bool
- type family ElemSym2 (a6989586621680110605 :: a) (a6989586621680110606 :: t a) :: Bool where ...
- data NotElemSym0 :: (~>) a ((~>) (t a) Bool)
- data NotElemSym1 (a6989586621680110352 :: a) :: (~>) (t a) Bool
- type family NotElemSym2 (a6989586621680110352 :: a) (a6989586621680110353 :: t a) :: Bool where ...
- data LookupSym0 :: (~>) a ((~>) [(a, b)] (Maybe b))
- data LookupSym1 (a6989586621679653221 :: a) :: (~>) [(a, b)] (Maybe b)
- type family LookupSym2 (a6989586621679653221 :: a) (a6989586621679653222 :: [(a, b)]) :: Maybe b where ...
- data FindSym0 :: (~>) ((~>) a Bool) ((~>) (t a) (Maybe a))
- data FindSym1 (a6989586621680110334 :: (~>) a Bool) :: (~>) (t a) (Maybe a)
- type family FindSym2 (a6989586621680110334 :: (~>) a Bool) (a6989586621680110335 :: t a) :: Maybe a where ...
- data FilterSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a])
- data FilterSym1 (a6989586621679653530 :: (~>) a Bool) :: (~>) [a] [a]
- type family FilterSym2 (a6989586621679653530 :: (~>) a Bool) (a6989586621679653531 :: [a]) :: [a] where ...
- data PartitionSym0 :: (~>) ((~>) a Bool) ((~>) [a] ([a], [a]))
- data PartitionSym1 (a6989586621679653214 :: (~>) a Bool) :: (~>) [a] ([a], [a])
- type family PartitionSym2 (a6989586621679653214 :: (~>) a Bool) (a6989586621679653215 :: [a]) :: ([a], [a]) where ...
- data (!!@#@$) :: (~>) [a] ((~>) Natural a)
- data (!!@#@$$) (a6989586621679653138 :: [a]) :: (~>) Natural a
- type family (a6989586621679653138 :: [a]) !!@#@$$$ (a6989586621679653139 :: Natural) :: a where ...
- data ElemIndexSym0 :: (~>) a ((~>) [a] (Maybe Natural))
- data ElemIndexSym1 (a6989586621679653514 :: a) :: (~>) [a] (Maybe Natural)
- type family ElemIndexSym2 (a6989586621679653514 :: a) (a6989586621679653515 :: [a]) :: Maybe Natural where ...
- data ElemIndicesSym0 :: (~>) a ((~>) [a] [Natural])
- data ElemIndicesSym1 (a6989586621679653505 :: a) :: (~>) [a] [Natural]
- type family ElemIndicesSym2 (a6989586621679653505 :: a) (a6989586621679653506 :: [a]) :: [Natural] where ...
- data FindIndexSym0 :: (~>) ((~>) a Bool) ((~>) [a] (Maybe Natural))
- data FindIndexSym1 (a6989586621679653496 :: (~>) a Bool) :: (~>) [a] (Maybe Natural)
- type family FindIndexSym2 (a6989586621679653496 :: (~>) a Bool) (a6989586621679653497 :: [a]) :: Maybe Natural where ...
- data FindIndicesSym0 :: (~>) ((~>) a Bool) ((~>) [a] [Natural])
- data FindIndicesSym1 (a6989586621679653473 :: (~>) a Bool) :: (~>) [a] [Natural]
- type family FindIndicesSym2 (a6989586621679653473 :: (~>) a Bool) (a6989586621679653474 :: [a]) :: [Natural] where ...
- data ZipSym0 :: (~>) [a] ((~>) [b] [(a, b)])
- data ZipSym1 (a6989586621679653848 :: [a]) :: (~>) [b] [(a, b)]
- type family ZipSym2 (a6989586621679653848 :: [a]) (a6989586621679653849 :: [b]) :: [(a, b)] where ...
- data Zip3Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] [(a, b, c)]))
- data Zip3Sym1 (a6989586621679653836 :: [a]) :: (~>) [b] ((~>) [c] [(a, b, c)])
- data Zip3Sym2 (a6989586621679653836 :: [a]) (a6989586621679653837 :: [b]) :: (~>) [c] [(a, b, c)]
- type family Zip3Sym3 (a6989586621679653836 :: [a]) (a6989586621679653837 :: [b]) (a6989586621679653838 :: [c]) :: [(a, b, c)] where ...
- data Zip4Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] [(a, b, c, d)])))
- data Zip4Sym1 (a6989586621679805269 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] [(a, b, c, d)]))
- data Zip4Sym2 (a6989586621679805269 :: [a]) (a6989586621679805270 :: [b]) :: (~>) [c] ((~>) [d] [(a, b, c, d)])
- data Zip4Sym3 (a6989586621679805269 :: [a]) (a6989586621679805270 :: [b]) (a6989586621679805271 :: [c]) :: (~>) [d] [(a, b, c, d)]
- type family Zip4Sym4 (a6989586621679805269 :: [a]) (a6989586621679805270 :: [b]) (a6989586621679805271 :: [c]) (a6989586621679805272 :: [d]) :: [(a, b, c, d)] where ...
- data Zip5Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [(a, b, c, d, e)]))))
- data Zip5Sym1 (a6989586621679805246 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [(a, b, c, d, e)])))
- data Zip5Sym2 (a6989586621679805246 :: [a]) (a6989586621679805247 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] [(a, b, c, d, e)]))
- data Zip5Sym3 (a6989586621679805246 :: [a]) (a6989586621679805247 :: [b]) (a6989586621679805248 :: [c]) :: (~>) [d] ((~>) [e] [(a, b, c, d, e)])
- data Zip5Sym4 (a6989586621679805246 :: [a]) (a6989586621679805247 :: [b]) (a6989586621679805248 :: [c]) (a6989586621679805249 :: [d]) :: (~>) [e] [(a, b, c, d, e)]
- type family Zip5Sym5 (a6989586621679805246 :: [a]) (a6989586621679805247 :: [b]) (a6989586621679805248 :: [c]) (a6989586621679805249 :: [d]) (a6989586621679805250 :: [e]) :: [(a, b, c, d, e)] where ...
- data Zip6Sym0 :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)])))))
- data Zip6Sym1 (a6989586621679805218 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)]))))
- data Zip6Sym2 (a6989586621679805218 :: [a]) (a6989586621679805219 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)])))
- data Zip6Sym3 (a6989586621679805218 :: [a]) (a6989586621679805219 :: [b]) (a6989586621679805220 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)]))
- data Zip6Sym4 (a6989586621679805218 :: [a]) (a6989586621679805219 :: [b]) (a6989586621679805220 :: [c]) (a6989586621679805221 :: [d]) :: (~>) [e] ((~>) [f] [(a, b, c, d, e, f)])
- data Zip6Sym5 (a6989586621679805218 :: [a]) (a6989586621679805219 :: [b]) (a6989586621679805220 :: [c]) (a6989586621679805221 :: [d]) (a6989586621679805222 :: [e]) :: (~>) [f] [(a, b, c, d, e, f)]
- type family Zip6Sym6 (a6989586621679805218 :: [a]) (a6989586621679805219 :: [b]) (a6989586621679805220 :: [c]) (a6989586621679805221 :: [d]) (a6989586621679805222 :: [e]) (a6989586621679805223 :: [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 (a6989586621679805185 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)])))))
- data Zip7Sym2 (a6989586621679805185 :: [a]) (a6989586621679805186 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)]))))
- data Zip7Sym3 (a6989586621679805185 :: [a]) (a6989586621679805186 :: [b]) (a6989586621679805187 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)])))
- data Zip7Sym4 (a6989586621679805185 :: [a]) (a6989586621679805186 :: [b]) (a6989586621679805187 :: [c]) (a6989586621679805188 :: [d]) :: (~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)]))
- data Zip7Sym5 (a6989586621679805185 :: [a]) (a6989586621679805186 :: [b]) (a6989586621679805187 :: [c]) (a6989586621679805188 :: [d]) (a6989586621679805189 :: [e]) :: (~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)])
- data Zip7Sym6 (a6989586621679805185 :: [a]) (a6989586621679805186 :: [b]) (a6989586621679805187 :: [c]) (a6989586621679805188 :: [d]) (a6989586621679805189 :: [e]) (a6989586621679805190 :: [f]) :: (~>) [g] [(a, b, c, d, e, f, g)]
- type family Zip7Sym7 (a6989586621679805185 :: [a]) (a6989586621679805186 :: [b]) (a6989586621679805187 :: [c]) (a6989586621679805188 :: [d]) (a6989586621679805189 :: [e]) (a6989586621679805190 :: [f]) (a6989586621679805191 :: [g]) :: [(a, b, c, d, e, f, g)] where ...
- data ZipWithSym0 :: (~>) ((~>) a ((~>) b c)) ((~>) [a] ((~>) [b] [c]))
- data ZipWithSym1 (a6989586621679653824 :: (~>) a ((~>) b c)) :: (~>) [a] ((~>) [b] [c])
- data ZipWithSym2 (a6989586621679653824 :: (~>) a ((~>) b c)) (a6989586621679653825 :: [a]) :: (~>) [b] [c]
- type family ZipWithSym3 (a6989586621679653824 :: (~>) a ((~>) b c)) (a6989586621679653825 :: [a]) (a6989586621679653826 :: [b]) :: [c] where ...
- data ZipWith3Sym0 :: (~>) ((~>) a ((~>) b ((~>) c d))) ((~>) [a] ((~>) [b] ((~>) [c] [d])))
- data ZipWith3Sym1 (a6989586621679653809 :: (~>) a ((~>) b ((~>) c d))) :: (~>) [a] ((~>) [b] ((~>) [c] [d]))
- data ZipWith3Sym2 (a6989586621679653809 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679653810 :: [a]) :: (~>) [b] ((~>) [c] [d])
- data ZipWith3Sym3 (a6989586621679653809 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679653810 :: [a]) (a6989586621679653811 :: [b]) :: (~>) [c] [d]
- type family ZipWith3Sym4 (a6989586621679653809 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679653810 :: [a]) (a6989586621679653811 :: [b]) (a6989586621679653812 :: [c]) :: [d] where ...
- data ZipWith4Sym0 :: (~>) ((~>) a ((~>) b ((~>) c ((~>) d e)))) ((~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] [e]))))
- data ZipWith4Sym1 (a6989586621679805149 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] [e])))
- data ZipWith4Sym2 (a6989586621679805149 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679805150 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] [e]))
- data ZipWith4Sym3 (a6989586621679805149 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679805150 :: [a]) (a6989586621679805151 :: [b]) :: (~>) [c] ((~>) [d] [e])
- data ZipWith4Sym4 (a6989586621679805149 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679805150 :: [a]) (a6989586621679805151 :: [b]) (a6989586621679805152 :: [c]) :: (~>) [d] [e]
- type family ZipWith4Sym5 (a6989586621679805149 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679805150 :: [a]) (a6989586621679805151 :: [b]) (a6989586621679805152 :: [c]) (a6989586621679805153 :: [d]) :: [e] where ...
- data ZipWith5Sym0 :: (~>) ((~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) ((~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [f])))))
- data ZipWith5Sym1 (a6989586621679805126 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [f]))))
- data ZipWith5Sym2 (a6989586621679805126 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679805127 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [f])))
- data ZipWith5Sym3 (a6989586621679805126 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679805127 :: [a]) (a6989586621679805128 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] [f]))
- data ZipWith5Sym4 (a6989586621679805126 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679805127 :: [a]) (a6989586621679805128 :: [b]) (a6989586621679805129 :: [c]) :: (~>) [d] ((~>) [e] [f])
- data ZipWith5Sym5 (a6989586621679805126 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679805127 :: [a]) (a6989586621679805128 :: [b]) (a6989586621679805129 :: [c]) (a6989586621679805130 :: [d]) :: (~>) [e] [f]
- type family ZipWith5Sym6 (a6989586621679805126 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679805127 :: [a]) (a6989586621679805128 :: [b]) (a6989586621679805129 :: [c]) (a6989586621679805130 :: [d]) (a6989586621679805131 :: [e]) :: [f] where ...
- data ZipWith6Sym0 :: (~>) ((~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) ((~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g]))))))
- data ZipWith6Sym1 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g])))))
- data ZipWith6Sym2 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679805100 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g]))))
- data ZipWith6Sym3 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679805100 :: [a]) (a6989586621679805101 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g])))
- data ZipWith6Sym4 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679805100 :: [a]) (a6989586621679805101 :: [b]) (a6989586621679805102 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] [g]))
- data ZipWith6Sym5 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679805100 :: [a]) (a6989586621679805101 :: [b]) (a6989586621679805102 :: [c]) (a6989586621679805103 :: [d]) :: (~>) [e] ((~>) [f] [g])
- data ZipWith6Sym6 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679805100 :: [a]) (a6989586621679805101 :: [b]) (a6989586621679805102 :: [c]) (a6989586621679805103 :: [d]) (a6989586621679805104 :: [e]) :: (~>) [f] [g]
- type family ZipWith6Sym7 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679805100 :: [a]) (a6989586621679805101 :: [b]) (a6989586621679805102 :: [c]) (a6989586621679805103 :: [d]) (a6989586621679805104 :: [e]) (a6989586621679805105 :: [f]) :: [g] where ...
- data ZipWith7Sym0 :: (~>) ((~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) ((~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h])))))))
- data ZipWith7Sym1 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h]))))))
- data ZipWith7Sym2 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h])))))
- data ZipWith7Sym3 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) (a6989586621679805070 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h]))))
- data ZipWith7Sym4 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) (a6989586621679805070 :: [b]) (a6989586621679805071 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h])))
- data ZipWith7Sym5 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) (a6989586621679805070 :: [b]) (a6989586621679805071 :: [c]) (a6989586621679805072 :: [d]) :: (~>) [e] ((~>) [f] ((~>) [g] [h]))
- data ZipWith7Sym6 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) (a6989586621679805070 :: [b]) (a6989586621679805071 :: [c]) (a6989586621679805072 :: [d]) (a6989586621679805073 :: [e]) :: (~>) [f] ((~>) [g] [h])
- data ZipWith7Sym7 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) (a6989586621679805070 :: [b]) (a6989586621679805071 :: [c]) (a6989586621679805072 :: [d]) (a6989586621679805073 :: [e]) (a6989586621679805074 :: [f]) :: (~>) [g] [h]
- type family ZipWith7Sym8 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) (a6989586621679805070 :: [b]) (a6989586621679805071 :: [c]) (a6989586621679805072 :: [d]) (a6989586621679805073 :: [e]) (a6989586621679805074 :: [f]) (a6989586621679805075 :: [g]) :: [h] where ...
- data UnzipSym0 :: (~>) [(a, b)] ([a], [b])
- type family UnzipSym1 (a6989586621679653790 :: [(a, b)]) :: ([a], [b]) where ...
- data Unzip3Sym0 :: (~>) [(a, b, c)] ([a], [b], [c])
- type family Unzip3Sym1 (a6989586621679653772 :: [(a, b, c)]) :: ([a], [b], [c]) where ...
- data Unzip4Sym0 :: (~>) [(a, b, c, d)] ([a], [b], [c], [d])
- type family Unzip4Sym1 (a6989586621679653752 :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
- data Unzip5Sym0 :: (~>) [(a, b, c, d, e)] ([a], [b], [c], [d], [e])
- type family Unzip5Sym1 (a6989586621679653730 :: [(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 (a6989586621679653706 :: [(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 (a6989586621679653680 :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
- data UnlinesSym0 :: (~>) [Symbol] Symbol
- type family UnlinesSym1 (a6989586621679653675 :: [Symbol]) :: Symbol where ...
- data UnwordsSym0 :: (~>) [Symbol] Symbol
- type family UnwordsSym1 (a6989586621679653665 :: [Symbol]) :: Symbol where ...
- data NubSym0 :: (~>) [a] [a]
- type family NubSym1 (a6989586621679653121 :: [a]) :: [a] where ...
- data DeleteSym0 :: (~>) a ((~>) [a] [a])
- data DeleteSym1 (a6989586621679653659 :: a) :: (~>) [a] [a]
- type family DeleteSym2 (a6989586621679653659 :: a) (a6989586621679653660 :: [a]) :: [a] where ...
- data (\\@#@$) :: (~>) [a] ((~>) [a] [a])
- data (\\@#@$$) (a6989586621679653648 :: [a]) :: (~>) [a] [a]
- type family (a6989586621679653648 :: [a]) \\@#@$$$ (a6989586621679653649 :: [a]) :: [a] where ...
- data UnionSym0 :: (~>) [a] ((~>) [a] [a])
- data UnionSym1 (a6989586621679653075 :: [a]) :: (~>) [a] [a]
- type family UnionSym2 (a6989586621679653075 :: [a]) (a6989586621679653076 :: [a]) :: [a] where ...
- data IntersectSym0 :: (~>) [a] ((~>) [a] [a])
- data IntersectSym1 (a6989586621679653466 :: [a]) :: (~>) [a] [a]
- type family IntersectSym2 (a6989586621679653466 :: [a]) (a6989586621679653467 :: [a]) :: [a] where ...
- data InsertSym0 :: (~>) a ((~>) [a] [a])
- data InsertSym1 (a6989586621679653268 :: a) :: (~>) [a] [a]
- type family InsertSym2 (a6989586621679653268 :: a) (a6989586621679653269 :: [a]) :: [a] where ...
- data SortSym0 :: (~>) [a] [a]
- type family SortSym1 (a6989586621679653263 :: [a]) :: [a] where ...
- data NubBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] [a])
- data NubBySym1 (a6989586621679653103 :: (~>) a ((~>) a Bool)) :: (~>) [a] [a]
- type family NubBySym2 (a6989586621679653103 :: (~>) a ((~>) a Bool)) (a6989586621679653104 :: [a]) :: [a] where ...
- data DeleteBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) a ((~>) [a] [a]))
- data DeleteBySym1 (a6989586621679653629 :: (~>) a ((~>) a Bool)) :: (~>) a ((~>) [a] [a])
- data DeleteBySym2 (a6989586621679653629 :: (~>) a ((~>) a Bool)) (a6989586621679653630 :: a) :: (~>) [a] [a]
- type family DeleteBySym3 (a6989586621679653629 :: (~>) a ((~>) a Bool)) (a6989586621679653630 :: a) (a6989586621679653631 :: [a]) :: [a] where ...
- data DeleteFirstsBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] ((~>) [a] [a]))
- data DeleteFirstsBySym1 (a6989586621679653619 :: (~>) a ((~>) a Bool)) :: (~>) [a] ((~>) [a] [a])
- data DeleteFirstsBySym2 (a6989586621679653619 :: (~>) a ((~>) a Bool)) (a6989586621679653620 :: [a]) :: (~>) [a] [a]
- type family DeleteFirstsBySym3 (a6989586621679653619 :: (~>) a ((~>) a Bool)) (a6989586621679653620 :: [a]) (a6989586621679653621 :: [a]) :: [a] where ...
- data UnionBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] ((~>) [a] [a]))
- data UnionBySym1 (a6989586621679653083 :: (~>) a ((~>) a Bool)) :: (~>) [a] ((~>) [a] [a])
- data UnionBySym2 (a6989586621679653083 :: (~>) a ((~>) a Bool)) (a6989586621679653084 :: [a]) :: (~>) [a] [a]
- type family UnionBySym3 (a6989586621679653083 :: (~>) a ((~>) a Bool)) (a6989586621679653084 :: [a]) (a6989586621679653085 :: [a]) :: [a] where ...
- data IntersectBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] ((~>) [a] [a]))
- data IntersectBySym1 (a6989586621679653444 :: (~>) a ((~>) a Bool)) :: (~>) [a] ((~>) [a] [a])
- data IntersectBySym2 (a6989586621679653444 :: (~>) a ((~>) a Bool)) (a6989586621679653445 :: [a]) :: (~>) [a] [a]
- type family IntersectBySym3 (a6989586621679653444 :: (~>) a ((~>) a Bool)) (a6989586621679653445 :: [a]) (a6989586621679653446 :: [a]) :: [a] where ...
- data GroupBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] [[a]])
- data GroupBySym1 (a6989586621679653236 :: (~>) a ((~>) a Bool)) :: (~>) [a] [[a]]
- type family GroupBySym2 (a6989586621679653236 :: (~>) a ((~>) a Bool)) (a6989586621679653237 :: [a]) :: [[a]] where ...
- data SortBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) [a] [a])
- data SortBySym1 (a6989586621679653607 :: (~>) a ((~>) a Ordering)) :: (~>) [a] [a]
- type family SortBySym2 (a6989586621679653607 :: (~>) a ((~>) a Ordering)) (a6989586621679653608 :: [a]) :: [a] where ...
- data InsertBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) a ((~>) [a] [a]))
- data InsertBySym1 (a6989586621679653587 :: (~>) a ((~>) a Ordering)) :: (~>) a ((~>) [a] [a])
- data InsertBySym2 (a6989586621679653587 :: (~>) a ((~>) a Ordering)) (a6989586621679653588 :: a) :: (~>) [a] [a]
- type family InsertBySym3 (a6989586621679653587 :: (~>) a ((~>) a Ordering)) (a6989586621679653588 :: a) (a6989586621679653589 :: [a]) :: [a] where ...
- data MaximumBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (t a) a)
- data MaximumBySym1 (a6989586621680110381 :: (~>) a ((~>) a Ordering)) :: (~>) (t a) a
- type family MaximumBySym2 (a6989586621680110381 :: (~>) a ((~>) a Ordering)) (a6989586621680110382 :: t a) :: a where ...
- data MinimumBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (t a) a)
- data MinimumBySym1 (a6989586621680110361 :: (~>) a ((~>) a Ordering)) :: (~>) (t a) a
- type family MinimumBySym2 (a6989586621680110361 :: (~>) a ((~>) a Ordering)) (a6989586621680110362 :: t a) :: a where ...
- data GenericLengthSym0 :: (~>) [a] i
- type family GenericLengthSym1 (a6989586621679653066 :: [a]) :: i where ...
The singleton for lists
type family Sing :: k -> Type #
The singleton kind-indexed type family.
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 Methods testCoercion :: forall (a0 :: k) (b :: k). SList a0 -> SList b -> Maybe (Coercion a0 b) | |
| (SDecide a, SDecide [a]) => TestEquality (SList :: [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods testEquality :: forall (a0 :: k) (b :: k). SList a0 -> SList b -> Maybe (a0 :~: b) | |
| (ShowSing a, ShowSing [a]) => Show (SList z) Source # | |
Basic functions
(%++) :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a]) :: Type infixr 5 Source #
type family Null (arg :: t a) :: Bool Source #
Instances
| type Null (a2 :: Identity a1) Source # | |
Defined in Data.Functor.Identity.Singletons type Null (a2 :: Identity a1) | |
| type Null (arg :: First a) Source # | |
Defined in Data.Foldable.Singletons type Null (arg :: First a) | |
| type Null (arg :: Last a) Source # | |
Defined in Data.Foldable.Singletons type Null (arg :: Last a) | |
| type Null (arg :: First a) Source # | |
Defined in Data.Semigroup.Singletons type Null (arg :: First a) | |
| type Null (arg :: Last a) Source # | |
Defined in Data.Semigroup.Singletons type Null (arg :: Last a) | |
| type Null (arg :: Max a) Source # | |
Defined in Data.Semigroup.Singletons type Null (arg :: Max a) | |
| type Null (arg :: Min a) Source # | |
Defined in Data.Semigroup.Singletons type Null (arg :: Min a) | |
| type Null (a2 :: Dual a1) Source # | |
Defined in Data.Foldable.Singletons type Null (a2 :: Dual a1) | |
| type Null (a2 :: Product a1) Source # | |
Defined in Data.Foldable.Singletons type Null (a2 :: Product a1) | |
| type Null (a2 :: Sum a1) Source # | |
Defined in Data.Foldable.Singletons type Null (a2 :: Sum a1) | |
| type Null (arg :: NonEmpty a) Source # | |
Defined in Data.Foldable.Singletons type Null (arg :: NonEmpty a) | |
| type Null (arg :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons type Null (arg :: Maybe a) | |
| type Null (a2 :: [a1]) Source # | |
Defined in Data.Foldable.Singletons type Null (a2 :: [a1]) | |
| type Null (a3 :: Either a1 a2) Source # | |
Defined in Data.Foldable.Singletons type Null (a3 :: Either a1 a2) | |
| type Null (a2 :: Proxy a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Null (arg :: Arg a1 a2) Source # | |
Defined in Data.Semigroup.Singletons type Null (arg :: Arg a1 a2) | |
| type Null (arg :: (a1, a2)) Source # | |
Defined in Data.Foldable.Singletons type Null (arg :: (a1, a2)) | |
| type Null (arg :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Null (arg :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons type Null (arg :: Product f g a) | |
| type Null (arg :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons type Null (arg :: Sum f g a) | |
| type Null (arg :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons type Null (arg :: Compose f g a) | |
sNull :: SFoldable t => forall (t :: t a). Sing t -> Sing (Apply NullSym0 t :: Bool) :: Type Source #
type family Length (arg :: t a) :: Natural Source #
Instances
| type Length (a2 :: Identity a1) Source # | |
Defined in Data.Functor.Identity.Singletons type Length (a2 :: Identity a1) | |
| type Length (arg :: First a) Source # | |
Defined in Data.Foldable.Singletons type Length (arg :: First a) | |
| type Length (arg :: Last a) Source # | |
Defined in Data.Foldable.Singletons type Length (arg :: Last a) | |
| type Length (arg :: First a) Source # | |
Defined in Data.Semigroup.Singletons type Length (arg :: First a) | |
| type Length (arg :: Last a) Source # | |
Defined in Data.Semigroup.Singletons type Length (arg :: Last a) | |
| type Length (arg :: Max a) Source # | |
Defined in Data.Semigroup.Singletons type Length (arg :: Max a) | |
| type Length (arg :: Min a) Source # | |
Defined in Data.Semigroup.Singletons type Length (arg :: Min a) | |
| type Length (a2 :: Dual a1) Source # | |
Defined in Data.Foldable.Singletons type Length (a2 :: Dual a1) | |
| type Length (a2 :: Product a1) Source # | |
Defined in Data.Foldable.Singletons type Length (a2 :: Product a1) | |
| type Length (a2 :: Sum a1) Source # | |
Defined in Data.Foldable.Singletons type Length (a2 :: Sum a1) | |
| type Length (arg :: NonEmpty a) Source # | |
Defined in Data.Foldable.Singletons type Length (arg :: NonEmpty a) | |
| type Length (arg :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons type Length (arg :: Maybe a) | |
| type Length (a2 :: [a1]) Source # | |
Defined in Data.Foldable.Singletons type Length (a2 :: [a1]) | |
| type Length (a3 :: Either a1 a2) Source # | |
Defined in Data.Foldable.Singletons type Length (a3 :: Either a1 a2) | |
| type Length (a2 :: Proxy a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Length (arg :: Arg a1 a2) Source # | |
Defined in Data.Semigroup.Singletons type Length (arg :: Arg a1 a2) | |
| type Length (arg :: (a1, a2)) Source # | |
Defined in Data.Foldable.Singletons type Length (arg :: (a1, a2)) | |
| type Length (arg :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Length (arg :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons type Length (arg :: Product f g a) | |
| type Length (arg :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons type Length (arg :: Sum f g a) | |
| type Length (arg :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons type Length (arg :: Compose f g a) | |
sLength :: SFoldable t => forall (t :: t a). Sing t -> Sing (Apply LengthSym0 t :: Natural) :: Type Source #
List transformations
sMap :: forall (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b]) :: Type 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 (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a]) :: Type Source #
type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ... Source #
Equations
| Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) |
sIntercalate :: forall (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a]) :: Type Source #
sTranspose :: forall (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]]) :: Type Source #
type family Subsequences (a :: [a]) :: [[a]] where ... Source #
sSubsequences :: forall (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]]) :: Type Source #
type family Permutations (a :: [a]) :: [[a]] where ... Source #
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 (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: 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 (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (arg :: b ~> (a1 ~> b)) (arg1 :: b) (arg2 :: 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 (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Proxy a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldl :: SFoldable t => forall (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) :: Type 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' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: 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' (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' (arg :: b ~> (a1 ~> b)) (arg1 :: b) (arg2 :: 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' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldl' :: SFoldable t => forall (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) :: Type 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 (arg :: a ~> (a ~> a)) (arg1 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: 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 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (arg :: a1 ~> (a1 ~> a1)) (arg1 :: 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 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldl1 :: SFoldable t => forall (t :: (~>) a ((~>) a a)) (t :: t a). Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) :: Type Source #
sFoldl1' :: forall (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a) :: Type 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 (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 (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Const m a1) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldr (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldr (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldr (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldr :: SFoldable t => forall (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) :: Type 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 (arg :: a ~> (a ~> a)) (arg1 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: 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 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (arg :: a1 ~> (a1 ~> a1)) (arg1 :: 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 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldr1 :: SFoldable t => forall (t :: (~>) a ((~>) a a)) (t :: t a). Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) :: Type Source #
Special folds
sConcat :: forall (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a]) :: Type Source #
sConcatMap :: forall (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) :: Type Source #
type family And (a :: t Bool) :: Bool where ... Source #
Equations
| And a_6989586621680110420 = Apply (Apply (Apply (.@#@$) GetAllSym0) (Apply FoldMapSym0 All_Sym0)) a_6989586621680110420 |
sAnd :: forall (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool) :: Type Source #
type family Or (a :: t Bool) :: Bool where ... Source #
Equations
| Or a_6989586621680110414 = Apply (Apply (Apply (.@#@$) GetAnySym0) (Apply FoldMapSym0 Any_Sym0)) a_6989586621680110414 |
sOr :: forall (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool) :: Type Source #
sAny :: forall (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool) :: Type Source #
sAll :: forall (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) :: Type Source #
type family Sum (arg :: t a) :: a Source #
Instances
| type Sum (a :: Identity k2) Source # | |
Defined in Data.Functor.Identity.Singletons type Sum (a :: Identity k2) | |
| type Sum (arg :: First a) Source # | |
Defined in Data.Foldable.Singletons type Sum (arg :: First a) | |
| type Sum (arg :: Last a) Source # | |
Defined in Data.Foldable.Singletons type Sum (arg :: Last a) | |
| type Sum (arg :: First a) Source # | |
Defined in Data.Semigroup.Singletons type Sum (arg :: First a) | |
| type Sum (arg :: Last a) Source # | |
Defined in Data.Semigroup.Singletons type Sum (arg :: Last a) | |
| type Sum (arg :: Max a) Source # | |
Defined in Data.Semigroup.Singletons type Sum (arg :: Max a) | |
| type Sum (arg :: Min a) Source # | |
Defined in Data.Semigroup.Singletons type Sum (arg :: Min a) | |
| type Sum (a :: Dual k2) Source # | |
Defined in Data.Foldable.Singletons type Sum (a :: Dual k2) | |
| type Sum (a :: Product k2) Source # | |
Defined in Data.Foldable.Singletons type Sum (a :: Product k2) | |
| type Sum (a :: Sum k2) Source # | |
Defined in Data.Foldable.Singletons type Sum (a :: Sum k2) | |
| type Sum (arg :: NonEmpty a) Source # | |
Defined in Data.Foldable.Singletons type Sum (arg :: NonEmpty a) | |
| type Sum (arg :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons type Sum (arg :: Maybe a) | |
| type Sum (a :: [k2]) Source # | |
Defined in Data.Foldable.Singletons type Sum (a :: [k2]) | |
| type Sum (arg :: Either a1 a2) Source # | |
Defined in Data.Foldable.Singletons type Sum (arg :: Either a1 a2) | |
| type Sum (a :: Proxy k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Sum (arg :: Arg a1 a2) Source # | |
Defined in Data.Semigroup.Singletons type Sum (arg :: Arg a1 a2) | |
| type Sum (arg :: (a1, a2)) Source # | |
Defined in Data.Foldable.Singletons type Sum (arg :: (a1, a2)) | |
| type Sum (arg :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Sum (arg :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons type Sum (arg :: Product f g a) | |
| type Sum (arg :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons type Sum (arg :: Sum f g a) | |
| type Sum (arg :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons type Sum (arg :: Compose f g a) | |
sSum :: SFoldable t => forall (t :: t a). SNum a => Sing t -> Sing (Apply SumSym0 t :: a) :: Type Source #
type family Product (arg :: t a) :: a Source #
Instances
| type Product (a :: Identity k2) Source # | |
Defined in Data.Functor.Identity.Singletons type Product (a :: Identity k2) | |
| type Product (arg :: First a) Source # | |
Defined in Data.Foldable.Singletons type Product (arg :: First a) | |
| type Product (arg :: Last a) Source # | |
Defined in Data.Foldable.Singletons type Product (arg :: Last a) | |
| type Product (arg :: First a) Source # | |
Defined in Data.Semigroup.Singletons type Product (arg :: First a) | |
| type Product (arg :: Last a) Source # | |
Defined in Data.Semigroup.Singletons type Product (arg :: Last a) | |
| type Product (arg :: Max a) Source # | |
Defined in Data.Semigroup.Singletons type Product (arg :: Max a) | |
| type Product (arg :: Min a) Source # | |
Defined in Data.Semigroup.Singletons type Product (arg :: Min a) | |
| type Product (a :: Dual k2) Source # | |
Defined in Data.Foldable.Singletons type Product (a :: Dual k2) | |
| type Product (a :: Product k2) Source # | |
Defined in Data.Foldable.Singletons type Product (a :: Product k2) | |
| type Product (a :: Sum k2) Source # | |
Defined in Data.Foldable.Singletons type Product (a :: Sum k2) | |
| type Product (arg :: NonEmpty a) Source # | |
Defined in Data.Foldable.Singletons type Product (arg :: NonEmpty a) | |
| type Product (arg :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons type Product (arg :: Maybe a) | |
| type Product (a :: [k2]) Source # | |
Defined in Data.Foldable.Singletons type Product (a :: [k2]) | |
| type Product (arg :: Either a1 a2) Source # | |
Defined in Data.Foldable.Singletons type Product (arg :: Either a1 a2) | |
| type Product (a :: Proxy k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Product (arg :: Arg a1 a2) Source # | |
Defined in Data.Semigroup.Singletons type Product (arg :: Arg a1 a2) | |
| type Product (arg :: (a1, a2)) Source # | |
Defined in Data.Foldable.Singletons type Product (arg :: (a1, a2)) | |
| type Product (arg :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Product (arg :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons type Product (arg :: Product f g a) | |
| type Product (arg :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons type Product (arg :: Sum f g a) | |
| type Product (arg :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons type Product (arg :: Compose f g a) | |
sProduct :: SFoldable t => forall (t :: t a). SNum a => Sing t -> Sing (Apply ProductSym0 t :: a) :: Type Source #
type family Maximum (arg :: t a) :: a Source #
Instances
| type Maximum (a :: Identity k2) Source # | |
Defined in Data.Functor.Identity.Singletons type Maximum (a :: Identity k2) | |
| type Maximum (arg :: First a) Source # | |
Defined in Data.Foldable.Singletons type Maximum (arg :: First a) | |
| type Maximum (arg :: Last a) Source # | |
Defined in Data.Foldable.Singletons type Maximum (arg :: Last a) | |
| type Maximum (arg :: First a) Source # | |
Defined in Data.Semigroup.Singletons type Maximum (arg :: First a) | |
| type Maximum (arg :: Last a) Source # | |
Defined in Data.Semigroup.Singletons type Maximum (arg :: Last a) | |
| type Maximum (arg :: Max a) Source # | |
Defined in Data.Semigroup.Singletons type Maximum (arg :: Max a) | |
| type Maximum (arg :: Min a) Source # | |
Defined in Data.Semigroup.Singletons type Maximum (arg :: Min a) | |
| type Maximum (a :: Dual k2) Source # | |
Defined in Data.Foldable.Singletons type Maximum (a :: Dual k2) | |
| type Maximum (a :: Product k2) Source # | |
Defined in Data.Foldable.Singletons type Maximum (a :: Product k2) | |
| type Maximum (a :: Sum k2) Source # | |
Defined in Data.Foldable.Singletons type Maximum (a :: Sum k2) | |
| type Maximum (arg :: NonEmpty a) Source # | |
Defined in Data.Foldable.Singletons type Maximum (arg :: NonEmpty a) | |
| type Maximum (arg :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons type Maximum (arg :: Maybe a) | |
| type Maximum (a :: [k2]) Source # | |
Defined in Data.Foldable.Singletons type Maximum (a :: [k2]) | |
| type Maximum (arg :: Either a1 a2) Source # | |
Defined in Data.Foldable.Singletons type Maximum (arg :: Either a1 a2) | |
| type Maximum (arg :: Proxy a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Maximum (arg :: Arg a1 a2) Source # | |
Defined in Data.Semigroup.Singletons type Maximum (arg :: Arg a1 a2) | |
| type Maximum (arg :: (a1, a2)) Source # | |
Defined in Data.Foldable.Singletons type Maximum (arg :: (a1, a2)) | |
| type Maximum (arg :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Maximum (arg :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons type Maximum (arg :: Product f g a) | |
| type Maximum (arg :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons type Maximum (arg :: Sum f g a) | |
| type Maximum (arg :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons type Maximum (arg :: Compose f g a) | |
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
| type Minimum (a :: Identity k2) Source # | |
Defined in Data.Functor.Identity.Singletons type Minimum (a :: Identity k2) | |
| type Minimum (arg :: First a) Source # | |
Defined in Data.Foldable.Singletons type Minimum (arg :: First a) | |
| type Minimum (arg :: Last a) Source # | |
Defined in Data.Foldable.Singletons type Minimum (arg :: Last a) | |
| type Minimum (arg :: First a) Source # | |
Defined in Data.Semigroup.Singletons type Minimum (arg :: First a) | |
| type Minimum (arg :: Last a) Source # | |
Defined in Data.Semigroup.Singletons type Minimum (arg :: Last a) | |
| type Minimum (arg :: Max a) Source # | |
Defined in Data.Semigroup.Singletons type Minimum (arg :: Max a) | |
| type Minimum (arg :: Min a) Source # | |
Defined in Data.Semigroup.Singletons type Minimum (arg :: Min a) | |
| type Minimum (a :: Dual k2) Source # | |
Defined in Data.Foldable.Singletons type Minimum (a :: Dual k2) | |
| type Minimum (a :: Product k2) Source # | |
Defined in Data.Foldable.Singletons type Minimum (a :: Product k2) | |
| type Minimum (a :: Sum k2) Source # | |
Defined in Data.Foldable.Singletons type Minimum (a :: Sum k2) | |
| type Minimum (arg :: NonEmpty a) Source # | |
Defined in Data.Foldable.Singletons type Minimum (arg :: NonEmpty a) | |
| type Minimum (arg :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons type Minimum (arg :: Maybe a) | |
| type Minimum (a :: [k2]) Source # | |
Defined in Data.Foldable.Singletons type Minimum (a :: [k2]) | |
| type Minimum (arg :: Either a1 a2) Source # | |
Defined in Data.Foldable.Singletons type Minimum (arg :: Either a1 a2) | |
| type Minimum (arg :: Proxy a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Minimum (arg :: Arg a1 a2) Source # | |
Defined in Data.Semigroup.Singletons type Minimum (arg :: Arg a1 a2) | |
| type Minimum (arg :: (a1, a2)) Source # | |
Defined in Data.Foldable.Singletons type Minimum (arg :: (a1, a2)) | |
| type Minimum (arg :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Minimum (arg :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons type Minimum (arg :: Product f g a) | |
| type Minimum (arg :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons type Minimum (arg :: Sum f g a) | |
| type Minimum (arg :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons type Minimum (arg :: Compose f g a) | |
sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a) Source #
Building lists
Scans
sScanl :: forall (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b]) :: Type Source #
sScanl1 :: forall (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a]) :: Type Source #
sScanr :: forall (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b]) :: Type 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_6989586621679650009 wild_6989586621679650011)) = Case_6989586621679654032 f x wild_6989586621679650009 wild_6989586621679650011 (Let6989586621679654030Scrutinee_6989586621679650003Sym4 f x wild_6989586621679650009 wild_6989586621679650011) |
sScanr1 :: forall (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a]) :: Type Source #
Accumulating maps
type family MapAccumL (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ... Source #
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 #
sMapAccumR :: forall (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 Source #
Cyclical lists
type family Replicate (a :: Natural) (a :: a) :: [a] where ... Source #
Equations
| Replicate n x = Case_6989586621679653164 n x (Let6989586621679653162Scrutinee_6989586621679650105Sym2 n x) |
sReplicate :: forall (t :: Natural) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a]) :: Type Source #
Unfolding
type family Unfoldr (a :: (~>) b (Maybe (a, b))) (a :: b) :: [a] where ... Source #
Equations
| Unfoldr f b = Case_6989586621679653919 f b (Let6989586621679653917Scrutinee_6989586621679650013Sym2 f b) |
sUnfoldr :: forall (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a]) :: Type Source #
Sublists
Extracting sublists
sTake :: forall (t :: Natural) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) :: Type Source #
sDrop :: forall (t :: Natural) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) :: Type Source #
sSplitAt :: forall (t :: Natural) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) :: Type Source #
sTakeWhile :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) :: Type Source #
sDropWhile :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) :: Type Source #
type family DropWhileEnd (a :: (~>) a Bool) (a :: [a]) :: [a] where ... Source #
sDropWhileEnd :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a]) :: Type Source #
type family Span (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
| Span _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679653363XsSym0) Let6989586621679653363XsSym0 | |
| Span p ('(:) x xs') = Case_6989586621679653372 p x xs' (Let6989586621679653370Scrutinee_6989586621679650085Sym3 p x xs') |
sSpan :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) :: Type Source #
type family Break (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
| Break _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679653328XsSym0) Let6989586621679653328XsSym0 | |
| Break p ('(:) x xs') = Case_6989586621679653337 p x xs' (Let6989586621679653335Scrutinee_6989586621679650087Sym3 p x xs') |
sBreak :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) :: Type Source #
type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ... Source #
Equations
| StripPrefix '[] ys = Apply JustSym0 ys | |
| StripPrefix arg_6989586621679803971 arg_6989586621679803973 = Case_6989586621679805285 arg_6989586621679803971 arg_6989586621679803973 (Apply (Apply Tuple2Sym0 arg_6989586621679803971) arg_6989586621679803973) |
type family Group (a :: [a]) :: [[a]] where ... Source #
Equations
| Group xs = Apply (Apply GroupBySym0 (==@#@$)) xs |
Predicates
type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
Equations
| IsPrefixOf '[] '[] = TrueSym0 | |
| IsPrefixOf '[] ('(:) _ _) = TrueSym0 | |
| IsPrefixOf ('(:) _ _) '[] = FalseSym0 | |
| IsPrefixOf ('(:) x xs) ('(:) y ys) = Apply (Apply (&&@#@$) (Apply (Apply (==@#@$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) |
sIsPrefixOf :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) :: Type Source #
type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
Equations
| IsSuffixOf x y = Apply (Apply IsPrefixOfSym0 (Apply ReverseSym0 x)) (Apply ReverseSym0 y) |
sIsSuffixOf :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) :: Type Source #
sIsInfixOf :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool) :: Type 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 :: First a) | |
| type Elem (arg1 :: a) (arg2 :: Last a) Source # | |
Defined in Data.Foldable.Singletons type Elem (arg1 :: a) (arg2 :: Last a) | |
| type Elem (arg :: a) (arg1 :: First a) Source # | |
Defined in Data.Semigroup.Singletons type Elem (arg :: a) (arg1 :: First a) | |
| type Elem (arg :: a) (arg1 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons type Elem (arg :: a) (arg1 :: Last a) | |
| type Elem (arg :: a) (arg1 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons type Elem (arg :: a) (arg1 :: Max a) | |
| type Elem (arg :: a) (arg1 :: Min a) Source # | |
Defined in Data.Semigroup.Singletons type Elem (arg :: a) (arg1 :: Min a) | |
| type Elem (arg1 :: a) (arg2 :: NonEmpty a) Source # | |
Defined in Data.Foldable.Singletons type Elem (arg1 :: a) (arg2 :: NonEmpty a) | |
| type Elem (arg1 :: a) (arg2 :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons type Elem (arg1 :: a) (arg2 :: Maybe a) | |
| type Elem (a1 :: k1) (a2 :: Identity k1) Source # | |
Defined in Data.Functor.Identity.Singletons type Elem (a1 :: k1) (a2 :: Identity k1) | |
| type Elem (a1 :: k1) (a2 :: Dual k1) Source # | |
Defined in Data.Foldable.Singletons type Elem (a1 :: k1) (a2 :: Dual k1) | |
| type Elem (a1 :: k1) (a2 :: Product k1) Source # | |
Defined in Data.Foldable.Singletons type Elem (a1 :: k1) (a2 :: Product k1) | |
| type Elem (a1 :: k1) (a2 :: Sum k1) Source # | |
Defined in Data.Foldable.Singletons type Elem (a1 :: k1) (a2 :: Sum k1) | |
| 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 :: Either a2 a1) | |
| type Elem (arg :: a1) (arg1 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons type Elem (arg :: a1) (arg1 :: Arg a2 a1) | |
| 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 (arg :: a) (arg1 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Elem (arg :: a) (arg1 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons type Elem (arg :: a) (arg1 :: Product f g a) | |
| type Elem (arg :: a) (arg1 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons type Elem (arg :: a) (arg1 :: Sum f g a) | |
| type Elem (arg :: a) (arg1 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons type Elem (arg :: a) (arg1 :: Compose f g a) | |
sElem :: SFoldable t => forall (t :: a) (t :: t a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) :: Type Source #
sNotElem :: forall (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) :: Type Source #
type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... Source #
Equations
| Lookup _key '[] = NothingSym0 | |
| Lookup key ('(:) '(x, y) xys) = Case_6989586621679653230 key x y xys (Let6989586621679653228Scrutinee_6989586621679650101Sym4 key x y xys) |
sLookup :: forall (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b) :: Type Source #
Searching with a predicate
type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ... Source #
Equations
| Find p a_6989586621680110329 = Apply (Apply (Apply (.@#@$) GetFirstSym0) (Apply FoldMapSym0 (Apply (Apply Lambda_6989586621680110338Sym0 p) a_6989586621680110329))) a_6989586621680110329 |
sFind :: forall (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a) :: Type Source #
sFilter :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) :: Type Source #
sPartition :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) :: Type Source #
Indexing lists
(%!!) :: forall (t :: [a]) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) :: Type infixl 9 Source #
sElemIndex :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Natural) :: Type Source #
type family ElemIndices (a :: a) (a :: [a]) :: [Natural] where ... Source #
Equations
| ElemIndices x a_6989586621679653500 = Apply (Apply FindIndicesSym0 (Apply (==@#@$) x)) a_6989586621679653500 |
sElemIndices :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Natural]) :: Type Source #
type family FindIndex (a :: (~>) a Bool) (a :: [a]) :: Maybe Natural where ... Source #
Equations
| FindIndex p a_6989586621679653491 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679653491 |
sFindIndex :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Natural) :: Type Source #
type family FindIndices (a :: (~>) a Bool) (a :: [a]) :: [Natural] where ... Source #
sFindIndices :: forall (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Natural]) :: Type Source #
Zipping and unzipping lists
sZip :: forall (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)]) :: Type 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 (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)]) :: Type Source #
type family Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ... Source #
Equations
| Zip4 a_6989586621679805256 a_6989586621679805258 a_6989586621679805260 a_6989586621679805262 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621679805256) a_6989586621679805258) a_6989586621679805260) a_6989586621679805262 |
type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ... Source #
Equations
| Zip5 a_6989586621679805230 a_6989586621679805232 a_6989586621679805234 a_6989586621679805236 a_6989586621679805238 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621679805230) a_6989586621679805232) a_6989586621679805234) a_6989586621679805236) a_6989586621679805238 |
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_6989586621679805199 a_6989586621679805201 a_6989586621679805203 a_6989586621679805205 a_6989586621679805207 a_6989586621679805209 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621679805199) a_6989586621679805201) a_6989586621679805203) a_6989586621679805205) a_6989586621679805207) a_6989586621679805209 |
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_6989586621679805163 a_6989586621679805165 a_6989586621679805167 a_6989586621679805169 a_6989586621679805171 a_6989586621679805173 a_6989586621679805175 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621679805163) a_6989586621679805165) a_6989586621679805167) a_6989586621679805169) a_6989586621679805171) a_6989586621679805173) a_6989586621679805175 |
sZipWith :: forall (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c]) :: Type 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 (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 Source #
type family ZipWith4 (a :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ... Source #
type family ZipWith5 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ... Source #
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 #
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 |
sUnzip3 :: forall (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c])) :: Type Source #
sUnzip4 :: forall (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d])) :: Type Source #
sUnzip5 :: forall (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e])) :: Type Source #
sUnzip6 :: forall (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f])) :: Type Source #
type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... Source #
sUnzip7 :: forall (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g])) :: Type Source #
Special lists
Functions on Symbols
"Set" operations
sDelete :: forall (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a]) :: Type Source #
(%\\) :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (\\@#@$) t) t :: [a]) :: Type infix 5 Source #
sUnion :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a]) :: Type Source #
sIntersect :: forall (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a]) :: Type Source #
Ordered lists
type family Insert (a :: a) (a :: [a]) :: [a] where ... Source #
Equations
| Insert e ls = Apply (Apply (Apply InsertBySym0 CompareSym0) e) ls |
sInsert :: forall (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a]) :: Type Source #
type family Sort (a :: [a]) :: [a] where ... Source #
Equations
| Sort a_6989586621679653259 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679653259 |
Generalized functions
The "By" operations
User-supplied equality (replacing an Eq context)
The predicate is assumed to define an equivalence.
sNubBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a]) :: Type Source #
sDeleteBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a]) :: Type Source #
type family DeleteFirstsBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ... Source #
Equations
| DeleteFirstsBy eq a_6989586621679653611 a_6989586621679653613 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679653611) a_6989586621679653613 |
sDeleteFirstsBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a]) :: Type Source #
sUnionBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a]) :: Type 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_6989586621679650071 wild_6989586621679650073) ('(:) wild_6989586621679650075 wild_6989586621679650077) = Apply (Apply (>>=@#@$) (Let6989586621679653452XsSym5 eq wild_6989586621679650071 wild_6989586621679650073 wild_6989586621679650075 wild_6989586621679650077)) (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679653455Sym0 eq) wild_6989586621679650071) wild_6989586621679650073) wild_6989586621679650075) wild_6989586621679650077) |
sIntersectBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a]) :: Type Source #
sGroupBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]]) :: Type Source #
User-supplied comparison (replacing an Ord context)
The function is assumed to define a total ordering.
sSortBy :: forall (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a]) :: Type Source #
sInsertBy :: forall (t :: (~>) a ((~>) a Ordering)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a]) :: Type Source #
type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #
Equations
| MaximumBy cmp a_6989586621680110376 = Apply (Apply Foldl1Sym0 (Let6989586621680110385Max'Sym2 cmp a_6989586621680110376)) a_6989586621680110376 |
sMaximumBy :: forall (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) :: Type Source #
type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #
Equations
| MinimumBy cmp a_6989586621680110356 = Apply (Apply Foldl1Sym0 (Let6989586621680110365Min'Sym2 cmp a_6989586621680110356)) a_6989586621680110356 |
sMinimumBy :: forall (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) :: Type Source #
The "generic" operations
The prefix `generic' indicates an overloaded function that
is a generalized version of a Prelude function.
type family GenericLength (a :: [a]) :: i where ... Source #
Equations
| GenericLength '[] = FromInteger 0 | |
| GenericLength ('(:) _ xs) = Apply (Apply (+@#@$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
sGenericLength :: forall (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i) :: Type 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) (a6989586621679037552 :: a) Source # | |
data (:@#@$$) (a6989586621679037552 :: a) :: (~>) [a] [a :: Type] infixr 5 Source #
Instances
| SingI1 ((:@#@$$) :: a -> TyFun [a] [a] -> Type) Source # | |
| SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| SuppressUnusedWarnings ((:@#@$$) a6989586621679037552 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods suppressUnusedWarnings :: () # | |
| type Apply ((:@#@$$) a6989586621679037552 :: TyFun [a] [a] -> Type) (a6989586621679037553 :: [a]) Source # | |
Defined in Data.Singletons.Base.Instances | |
type family (a6989586621679037552 :: a) :@#@$$$ (a6989586621679037553 :: [a]) :: [a :: Type] where ... infixr 5 Source #
Equations
| a6989586621679037552 :@#@$$$ a6989586621679037553 = '(:) a6989586621679037552 a6989586621679037553 |
type family (a6989586621679144197 :: [a]) ++@#@$$$ (a6989586621679144198 :: [a]) :: [a] where ... infixr 5 Source #
data (++@#@$$) (a6989586621679144197 :: [a]) :: (~>) [a] [a] infixr 5 Source #
Instances
| SingI1 ((++@#@$$) :: [a] -> TyFun [a] [a] -> Type) Source # | |
| SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
Defined in GHC.Base.Singletons | |
| SuppressUnusedWarnings ((++@#@$$) a6989586621679144197 :: TyFun [a] [a] -> Type) Source # | |
Defined in GHC.Base.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((++@#@$$) a6989586621679144197 :: TyFun [a] [a] -> Type) (a6989586621679144198 :: [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) (a6989586621679144197 :: [a]) Source # | |
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) (a6989586621679654300 :: [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) (a6989586621679654294 :: [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) (a6989586621679654290 :: [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) (a6989586621679654278 :: [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) (a6989586621680110598 :: 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) (a6989586621680110601 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621680110601 :: t a) = Length a6989586621680110601 | |
type family LengthSym1 (a6989586621680110601 :: t a) :: Natural where ... Source #
Equations
| LengthSym1 a6989586621680110601 = Length a6989586621680110601 |
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) (a6989586621679144206 :: a ~> b) Source # | |
data MapSym1 (a6989586621679144206 :: (~>) a b) :: (~>) [a] [b] Source #
Instances
| SingI1 (MapSym1 :: (a ~> b) -> TyFun [a] [b] -> Type) Source # | |
| SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # | |
Defined in GHC.Base.Singletons | |
| SuppressUnusedWarnings (MapSym1 a6989586621679144206 :: TyFun [a] [b] -> Type) Source # | |
Defined in GHC.Base.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapSym1 a6989586621679144206 :: TyFun [a] [b] -> Type) (a6989586621679144207 :: [a]) Source # | |
Defined in GHC.Base.Singletons | |
type family MapSym2 (a6989586621679144206 :: (~>) a b) (a6989586621679144207 :: [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) (a6989586621679654263 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679654263 :: [a]) = Reverse a6989586621679654263 | |
type family ReverseSym1 (a6989586621679654263 :: [a]) :: [a] where ... Source #
Equations
| ReverseSym1 a6989586621679654263 = Reverse a6989586621679654263 |
data IntersperseSym0 :: (~>) a ((~>) [a] [a]) Source #
Instances
| SingI (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing IntersperseSym0 # | |
| SuppressUnusedWarnings (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679654256 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679654256 :: a) = IntersperseSym1 a6989586621679654256 | |
data IntersperseSym1 (a6989586621679654256 :: 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 a6989586621679654256 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersperseSym1 a6989586621679654256 :: TyFun [a] [a] -> Type) (a6989586621679654257 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersperseSym1 a6989586621679654256 :: TyFun [a] [a] -> Type) (a6989586621679654257 :: [a]) = Intersperse a6989586621679654256 a6989586621679654257 | |
type family IntersperseSym2 (a6989586621679654256 :: a) (a6989586621679654257 :: [a]) :: [a] where ... Source #
Equations
| IntersperseSym2 a6989586621679654256 a6989586621679654257 = Intersperse a6989586621679654256 a6989586621679654257 |
data IntercalateSym0 :: (~>) [a] ((~>) [[a]] [a]) Source #
Instances
| SingI (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing IntercalateSym0 # | |
| SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679654249 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679654249 :: [a]) = IntercalateSym1 a6989586621679654249 | |
data IntercalateSym1 (a6989586621679654249 :: [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 a6989586621679654249 :: TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntercalateSym1 a6989586621679654249 :: TyFun [[a]] [a] -> Type) (a6989586621679654250 :: [[a]]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntercalateSym1 a6989586621679654249 :: TyFun [[a]] [a] -> Type) (a6989586621679654250 :: [[a]]) = Intercalate a6989586621679654249 a6989586621679654250 | |
type family IntercalateSym2 (a6989586621679654249 :: [a]) (a6989586621679654250 :: [[a]]) :: [a] where ... Source #
Equations
| IntercalateSym2 a6989586621679654249 a6989586621679654250 = Intercalate a6989586621679654249 a6989586621679654250 |
data TransposeSym0 :: (~>) [[a]] [[a]] Source #
Instances
| SingI (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing TransposeSym0 # | |
| SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679653150 :: [[a]]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679653150 :: [[a]]) = Transpose a6989586621679653150 | |
type family TransposeSym1 (a6989586621679653150 :: [[a]]) :: [[a]] where ... Source #
Equations
| TransposeSym1 a6989586621679653150 = Transpose a6989586621679653150 |
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) (a6989586621679654244 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679654244 :: [a]) = Subsequences a6989586621679654244 | |
type family SubsequencesSym1 (a6989586621679654244 :: [a]) :: [[a]] where ... Source #
Equations
| SubsequencesSym1 a6989586621679654244 = Subsequences a6989586621679654244 |
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) (a6989586621679654170 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679654170 :: [a]) = Permutations a6989586621679654170 | |
type family PermutationsSym1 (a6989586621679654170 :: [a]) :: [[a]] where ... Source #
Equations
| PermutationsSym1 a6989586621679654170 = Permutations a6989586621679654170 |
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) (a6989586621680110573 :: b ~> (a ~> b)) Source # | |
data FoldlSym1 (a6989586621680110573 :: (~>) b ((~>) a b)) :: (~>) b ((~>) (t a) b) Source #
Instances
| SFoldable t => SingI1 (FoldlSym1 :: (b ~> (a ~> b)) -> TyFun b (t a ~> b) -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (FoldlSym1 d :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (FoldlSym1 a6989586621680110573 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldlSym1 a6989586621680110573 :: TyFun b (t a ~> b) -> Type) (a6989586621680110574 :: b) Source # | |
data FoldlSym2 (a6989586621680110573 :: (~>) b ((~>) a b)) (a6989586621680110574 :: b) :: (~>) (t a) b Source #
Instances
| (SFoldable t, SingI d) => SingI1 (FoldlSym2 d :: b -> TyFun (t a) b -> Type) Source # | |
| 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 a6989586621680110573 a6989586621680110574 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldlSym2 a6989586621680110573 a6989586621680110574 :: TyFun (t a) b -> Type) (a6989586621680110575 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family FoldlSym3 (a6989586621680110573 :: (~>) b ((~>) a b)) (a6989586621680110574 :: b) (a6989586621680110575 :: 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) (a6989586621680110580 :: b ~> (a ~> b)) Source # | |
Defined in Data.Foldable.Singletons | |
data Foldl'Sym1 (a6989586621680110580 :: (~>) 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 a6989586621680110580 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl'Sym1 a6989586621680110580 :: TyFun b (t a ~> b) -> Type) (a6989586621680110581 :: b) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl'Sym1 a6989586621680110580 :: TyFun b (t a ~> b) -> Type) (a6989586621680110581 :: b) = Foldl'Sym2 a6989586621680110580 a6989586621680110581 :: TyFun (t a) b -> Type | |
data Foldl'Sym2 (a6989586621680110580 :: (~>) b ((~>) a b)) (a6989586621680110581 :: 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 | |
| (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 a6989586621680110580 a6989586621680110581 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl'Sym2 a6989586621680110580 a6989586621680110581 :: TyFun (t a) b -> Type) (a6989586621680110582 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl'Sym2 a6989586621680110580 a6989586621680110581 :: TyFun (t a) b -> Type) (a6989586621680110582 :: t a) = Foldl' a6989586621680110580 a6989586621680110581 a6989586621680110582 | |
type family Foldl'Sym3 (a6989586621680110580 :: (~>) b ((~>) a b)) (a6989586621680110581 :: b) (a6989586621680110582 :: t a) :: b where ... Source #
Equations
| Foldl'Sym3 a6989586621680110580 a6989586621680110581 a6989586621680110582 = Foldl' a6989586621680110580 a6989586621680110581 a6989586621680110582 |
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) (a6989586621680110591 :: a ~> (a ~> a)) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680110591 :: a ~> (a ~> a)) = Foldl1Sym1 a6989586621680110591 :: TyFun (t a) a -> Type | |
data Foldl1Sym1 (a6989586621680110591 :: (~>) 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 a6989586621680110591 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl1Sym1 a6989586621680110591 :: TyFun (t a) a -> Type) (a6989586621680110592 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl1Sym1 a6989586621680110591 :: TyFun (t a) a -> Type) (a6989586621680110592 :: t a) = Foldl1 a6989586621680110591 a6989586621680110592 | |
type family Foldl1Sym2 (a6989586621680110591 :: (~>) a ((~>) a a)) (a6989586621680110592 :: t a) :: a where ... Source #
Equations
| Foldl1Sym2 a6989586621680110591 a6989586621680110592 = Foldl1 a6989586621680110591 a6989586621680110592 |
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) (a6989586621679654135 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679654135 :: a ~> (a ~> a)) = Foldl1'Sym1 a6989586621679654135 | |
data Foldl1'Sym1 (a6989586621679654135 :: (~>) 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 a6989586621679654135 :: 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 a6989586621679654135 :: TyFun [a] a -> Type) (a6989586621679654136 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Foldl1'Sym1 a6989586621679654135 :: TyFun [a] a -> Type) (a6989586621679654136 :: [a]) = Foldl1' a6989586621679654135 a6989586621679654136 | |
type family Foldl1'Sym2 (a6989586621679654135 :: (~>) a ((~>) a a)) (a6989586621679654136 :: [a]) :: a where ... Source #
Equations
| Foldl1'Sym2 a6989586621679654135 a6989586621679654136 = Foldl1' a6989586621679654135 a6989586621679654136 |
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) (a6989586621680110559 :: a ~> (b ~> b)) Source # | |
data FoldrSym1 (a6989586621680110559 :: (~>) a ((~>) b b)) :: (~>) b ((~>) (t a) b) Source #
Instances
| SFoldable t => SingI1 (FoldrSym1 :: (a ~> (b ~> b)) -> TyFun b (t a ~> b) -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (FoldrSym1 d :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (FoldrSym1 a6989586621680110559 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldrSym1 a6989586621680110559 :: TyFun b (t a ~> b) -> Type) (a6989586621680110560 :: b) Source # | |
data FoldrSym2 (a6989586621680110559 :: (~>) a ((~>) b b)) (a6989586621680110560 :: b) :: (~>) (t a) b Source #
Instances
| (SFoldable t, SingI d) => SingI1 (FoldrSym2 d :: b -> TyFun (t a) b -> Type) Source # | |
| 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 a6989586621680110559 a6989586621680110560 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldrSym2 a6989586621680110559 a6989586621680110560 :: TyFun (t a) b -> Type) (a6989586621680110561 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family FoldrSym3 (a6989586621680110559 :: (~>) a ((~>) b b)) (a6989586621680110560 :: b) (a6989586621680110561 :: 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) (a6989586621680110586 :: a ~> (a ~> a)) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680110586 :: a ~> (a ~> a)) = Foldr1Sym1 a6989586621680110586 :: TyFun (t a) a -> Type | |
data Foldr1Sym1 (a6989586621680110586 :: (~>) 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 a6989586621680110586 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldr1Sym1 a6989586621680110586 :: TyFun (t a) a -> Type) (a6989586621680110587 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldr1Sym1 a6989586621680110586 :: TyFun (t a) a -> Type) (a6989586621680110587 :: t a) = Foldr1 a6989586621680110586 a6989586621680110587 | |
type family Foldr1Sym2 (a6989586621680110586 :: (~>) a ((~>) a a)) (a6989586621680110587 :: t a) :: a where ... Source #
Equations
| Foldr1Sym2 a6989586621680110586 a6989586621680110587 = Foldr1 a6989586621680110586 a6989586621680110587 |
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) (a6989586621680110440 :: t [a]) Source # | |
Defined in Data.Foldable.Singletons type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680110440 :: t [a]) = Concat a6989586621680110440 | |
type family ConcatSym1 (a6989586621680110440 :: t [a]) :: [a] where ... Source #
Equations
| ConcatSym1 a6989586621680110440 = Concat a6989586621680110440 |
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 sing :: Sing ConcatMapSym0 # | |
| 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) (a6989586621680110429 :: a ~> [b]) Source # | |
Defined in Data.Foldable.Singletons type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680110429 :: a ~> [b]) = ConcatMapSym1 a6989586621680110429 :: TyFun (t a) [b] -> Type | |
data ConcatMapSym1 (a6989586621680110429 :: (~>) 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 a6989586621680110429 :: TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ConcatMapSym1 a6989586621680110429 :: TyFun (t a) [b] -> Type) (a6989586621680110430 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (ConcatMapSym1 a6989586621680110429 :: TyFun (t a) [b] -> Type) (a6989586621680110430 :: t a) = ConcatMap a6989586621680110429 a6989586621680110430 | |
type family ConcatMapSym2 (a6989586621680110429 :: (~>) a [b]) (a6989586621680110430 :: t a) :: [b] where ... Source #
Equations
| ConcatMapSym2 a6989586621680110429 a6989586621680110430 = ConcatMap a6989586621680110429 a6989586621680110430 |
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) (a6989586621680110424 :: t Bool) Source # | |
Defined in Data.Foldable.Singletons | |
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) (a6989586621680110418 :: t Bool) Source # | |
Defined in Data.Foldable.Singletons | |
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) (a6989586621680110410 :: a ~> Bool) Source # | |
data AnySym1 (a6989586621680110410 :: (~>) a Bool) :: (~>) (t a) Bool Source #
Instances
| SFoldable t => SingI1 (AnySym1 :: (a ~> Bool) -> TyFun (t a) Bool -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (AnySym1 d :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (AnySym1 a6989586621680110410 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (AnySym1 a6989586621680110410 :: TyFun (t a) Bool -> Type) (a6989586621680110411 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family AnySym2 (a6989586621680110410 :: (~>) a Bool) (a6989586621680110411 :: 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) (a6989586621680110401 :: a ~> Bool) Source # | |
data AllSym1 (a6989586621680110401 :: (~>) a Bool) :: (~>) (t a) Bool Source #
Instances
| SFoldable t => SingI1 (AllSym1 :: (a ~> Bool) -> TyFun (t a) Bool -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (AllSym1 d :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (AllSym1 a6989586621680110401 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (AllSym1 a6989586621680110401 :: TyFun (t a) Bool -> Type) (a6989586621680110402 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family AllSym2 (a6989586621680110401 :: (~>) a Bool) (a6989586621680110402 :: 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) (a6989586621680110615 :: 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) (a6989586621680110618 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680110618 :: t a) = Product a6989586621680110618 | |
type family ProductSym1 (a6989586621680110618 :: t a) :: a where ... Source #
Equations
| ProductSym1 a6989586621680110618 = Product a6989586621680110618 |
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) (a6989586621680110609 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680110609 :: t a) = Maximum a6989586621680110609 | |
type family MaximumSym1 (a6989586621680110609 :: t a) :: a where ... Source #
Equations
| MaximumSym1 a6989586621680110609 = Maximum a6989586621680110609 |
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) (a6989586621680110612 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680110612 :: t a) = Minimum a6989586621680110612 | |
type family MinimumSym1 (a6989586621680110612 :: t a) :: a where ... Source #
Equations
| MinimumSym1 a6989586621680110612 = Minimum a6989586621680110612 |
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) (a6989586621679654068 :: b ~> (a ~> b)) Source # | |
data ScanlSym1 (a6989586621679654068 :: (~>) b ((~>) a b)) :: (~>) b ((~>) [a] [b]) Source #
Instances
| SingI1 (ScanlSym1 :: (b ~> (a ~> b)) -> TyFun b ([a] ~> [b]) -> Type) Source # | |
| SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ScanlSym1 a6989586621679654068 :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym1 a6989586621679654068 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679654069 :: b) Source # | |
data ScanlSym2 (a6989586621679654068 :: (~>) b ((~>) a b)) (a6989586621679654069 :: b) :: (~>) [a] [b] Source #
Instances
| SingI d => SingI1 (ScanlSym2 d :: b -> TyFun [a] [b] -> Type) Source # | |
| 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 a6989586621679654068 a6989586621679654069 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym2 a6989586621679654068 a6989586621679654069 :: TyFun [a] [b] -> Type) (a6989586621679654070 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family ScanlSym3 (a6989586621679654068 :: (~>) b ((~>) a b)) (a6989586621679654069 :: b) (a6989586621679654070 :: [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) (a6989586621679654059 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679654059 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621679654059 | |
data Scanl1Sym1 (a6989586621679654059 :: (~>) 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 a6989586621679654059 :: 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 a6989586621679654059 :: TyFun [a] [a] -> Type) (a6989586621679654060 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanl1Sym1 a6989586621679654059 :: TyFun [a] [a] -> Type) (a6989586621679654060 :: [a]) = Scanl1 a6989586621679654059 a6989586621679654060 | |
type family Scanl1Sym2 (a6989586621679654059 :: (~>) a ((~>) a a)) (a6989586621679654060 :: [a]) :: [a] where ... Source #
Equations
| Scanl1Sym2 a6989586621679654059 a6989586621679654060 = Scanl1 a6989586621679654059 a6989586621679654060 |
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) (a6989586621679654041 :: a ~> (b ~> b)) Source # | |
data ScanrSym1 (a6989586621679654041 :: (~>) a ((~>) b b)) :: (~>) b ((~>) [a] [b]) Source #
Instances
| SingI1 (ScanrSym1 :: (a ~> (b ~> b)) -> TyFun b ([a] ~> [b]) -> Type) Source # | |
| SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ScanrSym1 a6989586621679654041 :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym1 a6989586621679654041 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679654042 :: b) Source # | |
data ScanrSym2 (a6989586621679654041 :: (~>) a ((~>) b b)) (a6989586621679654042 :: b) :: (~>) [a] [b] Source #
Instances
| SingI d => SingI1 (ScanrSym2 d :: b -> TyFun [a] [b] -> Type) Source # | |
| 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 a6989586621679654041 a6989586621679654042 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym2 a6989586621679654041 a6989586621679654042 :: TyFun [a] [b] -> Type) (a6989586621679654043 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family ScanrSym3 (a6989586621679654041 :: (~>) a ((~>) b b)) (a6989586621679654042 :: b) (a6989586621679654043 :: [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) (a6989586621679654021 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679654021 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621679654021 | |
data Scanr1Sym1 (a6989586621679654021 :: (~>) 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 a6989586621679654021 :: 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 a6989586621679654021 :: TyFun [a] [a] -> Type) (a6989586621679654022 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanr1Sym1 a6989586621679654021 :: TyFun [a] [a] -> Type) (a6989586621679654022 :: [a]) = Scanr1 a6989586621679654021 a6989586621679654022 | |
type family Scanr1Sym2 (a6989586621679654021 :: (~>) a ((~>) a a)) (a6989586621679654022 :: [a]) :: [a] where ... Source #
Equations
| Scanr1Sym2 a6989586621679654021 a6989586621679654022 = Scanr1 a6989586621679654021 a6989586621679654022 |
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 sing :: Sing MapAccumLSym0 # | |
| 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) (a6989586621680387583 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Traversable.Singletons | |
data MapAccumLSym1 (a6989586621680387583 :: (~>) 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 a6989586621680387583 :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumLSym1 a6989586621680387583 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680387584 :: a) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumLSym1 a6989586621680387583 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680387584 :: a) = MapAccumLSym2 a6989586621680387583 a6989586621680387584 :: TyFun (t b) (a, t c) -> Type | |
data MapAccumLSym2 (a6989586621680387583 :: (~>) a ((~>) b (a, c))) (a6989586621680387584 :: 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 | |
| (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 a6989586621680387583 a6989586621680387584 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumLSym2 a6989586621680387583 a6989586621680387584 :: TyFun (t b) (a, t c) -> Type) (a6989586621680387585 :: t b) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumLSym2 a6989586621680387583 a6989586621680387584 :: TyFun (t b) (a, t c) -> Type) (a6989586621680387585 :: t b) = MapAccumL a6989586621680387583 a6989586621680387584 a6989586621680387585 | |
type family MapAccumLSym3 (a6989586621680387583 :: (~>) a ((~>) b (a, c))) (a6989586621680387584 :: a) (a6989586621680387585 :: t b) :: (a, t c) where ... Source #
Equations
| MapAccumLSym3 a6989586621680387583 a6989586621680387584 a6989586621680387585 = MapAccumL a6989586621680387583 a6989586621680387584 a6989586621680387585 |
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 sing :: Sing MapAccumRSym0 # | |
| 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) (a6989586621680387573 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Traversable.Singletons | |
data MapAccumRSym1 (a6989586621680387573 :: (~>) 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 a6989586621680387573 :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumRSym1 a6989586621680387573 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680387574 :: a) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumRSym1 a6989586621680387573 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680387574 :: a) = MapAccumRSym2 a6989586621680387573 a6989586621680387574 :: TyFun (t b) (a, t c) -> Type | |
data MapAccumRSym2 (a6989586621680387573 :: (~>) a ((~>) b (a, c))) (a6989586621680387574 :: 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 | |
| (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 a6989586621680387573 a6989586621680387574 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumRSym2 a6989586621680387573 a6989586621680387574 :: TyFun (t b) (a, t c) -> Type) (a6989586621680387575 :: t b) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumRSym2 a6989586621680387573 a6989586621680387574 :: TyFun (t b) (a, t c) -> Type) (a6989586621680387575 :: t b) = MapAccumR a6989586621680387573 a6989586621680387574 a6989586621680387575 | |
type family MapAccumRSym3 (a6989586621680387573 :: (~>) a ((~>) b (a, c))) (a6989586621680387574 :: a) (a6989586621680387575 :: t b) :: (a, t c) where ... Source #
Equations
| MapAccumRSym3 a6989586621680387573 a6989586621680387574 a6989586621680387575 = MapAccumR a6989586621680387573 a6989586621680387574 a6989586621680387575 |
data ReplicateSym0 :: (~>) Natural ((~>) a [a]) Source #
Instances
| SingI (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing ReplicateSym0 # | |
| SuppressUnusedWarnings (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679653158 :: Natural) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679653158 :: Natural) = ReplicateSym1 a6989586621679653158 :: TyFun a [a] -> Type | |
data ReplicateSym1 (a6989586621679653158 :: 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 a6989586621679653158 :: TyFun a [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ReplicateSym1 a6989586621679653158 :: TyFun a [a] -> Type) (a6989586621679653159 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ReplicateSym1 a6989586621679653158 :: TyFun a [a] -> Type) (a6989586621679653159 :: a) = Replicate a6989586621679653158 a6989586621679653159 | |
type family ReplicateSym2 (a6989586621679653158 :: Natural) (a6989586621679653159 :: a) :: [a] where ... Source #
Equations
| ReplicateSym2 a6989586621679653158 a6989586621679653159 = Replicate a6989586621679653158 a6989586621679653159 |
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) (a6989586621679653913 :: b ~> Maybe (a, b)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679653913 :: b ~> Maybe (a, b)) = UnfoldrSym1 a6989586621679653913 | |
data UnfoldrSym1 (a6989586621679653913 :: (~>) 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 a6989586621679653913 :: TyFun b [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnfoldrSym1 a6989586621679653913 :: TyFun b [a] -> Type) (a6989586621679653914 :: b) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnfoldrSym1 a6989586621679653913 :: TyFun b [a] -> Type) (a6989586621679653914 :: b) = Unfoldr a6989586621679653913 a6989586621679653914 | |
type family UnfoldrSym2 (a6989586621679653913 :: (~>) b (Maybe (a, b))) (a6989586621679653914 :: b) :: [a] where ... Source #
Equations
| UnfoldrSym2 a6989586621679653913 a6989586621679653914 = Unfoldr a6989586621679653913 a6989586621679653914 |
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) (a6989586621679653313 :: Natural) Source # | |
data TakeSym1 (a6989586621679653313 :: Natural) :: (~>) [a] [a] Source #
Instances
| SingI1 (TakeSym1 :: Natural -> TyFun [a] [a] -> Type) Source # | |
| SingI d => SingI (TakeSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (TakeSym1 a6989586621679653313 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeSym1 a6989586621679653313 :: TyFun [a] [a] -> Type) (a6989586621679653314 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family TakeSym2 (a6989586621679653313 :: Natural) (a6989586621679653314 :: [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) (a6989586621679653300 :: Natural) Source # | |
data DropSym1 (a6989586621679653300 :: Natural) :: (~>) [a] [a] Source #
Instances
| SingI1 (DropSym1 :: Natural -> TyFun [a] [a] -> Type) Source # | |
| SingI d => SingI (DropSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (DropSym1 a6989586621679653300 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DropSym1 a6989586621679653300 :: TyFun [a] [a] -> Type) (a6989586621679653301 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family DropSym2 (a6989586621679653300 :: Natural) (a6989586621679653301 :: [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) (a6989586621679653293 :: Natural) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679653293 :: Natural) = SplitAtSym1 a6989586621679653293 :: TyFun [a] ([a], [a]) -> Type | |
data SplitAtSym1 (a6989586621679653293 :: 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 a6989586621679653293 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (SplitAtSym1 a6989586621679653293 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679653294 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SplitAtSym1 a6989586621679653293 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679653294 :: [a]) = SplitAt a6989586621679653293 a6989586621679653294 | |
type family SplitAtSym2 (a6989586621679653293 :: Natural) (a6989586621679653294 :: [a]) :: ([a], [a]) where ... Source #
Equations
| SplitAtSym2 a6989586621679653293 a6989586621679653294 = SplitAt a6989586621679653293 a6989586621679653294 |
data TakeWhileSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a]) Source #
Instances
| SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing TakeWhileSym0 # | |
| 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) (a6989586621679653430 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679653430 :: a ~> Bool) = TakeWhileSym1 a6989586621679653430 | |
data TakeWhileSym1 (a6989586621679653430 :: (~>) 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 a6989586621679653430 :: 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 a6989586621679653430 :: TyFun [a] [a] -> Type) (a6989586621679653431 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (TakeWhileSym1 a6989586621679653430 :: TyFun [a] [a] -> Type) (a6989586621679653431 :: [a]) = TakeWhile a6989586621679653430 a6989586621679653431 | |
type family TakeWhileSym2 (a6989586621679653430 :: (~>) a Bool) (a6989586621679653431 :: [a]) :: [a] where ... Source #
Equations
| TakeWhileSym2 a6989586621679653430 a6989586621679653431 = TakeWhile a6989586621679653430 a6989586621679653431 |
data DropWhileSym0 :: (~>) ((~>) a Bool) ((~>) [a] [a]) Source #
Instances
| SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing DropWhileSym0 # | |
| 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) (a6989586621679653415 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679653415 :: a ~> Bool) = DropWhileSym1 a6989586621679653415 | |
data DropWhileSym1 (a6989586621679653415 :: (~>) 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 a6989586621679653415 :: 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 a6989586621679653415 :: TyFun [a] [a] -> Type) (a6989586621679653416 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileSym1 a6989586621679653415 :: TyFun [a] [a] -> Type) (a6989586621679653416 :: [a]) = DropWhile a6989586621679653415 a6989586621679653416 | |
type family DropWhileSym2 (a6989586621679653415 :: (~>) a Bool) (a6989586621679653416 :: [a]) :: [a] where ... Source #
Equations
| DropWhileSym2 a6989586621679653415 a6989586621679653416 = DropWhile a6989586621679653415 a6989586621679653416 |
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) (a6989586621679653398 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679653398 :: a ~> Bool) = DropWhileEndSym1 a6989586621679653398 | |
data DropWhileEndSym1 (a6989586621679653398 :: (~>) 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 a6989586621679653398 :: 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 a6989586621679653398 :: TyFun [a] [a] -> Type) (a6989586621679653399 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileEndSym1 a6989586621679653398 :: TyFun [a] [a] -> Type) (a6989586621679653399 :: [a]) = DropWhileEnd a6989586621679653398 a6989586621679653399 | |
type family DropWhileEndSym2 (a6989586621679653398 :: (~>) a Bool) (a6989586621679653399 :: [a]) :: [a] where ... Source #
Equations
| DropWhileEndSym2 a6989586621679653398 a6989586621679653399 = DropWhileEnd a6989586621679653398 a6989586621679653399 |
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) (a6989586621679653361 :: a ~> Bool) Source # | |
data SpanSym1 (a6989586621679653361 :: (~>) 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 a6989586621679653361 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (SpanSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # | |
| type Apply (SpanSym1 a6989586621679653361 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679653362 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family SpanSym2 (a6989586621679653361 :: (~>) a Bool) (a6989586621679653362 :: [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) (a6989586621679653326 :: a ~> Bool) Source # | |
data BreakSym1 (a6989586621679653326 :: (~>) 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 a6989586621679653326 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (BreakSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # | |
| type Apply (BreakSym1 a6989586621679653326 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679653327 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family BreakSym2 (a6989586621679653326 :: (~>) a Bool) (a6989586621679653327 :: [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) (a6989586621679805280 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679805280 :: [a]) = StripPrefixSym1 a6989586621679805280 | |
data StripPrefixSym1 (a6989586621679805280 :: [a]) :: (~>) [a] (Maybe [a]) Source #
Instances
| SuppressUnusedWarnings (StripPrefixSym1 a6989586621679805280 :: TyFun [a] (Maybe [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (StripPrefixSym1 a6989586621679805280 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679805281 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (StripPrefixSym1 a6989586621679805280 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679805281 :: [a]) = StripPrefix a6989586621679805280 a6989586621679805281 | |
type family StripPrefixSym2 (a6989586621679805280 :: [a]) (a6989586621679805281 :: [a]) :: Maybe [a] where ... Source #
Equations
| StripPrefixSym2 a6989586621679805280 a6989586621679805281 = StripPrefix a6989586621679805280 a6989586621679805281 |
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) (a6989586621679653288 :: [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) (a6989586621679653903 :: [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) (a6989586621679653895 :: [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 sing :: Sing IsPrefixOfSym0 # | |
| SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679653887 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679653887 :: [a]) = IsPrefixOfSym1 a6989586621679653887 | |
data IsPrefixOfSym1 (a6989586621679653887 :: [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 a6989586621679653887 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsPrefixOfSym1 a6989586621679653887 :: TyFun [a] Bool -> Type) (a6989586621679653888 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsPrefixOfSym1 a6989586621679653887 :: TyFun [a] Bool -> Type) (a6989586621679653888 :: [a]) = IsPrefixOf a6989586621679653887 a6989586621679653888 | |
type family IsPrefixOfSym2 (a6989586621679653887 :: [a]) (a6989586621679653888 :: [a]) :: Bool where ... Source #
Equations
| IsPrefixOfSym2 a6989586621679653887 a6989586621679653888 = IsPrefixOf a6989586621679653887 a6989586621679653888 |
data IsSuffixOfSym0 :: (~>) [a] ((~>) [a] Bool) Source #
Instances
| SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing IsSuffixOfSym0 # | |
| SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679653880 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679653880 :: [a]) = IsSuffixOfSym1 a6989586621679653880 | |
data IsSuffixOfSym1 (a6989586621679653880 :: [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 a6989586621679653880 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsSuffixOfSym1 a6989586621679653880 :: TyFun [a] Bool -> Type) (a6989586621679653881 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsSuffixOfSym1 a6989586621679653880 :: TyFun [a] Bool -> Type) (a6989586621679653881 :: [a]) = IsSuffixOf a6989586621679653880 a6989586621679653881 | |
type family IsSuffixOfSym2 (a6989586621679653880 :: [a]) (a6989586621679653881 :: [a]) :: Bool where ... Source #
Equations
| IsSuffixOfSym2 a6989586621679653880 a6989586621679653881 = IsSuffixOf a6989586621679653880 a6989586621679653881 |
data IsInfixOfSym0 :: (~>) [a] ((~>) [a] Bool) Source #
Instances
| SEq a => SingI (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing IsInfixOfSym0 # | |
| SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679653873 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679653873 :: [a]) = IsInfixOfSym1 a6989586621679653873 | |
data IsInfixOfSym1 (a6989586621679653873 :: [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 a6989586621679653873 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsInfixOfSym1 a6989586621679653873 :: TyFun [a] Bool -> Type) (a6989586621679653874 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsInfixOfSym1 a6989586621679653873 :: TyFun [a] Bool -> Type) (a6989586621679653874 :: [a]) = IsInfixOf a6989586621679653873 a6989586621679653874 | |
type family IsInfixOfSym2 (a6989586621679653873 :: [a]) (a6989586621679653874 :: [a]) :: Bool where ... Source #
Equations
| IsInfixOfSym2 a6989586621679653873 a6989586621679653874 = IsInfixOf a6989586621679653873 a6989586621679653874 |
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) (a6989586621680110605 :: a) Source # | |
data ElemSym1 (a6989586621680110605 :: a) :: (~>) (t a) Bool Source #
Instances
| (SFoldable t, SEq a) => SingI1 (ElemSym1 :: a -> TyFun (t a) Bool -> Type) Source # | |
| (SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (ElemSym1 a6989586621680110605 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemSym1 a6989586621680110605 :: TyFun (t a) Bool -> Type) (a6989586621680110606 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family ElemSym2 (a6989586621680110605 :: a) (a6989586621680110606 :: 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) (a6989586621680110352 :: a) Source # | |
Defined in Data.Foldable.Singletons type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680110352 :: a) = NotElemSym1 a6989586621680110352 :: TyFun (t a) Bool -> Type | |
data NotElemSym1 (a6989586621680110352 :: 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 a6989586621680110352 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (NotElemSym1 a6989586621680110352 :: TyFun (t a) Bool -> Type) (a6989586621680110353 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (NotElemSym1 a6989586621680110352 :: TyFun (t a) Bool -> Type) (a6989586621680110353 :: t a) = NotElem a6989586621680110352 a6989586621680110353 | |
type family NotElemSym2 (a6989586621680110352 :: a) (a6989586621680110353 :: t a) :: Bool where ... Source #
Equations
| NotElemSym2 a6989586621680110352 a6989586621680110353 = NotElem a6989586621680110352 a6989586621680110353 |
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) (a6989586621679653221 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679653221 :: a) = LookupSym1 a6989586621679653221 :: TyFun [(a, b)] (Maybe b) -> Type | |
data LookupSym1 (a6989586621679653221 :: 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 a6989586621679653221 :: TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (LookupSym1 a6989586621679653221 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679653222 :: [(a, b)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (LookupSym1 a6989586621679653221 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679653222 :: [(a, b)]) = Lookup a6989586621679653221 a6989586621679653222 | |
type family LookupSym2 (a6989586621679653221 :: a) (a6989586621679653222 :: [(a, b)]) :: Maybe b where ... Source #
Equations
| LookupSym2 a6989586621679653221 a6989586621679653222 = Lookup a6989586621679653221 a6989586621679653222 |
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) (a6989586621680110334 :: a ~> Bool) Source # | |
data FindSym1 (a6989586621680110334 :: (~>) a Bool) :: (~>) (t a) (Maybe a) Source #
Instances
| SFoldable t => SingI1 (FindSym1 :: (a ~> Bool) -> TyFun (t a) (Maybe a) -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (FindSym1 d :: TyFun (t a) (Maybe a) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (FindSym1 a6989586621680110334 :: TyFun (t a) (Maybe a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FindSym1 a6989586621680110334 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680110335 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family FindSym2 (a6989586621680110334 :: (~>) a Bool) (a6989586621680110335 :: 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) (a6989586621679653530 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679653530 :: a ~> Bool) = FilterSym1 a6989586621679653530 | |
data FilterSym1 (a6989586621679653530 :: (~>) 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 a6989586621679653530 :: 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 a6989586621679653530 :: TyFun [a] [a] -> Type) (a6989586621679653531 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FilterSym1 a6989586621679653530 :: TyFun [a] [a] -> Type) (a6989586621679653531 :: [a]) = Filter a6989586621679653530 a6989586621679653531 | |
type family FilterSym2 (a6989586621679653530 :: (~>) a Bool) (a6989586621679653531 :: [a]) :: [a] where ... Source #
Equations
| FilterSym2 a6989586621679653530 a6989586621679653531 = Filter a6989586621679653530 a6989586621679653531 |
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 sing :: Sing PartitionSym0 # | |
| 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) (a6989586621679653214 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679653214 :: a ~> Bool) = PartitionSym1 a6989586621679653214 | |
data PartitionSym1 (a6989586621679653214 :: (~>) 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 a6989586621679653214 :: 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 a6989586621679653214 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679653215 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (PartitionSym1 a6989586621679653214 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679653215 :: [a]) = Partition a6989586621679653214 a6989586621679653215 | |
type family PartitionSym2 (a6989586621679653214 :: (~>) a Bool) (a6989586621679653215 :: [a]) :: ([a], [a]) where ... Source #
Equations
| PartitionSym2 a6989586621679653214 a6989586621679653215 = Partition a6989586621679653214 a6989586621679653215 |
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) (a6989586621679653138 :: [a]) Source # | |
data (!!@#@$$) (a6989586621679653138 :: [a]) :: (~>) Natural a infixl 9 Source #
Instances
| SingI1 ((!!@#@$$) :: [a] -> TyFun Natural a -> Type) Source # | |
| SingI d => SingI ((!!@#@$$) d :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings ((!!@#@$$) a6989586621679653138 :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply ((!!@#@$$) a6989586621679653138 :: TyFun Natural a -> Type) (a6989586621679653139 :: Natural) Source # | |
type family (a6989586621679653138 :: [a]) !!@#@$$$ (a6989586621679653139 :: 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 sing :: Sing ElemIndexSym0 # | |
| 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) (a6989586621679653514 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) (a6989586621679653514 :: a) = ElemIndexSym1 a6989586621679653514 | |
data ElemIndexSym1 (a6989586621679653514 :: 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 a6989586621679653514 :: TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemIndexSym1 a6989586621679653514 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679653515 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndexSym1 a6989586621679653514 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679653515 :: [a]) = ElemIndex a6989586621679653514 a6989586621679653515 | |
type family ElemIndexSym2 (a6989586621679653514 :: a) (a6989586621679653515 :: [a]) :: Maybe Natural where ... Source #
Equations
| ElemIndexSym2 a6989586621679653514 a6989586621679653515 = ElemIndex a6989586621679653514 a6989586621679653515 |
data ElemIndicesSym0 :: (~>) a ((~>) [a] [Natural]) Source #
Instances
| SEq a => SingI (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing ElemIndicesSym0 # | |
| SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) (a6989586621679653505 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) (a6989586621679653505 :: a) = ElemIndicesSym1 a6989586621679653505 | |
data ElemIndicesSym1 (a6989586621679653505 :: 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 a6989586621679653505 :: TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemIndicesSym1 a6989586621679653505 :: TyFun [a] [Natural] -> Type) (a6989586621679653506 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndicesSym1 a6989586621679653505 :: TyFun [a] [Natural] -> Type) (a6989586621679653506 :: [a]) = ElemIndices a6989586621679653505 a6989586621679653506 | |
type family ElemIndicesSym2 (a6989586621679653505 :: a) (a6989586621679653506 :: [a]) :: [Natural] where ... Source #
Equations
| ElemIndicesSym2 a6989586621679653505 a6989586621679653506 = ElemIndices a6989586621679653505 a6989586621679653506 |
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 sing :: Sing FindIndexSym0 # | |
| 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) (a6989586621679653496 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679653496 :: a ~> Bool) = FindIndexSym1 a6989586621679653496 | |
data FindIndexSym1 (a6989586621679653496 :: (~>) 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 a6989586621679653496 :: 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 a6989586621679653496 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679653497 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FindIndexSym1 a6989586621679653496 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679653497 :: [a]) = FindIndex a6989586621679653496 a6989586621679653497 | |
type family FindIndexSym2 (a6989586621679653496 :: (~>) a Bool) (a6989586621679653497 :: [a]) :: Maybe Natural where ... Source #
Equations
| FindIndexSym2 a6989586621679653496 a6989586621679653497 = FindIndex a6989586621679653496 a6989586621679653497 |
data FindIndicesSym0 :: (~>) ((~>) a Bool) ((~>) [a] [Natural]) Source #
Instances
| SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing FindIndicesSym0 # | |
| 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) (a6989586621679653473 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679653473 :: a ~> Bool) = FindIndicesSym1 a6989586621679653473 | |
data FindIndicesSym1 (a6989586621679653473 :: (~>) 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 a6989586621679653473 :: 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 a6989586621679653473 :: TyFun [a] [Natural] -> Type) (a6989586621679653474 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FindIndicesSym1 a6989586621679653473 :: TyFun [a] [Natural] -> Type) (a6989586621679653474 :: [a]) = FindIndices a6989586621679653473 a6989586621679653474 | |
type family FindIndicesSym2 (a6989586621679653473 :: (~>) a Bool) (a6989586621679653474 :: [a]) :: [Natural] where ... Source #
Equations
| FindIndicesSym2 a6989586621679653473 a6989586621679653474 = FindIndices a6989586621679653473 a6989586621679653474 |
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) (a6989586621679653848 :: [a]) Source # | |
data ZipSym1 (a6989586621679653848 :: [a]) :: (~>) [b] [(a, b)] Source #
Instances
| SingI1 (ZipSym1 :: [a] -> TyFun [b] [(a, b)] -> Type) Source # | |
| SingI d => SingI (ZipSym1 d :: TyFun [b] [(a, b)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ZipSym1 a6989586621679653848 :: TyFun [b] [(a, b)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipSym1 a6989586621679653848 :: TyFun [b] [(a, b)] -> Type) (a6989586621679653849 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family ZipSym2 (a6989586621679653848 :: [a]) (a6989586621679653849 :: [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) (a6989586621679653836 :: [a]) Source # | |
data Zip3Sym1 (a6989586621679653836 :: [a]) :: (~>) [b] ((~>) [c] [(a, b, c)]) Source #
Instances
| SingI1 (Zip3Sym1 :: [a] -> TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
| SingI d => SingI (Zip3Sym1 d :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Zip3Sym1 a6989586621679653836 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip3Sym1 a6989586621679653836 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679653837 :: [b]) Source # | |
data Zip3Sym2 (a6989586621679653836 :: [a]) (a6989586621679653837 :: [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 # | |
| (SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 :: TyFun [c] [(a, b, c)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Zip3Sym2 a6989586621679653836 a6989586621679653837 :: TyFun [c] [(a, b, c)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip3Sym2 a6989586621679653836 a6989586621679653837 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679653838 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family Zip3Sym3 (a6989586621679653836 :: [a]) (a6989586621679653837 :: [b]) (a6989586621679653838 :: [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) (a6989586621679805269 :: [a]) Source # | |
data Zip4Sym1 (a6989586621679805269 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] [(a, b, c, d)])) Source #
Instances
| SuppressUnusedWarnings (Zip4Sym1 a6989586621679805269 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip4Sym1 a6989586621679805269 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621679805270 :: [b]) Source # | |
data Zip4Sym2 (a6989586621679805269 :: [a]) (a6989586621679805270 :: [b]) :: (~>) [c] ((~>) [d] [(a, b, c, d)]) Source #
Instances
| SuppressUnusedWarnings (Zip4Sym2 a6989586621679805269 a6989586621679805270 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip4Sym2 a6989586621679805269 a6989586621679805270 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621679805271 :: [c]) Source # | |
data Zip4Sym3 (a6989586621679805269 :: [a]) (a6989586621679805270 :: [b]) (a6989586621679805271 :: [c]) :: (~>) [d] [(a, b, c, d)] Source #
Instances
| SuppressUnusedWarnings (Zip4Sym3 a6989586621679805269 a6989586621679805270 a6989586621679805271 :: TyFun [d] [(a, b, c, d)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip4Sym3 a6989586621679805269 a6989586621679805270 a6989586621679805271 :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621679805272 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family Zip4Sym4 (a6989586621679805269 :: [a]) (a6989586621679805270 :: [b]) (a6989586621679805271 :: [c]) (a6989586621679805272 :: [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) (a6989586621679805246 :: [a]) Source # | |
data Zip5Sym1 (a6989586621679805246 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [(a, b, c, d, e)]))) Source #
Instances
| SuppressUnusedWarnings (Zip5Sym1 a6989586621679805246 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym1 a6989586621679805246 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621679805247 :: [b]) Source # | |
data Zip5Sym2 (a6989586621679805246 :: [a]) (a6989586621679805247 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] [(a, b, c, d, e)])) Source #
Instances
| SuppressUnusedWarnings (Zip5Sym2 a6989586621679805246 a6989586621679805247 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym2 a6989586621679805246 a6989586621679805247 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621679805248 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip5Sym3 (a6989586621679805246 :: [a]) (a6989586621679805247 :: [b]) (a6989586621679805248 :: [c]) :: (~>) [d] ((~>) [e] [(a, b, c, d, e)]) Source #
Instances
| SuppressUnusedWarnings (Zip5Sym3 a6989586621679805246 a6989586621679805247 a6989586621679805248 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym3 a6989586621679805246 a6989586621679805247 a6989586621679805248 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621679805249 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip5Sym4 (a6989586621679805246 :: [a]) (a6989586621679805247 :: [b]) (a6989586621679805248 :: [c]) (a6989586621679805249 :: [d]) :: (~>) [e] [(a, b, c, d, e)] Source #
Instances
| SuppressUnusedWarnings (Zip5Sym4 a6989586621679805246 a6989586621679805247 a6989586621679805248 a6989586621679805249 :: TyFun [e] [(a, b, c, d, e)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym4 a6989586621679805246 a6989586621679805247 a6989586621679805248 a6989586621679805249 :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621679805250 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family Zip5Sym5 (a6989586621679805246 :: [a]) (a6989586621679805247 :: [b]) (a6989586621679805248 :: [c]) (a6989586621679805249 :: [d]) (a6989586621679805250 :: [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) (a6989586621679805218 :: [a]) Source # | |
data Zip6Sym1 (a6989586621679805218 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)])))) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym1 a6989586621679805218 :: 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 a6989586621679805218 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621679805219 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip6Sym2 (a6989586621679805218 :: [a]) (a6989586621679805219 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)]))) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym2 a6989586621679805218 a6989586621679805219 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym2 a6989586621679805218 a6989586621679805219 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621679805220 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip6Sym3 (a6989586621679805218 :: [a]) (a6989586621679805219 :: [b]) (a6989586621679805220 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] [(a, b, c, d, e, f)])) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym3 a6989586621679805218 a6989586621679805219 a6989586621679805220 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym3 a6989586621679805218 a6989586621679805219 a6989586621679805220 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679805221 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip6Sym3 a6989586621679805218 a6989586621679805219 a6989586621679805220 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679805221 :: [d]) = Zip6Sym4 a6989586621679805218 a6989586621679805219 a6989586621679805220 a6989586621679805221 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type | |
data Zip6Sym4 (a6989586621679805218 :: [a]) (a6989586621679805219 :: [b]) (a6989586621679805220 :: [c]) (a6989586621679805221 :: [d]) :: (~>) [e] ((~>) [f] [(a, b, c, d, e, f)]) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym4 a6989586621679805218 a6989586621679805219 a6989586621679805220 a6989586621679805221 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym4 a6989586621679805218 a6989586621679805219 a6989586621679805220 a6989586621679805221 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679805222 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip6Sym4 a6989586621679805218 a6989586621679805219 a6989586621679805220 a6989586621679805221 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679805222 :: [e]) = Zip6Sym5 a6989586621679805218 a6989586621679805219 a6989586621679805220 a6989586621679805221 a6989586621679805222 :: TyFun [f] [(a, b, c, d, e, f)] -> Type | |
data Zip6Sym5 (a6989586621679805218 :: [a]) (a6989586621679805219 :: [b]) (a6989586621679805220 :: [c]) (a6989586621679805221 :: [d]) (a6989586621679805222 :: [e]) :: (~>) [f] [(a, b, c, d, e, f)] Source #
Instances
| SuppressUnusedWarnings (Zip6Sym5 a6989586621679805218 a6989586621679805219 a6989586621679805220 a6989586621679805221 a6989586621679805222 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym5 a6989586621679805218 a6989586621679805219 a6989586621679805220 a6989586621679805221 a6989586621679805222 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621679805223 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip6Sym5 a6989586621679805218 a6989586621679805219 a6989586621679805220 a6989586621679805221 a6989586621679805222 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621679805223 :: [f]) = Zip6 a6989586621679805218 a6989586621679805219 a6989586621679805220 a6989586621679805221 a6989586621679805222 a6989586621679805223 | |
type family Zip6Sym6 (a6989586621679805218 :: [a]) (a6989586621679805219 :: [b]) (a6989586621679805220 :: [c]) (a6989586621679805221 :: [d]) (a6989586621679805222 :: [e]) (a6989586621679805223 :: [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) (a6989586621679805185 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip7Sym1 (a6989586621679805185 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)]))))) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym1 a6989586621679805185 :: 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 a6989586621679805185 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621679805186 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip7Sym2 (a6989586621679805185 :: [a]) (a6989586621679805186 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)])))) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym2 a6989586621679805185 a6989586621679805186 :: 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 a6989586621679805185 a6989586621679805186 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679805187 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym2 a6989586621679805185 a6989586621679805186 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679805187 :: [c]) = Zip7Sym3 a6989586621679805185 a6989586621679805186 a6989586621679805187 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type | |
data Zip7Sym3 (a6989586621679805185 :: [a]) (a6989586621679805186 :: [b]) (a6989586621679805187 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)]))) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym3 a6989586621679805185 a6989586621679805186 a6989586621679805187 :: 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 a6989586621679805185 a6989586621679805186 a6989586621679805187 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679805188 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym3 a6989586621679805185 a6989586621679805186 a6989586621679805187 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679805188 :: [d]) = Zip7Sym4 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type | |
data Zip7Sym4 (a6989586621679805185 :: [a]) (a6989586621679805186 :: [b]) (a6989586621679805187 :: [c]) (a6989586621679805188 :: [d]) :: (~>) [e] ((~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)])) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym4 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym4 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679805189 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym4 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679805189 :: [e]) = Zip7Sym5 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 a6989586621679805189 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type | |
data Zip7Sym5 (a6989586621679805185 :: [a]) (a6989586621679805186 :: [b]) (a6989586621679805187 :: [c]) (a6989586621679805188 :: [d]) (a6989586621679805189 :: [e]) :: (~>) [f] ((~>) [g] [(a, b, c, d, e, f, g)]) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym5 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 a6989586621679805189 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym5 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 a6989586621679805189 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679805190 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym5 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 a6989586621679805189 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679805190 :: [f]) = Zip7Sym6 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 a6989586621679805189 a6989586621679805190 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type | |
data Zip7Sym6 (a6989586621679805185 :: [a]) (a6989586621679805186 :: [b]) (a6989586621679805187 :: [c]) (a6989586621679805188 :: [d]) (a6989586621679805189 :: [e]) (a6989586621679805190 :: [f]) :: (~>) [g] [(a, b, c, d, e, f, g)] Source #
Instances
| SuppressUnusedWarnings (Zip7Sym6 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 a6989586621679805189 a6989586621679805190 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym6 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 a6989586621679805189 a6989586621679805190 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621679805191 :: [g]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym6 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 a6989586621679805189 a6989586621679805190 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621679805191 :: [g]) = Zip7 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 a6989586621679805189 a6989586621679805190 a6989586621679805191 | |
type family Zip7Sym7 (a6989586621679805185 :: [a]) (a6989586621679805186 :: [b]) (a6989586621679805187 :: [c]) (a6989586621679805188 :: [d]) (a6989586621679805189 :: [e]) (a6989586621679805190 :: [f]) (a6989586621679805191 :: [g]) :: [(a, b, c, d, e, f, g)] where ... Source #
Equations
| Zip7Sym7 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 a6989586621679805189 a6989586621679805190 a6989586621679805191 = Zip7 a6989586621679805185 a6989586621679805186 a6989586621679805187 a6989586621679805188 a6989586621679805189 a6989586621679805190 a6989586621679805191 |
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) (a6989586621679653824 :: a ~> (b ~> c)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679653824 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621679653824 | |
data ZipWithSym1 (a6989586621679653824 :: (~>) 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 a6989586621679653824 :: TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym1 a6989586621679653824 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679653825 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWithSym1 a6989586621679653824 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679653825 :: [a]) = ZipWithSym2 a6989586621679653824 a6989586621679653825 | |
data ZipWithSym2 (a6989586621679653824 :: (~>) a ((~>) b c)) (a6989586621679653825 :: [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 | |
| (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 a6989586621679653824 a6989586621679653825 :: TyFun [b] [c] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym2 a6989586621679653824 a6989586621679653825 :: TyFun [b] [c] -> Type) (a6989586621679653826 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWithSym2 a6989586621679653824 a6989586621679653825 :: TyFun [b] [c] -> Type) (a6989586621679653826 :: [b]) = ZipWith a6989586621679653824 a6989586621679653825 a6989586621679653826 | |
type family ZipWithSym3 (a6989586621679653824 :: (~>) a ((~>) b c)) (a6989586621679653825 :: [a]) (a6989586621679653826 :: [b]) :: [c] where ... Source #
Equations
| ZipWithSym3 a6989586621679653824 a6989586621679653825 a6989586621679653826 = ZipWith a6989586621679653824 a6989586621679653825 a6989586621679653826 |
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) (a6989586621679653809 :: a ~> (b ~> (c ~> d))) Source # | |
Defined in Data.List.Singletons.Internal | |
data ZipWith3Sym1 (a6989586621679653809 :: (~>) 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 a6989586621679653809 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith3Sym1 a6989586621679653809 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679653810 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym1 a6989586621679653809 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679653810 :: [a]) = ZipWith3Sym2 a6989586621679653809 a6989586621679653810 | |
data ZipWith3Sym2 (a6989586621679653809 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679653810 :: [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 | |
| (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 a6989586621679653809 a6989586621679653810 :: TyFun [b] ([c] ~> [d]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith3Sym2 a6989586621679653809 a6989586621679653810 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679653811 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym2 a6989586621679653809 a6989586621679653810 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679653811 :: [b]) = ZipWith3Sym3 a6989586621679653809 a6989586621679653810 a6989586621679653811 | |
data ZipWith3Sym3 (a6989586621679653809 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679653810 :: [a]) (a6989586621679653811 :: [b]) :: (~>) [c] [d] Source #
Instances
| SingI d2 => SingI2 (ZipWith3Sym3 d2 :: [a] -> [b] -> TyFun [c] [d1] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (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 a6989586621679653809 a6989586621679653810 a6989586621679653811 :: TyFun [c] [d] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith3Sym3 a6989586621679653809 a6989586621679653810 a6989586621679653811 :: TyFun [c] [d] -> Type) (a6989586621679653812 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym3 a6989586621679653809 a6989586621679653810 a6989586621679653811 :: TyFun [c] [d] -> Type) (a6989586621679653812 :: [c]) = ZipWith3 a6989586621679653809 a6989586621679653810 a6989586621679653811 a6989586621679653812 | |
type family ZipWith3Sym4 (a6989586621679653809 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679653810 :: [a]) (a6989586621679653811 :: [b]) (a6989586621679653812 :: [c]) :: [d] where ... Source #
Equations
| ZipWith3Sym4 a6989586621679653809 a6989586621679653810 a6989586621679653811 a6989586621679653812 = ZipWith3 a6989586621679653809 a6989586621679653810 a6989586621679653811 a6989586621679653812 |
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) (a6989586621679805149 :: a ~> (b ~> (c ~> (d ~> e)))) Source # | |
data ZipWith4Sym1 (a6989586621679805149 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] [e]))) Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym1 a6989586621679805149 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym1 a6989586621679805149 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679805150 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym1 a6989586621679805149 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679805150 :: [a]) = ZipWith4Sym2 a6989586621679805149 a6989586621679805150 | |
data ZipWith4Sym2 (a6989586621679805149 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679805150 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] [e])) Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym2 a6989586621679805149 a6989586621679805150 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym2 a6989586621679805149 a6989586621679805150 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679805151 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym2 a6989586621679805149 a6989586621679805150 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679805151 :: [b]) = ZipWith4Sym3 a6989586621679805149 a6989586621679805150 a6989586621679805151 | |
data ZipWith4Sym3 (a6989586621679805149 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679805150 :: [a]) (a6989586621679805151 :: [b]) :: (~>) [c] ((~>) [d] [e]) Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym3 a6989586621679805149 a6989586621679805150 a6989586621679805151 :: TyFun [c] ([d] ~> [e]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym3 a6989586621679805149 a6989586621679805150 a6989586621679805151 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679805152 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym3 a6989586621679805149 a6989586621679805150 a6989586621679805151 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679805152 :: [c]) = ZipWith4Sym4 a6989586621679805149 a6989586621679805150 a6989586621679805151 a6989586621679805152 | |
data ZipWith4Sym4 (a6989586621679805149 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679805150 :: [a]) (a6989586621679805151 :: [b]) (a6989586621679805152 :: [c]) :: (~>) [d] [e] Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym4 a6989586621679805149 a6989586621679805150 a6989586621679805151 a6989586621679805152 :: TyFun [d] [e] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym4 a6989586621679805149 a6989586621679805150 a6989586621679805151 a6989586621679805152 :: TyFun [d] [e] -> Type) (a6989586621679805153 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym4 a6989586621679805149 a6989586621679805150 a6989586621679805151 a6989586621679805152 :: TyFun [d] [e] -> Type) (a6989586621679805153 :: [d]) = ZipWith4 a6989586621679805149 a6989586621679805150 a6989586621679805151 a6989586621679805152 a6989586621679805153 | |
type family ZipWith4Sym5 (a6989586621679805149 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621679805150 :: [a]) (a6989586621679805151 :: [b]) (a6989586621679805152 :: [c]) (a6989586621679805153 :: [d]) :: [e] where ... Source #
Equations
| ZipWith4Sym5 a6989586621679805149 a6989586621679805150 a6989586621679805151 a6989586621679805152 a6989586621679805153 = ZipWith4 a6989586621679805149 a6989586621679805150 a6989586621679805151 a6989586621679805152 a6989586621679805153 |
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) (a6989586621679805126 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) Source # | |
data ZipWith5Sym1 (a6989586621679805126 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [f])))) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym1 a6989586621679805126 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym1 a6989586621679805126 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679805127 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym1 a6989586621679805126 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679805127 :: [a]) = ZipWith5Sym2 a6989586621679805126 a6989586621679805127 | |
data ZipWith5Sym2 (a6989586621679805126 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679805127 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] [f]))) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym2 a6989586621679805126 a6989586621679805127 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym2 a6989586621679805126 a6989586621679805127 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679805128 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym2 a6989586621679805126 a6989586621679805127 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679805128 :: [b]) = ZipWith5Sym3 a6989586621679805126 a6989586621679805127 a6989586621679805128 | |
data ZipWith5Sym3 (a6989586621679805126 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679805127 :: [a]) (a6989586621679805128 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] [f])) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym3 a6989586621679805126 a6989586621679805127 a6989586621679805128 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym3 a6989586621679805126 a6989586621679805127 a6989586621679805128 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679805129 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym3 a6989586621679805126 a6989586621679805127 a6989586621679805128 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679805129 :: [c]) = ZipWith5Sym4 a6989586621679805126 a6989586621679805127 a6989586621679805128 a6989586621679805129 | |
data ZipWith5Sym4 (a6989586621679805126 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679805127 :: [a]) (a6989586621679805128 :: [b]) (a6989586621679805129 :: [c]) :: (~>) [d] ((~>) [e] [f]) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym4 a6989586621679805126 a6989586621679805127 a6989586621679805128 a6989586621679805129 :: TyFun [d] ([e] ~> [f]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym4 a6989586621679805126 a6989586621679805127 a6989586621679805128 a6989586621679805129 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679805130 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym4 a6989586621679805126 a6989586621679805127 a6989586621679805128 a6989586621679805129 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679805130 :: [d]) = ZipWith5Sym5 a6989586621679805126 a6989586621679805127 a6989586621679805128 a6989586621679805129 a6989586621679805130 | |
data ZipWith5Sym5 (a6989586621679805126 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679805127 :: [a]) (a6989586621679805128 :: [b]) (a6989586621679805129 :: [c]) (a6989586621679805130 :: [d]) :: (~>) [e] [f] Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym5 a6989586621679805126 a6989586621679805127 a6989586621679805128 a6989586621679805129 a6989586621679805130 :: TyFun [e] [f] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym5 a6989586621679805126 a6989586621679805127 a6989586621679805128 a6989586621679805129 a6989586621679805130 :: TyFun [e] [f] -> Type) (a6989586621679805131 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym5 a6989586621679805126 a6989586621679805127 a6989586621679805128 a6989586621679805129 a6989586621679805130 :: TyFun [e] [f] -> Type) (a6989586621679805131 :: [e]) = ZipWith5 a6989586621679805126 a6989586621679805127 a6989586621679805128 a6989586621679805129 a6989586621679805130 a6989586621679805131 | |
type family ZipWith5Sym6 (a6989586621679805126 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621679805127 :: [a]) (a6989586621679805128 :: [b]) (a6989586621679805129 :: [c]) (a6989586621679805130 :: [d]) (a6989586621679805131 :: [e]) :: [f] where ... Source #
Equations
| ZipWith5Sym6 a6989586621679805126 a6989586621679805127 a6989586621679805128 a6989586621679805129 a6989586621679805130 a6989586621679805131 = ZipWith5 a6989586621679805126 a6989586621679805127 a6989586621679805128 a6989586621679805129 a6989586621679805130 a6989586621679805131 |
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) (a6989586621679805099 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) Source # | |
data ZipWith6Sym1 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g]))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym1 a6989586621679805099 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym1 a6989586621679805099 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679805100 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym1 a6989586621679805099 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679805100 :: [a]) = ZipWith6Sym2 a6989586621679805099 a6989586621679805100 | |
data ZipWith6Sym2 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679805100 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g])))) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym2 a6989586621679805099 a6989586621679805100 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym2 a6989586621679805099 a6989586621679805100 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679805101 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym2 a6989586621679805099 a6989586621679805100 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679805101 :: [b]) = ZipWith6Sym3 a6989586621679805099 a6989586621679805100 a6989586621679805101 | |
data ZipWith6Sym3 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679805100 :: [a]) (a6989586621679805101 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] [g]))) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym3 a6989586621679805099 a6989586621679805100 a6989586621679805101 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym3 a6989586621679805099 a6989586621679805100 a6989586621679805101 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679805102 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym3 a6989586621679805099 a6989586621679805100 a6989586621679805101 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679805102 :: [c]) = ZipWith6Sym4 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 | |
data ZipWith6Sym4 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679805100 :: [a]) (a6989586621679805101 :: [b]) (a6989586621679805102 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] [g])) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym4 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym4 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679805103 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym4 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679805103 :: [d]) = ZipWith6Sym5 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 a6989586621679805103 | |
data ZipWith6Sym5 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679805100 :: [a]) (a6989586621679805101 :: [b]) (a6989586621679805102 :: [c]) (a6989586621679805103 :: [d]) :: (~>) [e] ((~>) [f] [g]) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym5 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 a6989586621679805103 :: TyFun [e] ([f] ~> [g]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym5 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 a6989586621679805103 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679805104 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym5 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 a6989586621679805103 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679805104 :: [e]) = ZipWith6Sym6 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 a6989586621679805103 a6989586621679805104 | |
data ZipWith6Sym6 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679805100 :: [a]) (a6989586621679805101 :: [b]) (a6989586621679805102 :: [c]) (a6989586621679805103 :: [d]) (a6989586621679805104 :: [e]) :: (~>) [f] [g] Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym6 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 a6989586621679805103 a6989586621679805104 :: TyFun [f] [g] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym6 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 a6989586621679805103 a6989586621679805104 :: TyFun [f] [g] -> Type) (a6989586621679805105 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym6 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 a6989586621679805103 a6989586621679805104 :: TyFun [f] [g] -> Type) (a6989586621679805105 :: [f]) = ZipWith6 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 a6989586621679805103 a6989586621679805104 a6989586621679805105 | |
type family ZipWith6Sym7 (a6989586621679805099 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621679805100 :: [a]) (a6989586621679805101 :: [b]) (a6989586621679805102 :: [c]) (a6989586621679805103 :: [d]) (a6989586621679805104 :: [e]) (a6989586621679805105 :: [f]) :: [g] where ... Source #
Equations
| ZipWith6Sym7 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 a6989586621679805103 a6989586621679805104 a6989586621679805105 = ZipWith6 a6989586621679805099 a6989586621679805100 a6989586621679805101 a6989586621679805102 a6989586621679805103 a6989586621679805104 a6989586621679805105 |
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) (a6989586621679805068 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) Source # | |
Defined in Data.List.Singletons.Internal | |
data ZipWith7Sym1 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) :: (~>) [a] ((~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h])))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym1 a6989586621679805068 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym1 a6989586621679805068 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679805069 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym1 a6989586621679805068 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679805069 :: [a]) = ZipWith7Sym2 a6989586621679805068 a6989586621679805069 | |
data ZipWith7Sym2 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) :: (~>) [b] ((~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h]))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym2 a6989586621679805068 a6989586621679805069 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym2 a6989586621679805068 a6989586621679805069 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679805070 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym2 a6989586621679805068 a6989586621679805069 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679805070 :: [b]) = ZipWith7Sym3 a6989586621679805068 a6989586621679805069 a6989586621679805070 | |
data ZipWith7Sym3 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) (a6989586621679805070 :: [b]) :: (~>) [c] ((~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h])))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym3 a6989586621679805068 a6989586621679805069 a6989586621679805070 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym3 a6989586621679805068 a6989586621679805069 a6989586621679805070 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679805071 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym3 a6989586621679805068 a6989586621679805069 a6989586621679805070 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679805071 :: [c]) = ZipWith7Sym4 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 | |
data ZipWith7Sym4 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) (a6989586621679805070 :: [b]) (a6989586621679805071 :: [c]) :: (~>) [d] ((~>) [e] ((~>) [f] ((~>) [g] [h]))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym4 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym4 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679805072 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym4 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679805072 :: [d]) = ZipWith7Sym5 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 | |
data ZipWith7Sym5 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) (a6989586621679805070 :: [b]) (a6989586621679805071 :: [c]) (a6989586621679805072 :: [d]) :: (~>) [e] ((~>) [f] ((~>) [g] [h])) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym5 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym5 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679805073 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym5 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679805073 :: [e]) = ZipWith7Sym6 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 a6989586621679805073 | |
data ZipWith7Sym6 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) (a6989586621679805070 :: [b]) (a6989586621679805071 :: [c]) (a6989586621679805072 :: [d]) (a6989586621679805073 :: [e]) :: (~>) [f] ((~>) [g] [h]) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym6 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 a6989586621679805073 :: TyFun [f] ([g] ~> [h]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym6 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 a6989586621679805073 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679805074 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym6 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 a6989586621679805073 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679805074 :: [f]) = ZipWith7Sym7 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 a6989586621679805073 a6989586621679805074 | |
data ZipWith7Sym7 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) (a6989586621679805070 :: [b]) (a6989586621679805071 :: [c]) (a6989586621679805072 :: [d]) (a6989586621679805073 :: [e]) (a6989586621679805074 :: [f]) :: (~>) [g] [h] Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym7 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 a6989586621679805073 a6989586621679805074 :: TyFun [g] [h] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym7 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 a6989586621679805073 a6989586621679805074 :: TyFun [g] [h] -> Type) (a6989586621679805075 :: [g]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym7 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 a6989586621679805073 a6989586621679805074 :: TyFun [g] [h] -> Type) (a6989586621679805075 :: [g]) = ZipWith7 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 a6989586621679805073 a6989586621679805074 a6989586621679805075 | |
type family ZipWith7Sym8 (a6989586621679805068 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621679805069 :: [a]) (a6989586621679805070 :: [b]) (a6989586621679805071 :: [c]) (a6989586621679805072 :: [d]) (a6989586621679805073 :: [e]) (a6989586621679805074 :: [f]) (a6989586621679805075 :: [g]) :: [h] where ... Source #
Equations
| ZipWith7Sym8 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 a6989586621679805073 a6989586621679805074 a6989586621679805075 = ZipWith7 a6989586621679805068 a6989586621679805069 a6989586621679805070 a6989586621679805071 a6989586621679805072 a6989586621679805073 a6989586621679805074 a6989586621679805075 |
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) (a6989586621679653790 :: [(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) (a6989586621679653772 :: [(a, b, c)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679653772 :: [(a, b, c)]) = Unzip3 a6989586621679653772 | |
type family Unzip3Sym1 (a6989586621679653772 :: [(a, b, c)]) :: ([a], [b], [c]) where ... Source #
Equations
| Unzip3Sym1 a6989586621679653772 = Unzip3 a6989586621679653772 |
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) (a6989586621679653752 :: [(a, b, c, d)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679653752 :: [(a, b, c, d)]) = Unzip4 a6989586621679653752 | |
type family Unzip4Sym1 (a6989586621679653752 :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ... Source #
Equations
| Unzip4Sym1 a6989586621679653752 = Unzip4 a6989586621679653752 |
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) (a6989586621679653730 :: [(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) (a6989586621679653730 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679653730 | |
type family Unzip5Sym1 (a6989586621679653730 :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ... Source #
Equations
| Unzip5Sym1 a6989586621679653730 = Unzip5 a6989586621679653730 |
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) (a6989586621679653706 :: [(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) (a6989586621679653706 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679653706 | |
type family Unzip6Sym1 (a6989586621679653706 :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ... Source #
Equations
| Unzip6Sym1 a6989586621679653706 = Unzip6 a6989586621679653706 |
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) (a6989586621679653680 :: [(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) (a6989586621679653680 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679653680 | |
type family Unzip7Sym1 (a6989586621679653680 :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... Source #
Equations
| Unzip7Sym1 a6989586621679653680 = Unzip7 a6989586621679653680 |
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 (a6989586621679653675 :: [Symbol]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family UnlinesSym1 (a6989586621679653675 :: [Symbol]) :: Symbol where ... Source #
Equations
| UnlinesSym1 a6989586621679653675 = Unlines a6989586621679653675 |
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 (a6989586621679653665 :: [Symbol]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family UnwordsSym1 (a6989586621679653665 :: [Symbol]) :: Symbol where ... Source #
Equations
| UnwordsSym1 a6989586621679653665 = Unwords a6989586621679653665 |
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) (a6989586621679653121 :: [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) (a6989586621679653659 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679653659 :: a) = DeleteSym1 a6989586621679653659 | |
data DeleteSym1 (a6989586621679653659 :: 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 a6989586621679653659 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteSym1 a6989586621679653659 :: TyFun [a] [a] -> Type) (a6989586621679653660 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteSym1 a6989586621679653659 :: TyFun [a] [a] -> Type) (a6989586621679653660 :: [a]) = Delete a6989586621679653659 a6989586621679653660 | |
type family DeleteSym2 (a6989586621679653659 :: a) (a6989586621679653660 :: [a]) :: [a] where ... Source #
Equations
| DeleteSym2 a6989586621679653659 a6989586621679653660 = Delete a6989586621679653659 a6989586621679653660 |
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) (a6989586621679653648 :: [a]) Source # | |
data (\\@#@$$) (a6989586621679653648 :: [a]) :: (~>) [a] [a] infix 5 Source #
Instances
| SEq a => SingI1 ((\\@#@$$) :: [a] -> TyFun [a] [a] -> Type) Source # | |
| (SEq a, SingI d) => SingI ((\\@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings ((\\@#@$$) a6989586621679653648 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply ((\\@#@$$) a6989586621679653648 :: TyFun [a] [a] -> Type) (a6989586621679653649 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family (a6989586621679653648 :: [a]) \\@#@$$$ (a6989586621679653649 :: [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) (a6989586621679653075 :: [a]) Source # | |
data UnionSym1 (a6989586621679653075 :: [a]) :: (~>) [a] [a] Source #
Instances
| SEq a => SingI1 (UnionSym1 :: [a] -> TyFun [a] [a] -> Type) Source # | |
| (SEq a, SingI d) => SingI (UnionSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (UnionSym1 a6989586621679653075 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnionSym1 a6989586621679653075 :: TyFun [a] [a] -> Type) (a6989586621679653076 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family UnionSym2 (a6989586621679653075 :: [a]) (a6989586621679653076 :: [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 sing :: Sing IntersectSym0 # | |
| SuppressUnusedWarnings (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679653466 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679653466 :: [a]) = IntersectSym1 a6989586621679653466 | |
data IntersectSym1 (a6989586621679653466 :: [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 a6989586621679653466 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersectSym1 a6989586621679653466 :: TyFun [a] [a] -> Type) (a6989586621679653467 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectSym1 a6989586621679653466 :: TyFun [a] [a] -> Type) (a6989586621679653467 :: [a]) = Intersect a6989586621679653466 a6989586621679653467 | |
type family IntersectSym2 (a6989586621679653466 :: [a]) (a6989586621679653467 :: [a]) :: [a] where ... Source #
Equations
| IntersectSym2 a6989586621679653466 a6989586621679653467 = Intersect a6989586621679653466 a6989586621679653467 |
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) (a6989586621679653268 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679653268 :: a) = InsertSym1 a6989586621679653268 | |
data InsertSym1 (a6989586621679653268 :: 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 a6989586621679653268 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertSym1 a6989586621679653268 :: TyFun [a] [a] -> Type) (a6989586621679653269 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertSym1 a6989586621679653268 :: TyFun [a] [a] -> Type) (a6989586621679653269 :: [a]) = Insert a6989586621679653268 a6989586621679653269 | |
type family InsertSym2 (a6989586621679653268 :: a) (a6989586621679653269 :: [a]) :: [a] where ... Source #
Equations
| InsertSym2 a6989586621679653268 a6989586621679653269 = Insert a6989586621679653268 a6989586621679653269 |
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) (a6989586621679653263 :: [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) (a6989586621679653103 :: a ~> (a ~> Bool)) Source # | |
data NubBySym1 (a6989586621679653103 :: (~>) 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 a6989586621679653103 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (NubBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [a] -> Type) Source # | |
| type Apply (NubBySym1 a6989586621679653103 :: TyFun [a] [a] -> Type) (a6989586621679653104 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family NubBySym2 (a6989586621679653103 :: (~>) a ((~>) a Bool)) (a6989586621679653104 :: [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) (a6989586621679653629 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679653629 :: a ~> (a ~> Bool)) = DeleteBySym1 a6989586621679653629 | |
data DeleteBySym1 (a6989586621679653629 :: (~>) 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 a6989586621679653629 :: 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 a6989586621679653629 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679653630 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteBySym1 a6989586621679653629 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679653630 :: a) = DeleteBySym2 a6989586621679653629 a6989586621679653630 | |
data DeleteBySym2 (a6989586621679653629 :: (~>) a ((~>) a Bool)) (a6989586621679653630 :: 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 | |
| (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 a6989586621679653629 a6989586621679653630 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteBySym2 a6989586621679653629 a6989586621679653630 :: TyFun [a] [a] -> Type) (a6989586621679653631 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteBySym2 a6989586621679653629 a6989586621679653630 :: TyFun [a] [a] -> Type) (a6989586621679653631 :: [a]) = DeleteBy a6989586621679653629 a6989586621679653630 a6989586621679653631 | |
type family DeleteBySym3 (a6989586621679653629 :: (~>) a ((~>) a Bool)) (a6989586621679653630 :: a) (a6989586621679653631 :: [a]) :: [a] where ... Source #
Equations
| DeleteBySym3 a6989586621679653629 a6989586621679653630 a6989586621679653631 = DeleteBy a6989586621679653629 a6989586621679653630 a6989586621679653631 |
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) (a6989586621679653619 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679653619 :: a ~> (a ~> Bool)) = DeleteFirstsBySym1 a6989586621679653619 | |
data DeleteFirstsBySym1 (a6989586621679653619 :: (~>) 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 a6989586621679653619 :: 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 a6989586621679653619 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679653620 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteFirstsBySym1 a6989586621679653619 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679653620 :: [a]) = DeleteFirstsBySym2 a6989586621679653619 a6989586621679653620 | |
data DeleteFirstsBySym2 (a6989586621679653619 :: (~>) a ((~>) a Bool)) (a6989586621679653620 :: [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 | |
| (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 a6989586621679653619 a6989586621679653620 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteFirstsBySym2 a6989586621679653619 a6989586621679653620 :: TyFun [a] [a] -> Type) (a6989586621679653621 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteFirstsBySym2 a6989586621679653619 a6989586621679653620 :: TyFun [a] [a] -> Type) (a6989586621679653621 :: [a]) = DeleteFirstsBy a6989586621679653619 a6989586621679653620 a6989586621679653621 | |
type family DeleteFirstsBySym3 (a6989586621679653619 :: (~>) a ((~>) a Bool)) (a6989586621679653620 :: [a]) (a6989586621679653621 :: [a]) :: [a] where ... Source #
Equations
| DeleteFirstsBySym3 a6989586621679653619 a6989586621679653620 a6989586621679653621 = DeleteFirstsBy a6989586621679653619 a6989586621679653620 a6989586621679653621 |
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) (a6989586621679653083 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679653083 :: a ~> (a ~> Bool)) = UnionBySym1 a6989586621679653083 | |
data UnionBySym1 (a6989586621679653083 :: (~>) 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 a6989586621679653083 :: 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 a6989586621679653083 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679653084 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnionBySym1 a6989586621679653083 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679653084 :: [a]) = UnionBySym2 a6989586621679653083 a6989586621679653084 | |
data UnionBySym2 (a6989586621679653083 :: (~>) a ((~>) a Bool)) (a6989586621679653084 :: [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 | |
| (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 a6989586621679653083 a6989586621679653084 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnionBySym2 a6989586621679653083 a6989586621679653084 :: TyFun [a] [a] -> Type) (a6989586621679653085 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnionBySym2 a6989586621679653083 a6989586621679653084 :: TyFun [a] [a] -> Type) (a6989586621679653085 :: [a]) = UnionBy a6989586621679653083 a6989586621679653084 a6989586621679653085 | |
type family UnionBySym3 (a6989586621679653083 :: (~>) a ((~>) a Bool)) (a6989586621679653084 :: [a]) (a6989586621679653085 :: [a]) :: [a] where ... Source #
Equations
| UnionBySym3 a6989586621679653083 a6989586621679653084 a6989586621679653085 = UnionBy a6989586621679653083 a6989586621679653084 a6989586621679653085 |
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 sing :: Sing IntersectBySym0 # | |
| 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) (a6989586621679653444 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679653444 :: a ~> (a ~> Bool)) = IntersectBySym1 a6989586621679653444 | |
data IntersectBySym1 (a6989586621679653444 :: (~>) 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 a6989586621679653444 :: 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 a6989586621679653444 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679653445 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectBySym1 a6989586621679653444 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679653445 :: [a]) = IntersectBySym2 a6989586621679653444 a6989586621679653445 | |
data IntersectBySym2 (a6989586621679653444 :: (~>) a ((~>) a Bool)) (a6989586621679653445 :: [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 | |
| (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 a6989586621679653444 a6989586621679653445 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersectBySym2 a6989586621679653444 a6989586621679653445 :: TyFun [a] [a] -> Type) (a6989586621679653446 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectBySym2 a6989586621679653444 a6989586621679653445 :: TyFun [a] [a] -> Type) (a6989586621679653446 :: [a]) = IntersectBy a6989586621679653444 a6989586621679653445 a6989586621679653446 | |
type family IntersectBySym3 (a6989586621679653444 :: (~>) a ((~>) a Bool)) (a6989586621679653445 :: [a]) (a6989586621679653446 :: [a]) :: [a] where ... Source #
Equations
| IntersectBySym3 a6989586621679653444 a6989586621679653445 a6989586621679653446 = IntersectBy a6989586621679653444 a6989586621679653445 a6989586621679653446 |
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) (a6989586621679653236 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679653236 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621679653236 | |
data GroupBySym1 (a6989586621679653236 :: (~>) 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 a6989586621679653236 :: 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 a6989586621679653236 :: TyFun [a] [[a]] -> Type) (a6989586621679653237 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (GroupBySym1 a6989586621679653236 :: TyFun [a] [[a]] -> Type) (a6989586621679653237 :: [a]) = GroupBy a6989586621679653236 a6989586621679653237 | |
type family GroupBySym2 (a6989586621679653236 :: (~>) a ((~>) a Bool)) (a6989586621679653237 :: [a]) :: [[a]] where ... Source #
Equations
| GroupBySym2 a6989586621679653236 a6989586621679653237 = GroupBy a6989586621679653236 a6989586621679653237 |
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) (a6989586621679653607 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679653607 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621679653607 | |
data SortBySym1 (a6989586621679653607 :: (~>) 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 a6989586621679653607 :: 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 a6989586621679653607 :: TyFun [a] [a] -> Type) (a6989586621679653608 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SortBySym1 a6989586621679653607 :: TyFun [a] [a] -> Type) (a6989586621679653608 :: [a]) = SortBy a6989586621679653607 a6989586621679653608 | |
type family SortBySym2 (a6989586621679653607 :: (~>) a ((~>) a Ordering)) (a6989586621679653608 :: [a]) :: [a] where ... Source #
Equations
| SortBySym2 a6989586621679653607 a6989586621679653608 = SortBy a6989586621679653607 a6989586621679653608 |
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) (a6989586621679653587 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679653587 :: a ~> (a ~> Ordering)) = InsertBySym1 a6989586621679653587 | |
data InsertBySym1 (a6989586621679653587 :: (~>) 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 a6989586621679653587 :: 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 a6989586621679653587 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679653588 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertBySym1 a6989586621679653587 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679653588 :: a) = InsertBySym2 a6989586621679653587 a6989586621679653588 | |
data InsertBySym2 (a6989586621679653587 :: (~>) a ((~>) a Ordering)) (a6989586621679653588 :: 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 | |
| (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 a6989586621679653587 a6989586621679653588 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertBySym2 a6989586621679653587 a6989586621679653588 :: TyFun [a] [a] -> Type) (a6989586621679653589 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertBySym2 a6989586621679653587 a6989586621679653588 :: TyFun [a] [a] -> Type) (a6989586621679653589 :: [a]) = InsertBy a6989586621679653587 a6989586621679653588 a6989586621679653589 | |
type family InsertBySym3 (a6989586621679653587 :: (~>) a ((~>) a Ordering)) (a6989586621679653588 :: a) (a6989586621679653589 :: [a]) :: [a] where ... Source #
Equations
| InsertBySym3 a6989586621679653587 a6989586621679653588 a6989586621679653589 = InsertBy a6989586621679653587 a6989586621679653588 a6989586621679653589 |
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 sing :: Sing MaximumBySym0 # | |
| 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) (a6989586621680110381 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Foldable.Singletons type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680110381 :: a ~> (a ~> Ordering)) = MaximumBySym1 a6989586621680110381 :: TyFun (t a) a -> Type | |
data MaximumBySym1 (a6989586621680110381 :: (~>) 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 a6989586621680110381 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MaximumBySym1 a6989586621680110381 :: TyFun (t a) a -> Type) (a6989586621680110382 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MaximumBySym1 a6989586621680110381 :: TyFun (t a) a -> Type) (a6989586621680110382 :: t a) = MaximumBy a6989586621680110381 a6989586621680110382 | |
type family MaximumBySym2 (a6989586621680110381 :: (~>) a ((~>) a Ordering)) (a6989586621680110382 :: t a) :: a where ... Source #
Equations
| MaximumBySym2 a6989586621680110381 a6989586621680110382 = MaximumBy a6989586621680110381 a6989586621680110382 |
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 sing :: Sing MinimumBySym0 # | |
| 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) (a6989586621680110361 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Foldable.Singletons type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680110361 :: a ~> (a ~> Ordering)) = MinimumBySym1 a6989586621680110361 :: TyFun (t a) a -> Type | |
data MinimumBySym1 (a6989586621680110361 :: (~>) 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 a6989586621680110361 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MinimumBySym1 a6989586621680110361 :: TyFun (t a) a -> Type) (a6989586621680110362 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MinimumBySym1 a6989586621680110361 :: TyFun (t a) a -> Type) (a6989586621680110362 :: t a) = MinimumBy a6989586621680110361 a6989586621680110362 | |
type family MinimumBySym2 (a6989586621680110361 :: (~>) a ((~>) a Ordering)) (a6989586621680110362 :: t a) :: a where ... Source #
Equations
| MinimumBySym2 a6989586621680110361 a6989586621680110362 = MinimumBy a6989586621680110361 a6989586621680110362 |
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) (a6989586621679653066 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679653066 :: [a]) = GenericLength a6989586621679653066 :: k2 | |
type family GenericLengthSym1 (a6989586621679653066 :: [a]) :: i where ... Source #
Equations
| GenericLengthSym1 a6989586621679653066 = GenericLength a6989586621679653066 |