Copyright | (C) 2013-2014 Richard Eisenberg Jan Stolarek |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Defines functions and datatypes relating to the singleton for '[]',
including a singletons version of a few of the definitions in Data.List
.
Because many of these definitions are produced by Template Haskell,
it is not possible to create proper Haddock documentation. Please look
up the corresponding operation in Data.List
. Also, please excuse
the apparent repeated variable names. This is due to an interaction
between Template Haskell and Haddock.
Synopsis
- type family Sing
- data SList z where
- type family a ++ a where ...
- (%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a])
- type family Head a where ...
- sHead :: forall a (t :: [a]). Sing t -> Sing (Apply HeadSym0 t :: a)
- type family Last a where ...
- sLast :: forall a (t :: [a]). Sing t -> Sing (Apply LastSym0 t :: a)
- type family Tail a where ...
- sTail :: forall a (t :: [a]). Sing t -> Sing (Apply TailSym0 t :: [a])
- type family Init a where ...
- sInit :: forall a (t :: [a]). Sing t -> Sing (Apply InitSym0 t :: [a])
- type family Null (arg :: t a) :: Bool
- sNull :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply NullSym0 t :: Bool)
- type family Length (arg :: t a) :: Nat
- sLength :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply LengthSym0 t :: Nat)
- type family Map a a where ...
- sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b])
- type family Reverse a where ...
- sReverse :: forall a (t :: [a]). Sing t -> Sing (Apply ReverseSym0 t :: [a])
- type family Intersperse a a where ...
- sIntersperse :: forall a (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a])
- type family Intercalate a a where ...
- sIntercalate :: forall a (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a])
- type family Transpose a where ...
- sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]])
- type family Subsequences a where ...
- sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]])
- type family Permutations a where ...
- sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]])
- type family Foldl (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
- sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b)
- type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
- sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b)
- type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
- sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a)
- type family Foldl1' a a where ...
- sFoldl1' :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a)
- type family Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b
- sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b)
- type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
- sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a)
- type family Concat a where ...
- sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a])
- type family ConcatMap a a where ...
- sConcatMap :: forall a b t (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b])
- type family And a where ...
- sAnd :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool)
- type family Or a where ...
- sOr :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool)
- type family Any a a where ...
- sAny :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool)
- type family All a a where ...
- sAll :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool)
- type family Sum (arg :: t a) :: a
- sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a)
- type family Product (arg :: t a) :: a
- sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a)
- type family Maximum (arg :: t a) :: a
- sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a)
- type family Minimum (arg :: t a) :: a
- sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a)
- type family Scanl a a a where ...
- sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b])
- type family Scanl1 a a where ...
- sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a])
- type family Scanr a a a where ...
- sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b])
- type family Scanr1 a a where ...
- sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a])
- type family MapAccumL a a a 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 a where ...
- sMapAccumR :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c))
- type family Replicate a a where ...
- sReplicate :: forall a (t :: Nat) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a])
- type family Unfoldr a a where ...
- sUnfoldr :: forall b a (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a])
- type family Take a a where ...
- sTake :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a])
- type family Drop a a where ...
- sDrop :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a])
- type family SplitAt a a where ...
- sSplitAt :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a]))
- type family TakeWhile a a where ...
- sTakeWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a])
- type family DropWhile a a where ...
- sDropWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a])
- type family DropWhileEnd a a where ...
- sDropWhileEnd :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a])
- type family Span a a where ...
- sSpan :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a]))
- type family Break a a where ...
- sBreak :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a]))
- type family StripPrefix a a where ...
- type family Group a where ...
- sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [[a]])
- type family Inits a where ...
- sInits :: forall a (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: [[a]])
- type family Tails a where ...
- sTails :: forall a (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: [[a]])
- type family IsPrefixOf a a where ...
- sIsPrefixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool)
- type family IsSuffixOf a a where ...
- sIsSuffixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool)
- type family IsInfixOf a a where ...
- sIsInfixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool)
- type family Elem (arg :: a) (arg :: t a) :: Bool
- sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool)
- type family NotElem a a where ...
- sNotElem :: forall a t (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool)
- type family Lookup a a where ...
- sLookup :: forall a b (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b)
- type family Find a a where ...
- sFind :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a)
- type family Filter a a where ...
- sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
- type family Partition a a where ...
- sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
- type family a !! a where ...
- (%!!) :: forall a (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a)
- type family ElemIndex a a where ...
- sElemIndex :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat)
- type family ElemIndices a a where ...
- sElemIndices :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat])
- type family FindIndex a a where ...
- sFindIndex :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat)
- type family FindIndices a a where ...
- sFindIndices :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat])
- type family Zip a a where ...
- sZip :: forall a b (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)])
- type family Zip3 a a a where ...
- sZip3 :: forall a b c (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)])
- type family Zip4 a a a a where ...
- type family Zip5 a a a a a where ...
- type family Zip6 a a a a a a where ...
- type family Zip7 a a a a a a a where ...
- type family ZipWith a a a where ...
- sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c])
- type family ZipWith3 a a a a where ...
- sZipWith3 :: forall a b c d (t :: (~>) a ((~>) b ((~>) c d))) (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d])
- type family ZipWith4 a a a a a where ...
- type family ZipWith5 a a a a a a where ...
- type family ZipWith6 a a a a a a a where ...
- type family ZipWith7 a a a a a a a a where ...
- type family Unzip a where ...
- sUnzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b]))
- type family Unzip3 a where ...
- sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c]))
- type family Unzip4 a where ...
- sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d]))
- type family Unzip5 a where ...
- sUnzip5 :: forall a b c d e (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e]))
- type family Unzip6 a where ...
- sUnzip6 :: forall a b c d e f (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f]))
- type family Unzip7 a where ...
- sUnzip7 :: forall a b c d e f g (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g]))
- type family Unlines a where ...
- sUnlines :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnlinesSym0 t :: Symbol)
- type family Unwords a where ...
- sUnwords :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnwordsSym0 t :: Symbol)
- type family Nub a where ...
- sNub :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply NubSym0 t :: [a])
- type family Delete a a where ...
- sDelete :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a])
- type family a \\ a where ...
- (%\\) :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (\\@#@$) t) t :: [a])
- type family Union a a where ...
- sUnion :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a])
- type family Intersect a a where ...
- sIntersect :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a])
- type family Insert a a where ...
- sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a])
- type family Sort a where ...
- sSort :: forall a (t :: [a]). SOrd a => Sing t -> Sing (Apply SortSym0 t :: [a])
- type family NubBy a a where ...
- sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a])
- type family DeleteBy a a a where ...
- sDeleteBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a])
- type family DeleteFirstsBy a a a where ...
- sDeleteFirstsBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a])
- type family UnionBy a a a where ...
- sUnionBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a])
- type family IntersectBy a a a where ...
- sIntersectBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a])
- type family GroupBy a a where ...
- sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]])
- type family SortBy a a where ...
- sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a])
- type family InsertBy a a a where ...
- sInsertBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a])
- type family MaximumBy a a where ...
- sMaximumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a)
- type family MinimumBy a a where ...
- sMinimumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a)
- type family GenericLength a where ...
- sGenericLength :: forall a i (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i)
- type NilSym0 = '[] :: [a :: Type]
- data (:@#@$) a6989586621679304138
- data a6989586621679304138 :@#@$$ a6989586621679304139
- type (:@#@$$$) (a6989586621679304138 :: a) (a6989586621679304139 :: [a]) = '(:) a6989586621679304138 a6989586621679304139 :: [a :: Type]
- type (++@#@$$$) (a6989586621679534210 :: [a]) (a6989586621679534211 :: [a]) = (++) a6989586621679534210 a6989586621679534211 :: [a]
- data a6989586621679534210 ++@#@$$ a6989586621679534211
- data (++@#@$) a6989586621679534210
- data HeadSym0 a6989586621679970037
- type HeadSym1 (a6989586621679970037 :: [a]) = Head a6989586621679970037 :: a
- data LastSym0 a6989586621679970031
- type LastSym1 (a6989586621679970031 :: [a]) = Last a6989586621679970031 :: a
- data TailSym0 a6989586621679970027
- type TailSym1 (a6989586621679970027 :: [a]) = Tail a6989586621679970027 :: [a]
- data InitSym0 a6989586621679970015
- type InitSym1 (a6989586621679970015 :: [a]) = Init a6989586621679970015 :: [a]
- data NullSym0 a6989586621680492490
- type NullSym1 (a6989586621680492490 :: t a) = Null a6989586621680492490 :: Bool
- data LengthSym0 a6989586621680492493
- type LengthSym1 (a6989586621680492493 :: t a) = Length a6989586621680492493 :: Nat
- data MapSym0 a6989586621679534219
- data MapSym1 a6989586621679534219 a6989586621679534220
- type MapSym2 (a6989586621679534219 :: (~>) a b) (a6989586621679534220 :: [a]) = Map a6989586621679534219 a6989586621679534220 :: [b]
- data ReverseSym0 a6989586621679970000
- type ReverseSym1 (a6989586621679970000 :: [a]) = Reverse a6989586621679970000 :: [a]
- data IntersperseSym0 a6989586621679969993
- data IntersperseSym1 a6989586621679969993 a6989586621679969994
- type IntersperseSym2 (a6989586621679969993 :: a) (a6989586621679969994 :: [a]) = Intersperse a6989586621679969993 a6989586621679969994 :: [a]
- data IntercalateSym0 a6989586621679969986
- data IntercalateSym1 a6989586621679969986 a6989586621679969987
- type IntercalateSym2 (a6989586621679969986 :: [a]) (a6989586621679969987 :: [[a]]) = Intercalate a6989586621679969986 a6989586621679969987 :: [a]
- data TransposeSym0 a6989586621679968887
- type TransposeSym1 (a6989586621679968887 :: [[a]]) = Transpose a6989586621679968887 :: [[a]]
- data SubsequencesSym0 a6989586621679969981
- type SubsequencesSym1 (a6989586621679969981 :: [a]) = Subsequences a6989586621679969981 :: [[a]]
- data PermutationsSym0 a6989586621679969907
- type PermutationsSym1 (a6989586621679969907 :: [a]) = Permutations a6989586621679969907 :: [[a]]
- data FoldlSym0 a6989586621680492465
- data FoldlSym1 a6989586621680492465 a6989586621680492466
- data FoldlSym2 a6989586621680492465 a6989586621680492466 a6989586621680492467
- type FoldlSym3 (a6989586621680492465 :: (~>) b ((~>) a b)) (a6989586621680492466 :: b) (a6989586621680492467 :: t a) = Foldl a6989586621680492465 a6989586621680492466 a6989586621680492467 :: b
- data Foldl'Sym0 a6989586621680492472
- data Foldl'Sym1 a6989586621680492472 a6989586621680492473
- data Foldl'Sym2 a6989586621680492472 a6989586621680492473 a6989586621680492474
- type Foldl'Sym3 (a6989586621680492472 :: (~>) b ((~>) a b)) (a6989586621680492473 :: b) (a6989586621680492474 :: t a) = Foldl' a6989586621680492472 a6989586621680492473 a6989586621680492474 :: b
- data Foldl1Sym0 a6989586621680492483
- data Foldl1Sym1 a6989586621680492483 a6989586621680492484
- type Foldl1Sym2 (a6989586621680492483 :: (~>) a ((~>) a a)) (a6989586621680492484 :: t a) = Foldl1 a6989586621680492483 a6989586621680492484 :: a
- data Foldl1'Sym0 a6989586621679969872
- data Foldl1'Sym1 a6989586621679969872 a6989586621679969873
- type Foldl1'Sym2 (a6989586621679969872 :: (~>) a ((~>) a a)) (a6989586621679969873 :: [a]) = Foldl1' a6989586621679969872 a6989586621679969873 :: a
- data FoldrSym0 a6989586621680492451
- data FoldrSym1 a6989586621680492451 a6989586621680492452
- data FoldrSym2 a6989586621680492451 a6989586621680492452 a6989586621680492453
- type FoldrSym3 (a6989586621680492451 :: (~>) a ((~>) b b)) (a6989586621680492452 :: b) (a6989586621680492453 :: t a) = Foldr a6989586621680492451 a6989586621680492452 a6989586621680492453 :: b
- data Foldr1Sym0 a6989586621680492478
- data Foldr1Sym1 a6989586621680492478 a6989586621680492479
- type Foldr1Sym2 (a6989586621680492478 :: (~>) a ((~>) a a)) (a6989586621680492479 :: t a) = Foldr1 a6989586621680492478 a6989586621680492479 :: a
- data ConcatSym0 a6989586621680492332
- type ConcatSym1 (a6989586621680492332 :: t [a]) = Concat a6989586621680492332 :: [a]
- data ConcatMapSym0 a6989586621680492321
- data ConcatMapSym1 a6989586621680492321 a6989586621680492322
- type ConcatMapSym2 (a6989586621680492321 :: (~>) a [b]) (a6989586621680492322 :: t a) = ConcatMap a6989586621680492321 a6989586621680492322 :: [b]
- data AndSym0 a6989586621680492316
- type AndSym1 (a6989586621680492316 :: t Bool) = And a6989586621680492316 :: Bool
- data OrSym0 a6989586621680492310
- type OrSym1 (a6989586621680492310 :: t Bool) = Or a6989586621680492310 :: Bool
- data AnySym0 a6989586621680492302
- data AnySym1 a6989586621680492302 a6989586621680492303
- type AnySym2 (a6989586621680492302 :: (~>) a Bool) (a6989586621680492303 :: t a) = Any a6989586621680492302 a6989586621680492303 :: Bool
- data AllSym0 a6989586621680492293
- data AllSym1 a6989586621680492293 a6989586621680492294
- type AllSym2 (a6989586621680492293 :: (~>) a Bool) (a6989586621680492294 :: t a) = All a6989586621680492293 a6989586621680492294 :: Bool
- data SumSym0 a6989586621680492507
- type SumSym1 (a6989586621680492507 :: t a) = Sum a6989586621680492507 :: a
- data ProductSym0 a6989586621680492510
- type ProductSym1 (a6989586621680492510 :: t a) = Product a6989586621680492510 :: a
- data MaximumSym0 a6989586621680492501
- type MaximumSym1 (a6989586621680492501 :: t a) = Maximum a6989586621680492501 :: a
- data MinimumSym0 a6989586621680492504
- type MinimumSym1 (a6989586621680492504 :: t a) = Minimum a6989586621680492504 :: a
- data ScanlSym0 a6989586621679969805
- data ScanlSym1 a6989586621679969805 a6989586621679969806
- data ScanlSym2 a6989586621679969805 a6989586621679969806 a6989586621679969807
- type ScanlSym3 (a6989586621679969805 :: (~>) b ((~>) a b)) (a6989586621679969806 :: b) (a6989586621679969807 :: [a]) = Scanl a6989586621679969805 a6989586621679969806 a6989586621679969807 :: [b]
- data Scanl1Sym0 a6989586621679969796
- data Scanl1Sym1 a6989586621679969796 a6989586621679969797
- type Scanl1Sym2 (a6989586621679969796 :: (~>) a ((~>) a a)) (a6989586621679969797 :: [a]) = Scanl1 a6989586621679969796 a6989586621679969797 :: [a]
- data ScanrSym0 a6989586621679969778
- data ScanrSym1 a6989586621679969778 a6989586621679969779
- data ScanrSym2 a6989586621679969778 a6989586621679969779 a6989586621679969780
- type ScanrSym3 (a6989586621679969778 :: (~>) a ((~>) b b)) (a6989586621679969779 :: b) (a6989586621679969780 :: [a]) = Scanr a6989586621679969778 a6989586621679969779 a6989586621679969780 :: [b]
- data Scanr1Sym0 a6989586621679969758
- data Scanr1Sym1 a6989586621679969758 a6989586621679969759
- type Scanr1Sym2 (a6989586621679969758 :: (~>) a ((~>) a a)) (a6989586621679969759 :: [a]) = Scanr1 a6989586621679969758 a6989586621679969759 :: [a]
- data MapAccumLSym0 a6989586621680823006
- data MapAccumLSym1 a6989586621680823006 a6989586621680823007
- data MapAccumLSym2 a6989586621680823006 a6989586621680823007 a6989586621680823008
- type MapAccumLSym3 (a6989586621680823006 :: (~>) a ((~>) b (a, c))) (a6989586621680823007 :: a) (a6989586621680823008 :: t b) = MapAccumL a6989586621680823006 a6989586621680823007 a6989586621680823008 :: (a, t c)
- data MapAccumRSym0 a6989586621680822996
- data MapAccumRSym1 a6989586621680822996 a6989586621680822997
- data MapAccumRSym2 a6989586621680822996 a6989586621680822997 a6989586621680822998
- type MapAccumRSym3 (a6989586621680822996 :: (~>) a ((~>) b (a, c))) (a6989586621680822997 :: a) (a6989586621680822998 :: t b) = MapAccumR a6989586621680822996 a6989586621680822997 a6989586621680822998 :: (a, t c)
- data ReplicateSym0 a6989586621679968895
- data ReplicateSym1 a6989586621679968895 a6989586621679968896
- type ReplicateSym2 (a6989586621679968895 :: Nat) (a6989586621679968896 :: a) = Replicate a6989586621679968895 a6989586621679968896 :: [a]
- data UnfoldrSym0 a6989586621679969650
- data UnfoldrSym1 a6989586621679969650 a6989586621679969651
- type UnfoldrSym2 (a6989586621679969650 :: (~>) b (Maybe (a, b))) (a6989586621679969651 :: b) = Unfoldr a6989586621679969650 a6989586621679969651 :: [a]
- data TakeSym0 a6989586621679969050
- data TakeSym1 a6989586621679969050 a6989586621679969051
- type TakeSym2 (a6989586621679969050 :: Nat) (a6989586621679969051 :: [a]) = Take a6989586621679969050 a6989586621679969051 :: [a]
- data DropSym0 a6989586621679969037
- data DropSym1 a6989586621679969037 a6989586621679969038
- type DropSym2 (a6989586621679969037 :: Nat) (a6989586621679969038 :: [a]) = Drop a6989586621679969037 a6989586621679969038 :: [a]
- data SplitAtSym0 a6989586621679969030
- data SplitAtSym1 a6989586621679969030 a6989586621679969031
- type SplitAtSym2 (a6989586621679969030 :: Nat) (a6989586621679969031 :: [a]) = SplitAt a6989586621679969030 a6989586621679969031 :: ([a], [a])
- data TakeWhileSym0 a6989586621679969167
- data TakeWhileSym1 a6989586621679969167 a6989586621679969168
- type TakeWhileSym2 (a6989586621679969167 :: (~>) a Bool) (a6989586621679969168 :: [a]) = TakeWhile a6989586621679969167 a6989586621679969168 :: [a]
- data DropWhileSym0 a6989586621679969152
- data DropWhileSym1 a6989586621679969152 a6989586621679969153
- type DropWhileSym2 (a6989586621679969152 :: (~>) a Bool) (a6989586621679969153 :: [a]) = DropWhile a6989586621679969152 a6989586621679969153 :: [a]
- data DropWhileEndSym0 a6989586621679969135
- data DropWhileEndSym1 a6989586621679969135 a6989586621679969136
- type DropWhileEndSym2 (a6989586621679969135 :: (~>) a Bool) (a6989586621679969136 :: [a]) = DropWhileEnd a6989586621679969135 a6989586621679969136 :: [a]
- data SpanSym0 a6989586621679969098
- data SpanSym1 a6989586621679969098 a6989586621679969099
- type SpanSym2 (a6989586621679969098 :: (~>) a Bool) (a6989586621679969099 :: [a]) = Span a6989586621679969098 a6989586621679969099 :: ([a], [a])
- data BreakSym0 a6989586621679969063
- data BreakSym1 a6989586621679969063 a6989586621679969064
- type BreakSym2 (a6989586621679969063 :: (~>) a Bool) (a6989586621679969064 :: [a]) = Break a6989586621679969063 a6989586621679969064 :: ([a], [a])
- data StripPrefixSym0 a6989586621680091346
- data StripPrefixSym1 a6989586621680091346 a6989586621680091347
- type StripPrefixSym2 (a6989586621680091346 :: [a]) (a6989586621680091347 :: [a]) = StripPrefix a6989586621680091346 a6989586621680091347 :: Maybe [a]
- data GroupSym0 a6989586621679969025
- type GroupSym1 (a6989586621679969025 :: [a]) = Group a6989586621679969025 :: [[a]]
- data InitsSym0 a6989586621679969640
- type InitsSym1 (a6989586621679969640 :: [a]) = Inits a6989586621679969640 :: [[a]]
- data TailsSym0 a6989586621679969632
- type TailsSym1 (a6989586621679969632 :: [a]) = Tails a6989586621679969632 :: [[a]]
- data IsPrefixOfSym0 a6989586621679969624
- data IsPrefixOfSym1 a6989586621679969624 a6989586621679969625
- type IsPrefixOfSym2 (a6989586621679969624 :: [a]) (a6989586621679969625 :: [a]) = IsPrefixOf a6989586621679969624 a6989586621679969625 :: Bool
- data IsSuffixOfSym0 a6989586621679969617
- data IsSuffixOfSym1 a6989586621679969617 a6989586621679969618
- type IsSuffixOfSym2 (a6989586621679969617 :: [a]) (a6989586621679969618 :: [a]) = IsSuffixOf a6989586621679969617 a6989586621679969618 :: Bool
- data IsInfixOfSym0 a6989586621679969610
- data IsInfixOfSym1 a6989586621679969610 a6989586621679969611
- type IsInfixOfSym2 (a6989586621679969610 :: [a]) (a6989586621679969611 :: [a]) = IsInfixOf a6989586621679969610 a6989586621679969611 :: Bool
- data ElemSym0 a6989586621680492497
- data ElemSym1 a6989586621680492497 a6989586621680492498
- type ElemSym2 (a6989586621680492497 :: a) (a6989586621680492498 :: t a) = Elem a6989586621680492497 a6989586621680492498 :: Bool
- data NotElemSym0 a6989586621680492244
- data NotElemSym1 a6989586621680492244 a6989586621680492245
- type NotElemSym2 (a6989586621680492244 :: a) (a6989586621680492245 :: t a) = NotElem a6989586621680492244 a6989586621680492245 :: Bool
- data LookupSym0 a6989586621679968958
- data LookupSym1 a6989586621679968958 a6989586621679968959
- type LookupSym2 (a6989586621679968958 :: a) (a6989586621679968959 :: [(a, b)]) = Lookup a6989586621679968958 a6989586621679968959 :: Maybe b
- data FindSym0 a6989586621680492226
- data FindSym1 a6989586621680492226 a6989586621680492227
- type FindSym2 (a6989586621680492226 :: (~>) a Bool) (a6989586621680492227 :: t a) = Find a6989586621680492226 a6989586621680492227 :: Maybe a
- data FilterSym0 a6989586621679969267
- data FilterSym1 a6989586621679969267 a6989586621679969268
- type FilterSym2 (a6989586621679969267 :: (~>) a Bool) (a6989586621679969268 :: [a]) = Filter a6989586621679969267 a6989586621679969268 :: [a]
- data PartitionSym0 a6989586621679968951
- data PartitionSym1 a6989586621679968951 a6989586621679968952
- type PartitionSym2 (a6989586621679968951 :: (~>) a Bool) (a6989586621679968952 :: [a]) = Partition a6989586621679968951 a6989586621679968952 :: ([a], [a])
- data (!!@#@$) a6989586621679968875
- data a6989586621679968875 !!@#@$$ a6989586621679968876
- type (!!@#@$$$) (a6989586621679968875 :: [a]) (a6989586621679968876 :: Nat) = (!!) a6989586621679968875 a6989586621679968876 :: a
- data ElemIndexSym0 a6989586621679969251
- data ElemIndexSym1 a6989586621679969251 a6989586621679969252
- type ElemIndexSym2 (a6989586621679969251 :: a) (a6989586621679969252 :: [a]) = ElemIndex a6989586621679969251 a6989586621679969252 :: Maybe Nat
- data ElemIndicesSym0 a6989586621679969242
- data ElemIndicesSym1 a6989586621679969242 a6989586621679969243
- type ElemIndicesSym2 (a6989586621679969242 :: a) (a6989586621679969243 :: [a]) = ElemIndices a6989586621679969242 a6989586621679969243 :: [Nat]
- data FindIndexSym0 a6989586621679969233
- data FindIndexSym1 a6989586621679969233 a6989586621679969234
- type FindIndexSym2 (a6989586621679969233 :: (~>) a Bool) (a6989586621679969234 :: [a]) = FindIndex a6989586621679969233 a6989586621679969234 :: Maybe Nat
- data FindIndicesSym0 a6989586621679969210
- data FindIndicesSym1 a6989586621679969210 a6989586621679969211
- type FindIndicesSym2 (a6989586621679969210 :: (~>) a Bool) (a6989586621679969211 :: [a]) = FindIndices a6989586621679969210 a6989586621679969211 :: [Nat]
- data ZipSym0 a6989586621679969585
- data ZipSym1 a6989586621679969585 a6989586621679969586
- type ZipSym2 (a6989586621679969585 :: [a]) (a6989586621679969586 :: [b]) = Zip a6989586621679969585 a6989586621679969586 :: [(a, b)]
- data Zip3Sym0 a6989586621679969573
- data Zip3Sym1 a6989586621679969573 a6989586621679969574
- data Zip3Sym2 a6989586621679969573 a6989586621679969574 a6989586621679969575
- type Zip3Sym3 (a6989586621679969573 :: [a]) (a6989586621679969574 :: [b]) (a6989586621679969575 :: [c]) = Zip3 a6989586621679969573 a6989586621679969574 a6989586621679969575 :: [(a, b, c)]
- data Zip4Sym0 a6989586621680091335
- data Zip4Sym1 a6989586621680091335 a6989586621680091336
- data Zip4Sym2 a6989586621680091335 a6989586621680091336 a6989586621680091337
- data Zip4Sym3 a6989586621680091335 a6989586621680091336 a6989586621680091337 a6989586621680091338
- type Zip4Sym4 (a6989586621680091335 :: [a]) (a6989586621680091336 :: [b]) (a6989586621680091337 :: [c]) (a6989586621680091338 :: [d]) = Zip4 a6989586621680091335 a6989586621680091336 a6989586621680091337 a6989586621680091338 :: [(a, b, c, d)]
- data Zip5Sym0 a6989586621680091312
- data Zip5Sym1 a6989586621680091312 a6989586621680091313
- data Zip5Sym2 a6989586621680091312 a6989586621680091313 a6989586621680091314
- data Zip5Sym3 a6989586621680091312 a6989586621680091313 a6989586621680091314 a6989586621680091315
- data Zip5Sym4 a6989586621680091312 a6989586621680091313 a6989586621680091314 a6989586621680091315 a6989586621680091316
- type Zip5Sym5 (a6989586621680091312 :: [a]) (a6989586621680091313 :: [b]) (a6989586621680091314 :: [c]) (a6989586621680091315 :: [d]) (a6989586621680091316 :: [e]) = Zip5 a6989586621680091312 a6989586621680091313 a6989586621680091314 a6989586621680091315 a6989586621680091316 :: [(a, b, c, d, e)]
- data Zip6Sym0 a6989586621680091284
- data Zip6Sym1 a6989586621680091284 a6989586621680091285
- data Zip6Sym2 a6989586621680091284 a6989586621680091285 a6989586621680091286
- data Zip6Sym3 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287
- data Zip6Sym4 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288
- data Zip6Sym5 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 a6989586621680091289
- type Zip6Sym6 (a6989586621680091284 :: [a]) (a6989586621680091285 :: [b]) (a6989586621680091286 :: [c]) (a6989586621680091287 :: [d]) (a6989586621680091288 :: [e]) (a6989586621680091289 :: [f]) = Zip6 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 a6989586621680091289 :: [(a, b, c, d, e, f)]
- data Zip7Sym0 a6989586621680091251
- data Zip7Sym1 a6989586621680091251 a6989586621680091252
- data Zip7Sym2 a6989586621680091251 a6989586621680091252 a6989586621680091253
- data Zip7Sym3 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254
- data Zip7Sym4 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255
- data Zip7Sym5 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256
- data Zip7Sym6 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 a6989586621680091257
- type Zip7Sym7 (a6989586621680091251 :: [a]) (a6989586621680091252 :: [b]) (a6989586621680091253 :: [c]) (a6989586621680091254 :: [d]) (a6989586621680091255 :: [e]) (a6989586621680091256 :: [f]) (a6989586621680091257 :: [g]) = Zip7 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 a6989586621680091257 :: [(a, b, c, d, e, f, g)]
- data ZipWithSym0 a6989586621679969561
- data ZipWithSym1 a6989586621679969561 a6989586621679969562
- data ZipWithSym2 a6989586621679969561 a6989586621679969562 a6989586621679969563
- type ZipWithSym3 (a6989586621679969561 :: (~>) a ((~>) b c)) (a6989586621679969562 :: [a]) (a6989586621679969563 :: [b]) = ZipWith a6989586621679969561 a6989586621679969562 a6989586621679969563 :: [c]
- data ZipWith3Sym0 a6989586621679969546
- data ZipWith3Sym1 a6989586621679969546 a6989586621679969547
- data ZipWith3Sym2 a6989586621679969546 a6989586621679969547 a6989586621679969548
- data ZipWith3Sym3 a6989586621679969546 a6989586621679969547 a6989586621679969548 a6989586621679969549
- type ZipWith3Sym4 (a6989586621679969546 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679969547 :: [a]) (a6989586621679969548 :: [b]) (a6989586621679969549 :: [c]) = ZipWith3 a6989586621679969546 a6989586621679969547 a6989586621679969548 a6989586621679969549 :: [d]
- data ZipWith4Sym0 a6989586621680091215
- data ZipWith4Sym1 a6989586621680091215 a6989586621680091216
- data ZipWith4Sym2 a6989586621680091215 a6989586621680091216 a6989586621680091217
- data ZipWith4Sym3 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218
- data ZipWith4Sym4 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 a6989586621680091219
- type ZipWith4Sym5 (a6989586621680091215 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621680091216 :: [a]) (a6989586621680091217 :: [b]) (a6989586621680091218 :: [c]) (a6989586621680091219 :: [d]) = ZipWith4 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 a6989586621680091219 :: [e]
- data ZipWith5Sym0 a6989586621680091192
- data ZipWith5Sym1 a6989586621680091192 a6989586621680091193
- data ZipWith5Sym2 a6989586621680091192 a6989586621680091193 a6989586621680091194
- data ZipWith5Sym3 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195
- data ZipWith5Sym4 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196
- data ZipWith5Sym5 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 a6989586621680091197
- type ZipWith5Sym6 (a6989586621680091192 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621680091193 :: [a]) (a6989586621680091194 :: [b]) (a6989586621680091195 :: [c]) (a6989586621680091196 :: [d]) (a6989586621680091197 :: [e]) = ZipWith5 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 a6989586621680091197 :: [f]
- data ZipWith6Sym0 a6989586621680091165
- data ZipWith6Sym1 a6989586621680091165 a6989586621680091166
- data ZipWith6Sym2 a6989586621680091165 a6989586621680091166 a6989586621680091167
- data ZipWith6Sym3 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168
- data ZipWith6Sym4 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169
- data ZipWith6Sym5 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170
- data ZipWith6Sym6 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 a6989586621680091171
- type ZipWith6Sym7 (a6989586621680091165 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621680091166 :: [a]) (a6989586621680091167 :: [b]) (a6989586621680091168 :: [c]) (a6989586621680091169 :: [d]) (a6989586621680091170 :: [e]) (a6989586621680091171 :: [f]) = ZipWith6 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 a6989586621680091171 :: [g]
- data ZipWith7Sym0 a6989586621680091134
- data ZipWith7Sym1 a6989586621680091134 a6989586621680091135
- data ZipWith7Sym2 a6989586621680091134 a6989586621680091135 a6989586621680091136
- data ZipWith7Sym3 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137
- data ZipWith7Sym4 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138
- data ZipWith7Sym5 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139
- data ZipWith7Sym6 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140
- data ZipWith7Sym7 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 a6989586621680091141
- type ZipWith7Sym8 (a6989586621680091134 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621680091135 :: [a]) (a6989586621680091136 :: [b]) (a6989586621680091137 :: [c]) (a6989586621680091138 :: [d]) (a6989586621680091139 :: [e]) (a6989586621680091140 :: [f]) (a6989586621680091141 :: [g]) = ZipWith7 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 a6989586621680091141 :: [h]
- data UnzipSym0 a6989586621679969527
- type UnzipSym1 (a6989586621679969527 :: [(a, b)]) = Unzip a6989586621679969527 :: ([a], [b])
- data Unzip3Sym0 a6989586621679969509
- type Unzip3Sym1 (a6989586621679969509 :: [(a, b, c)]) = Unzip3 a6989586621679969509 :: ([a], [b], [c])
- data Unzip4Sym0 a6989586621679969489
- type Unzip4Sym1 (a6989586621679969489 :: [(a, b, c, d)]) = Unzip4 a6989586621679969489 :: ([a], [b], [c], [d])
- data Unzip5Sym0 a6989586621679969467
- type Unzip5Sym1 (a6989586621679969467 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679969467 :: ([a], [b], [c], [d], [e])
- data Unzip6Sym0 a6989586621679969443
- type Unzip6Sym1 (a6989586621679969443 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679969443 :: ([a], [b], [c], [d], [e], [f])
- data Unzip7Sym0 a6989586621679969417
- type Unzip7Sym1 (a6989586621679969417 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679969417 :: ([a], [b], [c], [d], [e], [f], [g])
- data UnlinesSym0 a6989586621679969412
- type UnlinesSym1 (a6989586621679969412 :: [Symbol]) = Unlines a6989586621679969412 :: Symbol
- data UnwordsSym0 a6989586621679969402
- type UnwordsSym1 (a6989586621679969402 :: [Symbol]) = Unwords a6989586621679969402 :: Symbol
- data NubSym0 a6989586621679968858
- type NubSym1 (a6989586621679968858 :: [a]) = Nub a6989586621679968858 :: [a]
- data DeleteSym0 a6989586621679969396
- data DeleteSym1 a6989586621679969396 a6989586621679969397
- type DeleteSym2 (a6989586621679969396 :: a) (a6989586621679969397 :: [a]) = Delete a6989586621679969396 a6989586621679969397 :: [a]
- data (\\@#@$) a6989586621679969385
- data a6989586621679969385 \\@#@$$ a6989586621679969386
- type (\\@#@$$$) (a6989586621679969385 :: [a]) (a6989586621679969386 :: [a]) = (\\) a6989586621679969385 a6989586621679969386 :: [a]
- data UnionSym0 a6989586621679968812
- data UnionSym1 a6989586621679968812 a6989586621679968813
- type UnionSym2 (a6989586621679968812 :: [a]) (a6989586621679968813 :: [a]) = Union a6989586621679968812 a6989586621679968813 :: [a]
- data IntersectSym0 a6989586621679969203
- data IntersectSym1 a6989586621679969203 a6989586621679969204
- type IntersectSym2 (a6989586621679969203 :: [a]) (a6989586621679969204 :: [a]) = Intersect a6989586621679969203 a6989586621679969204 :: [a]
- data InsertSym0 a6989586621679969005
- data InsertSym1 a6989586621679969005 a6989586621679969006
- type InsertSym2 (a6989586621679969005 :: a) (a6989586621679969006 :: [a]) = Insert a6989586621679969005 a6989586621679969006 :: [a]
- data SortSym0 a6989586621679969000
- type SortSym1 (a6989586621679969000 :: [a]) = Sort a6989586621679969000 :: [a]
- data NubBySym0 a6989586621679968840
- data NubBySym1 a6989586621679968840 a6989586621679968841
- type NubBySym2 (a6989586621679968840 :: (~>) a ((~>) a Bool)) (a6989586621679968841 :: [a]) = NubBy a6989586621679968840 a6989586621679968841 :: [a]
- data DeleteBySym0 a6989586621679969366
- data DeleteBySym1 a6989586621679969366 a6989586621679969367
- data DeleteBySym2 a6989586621679969366 a6989586621679969367 a6989586621679969368
- type DeleteBySym3 (a6989586621679969366 :: (~>) a ((~>) a Bool)) (a6989586621679969367 :: a) (a6989586621679969368 :: [a]) = DeleteBy a6989586621679969366 a6989586621679969367 a6989586621679969368 :: [a]
- data DeleteFirstsBySym0 a6989586621679969356
- data DeleteFirstsBySym1 a6989586621679969356 a6989586621679969357
- data DeleteFirstsBySym2 a6989586621679969356 a6989586621679969357 a6989586621679969358
- type DeleteFirstsBySym3 (a6989586621679969356 :: (~>) a ((~>) a Bool)) (a6989586621679969357 :: [a]) (a6989586621679969358 :: [a]) = DeleteFirstsBy a6989586621679969356 a6989586621679969357 a6989586621679969358 :: [a]
- data UnionBySym0 a6989586621679968820
- data UnionBySym1 a6989586621679968820 a6989586621679968821
- data UnionBySym2 a6989586621679968820 a6989586621679968821 a6989586621679968822
- type UnionBySym3 (a6989586621679968820 :: (~>) a ((~>) a Bool)) (a6989586621679968821 :: [a]) (a6989586621679968822 :: [a]) = UnionBy a6989586621679968820 a6989586621679968821 a6989586621679968822 :: [a]
- data IntersectBySym0 a6989586621679969181
- data IntersectBySym1 a6989586621679969181 a6989586621679969182
- data IntersectBySym2 a6989586621679969181 a6989586621679969182 a6989586621679969183
- type IntersectBySym3 (a6989586621679969181 :: (~>) a ((~>) a Bool)) (a6989586621679969182 :: [a]) (a6989586621679969183 :: [a]) = IntersectBy a6989586621679969181 a6989586621679969182 a6989586621679969183 :: [a]
- data GroupBySym0 a6989586621679968973
- data GroupBySym1 a6989586621679968973 a6989586621679968974
- type GroupBySym2 (a6989586621679968973 :: (~>) a ((~>) a Bool)) (a6989586621679968974 :: [a]) = GroupBy a6989586621679968973 a6989586621679968974 :: [[a]]
- data SortBySym0 a6989586621679969344
- data SortBySym1 a6989586621679969344 a6989586621679969345
- type SortBySym2 (a6989586621679969344 :: (~>) a ((~>) a Ordering)) (a6989586621679969345 :: [a]) = SortBy a6989586621679969344 a6989586621679969345 :: [a]
- data InsertBySym0 a6989586621679969324
- data InsertBySym1 a6989586621679969324 a6989586621679969325
- data InsertBySym2 a6989586621679969324 a6989586621679969325 a6989586621679969326
- type InsertBySym3 (a6989586621679969324 :: (~>) a ((~>) a Ordering)) (a6989586621679969325 :: a) (a6989586621679969326 :: [a]) = InsertBy a6989586621679969324 a6989586621679969325 a6989586621679969326 :: [a]
- data MaximumBySym0 a6989586621680492273
- data MaximumBySym1 a6989586621680492273 a6989586621680492274
- type MaximumBySym2 (a6989586621680492273 :: (~>) a ((~>) a Ordering)) (a6989586621680492274 :: t a) = MaximumBy a6989586621680492273 a6989586621680492274 :: a
- data MinimumBySym0 a6989586621680492253
- data MinimumBySym1 a6989586621680492253 a6989586621680492254
- type MinimumBySym2 (a6989586621680492253 :: (~>) a ((~>) a Ordering)) (a6989586621680492254 :: t a) = MinimumBy a6989586621680492253 a6989586621680492254 :: a
- data GenericLengthSym0 a6989586621679968803
- type GenericLengthSym1 (a6989586621679968803 :: [a]) = GenericLength a6989586621679968803 :: i
The singleton for lists
The singleton kind-indexed type family.
Instances
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 |
Basic functions
(%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a]) infixr 5 Source #
type family Null (arg :: t a) :: Bool Source #
Instances
type family Length (arg :: t a) :: Nat Source #
Instances
List transformations
sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b]) Source #
type family Intersperse a a where ... Source #
Intersperse _ '[] = NilSym0 | |
Intersperse sep ('(:) x xs) = Apply (Apply (:@#@$) x) (Apply (Apply PrependToAllSym0 sep) xs) |
sIntersperse :: forall a (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a]) Source #
type family Intercalate a a where ... Source #
Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) |
sIntercalate :: forall a (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a]) Source #
sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]]) Source #
type family Subsequences a where ... Source #
sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]]) Source #
type family Permutations 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 (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: [a1]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: NonEmpty a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Dual a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Sum a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Product a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Identity a1) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Min a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Max a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Proxy a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Arg a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Const m a) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source #
type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #
Instances
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: [a1]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Dual a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Sum a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Product a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Identity a1) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Min a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Max a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Proxy a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Arg a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Const m a) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) Source #
type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #
Instances
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Min a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Max a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Arg a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Const m a) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) Source #
sFoldl1' :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a) Source #
type family Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b Source #
Instances
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: [a1]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: NonEmpty a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Dual a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Sum a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Product a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: First a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Last a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Identity a1) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Min a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Max a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: First a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Last a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a3 :: a1 ~> (k2 ~> k2)) (a4 :: k2) (a5 :: Either a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Proxy a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a3 :: a1 ~> (k2 ~> k2)) (a4 :: k2) (a5 :: (a2, a1)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a3 :: a1 ~> (k2 ~> k2)) (a4 :: k2) (a5 :: Arg a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Const m a1) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source #
type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #
Instances
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Min a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Max a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Arg a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Const m a) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) Source #
Special folds
sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a]) Source #
sConcatMap :: forall a b t (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) Source #
type family And a where ... Source #
And a_6989586621680492312 = Apply (Apply (Apply (.@#@$) GetAllSym0) (Apply FoldMapSym0 All_Sym0)) a_6989586621680492312 |
type family Or a where ... Source #
Or a_6989586621680492306 = Apply (Apply (Apply (.@#@$) GetAnySym0) (Apply FoldMapSym0 Any_Sym0)) a_6989586621680492306 |
sAny :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool) Source #
sAll :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) Source #
type family Sum (arg :: t a) :: a Source #
Instances
sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a) Source #
type family Product (arg :: t a) :: a Source #
Instances
sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a) Source #
type family Maximum (arg :: t a) :: a Source #
Instances
sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a) Source #
type family Minimum (arg :: t a) :: a Source #
Instances
sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a) Source #
Building lists
Scans
sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b]) Source #
sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a]) Source #
sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b]) Source #
type family Scanr1 a a where ... Source #
Scanr1 _ '[] = NilSym0 | |
Scanr1 _ '[x] = Apply (Apply (:@#@$) x) NilSym0 | |
Scanr1 f ('(:) x ('(:) wild_6989586621679965248 wild_6989586621679965250)) = Case_6989586621679969769 f x wild_6989586621679965248 wild_6989586621679965250 (Let6989586621679969767Scrutinee_6989586621679965242Sym4 f x wild_6989586621679965248 wild_6989586621679965250) |
sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a]) Source #
Accumulating maps
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 #
sMapAccumR :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c)) Source #
Cyclical lists
type family Replicate a a where ... Source #
Replicate n x = Case_6989586621679968901 n x (Let6989586621679968899Scrutinee_6989586621679965344Sym2 n x) |
sReplicate :: forall a (t :: Nat) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a]) Source #
Unfolding
type family Unfoldr a a where ... Source #
Unfoldr f b = Case_6989586621679969656 f b (Let6989586621679969654Scrutinee_6989586621679965252Sym2 f b) |
sUnfoldr :: forall b a (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a]) Source #
Sublists
Extracting sublists
sTake :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) Source #
sDrop :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) Source #
sSplitAt :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) Source #
sTakeWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) Source #
sDropWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) Source #
type family DropWhileEnd a a where ... Source #
sDropWhileEnd :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a]) Source #
type family Span a a where ... Source #
Span _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679969100XsSym0) Let6989586621679969100XsSym0 | |
Span p ('(:) x xs') = Case_6989586621679969109 p x xs' (Let6989586621679969107Scrutinee_6989586621679965324Sym3 p x xs') |
sSpan :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) Source #
type family Break a a where ... Source #
Break _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679969065XsSym0) Let6989586621679969065XsSym0 | |
Break p ('(:) x xs') = Case_6989586621679969074 p x xs' (Let6989586621679969072Scrutinee_6989586621679965326Sym3 p x xs') |
sBreak :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) Source #
type family StripPrefix a a where ... Source #
StripPrefix '[] ys = Apply JustSym0 ys | |
StripPrefix arg_6989586621680089879 arg_6989586621680089881 = Case_6989586621680091351 arg_6989586621680089879 arg_6989586621680089881 (Apply (Apply Tuple2Sym0 arg_6989586621680089879) arg_6989586621680089881) |
Predicates
type family IsPrefixOf a a where ... Source #
IsPrefixOf '[] '[] = TrueSym0 | |
IsPrefixOf '[] ('(:) _ _) = TrueSym0 | |
IsPrefixOf ('(:) _ _) '[] = FalseSym0 | |
IsPrefixOf ('(:) x xs) ('(:) y ys) = Apply (Apply (&&@#@$) (Apply (Apply (==@#@$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) |
sIsPrefixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) Source #
type family IsSuffixOf a a where ... Source #
IsSuffixOf x y = Apply (Apply IsPrefixOfSym0 (Apply ReverseSym0 x)) (Apply ReverseSym0 y) |
sIsSuffixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) Source #
sIsInfixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool) Source #
Searching lists
Searching by equality
type family Elem (arg :: a) (arg :: t a) :: Bool Source #
Instances
type Elem (arg1 :: a) (arg2 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (a1 :: k1) (a2 :: [k1]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (a1 :: k1) (a2 :: [k1]) | |
type Elem (arg1 :: a) (arg2 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (a1 :: k1) (a2 :: Dual k1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (a1 :: k1) (a2 :: Sum k1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (a1 :: k1) (a2 :: Product k1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (arg1 :: a) (arg2 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (arg1 :: a) (arg2 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (a1 :: k1) (a2 :: Identity k1) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Elem (arg1 :: a) (arg2 :: Min a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a) (arg2 :: Max a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a) (arg2 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a) (arg2 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a) (arg2 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a1) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (a1 :: k1) (a2 :: Proxy k1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (arg1 :: a1) (arg2 :: (a2, a1)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (arg1 :: a1) (arg2 :: (a2, a1)) | |
type Elem (arg1 :: a1) (arg2 :: Arg a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a) (arg2 :: Const m a) Source # | |
Defined in Data.Singletons.Prelude.Const |
sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) Source #
sNotElem :: forall a t (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) Source #
type family Lookup a a where ... Source #
Lookup _key '[] = NothingSym0 | |
Lookup key ('(:) '(x, y) xys) = Case_6989586621679968967 key x y xys (Let6989586621679968965Scrutinee_6989586621679965340Sym4 key x y xys) |
sLookup :: forall a b (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b) Source #
Searching with a predicate
type family Find a a where ... Source #
Find p a_6989586621680492221 = Apply (Apply (Apply (.@#@$) GetFirstSym0) (Apply FoldMapSym0 (Apply (Apply Lambda_6989586621680492230Sym0 p) a_6989586621680492221))) a_6989586621680492221 |
sFind :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a) Source #
sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) Source #
sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) Source #
Indexing lists
(%!!) :: forall a (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) infixl 9 Source #
sElemIndex :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat) Source #
type family ElemIndices a a where ... Source #
ElemIndices x a_6989586621679969237 = Apply (Apply FindIndicesSym0 (Apply (==@#@$) x)) a_6989586621679969237 |
sElemIndices :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat]) Source #
type family FindIndex a a where ... Source #
FindIndex p a_6989586621679969228 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679969228 |
sFindIndex :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat) Source #
type family FindIndices a a where ... Source #
sFindIndices :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat]) Source #
Zipping and unzipping lists
sZip :: forall a b (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)]) Source #
type family Zip3 a a a where ... Source #
Zip3 ('(:) a as) ('(:) b bs) ('(:) c cs) = Apply (Apply (:@#@$) (Apply (Apply (Apply Tuple3Sym0 a) b) c)) (Apply (Apply (Apply Zip3Sym0 as) bs) cs) | |
Zip3 '[] '[] '[] = NilSym0 | |
Zip3 '[] '[] ('(:) _ _) = NilSym0 | |
Zip3 '[] ('(:) _ _) '[] = NilSym0 | |
Zip3 '[] ('(:) _ _) ('(:) _ _) = NilSym0 | |
Zip3 ('(:) _ _) '[] '[] = NilSym0 | |
Zip3 ('(:) _ _) '[] ('(:) _ _) = NilSym0 | |
Zip3 ('(:) _ _) ('(:) _ _) '[] = NilSym0 |
sZip3 :: forall a b c (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)]) Source #
type family Zip4 a a a a where ... Source #
Zip4 a_6989586621680091322 a_6989586621680091324 a_6989586621680091326 a_6989586621680091328 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621680091322) a_6989586621680091324) a_6989586621680091326) a_6989586621680091328 |
type family Zip5 a a a a a where ... Source #
Zip5 a_6989586621680091296 a_6989586621680091298 a_6989586621680091300 a_6989586621680091302 a_6989586621680091304 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621680091296) a_6989586621680091298) a_6989586621680091300) a_6989586621680091302) a_6989586621680091304 |
type family Zip6 a a a a a a where ... Source #
Zip6 a_6989586621680091265 a_6989586621680091267 a_6989586621680091269 a_6989586621680091271 a_6989586621680091273 a_6989586621680091275 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621680091265) a_6989586621680091267) a_6989586621680091269) a_6989586621680091271) a_6989586621680091273) a_6989586621680091275 |
type family Zip7 a a a a a a a where ... Source #
Zip7 a_6989586621680091229 a_6989586621680091231 a_6989586621680091233 a_6989586621680091235 a_6989586621680091237 a_6989586621680091239 a_6989586621680091241 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621680091229) a_6989586621680091231) a_6989586621680091233) a_6989586621680091235) a_6989586621680091237) a_6989586621680091239) a_6989586621680091241 |
sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c]) Source #
type family ZipWith3 a a a a where ... Source #
ZipWith3 z ('(:) a as) ('(:) b bs) ('(:) c cs) = Apply (Apply (:@#@$) (Apply (Apply (Apply z a) b) c)) (Apply (Apply (Apply (Apply ZipWith3Sym0 z) as) bs) cs) | |
ZipWith3 _ '[] '[] '[] = NilSym0 | |
ZipWith3 _ '[] '[] ('(:) _ _) = NilSym0 | |
ZipWith3 _ '[] ('(:) _ _) '[] = NilSym0 | |
ZipWith3 _ '[] ('(:) _ _) ('(:) _ _) = NilSym0 | |
ZipWith3 _ ('(:) _ _) '[] '[] = NilSym0 | |
ZipWith3 _ ('(:) _ _) '[] ('(:) _ _) = NilSym0 | |
ZipWith3 _ ('(:) _ _) ('(:) _ _) '[] = NilSym0 |
sZipWith3 :: forall a b c d (t :: (~>) a ((~>) b ((~>) c d))) (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d]) Source #
type family ZipWith7 a a a a a a a a where ... Source #
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 a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c])) Source #
sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d])) Source #
sUnzip5 :: forall a b c d e (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e])) Source #
sUnzip6 :: forall a b c d e f (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f])) Source #
sUnzip7 :: forall a b c d e f g (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g])) Source #
Special lists
Functions on Symbol
s
"Set" operations
sDelete :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a]) Source #
(%\\) :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (\\@#@$) t) t :: [a]) infix 5 Source #
sUnion :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a]) Source #
sIntersect :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a]) Source #
Ordered lists
type family Insert a a where ... Source #
Insert e ls = Apply (Apply (Apply InsertBySym0 CompareSym0) e) ls |
sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a]) Source #
type family Sort a where ... Source #
Sort a_6989586621679968996 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679968996 |
Generalized functions
The "By
" operations
User-supplied equality (replacing an Eq
context)
The predicate is assumed to define an equivalence.
sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a]) Source #
sDeleteBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a]) Source #
type family DeleteFirstsBy a a a where ... Source #
DeleteFirstsBy eq a_6989586621679969348 a_6989586621679969350 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679969348) a_6989586621679969350 |
sDeleteFirstsBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a]) Source #
sUnionBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a]) Source #
type family IntersectBy a a a where ... Source #
IntersectBy _ '[] '[] = NilSym0 | |
IntersectBy _ '[] ('(:) _ _) = NilSym0 | |
IntersectBy _ ('(:) _ _) '[] = NilSym0 | |
IntersectBy eq ('(:) wild_6989586621679965310 wild_6989586621679965312) ('(:) wild_6989586621679965314 wild_6989586621679965316) = Apply (Apply (>>=@#@$) (Let6989586621679969189XsSym5 eq wild_6989586621679965310 wild_6989586621679965312 wild_6989586621679965314 wild_6989586621679965316)) (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679969192Sym0 eq) wild_6989586621679965310) wild_6989586621679965312) wild_6989586621679965314) wild_6989586621679965316) |
sIntersectBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a]) Source #
sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]]) Source #
User-supplied comparison (replacing an Ord
context)
The function is assumed to define a total ordering.
sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a]) Source #
sInsertBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a]) Source #
type family MaximumBy a a where ... Source #
MaximumBy cmp a_6989586621680492268 = Apply (Apply Foldl1Sym0 (Let6989586621680492277Max'Sym2 cmp a_6989586621680492268)) a_6989586621680492268 |
sMaximumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) Source #
type family MinimumBy a a where ... Source #
MinimumBy cmp a_6989586621680492248 = Apply (Apply Foldl1Sym0 (Let6989586621680492257Min'Sym2 cmp a_6989586621680492248)) a_6989586621680492248 |
sMinimumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) Source #
The "generic
" operations
The prefix `generic
' indicates an overloaded function that
is a generalized version of a Prelude function.
type family GenericLength a where ... Source #
GenericLength '[] = FromInteger 0 | |
GenericLength ('(:) _ xs) = Apply (Apply (+@#@$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
sGenericLength :: forall a i (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i) Source #
Defunctionalization symbols
data (:@#@$) a6989586621679304138 infixr 5 Source #
Instances
SingI ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances suppressUnusedWarnings :: () Source # | |
type Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679304138 :: a) Source # | |
data a6989586621679304138 :@#@$$ a6989586621679304139 infixr 5 Source #
Instances
SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((:@#@$$) a6989586621679304138 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances suppressUnusedWarnings :: () Source # | |
type Apply ((:@#@$$) a6989586621679304138 :: TyFun [a] [a] -> Type) (a6989586621679304139 :: [a]) Source # | |
type (:@#@$$$) (a6989586621679304138 :: a) (a6989586621679304139 :: [a]) = '(:) a6989586621679304138 a6989586621679304139 :: [a :: Type] infixr 5 Source #
type (++@#@$$$) (a6989586621679534210 :: [a]) (a6989586621679534211 :: [a]) = (++) a6989586621679534210 a6989586621679534211 :: [a] infixr 5 Source #
data a6989586621679534210 ++@#@$$ a6989586621679534211 infixr 5 Source #
Instances
SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((++@#@$$) a6989586621679534210 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$$) a6989586621679534210 :: TyFun [a] [a] -> Type) (a6989586621679534211 :: [a]) Source # | |
data (++@#@$) a6989586621679534210 infixr 5 Source #
Instances
SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679534210 :: [a]) Source # | |
data TailSym0 a6989586621679970027 Source #
Instances
data InitSym0 a6989586621679970015 Source #
Instances
data NullSym0 a6989586621680492490 Source #
Instances
SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (NullSym0 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680492490 :: t a) Source # | |
data LengthSym0 a6989586621680492493 Source #
Instances
SFoldable t => SingI (LengthSym0 :: TyFun (t a) Nat -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing LengthSym0 Source # | |
SuppressUnusedWarnings (LengthSym0 :: TyFun (t a) Nat -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (a6989586621680492493 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (a6989586621680492493 :: t a) = LengthSym1 a6989586621680492493 |
type LengthSym1 (a6989586621680492493 :: t a) = Length a6989586621680492493 :: Nat Source #
data MapSym0 a6989586621679534219 Source #
Instances
SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679534219 :: a ~> b) Source # | |
data MapSym1 a6989586621679534219 a6989586621679534220 Source #
Instances
SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (MapSym1 a6989586621679534219 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply (MapSym1 a6989586621679534219 :: TyFun [a] [b] -> Type) (a6989586621679534220 :: [a]) Source # | |
type MapSym2 (a6989586621679534219 :: (~>) a b) (a6989586621679534220 :: [a]) = Map a6989586621679534219 a6989586621679534220 :: [b] Source #
data ReverseSym0 a6989586621679970000 Source #
Instances
SingI (ReverseSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing ReverseSym0 Source # | |
SuppressUnusedWarnings (ReverseSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679970000 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679970000 :: [a]) = ReverseSym1 a6989586621679970000 |
type ReverseSym1 (a6989586621679970000 :: [a]) = Reverse a6989586621679970000 :: [a] Source #
data IntersperseSym0 a6989586621679969993 Source #
Instances
SingI (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969993 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969993 :: a) = IntersperseSym1 a6989586621679969993 |
data IntersperseSym1 a6989586621679969993 a6989586621679969994 Source #
Instances
SingI d => SingI (IntersperseSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IntersperseSym1 d) Source # | |
SuppressUnusedWarnings (IntersperseSym1 a6989586621679969993 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym1 a6989586621679969993 :: TyFun [a] [a] -> Type) (a6989586621679969994 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym1 a6989586621679969993 :: TyFun [a] [a] -> Type) (a6989586621679969994 :: [a]) = IntersperseSym2 a6989586621679969993 a6989586621679969994 |
type IntersperseSym2 (a6989586621679969993 :: a) (a6989586621679969994 :: [a]) = Intersperse a6989586621679969993 a6989586621679969994 :: [a] Source #
data IntercalateSym0 a6989586621679969986 Source #
Instances
SingI (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679969986 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679969986 :: [a]) = IntercalateSym1 a6989586621679969986 |
data IntercalateSym1 a6989586621679969986 a6989586621679969987 Source #
Instances
SingI d => SingI (IntercalateSym1 d :: TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IntercalateSym1 d) Source # | |
SuppressUnusedWarnings (IntercalateSym1 a6989586621679969986 :: TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym1 a6989586621679969986 :: TyFun [[a]] [a] -> Type) (a6989586621679969987 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym1 a6989586621679969986 :: TyFun [[a]] [a] -> Type) (a6989586621679969987 :: [[a]]) = IntercalateSym2 a6989586621679969986 a6989586621679969987 |
type IntercalateSym2 (a6989586621679969986 :: [a]) (a6989586621679969987 :: [[a]]) = Intercalate a6989586621679969986 a6989586621679969987 :: [a] Source #
data TransposeSym0 a6989586621679968887 Source #
Instances
SingI (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing TransposeSym0 Source # | |
SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679968887 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679968887 :: [[a]]) = TransposeSym1 a6989586621679968887 |
type TransposeSym1 (a6989586621679968887 :: [[a]]) = Transpose a6989586621679968887 :: [[a]] Source #
data SubsequencesSym0 a6989586621679969981 Source #
Instances
SingI (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969981 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969981 :: [a]) = SubsequencesSym1 a6989586621679969981 |
type SubsequencesSym1 (a6989586621679969981 :: [a]) = Subsequences a6989586621679969981 :: [[a]] Source #
data PermutationsSym0 a6989586621679969907 Source #
Instances
SingI (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969907 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969907 :: [a]) = PermutationsSym1 a6989586621679969907 |
type PermutationsSym1 (a6989586621679969907 :: [a]) = Permutations a6989586621679969907 :: [[a]] Source #
data FoldlSym0 a6989586621680492465 Source #
Instances
SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680492465 :: b ~> (a ~> b)) Source # | |
data FoldlSym1 a6989586621680492465 a6989586621680492466 Source #
Instances
(SFoldable t, SingI d) => SingI (FoldlSym1 d :: TyFun b (t a ~> b) -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym1 a6989586621680492465 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym1 a6989586621680492465 :: TyFun b (t a ~> b) -> Type) (a6989586621680492466 :: b) Source # | |
data FoldlSym2 a6989586621680492465 a6989586621680492466 a6989586621680492467 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 :: TyFun (t a) b -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym2 a6989586621680492465 a6989586621680492466 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym2 a6989586621680492465 a6989586621680492466 :: TyFun (t a) b -> Type) (a6989586621680492467 :: t a) Source # | |
type FoldlSym3 (a6989586621680492465 :: (~>) b ((~>) a b)) (a6989586621680492466 :: b) (a6989586621680492467 :: t a) = Foldl a6989586621680492465 a6989586621680492466 a6989586621680492467 :: b Source #
data Foldl'Sym0 a6989586621680492472 Source #
Instances
SFoldable t => SingI (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing Foldl'Sym0 Source # | |
SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680492472 :: b ~> (a ~> b)) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data Foldl'Sym1 a6989586621680492472 a6989586621680492473 Source #
Instances
(SFoldable t, SingI d) => SingI (Foldl'Sym1 d :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (Foldl'Sym1 d) Source # | |
SuppressUnusedWarnings (Foldl'Sym1 a6989586621680492472 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym1 a6989586621680492472 :: TyFun b (t a ~> b) -> Type) (a6989586621680492473 :: b) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym1 a6989586621680492472 :: TyFun b (t a ~> b) -> Type) (a6989586621680492473 :: b) = Foldl'Sym2 a6989586621680492472 a6989586621680492473 :: TyFun (t a) b -> Type |
data Foldl'Sym2 a6989586621680492472 a6989586621680492473 a6989586621680492474 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (Foldl'Sym2 d1 d2 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (Foldl'Sym2 d1 d2) Source # | |
SuppressUnusedWarnings (Foldl'Sym2 a6989586621680492472 a6989586621680492473 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym2 a6989586621680492472 a6989586621680492473 :: TyFun (t a) b -> Type) (a6989586621680492474 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym2 a6989586621680492472 a6989586621680492473 :: TyFun (t a) b -> Type) (a6989586621680492474 :: t a) = Foldl'Sym3 a6989586621680492472 a6989586621680492473 a6989586621680492474 |
type Foldl'Sym3 (a6989586621680492472 :: (~>) b ((~>) a b)) (a6989586621680492473 :: b) (a6989586621680492474 :: t a) = Foldl' a6989586621680492472 a6989586621680492473 a6989586621680492474 :: b Source #
data Foldl1Sym0 a6989586621680492483 Source #
Instances
SFoldable t => SingI (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing Foldl1Sym0 Source # | |
SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680492483 :: a ~> (a ~> a)) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data Foldl1Sym1 a6989586621680492483 a6989586621680492484 Source #
Instances
(SFoldable t, SingI d) => SingI (Foldl1Sym1 d :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (Foldl1Sym1 d) Source # | |
SuppressUnusedWarnings (Foldl1Sym1 a6989586621680492483 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym1 a6989586621680492483 :: TyFun (t a) a -> Type) (a6989586621680492484 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl1Sym1 a6989586621680492483 :: TyFun (t a) a -> Type) (a6989586621680492484 :: t a) = Foldl1Sym2 a6989586621680492483 a6989586621680492484 |
type Foldl1Sym2 (a6989586621680492483 :: (~>) a ((~>) a a)) (a6989586621680492484 :: t a) = Foldl1 a6989586621680492483 a6989586621680492484 :: a Source #
data Foldl1'Sym0 a6989586621679969872 Source #
Instances
SingI (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Foldl1'Sym0 Source # | |
SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679969872 :: a ~> (a ~> a)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679969872 :: a ~> (a ~> a)) = Foldl1'Sym1 a6989586621679969872 |
data Foldl1'Sym1 a6989586621679969872 a6989586621679969873 Source #
Instances
SingI d => SingI (Foldl1'Sym1 d :: TyFun [a] a -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (Foldl1'Sym1 d) Source # | |
SuppressUnusedWarnings (Foldl1'Sym1 a6989586621679969872 :: TyFun [a] a -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym1 a6989586621679969872 :: TyFun [a] a -> Type) (a6989586621679969873 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym1 a6989586621679969872 :: TyFun [a] a -> Type) (a6989586621679969873 :: [a]) = Foldl1'Sym2 a6989586621679969872 a6989586621679969873 |
type Foldl1'Sym2 (a6989586621679969872 :: (~>) a ((~>) a a)) (a6989586621679969873 :: [a]) = Foldl1' a6989586621679969872 a6989586621679969873 :: a Source #
data FoldrSym0 a6989586621680492451 Source #
Instances
SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680492451 :: a ~> (b ~> b)) Source # | |
data FoldrSym1 a6989586621680492451 a6989586621680492452 Source #
Instances
(SFoldable t, SingI d) => SingI (FoldrSym1 d :: TyFun b (t a ~> b) -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym1 a6989586621680492451 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym1 a6989586621680492451 :: TyFun b (t a ~> b) -> Type) (a6989586621680492452 :: b) Source # | |
data FoldrSym2 a6989586621680492451 a6989586621680492452 a6989586621680492453 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 :: TyFun (t a) b -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym2 a6989586621680492451 a6989586621680492452 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym2 a6989586621680492451 a6989586621680492452 :: TyFun (t a) b -> Type) (a6989586621680492453 :: t a) Source # | |
type FoldrSym3 (a6989586621680492451 :: (~>) a ((~>) b b)) (a6989586621680492452 :: b) (a6989586621680492453 :: t a) = Foldr a6989586621680492451 a6989586621680492452 a6989586621680492453 :: b Source #
data Foldr1Sym0 a6989586621680492478 Source #
Instances
SFoldable t => SingI (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing Foldr1Sym0 Source # | |
SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680492478 :: a ~> (a ~> a)) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data Foldr1Sym1 a6989586621680492478 a6989586621680492479 Source #
Instances
(SFoldable t, SingI d) => SingI (Foldr1Sym1 d :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (Foldr1Sym1 d) Source # | |
SuppressUnusedWarnings (Foldr1Sym1 a6989586621680492478 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym1 a6989586621680492478 :: TyFun (t a) a -> Type) (a6989586621680492479 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr1Sym1 a6989586621680492478 :: TyFun (t a) a -> Type) (a6989586621680492479 :: t a) = Foldr1Sym2 a6989586621680492478 a6989586621680492479 |
type Foldr1Sym2 (a6989586621680492478 :: (~>) a ((~>) a a)) (a6989586621680492479 :: t a) = Foldr1 a6989586621680492478 a6989586621680492479 :: a Source #
data ConcatSym0 a6989586621680492332 Source #
Instances
SFoldable t => SingI (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing ConcatSym0 Source # | |
SuppressUnusedWarnings (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680492332 :: t [a]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680492332 :: t [a]) = ConcatSym1 a6989586621680492332 |
type ConcatSym1 (a6989586621680492332 :: t [a]) = Concat a6989586621680492332 :: [a] Source #
data ConcatMapSym0 a6989586621680492321 Source #
Instances
SFoldable t => SingI (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing ConcatMapSym0 Source # | |
SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680492321 :: a ~> [b]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680492321 :: a ~> [b]) = ConcatMapSym1 a6989586621680492321 :: TyFun (t a) [b] -> Type |
data ConcatMapSym1 a6989586621680492321 a6989586621680492322 Source #
Instances
(SFoldable t, SingI d) => SingI (ConcatMapSym1 d :: TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (ConcatMapSym1 d) Source # | |
SuppressUnusedWarnings (ConcatMapSym1 a6989586621680492321 :: TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym1 a6989586621680492321 :: TyFun (t a) [b] -> Type) (a6989586621680492322 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym1 a6989586621680492321 :: TyFun (t a) [b] -> Type) (a6989586621680492322 :: t a) = ConcatMapSym2 a6989586621680492321 a6989586621680492322 |
type ConcatMapSym2 (a6989586621680492321 :: (~>) a [b]) (a6989586621680492322 :: t a) = ConcatMap a6989586621680492321 a6989586621680492322 :: [b] Source #
data AndSym0 a6989586621680492316 Source #
Instances
SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
SuppressUnusedWarnings (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680492316 :: t Bool) Source # | |
data OrSym0 a6989586621680492310 Source #
Instances
SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
SuppressUnusedWarnings (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680492310 :: t Bool) Source # | |
data AnySym0 a6989586621680492302 Source #
Instances
SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680492302 :: a ~> Bool) Source # | |
data AnySym1 a6989586621680492302 a6989586621680492303 Source #
Instances
(SFoldable t, SingI d) => SingI (AnySym1 d :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (AnySym1 a6989586621680492302 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AnySym1 a6989586621680492302 :: TyFun (t a) Bool -> Type) (a6989586621680492303 :: t a) Source # | |
type AnySym2 (a6989586621680492302 :: (~>) a Bool) (a6989586621680492303 :: t a) = Any a6989586621680492302 a6989586621680492303 :: Bool Source #
data AllSym0 a6989586621680492293 Source #
Instances
SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680492293 :: a ~> Bool) Source # | |
data AllSym1 a6989586621680492293 a6989586621680492294 Source #
Instances
(SFoldable t, SingI d) => SingI (AllSym1 d :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (AllSym1 a6989586621680492293 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AllSym1 a6989586621680492293 :: TyFun (t a) Bool -> Type) (a6989586621680492294 :: t a) Source # | |
type AllSym2 (a6989586621680492293 :: (~>) a Bool) (a6989586621680492294 :: t a) = All a6989586621680492293 a6989586621680492294 :: Bool Source #
data SumSym0 a6989586621680492507 Source #
Instances
(SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # | |
SuppressUnusedWarnings (SumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (SumSym0 :: TyFun (t a) a -> Type) (a6989586621680492507 :: t a) Source # | |
data ProductSym0 a6989586621680492510 Source #
Instances
(SFoldable t, SNum a) => SingI (ProductSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing ProductSym0 Source # | |
SuppressUnusedWarnings (ProductSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680492510 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680492510 :: t a) = ProductSym1 a6989586621680492510 |
type ProductSym1 (a6989586621680492510 :: t a) = Product a6989586621680492510 :: a Source #
data MaximumSym0 a6989586621680492501 Source #
Instances
(SFoldable t, SOrd a) => SingI (MaximumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing MaximumSym0 Source # | |
SuppressUnusedWarnings (MaximumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680492501 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680492501 :: t a) = MaximumSym1 a6989586621680492501 |
type MaximumSym1 (a6989586621680492501 :: t a) = Maximum a6989586621680492501 :: a Source #
data MinimumSym0 a6989586621680492504 Source #
Instances
(SFoldable t, SOrd a) => SingI (MinimumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing MinimumSym0 Source # | |
SuppressUnusedWarnings (MinimumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680492504 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680492504 :: t a) = MinimumSym1 a6989586621680492504 |
type MinimumSym1 (a6989586621680492504 :: t a) = Minimum a6989586621680492504 :: a Source #
data ScanlSym0 a6989586621679969805 Source #
Instances
SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679969805 :: b ~> (a ~> b)) Source # | |
data ScanlSym1 a6989586621679969805 a6989586621679969806 Source #
Instances
SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym1 a6989586621679969805 :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym1 a6989586621679969805 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679969806 :: b) Source # | |
data ScanlSym2 a6989586621679969805 a6989586621679969806 a6989586621679969807 Source #
Instances
(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym2 a6989586621679969805 a6989586621679969806 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym2 a6989586621679969805 a6989586621679969806 :: TyFun [a] [b] -> Type) (a6989586621679969807 :: [a]) Source # | |
type ScanlSym3 (a6989586621679969805 :: (~>) b ((~>) a b)) (a6989586621679969806 :: b) (a6989586621679969807 :: [a]) = Scanl a6989586621679969805 a6989586621679969806 a6989586621679969807 :: [b] Source #
data Scanl1Sym0 a6989586621679969796 Source #
Instances
SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Scanl1Sym0 Source # | |
SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679969796 :: a ~> (a ~> a)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679969796 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621679969796 |
data Scanl1Sym1 a6989586621679969796 a6989586621679969797 Source #
Instances
SingI d => SingI (Scanl1Sym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (Scanl1Sym1 d) Source # | |
SuppressUnusedWarnings (Scanl1Sym1 a6989586621679969796 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym1 a6989586621679969796 :: TyFun [a] [a] -> Type) (a6989586621679969797 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym1 a6989586621679969796 :: TyFun [a] [a] -> Type) (a6989586621679969797 :: [a]) = Scanl1Sym2 a6989586621679969796 a6989586621679969797 |
type Scanl1Sym2 (a6989586621679969796 :: (~>) a ((~>) a a)) (a6989586621679969797 :: [a]) = Scanl1 a6989586621679969796 a6989586621679969797 :: [a] Source #
data ScanrSym0 a6989586621679969778 Source #
Instances
SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679969778 :: a ~> (b ~> b)) Source # | |
data ScanrSym1 a6989586621679969778 a6989586621679969779 Source #
Instances
SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym1 a6989586621679969778 :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym1 a6989586621679969778 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679969779 :: b) Source # | |
data ScanrSym2 a6989586621679969778 a6989586621679969779 a6989586621679969780 Source #
Instances
(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym2 a6989586621679969778 a6989586621679969779 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym2 a6989586621679969778 a6989586621679969779 :: TyFun [a] [b] -> Type) (a6989586621679969780 :: [a]) Source # | |
type ScanrSym3 (a6989586621679969778 :: (~>) a ((~>) b b)) (a6989586621679969779 :: b) (a6989586621679969780 :: [a]) = Scanr a6989586621679969778 a6989586621679969779 a6989586621679969780 :: [b] Source #
data Scanr1Sym0 a6989586621679969758 Source #
Instances
SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Scanr1Sym0 Source # | |
SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679969758 :: a ~> (a ~> a)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679969758 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621679969758 |
data Scanr1Sym1 a6989586621679969758 a6989586621679969759 Source #
Instances
SingI d => SingI (Scanr1Sym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (Scanr1Sym1 d) Source # | |
SuppressUnusedWarnings (Scanr1Sym1 a6989586621679969758 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym1 a6989586621679969758 :: TyFun [a] [a] -> Type) (a6989586621679969759 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym1 a6989586621679969758 :: TyFun [a] [a] -> Type) (a6989586621679969759 :: [a]) = Scanr1Sym2 a6989586621679969758 a6989586621679969759 |
type Scanr1Sym2 (a6989586621679969758 :: (~>) a ((~>) a a)) (a6989586621679969759 :: [a]) = Scanr1 a6989586621679969758 a6989586621679969759 :: [a] Source #
data MapAccumLSym0 a6989586621680823006 Source #
Instances
STraversable t => SingI (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable sing :: Sing MapAccumLSym0 Source # | |
SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680823006 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Singletons.Prelude.Traversable |
data MapAccumLSym1 a6989586621680823006 a6989586621680823007 Source #
Instances
(STraversable t, SingI d) => SingI (MapAccumLSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable sing :: Sing (MapAccumLSym1 d) Source # | |
SuppressUnusedWarnings (MapAccumLSym1 a6989586621680823006 :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym1 a6989586621680823006 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680823007 :: a) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym1 a6989586621680823006 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680823007 :: a) = MapAccumLSym2 a6989586621680823006 a6989586621680823007 :: TyFun (t b) (a, t c) -> Type |
data MapAccumLSym2 a6989586621680823006 a6989586621680823007 a6989586621680823008 Source #
Instances
(STraversable t, SingI d1, SingI d2) => SingI (MapAccumLSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable sing :: Sing (MapAccumLSym2 d1 d2) Source # | |
SuppressUnusedWarnings (MapAccumLSym2 a6989586621680823006 a6989586621680823007 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym2 a6989586621680823006 a6989586621680823007 :: TyFun (t b) (a, t c) -> Type) (a6989586621680823008 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym2 a6989586621680823006 a6989586621680823007 :: TyFun (t b) (a, t c) -> Type) (a6989586621680823008 :: t b) = MapAccumLSym3 a6989586621680823006 a6989586621680823007 a6989586621680823008 |
type MapAccumLSym3 (a6989586621680823006 :: (~>) a ((~>) b (a, c))) (a6989586621680823007 :: a) (a6989586621680823008 :: t b) = MapAccumL a6989586621680823006 a6989586621680823007 a6989586621680823008 :: (a, t c) Source #
data MapAccumRSym0 a6989586621680822996 Source #
Instances
STraversable t => SingI (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable sing :: Sing MapAccumRSym0 Source # | |
SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680822996 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Singletons.Prelude.Traversable |
data MapAccumRSym1 a6989586621680822996 a6989586621680822997 Source #
Instances
(STraversable t, SingI d) => SingI (MapAccumRSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable sing :: Sing (MapAccumRSym1 d) Source # | |
SuppressUnusedWarnings (MapAccumRSym1 a6989586621680822996 :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym1 a6989586621680822996 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680822997 :: a) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym1 a6989586621680822996 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680822997 :: a) = MapAccumRSym2 a6989586621680822996 a6989586621680822997 :: TyFun (t b) (a, t c) -> Type |
data MapAccumRSym2 a6989586621680822996 a6989586621680822997 a6989586621680822998 Source #
Instances
(STraversable t, SingI d1, SingI d2) => SingI (MapAccumRSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable sing :: Sing (MapAccumRSym2 d1 d2) Source # | |
SuppressUnusedWarnings (MapAccumRSym2 a6989586621680822996 a6989586621680822997 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym2 a6989586621680822996 a6989586621680822997 :: TyFun (t b) (a, t c) -> Type) (a6989586621680822998 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym2 a6989586621680822996 a6989586621680822997 :: TyFun (t b) (a, t c) -> Type) (a6989586621680822998 :: t b) = MapAccumRSym3 a6989586621680822996 a6989586621680822997 a6989586621680822998 |
type MapAccumRSym3 (a6989586621680822996 :: (~>) a ((~>) b (a, c))) (a6989586621680822997 :: a) (a6989586621680822998 :: t b) = MapAccumR a6989586621680822996 a6989586621680822997 a6989586621680822998 :: (a, t c) Source #
data ReplicateSym0 a6989586621679968895 Source #
Instances
SingI (ReplicateSym0 :: TyFun Nat (a ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing ReplicateSym0 Source # | |
SuppressUnusedWarnings (ReplicateSym0 :: TyFun Nat (a ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym0 :: TyFun Nat (a ~> [a]) -> Type) (a6989586621679968895 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym0 :: TyFun Nat (a ~> [a]) -> Type) (a6989586621679968895 :: Nat) = ReplicateSym1 a6989586621679968895 :: TyFun a [a] -> Type |
data ReplicateSym1 a6989586621679968895 a6989586621679968896 Source #
Instances
SingI d => SingI (ReplicateSym1 d :: TyFun a [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ReplicateSym1 d) Source # | |
SuppressUnusedWarnings (ReplicateSym1 a6989586621679968895 :: TyFun a [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym1 a6989586621679968895 :: TyFun a [a] -> Type) (a6989586621679968896 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym1 a6989586621679968895 :: TyFun a [a] -> Type) (a6989586621679968896 :: a) = ReplicateSym2 a6989586621679968895 a6989586621679968896 |
type ReplicateSym2 (a6989586621679968895 :: Nat) (a6989586621679968896 :: a) = Replicate a6989586621679968895 a6989586621679968896 :: [a] Source #
data UnfoldrSym0 a6989586621679969650 Source #
Instances
SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing UnfoldrSym0 Source # | |
SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679969650 :: b ~> Maybe (a, b)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679969650 :: b ~> Maybe (a, b)) = UnfoldrSym1 a6989586621679969650 |
data UnfoldrSym1 a6989586621679969650 a6989586621679969651 Source #
Instances
SingI d => SingI (UnfoldrSym1 d :: TyFun b [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (UnfoldrSym1 d) Source # | |
SuppressUnusedWarnings (UnfoldrSym1 a6989586621679969650 :: TyFun b [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym1 a6989586621679969650 :: TyFun b [a] -> Type) (a6989586621679969651 :: b) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym1 a6989586621679969650 :: TyFun b [a] -> Type) (a6989586621679969651 :: b) = UnfoldrSym2 a6989586621679969650 a6989586621679969651 |
type UnfoldrSym2 (a6989586621679969650 :: (~>) b (Maybe (a, b))) (a6989586621679969651 :: b) = Unfoldr a6989586621679969650 a6989586621679969651 :: [a] Source #
data TakeSym0 a6989586621679969050 Source #
Instances
SingI (TakeSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (TakeSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym0 :: TyFun Nat ([a] ~> [a]) -> Type) (a6989586621679969050 :: Nat) Source # | |
data TakeSym1 a6989586621679969050 a6989586621679969051 Source #
Instances
SingI d => SingI (TakeSym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (TakeSym1 a6989586621679969050 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym1 a6989586621679969050 :: TyFun [a] [a] -> Type) (a6989586621679969051 :: [a]) Source # | |
type TakeSym2 (a6989586621679969050 :: Nat) (a6989586621679969051 :: [a]) = Take a6989586621679969050 a6989586621679969051 :: [a] Source #
data DropSym0 a6989586621679969037 Source #
Instances
SingI (DropSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (DropSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropSym0 :: TyFun Nat ([a] ~> [a]) -> Type) (a6989586621679969037 :: Nat) Source # | |
data DropSym1 a6989586621679969037 a6989586621679969038 Source #
Instances
SingI d => SingI (DropSym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (DropSym1 a6989586621679969037 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropSym1 a6989586621679969037 :: TyFun [a] [a] -> Type) (a6989586621679969038 :: [a]) Source # | |
type DropSym2 (a6989586621679969037 :: Nat) (a6989586621679969038 :: [a]) = Drop a6989586621679969037 a6989586621679969038 :: [a] Source #
data SplitAtSym0 a6989586621679969030 Source #
Instances
SingI (SplitAtSym0 :: TyFun Nat ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing SplitAtSym0 Source # | |
SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym0 :: TyFun Nat ([a] ~> ([a], [a])) -> Type) (a6989586621679969030 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym0 :: TyFun Nat ([a] ~> ([a], [a])) -> Type) (a6989586621679969030 :: Nat) = SplitAtSym1 a6989586621679969030 :: TyFun [a] ([a], [a]) -> Type |
data SplitAtSym1 a6989586621679969030 a6989586621679969031 Source #
Instances
SingI d => SingI (SplitAtSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (SplitAtSym1 d) Source # | |
SuppressUnusedWarnings (SplitAtSym1 a6989586621679969030 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym1 a6989586621679969030 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679969031 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym1 a6989586621679969030 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679969031 :: [a]) = SplitAtSym2 a6989586621679969030 a6989586621679969031 |
type SplitAtSym2 (a6989586621679969030 :: Nat) (a6989586621679969031 :: [a]) = SplitAt a6989586621679969030 a6989586621679969031 :: ([a], [a]) Source #
data TakeWhileSym0 a6989586621679969167 Source #
Instances
SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing TakeWhileSym0 Source # | |
SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969167 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969167 :: a ~> Bool) = TakeWhileSym1 a6989586621679969167 |
data TakeWhileSym1 a6989586621679969167 a6989586621679969168 Source #
Instances
SingI d => SingI (TakeWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (TakeWhileSym1 d) Source # | |
SuppressUnusedWarnings (TakeWhileSym1 a6989586621679969167 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym1 a6989586621679969167 :: TyFun [a] [a] -> Type) (a6989586621679969168 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym1 a6989586621679969167 :: TyFun [a] [a] -> Type) (a6989586621679969168 :: [a]) = TakeWhileSym2 a6989586621679969167 a6989586621679969168 |
type TakeWhileSym2 (a6989586621679969167 :: (~>) a Bool) (a6989586621679969168 :: [a]) = TakeWhile a6989586621679969167 a6989586621679969168 :: [a] Source #
data DropWhileSym0 a6989586621679969152 Source #
Instances
SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing DropWhileSym0 Source # | |
SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969152 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969152 :: a ~> Bool) = DropWhileSym1 a6989586621679969152 |
data DropWhileSym1 a6989586621679969152 a6989586621679969153 Source #
Instances
SingI d => SingI (DropWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DropWhileSym1 d) Source # | |
SuppressUnusedWarnings (DropWhileSym1 a6989586621679969152 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym1 a6989586621679969152 :: TyFun [a] [a] -> Type) (a6989586621679969153 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym1 a6989586621679969152 :: TyFun [a] [a] -> Type) (a6989586621679969153 :: [a]) = DropWhileSym2 a6989586621679969152 a6989586621679969153 |
type DropWhileSym2 (a6989586621679969152 :: (~>) a Bool) (a6989586621679969153 :: [a]) = DropWhile a6989586621679969152 a6989586621679969153 :: [a] Source #
data DropWhileEndSym0 a6989586621679969135 Source #
Instances
SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969135 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969135 :: a ~> Bool) = DropWhileEndSym1 a6989586621679969135 |
data DropWhileEndSym1 a6989586621679969135 a6989586621679969136 Source #
Instances
SingI d => SingI (DropWhileEndSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DropWhileEndSym1 d) Source # | |
SuppressUnusedWarnings (DropWhileEndSym1 a6989586621679969135 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym1 a6989586621679969135 :: TyFun [a] [a] -> Type) (a6989586621679969136 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym1 a6989586621679969135 :: TyFun [a] [a] -> Type) (a6989586621679969136 :: [a]) = DropWhileEndSym2 a6989586621679969135 a6989586621679969136 |
type DropWhileEndSym2 (a6989586621679969135 :: (~>) a Bool) (a6989586621679969136 :: [a]) = DropWhileEnd a6989586621679969135 a6989586621679969136 :: [a] Source #
data SpanSym0 a6989586621679969098 Source #
Instances
SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679969098 :: a ~> Bool) Source # | |
data SpanSym1 a6989586621679969098 a6989586621679969099 Source #
Instances
SingI d => SingI (SpanSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym1 a6989586621679969098 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym1 a6989586621679969098 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679969099 :: [a]) Source # | |
type SpanSym2 (a6989586621679969098 :: (~>) a Bool) (a6989586621679969099 :: [a]) = Span a6989586621679969098 a6989586621679969099 :: ([a], [a]) Source #
data BreakSym0 a6989586621679969063 Source #
Instances
SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679969063 :: a ~> Bool) Source # | |
data BreakSym1 a6989586621679969063 a6989586621679969064 Source #
Instances
SingI d => SingI (BreakSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym1 a6989586621679969063 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym1 a6989586621679969063 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679969064 :: [a]) Source # | |
type BreakSym2 (a6989586621679969063 :: (~>) a Bool) (a6989586621679969064 :: [a]) = Break a6989586621679969063 a6989586621679969064 :: ([a], [a]) Source #
data StripPrefixSym0 a6989586621680091346 Source #
Instances
SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621680091346 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621680091346 :: [a]) = StripPrefixSym1 a6989586621680091346 |
data StripPrefixSym1 a6989586621680091346 a6989586621680091347 Source #
Instances
SuppressUnusedWarnings (StripPrefixSym1 a6989586621680091346 :: TyFun [a] (Maybe [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (StripPrefixSym1 a6989586621680091346 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680091347 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym1 a6989586621680091346 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680091347 :: [a]) = StripPrefixSym2 a6989586621680091346 a6989586621680091347 |
type StripPrefixSym2 (a6989586621680091346 :: [a]) (a6989586621680091347 :: [a]) = StripPrefix a6989586621680091346 a6989586621680091347 :: Maybe [a] Source #
data GroupSym0 a6989586621679969025 Source #
Instances
SEq a => SingI (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969025 :: [a]) Source # | |
data InitsSym0 a6989586621679969640 Source #
Instances
SingI (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969640 :: [a]) Source # | |
data TailsSym0 a6989586621679969632 Source #
Instances
SingI (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969632 :: [a]) Source # | |
data IsPrefixOfSym0 a6989586621679969624 Source #
Instances
SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679969624 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679969624 :: [a]) = IsPrefixOfSym1 a6989586621679969624 |
data IsPrefixOfSym1 a6989586621679969624 a6989586621679969625 Source #
Instances
(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IsPrefixOfSym1 d) Source # | |
SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679969624 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym1 a6989586621679969624 :: TyFun [a] Bool -> Type) (a6989586621679969625 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym1 a6989586621679969624 :: TyFun [a] Bool -> Type) (a6989586621679969625 :: [a]) = IsPrefixOfSym2 a6989586621679969624 a6989586621679969625 |
type IsPrefixOfSym2 (a6989586621679969624 :: [a]) (a6989586621679969625 :: [a]) = IsPrefixOf a6989586621679969624 a6989586621679969625 :: Bool Source #
data IsSuffixOfSym0 a6989586621679969617 Source #
Instances
SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679969617 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679969617 :: [a]) = IsSuffixOfSym1 a6989586621679969617 |
data IsSuffixOfSym1 a6989586621679969617 a6989586621679969618 Source #
Instances
(SEq a, SingI d) => SingI (IsSuffixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IsSuffixOfSym1 d) Source # | |
SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679969617 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym1 a6989586621679969617 :: TyFun [a] Bool -> Type) (a6989586621679969618 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym1 a6989586621679969617 :: TyFun [a] Bool -> Type) (a6989586621679969618 :: [a]) = IsSuffixOfSym2 a6989586621679969617 a6989586621679969618 |
type IsSuffixOfSym2 (a6989586621679969617 :: [a]) (a6989586621679969618 :: [a]) = IsSuffixOf a6989586621679969617 a6989586621679969618 :: Bool Source #
data IsInfixOfSym0 a6989586621679969610 Source #
Instances
SEq a => SingI (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing IsInfixOfSym0 Source # | |
SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679969610 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679969610 :: [a]) = IsInfixOfSym1 a6989586621679969610 |
data IsInfixOfSym1 a6989586621679969610 a6989586621679969611 Source #
Instances
(SEq a, SingI d) => SingI (IsInfixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IsInfixOfSym1 d) Source # | |
SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679969610 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym1 a6989586621679969610 :: TyFun [a] Bool -> Type) (a6989586621679969611 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsInfixOfSym1 a6989586621679969610 :: TyFun [a] Bool -> Type) (a6989586621679969611 :: [a]) = IsInfixOfSym2 a6989586621679969610 a6989586621679969611 |
type IsInfixOfSym2 (a6989586621679969610 :: [a]) (a6989586621679969611 :: [a]) = IsInfixOf a6989586621679969610 a6989586621679969611 :: Bool Source #
data ElemSym0 a6989586621680492497 Source #
Instances
(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680492497 :: a) Source # | |
data ElemSym1 a6989586621680492497 a6989586621680492498 Source #
Instances
(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (ElemSym1 a6989586621680492497 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym1 a6989586621680492497 :: TyFun (t a) Bool -> Type) (a6989586621680492498 :: t a) Source # | |
type ElemSym2 (a6989586621680492497 :: a) (a6989586621680492498 :: t a) = Elem a6989586621680492497 a6989586621680492498 :: Bool Source #
data NotElemSym0 a6989586621680492244 Source #
Instances
(SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing NotElemSym0 Source # | |
SuppressUnusedWarnings (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680492244 :: a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680492244 :: a) = NotElemSym1 a6989586621680492244 :: TyFun (t a) Bool -> Type |
data NotElemSym1 a6989586621680492244 a6989586621680492245 Source #
Instances
(SFoldable t, SEq a, SingI d) => SingI (NotElemSym1 d :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (NotElemSym1 d) Source # | |
SuppressUnusedWarnings (NotElemSym1 a6989586621680492244 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym1 a6989586621680492244 :: TyFun (t a) Bool -> Type) (a6989586621680492245 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (NotElemSym1 a6989586621680492244 :: TyFun (t a) Bool -> Type) (a6989586621680492245 :: t a) = NotElemSym2 a6989586621680492244 a6989586621680492245 |
type NotElemSym2 (a6989586621680492244 :: a) (a6989586621680492245 :: t a) = NotElem a6989586621680492244 a6989586621680492245 :: Bool Source #
data LookupSym0 a6989586621679968958 Source #
Instances
SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing LookupSym0 Source # | |
SuppressUnusedWarnings (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679968958 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679968958 :: a) = LookupSym1 a6989586621679968958 :: TyFun [(a, b)] (Maybe b) -> Type |
data LookupSym1 a6989586621679968958 a6989586621679968959 Source #
Instances
(SEq a, SingI d) => SingI (LookupSym1 d :: TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (LookupSym1 d) Source # | |
SuppressUnusedWarnings (LookupSym1 a6989586621679968958 :: TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym1 a6989586621679968958 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679968959 :: [(a, b)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (LookupSym1 a6989586621679968958 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679968959 :: [(a, b)]) = LookupSym2 a6989586621679968958 a6989586621679968959 |
type LookupSym2 (a6989586621679968958 :: a) (a6989586621679968959 :: [(a, b)]) = Lookup a6989586621679968958 a6989586621679968959 :: Maybe b Source #
data FindSym0 a6989586621680492226 Source #
Instances
SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # | |
SuppressUnusedWarnings (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680492226 :: a ~> Bool) Source # | |
data FindSym1 a6989586621680492226 a6989586621680492227 Source #
Instances
(SFoldable t, SingI d) => SingI (FindSym1 d :: TyFun (t a) (Maybe a) -> Type) Source # | |
SuppressUnusedWarnings (FindSym1 a6989586621680492226 :: TyFun (t a) (Maybe a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FindSym1 a6989586621680492226 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680492227 :: t a) Source # | |
type FindSym2 (a6989586621680492226 :: (~>) a Bool) (a6989586621680492227 :: t a) = Find a6989586621680492226 a6989586621680492227 :: Maybe a Source #
data FilterSym0 a6989586621679969267 Source #
Instances
SingI (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing FilterSym0 Source # | |
SuppressUnusedWarnings (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969267 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969267 :: a ~> Bool) = FilterSym1 a6989586621679969267 |
data FilterSym1 a6989586621679969267 a6989586621679969268 Source #
Instances
SingI d => SingI (FilterSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (FilterSym1 d) Source # | |
SuppressUnusedWarnings (FilterSym1 a6989586621679969267 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym1 a6989586621679969267 :: TyFun [a] [a] -> Type) (a6989586621679969268 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym1 a6989586621679969267 :: TyFun [a] [a] -> Type) (a6989586621679969268 :: [a]) = FilterSym2 a6989586621679969267 a6989586621679969268 |
type FilterSym2 (a6989586621679969267 :: (~>) a Bool) (a6989586621679969268 :: [a]) = Filter a6989586621679969267 a6989586621679969268 :: [a] Source #
data PartitionSym0 a6989586621679968951 Source #
Instances
SingI (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing PartitionSym0 Source # | |
SuppressUnusedWarnings (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679968951 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679968951 :: a ~> Bool) = PartitionSym1 a6989586621679968951 |
data PartitionSym1 a6989586621679968951 a6989586621679968952 Source #
Instances
SingI d => SingI (PartitionSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (PartitionSym1 d) Source # | |
SuppressUnusedWarnings (PartitionSym1 a6989586621679968951 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym1 a6989586621679968951 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679968952 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym1 a6989586621679968951 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679968952 :: [a]) = PartitionSym2 a6989586621679968951 a6989586621679968952 |
type PartitionSym2 (a6989586621679968951 :: (~>) a Bool) (a6989586621679968952 :: [a]) = Partition a6989586621679968951 a6989586621679968952 :: ([a], [a]) Source #
data (!!@#@$) a6989586621679968875 infixl 9 Source #
Instances
SingI ((!!@#@$) :: TyFun [a] (Nat ~> a) -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$) :: TyFun [a] (Nat ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$) :: TyFun [a] (Nat ~> a) -> Type) (a6989586621679968875 :: [a]) Source # | |
data a6989586621679968875 !!@#@$$ a6989586621679968876 infixl 9 Source #
Instances
SingI d => SingI ((!!@#@$$) d :: TyFun Nat a -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$$) a6989586621679968875 :: TyFun Nat a -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$$) a6989586621679968875 :: TyFun Nat a -> Type) (a6989586621679968876 :: Nat) Source # | |
type (!!@#@$$$) (a6989586621679968875 :: [a]) (a6989586621679968876 :: Nat) = (!!) a6989586621679968875 a6989586621679968876 :: a infixl 9 Source #
data ElemIndexSym0 a6989586621679969251 Source #
Instances
SEq a => SingI (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing ElemIndexSym0 Source # | |
SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) (a6989586621679969251 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) (a6989586621679969251 :: a) = ElemIndexSym1 a6989586621679969251 |
data ElemIndexSym1 a6989586621679969251 a6989586621679969252 Source #
Instances
(SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ElemIndexSym1 d) Source # | |
SuppressUnusedWarnings (ElemIndexSym1 a6989586621679969251 :: TyFun [a] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym1 a6989586621679969251 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679969252 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndexSym1 a6989586621679969251 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679969252 :: [a]) = ElemIndexSym2 a6989586621679969251 a6989586621679969252 |
type ElemIndexSym2 (a6989586621679969251 :: a) (a6989586621679969252 :: [a]) = ElemIndex a6989586621679969251 a6989586621679969252 :: Maybe Nat Source #
data ElemIndicesSym0 a6989586621679969242 Source #
Instances
SEq a => SingI (ElemIndicesSym0 :: TyFun a ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Nat]) -> Type) (a6989586621679969242 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Nat]) -> Type) (a6989586621679969242 :: a) = ElemIndicesSym1 a6989586621679969242 |
data ElemIndicesSym1 a6989586621679969242 a6989586621679969243 Source #
Instances
(SEq a, SingI d) => SingI (ElemIndicesSym1 d :: TyFun [a] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ElemIndicesSym1 d) Source # | |
SuppressUnusedWarnings (ElemIndicesSym1 a6989586621679969242 :: TyFun [a] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym1 a6989586621679969242 :: TyFun [a] [Nat] -> Type) (a6989586621679969243 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym1 a6989586621679969242 :: TyFun [a] [Nat] -> Type) (a6989586621679969243 :: [a]) = ElemIndicesSym2 a6989586621679969242 a6989586621679969243 |
type ElemIndicesSym2 (a6989586621679969242 :: a) (a6989586621679969243 :: [a]) = ElemIndices a6989586621679969242 a6989586621679969243 :: [Nat] Source #
data FindIndexSym0 a6989586621679969233 Source #
Instances
SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing FindIndexSym0 Source # | |
SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) (a6989586621679969233 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data FindIndexSym1 a6989586621679969233 a6989586621679969234 Source #
Instances
SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (FindIndexSym1 d) Source # | |
SuppressUnusedWarnings (FindIndexSym1 a6989586621679969233 :: TyFun [a] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym1 a6989586621679969233 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679969234 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndexSym1 a6989586621679969233 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679969234 :: [a]) = FindIndexSym2 a6989586621679969233 a6989586621679969234 |
type FindIndexSym2 (a6989586621679969233 :: (~>) a Bool) (a6989586621679969234 :: [a]) = FindIndex a6989586621679969233 a6989586621679969234 :: Maybe Nat Source #
data FindIndicesSym0 a6989586621679969210 Source #
Instances
SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) (a6989586621679969210 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data FindIndicesSym1 a6989586621679969210 a6989586621679969211 Source #
Instances
SingI d => SingI (FindIndicesSym1 d :: TyFun [a] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (FindIndicesSym1 d) Source # | |
SuppressUnusedWarnings (FindIndicesSym1 a6989586621679969210 :: TyFun [a] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym1 a6989586621679969210 :: TyFun [a] [Nat] -> Type) (a6989586621679969211 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndicesSym1 a6989586621679969210 :: TyFun [a] [Nat] -> Type) (a6989586621679969211 :: [a]) = FindIndicesSym2 a6989586621679969210 a6989586621679969211 |
type FindIndicesSym2 (a6989586621679969210 :: (~>) a Bool) (a6989586621679969211 :: [a]) = FindIndices a6989586621679969210 a6989586621679969211 :: [Nat] Source #
data ZipSym0 a6989586621679969585 Source #
Instances
SingI (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # | |
SuppressUnusedWarnings (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679969585 :: [a]) Source # | |
data ZipSym1 a6989586621679969585 a6989586621679969586 Source #
Instances
SingI d => SingI (ZipSym1 d :: TyFun [b] [(a, b)] -> Type) Source # | |
SuppressUnusedWarnings (ZipSym1 a6989586621679969585 :: TyFun [b] [(a, b)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym1 a6989586621679969585 :: TyFun [b] [(a, b)] -> Type) (a6989586621679969586 :: [b]) Source # | |
type ZipSym2 (a6989586621679969585 :: [a]) (a6989586621679969586 :: [b]) = Zip a6989586621679969585 a6989586621679969586 :: [(a, b)] Source #
data Zip3Sym0 a6989586621679969573 Source #
Instances
SingI (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679969573 :: [a]) Source # | |
data Zip3Sym1 a6989586621679969573 a6989586621679969574 Source #
Instances
SingI d => SingI (Zip3Sym1 d :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym1 a6989586621679969573 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym1 a6989586621679969573 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679969574 :: [b]) Source # | |
data Zip3Sym2 a6989586621679969573 a6989586621679969574 a6989586621679969575 Source #
Instances
(SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 :: TyFun [c] [(a, b, c)] -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym2 a6989586621679969573 a6989586621679969574 :: TyFun [c] [(a, b, c)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym2 a6989586621679969573 a6989586621679969574 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679969575 :: [c]) Source # | |
type Zip3Sym3 (a6989586621679969573 :: [a]) (a6989586621679969574 :: [b]) (a6989586621679969575 :: [c]) = Zip3 a6989586621679969573 a6989586621679969574 a6989586621679969575 :: [(a, b, c)] Source #
data Zip4Sym0 a6989586621680091335 Source #
Instances
SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621680091335 :: [a]) Source # | |
data Zip4Sym1 a6989586621680091335 a6989586621680091336 Source #
Instances
SuppressUnusedWarnings (Zip4Sym1 a6989586621680091335 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym1 a6989586621680091335 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621680091336 :: [b]) Source # | |
data Zip4Sym2 a6989586621680091335 a6989586621680091336 a6989586621680091337 Source #
Instances
SuppressUnusedWarnings (Zip4Sym2 a6989586621680091335 a6989586621680091336 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym2 a6989586621680091335 a6989586621680091336 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621680091337 :: [c]) Source # | |
data Zip4Sym3 a6989586621680091335 a6989586621680091336 a6989586621680091337 a6989586621680091338 Source #
Instances
SuppressUnusedWarnings (Zip4Sym3 a6989586621680091335 a6989586621680091336 a6989586621680091337 :: TyFun [d] [(a, b, c, d)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym3 a6989586621680091335 a6989586621680091336 a6989586621680091337 :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621680091338 :: [d]) Source # | |
type Zip4Sym4 (a6989586621680091335 :: [a]) (a6989586621680091336 :: [b]) (a6989586621680091337 :: [c]) (a6989586621680091338 :: [d]) = Zip4 a6989586621680091335 a6989586621680091336 a6989586621680091337 a6989586621680091338 :: [(a, b, c, d)] Source #
data Zip5Sym0 a6989586621680091312 Source #
Instances
SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) (a6989586621680091312 :: [a]) Source # | |
data Zip5Sym1 a6989586621680091312 a6989586621680091313 Source #
Instances
SuppressUnusedWarnings (Zip5Sym1 a6989586621680091312 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym1 a6989586621680091312 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621680091313 :: [b]) Source # | |
data Zip5Sym2 a6989586621680091312 a6989586621680091313 a6989586621680091314 Source #
Instances
SuppressUnusedWarnings (Zip5Sym2 a6989586621680091312 a6989586621680091313 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym2 a6989586621680091312 a6989586621680091313 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621680091314 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data Zip5Sym3 a6989586621680091312 a6989586621680091313 a6989586621680091314 a6989586621680091315 Source #
Instances
SuppressUnusedWarnings (Zip5Sym3 a6989586621680091312 a6989586621680091313 a6989586621680091314 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym3 a6989586621680091312 a6989586621680091313 a6989586621680091314 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621680091315 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data Zip5Sym4 a6989586621680091312 a6989586621680091313 a6989586621680091314 a6989586621680091315 a6989586621680091316 Source #
Instances
SuppressUnusedWarnings (Zip5Sym4 a6989586621680091312 a6989586621680091313 a6989586621680091314 a6989586621680091315 :: TyFun [e] [(a, b, c, d, e)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym4 a6989586621680091312 a6989586621680091313 a6989586621680091314 a6989586621680091315 :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621680091316 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type Zip5Sym5 (a6989586621680091312 :: [a]) (a6989586621680091313 :: [b]) (a6989586621680091314 :: [c]) (a6989586621680091315 :: [d]) (a6989586621680091316 :: [e]) = Zip5 a6989586621680091312 a6989586621680091313 a6989586621680091314 a6989586621680091315 a6989586621680091316 :: [(a, b, c, d, e)] Source #
data Zip6Sym0 a6989586621680091284 Source #
Instances
SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) (a6989586621680091284 :: [a]) Source # | |
data Zip6Sym1 a6989586621680091284 a6989586621680091285 Source #
Instances
SuppressUnusedWarnings (Zip6Sym1 a6989586621680091284 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym1 a6989586621680091284 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621680091285 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data Zip6Sym2 a6989586621680091284 a6989586621680091285 a6989586621680091286 Source #
Instances
SuppressUnusedWarnings (Zip6Sym2 a6989586621680091284 a6989586621680091285 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym2 a6989586621680091284 a6989586621680091285 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621680091286 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data Zip6Sym3 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 Source #
Instances
SuppressUnusedWarnings (Zip6Sym3 a6989586621680091284 a6989586621680091285 a6989586621680091286 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym3 a6989586621680091284 a6989586621680091285 a6989586621680091286 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621680091287 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym3 a6989586621680091284 a6989586621680091285 a6989586621680091286 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621680091287 :: [d]) = Zip6Sym4 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type |
data Zip6Sym4 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 Source #
Instances
SuppressUnusedWarnings (Zip6Sym4 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym4 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621680091288 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym4 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621680091288 :: [e]) = Zip6Sym5 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 :: TyFun [f] [(a, b, c, d, e, f)] -> Type |
data Zip6Sym5 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 a6989586621680091289 Source #
Instances
SuppressUnusedWarnings (Zip6Sym5 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym5 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680091289 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym5 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680091289 :: [f]) = Zip6Sym6 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 a6989586621680091289 |
type Zip6Sym6 (a6989586621680091284 :: [a]) (a6989586621680091285 :: [b]) (a6989586621680091286 :: [c]) (a6989586621680091287 :: [d]) (a6989586621680091288 :: [e]) (a6989586621680091289 :: [f]) = Zip6 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 a6989586621680091289 :: [(a, b, c, d, e, f)] Source #
data Zip7Sym0 a6989586621680091251 Source #
Instances
SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) (a6989586621680091251 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data Zip7Sym1 a6989586621680091251 a6989586621680091252 Source #
Instances
SuppressUnusedWarnings (Zip7Sym1 a6989586621680091251 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym1 a6989586621680091251 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621680091252 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data Zip7Sym2 a6989586621680091251 a6989586621680091252 a6989586621680091253 Source #
Instances
SuppressUnusedWarnings (Zip7Sym2 a6989586621680091251 a6989586621680091252 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym2 a6989586621680091251 a6989586621680091252 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621680091253 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym2 a6989586621680091251 a6989586621680091252 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621680091253 :: [c]) = Zip7Sym3 a6989586621680091251 a6989586621680091252 a6989586621680091253 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type |
data Zip7Sym3 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 Source #
Instances
SuppressUnusedWarnings (Zip7Sym3 a6989586621680091251 a6989586621680091252 a6989586621680091253 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym3 a6989586621680091251 a6989586621680091252 a6989586621680091253 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621680091254 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym3 a6989586621680091251 a6989586621680091252 a6989586621680091253 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621680091254 :: [d]) = Zip7Sym4 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type |
data Zip7Sym4 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 Source #
Instances
SuppressUnusedWarnings (Zip7Sym4 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym4 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621680091255 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym4 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621680091255 :: [e]) = Zip7Sym5 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type |
data Zip7Sym5 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 Source #
Instances
SuppressUnusedWarnings (Zip7Sym5 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym5 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621680091256 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym5 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621680091256 :: [f]) = Zip7Sym6 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type |
data Zip7Sym6 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 a6989586621680091257 Source #
Instances
SuppressUnusedWarnings (Zip7Sym6 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym6 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680091257 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym6 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680091257 :: [g]) = Zip7Sym7 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 a6989586621680091257 |
type Zip7Sym7 (a6989586621680091251 :: [a]) (a6989586621680091252 :: [b]) (a6989586621680091253 :: [c]) (a6989586621680091254 :: [d]) (a6989586621680091255 :: [e]) (a6989586621680091256 :: [f]) (a6989586621680091257 :: [g]) = Zip7 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 a6989586621680091257 :: [(a, b, c, d, e, f, g)] Source #
data ZipWithSym0 a6989586621679969561 Source #
Instances
SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing ZipWithSym0 Source # | |
SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679969561 :: a ~> (b ~> c)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data ZipWithSym1 a6989586621679969561 a6989586621679969562 Source #
Instances
SingI d => SingI (ZipWithSym1 d :: TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ZipWithSym1 d) Source # | |
SuppressUnusedWarnings (ZipWithSym1 a6989586621679969561 :: TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym1 a6989586621679969561 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679969562 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym1 a6989586621679969561 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679969562 :: [a]) = ZipWithSym2 a6989586621679969561 a6989586621679969562 |
data ZipWithSym2 a6989586621679969561 a6989586621679969562 a6989586621679969563 Source #
Instances
(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun [b] [c] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ZipWithSym2 d1 d2) Source # | |
SuppressUnusedWarnings (ZipWithSym2 a6989586621679969561 a6989586621679969562 :: TyFun [b] [c] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym2 a6989586621679969561 a6989586621679969562 :: TyFun [b] [c] -> Type) (a6989586621679969563 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym2 a6989586621679969561 a6989586621679969562 :: TyFun [b] [c] -> Type) (a6989586621679969563 :: [b]) = ZipWithSym3 a6989586621679969561 a6989586621679969562 a6989586621679969563 |
type ZipWithSym3 (a6989586621679969561 :: (~>) a ((~>) b c)) (a6989586621679969562 :: [a]) (a6989586621679969563 :: [b]) = ZipWith a6989586621679969561 a6989586621679969562 a6989586621679969563 :: [c] Source #
data ZipWith3Sym0 a6989586621679969546 Source #
Instances
SingI (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing ZipWith3Sym0 Source # | |
SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679969546 :: a ~> (b ~> (c ~> d))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data ZipWith3Sym1 a6989586621679969546 a6989586621679969547 Source #
Instances
SingI d2 => SingI (ZipWith3Sym1 d2 :: TyFun [a] ([b] ~> ([c] ~> [d1])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ZipWith3Sym1 d2) Source # | |
SuppressUnusedWarnings (ZipWith3Sym1 a6989586621679969546 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym1 a6989586621679969546 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679969547 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym1 a6989586621679969546 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679969547 :: [a]) = ZipWith3Sym2 a6989586621679969546 a6989586621679969547 |
data ZipWith3Sym2 a6989586621679969546 a6989586621679969547 a6989586621679969548 Source #
Instances
(SingI d2, SingI d3) => SingI (ZipWith3Sym2 d2 d3 :: TyFun [b] ([c] ~> [d1]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ZipWith3Sym2 d2 d3) Source # | |
SuppressUnusedWarnings (ZipWith3Sym2 a6989586621679969546 a6989586621679969547 :: TyFun [b] ([c] ~> [d]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym2 a6989586621679969546 a6989586621679969547 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679969548 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym2 a6989586621679969546 a6989586621679969547 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679969548 :: [b]) = ZipWith3Sym3 a6989586621679969546 a6989586621679969547 a6989586621679969548 |
data ZipWith3Sym3 a6989586621679969546 a6989586621679969547 a6989586621679969548 a6989586621679969549 Source #
Instances
(SingI d2, SingI d3, SingI d4) => SingI (ZipWith3Sym3 d2 d3 d4 :: TyFun [c] [d1] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ZipWith3Sym3 d2 d3 d4) Source # | |
SuppressUnusedWarnings (ZipWith3Sym3 a6989586621679969546 a6989586621679969547 a6989586621679969548 :: TyFun [c] [d] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym3 a6989586621679969546 a6989586621679969547 a6989586621679969548 :: TyFun [c] [d] -> Type) (a6989586621679969549 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym3 a6989586621679969546 a6989586621679969547 a6989586621679969548 :: TyFun [c] [d] -> Type) (a6989586621679969549 :: [c]) = ZipWith3Sym4 a6989586621679969546 a6989586621679969547 a6989586621679969548 a6989586621679969549 |
type ZipWith3Sym4 (a6989586621679969546 :: (~>) a ((~>) b ((~>) c d))) (a6989586621679969547 :: [a]) (a6989586621679969548 :: [b]) (a6989586621679969549 :: [c]) = ZipWith3 a6989586621679969546 a6989586621679969547 a6989586621679969548 a6989586621679969549 :: [d] Source #
data ZipWith4Sym0 a6989586621680091215 Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) (a6989586621680091215 :: a ~> (b ~> (c ~> (d ~> e)))) Source # | |
data ZipWith4Sym1 a6989586621680091215 a6989586621680091216 Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym1 a6989586621680091215 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym1 a6989586621680091215 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621680091216 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym1 a6989586621680091215 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621680091216 :: [a]) = ZipWith4Sym2 a6989586621680091215 a6989586621680091216 |
data ZipWith4Sym2 a6989586621680091215 a6989586621680091216 a6989586621680091217 Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym2 a6989586621680091215 a6989586621680091216 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym2 a6989586621680091215 a6989586621680091216 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621680091217 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym2 a6989586621680091215 a6989586621680091216 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621680091217 :: [b]) = ZipWith4Sym3 a6989586621680091215 a6989586621680091216 a6989586621680091217 |
data ZipWith4Sym3 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym3 a6989586621680091215 a6989586621680091216 a6989586621680091217 :: TyFun [c] ([d] ~> [e]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym3 a6989586621680091215 a6989586621680091216 a6989586621680091217 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621680091218 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym3 a6989586621680091215 a6989586621680091216 a6989586621680091217 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621680091218 :: [c]) = ZipWith4Sym4 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 |
data ZipWith4Sym4 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 a6989586621680091219 Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym4 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 :: TyFun [d] [e] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym4 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 :: TyFun [d] [e] -> Type) (a6989586621680091219 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym4 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 :: TyFun [d] [e] -> Type) (a6989586621680091219 :: [d]) = ZipWith4Sym5 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 a6989586621680091219 |
type ZipWith4Sym5 (a6989586621680091215 :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a6989586621680091216 :: [a]) (a6989586621680091217 :: [b]) (a6989586621680091218 :: [c]) (a6989586621680091219 :: [d]) = ZipWith4 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 a6989586621680091219 :: [e] Source #
data ZipWith5Sym0 a6989586621680091192 Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) (a6989586621680091192 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) Source # | |
data ZipWith5Sym1 a6989586621680091192 a6989586621680091193 Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym1 a6989586621680091192 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym1 a6989586621680091192 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621680091193 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym1 a6989586621680091192 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621680091193 :: [a]) = ZipWith5Sym2 a6989586621680091192 a6989586621680091193 |
data ZipWith5Sym2 a6989586621680091192 a6989586621680091193 a6989586621680091194 Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym2 a6989586621680091192 a6989586621680091193 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym2 a6989586621680091192 a6989586621680091193 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621680091194 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym2 a6989586621680091192 a6989586621680091193 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621680091194 :: [b]) = ZipWith5Sym3 a6989586621680091192 a6989586621680091193 a6989586621680091194 |
data ZipWith5Sym3 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym3 a6989586621680091192 a6989586621680091193 a6989586621680091194 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym3 a6989586621680091192 a6989586621680091193 a6989586621680091194 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621680091195 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym3 a6989586621680091192 a6989586621680091193 a6989586621680091194 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621680091195 :: [c]) = ZipWith5Sym4 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 |
data ZipWith5Sym4 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym4 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 :: TyFun [d] ([e] ~> [f]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym4 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621680091196 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym4 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621680091196 :: [d]) = ZipWith5Sym5 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 |
data ZipWith5Sym5 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 a6989586621680091197 Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym5 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 :: TyFun [e] [f] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym5 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 :: TyFun [e] [f] -> Type) (a6989586621680091197 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym5 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 :: TyFun [e] [f] -> Type) (a6989586621680091197 :: [e]) = ZipWith5Sym6 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 a6989586621680091197 |
type ZipWith5Sym6 (a6989586621680091192 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a6989586621680091193 :: [a]) (a6989586621680091194 :: [b]) (a6989586621680091195 :: [c]) (a6989586621680091196 :: [d]) (a6989586621680091197 :: [e]) = ZipWith5 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 a6989586621680091197 :: [f] Source #
data ZipWith6Sym0 a6989586621680091165 Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) (a6989586621680091165 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) Source # | |
data ZipWith6Sym1 a6989586621680091165 a6989586621680091166 Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym1 a6989586621680091165 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym1 a6989586621680091165 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621680091166 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym1 a6989586621680091165 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621680091166 :: [a]) = ZipWith6Sym2 a6989586621680091165 a6989586621680091166 |
data ZipWith6Sym2 a6989586621680091165 a6989586621680091166 a6989586621680091167 Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym2 a6989586621680091165 a6989586621680091166 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym2 a6989586621680091165 a6989586621680091166 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621680091167 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym2 a6989586621680091165 a6989586621680091166 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621680091167 :: [b]) = ZipWith6Sym3 a6989586621680091165 a6989586621680091166 a6989586621680091167 |
data ZipWith6Sym3 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym3 a6989586621680091165 a6989586621680091166 a6989586621680091167 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym3 a6989586621680091165 a6989586621680091166 a6989586621680091167 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621680091168 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym3 a6989586621680091165 a6989586621680091166 a6989586621680091167 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621680091168 :: [c]) = ZipWith6Sym4 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 |
data ZipWith6Sym4 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym4 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym4 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621680091169 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym4 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621680091169 :: [d]) = ZipWith6Sym5 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 |
data ZipWith6Sym5 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym5 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 :: TyFun [e] ([f] ~> [g]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym5 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621680091170 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym5 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621680091170 :: [e]) = ZipWith6Sym6 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 |
data ZipWith6Sym6 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 a6989586621680091171 Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym6 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 :: TyFun [f] [g] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym6 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 :: TyFun [f] [g] -> Type) (a6989586621680091171 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym6 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 :: TyFun [f] [g] -> Type) (a6989586621680091171 :: [f]) = ZipWith6Sym7 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 a6989586621680091171 |
type ZipWith6Sym7 (a6989586621680091165 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a6989586621680091166 :: [a]) (a6989586621680091167 :: [b]) (a6989586621680091168 :: [c]) (a6989586621680091169 :: [d]) (a6989586621680091170 :: [e]) (a6989586621680091171 :: [f]) = ZipWith6 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 a6989586621680091171 :: [g] Source #
data ZipWith7Sym0 a6989586621680091134 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.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) (a6989586621680091134 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data ZipWith7Sym1 a6989586621680091134 a6989586621680091135 Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym1 a6989586621680091134 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym1 a6989586621680091134 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621680091135 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data ZipWith7Sym2 a6989586621680091134 a6989586621680091135 a6989586621680091136 Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym2 a6989586621680091134 a6989586621680091135 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym2 a6989586621680091134 a6989586621680091135 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621680091136 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym2 a6989586621680091134 a6989586621680091135 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621680091136 :: [b]) = ZipWith7Sym3 a6989586621680091134 a6989586621680091135 a6989586621680091136 |
data ZipWith7Sym3 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym3 a6989586621680091134 a6989586621680091135 a6989586621680091136 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym3 a6989586621680091134 a6989586621680091135 a6989586621680091136 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621680091137 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym3 a6989586621680091134 a6989586621680091135 a6989586621680091136 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621680091137 :: [c]) = ZipWith7Sym4 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 |
data ZipWith7Sym4 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym4 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym4 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621680091138 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym4 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621680091138 :: [d]) = ZipWith7Sym5 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 |
data ZipWith7Sym5 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym5 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym5 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621680091139 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym5 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621680091139 :: [e]) = ZipWith7Sym6 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 |
data ZipWith7Sym6 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym6 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 :: TyFun [f] ([g] ~> [h]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym6 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621680091140 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym6 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621680091140 :: [f]) = ZipWith7Sym7 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 |
data ZipWith7Sym7 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 a6989586621680091141 Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym7 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 :: TyFun [g] [h] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym7 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 :: TyFun [g] [h] -> Type) (a6989586621680091141 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym7 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 :: TyFun [g] [h] -> Type) (a6989586621680091141 :: [g]) = ZipWith7Sym8 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 a6989586621680091141 |
type ZipWith7Sym8 (a6989586621680091134 :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a6989586621680091135 :: [a]) (a6989586621680091136 :: [b]) (a6989586621680091137 :: [c]) (a6989586621680091138 :: [d]) (a6989586621680091139 :: [e]) (a6989586621680091140 :: [f]) (a6989586621680091141 :: [g]) = ZipWith7 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 a6989586621680091141 :: [h] Source #
data UnzipSym0 a6989586621679969527 Source #
Instances
SingI (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # | |
SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679969527 :: [(a, b)]) Source # | |
type UnzipSym1 (a6989586621679969527 :: [(a, b)]) = Unzip a6989586621679969527 :: ([a], [b]) Source #
data Unzip3Sym0 a6989586621679969509 Source #
Instances
SingI (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Unzip3Sym0 Source # | |
SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679969509 :: [(a, b, c)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679969509 :: [(a, b, c)]) = Unzip3Sym1 a6989586621679969509 |
type Unzip3Sym1 (a6989586621679969509 :: [(a, b, c)]) = Unzip3 a6989586621679969509 :: ([a], [b], [c]) Source #
data Unzip4Sym0 a6989586621679969489 Source #
Instances
SingI (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Unzip4Sym0 Source # | |
SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679969489 :: [(a, b, c, d)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679969489 :: [(a, b, c, d)]) = Unzip4Sym1 a6989586621679969489 |
type Unzip4Sym1 (a6989586621679969489 :: [(a, b, c, d)]) = Unzip4 a6989586621679969489 :: ([a], [b], [c], [d]) Source #
data Unzip5Sym0 a6989586621679969467 Source #
Instances
SingI (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Unzip5Sym0 Source # | |
SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679969467 :: [(a, b, c, d, e)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679969467 :: [(a, b, c, d, e)]) = Unzip5Sym1 a6989586621679969467 |
type Unzip5Sym1 (a6989586621679969467 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679969467 :: ([a], [b], [c], [d], [e]) Source #
data Unzip6Sym0 a6989586621679969443 Source #
Instances
SingI (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Unzip6Sym0 Source # | |
SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679969443 :: [(a, b, c, d, e, f)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679969443 :: [(a, b, c, d, e, f)]) = Unzip6Sym1 a6989586621679969443 |
type Unzip6Sym1 (a6989586621679969443 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679969443 :: ([a], [b], [c], [d], [e], [f]) Source #
data Unzip7Sym0 a6989586621679969417 Source #
Instances
SingI (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Unzip7Sym0 Source # | |
SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679969417 :: [(a, b, c, d, e, f, g)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679969417 :: [(a, b, c, d, e, f, g)]) = Unzip7Sym1 a6989586621679969417 |
type Unzip7Sym1 (a6989586621679969417 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679969417 :: ([a], [b], [c], [d], [e], [f], [g]) Source #
data UnlinesSym0 a6989586621679969412 Source #
Instances
SingI UnlinesSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing UnlinesSym0 Source # | |
SuppressUnusedWarnings UnlinesSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply UnlinesSym0 (a6989586621679969412 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnlinesSym1 (a6989586621679969412 :: [Symbol]) = Unlines a6989586621679969412 :: Symbol Source #
data UnwordsSym0 a6989586621679969402 Source #
Instances
SingI UnwordsSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing UnwordsSym0 Source # | |
SuppressUnusedWarnings UnwordsSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply UnwordsSym0 (a6989586621679969402 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnwordsSym1 (a6989586621679969402 :: [Symbol]) = Unwords a6989586621679969402 :: Symbol Source #
data NubSym0 a6989586621679968858 Source #
Instances
data DeleteSym0 a6989586621679969396 Source #
Instances
SEq a => SingI (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing DeleteSym0 Source # | |
SuppressUnusedWarnings (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969396 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969396 :: a) = DeleteSym1 a6989586621679969396 |
data DeleteSym1 a6989586621679969396 a6989586621679969397 Source #
Instances
(SEq a, SingI d) => SingI (DeleteSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DeleteSym1 d) Source # | |
SuppressUnusedWarnings (DeleteSym1 a6989586621679969396 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym1 a6989586621679969396 :: TyFun [a] [a] -> Type) (a6989586621679969397 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym1 a6989586621679969396 :: TyFun [a] [a] -> Type) (a6989586621679969397 :: [a]) = DeleteSym2 a6989586621679969396 a6989586621679969397 |
type DeleteSym2 (a6989586621679969396 :: a) (a6989586621679969397 :: [a]) = Delete a6989586621679969396 a6989586621679969397 :: [a] Source #
data (\\@#@$) a6989586621679969385 infix 5 Source #
Instances
SEq a => SingI ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969385 :: [a]) Source # | |
data a6989586621679969385 \\@#@$$ a6989586621679969386 infix 5 Source #
Instances
(SEq a, SingI d) => SingI ((\\@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((\\@#@$$) a6989586621679969385 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$$) a6989586621679969385 :: TyFun [a] [a] -> Type) (a6989586621679969386 :: [a]) Source # | |
type (\\@#@$$$) (a6989586621679969385 :: [a]) (a6989586621679969386 :: [a]) = (\\) a6989586621679969385 a6989586621679969386 :: [a] infix 5 Source #
data UnionSym0 a6989586621679968812 Source #
Instances
SEq a => SingI (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679968812 :: [a]) Source # | |
data UnionSym1 a6989586621679968812 a6989586621679968813 Source #
Instances
(SEq a, SingI d) => SingI (UnionSym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (UnionSym1 a6989586621679968812 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym1 a6989586621679968812 :: TyFun [a] [a] -> Type) (a6989586621679968813 :: [a]) Source # | |
type UnionSym2 (a6989586621679968812 :: [a]) (a6989586621679968813 :: [a]) = Union a6989586621679968812 a6989586621679968813 :: [a] Source #
data IntersectSym0 a6989586621679969203 Source #
Instances
SEq a => SingI (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing IntersectSym0 Source # | |
SuppressUnusedWarnings (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969203 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969203 :: [a]) = IntersectSym1 a6989586621679969203 |
data IntersectSym1 a6989586621679969203 a6989586621679969204 Source #
Instances
(SEq a, SingI d) => SingI (IntersectSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IntersectSym1 d) Source # | |
SuppressUnusedWarnings (IntersectSym1 a6989586621679969203 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym1 a6989586621679969203 :: TyFun [a] [a] -> Type) (a6989586621679969204 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym1 a6989586621679969203 :: TyFun [a] [a] -> Type) (a6989586621679969204 :: [a]) = IntersectSym2 a6989586621679969203 a6989586621679969204 |
type IntersectSym2 (a6989586621679969203 :: [a]) (a6989586621679969204 :: [a]) = Intersect a6989586621679969203 a6989586621679969204 :: [a] Source #
data InsertSym0 a6989586621679969005 Source #
Instances
SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing InsertSym0 Source # | |
SuppressUnusedWarnings (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969005 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969005 :: a) = InsertSym1 a6989586621679969005 |
data InsertSym1 a6989586621679969005 a6989586621679969006 Source #
Instances
(SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (InsertSym1 d) Source # | |
SuppressUnusedWarnings (InsertSym1 a6989586621679969005 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym1 a6989586621679969005 :: TyFun [a] [a] -> Type) (a6989586621679969006 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym1 a6989586621679969005 :: TyFun [a] [a] -> Type) (a6989586621679969006 :: [a]) = InsertSym2 a6989586621679969005 a6989586621679969006 |
type InsertSym2 (a6989586621679969005 :: a) (a6989586621679969006 :: [a]) = Insert a6989586621679969005 a6989586621679969006 :: [a] Source #
data SortSym0 a6989586621679969000 Source #
Instances
SOrd a => SingI (SortSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (SortSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SortSym0 :: TyFun [a] [a] -> Type) (a6989586621679969000 :: [a]) Source # | |
data NubBySym0 a6989586621679968840 Source #
Instances
SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679968840 :: a ~> (a ~> Bool)) Source # | |
data NubBySym1 a6989586621679968840 a6989586621679968841 Source #
Instances
SingI d => SingI (NubBySym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (NubBySym1 a6989586621679968840 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym1 a6989586621679968840 :: TyFun [a] [a] -> Type) (a6989586621679968841 :: [a]) Source # | |
type NubBySym2 (a6989586621679968840 :: (~>) a ((~>) a Bool)) (a6989586621679968841 :: [a]) = NubBy a6989586621679968840 a6989586621679968841 :: [a] Source #
data DeleteBySym0 a6989586621679969366 Source #
Instances
SingI (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing DeleteBySym0 Source # | |
SuppressUnusedWarnings (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679969366 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data DeleteBySym1 a6989586621679969366 a6989586621679969367 Source #
Instances
SingI d => SingI (DeleteBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DeleteBySym1 d) Source # | |
SuppressUnusedWarnings (DeleteBySym1 a6989586621679969366 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym1 a6989586621679969366 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969367 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym1 a6989586621679969366 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969367 :: a) = DeleteBySym2 a6989586621679969366 a6989586621679969367 |
data DeleteBySym2 a6989586621679969366 a6989586621679969367 a6989586621679969368 Source #
Instances
(SingI d1, SingI d2) => SingI (DeleteBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DeleteBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (DeleteBySym2 a6989586621679969366 a6989586621679969367 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym2 a6989586621679969366 a6989586621679969367 :: TyFun [a] [a] -> Type) (a6989586621679969368 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym2 a6989586621679969366 a6989586621679969367 :: TyFun [a] [a] -> Type) (a6989586621679969368 :: [a]) = DeleteBySym3 a6989586621679969366 a6989586621679969367 a6989586621679969368 |
type DeleteBySym3 (a6989586621679969366 :: (~>) a ((~>) a Bool)) (a6989586621679969367 :: a) (a6989586621679969368 :: [a]) = DeleteBy a6989586621679969366 a6989586621679969367 a6989586621679969368 :: [a] Source #
data DeleteFirstsBySym0 a6989586621679969356 Source #
Instances
SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679969356 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data DeleteFirstsBySym1 a6989586621679969356 a6989586621679969357 Source #
Instances
SingI d => SingI (DeleteFirstsBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DeleteFirstsBySym1 d) Source # | |
SuppressUnusedWarnings (DeleteFirstsBySym1 a6989586621679969356 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym1 a6989586621679969356 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969357 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym1 a6989586621679969356 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969357 :: [a]) = DeleteFirstsBySym2 a6989586621679969356 a6989586621679969357 |
data DeleteFirstsBySym2 a6989586621679969356 a6989586621679969357 a6989586621679969358 Source #
Instances
(SingI d1, SingI d2) => SingI (DeleteFirstsBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DeleteFirstsBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (DeleteFirstsBySym2 a6989586621679969356 a6989586621679969357 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym2 a6989586621679969356 a6989586621679969357 :: TyFun [a] [a] -> Type) (a6989586621679969358 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym2 a6989586621679969356 a6989586621679969357 :: TyFun [a] [a] -> Type) (a6989586621679969358 :: [a]) = DeleteFirstsBySym3 a6989586621679969356 a6989586621679969357 a6989586621679969358 |
type DeleteFirstsBySym3 (a6989586621679969356 :: (~>) a ((~>) a Bool)) (a6989586621679969357 :: [a]) (a6989586621679969358 :: [a]) = DeleteFirstsBy a6989586621679969356 a6989586621679969357 a6989586621679969358 :: [a] Source #
data UnionBySym0 a6989586621679968820 Source #
Instances
SingI (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing UnionBySym0 Source # | |
SuppressUnusedWarnings (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679968820 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data UnionBySym1 a6989586621679968820 a6989586621679968821 Source #
Instances
SingI d => SingI (UnionBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (UnionBySym1 d) Source # | |
SuppressUnusedWarnings (UnionBySym1 a6989586621679968820 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym1 a6989586621679968820 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679968821 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym1 a6989586621679968820 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679968821 :: [a]) = UnionBySym2 a6989586621679968820 a6989586621679968821 |
data UnionBySym2 a6989586621679968820 a6989586621679968821 a6989586621679968822 Source #
Instances
(SingI d1, SingI d2) => SingI (UnionBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (UnionBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (UnionBySym2 a6989586621679968820 a6989586621679968821 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym2 a6989586621679968820 a6989586621679968821 :: TyFun [a] [a] -> Type) (a6989586621679968822 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym2 a6989586621679968820 a6989586621679968821 :: TyFun [a] [a] -> Type) (a6989586621679968822 :: [a]) = UnionBySym3 a6989586621679968820 a6989586621679968821 a6989586621679968822 |
type UnionBySym3 (a6989586621679968820 :: (~>) a ((~>) a Bool)) (a6989586621679968821 :: [a]) (a6989586621679968822 :: [a]) = UnionBy a6989586621679968820 a6989586621679968821 a6989586621679968822 :: [a] Source #
data IntersectBySym0 a6989586621679969181 Source #
Instances
SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679969181 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data IntersectBySym1 a6989586621679969181 a6989586621679969182 Source #
Instances
SingI d => SingI (IntersectBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IntersectBySym1 d) Source # | |
SuppressUnusedWarnings (IntersectBySym1 a6989586621679969181 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym1 a6989586621679969181 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969182 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym1 a6989586621679969181 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969182 :: [a]) = IntersectBySym2 a6989586621679969181 a6989586621679969182 |
data IntersectBySym2 a6989586621679969181 a6989586621679969182 a6989586621679969183 Source #
Instances
(SingI d1, SingI d2) => SingI (IntersectBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IntersectBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (IntersectBySym2 a6989586621679969181 a6989586621679969182 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym2 a6989586621679969181 a6989586621679969182 :: TyFun [a] [a] -> Type) (a6989586621679969183 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym2 a6989586621679969181 a6989586621679969182 :: TyFun [a] [a] -> Type) (a6989586621679969183 :: [a]) = IntersectBySym3 a6989586621679969181 a6989586621679969182 a6989586621679969183 |
type IntersectBySym3 (a6989586621679969181 :: (~>) a ((~>) a Bool)) (a6989586621679969182 :: [a]) (a6989586621679969183 :: [a]) = IntersectBy a6989586621679969181 a6989586621679969182 a6989586621679969183 :: [a] Source #
data GroupBySym0 a6989586621679968973 Source #
Instances
SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing GroupBySym0 Source # | |
SuppressUnusedWarnings (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679968973 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data GroupBySym1 a6989586621679968973 a6989586621679968974 Source #
Instances
SingI d => SingI (GroupBySym1 d :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (GroupBySym1 d) Source # | |
SuppressUnusedWarnings (GroupBySym1 a6989586621679968973 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym1 a6989586621679968973 :: TyFun [a] [[a]] -> Type) (a6989586621679968974 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GroupBySym1 a6989586621679968973 :: TyFun [a] [[a]] -> Type) (a6989586621679968974 :: [a]) = GroupBySym2 a6989586621679968973 a6989586621679968974 |
type GroupBySym2 (a6989586621679968973 :: (~>) a ((~>) a Bool)) (a6989586621679968974 :: [a]) = GroupBy a6989586621679968973 a6989586621679968974 :: [[a]] Source #
data SortBySym0 a6989586621679969344 Source #
Instances
SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing SortBySym0 Source # | |
SuppressUnusedWarnings (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679969344 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data SortBySym1 a6989586621679969344 a6989586621679969345 Source #
Instances
SingI d => SingI (SortBySym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (SortBySym1 d) Source # | |
SuppressUnusedWarnings (SortBySym1 a6989586621679969344 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym1 a6989586621679969344 :: TyFun [a] [a] -> Type) (a6989586621679969345 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SortBySym1 a6989586621679969344 :: TyFun [a] [a] -> Type) (a6989586621679969345 :: [a]) = SortBySym2 a6989586621679969344 a6989586621679969345 |
type SortBySym2 (a6989586621679969344 :: (~>) a ((~>) a Ordering)) (a6989586621679969345 :: [a]) = SortBy a6989586621679969344 a6989586621679969345 :: [a] Source #
data InsertBySym0 a6989586621679969324 Source #
Instances
SingI (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing InsertBySym0 Source # | |
SuppressUnusedWarnings (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679969324 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data InsertBySym1 a6989586621679969324 a6989586621679969325 Source #
Instances
SingI d => SingI (InsertBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (InsertBySym1 d) Source # | |
SuppressUnusedWarnings (InsertBySym1 a6989586621679969324 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym1 a6989586621679969324 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969325 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym1 a6989586621679969324 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969325 :: a) = InsertBySym2 a6989586621679969324 a6989586621679969325 |
data InsertBySym2 a6989586621679969324 a6989586621679969325 a6989586621679969326 Source #
Instances
(SingI d1, SingI d2) => SingI (InsertBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (InsertBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (InsertBySym2 a6989586621679969324 a6989586621679969325 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym2 a6989586621679969324 a6989586621679969325 :: TyFun [a] [a] -> Type) (a6989586621679969326 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym2 a6989586621679969324 a6989586621679969325 :: TyFun [a] [a] -> Type) (a6989586621679969326 :: [a]) = InsertBySym3 a6989586621679969324 a6989586621679969325 a6989586621679969326 |
type InsertBySym3 (a6989586621679969324 :: (~>) a ((~>) a Ordering)) (a6989586621679969325 :: a) (a6989586621679969326 :: [a]) = InsertBy a6989586621679969324 a6989586621679969325 a6989586621679969326 :: [a] Source #
data MaximumBySym0 a6989586621680492273 Source #
Instances
SFoldable t => SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing MaximumBySym0 Source # | |
SuppressUnusedWarnings (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680492273 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data MaximumBySym1 a6989586621680492273 a6989586621680492274 Source #
Instances
(SFoldable t, SingI d) => SingI (MaximumBySym1 d :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (MaximumBySym1 d) Source # | |
SuppressUnusedWarnings (MaximumBySym1 a6989586621680492273 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym1 a6989586621680492273 :: TyFun (t a) a -> Type) (a6989586621680492274 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym1 a6989586621680492273 :: TyFun (t a) a -> Type) (a6989586621680492274 :: t a) = MaximumBySym2 a6989586621680492273 a6989586621680492274 |
type MaximumBySym2 (a6989586621680492273 :: (~>) a ((~>) a Ordering)) (a6989586621680492274 :: t a) = MaximumBy a6989586621680492273 a6989586621680492274 :: a Source #
data MinimumBySym0 a6989586621680492253 Source #
Instances
SFoldable t => SingI (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing MinimumBySym0 Source # | |
SuppressUnusedWarnings (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680492253 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data MinimumBySym1 a6989586621680492253 a6989586621680492254 Source #
Instances
(SFoldable t, SingI d) => SingI (MinimumBySym1 d :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (MinimumBySym1 d) Source # | |
SuppressUnusedWarnings (MinimumBySym1 a6989586621680492253 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym1 a6989586621680492253 :: TyFun (t a) a -> Type) (a6989586621680492254 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym1 a6989586621680492253 :: TyFun (t a) a -> Type) (a6989586621680492254 :: t a) = MinimumBySym2 a6989586621680492253 a6989586621680492254 |
type MinimumBySym2 (a6989586621680492253 :: (~>) a ((~>) a Ordering)) (a6989586621680492254 :: t a) = MinimumBy a6989586621680492253 a6989586621680492254 :: a Source #
data GenericLengthSym0 a6989586621679968803 Source #
Instances
SNum i => SingI (GenericLengthSym0 :: TyFun [a] i -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a] i -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679968803 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679968803 :: [a]) = GenericLengthSym1 a6989586621679968803 :: k2 |
type GenericLengthSym1 (a6989586621679968803 :: [a]) = GenericLength a6989586621679968803 :: i Source #