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 |
Data.Singletons.Prelude.List
Contents
Description
Defines functions and datatypes relating to the singleton for '[]',
including a singletons version of a few of the definitions in Data.List
.
Because many of these definitions are produced by Template Haskell,
it is not possible to create proper Haddock documentation. Please look
up the corresponding operation in Data.List
. Also, please excuse
the apparent repeated variable names. This is due to an interaction
between Template Haskell and Haddock.
Synopsis
- data family Sing :: k -> Type
- type SList = (Sing :: [a] -> Type)
- type family (a :: [a]) ++ (a :: [a]) :: [a] where ...
- (%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a])
- type family Head (a :: [a]) :: a where ...
- sHead :: forall a (t :: [a]). Sing t -> Sing (Apply HeadSym0 t :: a)
- type family Last (a :: [a]) :: a where ...
- sLast :: forall a (t :: [a]). Sing t -> Sing (Apply LastSym0 t :: a)
- type family Tail (a :: [a]) :: [a] where ...
- sTail :: forall a (t :: [a]). Sing t -> Sing (Apply TailSym0 t :: [a])
- type family Init (a :: [a]) :: [a] where ...
- sInit :: forall a (t :: [a]). Sing t -> Sing (Apply InitSym0 t :: [a])
- type family Null (arg :: t a) :: Bool
- sNull :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply NullSym0 t :: Bool)
- type family Length (arg :: t a) :: Nat
- sLength :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply LengthSym0 t :: Nat)
- type family Map (a :: (~>) a b) (a :: [a]) :: [b] where ...
- sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b])
- type family Reverse (a :: [a]) :: [a] where ...
- sReverse :: forall a (t :: [a]). Sing t -> Sing (Apply ReverseSym0 t :: [a])
- type family Intersperse (a :: a) (a :: [a]) :: [a] where ...
- sIntersperse :: forall a (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a])
- type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ...
- sIntercalate :: forall a (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a])
- type family Transpose (a :: [[a]]) :: [[a]] where ...
- sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]])
- type family Subsequences (a :: [a]) :: [[a]] where ...
- sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]])
- type family Permutations (a :: [a]) :: [[a]] where ...
- sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]])
- type family Foldl (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
- sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b)
- type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
- sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b)
- type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
- sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a)
- type family Foldl1' (a :: (~>) a ((~>) a a)) (a :: [a]) :: a where ...
- sFoldl1' :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a)
- type family Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b
- sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b)
- type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
- sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a)
- type family Concat (a :: t [a]) :: [a] where ...
- sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a])
- type family ConcatMap (a :: (~>) a [b]) (a :: t a) :: [b] where ...
- sConcatMap :: forall t a b (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b])
- type family And (a :: t Bool) :: Bool where ...
- sAnd :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool)
- type family Or (a :: t Bool) :: Bool where ...
- sOr :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool)
- type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ...
- sAny :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool)
- type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ...
- sAll :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool)
- type family Sum (arg :: t a) :: a
- sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a)
- type family Product (arg :: t a) :: a
- sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a)
- type family Maximum (arg :: t a) :: a
- sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a)
- type family Minimum (arg :: t a) :: a
- sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a)
- type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: [b] where ...
- sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b])
- type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
- sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a])
- type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: [b] where ...
- sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b])
- type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
- sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a])
- type family MapAccumL (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
- sMapAccumL :: forall t a b c (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (a, t c))
- type family MapAccumR (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
- sMapAccumR :: forall 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 MapAccumRSym0 t) t) t :: (a, t c))
- type family Replicate (a :: Nat) (a :: 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 :: (~>) b (Maybe (a, b))) (a :: b) :: [a] where ...
- sUnfoldr :: forall b a (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a])
- type family Take (a :: Nat) (a :: [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 :: Nat) (a :: [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 :: Nat) (a :: [a]) :: ([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 Bool) (a :: [a]) :: [a] where ...
- sTakeWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a])
- type family DropWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sDropWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a])
- type family DropWhileEnd (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sDropWhileEnd :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a])
- type family Span (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sSpan :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a]))
- type family Break (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sBreak :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a]))
- type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ...
- type family Group (a :: [a]) :: [[a]] where ...
- sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [[a]])
- type family Inits (a :: [a]) :: [[a]] where ...
- sInits :: forall a (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: [[a]])
- type family Tails (a :: [a]) :: [[a]] where ...
- sTails :: forall a (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: [[a]])
- type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsPrefixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool)
- type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsSuffixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool)
- type family IsInfixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsInfixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool)
- type family Elem (arg :: a) (arg :: t a) :: Bool
- sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool)
- type family NotElem (a :: a) (a :: t a) :: Bool where ...
- sNotElem :: forall t a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool)
- type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ...
- sLookup :: forall a b (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b)
- type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ...
- sFind :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a)
- type family Filter (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
- type family Partition (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
- type family (a :: [a]) !! (a :: Nat) :: a where ...
- (%!!) :: forall a (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a)
- type family ElemIndex (a :: a) (a :: [a]) :: Maybe Nat where ...
- sElemIndex :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat)
- type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ...
- sElemIndices :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat])
- type family FindIndex (a :: (~>) a Bool) (a :: [a]) :: Maybe Nat 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 Bool) (a :: [a]) :: [Nat] 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]) (a :: [b]) :: [(a, b)] where ...
- sZip :: forall a b (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)])
- type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ...
- sZip3 :: forall a b c (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)])
- type family Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ...
- type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ...
- type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ...
- type family Zip7 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [(a, b, c, d, e, f, g)] where ...
- type family ZipWith (a :: (~>) a ((~>) b c)) (a :: [a]) (a :: [b]) :: [c] where ...
- sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c])
- type family ZipWith3 (a :: (~>) a ((~>) b ((~>) c d))) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ...
- sZipWith3 :: forall a b c d (t :: (~>) a ((~>) b ((~>) c d))) (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d])
- type family ZipWith4 (a :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ...
- type family ZipWith5 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ...
- type family ZipWith6 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ...
- type family ZipWith7 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ...
- type family Unzip (a :: [(a, b)]) :: ([a], [b]) where ...
- sUnzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b]))
- type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ...
- sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c]))
- type family Unzip4 (a :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
- sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d]))
- type family Unzip5 (a :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ...
- sUnzip5 :: forall a b c d e (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e]))
- type family Unzip6 (a :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ...
- sUnzip6 :: forall a b c d e f (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f]))
- type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
- sUnzip7 :: forall a b c d e f g (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g]))
- type family Unlines (a :: [Symbol]) :: Symbol where ...
- sUnlines :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnlinesSym0 t :: Symbol)
- type family Unwords (a :: [Symbol]) :: Symbol where ...
- sUnwords :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnwordsSym0 t :: Symbol)
- type family Nub (a :: [a]) :: [a] where ...
- sNub :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply NubSym0 t :: [a])
- type family Delete (a :: a) (a :: [a]) :: [a] where ...
- sDelete :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a])
- type family (a :: [a]) \\ (a :: [a]) :: [a] where ...
- (%\\) :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (\\@#@$) t) t :: [a])
- type family Union (a :: [a]) (a :: [a]) :: [a] where ...
- sUnion :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a])
- type family Intersect (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersect :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a])
- type family Insert (a :: a) (a :: [a]) :: [a] where ...
- sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a])
- type family Sort (a :: [a]) :: [a] where ...
- sSort :: forall a (t :: [a]). SOrd a => Sing t -> Sing (Apply SortSym0 t :: [a])
- type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [a] where ...
- sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a])
- type family DeleteBy (a :: (~>) a ((~>) a Bool)) (a :: a) (a :: [a]) :: [a] where ...
- sDeleteBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a])
- type family DeleteFirstsBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sDeleteFirstsBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a])
- type family UnionBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sUnionBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a])
- type family IntersectBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersectBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a])
- type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [[a]] where ...
- sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]])
- type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: [a]) :: [a] where ...
- sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a])
- type family InsertBy (a :: (~>) a ((~>) a Ordering)) (a :: a) (a :: [a]) :: [a] where ...
- sInsertBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a])
- type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
- sMaximumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a)
- type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
- sMinimumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a)
- type family GenericLength (a :: [a]) :: i where ...
- sGenericLength :: forall i a (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i)
- type family GenericTake (a :: i) (a :: [a]) :: [a] where ...
- type family GenericDrop (a :: i) (a :: [a]) :: [a] where ...
- type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ...
- type family GenericIndex (a :: [a]) (a :: i) :: a where ...
- type family GenericReplicate (a :: i) (a :: a) :: [a] where ...
- type NilSym0 = '[]
- data (:@#@$) :: forall (a3530822107858468865 :: Type). (~>) a3530822107858468865 ((~>) [a3530822107858468865] [(a3530822107858468865 :: Type)])
- data (:@#@$$) (t6989586621679301578 :: (a3530822107858468865 :: Type)) :: (~>) [a3530822107858468865] [(a3530822107858468865 :: Type)]
- type (:@#@$$$) (t6989586621679301578 :: a3530822107858468865) (t6989586621679301579 :: [a3530822107858468865]) = (:) t6989586621679301578 t6989586621679301579
- type (++@#@$$$) (a6989586621679521912 :: [a6989586621679521715]) (a6989586621679521913 :: [a6989586621679521715]) = (++) a6989586621679521912 a6989586621679521913
- data (++@#@$$) (a6989586621679521912 :: [a6989586621679521715]) :: (~>) [a6989586621679521715] [a6989586621679521715]
- data (++@#@$) :: forall a6989586621679521715. (~>) [a6989586621679521715] ((~>) [a6989586621679521715] [a6989586621679521715])
- data HeadSym0 :: forall a6989586621679939457. (~>) [a6989586621679939457] a6989586621679939457
- type HeadSym1 (a6989586621679949980 :: [a6989586621679939457]) = Head a6989586621679949980
- data LastSym0 :: forall a6989586621679939456. (~>) [a6989586621679939456] a6989586621679939456
- type LastSym1 (a6989586621679949975 :: [a6989586621679939456]) = Last a6989586621679949975
- data TailSym0 :: forall a6989586621679939455. (~>) [a6989586621679939455] [a6989586621679939455]
- type TailSym1 (a6989586621679949972 :: [a6989586621679939455]) = Tail a6989586621679949972
- data InitSym0 :: forall a6989586621679939454. (~>) [a6989586621679939454] [a6989586621679939454]
- type InitSym1 (a6989586621679949958 :: [a6989586621679939454]) = Init a6989586621679949958
- data NullSym0 :: forall a6989586621680448459 t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448459) Bool
- type NullSym1 (arg6989586621680449107 :: t6989586621680448444 a6989586621680448459) = Null arg6989586621680449107
- data LengthSym0 :: forall a6989586621680448460 t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448460) Nat
- type LengthSym1 (arg6989586621680449109 :: t6989586621680448444 a6989586621680448460) = Length arg6989586621680449109
- data MapSym0 :: forall a6989586621679521716 b6989586621679521717. (~>) ((~>) a6989586621679521716 b6989586621679521717) ((~>) [a6989586621679521716] [b6989586621679521717])
- data MapSym1 (a6989586621679521920 :: (~>) a6989586621679521716 b6989586621679521717) :: (~>) [a6989586621679521716] [b6989586621679521717]
- type MapSym2 (a6989586621679521920 :: (~>) a6989586621679521716 b6989586621679521717) (a6989586621679521921 :: [a6989586621679521716]) = Map a6989586621679521920 a6989586621679521921
- data ReverseSym0 :: forall a6989586621679939452. (~>) [a6989586621679939452] [a6989586621679939452]
- type ReverseSym1 (a6989586621679949911 :: [a6989586621679939452]) = Reverse a6989586621679949911
- data IntersperseSym0 :: forall a6989586621679939451. (~>) a6989586621679939451 ((~>) [a6989586621679939451] [a6989586621679939451])
- data IntersperseSym1 (a6989586621679949898 :: a6989586621679939451) :: (~>) [a6989586621679939451] [a6989586621679939451]
- type IntersperseSym2 (a6989586621679949898 :: a6989586621679939451) (a6989586621679949899 :: [a6989586621679939451]) = Intersperse a6989586621679949898 a6989586621679949899
- data IntercalateSym0 :: forall a6989586621679939450. (~>) [a6989586621679939450] ((~>) [[a6989586621679939450]] [a6989586621679939450])
- data IntercalateSym1 (a6989586621679949905 :: [a6989586621679939450]) :: (~>) [[a6989586621679939450]] [a6989586621679939450]
- type IntercalateSym2 (a6989586621679949905 :: [a6989586621679939450]) (a6989586621679949906 :: [[a6989586621679939450]]) = Intercalate a6989586621679949905 a6989586621679949906
- data TransposeSym0 :: forall a6989586621679939337. (~>) [[a6989586621679939337]] [[a6989586621679939337]]
- type TransposeSym1 (a6989586621679949983 :: [[a6989586621679939337]]) = Transpose a6989586621679949983
- data SubsequencesSym0 :: forall a6989586621679939449. (~>) [a6989586621679939449] [[a6989586621679939449]]
- type SubsequencesSym1 (a6989586621679949895 :: [a6989586621679939449]) = Subsequences a6989586621679949895
- data PermutationsSym0 :: forall a6989586621679939446. (~>) [a6989586621679939446] [[a6989586621679939446]]
- type PermutationsSym1 (a6989586621679949777 :: [a6989586621679939446]) = Permutations a6989586621679949777
- data FoldlSym0 :: forall a6989586621680448453 b6989586621680448452 t6989586621680448444. (~>) ((~>) b6989586621680448452 ((~>) a6989586621680448453 b6989586621680448452)) ((~>) b6989586621680448452 ((~>) (t6989586621680448444 a6989586621680448453) b6989586621680448452))
- data FoldlSym1 (arg6989586621680449085 :: (~>) b6989586621680448452 ((~>) a6989586621680448453 b6989586621680448452)) :: forall t6989586621680448444. (~>) b6989586621680448452 ((~>) (t6989586621680448444 a6989586621680448453) b6989586621680448452)
- data FoldlSym2 (arg6989586621680449085 :: (~>) b6989586621680448452 ((~>) a6989586621680448453 b6989586621680448452)) (arg6989586621680449086 :: b6989586621680448452) :: forall t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448453) b6989586621680448452
- type FoldlSym3 (arg6989586621680449085 :: (~>) b6989586621680448452 ((~>) a6989586621680448453 b6989586621680448452)) (arg6989586621680449086 :: b6989586621680448452) (arg6989586621680449087 :: t6989586621680448444 a6989586621680448453) = Foldl arg6989586621680449085 arg6989586621680449086 arg6989586621680449087
- data Foldl'Sym0 :: forall a6989586621680448455 b6989586621680448454 t6989586621680448444. (~>) ((~>) b6989586621680448454 ((~>) a6989586621680448455 b6989586621680448454)) ((~>) b6989586621680448454 ((~>) (t6989586621680448444 a6989586621680448455) b6989586621680448454))
- data Foldl'Sym1 (arg6989586621680449091 :: (~>) b6989586621680448454 ((~>) a6989586621680448455 b6989586621680448454)) :: forall t6989586621680448444. (~>) b6989586621680448454 ((~>) (t6989586621680448444 a6989586621680448455) b6989586621680448454)
- data Foldl'Sym2 (arg6989586621680449091 :: (~>) b6989586621680448454 ((~>) a6989586621680448455 b6989586621680448454)) (arg6989586621680449092 :: b6989586621680448454) :: forall t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448455) b6989586621680448454
- type Foldl'Sym3 (arg6989586621680449091 :: (~>) b6989586621680448454 ((~>) a6989586621680448455 b6989586621680448454)) (arg6989586621680449092 :: b6989586621680448454) (arg6989586621680449093 :: t6989586621680448444 a6989586621680448455) = Foldl' arg6989586621680449091 arg6989586621680449092 arg6989586621680449093
- data Foldl1Sym0 :: forall a6989586621680448457 t6989586621680448444. (~>) ((~>) a6989586621680448457 ((~>) a6989586621680448457 a6989586621680448457)) ((~>) (t6989586621680448444 a6989586621680448457) a6989586621680448457)
- data Foldl1Sym1 (arg6989586621680449101 :: (~>) a6989586621680448457 ((~>) a6989586621680448457 a6989586621680448457)) :: forall t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448457) a6989586621680448457
- type Foldl1Sym2 (arg6989586621680449101 :: (~>) a6989586621680448457 ((~>) a6989586621680448457 a6989586621680448457)) (arg6989586621680449102 :: t6989586621680448444 a6989586621680448457) = Foldl1 arg6989586621680449101 arg6989586621680449102
- data Foldl1'Sym0 :: forall a6989586621679939442. (~>) ((~>) a6989586621679939442 ((~>) a6989586621679939442 a6989586621679939442)) ((~>) [a6989586621679939442] a6989586621679939442)
- data Foldl1'Sym1 (a6989586621679949770 :: (~>) a6989586621679939442 ((~>) a6989586621679939442 a6989586621679939442)) :: (~>) [a6989586621679939442] a6989586621679939442
- type Foldl1'Sym2 (a6989586621679949770 :: (~>) a6989586621679939442 ((~>) a6989586621679939442 a6989586621679939442)) (a6989586621679949771 :: [a6989586621679939442]) = Foldl1' a6989586621679949770 a6989586621679949771
- data FoldrSym0 :: forall a6989586621680448448 b6989586621680448449 t6989586621680448444. (~>) ((~>) a6989586621680448448 ((~>) b6989586621680448449 b6989586621680448449)) ((~>) b6989586621680448449 ((~>) (t6989586621680448444 a6989586621680448448) b6989586621680448449))
- data FoldrSym1 (arg6989586621680449073 :: (~>) a6989586621680448448 ((~>) b6989586621680448449 b6989586621680448449)) :: forall t6989586621680448444. (~>) b6989586621680448449 ((~>) (t6989586621680448444 a6989586621680448448) b6989586621680448449)
- data FoldrSym2 (arg6989586621680449073 :: (~>) a6989586621680448448 ((~>) b6989586621680448449 b6989586621680448449)) (arg6989586621680449074 :: b6989586621680448449) :: forall t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448448) b6989586621680448449
- type FoldrSym3 (arg6989586621680449073 :: (~>) a6989586621680448448 ((~>) b6989586621680448449 b6989586621680448449)) (arg6989586621680449074 :: b6989586621680448449) (arg6989586621680449075 :: t6989586621680448444 a6989586621680448448) = Foldr arg6989586621680449073 arg6989586621680449074 arg6989586621680449075
- data Foldr1Sym0 :: forall a6989586621680448456 t6989586621680448444. (~>) ((~>) a6989586621680448456 ((~>) a6989586621680448456 a6989586621680448456)) ((~>) (t6989586621680448444 a6989586621680448456) a6989586621680448456)
- data Foldr1Sym1 (arg6989586621680449097 :: (~>) a6989586621680448456 ((~>) a6989586621680448456 a6989586621680448456)) :: forall t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448456) a6989586621680448456
- type Foldr1Sym2 (arg6989586621680449097 :: (~>) a6989586621680448456 ((~>) a6989586621680448456 a6989586621680448456)) (arg6989586621680449098 :: t6989586621680448444 a6989586621680448456) = Foldr1 arg6989586621680449097 arg6989586621680449098
- data ConcatSym0 :: forall a6989586621680448370 t6989586621680448369. (~>) (t6989586621680448369 [a6989586621680448370]) [a6989586621680448370]
- type ConcatSym1 (a6989586621680448955 :: t6989586621680448369 [a6989586621680448370]) = Concat a6989586621680448955
- data ConcatMapSym0 :: forall a6989586621680448367 b6989586621680448368 t6989586621680448366. (~>) ((~>) a6989586621680448367 [b6989586621680448368]) ((~>) (t6989586621680448366 a6989586621680448367) [b6989586621680448368])
- data ConcatMapSym1 (a6989586621680448939 :: (~>) a6989586621680448367 [b6989586621680448368]) :: forall t6989586621680448366. (~>) (t6989586621680448366 a6989586621680448367) [b6989586621680448368]
- type ConcatMapSym2 (a6989586621680448939 :: (~>) a6989586621680448367 [b6989586621680448368]) (a6989586621680448940 :: t6989586621680448366 a6989586621680448367) = ConcatMap a6989586621680448939 a6989586621680448940
- data AndSym0 :: forall t6989586621680448365. (~>) (t6989586621680448365 Bool) Bool
- type AndSym1 (a6989586621680448930 :: t6989586621680448365 Bool) = And a6989586621680448930
- data OrSym0 :: forall t6989586621680448364. (~>) (t6989586621680448364 Bool) Bool
- type OrSym1 (a6989586621680448921 :: t6989586621680448364 Bool) = Or a6989586621680448921
- data AnySym0 :: forall a6989586621680448363 t6989586621680448362. (~>) ((~>) a6989586621680448363 Bool) ((~>) (t6989586621680448362 a6989586621680448363) Bool)
- data AnySym1 (a6989586621680448908 :: (~>) a6989586621680448363 Bool) :: forall t6989586621680448362. (~>) (t6989586621680448362 a6989586621680448363) Bool
- type AnySym2 (a6989586621680448908 :: (~>) a6989586621680448363 Bool) (a6989586621680448909 :: t6989586621680448362 a6989586621680448363) = Any a6989586621680448908 a6989586621680448909
- data AllSym0 :: forall a6989586621680448361 t6989586621680448360. (~>) ((~>) a6989586621680448361 Bool) ((~>) (t6989586621680448360 a6989586621680448361) Bool)
- data AllSym1 (a6989586621680448895 :: (~>) a6989586621680448361 Bool) :: forall t6989586621680448360. (~>) (t6989586621680448360 a6989586621680448361) Bool
- type AllSym2 (a6989586621680448895 :: (~>) a6989586621680448361 Bool) (a6989586621680448896 :: t6989586621680448360 a6989586621680448361) = All a6989586621680448895 a6989586621680448896
- data SumSym0 :: forall a6989586621680448464 t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448464) a6989586621680448464
- type SumSym1 (arg6989586621680449119 :: t6989586621680448444 a6989586621680448464) = Sum arg6989586621680449119
- data ProductSym0 :: forall a6989586621680448465 t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448465) a6989586621680448465
- type ProductSym1 (arg6989586621680449121 :: t6989586621680448444 a6989586621680448465) = Product arg6989586621680449121
- data MaximumSym0 :: forall a6989586621680448462 t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448462) a6989586621680448462
- type MaximumSym1 (arg6989586621680449115 :: t6989586621680448444 a6989586621680448462) = Maximum arg6989586621680449115
- data MinimumSym0 :: forall a6989586621680448463 t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448463) a6989586621680448463
- type MinimumSym1 (arg6989586621680449117 :: t6989586621680448444 a6989586621680448463) = Minimum arg6989586621680449117
- data ScanlSym0 :: forall a6989586621679939435 b6989586621679939434. (~>) ((~>) b6989586621679939434 ((~>) a6989586621679939435 b6989586621679939434)) ((~>) b6989586621679939434 ((~>) [a6989586621679939435] [b6989586621679939434]))
- data ScanlSym1 (a6989586621679949543 :: (~>) b6989586621679939434 ((~>) a6989586621679939435 b6989586621679939434)) :: (~>) b6989586621679939434 ((~>) [a6989586621679939435] [b6989586621679939434])
- data ScanlSym2 (a6989586621679949543 :: (~>) b6989586621679939434 ((~>) a6989586621679939435 b6989586621679939434)) (a6989586621679949544 :: b6989586621679939434) :: (~>) [a6989586621679939435] [b6989586621679939434]
- type ScanlSym3 (a6989586621679949543 :: (~>) b6989586621679939434 ((~>) a6989586621679939435 b6989586621679939434)) (a6989586621679949544 :: b6989586621679939434) (a6989586621679949545 :: [a6989586621679939435]) = Scanl a6989586621679949543 a6989586621679949544 a6989586621679949545
- data Scanl1Sym0 :: forall a6989586621679939433. (~>) ((~>) a6989586621679939433 ((~>) a6989586621679939433 a6989586621679939433)) ((~>) [a6989586621679939433] [a6989586621679939433])
- data Scanl1Sym1 (a6989586621679949557 :: (~>) a6989586621679939433 ((~>) a6989586621679939433 a6989586621679939433)) :: (~>) [a6989586621679939433] [a6989586621679939433]
- type Scanl1Sym2 (a6989586621679949557 :: (~>) a6989586621679939433 ((~>) a6989586621679939433 a6989586621679939433)) (a6989586621679949558 :: [a6989586621679939433]) = Scanl1 a6989586621679949557 a6989586621679949558
- data ScanrSym0 :: forall a6989586621679939431 b6989586621679939432. (~>) ((~>) a6989586621679939431 ((~>) b6989586621679939432 b6989586621679939432)) ((~>) b6989586621679939432 ((~>) [a6989586621679939431] [b6989586621679939432]))
- data ScanrSym1 (a6989586621679949522 :: (~>) a6989586621679939431 ((~>) b6989586621679939432 b6989586621679939432)) :: (~>) b6989586621679939432 ((~>) [a6989586621679939431] [b6989586621679939432])
- data ScanrSym2 (a6989586621679949522 :: (~>) a6989586621679939431 ((~>) b6989586621679939432 b6989586621679939432)) (a6989586621679949523 :: b6989586621679939432) :: (~>) [a6989586621679939431] [b6989586621679939432]
- type ScanrSym3 (a6989586621679949522 :: (~>) a6989586621679939431 ((~>) b6989586621679939432 b6989586621679939432)) (a6989586621679949523 :: b6989586621679939432) (a6989586621679949524 :: [a6989586621679939431]) = Scanr a6989586621679949522 a6989586621679949523 a6989586621679949524
- data Scanr1Sym0 :: forall a6989586621679939430. (~>) ((~>) a6989586621679939430 ((~>) a6989586621679939430 a6989586621679939430)) ((~>) [a6989586621679939430] [a6989586621679939430])
- data Scanr1Sym1 (a6989586621679949498 :: (~>) a6989586621679939430 ((~>) a6989586621679939430 a6989586621679939430)) :: (~>) [a6989586621679939430] [a6989586621679939430]
- type Scanr1Sym2 (a6989586621679949498 :: (~>) a6989586621679939430 ((~>) a6989586621679939430 a6989586621679939430)) (a6989586621679949499 :: [a6989586621679939430]) = Scanr1 a6989586621679949498 a6989586621679949499
- data MapAccumLSym0 :: forall a6989586621680750463 b6989586621680750464 c6989586621680750465 t6989586621680750462. (~>) ((~>) a6989586621680750463 ((~>) b6989586621680750464 (a6989586621680750463, c6989586621680750465))) ((~>) a6989586621680750463 ((~>) (t6989586621680750462 b6989586621680750464) (a6989586621680750463, t6989586621680750462 c6989586621680750465)))
- data MapAccumLSym1 (a6989586621680751002 :: (~>) a6989586621680750463 ((~>) b6989586621680750464 (a6989586621680750463, c6989586621680750465))) :: forall t6989586621680750462. (~>) a6989586621680750463 ((~>) (t6989586621680750462 b6989586621680750464) (a6989586621680750463, t6989586621680750462 c6989586621680750465))
- data MapAccumLSym2 (a6989586621680751002 :: (~>) a6989586621680750463 ((~>) b6989586621680750464 (a6989586621680750463, c6989586621680750465))) (a6989586621680751003 :: a6989586621680750463) :: forall t6989586621680750462. (~>) (t6989586621680750462 b6989586621680750464) (a6989586621680750463, t6989586621680750462 c6989586621680750465)
- type MapAccumLSym3 (a6989586621680751002 :: (~>) a6989586621680750463 ((~>) b6989586621680750464 (a6989586621680750463, c6989586621680750465))) (a6989586621680751003 :: a6989586621680750463) (a6989586621680751004 :: t6989586621680750462 b6989586621680750464) = MapAccumL a6989586621680751002 a6989586621680751003 a6989586621680751004
- data MapAccumRSym0 :: forall a6989586621680750459 b6989586621680750460 c6989586621680750461 t6989586621680750458. (~>) ((~>) a6989586621680750459 ((~>) b6989586621680750460 (a6989586621680750459, c6989586621680750461))) ((~>) a6989586621680750459 ((~>) (t6989586621680750458 b6989586621680750460) (a6989586621680750459, t6989586621680750458 c6989586621680750461)))
- data MapAccumRSym1 (a6989586621680750985 :: (~>) a6989586621680750459 ((~>) b6989586621680750460 (a6989586621680750459, c6989586621680750461))) :: forall t6989586621680750458. (~>) a6989586621680750459 ((~>) (t6989586621680750458 b6989586621680750460) (a6989586621680750459, t6989586621680750458 c6989586621680750461))
- data MapAccumRSym2 (a6989586621680750985 :: (~>) a6989586621680750459 ((~>) b6989586621680750460 (a6989586621680750459, c6989586621680750461))) (a6989586621680750986 :: a6989586621680750459) :: forall t6989586621680750458. (~>) (t6989586621680750458 b6989586621680750460) (a6989586621680750459, t6989586621680750458 c6989586621680750461)
- type MapAccumRSym3 (a6989586621680750985 :: (~>) a6989586621680750459 ((~>) b6989586621680750460 (a6989586621680750459, c6989586621680750461))) (a6989586621680750986 :: a6989586621680750459) (a6989586621680750987 :: t6989586621680750458 b6989586621680750460) = MapAccumR a6989586621680750985 a6989586621680750986 a6989586621680750987
- data ReplicateSym0 :: forall a6989586621679939338. (~>) Nat ((~>) a6989586621679939338 [a6989586621679939338])
- data ReplicateSym1 (a6989586621679948640 :: Nat) :: forall a6989586621679939338. (~>) a6989586621679939338 [a6989586621679939338]
- type ReplicateSym2 (a6989586621679948640 :: Nat) (a6989586621679948641 :: a6989586621679939338) = Replicate a6989586621679948640 a6989586621679948641
- data UnfoldrSym0 :: forall a6989586621679939423 b6989586621679939422. (~>) ((~>) b6989586621679939422 (Maybe (a6989586621679939423, b6989586621679939422))) ((~>) b6989586621679939422 [a6989586621679939423])
- data UnfoldrSym1 (a6989586621679949356 :: (~>) b6989586621679939422 (Maybe (a6989586621679939423, b6989586621679939422))) :: (~>) b6989586621679939422 [a6989586621679939423]
- type UnfoldrSym2 (a6989586621679949356 :: (~>) b6989586621679939422 (Maybe (a6989586621679939423, b6989586621679939422))) (a6989586621679949357 :: b6989586621679939422) = Unfoldr a6989586621679949356 a6989586621679949357
- data TakeSym0 :: forall a6989586621679939354. (~>) Nat ((~>) [a6989586621679939354] [a6989586621679939354])
- data TakeSym1 (a6989586621679948736 :: Nat) :: forall a6989586621679939354. (~>) [a6989586621679939354] [a6989586621679939354]
- type TakeSym2 (a6989586621679948736 :: Nat) (a6989586621679948737 :: [a6989586621679939354]) = Take a6989586621679948736 a6989586621679948737
- data DropSym0 :: forall a6989586621679939353. (~>) Nat ((~>) [a6989586621679939353] [a6989586621679939353])
- data DropSym1 (a6989586621679948722 :: Nat) :: forall a6989586621679939353. (~>) [a6989586621679939353] [a6989586621679939353]
- type DropSym2 (a6989586621679948722 :: Nat) (a6989586621679948723 :: [a6989586621679939353]) = Drop a6989586621679948722 a6989586621679948723
- data SplitAtSym0 :: forall a6989586621679939352. (~>) Nat ((~>) [a6989586621679939352] ([a6989586621679939352], [a6989586621679939352]))
- data SplitAtSym1 (a6989586621679948750 :: Nat) :: forall a6989586621679939352. (~>) [a6989586621679939352] ([a6989586621679939352], [a6989586621679939352])
- type SplitAtSym2 (a6989586621679948750 :: Nat) (a6989586621679948751 :: [a6989586621679939352]) = SplitAt a6989586621679948750 a6989586621679948751
- data TakeWhileSym0 :: forall a6989586621679939359. (~>) ((~>) a6989586621679939359 Bool) ((~>) [a6989586621679939359] [a6989586621679939359])
- data TakeWhileSym1 (a6989586621679948894 :: (~>) a6989586621679939359 Bool) :: (~>) [a6989586621679939359] [a6989586621679939359]
- type TakeWhileSym2 (a6989586621679948894 :: (~>) a6989586621679939359 Bool) (a6989586621679948895 :: [a6989586621679939359]) = TakeWhile a6989586621679948894 a6989586621679948895
- data DropWhileSym0 :: forall a6989586621679939358. (~>) ((~>) a6989586621679939358 Bool) ((~>) [a6989586621679939358] [a6989586621679939358])
- data DropWhileSym1 (a6989586621679948876 :: (~>) a6989586621679939358 Bool) :: (~>) [a6989586621679939358] [a6989586621679939358]
- type DropWhileSym2 (a6989586621679948876 :: (~>) a6989586621679939358 Bool) (a6989586621679948877 :: [a6989586621679939358]) = DropWhile a6989586621679948876 a6989586621679948877
- data DropWhileEndSym0 :: forall a6989586621679939357. (~>) ((~>) a6989586621679939357 Bool) ((~>) [a6989586621679939357] [a6989586621679939357])
- data DropWhileEndSym1 (a6989586621679949932 :: (~>) a6989586621679939357 Bool) :: (~>) [a6989586621679939357] [a6989586621679939357]
- type DropWhileEndSym2 (a6989586621679949932 :: (~>) a6989586621679939357 Bool) (a6989586621679949933 :: [a6989586621679939357]) = DropWhileEnd a6989586621679949932 a6989586621679949933
- data SpanSym0 :: forall a6989586621679939356. (~>) ((~>) a6989586621679939356 Bool) ((~>) [a6989586621679939356] ([a6989586621679939356], [a6989586621679939356]))
- data SpanSym1 (a6989586621679948799 :: (~>) a6989586621679939356 Bool) :: (~>) [a6989586621679939356] ([a6989586621679939356], [a6989586621679939356])
- type SpanSym2 (a6989586621679948799 :: (~>) a6989586621679939356 Bool) (a6989586621679948800 :: [a6989586621679939356]) = Span a6989586621679948799 a6989586621679948800
- data BreakSym0 :: forall a6989586621679939355. (~>) ((~>) a6989586621679939355 Bool) ((~>) [a6989586621679939355] ([a6989586621679939355], [a6989586621679939355]))
- data BreakSym1 (a6989586621679948756 :: (~>) a6989586621679939355 Bool) :: (~>) [a6989586621679939355] ([a6989586621679939355], [a6989586621679939355])
- type BreakSym2 (a6989586621679948756 :: (~>) a6989586621679939355 Bool) (a6989586621679948757 :: [a6989586621679939355]) = Break a6989586621679948756 a6989586621679948757
- data StripPrefixSym0 :: forall a6989586621680065581. (~>) [a6989586621680065581] ((~>) [a6989586621680065581] (Maybe [a6989586621680065581]))
- data StripPrefixSym1 (a6989586621680078291 :: [a6989586621680065581]) :: (~>) [a6989586621680065581] (Maybe [a6989586621680065581])
- type StripPrefixSym2 (a6989586621680078291 :: [a6989586621680065581]) (a6989586621680078292 :: [a6989586621680065581]) = StripPrefix a6989586621680078291 a6989586621680078292
- data GroupSym0 :: forall a6989586621679939351. (~>) [a6989586621679939351] [[a6989586621679939351]]
- type GroupSym1 (a6989586621679948873 :: [a6989586621679939351]) = Group a6989586621679948873
- data InitsSym0 :: forall a6989586621679939421. (~>) [a6989586621679939421] [[a6989586621679939421]]
- type InitsSym1 (a6989586621679949348 :: [a6989586621679939421]) = Inits a6989586621679949348
- data TailsSym0 :: forall a6989586621679939420. (~>) [a6989586621679939420] [[a6989586621679939420]]
- type TailsSym1 (a6989586621679949341 :: [a6989586621679939420]) = Tails a6989586621679949341
- data IsPrefixOfSym0 :: forall a6989586621679939419. (~>) [a6989586621679939419] ((~>) [a6989586621679939419] Bool)
- data IsPrefixOfSym1 (a6989586621679949333 :: [a6989586621679939419]) :: (~>) [a6989586621679939419] Bool
- type IsPrefixOfSym2 (a6989586621679949333 :: [a6989586621679939419]) (a6989586621679949334 :: [a6989586621679939419]) = IsPrefixOf a6989586621679949333 a6989586621679949334
- data IsSuffixOfSym0 :: forall a6989586621679939418. (~>) [a6989586621679939418] ((~>) [a6989586621679939418] Bool)
- data IsSuffixOfSym1 (a6989586621679949924 :: [a6989586621679939418]) :: (~>) [a6989586621679939418] Bool
- type IsSuffixOfSym2 (a6989586621679949924 :: [a6989586621679939418]) (a6989586621679949925 :: [a6989586621679939418]) = IsSuffixOf a6989586621679949924 a6989586621679949925
- data IsInfixOfSym0 :: forall a6989586621679939417. (~>) [a6989586621679939417] ((~>) [a6989586621679939417] Bool)
- data IsInfixOfSym1 (a6989586621679949571 :: [a6989586621679939417]) :: (~>) [a6989586621679939417] Bool
- type IsInfixOfSym2 (a6989586621679949571 :: [a6989586621679939417]) (a6989586621679949572 :: [a6989586621679939417]) = IsInfixOf a6989586621679949571 a6989586621679949572
- data ElemSym0 :: forall a6989586621680448461 t6989586621680448444. (~>) a6989586621680448461 ((~>) (t6989586621680448444 a6989586621680448461) Bool)
- data ElemSym1 (arg6989586621680449111 :: a6989586621680448461) :: forall t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448461) Bool
- type ElemSym2 (arg6989586621680449111 :: a6989586621680448461) (arg6989586621680449112 :: t6989586621680448444 a6989586621680448461) = Elem arg6989586621680449111 arg6989586621680449112
- data NotElemSym0 :: forall a6989586621680448355 t6989586621680448354. (~>) a6989586621680448355 ((~>) (t6989586621680448354 a6989586621680448355) Bool)
- data NotElemSym1 (a6989586621680448837 :: a6989586621680448355) :: forall t6989586621680448354. (~>) (t6989586621680448354 a6989586621680448355) Bool
- type NotElemSym2 (a6989586621680448837 :: a6989586621680448355) (a6989586621680448838 :: t6989586621680448354 a6989586621680448355) = NotElem a6989586621680448837 a6989586621680448838
- data LookupSym0 :: forall a6989586621679939344 b6989586621679939345. (~>) a6989586621679939344 ((~>) [(a6989586621679939344, b6989586621679939345)] (Maybe b6989586621679939345))
- data LookupSym1 (a6989586621679948705 :: a6989586621679939344) :: forall b6989586621679939345. (~>) [(a6989586621679939344, b6989586621679939345)] (Maybe b6989586621679939345)
- type LookupSym2 (a6989586621679948705 :: a6989586621679939344) (a6989586621679948706 :: [(a6989586621679939344, b6989586621679939345)]) = Lookup a6989586621679948705 a6989586621679948706
- data FindSym0 :: forall a6989586621680448353 t6989586621680448352. (~>) ((~>) a6989586621680448353 Bool) ((~>) (t6989586621680448352 a6989586621680448353) (Maybe a6989586621680448353))
- data FindSym1 (a6989586621680448810 :: (~>) a6989586621680448353 Bool) :: forall t6989586621680448352. (~>) (t6989586621680448352 a6989586621680448353) (Maybe a6989586621680448353)
- type FindSym2 (a6989586621680448810 :: (~>) a6989586621680448353 Bool) (a6989586621680448811 :: t6989586621680448352 a6989586621680448353) = Find a6989586621680448810 a6989586621680448811
- data FilterSym0 :: forall a6989586621679939367. (~>) ((~>) a6989586621679939367 Bool) ((~>) [a6989586621679939367] [a6989586621679939367])
- data FilterSym1 (a6989586621679948908 :: (~>) a6989586621679939367 Bool) :: (~>) [a6989586621679939367] [a6989586621679939367]
- type FilterSym2 (a6989586621679948908 :: (~>) a6989586621679939367 Bool) (a6989586621679948909 :: [a6989586621679939367]) = Filter a6989586621679948908 a6989586621679948909
- data PartitionSym0 :: forall a6989586621679939343. (~>) ((~>) a6989586621679939343 Bool) ((~>) [a6989586621679939343] ([a6989586621679939343], [a6989586621679939343]))
- data PartitionSym1 (a6989586621679948699 :: (~>) a6989586621679939343 Bool) :: (~>) [a6989586621679939343] ([a6989586621679939343], [a6989586621679939343])
- type PartitionSym2 (a6989586621679948699 :: (~>) a6989586621679939343 Bool) (a6989586621679948700 :: [a6989586621679939343]) = Partition a6989586621679948699 a6989586621679948700
- data (!!@#@$) :: forall a6989586621679939336. (~>) [a6989586621679939336] ((~>) Nat a6989586621679939336)
- data (!!@#@$$) (a6989586621679948626 :: [a6989586621679939336]) :: (~>) Nat a6989586621679939336
- type (!!@#@$$$) (a6989586621679948626 :: [a6989586621679939336]) (a6989586621679948627 :: Nat) = (!!) a6989586621679948626 a6989586621679948627
- data ElemIndexSym0 :: forall a6989586621679939365. (~>) a6989586621679939365 ((~>) [a6989586621679939365] (Maybe Nat))
- data ElemIndexSym1 (a6989586621679949291 :: a6989586621679939365) :: (~>) [a6989586621679939365] (Maybe Nat)
- type ElemIndexSym2 (a6989586621679949291 :: a6989586621679939365) (a6989586621679949292 :: [a6989586621679939365]) = ElemIndex a6989586621679949291 a6989586621679949292
- data ElemIndicesSym0 :: forall a6989586621679939364. (~>) a6989586621679939364 ((~>) [a6989586621679939364] [Nat])
- data ElemIndicesSym1 (a6989586621679949275 :: a6989586621679939364) :: (~>) [a6989586621679939364] [Nat]
- type ElemIndicesSym2 (a6989586621679949275 :: a6989586621679939364) (a6989586621679949276 :: [a6989586621679939364]) = ElemIndices a6989586621679949275 a6989586621679949276
- data FindIndexSym0 :: forall a6989586621679939363. (~>) ((~>) a6989586621679939363 Bool) ((~>) [a6989586621679939363] (Maybe Nat))
- data FindIndexSym1 (a6989586621679949283 :: (~>) a6989586621679939363 Bool) :: (~>) [a6989586621679939363] (Maybe Nat)
- type FindIndexSym2 (a6989586621679949283 :: (~>) a6989586621679939363 Bool) (a6989586621679949284 :: [a6989586621679939363]) = FindIndex a6989586621679949283 a6989586621679949284
- data FindIndicesSym0 :: forall a6989586621679939362. (~>) ((~>) a6989586621679939362 Bool) ((~>) [a6989586621679939362] [Nat])
- data FindIndicesSym1 (a6989586621679949249 :: (~>) a6989586621679939362 Bool) :: (~>) [a6989586621679939362] [Nat]
- type FindIndicesSym2 (a6989586621679949249 :: (~>) a6989586621679939362 Bool) (a6989586621679949250 :: [a6989586621679939362]) = FindIndices a6989586621679949249 a6989586621679949250
- data ZipSym0 :: forall a6989586621679939413 b6989586621679939414. (~>) [a6989586621679939413] ((~>) [b6989586621679939414] [(a6989586621679939413, b6989586621679939414)])
- data ZipSym1 (a6989586621679949241 :: [a6989586621679939413]) :: forall b6989586621679939414. (~>) [b6989586621679939414] [(a6989586621679939413, b6989586621679939414)]
- type ZipSym2 (a6989586621679949241 :: [a6989586621679939413]) (a6989586621679949242 :: [b6989586621679939414]) = Zip a6989586621679949241 a6989586621679949242
- data Zip3Sym0 :: forall a6989586621679939410 b6989586621679939411 c6989586621679939412. (~>) [a6989586621679939410] ((~>) [b6989586621679939411] ((~>) [c6989586621679939412] [(a6989586621679939410, b6989586621679939411, c6989586621679939412)]))
- data Zip3Sym1 (a6989586621679949229 :: [a6989586621679939410]) :: forall b6989586621679939411 c6989586621679939412. (~>) [b6989586621679939411] ((~>) [c6989586621679939412] [(a6989586621679939410, b6989586621679939411, c6989586621679939412)])
- data Zip3Sym2 (a6989586621679949229 :: [a6989586621679939410]) (a6989586621679949230 :: [b6989586621679939411]) :: forall c6989586621679939412. (~>) [c6989586621679939412] [(a6989586621679939410, b6989586621679939411, c6989586621679939412)]
- type Zip3Sym3 (a6989586621679949229 :: [a6989586621679939410]) (a6989586621679949230 :: [b6989586621679939411]) (a6989586621679949231 :: [c6989586621679939412]) = Zip3 a6989586621679949229 a6989586621679949230 a6989586621679949231
- data Zip4Sym0 :: forall a6989586621680065577 b6989586621680065578 c6989586621680065579 d6989586621680065580. (~>) [a6989586621680065577] ((~>) [b6989586621680065578] ((~>) [c6989586621680065579] ((~>) [d6989586621680065580] [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)])))
- data Zip4Sym1 (a6989586621680078279 :: [a6989586621680065577]) :: forall b6989586621680065578 c6989586621680065579 d6989586621680065580. (~>) [b6989586621680065578] ((~>) [c6989586621680065579] ((~>) [d6989586621680065580] [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)]))
- data Zip4Sym2 (a6989586621680078279 :: [a6989586621680065577]) (a6989586621680078280 :: [b6989586621680065578]) :: forall c6989586621680065579 d6989586621680065580. (~>) [c6989586621680065579] ((~>) [d6989586621680065580] [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)])
- data Zip4Sym3 (a6989586621680078279 :: [a6989586621680065577]) (a6989586621680078280 :: [b6989586621680065578]) (a6989586621680078281 :: [c6989586621680065579]) :: forall d6989586621680065580. (~>) [d6989586621680065580] [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)]
- type Zip4Sym4 (a6989586621680078279 :: [a6989586621680065577]) (a6989586621680078280 :: [b6989586621680065578]) (a6989586621680078281 :: [c6989586621680065579]) (a6989586621680078282 :: [d6989586621680065580]) = Zip4 a6989586621680078279 a6989586621680078280 a6989586621680078281 a6989586621680078282
- data Zip5Sym0 :: forall a6989586621680065572 b6989586621680065573 c6989586621680065574 d6989586621680065575 e6989586621680065576. (~>) [a6989586621680065572] ((~>) [b6989586621680065573] ((~>) [c6989586621680065574] ((~>) [d6989586621680065575] ((~>) [e6989586621680065576] [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]))))
- data Zip5Sym1 (a6989586621680078256 :: [a6989586621680065572]) :: forall b6989586621680065573 c6989586621680065574 d6989586621680065575 e6989586621680065576. (~>) [b6989586621680065573] ((~>) [c6989586621680065574] ((~>) [d6989586621680065575] ((~>) [e6989586621680065576] [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)])))
- data Zip5Sym2 (a6989586621680078256 :: [a6989586621680065572]) (a6989586621680078257 :: [b6989586621680065573]) :: forall c6989586621680065574 d6989586621680065575 e6989586621680065576. (~>) [c6989586621680065574] ((~>) [d6989586621680065575] ((~>) [e6989586621680065576] [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]))
- data Zip5Sym3 (a6989586621680078256 :: [a6989586621680065572]) (a6989586621680078257 :: [b6989586621680065573]) (a6989586621680078258 :: [c6989586621680065574]) :: forall d6989586621680065575 e6989586621680065576. (~>) [d6989586621680065575] ((~>) [e6989586621680065576] [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)])
- data Zip5Sym4 (a6989586621680078256 :: [a6989586621680065572]) (a6989586621680078257 :: [b6989586621680065573]) (a6989586621680078258 :: [c6989586621680065574]) (a6989586621680078259 :: [d6989586621680065575]) :: forall e6989586621680065576. (~>) [e6989586621680065576] [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]
- type Zip5Sym5 (a6989586621680078256 :: [a6989586621680065572]) (a6989586621680078257 :: [b6989586621680065573]) (a6989586621680078258 :: [c6989586621680065574]) (a6989586621680078259 :: [d6989586621680065575]) (a6989586621680078260 :: [e6989586621680065576]) = Zip5 a6989586621680078256 a6989586621680078257 a6989586621680078258 a6989586621680078259 a6989586621680078260
- data Zip6Sym0 :: forall a6989586621680065566 b6989586621680065567 c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571. (~>) [a6989586621680065566] ((~>) [b6989586621680065567] ((~>) [c6989586621680065568] ((~>) [d6989586621680065569] ((~>) [e6989586621680065570] ((~>) [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])))))
- data Zip6Sym1 (a6989586621680078228 :: [a6989586621680065566]) :: forall b6989586621680065567 c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571. (~>) [b6989586621680065567] ((~>) [c6989586621680065568] ((~>) [d6989586621680065569] ((~>) [e6989586621680065570] ((~>) [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]))))
- data Zip6Sym2 (a6989586621680078228 :: [a6989586621680065566]) (a6989586621680078229 :: [b6989586621680065567]) :: forall c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571. (~>) [c6989586621680065568] ((~>) [d6989586621680065569] ((~>) [e6989586621680065570] ((~>) [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])))
- data Zip6Sym3 (a6989586621680078228 :: [a6989586621680065566]) (a6989586621680078229 :: [b6989586621680065567]) (a6989586621680078230 :: [c6989586621680065568]) :: forall d6989586621680065569 e6989586621680065570 f6989586621680065571. (~>) [d6989586621680065569] ((~>) [e6989586621680065570] ((~>) [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]))
- data Zip6Sym4 (a6989586621680078228 :: [a6989586621680065566]) (a6989586621680078229 :: [b6989586621680065567]) (a6989586621680078230 :: [c6989586621680065568]) (a6989586621680078231 :: [d6989586621680065569]) :: forall e6989586621680065570 f6989586621680065571. (~>) [e6989586621680065570] ((~>) [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])
- data Zip6Sym5 (a6989586621680078228 :: [a6989586621680065566]) (a6989586621680078229 :: [b6989586621680065567]) (a6989586621680078230 :: [c6989586621680065568]) (a6989586621680078231 :: [d6989586621680065569]) (a6989586621680078232 :: [e6989586621680065570]) :: forall f6989586621680065571. (~>) [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]
- type Zip6Sym6 (a6989586621680078228 :: [a6989586621680065566]) (a6989586621680078229 :: [b6989586621680065567]) (a6989586621680078230 :: [c6989586621680065568]) (a6989586621680078231 :: [d6989586621680065569]) (a6989586621680078232 :: [e6989586621680065570]) (a6989586621680078233 :: [f6989586621680065571]) = Zip6 a6989586621680078228 a6989586621680078229 a6989586621680078230 a6989586621680078231 a6989586621680078232 a6989586621680078233
- data Zip7Sym0 :: forall a6989586621680065559 b6989586621680065560 c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565. (~>) [a6989586621680065559] ((~>) [b6989586621680065560] ((~>) [c6989586621680065561] ((~>) [d6989586621680065562] ((~>) [e6989586621680065563] ((~>) [f6989586621680065564] ((~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))))))
- data Zip7Sym1 (a6989586621680078195 :: [a6989586621680065559]) :: forall b6989586621680065560 c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565. (~>) [b6989586621680065560] ((~>) [c6989586621680065561] ((~>) [d6989586621680065562] ((~>) [e6989586621680065563] ((~>) [f6989586621680065564] ((~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])))))
- data Zip7Sym2 (a6989586621680078195 :: [a6989586621680065559]) (a6989586621680078196 :: [b6989586621680065560]) :: forall c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565. (~>) [c6989586621680065561] ((~>) [d6989586621680065562] ((~>) [e6989586621680065563] ((~>) [f6989586621680065564] ((~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))))
- data Zip7Sym3 (a6989586621680078195 :: [a6989586621680065559]) (a6989586621680078196 :: [b6989586621680065560]) (a6989586621680078197 :: [c6989586621680065561]) :: forall d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565. (~>) [d6989586621680065562] ((~>) [e6989586621680065563] ((~>) [f6989586621680065564] ((~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])))
- data Zip7Sym4 (a6989586621680078195 :: [a6989586621680065559]) (a6989586621680078196 :: [b6989586621680065560]) (a6989586621680078197 :: [c6989586621680065561]) (a6989586621680078198 :: [d6989586621680065562]) :: forall e6989586621680065563 f6989586621680065564 g6989586621680065565. (~>) [e6989586621680065563] ((~>) [f6989586621680065564] ((~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))
- data Zip7Sym5 (a6989586621680078195 :: [a6989586621680065559]) (a6989586621680078196 :: [b6989586621680065560]) (a6989586621680078197 :: [c6989586621680065561]) (a6989586621680078198 :: [d6989586621680065562]) (a6989586621680078199 :: [e6989586621680065563]) :: forall f6989586621680065564 g6989586621680065565. (~>) [f6989586621680065564] ((~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])
- data Zip7Sym6 (a6989586621680078195 :: [a6989586621680065559]) (a6989586621680078196 :: [b6989586621680065560]) (a6989586621680078197 :: [c6989586621680065561]) (a6989586621680078198 :: [d6989586621680065562]) (a6989586621680078199 :: [e6989586621680065563]) (a6989586621680078200 :: [f6989586621680065564]) :: forall g6989586621680065565. (~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]
- type Zip7Sym7 (a6989586621680078195 :: [a6989586621680065559]) (a6989586621680078196 :: [b6989586621680065560]) (a6989586621680078197 :: [c6989586621680065561]) (a6989586621680078198 :: [d6989586621680065562]) (a6989586621680078199 :: [e6989586621680065563]) (a6989586621680078200 :: [f6989586621680065564]) (a6989586621680078201 :: [g6989586621680065565]) = Zip7 a6989586621680078195 a6989586621680078196 a6989586621680078197 a6989586621680078198 a6989586621680078199 a6989586621680078200 a6989586621680078201
- data ZipWithSym0 :: forall a6989586621679939407 b6989586621679939408 c6989586621679939409. (~>) ((~>) a6989586621679939407 ((~>) b6989586621679939408 c6989586621679939409)) ((~>) [a6989586621679939407] ((~>) [b6989586621679939408] [c6989586621679939409]))
- data ZipWithSym1 (a6989586621679949218 :: (~>) a6989586621679939407 ((~>) b6989586621679939408 c6989586621679939409)) :: (~>) [a6989586621679939407] ((~>) [b6989586621679939408] [c6989586621679939409])
- data ZipWithSym2 (a6989586621679949218 :: (~>) a6989586621679939407 ((~>) b6989586621679939408 c6989586621679939409)) (a6989586621679949219 :: [a6989586621679939407]) :: (~>) [b6989586621679939408] [c6989586621679939409]
- type ZipWithSym3 (a6989586621679949218 :: (~>) a6989586621679939407 ((~>) b6989586621679939408 c6989586621679939409)) (a6989586621679949219 :: [a6989586621679939407]) (a6989586621679949220 :: [b6989586621679939408]) = ZipWith a6989586621679949218 a6989586621679949219 a6989586621679949220
- data ZipWith3Sym0 :: forall a6989586621679939403 b6989586621679939404 c6989586621679939405 d6989586621679939406. (~>) ((~>) a6989586621679939403 ((~>) b6989586621679939404 ((~>) c6989586621679939405 d6989586621679939406))) ((~>) [a6989586621679939403] ((~>) [b6989586621679939404] ((~>) [c6989586621679939405] [d6989586621679939406])))
- data ZipWith3Sym1 (a6989586621679949203 :: (~>) a6989586621679939403 ((~>) b6989586621679939404 ((~>) c6989586621679939405 d6989586621679939406))) :: (~>) [a6989586621679939403] ((~>) [b6989586621679939404] ((~>) [c6989586621679939405] [d6989586621679939406]))
- data ZipWith3Sym2 (a6989586621679949203 :: (~>) a6989586621679939403 ((~>) b6989586621679939404 ((~>) c6989586621679939405 d6989586621679939406))) (a6989586621679949204 :: [a6989586621679939403]) :: (~>) [b6989586621679939404] ((~>) [c6989586621679939405] [d6989586621679939406])
- data ZipWith3Sym3 (a6989586621679949203 :: (~>) a6989586621679939403 ((~>) b6989586621679939404 ((~>) c6989586621679939405 d6989586621679939406))) (a6989586621679949204 :: [a6989586621679939403]) (a6989586621679949205 :: [b6989586621679939404]) :: (~>) [c6989586621679939405] [d6989586621679939406]
- type ZipWith3Sym4 (a6989586621679949203 :: (~>) a6989586621679939403 ((~>) b6989586621679939404 ((~>) c6989586621679939405 d6989586621679939406))) (a6989586621679949204 :: [a6989586621679939403]) (a6989586621679949205 :: [b6989586621679939404]) (a6989586621679949206 :: [c6989586621679939405]) = ZipWith3 a6989586621679949203 a6989586621679949204 a6989586621679949205 a6989586621679949206
- data ZipWith4Sym0 :: forall a6989586621680065554 b6989586621680065555 c6989586621680065556 d6989586621680065557 e6989586621680065558. (~>) ((~>) a6989586621680065554 ((~>) b6989586621680065555 ((~>) c6989586621680065556 ((~>) d6989586621680065557 e6989586621680065558)))) ((~>) [a6989586621680065554] ((~>) [b6989586621680065555] ((~>) [c6989586621680065556] ((~>) [d6989586621680065557] [e6989586621680065558]))))
- data ZipWith4Sym1 (a6989586621680078162 :: (~>) a6989586621680065554 ((~>) b6989586621680065555 ((~>) c6989586621680065556 ((~>) d6989586621680065557 e6989586621680065558)))) :: (~>) [a6989586621680065554] ((~>) [b6989586621680065555] ((~>) [c6989586621680065556] ((~>) [d6989586621680065557] [e6989586621680065558])))
- data ZipWith4Sym2 (a6989586621680078162 :: (~>) a6989586621680065554 ((~>) b6989586621680065555 ((~>) c6989586621680065556 ((~>) d6989586621680065557 e6989586621680065558)))) (a6989586621680078163 :: [a6989586621680065554]) :: (~>) [b6989586621680065555] ((~>) [c6989586621680065556] ((~>) [d6989586621680065557] [e6989586621680065558]))
- data ZipWith4Sym3 (a6989586621680078162 :: (~>) a6989586621680065554 ((~>) b6989586621680065555 ((~>) c6989586621680065556 ((~>) d6989586621680065557 e6989586621680065558)))) (a6989586621680078163 :: [a6989586621680065554]) (a6989586621680078164 :: [b6989586621680065555]) :: (~>) [c6989586621680065556] ((~>) [d6989586621680065557] [e6989586621680065558])
- data ZipWith4Sym4 (a6989586621680078162 :: (~>) a6989586621680065554 ((~>) b6989586621680065555 ((~>) c6989586621680065556 ((~>) d6989586621680065557 e6989586621680065558)))) (a6989586621680078163 :: [a6989586621680065554]) (a6989586621680078164 :: [b6989586621680065555]) (a6989586621680078165 :: [c6989586621680065556]) :: (~>) [d6989586621680065557] [e6989586621680065558]
- type ZipWith4Sym5 (a6989586621680078162 :: (~>) a6989586621680065554 ((~>) b6989586621680065555 ((~>) c6989586621680065556 ((~>) d6989586621680065557 e6989586621680065558)))) (a6989586621680078163 :: [a6989586621680065554]) (a6989586621680078164 :: [b6989586621680065555]) (a6989586621680078165 :: [c6989586621680065556]) (a6989586621680078166 :: [d6989586621680065557]) = ZipWith4 a6989586621680078162 a6989586621680078163 a6989586621680078164 a6989586621680078165 a6989586621680078166
- data ZipWith5Sym0 :: forall a6989586621680065548 b6989586621680065549 c6989586621680065550 d6989586621680065551 e6989586621680065552 f6989586621680065553. (~>) ((~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) ((~>) [a6989586621680065548] ((~>) [b6989586621680065549] ((~>) [c6989586621680065550] ((~>) [d6989586621680065551] ((~>) [e6989586621680065552] [f6989586621680065553])))))
- data ZipWith5Sym1 (a6989586621680078139 :: (~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) :: (~>) [a6989586621680065548] ((~>) [b6989586621680065549] ((~>) [c6989586621680065550] ((~>) [d6989586621680065551] ((~>) [e6989586621680065552] [f6989586621680065553]))))
- data ZipWith5Sym2 (a6989586621680078139 :: (~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) (a6989586621680078140 :: [a6989586621680065548]) :: (~>) [b6989586621680065549] ((~>) [c6989586621680065550] ((~>) [d6989586621680065551] ((~>) [e6989586621680065552] [f6989586621680065553])))
- data ZipWith5Sym3 (a6989586621680078139 :: (~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) (a6989586621680078140 :: [a6989586621680065548]) (a6989586621680078141 :: [b6989586621680065549]) :: (~>) [c6989586621680065550] ((~>) [d6989586621680065551] ((~>) [e6989586621680065552] [f6989586621680065553]))
- data ZipWith5Sym4 (a6989586621680078139 :: (~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) (a6989586621680078140 :: [a6989586621680065548]) (a6989586621680078141 :: [b6989586621680065549]) (a6989586621680078142 :: [c6989586621680065550]) :: (~>) [d6989586621680065551] ((~>) [e6989586621680065552] [f6989586621680065553])
- data ZipWith5Sym5 (a6989586621680078139 :: (~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) (a6989586621680078140 :: [a6989586621680065548]) (a6989586621680078141 :: [b6989586621680065549]) (a6989586621680078142 :: [c6989586621680065550]) (a6989586621680078143 :: [d6989586621680065551]) :: (~>) [e6989586621680065552] [f6989586621680065553]
- type ZipWith5Sym6 (a6989586621680078139 :: (~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) (a6989586621680078140 :: [a6989586621680065548]) (a6989586621680078141 :: [b6989586621680065549]) (a6989586621680078142 :: [c6989586621680065550]) (a6989586621680078143 :: [d6989586621680065551]) (a6989586621680078144 :: [e6989586621680065552]) = ZipWith5 a6989586621680078139 a6989586621680078140 a6989586621680078141 a6989586621680078142 a6989586621680078143 a6989586621680078144
- data ZipWith6Sym0 :: forall a6989586621680065541 b6989586621680065542 c6989586621680065543 d6989586621680065544 e6989586621680065545 f6989586621680065546 g6989586621680065547. (~>) ((~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) ((~>) [a6989586621680065541] ((~>) [b6989586621680065542] ((~>) [c6989586621680065543] ((~>) [d6989586621680065544] ((~>) [e6989586621680065545] ((~>) [f6989586621680065546] [g6989586621680065547]))))))
- data ZipWith6Sym1 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) :: (~>) [a6989586621680065541] ((~>) [b6989586621680065542] ((~>) [c6989586621680065543] ((~>) [d6989586621680065544] ((~>) [e6989586621680065545] ((~>) [f6989586621680065546] [g6989586621680065547])))))
- data ZipWith6Sym2 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) (a6989586621680078113 :: [a6989586621680065541]) :: (~>) [b6989586621680065542] ((~>) [c6989586621680065543] ((~>) [d6989586621680065544] ((~>) [e6989586621680065545] ((~>) [f6989586621680065546] [g6989586621680065547]))))
- data ZipWith6Sym3 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) (a6989586621680078113 :: [a6989586621680065541]) (a6989586621680078114 :: [b6989586621680065542]) :: (~>) [c6989586621680065543] ((~>) [d6989586621680065544] ((~>) [e6989586621680065545] ((~>) [f6989586621680065546] [g6989586621680065547])))
- data ZipWith6Sym4 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) (a6989586621680078113 :: [a6989586621680065541]) (a6989586621680078114 :: [b6989586621680065542]) (a6989586621680078115 :: [c6989586621680065543]) :: (~>) [d6989586621680065544] ((~>) [e6989586621680065545] ((~>) [f6989586621680065546] [g6989586621680065547]))
- data ZipWith6Sym5 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) (a6989586621680078113 :: [a6989586621680065541]) (a6989586621680078114 :: [b6989586621680065542]) (a6989586621680078115 :: [c6989586621680065543]) (a6989586621680078116 :: [d6989586621680065544]) :: (~>) [e6989586621680065545] ((~>) [f6989586621680065546] [g6989586621680065547])
- data ZipWith6Sym6 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) (a6989586621680078113 :: [a6989586621680065541]) (a6989586621680078114 :: [b6989586621680065542]) (a6989586621680078115 :: [c6989586621680065543]) (a6989586621680078116 :: [d6989586621680065544]) (a6989586621680078117 :: [e6989586621680065545]) :: (~>) [f6989586621680065546] [g6989586621680065547]
- type ZipWith6Sym7 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) (a6989586621680078113 :: [a6989586621680065541]) (a6989586621680078114 :: [b6989586621680065542]) (a6989586621680078115 :: [c6989586621680065543]) (a6989586621680078116 :: [d6989586621680065544]) (a6989586621680078117 :: [e6989586621680065545]) (a6989586621680078118 :: [f6989586621680065546]) = ZipWith6 a6989586621680078112 a6989586621680078113 a6989586621680078114 a6989586621680078115 a6989586621680078116 a6989586621680078117 a6989586621680078118
- data ZipWith7Sym0 :: forall a6989586621680065533 b6989586621680065534 c6989586621680065535 d6989586621680065536 e6989586621680065537 f6989586621680065538 g6989586621680065539 h6989586621680065540. (~>) ((~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) ((~>) [a6989586621680065533] ((~>) [b6989586621680065534] ((~>) [c6989586621680065535] ((~>) [d6989586621680065536] ((~>) [e6989586621680065537] ((~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540])))))))
- data ZipWith7Sym1 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) :: (~>) [a6989586621680065533] ((~>) [b6989586621680065534] ((~>) [c6989586621680065535] ((~>) [d6989586621680065536] ((~>) [e6989586621680065537] ((~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540]))))))
- data ZipWith7Sym2 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) :: (~>) [b6989586621680065534] ((~>) [c6989586621680065535] ((~>) [d6989586621680065536] ((~>) [e6989586621680065537] ((~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540])))))
- data ZipWith7Sym3 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) (a6989586621680078083 :: [b6989586621680065534]) :: (~>) [c6989586621680065535] ((~>) [d6989586621680065536] ((~>) [e6989586621680065537] ((~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540]))))
- data ZipWith7Sym4 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) (a6989586621680078083 :: [b6989586621680065534]) (a6989586621680078084 :: [c6989586621680065535]) :: (~>) [d6989586621680065536] ((~>) [e6989586621680065537] ((~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540])))
- data ZipWith7Sym5 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) (a6989586621680078083 :: [b6989586621680065534]) (a6989586621680078084 :: [c6989586621680065535]) (a6989586621680078085 :: [d6989586621680065536]) :: (~>) [e6989586621680065537] ((~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540]))
- data ZipWith7Sym6 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) (a6989586621680078083 :: [b6989586621680065534]) (a6989586621680078084 :: [c6989586621680065535]) (a6989586621680078085 :: [d6989586621680065536]) (a6989586621680078086 :: [e6989586621680065537]) :: (~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540])
- data ZipWith7Sym7 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) (a6989586621680078083 :: [b6989586621680065534]) (a6989586621680078084 :: [c6989586621680065535]) (a6989586621680078085 :: [d6989586621680065536]) (a6989586621680078086 :: [e6989586621680065537]) (a6989586621680078087 :: [f6989586621680065538]) :: (~>) [g6989586621680065539] [h6989586621680065540]
- type ZipWith7Sym8 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) (a6989586621680078083 :: [b6989586621680065534]) (a6989586621680078084 :: [c6989586621680065535]) (a6989586621680078085 :: [d6989586621680065536]) (a6989586621680078086 :: [e6989586621680065537]) (a6989586621680078087 :: [f6989586621680065538]) (a6989586621680078088 :: [g6989586621680065539]) = ZipWith7 a6989586621680078081 a6989586621680078082 a6989586621680078083 a6989586621680078084 a6989586621680078085 a6989586621680078086 a6989586621680078087 a6989586621680078088
- data UnzipSym0 :: forall a6989586621679939401 b6989586621679939402. (~>) [(a6989586621679939401, b6989586621679939402)] ([a6989586621679939401], [b6989586621679939402])
- type UnzipSym1 (a6989586621679949184 :: [(a6989586621679939401, b6989586621679939402)]) = Unzip a6989586621679949184
- data Unzip3Sym0 :: forall a6989586621679939398 b6989586621679939399 c6989586621679939400. (~>) [(a6989586621679939398, b6989586621679939399, c6989586621679939400)] ([a6989586621679939398], [b6989586621679939399], [c6989586621679939400])
- type Unzip3Sym1 (a6989586621679949163 :: [(a6989586621679939398, b6989586621679939399, c6989586621679939400)]) = Unzip3 a6989586621679949163
- data Unzip4Sym0 :: forall a6989586621679939394 b6989586621679939395 c6989586621679939396 d6989586621679939397. (~>) [(a6989586621679939394, b6989586621679939395, c6989586621679939396, d6989586621679939397)] ([a6989586621679939394], [b6989586621679939395], [c6989586621679939396], [d6989586621679939397])
- type Unzip4Sym1 (a6989586621679949140 :: [(a6989586621679939394, b6989586621679939395, c6989586621679939396, d6989586621679939397)]) = Unzip4 a6989586621679949140
- data Unzip5Sym0 :: forall a6989586621679939389 b6989586621679939390 c6989586621679939391 d6989586621679939392 e6989586621679939393. (~>) [(a6989586621679939389, b6989586621679939390, c6989586621679939391, d6989586621679939392, e6989586621679939393)] ([a6989586621679939389], [b6989586621679939390], [c6989586621679939391], [d6989586621679939392], [e6989586621679939393])
- type Unzip5Sym1 (a6989586621679949115 :: [(a6989586621679939389, b6989586621679939390, c6989586621679939391, d6989586621679939392, e6989586621679939393)]) = Unzip5 a6989586621679949115
- data Unzip6Sym0 :: forall a6989586621679939383 b6989586621679939384 c6989586621679939385 d6989586621679939386 e6989586621679939387 f6989586621679939388. (~>) [(a6989586621679939383, b6989586621679939384, c6989586621679939385, d6989586621679939386, e6989586621679939387, f6989586621679939388)] ([a6989586621679939383], [b6989586621679939384], [c6989586621679939385], [d6989586621679939386], [e6989586621679939387], [f6989586621679939388])
- type Unzip6Sym1 (a6989586621679949088 :: [(a6989586621679939383, b6989586621679939384, c6989586621679939385, d6989586621679939386, e6989586621679939387, f6989586621679939388)]) = Unzip6 a6989586621679949088
- data Unzip7Sym0 :: forall a6989586621679939376 b6989586621679939377 c6989586621679939378 d6989586621679939379 e6989586621679939380 f6989586621679939381 g6989586621679939382. (~>) [(a6989586621679939376, b6989586621679939377, c6989586621679939378, d6989586621679939379, e6989586621679939380, f6989586621679939381, g6989586621679939382)] ([a6989586621679939376], [b6989586621679939377], [c6989586621679939378], [d6989586621679939379], [e6989586621679939380], [f6989586621679939381], [g6989586621679939382])
- type Unzip7Sym1 (a6989586621679949059 :: [(a6989586621679939376, b6989586621679939377, c6989586621679939378, d6989586621679939379, e6989586621679939380, f6989586621679939381, g6989586621679939382)]) = Unzip7 a6989586621679949059
- data UnlinesSym0 :: (~>) [Symbol] Symbol
- type UnlinesSym1 (a6989586621679949055 :: [Symbol]) = Unlines a6989586621679949055
- data UnwordsSym0 :: (~>) [Symbol] Symbol
- type UnwordsSym1 (a6989586621679949044 :: [Symbol]) = Unwords a6989586621679949044
- data NubSym0 :: forall a6989586621679939335. (~>) [a6989586621679939335] [a6989586621679939335]
- type NubSym1 (a6989586621679949313 :: [a6989586621679939335]) = Nub a6989586621679949313
- data DeleteSym0 :: forall a6989586621679939375. (~>) a6989586621679939375 ((~>) [a6989586621679939375] [a6989586621679939375])
- data DeleteSym1 (a6989586621679949028 :: a6989586621679939375) :: (~>) [a6989586621679939375] [a6989586621679939375]
- type DeleteSym2 (a6989586621679949028 :: a6989586621679939375) (a6989586621679949029 :: [a6989586621679939375]) = Delete a6989586621679949028 a6989586621679949029
- data (\\@#@$) :: forall a6989586621679939374. (~>) [a6989586621679939374] ((~>) [a6989586621679939374] [a6989586621679939374])
- data (\\@#@$$) (a6989586621679949038 :: [a6989586621679939374]) :: (~>) [a6989586621679939374] [a6989586621679939374]
- type (\\@#@$$$) (a6989586621679949038 :: [a6989586621679939374]) (a6989586621679949039 :: [a6989586621679939374]) = (\\) a6989586621679949038 a6989586621679949039
- data UnionSym0 :: forall a6989586621679939331. (~>) [a6989586621679939331] ((~>) [a6989586621679939331] [a6989586621679939331])
- data UnionSym1 (a6989586621679949018 :: [a6989586621679939331]) :: (~>) [a6989586621679939331] [a6989586621679939331]
- type UnionSym2 (a6989586621679949018 :: [a6989586621679939331]) (a6989586621679949019 :: [a6989586621679939331]) = Union a6989586621679949018 a6989586621679949019
- data IntersectSym0 :: forall a6989586621679939361. (~>) [a6989586621679939361] ((~>) [a6989586621679939361] [a6989586621679939361])
- data IntersectSym1 (a6989586621679949613 :: [a6989586621679939361]) :: (~>) [a6989586621679939361] [a6989586621679939361]
- type IntersectSym2 (a6989586621679949613 :: [a6989586621679939361]) (a6989586621679949614 :: [a6989586621679939361]) = Intersect a6989586621679949613 a6989586621679949614
- data InsertSym0 :: forall a6989586621679939348. (~>) a6989586621679939348 ((~>) [a6989586621679939348] [a6989586621679939348])
- data InsertSym1 (a6989586621679948955 :: a6989586621679939348) :: (~>) [a6989586621679939348] [a6989586621679939348]
- type InsertSym2 (a6989586621679948955 :: a6989586621679939348) (a6989586621679948956 :: [a6989586621679939348]) = Insert a6989586621679948955 a6989586621679948956
- data SortSym0 :: forall a6989586621679939347. (~>) [a6989586621679939347] [a6989586621679939347]
- type SortSym1 (a6989586621679948971 :: [a6989586621679939347]) = Sort a6989586621679948971
- data NubBySym0 :: forall a6989586621679939334. (~>) ((~>) a6989586621679939334 ((~>) a6989586621679939334 Bool)) ((~>) [a6989586621679939334] [a6989586621679939334])
- data NubBySym1 (a6989586621679948601 :: (~>) a6989586621679939334 ((~>) a6989586621679939334 Bool)) :: (~>) [a6989586621679939334] [a6989586621679939334]
- type NubBySym2 (a6989586621679948601 :: (~>) a6989586621679939334 ((~>) a6989586621679939334 Bool)) (a6989586621679948602 :: [a6989586621679939334]) = NubBy a6989586621679948601 a6989586621679948602
- data DeleteBySym0 :: forall a6989586621679939373. (~>) ((~>) a6989586621679939373 ((~>) a6989586621679939373 Bool)) ((~>) a6989586621679939373 ((~>) [a6989586621679939373] [a6989586621679939373]))
- data DeleteBySym1 (a6989586621679948974 :: (~>) a6989586621679939373 ((~>) a6989586621679939373 Bool)) :: (~>) a6989586621679939373 ((~>) [a6989586621679939373] [a6989586621679939373])
- data DeleteBySym2 (a6989586621679948974 :: (~>) a6989586621679939373 ((~>) a6989586621679939373 Bool)) (a6989586621679948975 :: a6989586621679939373) :: (~>) [a6989586621679939373] [a6989586621679939373]
- type DeleteBySym3 (a6989586621679948974 :: (~>) a6989586621679939373 ((~>) a6989586621679939373 Bool)) (a6989586621679948975 :: a6989586621679939373) (a6989586621679948976 :: [a6989586621679939373]) = DeleteBy a6989586621679948974 a6989586621679948975 a6989586621679948976
- data DeleteFirstsBySym0 :: forall a6989586621679939372. (~>) ((~>) a6989586621679939372 ((~>) a6989586621679939372 Bool)) ((~>) [a6989586621679939372] ((~>) [a6989586621679939372] [a6989586621679939372]))
- data DeleteFirstsBySym1 (a6989586621679948992 :: (~>) a6989586621679939372 ((~>) a6989586621679939372 Bool)) :: (~>) [a6989586621679939372] ((~>) [a6989586621679939372] [a6989586621679939372])
- data DeleteFirstsBySym2 (a6989586621679948992 :: (~>) a6989586621679939372 ((~>) a6989586621679939372 Bool)) (a6989586621679948993 :: [a6989586621679939372]) :: (~>) [a6989586621679939372] [a6989586621679939372]
- type DeleteFirstsBySym3 (a6989586621679948992 :: (~>) a6989586621679939372 ((~>) a6989586621679939372 Bool)) (a6989586621679948993 :: [a6989586621679939372]) (a6989586621679948994 :: [a6989586621679939372]) = DeleteFirstsBy a6989586621679948992 a6989586621679948993 a6989586621679948994
- data UnionBySym0 :: forall a6989586621679939332. (~>) ((~>) a6989586621679939332 ((~>) a6989586621679939332 Bool)) ((~>) [a6989586621679939332] ((~>) [a6989586621679939332] [a6989586621679939332]))
- data UnionBySym1 (a6989586621679949005 :: (~>) a6989586621679939332 ((~>) a6989586621679939332 Bool)) :: (~>) [a6989586621679939332] ((~>) [a6989586621679939332] [a6989586621679939332])
- data UnionBySym2 (a6989586621679949005 :: (~>) a6989586621679939332 ((~>) a6989586621679939332 Bool)) (a6989586621679949006 :: [a6989586621679939332]) :: (~>) [a6989586621679939332] [a6989586621679939332]
- type UnionBySym3 (a6989586621679949005 :: (~>) a6989586621679939332 ((~>) a6989586621679939332 Bool)) (a6989586621679949006 :: [a6989586621679939332]) (a6989586621679949007 :: [a6989586621679939332]) = UnionBy a6989586621679949005 a6989586621679949006 a6989586621679949007
- data IntersectBySym0 :: forall a6989586621679939360. (~>) ((~>) a6989586621679939360 ((~>) a6989586621679939360 Bool)) ((~>) [a6989586621679939360] ((~>) [a6989586621679939360] [a6989586621679939360]))
- data IntersectBySym1 (a6989586621679949577 :: (~>) a6989586621679939360 ((~>) a6989586621679939360 Bool)) :: (~>) [a6989586621679939360] ((~>) [a6989586621679939360] [a6989586621679939360])
- data IntersectBySym2 (a6989586621679949577 :: (~>) a6989586621679939360 ((~>) a6989586621679939360 Bool)) (a6989586621679949578 :: [a6989586621679939360]) :: (~>) [a6989586621679939360] [a6989586621679939360]
- type IntersectBySym3 (a6989586621679949577 :: (~>) a6989586621679939360 ((~>) a6989586621679939360 Bool)) (a6989586621679949578 :: [a6989586621679939360]) (a6989586621679949579 :: [a6989586621679939360]) = IntersectBy a6989586621679949577 a6989586621679949578 a6989586621679949579
- data GroupBySym0 :: forall a6989586621679939346. (~>) ((~>) a6989586621679939346 ((~>) a6989586621679939346 Bool)) ((~>) [a6989586621679939346] [[a6989586621679939346]])
- data GroupBySym1 (a6989586621679948842 :: (~>) a6989586621679939346 ((~>) a6989586621679939346 Bool)) :: (~>) [a6989586621679939346] [[a6989586621679939346]]
- type GroupBySym2 (a6989586621679948842 :: (~>) a6989586621679939346 ((~>) a6989586621679939346 Bool)) (a6989586621679948843 :: [a6989586621679939346]) = GroupBy a6989586621679948842 a6989586621679948843
- data SortBySym0 :: forall a6989586621679939371. (~>) ((~>) a6989586621679939371 ((~>) a6989586621679939371 Ordering)) ((~>) [a6989586621679939371] [a6989586621679939371])
- data SortBySym1 (a6989586621679948961 :: (~>) a6989586621679939371 ((~>) a6989586621679939371 Ordering)) :: (~>) [a6989586621679939371] [a6989586621679939371]
- type SortBySym2 (a6989586621679948961 :: (~>) a6989586621679939371 ((~>) a6989586621679939371 Ordering)) (a6989586621679948962 :: [a6989586621679939371]) = SortBy a6989586621679948961 a6989586621679948962
- data InsertBySym0 :: forall a6989586621679939370. (~>) ((~>) a6989586621679939370 ((~>) a6989586621679939370 Ordering)) ((~>) a6989586621679939370 ((~>) [a6989586621679939370] [a6989586621679939370]))
- data InsertBySym1 (a6989586621679948931 :: (~>) a6989586621679939370 ((~>) a6989586621679939370 Ordering)) :: (~>) a6989586621679939370 ((~>) [a6989586621679939370] [a6989586621679939370])
- data InsertBySym2 (a6989586621679948931 :: (~>) a6989586621679939370 ((~>) a6989586621679939370 Ordering)) (a6989586621679948932 :: a6989586621679939370) :: (~>) [a6989586621679939370] [a6989586621679939370]
- type InsertBySym3 (a6989586621679948931 :: (~>) a6989586621679939370 ((~>) a6989586621679939370 Ordering)) (a6989586621679948932 :: a6989586621679939370) (a6989586621679948933 :: [a6989586621679939370]) = InsertBy a6989586621679948931 a6989586621679948932 a6989586621679948933
- data MaximumBySym0 :: forall a6989586621680448359 t6989586621680448358. (~>) ((~>) a6989586621680448359 ((~>) a6989586621680448359 Ordering)) ((~>) (t6989586621680448358 a6989586621680448359) a6989586621680448359)
- data MaximumBySym1 (a6989586621680448870 :: (~>) a6989586621680448359 ((~>) a6989586621680448359 Ordering)) :: forall t6989586621680448358. (~>) (t6989586621680448358 a6989586621680448359) a6989586621680448359
- type MaximumBySym2 (a6989586621680448870 :: (~>) a6989586621680448359 ((~>) a6989586621680448359 Ordering)) (a6989586621680448871 :: t6989586621680448358 a6989586621680448359) = MaximumBy a6989586621680448870 a6989586621680448871
- data MinimumBySym0 :: forall a6989586621680448357 t6989586621680448356. (~>) ((~>) a6989586621680448357 ((~>) a6989586621680448357 Ordering)) ((~>) (t6989586621680448356 a6989586621680448357) a6989586621680448357)
- data MinimumBySym1 (a6989586621680448845 :: (~>) a6989586621680448357 ((~>) a6989586621680448357 Ordering)) :: forall t6989586621680448356. (~>) (t6989586621680448356 a6989586621680448357) a6989586621680448357
- type MinimumBySym2 (a6989586621680448845 :: (~>) a6989586621680448357 ((~>) a6989586621680448357 Ordering)) (a6989586621680448846 :: t6989586621680448356 a6989586621680448357) = MinimumBy a6989586621680448845 a6989586621680448846
- data GenericLengthSym0 :: forall a6989586621679939330 i6989586621679939329. (~>) [a6989586621679939330] i6989586621679939329
- type GenericLengthSym1 (a6989586621679948588 :: [a6989586621679939330]) = GenericLength a6989586621679948588
- data GenericTakeSym0 :: forall a6989586621680065532 i6989586621680065531. (~>) i6989586621680065531 ((~>) [a6989586621680065532] [a6989586621680065532])
- data GenericTakeSym1 (a6989586621680078075 :: i6989586621680065531) :: forall a6989586621680065532. (~>) [a6989586621680065532] [a6989586621680065532]
- type GenericTakeSym2 (a6989586621680078075 :: i6989586621680065531) (a6989586621680078076 :: [a6989586621680065532]) = GenericTake a6989586621680078075 a6989586621680078076
- data GenericDropSym0 :: forall a6989586621680065530 i6989586621680065529. (~>) i6989586621680065529 ((~>) [a6989586621680065530] [a6989586621680065530])
- data GenericDropSym1 (a6989586621680078065 :: i6989586621680065529) :: forall a6989586621680065530. (~>) [a6989586621680065530] [a6989586621680065530]
- type GenericDropSym2 (a6989586621680078065 :: i6989586621680065529) (a6989586621680078066 :: [a6989586621680065530]) = GenericDrop a6989586621680078065 a6989586621680078066
- data GenericSplitAtSym0 :: forall a6989586621680065528 i6989586621680065527. (~>) i6989586621680065527 ((~>) [a6989586621680065528] ([a6989586621680065528], [a6989586621680065528]))
- data GenericSplitAtSym1 (a6989586621680078055 :: i6989586621680065527) :: forall a6989586621680065528. (~>) [a6989586621680065528] ([a6989586621680065528], [a6989586621680065528])
- type GenericSplitAtSym2 (a6989586621680078055 :: i6989586621680065527) (a6989586621680078056 :: [a6989586621680065528]) = GenericSplitAt a6989586621680078055 a6989586621680078056
- data GenericIndexSym0 :: forall a6989586621680065526 i6989586621680065525. (~>) [a6989586621680065526] ((~>) i6989586621680065525 a6989586621680065526)
- data GenericIndexSym1 (a6989586621680078045 :: [a6989586621680065526]) :: forall i6989586621680065525. (~>) i6989586621680065525 a6989586621680065526
- type GenericIndexSym2 (a6989586621680078045 :: [a6989586621680065526]) (a6989586621680078046 :: i6989586621680065525) = GenericIndex a6989586621680078045 a6989586621680078046
- data GenericReplicateSym0 :: forall a6989586621680065524 i6989586621680065523. (~>) i6989586621680065523 ((~>) a6989586621680065524 [a6989586621680065524])
- data GenericReplicateSym1 (a6989586621680078035 :: i6989586621680065523) :: forall a6989586621680065524. (~>) a6989586621680065524 [a6989586621680065524]
- type GenericReplicateSym2 (a6989586621680078035 :: i6989586621680065523) (a6989586621680078036 :: a6989586621680065524) = GenericReplicate a6989586621680078035 a6989586621680078036
The singleton for lists
data family Sing :: k -> Type infixr 5 Source #
The singleton kind-indexed data family.
Instances
SDecide k => TestCoercion (Sing :: k -> Type) Source # | |
Defined in Data.Singletons.Decide | |
SDecide k => TestEquality (Sing :: k -> Type) Source # | |
Defined in Data.Singletons.Decide | |
Show (SSymbol s) Source # | |
Show (SNat n) Source # | |
Eq (Sing a) Source # | |
Ord (Sing a) Source # | |
Show (Sing z) Source # | |
(ShowSing a, ShowSing [a]) => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
Show (Sing z) Source # | |
(ShowSing a, ShowSing b) => Show (Sing z) Source # | |
Show (Sing a) Source # | |
Show (Sing z) Source # | |
(ShowSing a, ShowSing b) => Show (Sing z) Source # | |
(ShowSing a, ShowSing b, ShowSing c) => Show (Sing z) Source # | |
(ShowSing a, ShowSing b, ShowSing c, ShowSing d) => Show (Sing z) Source # | |
(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e) => Show (Sing z) Source # | |
(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f) => Show (Sing z) Source # | |
(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f, ShowSing g) => Show (Sing z) Source # | |
Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
(ShowSing a, ShowSing b) => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
ShowSing m => Show (Sing z) Source # | |
ShowSing (Maybe a) => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
ShowSing (Maybe a) => Show (Sing z) Source # | |
ShowSing (Maybe a) => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
ShowSing Bool => Show (Sing z) Source # | |
ShowSing Bool => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
(ShowSing a, ShowSing [a]) => Show (Sing z) Source # | |
data Sing (a :: Bool) Source # | |
data Sing (a :: Ordering) Source # | |
data Sing (n :: Nat) Source # | |
data Sing (n :: Symbol) Source # | |
Defined in Data.Singletons.TypeLits.Internal | |
data Sing (a :: ()) Source # | |
Defined in Data.Singletons.Prelude.Instances | |
data Sing (a :: Void) Source # | |
Defined in Data.Singletons.Prelude.Instances | |
data Sing (a :: All) Source # | |
data Sing (a :: Any) Source # | |
data Sing (a :: PErrorMessage) Source # | |
Defined in Data.Singletons.TypeError data Sing (a :: PErrorMessage) where
| |
data Sing (b :: [a]) Source # | |
data Sing (b :: Maybe a) Source # | |
newtype Sing (a :: TYPE rep) Source # | A choice of singleton for the kind Conceivably, one could generalize this instance to `Sing :: k -> Type` for
any kind We cannot produce explicit singleton values for everything in |
Defined in Data.Singletons.TypeRepTYPE | |
data Sing (b :: Min a) Source # | |
data Sing (b :: Max a) Source # | |
data Sing (b :: First a) Source # | |
data Sing (b :: Last a) Source # | |
data Sing (a :: WrappedMonoid m) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal data Sing (a :: WrappedMonoid m) where
| |
data Sing (b :: Option a) Source # | |
data Sing (b :: Identity a) Source # | |
data Sing (b :: First a) Source # | |
data Sing (b :: Last a) Source # | |
data Sing (b :: Dual a) Source # | |
data Sing (b :: Sum a) Source # | |
data Sing (b :: Product a) Source # | |
data Sing (b :: Down a) Source # | |
data Sing (b :: NonEmpty a) Source # | |
data Sing (c :: Either a b) Source # | |
data Sing (c :: (a, b)) Source # | |
data Sing (c :: Arg a b) Source # | |
newtype Sing (f :: k1 ~> k2) Source # | |
data Sing (d :: (a, b, c)) Source # | |
data Sing (c :: Const a b) Source # | |
data Sing (e :: (a, b, c, d)) Source # | |
data Sing (f :: (a, b, c, d, e)) Source # | |
data Sing (g :: (a, b, c, d, e, f)) Source # | |
data Sing (h :: (a, b, c, d, e, f, g)) Source # | |
Defined in Data.Singletons.Prelude.Instances |
Though Haddock doesn't show it, the Sing
instance above declares
constructors
SNil :: Sing '[] SCons :: Sing (h :: k) -> Sing (t :: [k]) -> Sing (h ': t)
Basic functions
(%++) :: forall 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) (a :: [a]) :: [a] where ... Source #
Equations
Intersperse _ '[] = '[] | |
Intersperse sep ((:) x xs) = Apply (Apply (:@#@$) x) (Apply (Apply PrependToAllSym0 sep) xs) |
sIntersperse :: forall a (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a]) Source #
type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ... Source #
Equations
Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) |
sIntercalate :: forall a (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a]) Source #
sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]]) Source #
type family Subsequences (a :: [a]) :: [[a]] where ... Source #
Equations
Subsequences xs = Apply (Apply (:@#@$) '[]) (Apply NonEmptySubsequencesSym0 xs) |
sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]]) Source #
type family Permutations (a :: [a]) :: [[a]] where ... Source #
sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]]) Source #
Reducing lists (folds)
type family Foldl (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #
Instances
type Foldl (a1 :: k2 ~> (a6989586621680448453 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680448453]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680448453 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680448453) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
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 (a1 :: k2 ~> (a6989586621680448453 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680448453) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
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 (a1 :: k2 ~> (a6989586621680448453 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680448453) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680448453 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680448453) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680448453 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680448453) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680448453 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680448453) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 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' (a1 :: k2 ~> (a6989586621680448455 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680448455]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
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' (a1 :: k2 ~> (a6989586621680448455 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680448455) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
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' (a1 :: k2 ~> (a6989586621680448455 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680448455) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680448455 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680448455) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680448455 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680448455) 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' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 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 Foldl'Sym0 t) t) t :: b) Source #
type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #
Instances
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
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 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
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 :: 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 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) 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 (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680448448]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Min a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Max a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680448448) 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 (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldr (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a6989586621680448448 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Either a1 a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a6989586621680448448 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: (a1, a6989586621680448448)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a6989586621680448448 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Arg a1 a6989586621680448448) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680448448 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Const m a6989586621680448448) 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 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
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 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
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 :: 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 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) 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 t a b (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) Source #
type family And (a :: t Bool) :: Bool where ... Source #
Equations
And x = Case_6989586621680448935 x (Let6989586621680448933Scrutinee_6989586621680448691Sym1 x) |
type family Or (a :: t Bool) :: Bool where ... Source #
Equations
Or x = Case_6989586621680448926 x (Let6989586621680448924Scrutinee_6989586621680448693Sym1 x) |
type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #
Equations
Any p x = Case_6989586621680448917 p x (Let6989586621680448914Scrutinee_6989586621680448695Sym2 p x) |
sAny :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool) Source #
type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #
Equations
All p x = Case_6989586621680448904 p x (Let6989586621680448901Scrutinee_6989586621680448697Sym2 p x) |
sAll :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) Source #
type family Sum (arg :: t a) :: a Source #
Instances
sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a) Source #
type family Product (arg :: t a) :: a Source #
Instances
sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a) Source #
type family Maximum (arg :: t a) :: a Source #
Instances
sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a) Source #
type family Minimum (arg :: t a) :: a Source #
Instances
sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a) Source #
Building lists
Scans
sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b]) Source #
sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a]) Source #
sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b]) Source #
type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ... Source #
Equations
Scanr1 _ '[] = '[] | |
Scanr1 _ '[x] = Apply (Apply (:@#@$) x) '[] | |
Scanr1 f ((:) x ((:) wild_6989586621679939938 wild_6989586621679939940)) = Case_6989586621679949517 f x wild_6989586621679939938 wild_6989586621679939940 (Let6989586621679949512Scrutinee_6989586621679939932Sym4 f x wild_6989586621679939938 wild_6989586621679939940) |
sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a]) Source #
Accumulating maps
type family MapAccumL (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ... Source #
Equations
MapAccumL f s t = Case_6989586621680751015 f s t (Let6989586621680751011Scrutinee_6989586621680750546Sym3 f s t) |
sMapAccumL :: forall t a b c (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (a, t c)) Source #
type family MapAccumR (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ... Source #
Equations
MapAccumR f s t = Case_6989586621680750998 f s t (Let6989586621680750994Scrutinee_6989586621680750550Sym3 f s t) |
sMapAccumR :: 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 MapAccumRSym0 t) t) t :: (a, t c)) Source #
Cyclical lists
type family Replicate (a :: Nat) (a :: a) :: [a] where ... Source #
Equations
Replicate n x = Case_6989586621679948649 n x (Let6989586621679948646Scrutinee_6989586621679940034Sym2 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 :: (~>) b (Maybe (a, b))) (a :: b) :: [a] where ... Source #
Equations
Unfoldr f b = Case_6989586621679949365 f b (Let6989586621679949362Scrutinee_6989586621679939942Sym2 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 Bool) (a :: [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 Bool) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
Span _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679948803XsSym0) Let6989586621679948803XsSym0 | |
Span p ((:) x xs') = Case_6989586621679948815 p x xs' (Let6989586621679948811Scrutinee_6989586621679940014Sym3 p x xs') |
sSpan :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) Source #
type family Break (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
Break _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679948760XsSym0) Let6989586621679948760XsSym0 | |
Break p ((:) x xs') = Case_6989586621679948772 p x xs' (Let6989586621679948768Scrutinee_6989586621679940016Sym3 p x xs') |
sBreak :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) Source #
type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ... Source #
Equations
StripPrefix '[] ys = Apply JustSym0 ys | |
StripPrefix arg_6989586621680065649 arg_6989586621680065651 = Case_6989586621680078298 arg_6989586621680065649 arg_6989586621680065651 (Apply (Apply Tuple2Sym0 arg_6989586621680065649) arg_6989586621680065651) |
type family Group (a :: [a]) :: [[a]] where ... Source #
Equations
Group xs = Apply (Apply GroupBySym0 (==@#@$)) xs |
Predicates
type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
Equations
IsPrefixOf '[] '[] = TrueSym0 | |
IsPrefixOf '[] ((:) _ _) = TrueSym0 | |
IsPrefixOf ((:) _ _) '[] = FalseSym0 | |
IsPrefixOf ((:) x xs) ((:) y ys) = Apply (Apply (&&@#@$) (Apply (Apply (==@#@$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) |
sIsPrefixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) Source #
type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
Equations
IsSuffixOf x y = Apply (Apply IsPrefixOfSym0 (Apply ReverseSym0 x)) (Apply ReverseSym0 y) |
sIsSuffixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) Source #
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 (a1 :: k1) (a2 :: [k1]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (a1 :: k1) (a2 :: [k1]) | |
type Elem (arg1 :: a) (arg2 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
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 (a1 :: k1) (a2 :: Identity k1) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
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 :: 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 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (arg1 :: a1) (arg2 :: Either a2 a1) 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 t a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) Source #
type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... Source #
Equations
Lookup _key '[] = NothingSym0 | |
Lookup key ((:) '(x, y) xys) = Case_6989586621679948719 key x y xys (Let6989586621679948714Scrutinee_6989586621679940030Sym4 key x y xys) |
sLookup :: forall a b (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b) Source #
Searching with a predicate
type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ... Source #
Equations
Find p y = Case_6989586621680448833 p y (Let6989586621680448816Scrutinee_6989586621680448703Sym2 p y) |
sFind :: forall t a (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) (a :: [a]) :: [Nat] where ... Source #
Equations
ElemIndices x a_6989586621679949279 = Apply (Apply FindIndicesSym0 (Apply (==@#@$) x)) a_6989586621679949279 |
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 Bool) (a :: [a]) :: Maybe Nat where ... Source #
Equations
FindIndex p a_6989586621679949287 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679949287 |
sFindIndex :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat) 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 :: [b]) (a :: [c]) :: [(a, b, c)] where ... Source #
Equations
Zip3 ((:) a as) ((:) b bs) ((:) c cs) = Apply (Apply (:@#@$) (Apply (Apply (Apply Tuple3Sym0 a) b) c)) (Apply (Apply (Apply Zip3Sym0 as) bs) cs) | |
Zip3 '[] '[] '[] = '[] | |
Zip3 '[] '[] ((:) _ _) = '[] | |
Zip3 '[] ((:) _ _) '[] = '[] | |
Zip3 '[] ((:) _ _) ((:) _ _) = '[] | |
Zip3 ((:) _ _) '[] '[] = '[] | |
Zip3 ((:) _ _) '[] ((:) _ _) = '[] | |
Zip3 ((:) _ _) ((:) _ _) '[] = '[] |
sZip3 :: forall a b c (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)]) Source #
type family Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ... Source #
Equations
Zip4 a_6989586621680078271 a_6989586621680078273 a_6989586621680078275 a_6989586621680078277 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621680078271) a_6989586621680078273) a_6989586621680078275) a_6989586621680078277 |
type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ... Source #
Equations
Zip5 a_6989586621680078246 a_6989586621680078248 a_6989586621680078250 a_6989586621680078252 a_6989586621680078254 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621680078246) a_6989586621680078248) a_6989586621680078250) a_6989586621680078252) a_6989586621680078254 |
type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ... Source #
Equations
Zip6 a_6989586621680078216 a_6989586621680078218 a_6989586621680078220 a_6989586621680078222 a_6989586621680078224 a_6989586621680078226 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621680078216) a_6989586621680078218) a_6989586621680078220) a_6989586621680078222) a_6989586621680078224) a_6989586621680078226 |
type family Zip7 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [(a, b, c, d, e, f, g)] where ... Source #
Equations
Zip7 a_6989586621680078181 a_6989586621680078183 a_6989586621680078185 a_6989586621680078187 a_6989586621680078189 a_6989586621680078191 a_6989586621680078193 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621680078181) a_6989586621680078183) a_6989586621680078185) a_6989586621680078187) a_6989586621680078189) a_6989586621680078191) a_6989586621680078193 |
sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c]) Source #
type family ZipWith3 (a :: (~>) a ((~>) b ((~>) c d))) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ... Source #
Equations
ZipWith3 z ((:) a as) ((:) b bs) ((:) c cs) = Apply (Apply (:@#@$) (Apply (Apply (Apply z a) b) c)) (Apply (Apply (Apply (Apply ZipWith3Sym0 z) as) bs) cs) | |
ZipWith3 _ '[] '[] '[] = '[] | |
ZipWith3 _ '[] '[] ((:) _ _) = '[] | |
ZipWith3 _ '[] ((:) _ _) '[] = '[] | |
ZipWith3 _ '[] ((:) _ _) ((:) _ _) = '[] | |
ZipWith3 _ ((:) _ _) '[] '[] = '[] | |
ZipWith3 _ ((:) _ _) '[] ((:) _ _) = '[] | |
ZipWith3 _ ((:) _ _) ((:) _ _) '[] = '[] |
sZipWith3 :: forall a b c d (t :: (~>) a ((~>) b ((~>) c d))) (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d]) Source #
type family ZipWith4 (a :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ... Source #
type family ZipWith5 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ... Source #
type family ZipWith6 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ... Source #
type family ZipWith7 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ... Source #
Equations
ZipWith7 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) ((:) e es) ((:) f fs) ((:) g gs) = Apply (Apply (:@#@$) (Apply (Apply (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e) f) g)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 z) as) bs) cs) ds) es) fs) gs) | |
ZipWith7 _ _ _ _ _ _ _ _ = '[] |
sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c])) Source #
sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d])) Source #
sUnzip5 :: forall a b c d e (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e])) Source #
sUnzip6 :: forall a b c d e f (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f])) Source #
type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... Source #
sUnzip7 :: forall a b c d e f g (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g])) Source #
Special lists
Functions on 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) (a :: [a]) :: [a] where ... Source #
Equations
Insert e ls = Apply (Apply (Apply InsertBySym0 CompareSym0) e) ls |
sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a]) Source #
type family Sort (a :: [a]) :: [a] where ... Source #
Equations
Sort a_6989586621679948969 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679948969 |
Generalized functions
The "By
" operations
User-supplied equality (replacing an Eq
context)
The predicate is assumed to define an equivalence.
sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a]) Source #
sDeleteBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a]) Source #
type family DeleteFirstsBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ... Source #
Equations
DeleteFirstsBy eq a_6989586621679948998 a_6989586621679949000 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679948998) a_6989586621679949000 |
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 Bool)) (a :: [a]) (a :: [a]) :: [a] where ... Source #
Equations
IntersectBy _ '[] '[] = '[] | |
IntersectBy _ '[] ((:) _ _) = '[] | |
IntersectBy _ ((:) _ _) '[] = '[] | |
IntersectBy eq ((:) wild_6989586621679940000 wild_6989586621679940002) ((:) wild_6989586621679940004 wild_6989586621679940006) = Apply (Apply (>>=@#@$) (Let6989586621679949588XsSym5 eq wild_6989586621679940000 wild_6989586621679940002 wild_6989586621679940004 wild_6989586621679940006)) (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679949599Sym0 eq) wild_6989586621679940000) wild_6989586621679940002) wild_6989586621679940004) wild_6989586621679940006) |
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 ((~>) a Ordering)) (a :: t a) :: a where ... Source #
Equations
MaximumBy cmp a_6989586621680448874 = Apply (Apply Foldl1Sym0 (Let6989586621680448878Max'Sym2 cmp a_6989586621680448874)) a_6989586621680448874 |
sMaximumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) Source #
type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #
Equations
MinimumBy cmp a_6989586621680448849 = Apply (Apply Foldl1Sym0 (Let6989586621680448853Min'Sym2 cmp a_6989586621680448849)) a_6989586621680448849 |
sMinimumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) Source #
The "generic
" operations
The prefix `generic
' indicates an overloaded function that
is a generalized version of a Prelude function.
type family GenericLength (a :: [a]) :: i where ... Source #
Equations
GenericLength '[] = FromInteger 0 | |
GenericLength ((:) _ xs) = Apply (Apply (+@#@$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
sGenericLength :: forall i a (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i) Source #
type family GenericTake (a :: i) (a :: [a]) :: [a] where ... Source #
Equations
GenericTake a_6989586621680078071 a_6989586621680078073 = Apply (Apply TakeSym0 a_6989586621680078071) a_6989586621680078073 |
type family GenericDrop (a :: i) (a :: [a]) :: [a] where ... Source #
Equations
GenericDrop a_6989586621680078061 a_6989586621680078063 = Apply (Apply DropSym0 a_6989586621680078061) a_6989586621680078063 |
type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
GenericSplitAt a_6989586621680078051 a_6989586621680078053 = Apply (Apply SplitAtSym0 a_6989586621680078051) a_6989586621680078053 |
type family GenericIndex (a :: [a]) (a :: i) :: a where ... Source #
Equations
GenericIndex a_6989586621680078041 a_6989586621680078043 = Apply (Apply (!!@#@$) a_6989586621680078041) a_6989586621680078043 |
type family GenericReplicate (a :: i) (a :: a) :: [a] where ... Source #
Equations
GenericReplicate a_6989586621680078031 a_6989586621680078033 = Apply (Apply ReplicateSym0 a_6989586621680078031) a_6989586621680078033 |
Defunctionalization symbols
data (:@#@$) :: forall (a3530822107858468865 :: Type). (~>) a3530822107858468865 ((~>) [a3530822107858468865] [(a3530822107858468865 :: Type)]) infixr 5 Source #
Instances
SingI ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((:@#@$) :: TyFun a3530822107858468865 ([a3530822107858468865] ~> [a3530822107858468865]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances Methods suppressUnusedWarnings :: () Source # | |
type Apply ((:@#@$) :: TyFun a3530822107858468865 ([a3530822107858468865] ~> [a3530822107858468865]) -> Type) (t6989586621679301578 :: a3530822107858468865) Source # | |
data (:@#@$$) (t6989586621679301578 :: (a3530822107858468865 :: Type)) :: (~>) [a3530822107858468865] [(a3530822107858468865 :: Type)] infixr 5 Source #
Instances
SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((:@#@$$) t6989586621679301578 :: TyFun [a3530822107858468865] [a3530822107858468865] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances Methods suppressUnusedWarnings :: () Source # | |
type Apply ((:@#@$$) t6989586621679301578 :: TyFun [a] [a] -> Type) (t6989586621679301579 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Instances |
type (:@#@$$$) (t6989586621679301578 :: a3530822107858468865) (t6989586621679301579 :: [a3530822107858468865]) = (:) t6989586621679301578 t6989586621679301579 Source #
type (++@#@$$$) (a6989586621679521912 :: [a6989586621679521715]) (a6989586621679521913 :: [a6989586621679521715]) = (++) a6989586621679521912 a6989586621679521913 Source #
data (++@#@$$) (a6989586621679521912 :: [a6989586621679521715]) :: (~>) [a6989586621679521715] [a6989586621679521715] infixr 5 Source #
Instances
SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((++@#@$$) a6989586621679521912 :: TyFun [a6989586621679521715] [a6989586621679521715] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$$) a6989586621679521912 :: TyFun [a] [a] -> Type) (a6989586621679521913 :: [a]) Source # | |
data (++@#@$) :: forall a6989586621679521715. (~>) [a6989586621679521715] ((~>) [a6989586621679521715] [a6989586621679521715]) infixr 5 Source #
Instances
SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679521715] ([a6989586621679521715] ~> [a6989586621679521715]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$) :: TyFun [a6989586621679521715] ([a6989586621679521715] ~> [a6989586621679521715]) -> Type) (a6989586621679521912 :: [a6989586621679521715]) Source # | |
data HeadSym0 :: forall a6989586621679939457. (~>) [a6989586621679939457] a6989586621679939457 Source #
Instances
SingI (HeadSym0 :: TyFun [a] a -> Type) Source # | |
SuppressUnusedWarnings (HeadSym0 :: TyFun [a6989586621679939457] a6989586621679939457 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679949980 :: [a]) Source # | |
data LastSym0 :: forall a6989586621679939456. (~>) [a6989586621679939456] a6989586621679939456 Source #
Instances
SingI (LastSym0 :: TyFun [a] a -> Type) Source # | |
SuppressUnusedWarnings (LastSym0 :: TyFun [a6989586621679939456] a6989586621679939456 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679949975 :: [a]) Source # | |
data TailSym0 :: forall a6989586621679939455. (~>) [a6989586621679939455] [a6989586621679939455] Source #
Instances
SingI (TailSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (TailSym0 :: TyFun [a6989586621679939455] [a6989586621679939455] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679949972 :: [a]) Source # | |
data InitSym0 :: forall a6989586621679939454. (~>) [a6989586621679939454] [a6989586621679939454] Source #
Instances
SingI (InitSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (InitSym0 :: TyFun [a6989586621679939454] [a6989586621679939454] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679949958 :: [a]) Source # | |
data NullSym0 :: forall a6989586621680448459 t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448459) Bool Source #
Instances
SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680448444 a6989586621680448459) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680449107 :: t a) Source # | |
type NullSym1 (arg6989586621680449107 :: t6989586621680448444 a6989586621680448459) = Null arg6989586621680449107 Source #
data LengthSym0 :: forall a6989586621680448460 t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448460) Nat Source #
Instances
SFoldable t => SingI (LengthSym0 :: TyFun (t a) Nat -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing LengthSym0 Source # | |
SuppressUnusedWarnings (LengthSym0 :: TyFun (t6989586621680448444 a6989586621680448460) Nat -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (arg6989586621680449109 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type LengthSym1 (arg6989586621680449109 :: t6989586621680448444 a6989586621680448460) = Length arg6989586621680449109 Source #
data MapSym0 :: forall a6989586621679521716 b6989586621679521717. (~>) ((~>) a6989586621679521716 b6989586621679521717) ((~>) [a6989586621679521716] [b6989586621679521717]) Source #
Instances
SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (MapSym0 :: TyFun (a6989586621679521716 ~> b6989586621679521717) ([a6989586621679521716] ~> [b6989586621679521717]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapSym0 :: TyFun (a6989586621679521716 ~> b6989586621679521717) ([a6989586621679521716] ~> [b6989586621679521717]) -> Type) (a6989586621679521920 :: a6989586621679521716 ~> b6989586621679521717) Source # | |
data MapSym1 (a6989586621679521920 :: (~>) a6989586621679521716 b6989586621679521717) :: (~>) [a6989586621679521716] [b6989586621679521717] Source #
Instances
SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (MapSym1 a6989586621679521920 :: TyFun [a6989586621679521716] [b6989586621679521717] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapSym1 a6989586621679521920 :: TyFun [a] [b] -> Type) (a6989586621679521921 :: [a]) Source # | |
type MapSym2 (a6989586621679521920 :: (~>) a6989586621679521716 b6989586621679521717) (a6989586621679521921 :: [a6989586621679521716]) = Map a6989586621679521920 a6989586621679521921 Source #
data ReverseSym0 :: forall a6989586621679939452. (~>) [a6989586621679939452] [a6989586621679939452] Source #
Instances
SingI (ReverseSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing ReverseSym0 Source # | |
SuppressUnusedWarnings (ReverseSym0 :: TyFun [a6989586621679939452] [a6989586621679939452] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679949911 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679949911 :: [a]) = Reverse a6989586621679949911 |
type ReverseSym1 (a6989586621679949911 :: [a6989586621679939452]) = Reverse a6989586621679949911 Source #
data IntersperseSym0 :: forall a6989586621679939451. (~>) a6989586621679939451 ((~>) [a6989586621679939451] [a6989586621679939451]) Source #
Instances
SingI (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679939451 ([a6989586621679939451] ~> [a6989586621679939451]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym0 :: TyFun a6989586621679939451 ([a6989586621679939451] ~> [a6989586621679939451]) -> Type) (a6989586621679949898 :: a6989586621679939451) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym0 :: TyFun a6989586621679939451 ([a6989586621679939451] ~> [a6989586621679939451]) -> Type) (a6989586621679949898 :: a6989586621679939451) = IntersperseSym1 a6989586621679949898 |
data IntersperseSym1 (a6989586621679949898 :: a6989586621679939451) :: (~>) [a6989586621679939451] [a6989586621679939451] Source #
Instances
SingI d => SingI (IntersperseSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IntersperseSym1 d) Source # | |
SuppressUnusedWarnings (IntersperseSym1 a6989586621679949898 :: TyFun [a6989586621679939451] [a6989586621679939451] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym1 a6989586621679949898 :: TyFun [a] [a] -> Type) (a6989586621679949899 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym1 a6989586621679949898 :: TyFun [a] [a] -> Type) (a6989586621679949899 :: [a]) = Intersperse a6989586621679949898 a6989586621679949899 |
type IntersperseSym2 (a6989586621679949898 :: a6989586621679939451) (a6989586621679949899 :: [a6989586621679939451]) = Intersperse a6989586621679949898 a6989586621679949899 Source #
data IntercalateSym0 :: forall a6989586621679939450. (~>) [a6989586621679939450] ((~>) [[a6989586621679939450]] [a6989586621679939450]) Source #
Instances
SingI (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a6989586621679939450] ([[a6989586621679939450]] ~> [a6989586621679939450]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym0 :: TyFun [a6989586621679939450] ([[a6989586621679939450]] ~> [a6989586621679939450]) -> Type) (a6989586621679949905 :: [a6989586621679939450]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym0 :: TyFun [a6989586621679939450] ([[a6989586621679939450]] ~> [a6989586621679939450]) -> Type) (a6989586621679949905 :: [a6989586621679939450]) = IntercalateSym1 a6989586621679949905 |
data IntercalateSym1 (a6989586621679949905 :: [a6989586621679939450]) :: (~>) [[a6989586621679939450]] [a6989586621679939450] Source #
Instances
SingI d => SingI (IntercalateSym1 d :: TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IntercalateSym1 d) Source # | |
SuppressUnusedWarnings (IntercalateSym1 a6989586621679949905 :: TyFun [[a6989586621679939450]] [a6989586621679939450] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym1 a6989586621679949905 :: TyFun [[a]] [a] -> Type) (a6989586621679949906 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym1 a6989586621679949905 :: TyFun [[a]] [a] -> Type) (a6989586621679949906 :: [[a]]) = Intercalate a6989586621679949905 a6989586621679949906 |
type IntercalateSym2 (a6989586621679949905 :: [a6989586621679939450]) (a6989586621679949906 :: [[a6989586621679939450]]) = Intercalate a6989586621679949905 a6989586621679949906 Source #
data TransposeSym0 :: forall a6989586621679939337. (~>) [[a6989586621679939337]] [[a6989586621679939337]] Source #
Instances
SingI (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing TransposeSym0 Source # | |
SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a6989586621679939337]] [[a6989586621679939337]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679949983 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679949983 :: [[a]]) = Transpose a6989586621679949983 |
type TransposeSym1 (a6989586621679949983 :: [[a6989586621679939337]]) = Transpose a6989586621679949983 Source #
data SubsequencesSym0 :: forall a6989586621679939449. (~>) [a6989586621679939449] [[a6989586621679939449]] Source #
Instances
SingI (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a6989586621679939449] [[a6989586621679939449]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679949895 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679949895 :: [a]) = Subsequences a6989586621679949895 |
type SubsequencesSym1 (a6989586621679949895 :: [a6989586621679939449]) = Subsequences a6989586621679949895 Source #
data PermutationsSym0 :: forall a6989586621679939446. (~>) [a6989586621679939446] [[a6989586621679939446]] Source #
Instances
SingI (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a6989586621679939446] [[a6989586621679939446]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679949777 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679949777 :: [a]) = Permutations a6989586621679949777 |
type PermutationsSym1 (a6989586621679949777 :: [a6989586621679939446]) = Permutations a6989586621679949777 Source #
data FoldlSym0 :: forall a6989586621680448453 b6989586621680448452 t6989586621680448444. (~>) ((~>) b6989586621680448452 ((~>) a6989586621680448453 b6989586621680448452)) ((~>) b6989586621680448452 ((~>) (t6989586621680448444 a6989586621680448453) b6989586621680448452)) Source #
Instances
SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym0 :: TyFun (b6989586621680448452 ~> (a6989586621680448453 ~> b6989586621680448452)) (b6989586621680448452 ~> (t6989586621680448444 a6989586621680448453 ~> b6989586621680448452)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym0 :: TyFun (b6989586621680448452 ~> (a6989586621680448453 ~> b6989586621680448452)) (b6989586621680448452 ~> (t6989586621680448444 a6989586621680448453 ~> b6989586621680448452)) -> Type) (arg6989586621680449085 :: b6989586621680448452 ~> (a6989586621680448453 ~> b6989586621680448452)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldlSym0 :: TyFun (b6989586621680448452 ~> (a6989586621680448453 ~> b6989586621680448452)) (b6989586621680448452 ~> (t6989586621680448444 a6989586621680448453 ~> b6989586621680448452)) -> Type) (arg6989586621680449085 :: b6989586621680448452 ~> (a6989586621680448453 ~> b6989586621680448452)) = (FoldlSym1 arg6989586621680449085 t6989586621680448444 :: TyFun b6989586621680448452 (t6989586621680448444 a6989586621680448453 ~> b6989586621680448452) -> Type) |
data FoldlSym1 (arg6989586621680449085 :: (~>) b6989586621680448452 ((~>) a6989586621680448453 b6989586621680448452)) :: forall t6989586621680448444. (~>) b6989586621680448452 ((~>) (t6989586621680448444 a6989586621680448453) b6989586621680448452) Source #
Instances
(SFoldable t, SingI d) => SingI (FoldlSym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym1 arg6989586621680449085 t6989586621680448444 :: TyFun b6989586621680448452 (t6989586621680448444 a6989586621680448453 ~> b6989586621680448452) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym1 arg6989586621680449085 t6989586621680448444 :: TyFun b6989586621680448452 (t6989586621680448444 a6989586621680448453 ~> b6989586621680448452) -> Type) (arg6989586621680449086 :: b6989586621680448452) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldlSym1 arg6989586621680449085 t6989586621680448444 :: TyFun b6989586621680448452 (t6989586621680448444 a6989586621680448453 ~> b6989586621680448452) -> Type) (arg6989586621680449086 :: b6989586621680448452) = (FoldlSym2 arg6989586621680449085 arg6989586621680449086 t6989586621680448444 :: TyFun (t6989586621680448444 a6989586621680448453) b6989586621680448452 -> Type) |
data FoldlSym2 (arg6989586621680449085 :: (~>) b6989586621680448452 ((~>) a6989586621680448453 b6989586621680448452)) (arg6989586621680449086 :: b6989586621680448452) :: forall t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448453) b6989586621680448452 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym2 arg6989586621680449086 arg6989586621680449085 t6989586621680448444 :: TyFun (t6989586621680448444 a6989586621680448453) b6989586621680448452 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym2 arg6989586621680449086 arg6989586621680449085 t :: TyFun (t a) b -> Type) (arg6989586621680449087 :: t a) Source # | |
type FoldlSym3 (arg6989586621680449085 :: (~>) b6989586621680448452 ((~>) a6989586621680448453 b6989586621680448452)) (arg6989586621680449086 :: b6989586621680448452) (arg6989586621680449087 :: t6989586621680448444 a6989586621680448453) = Foldl arg6989586621680449085 arg6989586621680449086 arg6989586621680449087 Source #
data Foldl'Sym0 :: forall a6989586621680448455 b6989586621680448454 t6989586621680448444. (~>) ((~>) b6989586621680448454 ((~>) a6989586621680448455 b6989586621680448454)) ((~>) b6989586621680448454 ((~>) (t6989586621680448444 a6989586621680448455) b6989586621680448454)) Source #
Instances
SFoldable t => SingI (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing Foldl'Sym0 Source # | |
SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (b6989586621680448454 ~> (a6989586621680448455 ~> b6989586621680448454)) (b6989586621680448454 ~> (t6989586621680448444 a6989586621680448455 ~> b6989586621680448454)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym0 :: TyFun (b6989586621680448454 ~> (a6989586621680448455 ~> b6989586621680448454)) (b6989586621680448454 ~> (t6989586621680448444 a6989586621680448455 ~> b6989586621680448454)) -> Type) (arg6989586621680449091 :: b6989586621680448454 ~> (a6989586621680448455 ~> b6989586621680448454)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym0 :: TyFun (b6989586621680448454 ~> (a6989586621680448455 ~> b6989586621680448454)) (b6989586621680448454 ~> (t6989586621680448444 a6989586621680448455 ~> b6989586621680448454)) -> Type) (arg6989586621680449091 :: b6989586621680448454 ~> (a6989586621680448455 ~> b6989586621680448454)) = (Foldl'Sym1 arg6989586621680449091 t6989586621680448444 :: TyFun b6989586621680448454 (t6989586621680448444 a6989586621680448455 ~> b6989586621680448454) -> Type) |
data Foldl'Sym1 (arg6989586621680449091 :: (~>) b6989586621680448454 ((~>) a6989586621680448455 b6989586621680448454)) :: forall t6989586621680448444. (~>) b6989586621680448454 ((~>) (t6989586621680448444 a6989586621680448455) b6989586621680448454) Source #
Instances
(SFoldable t, SingI d) => SingI (Foldl'Sym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (Foldl'Sym1 d t) Source # | |
SuppressUnusedWarnings (Foldl'Sym1 arg6989586621680449091 t6989586621680448444 :: TyFun b6989586621680448454 (t6989586621680448444 a6989586621680448455 ~> b6989586621680448454) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym1 arg6989586621680449091 t6989586621680448444 :: TyFun b6989586621680448454 (t6989586621680448444 a6989586621680448455 ~> b6989586621680448454) -> Type) (arg6989586621680449092 :: b6989586621680448454) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym1 arg6989586621680449091 t6989586621680448444 :: TyFun b6989586621680448454 (t6989586621680448444 a6989586621680448455 ~> b6989586621680448454) -> Type) (arg6989586621680449092 :: b6989586621680448454) = (Foldl'Sym2 arg6989586621680449091 arg6989586621680449092 t6989586621680448444 :: TyFun (t6989586621680448444 a6989586621680448455) b6989586621680448454 -> Type) |
data Foldl'Sym2 (arg6989586621680449091 :: (~>) b6989586621680448454 ((~>) a6989586621680448455 b6989586621680448454)) (arg6989586621680449092 :: b6989586621680448454) :: forall t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448455) b6989586621680448454 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (Foldl'Sym2 d1 d2 t :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (Foldl'Sym2 d1 d2 t) Source # | |
SuppressUnusedWarnings (Foldl'Sym2 arg6989586621680449092 arg6989586621680449091 t6989586621680448444 :: TyFun (t6989586621680448444 a6989586621680448455) b6989586621680448454 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym2 arg6989586621680449092 arg6989586621680449091 t :: TyFun (t a) b -> Type) (arg6989586621680449093 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym2 arg6989586621680449092 arg6989586621680449091 t :: TyFun (t a) b -> Type) (arg6989586621680449093 :: t a) = Foldl' arg6989586621680449092 arg6989586621680449091 arg6989586621680449093 |
type Foldl'Sym3 (arg6989586621680449091 :: (~>) b6989586621680448454 ((~>) a6989586621680448455 b6989586621680448454)) (arg6989586621680449092 :: b6989586621680448454) (arg6989586621680449093 :: t6989586621680448444 a6989586621680448455) = Foldl' arg6989586621680449091 arg6989586621680449092 arg6989586621680449093 Source #
data Foldl1Sym0 :: forall a6989586621680448457 t6989586621680448444. (~>) ((~>) a6989586621680448457 ((~>) a6989586621680448457 a6989586621680448457)) ((~>) (t6989586621680448444 a6989586621680448457) a6989586621680448457) Source #
Instances
SFoldable t => SingI (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing Foldl1Sym0 Source # | |
SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (a6989586621680448457 ~> (a6989586621680448457 ~> a6989586621680448457)) (t6989586621680448444 a6989586621680448457 ~> a6989586621680448457) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym0 :: TyFun (a6989586621680448457 ~> (a6989586621680448457 ~> a6989586621680448457)) (t6989586621680448444 a6989586621680448457 ~> a6989586621680448457) -> Type) (arg6989586621680449101 :: a6989586621680448457 ~> (a6989586621680448457 ~> a6989586621680448457)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl1Sym0 :: TyFun (a6989586621680448457 ~> (a6989586621680448457 ~> a6989586621680448457)) (t6989586621680448444 a6989586621680448457 ~> a6989586621680448457) -> Type) (arg6989586621680449101 :: a6989586621680448457 ~> (a6989586621680448457 ~> a6989586621680448457)) = (Foldl1Sym1 arg6989586621680449101 t6989586621680448444 :: TyFun (t6989586621680448444 a6989586621680448457) a6989586621680448457 -> Type) |
data Foldl1Sym1 (arg6989586621680449101 :: (~>) a6989586621680448457 ((~>) a6989586621680448457 a6989586621680448457)) :: forall t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448457) a6989586621680448457 Source #
Instances
(SFoldable t, SingI d) => SingI (Foldl1Sym1 d t :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (Foldl1Sym1 d t) Source # | |
SuppressUnusedWarnings (Foldl1Sym1 arg6989586621680449101 t6989586621680448444 :: TyFun (t6989586621680448444 a6989586621680448457) a6989586621680448457 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym1 arg6989586621680449101 t :: TyFun (t a) a -> Type) (arg6989586621680449102 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl1Sym1 arg6989586621680449101 t :: TyFun (t a) a -> Type) (arg6989586621680449102 :: t a) = Foldl1 arg6989586621680449101 arg6989586621680449102 |
type Foldl1Sym2 (arg6989586621680449101 :: (~>) a6989586621680448457 ((~>) a6989586621680448457 a6989586621680448457)) (arg6989586621680449102 :: t6989586621680448444 a6989586621680448457) = Foldl1 arg6989586621680449101 arg6989586621680449102 Source #
data Foldl1'Sym0 :: forall a6989586621679939442. (~>) ((~>) a6989586621679939442 ((~>) a6989586621679939442 a6989586621679939442)) ((~>) [a6989586621679939442] a6989586621679939442) Source #
Instances
SingI (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Foldl1'Sym0 Source # | |
SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (a6989586621679939442 ~> (a6989586621679939442 ~> a6989586621679939442)) ([a6989586621679939442] ~> a6989586621679939442) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym0 :: TyFun (a6989586621679939442 ~> (a6989586621679939442 ~> a6989586621679939442)) ([a6989586621679939442] ~> a6989586621679939442) -> Type) (a6989586621679949770 :: a6989586621679939442 ~> (a6989586621679939442 ~> a6989586621679939442)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym0 :: TyFun (a6989586621679939442 ~> (a6989586621679939442 ~> a6989586621679939442)) ([a6989586621679939442] ~> a6989586621679939442) -> Type) (a6989586621679949770 :: a6989586621679939442 ~> (a6989586621679939442 ~> a6989586621679939442)) = Foldl1'Sym1 a6989586621679949770 |
data Foldl1'Sym1 (a6989586621679949770 :: (~>) a6989586621679939442 ((~>) a6989586621679939442 a6989586621679939442)) :: (~>) [a6989586621679939442] a6989586621679939442 Source #
Instances
SingI d => SingI (Foldl1'Sym1 d :: TyFun [a] a -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (Foldl1'Sym1 d) Source # | |
SuppressUnusedWarnings (Foldl1'Sym1 a6989586621679949770 :: TyFun [a6989586621679939442] a6989586621679939442 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym1 a6989586621679949770 :: TyFun [a] a -> Type) (a6989586621679949771 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym1 a6989586621679949770 :: TyFun [a] a -> Type) (a6989586621679949771 :: [a]) = Foldl1' a6989586621679949770 a6989586621679949771 |
type Foldl1'Sym2 (a6989586621679949770 :: (~>) a6989586621679939442 ((~>) a6989586621679939442 a6989586621679939442)) (a6989586621679949771 :: [a6989586621679939442]) = Foldl1' a6989586621679949770 a6989586621679949771 Source #
data FoldrSym0 :: forall a6989586621680448448 b6989586621680448449 t6989586621680448444. (~>) ((~>) a6989586621680448448 ((~>) b6989586621680448449 b6989586621680448449)) ((~>) b6989586621680448449 ((~>) (t6989586621680448444 a6989586621680448448) b6989586621680448449)) Source #
Instances
SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym0 :: TyFun (a6989586621680448448 ~> (b6989586621680448449 ~> b6989586621680448449)) (b6989586621680448449 ~> (t6989586621680448444 a6989586621680448448 ~> b6989586621680448449)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym0 :: TyFun (a6989586621680448448 ~> (b6989586621680448449 ~> b6989586621680448449)) (b6989586621680448449 ~> (t6989586621680448444 a6989586621680448448 ~> b6989586621680448449)) -> Type) (arg6989586621680449073 :: a6989586621680448448 ~> (b6989586621680448449 ~> b6989586621680448449)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldrSym0 :: TyFun (a6989586621680448448 ~> (b6989586621680448449 ~> b6989586621680448449)) (b6989586621680448449 ~> (t6989586621680448444 a6989586621680448448 ~> b6989586621680448449)) -> Type) (arg6989586621680449073 :: a6989586621680448448 ~> (b6989586621680448449 ~> b6989586621680448449)) = (FoldrSym1 arg6989586621680449073 t6989586621680448444 :: TyFun b6989586621680448449 (t6989586621680448444 a6989586621680448448 ~> b6989586621680448449) -> Type) |
data FoldrSym1 (arg6989586621680449073 :: (~>) a6989586621680448448 ((~>) b6989586621680448449 b6989586621680448449)) :: forall t6989586621680448444. (~>) b6989586621680448449 ((~>) (t6989586621680448444 a6989586621680448448) b6989586621680448449) Source #
Instances
(SFoldable t, SingI d) => SingI (FoldrSym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym1 arg6989586621680449073 t6989586621680448444 :: TyFun b6989586621680448449 (t6989586621680448444 a6989586621680448448 ~> b6989586621680448449) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym1 arg6989586621680449073 t6989586621680448444 :: TyFun b6989586621680448449 (t6989586621680448444 a6989586621680448448 ~> b6989586621680448449) -> Type) (arg6989586621680449074 :: b6989586621680448449) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldrSym1 arg6989586621680449073 t6989586621680448444 :: TyFun b6989586621680448449 (t6989586621680448444 a6989586621680448448 ~> b6989586621680448449) -> Type) (arg6989586621680449074 :: b6989586621680448449) = (FoldrSym2 arg6989586621680449073 arg6989586621680449074 t6989586621680448444 :: TyFun (t6989586621680448444 a6989586621680448448) b6989586621680448449 -> Type) |
data FoldrSym2 (arg6989586621680449073 :: (~>) a6989586621680448448 ((~>) b6989586621680448449 b6989586621680448449)) (arg6989586621680449074 :: b6989586621680448449) :: forall t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448448) b6989586621680448449 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym2 arg6989586621680449074 arg6989586621680449073 t6989586621680448444 :: TyFun (t6989586621680448444 a6989586621680448448) b6989586621680448449 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym2 arg6989586621680449074 arg6989586621680449073 t :: TyFun (t a) b -> Type) (arg6989586621680449075 :: t a) Source # | |
type FoldrSym3 (arg6989586621680449073 :: (~>) a6989586621680448448 ((~>) b6989586621680448449 b6989586621680448449)) (arg6989586621680449074 :: b6989586621680448449) (arg6989586621680449075 :: t6989586621680448444 a6989586621680448448) = Foldr arg6989586621680449073 arg6989586621680449074 arg6989586621680449075 Source #
data Foldr1Sym0 :: forall a6989586621680448456 t6989586621680448444. (~>) ((~>) a6989586621680448456 ((~>) a6989586621680448456 a6989586621680448456)) ((~>) (t6989586621680448444 a6989586621680448456) a6989586621680448456) Source #
Instances
SFoldable t => SingI (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing Foldr1Sym0 Source # | |
SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (a6989586621680448456 ~> (a6989586621680448456 ~> a6989586621680448456)) (t6989586621680448444 a6989586621680448456 ~> a6989586621680448456) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym0 :: TyFun (a6989586621680448456 ~> (a6989586621680448456 ~> a6989586621680448456)) (t6989586621680448444 a6989586621680448456 ~> a6989586621680448456) -> Type) (arg6989586621680449097 :: a6989586621680448456 ~> (a6989586621680448456 ~> a6989586621680448456)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr1Sym0 :: TyFun (a6989586621680448456 ~> (a6989586621680448456 ~> a6989586621680448456)) (t6989586621680448444 a6989586621680448456 ~> a6989586621680448456) -> Type) (arg6989586621680449097 :: a6989586621680448456 ~> (a6989586621680448456 ~> a6989586621680448456)) = (Foldr1Sym1 arg6989586621680449097 t6989586621680448444 :: TyFun (t6989586621680448444 a6989586621680448456) a6989586621680448456 -> Type) |
data Foldr1Sym1 (arg6989586621680449097 :: (~>) a6989586621680448456 ((~>) a6989586621680448456 a6989586621680448456)) :: forall t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448456) a6989586621680448456 Source #
Instances
(SFoldable t, SingI d) => SingI (Foldr1Sym1 d t :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (Foldr1Sym1 d t) Source # | |
SuppressUnusedWarnings (Foldr1Sym1 arg6989586621680449097 t6989586621680448444 :: TyFun (t6989586621680448444 a6989586621680448456) a6989586621680448456 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym1 arg6989586621680449097 t :: TyFun (t a) a -> Type) (arg6989586621680449098 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr1Sym1 arg6989586621680449097 t :: TyFun (t a) a -> Type) (arg6989586621680449098 :: t a) = Foldr1 arg6989586621680449097 arg6989586621680449098 |
type Foldr1Sym2 (arg6989586621680449097 :: (~>) a6989586621680448456 ((~>) a6989586621680448456 a6989586621680448456)) (arg6989586621680449098 :: t6989586621680448444 a6989586621680448456) = Foldr1 arg6989586621680449097 arg6989586621680449098 Source #
data ConcatSym0 :: forall a6989586621680448370 t6989586621680448369. (~>) (t6989586621680448369 [a6989586621680448370]) [a6989586621680448370] Source #
Instances
SFoldable t => SingI (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing ConcatSym0 Source # | |
SuppressUnusedWarnings (ConcatSym0 :: TyFun (t6989586621680448369 [a6989586621680448370]) [a6989586621680448370] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680448955 :: t [a]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680448955 :: t [a]) = Concat a6989586621680448955 |
type ConcatSym1 (a6989586621680448955 :: t6989586621680448369 [a6989586621680448370]) = Concat a6989586621680448955 Source #
data ConcatMapSym0 :: forall a6989586621680448367 b6989586621680448368 t6989586621680448366. (~>) ((~>) a6989586621680448367 [b6989586621680448368]) ((~>) (t6989586621680448366 a6989586621680448367) [b6989586621680448368]) Source #
Instances
SFoldable t => SingI (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing ConcatMapSym0 Source # | |
SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (a6989586621680448367 ~> [b6989586621680448368]) (t6989586621680448366 a6989586621680448367 ~> [b6989586621680448368]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym0 :: TyFun (a6989586621680448367 ~> [b6989586621680448368]) (t6989586621680448366 a6989586621680448367 ~> [b6989586621680448368]) -> Type) (a6989586621680448939 :: a6989586621680448367 ~> [b6989586621680448368]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym0 :: TyFun (a6989586621680448367 ~> [b6989586621680448368]) (t6989586621680448366 a6989586621680448367 ~> [b6989586621680448368]) -> Type) (a6989586621680448939 :: a6989586621680448367 ~> [b6989586621680448368]) = (ConcatMapSym1 a6989586621680448939 t6989586621680448366 :: TyFun (t6989586621680448366 a6989586621680448367) [b6989586621680448368] -> Type) |
data ConcatMapSym1 (a6989586621680448939 :: (~>) a6989586621680448367 [b6989586621680448368]) :: forall t6989586621680448366. (~>) (t6989586621680448366 a6989586621680448367) [b6989586621680448368] Source #
Instances
(SFoldable t, SingI d) => SingI (ConcatMapSym1 d t :: TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (ConcatMapSym1 d t) Source # | |
SuppressUnusedWarnings (ConcatMapSym1 a6989586621680448939 t6989586621680448366 :: TyFun (t6989586621680448366 a6989586621680448367) [b6989586621680448368] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym1 a6989586621680448939 t :: TyFun (t a) [b] -> Type) (a6989586621680448940 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym1 a6989586621680448939 t :: TyFun (t a) [b] -> Type) (a6989586621680448940 :: t a) = ConcatMap a6989586621680448939 a6989586621680448940 |
type ConcatMapSym2 (a6989586621680448939 :: (~>) a6989586621680448367 [b6989586621680448368]) (a6989586621680448940 :: t6989586621680448366 a6989586621680448367) = ConcatMap a6989586621680448939 a6989586621680448940 Source #
data AndSym0 :: forall t6989586621680448365. (~>) (t6989586621680448365 Bool) Bool Source #
Instances
SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
SuppressUnusedWarnings (AndSym0 :: TyFun (t6989586621680448365 Bool) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680448930 :: t Bool) Source # | |
type AndSym1 (a6989586621680448930 :: t6989586621680448365 Bool) = And a6989586621680448930 Source #
data OrSym0 :: forall t6989586621680448364. (~>) (t6989586621680448364 Bool) Bool Source #
Instances
SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
SuppressUnusedWarnings (OrSym0 :: TyFun (t6989586621680448364 Bool) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680448921 :: t Bool) Source # | |
data AnySym0 :: forall a6989586621680448363 t6989586621680448362. (~>) ((~>) a6989586621680448363 Bool) ((~>) (t6989586621680448362 a6989586621680448363) Bool) Source #
Instances
SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (AnySym0 :: TyFun (a6989586621680448363 ~> Bool) (t6989586621680448362 a6989586621680448363 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AnySym0 :: TyFun (a6989586621680448363 ~> Bool) (t6989586621680448362 a6989586621680448363 ~> Bool) -> Type) (a6989586621680448908 :: a6989586621680448363 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data AnySym1 (a6989586621680448908 :: (~>) a6989586621680448363 Bool) :: forall t6989586621680448362. (~>) (t6989586621680448362 a6989586621680448363) Bool Source #
Instances
(SFoldable t, SingI d) => SingI (AnySym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (AnySym1 a6989586621680448908 t6989586621680448362 :: TyFun (t6989586621680448362 a6989586621680448363) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AnySym1 a6989586621680448908 t :: TyFun (t a) Bool -> Type) (a6989586621680448909 :: t a) Source # | |
type AnySym2 (a6989586621680448908 :: (~>) a6989586621680448363 Bool) (a6989586621680448909 :: t6989586621680448362 a6989586621680448363) = Any a6989586621680448908 a6989586621680448909 Source #
data AllSym0 :: forall a6989586621680448361 t6989586621680448360. (~>) ((~>) a6989586621680448361 Bool) ((~>) (t6989586621680448360 a6989586621680448361) Bool) Source #
Instances
SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (AllSym0 :: TyFun (a6989586621680448361 ~> Bool) (t6989586621680448360 a6989586621680448361 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AllSym0 :: TyFun (a6989586621680448361 ~> Bool) (t6989586621680448360 a6989586621680448361 ~> Bool) -> Type) (a6989586621680448895 :: a6989586621680448361 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data AllSym1 (a6989586621680448895 :: (~>) a6989586621680448361 Bool) :: forall t6989586621680448360. (~>) (t6989586621680448360 a6989586621680448361) Bool Source #
Instances
(SFoldable t, SingI d) => SingI (AllSym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (AllSym1 a6989586621680448895 t6989586621680448360 :: TyFun (t6989586621680448360 a6989586621680448361) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AllSym1 a6989586621680448895 t :: TyFun (t a) Bool -> Type) (a6989586621680448896 :: t a) Source # | |
type AllSym2 (a6989586621680448895 :: (~>) a6989586621680448361 Bool) (a6989586621680448896 :: t6989586621680448360 a6989586621680448361) = All a6989586621680448895 a6989586621680448896 Source #
data SumSym0 :: forall a6989586621680448464 t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448464) a6989586621680448464 Source #
Instances
(SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # | |
SuppressUnusedWarnings (SumSym0 :: TyFun (t6989586621680448444 a6989586621680448464) a6989586621680448464 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (SumSym0 :: TyFun (t a) a -> Type) (arg6989586621680449119 :: t a) Source # | |
type SumSym1 (arg6989586621680449119 :: t6989586621680448444 a6989586621680448464) = Sum arg6989586621680449119 Source #
data ProductSym0 :: forall a6989586621680448465 t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448465) a6989586621680448465 Source #
Instances
(SFoldable t, SNum a) => SingI (ProductSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing ProductSym0 Source # | |
SuppressUnusedWarnings (ProductSym0 :: TyFun (t6989586621680448444 a6989586621680448465) a6989586621680448465 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680449121 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680449121 :: t a) = Product arg6989586621680449121 |
type ProductSym1 (arg6989586621680449121 :: t6989586621680448444 a6989586621680448465) = Product arg6989586621680449121 Source #
data MaximumSym0 :: forall a6989586621680448462 t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448462) a6989586621680448462 Source #
Instances
(SFoldable t, SOrd a) => SingI (MaximumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing MaximumSym0 Source # | |
SuppressUnusedWarnings (MaximumSym0 :: TyFun (t6989586621680448444 a6989586621680448462) a6989586621680448462 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680449115 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680449115 :: t a) = Maximum arg6989586621680449115 |
type MaximumSym1 (arg6989586621680449115 :: t6989586621680448444 a6989586621680448462) = Maximum arg6989586621680449115 Source #
data MinimumSym0 :: forall a6989586621680448463 t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448463) a6989586621680448463 Source #
Instances
(SFoldable t, SOrd a) => SingI (MinimumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing MinimumSym0 Source # | |
SuppressUnusedWarnings (MinimumSym0 :: TyFun (t6989586621680448444 a6989586621680448463) a6989586621680448463 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680449117 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680449117 :: t a) = Minimum arg6989586621680449117 |
type MinimumSym1 (arg6989586621680449117 :: t6989586621680448444 a6989586621680448463) = Minimum arg6989586621680449117 Source #
data ScanlSym0 :: forall a6989586621679939435 b6989586621679939434. (~>) ((~>) b6989586621679939434 ((~>) a6989586621679939435 b6989586621679939434)) ((~>) b6989586621679939434 ((~>) [a6989586621679939435] [b6989586621679939434])) Source #
Instances
SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym0 :: TyFun (b6989586621679939434 ~> (a6989586621679939435 ~> b6989586621679939434)) (b6989586621679939434 ~> ([a6989586621679939435] ~> [b6989586621679939434])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym0 :: TyFun (b6989586621679939434 ~> (a6989586621679939435 ~> b6989586621679939434)) (b6989586621679939434 ~> ([a6989586621679939435] ~> [b6989586621679939434])) -> Type) (a6989586621679949543 :: b6989586621679939434 ~> (a6989586621679939435 ~> b6989586621679939434)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ScanlSym0 :: TyFun (b6989586621679939434 ~> (a6989586621679939435 ~> b6989586621679939434)) (b6989586621679939434 ~> ([a6989586621679939435] ~> [b6989586621679939434])) -> Type) (a6989586621679949543 :: b6989586621679939434 ~> (a6989586621679939435 ~> b6989586621679939434)) = ScanlSym1 a6989586621679949543 |
data ScanlSym1 (a6989586621679949543 :: (~>) b6989586621679939434 ((~>) a6989586621679939435 b6989586621679939434)) :: (~>) b6989586621679939434 ((~>) [a6989586621679939435] [b6989586621679939434]) Source #
Instances
SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym1 a6989586621679949543 :: TyFun b6989586621679939434 ([a6989586621679939435] ~> [b6989586621679939434]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym1 a6989586621679949543 :: TyFun b6989586621679939434 ([a6989586621679939435] ~> [b6989586621679939434]) -> Type) (a6989586621679949544 :: b6989586621679939434) Source # | |
data ScanlSym2 (a6989586621679949543 :: (~>) b6989586621679939434 ((~>) a6989586621679939435 b6989586621679939434)) (a6989586621679949544 :: b6989586621679939434) :: (~>) [a6989586621679939435] [b6989586621679939434] Source #
Instances
(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym2 a6989586621679949544 a6989586621679949543 :: TyFun [a6989586621679939435] [b6989586621679939434] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym2 a6989586621679949544 a6989586621679949543 :: TyFun [a] [b] -> Type) (a6989586621679949545 :: [a]) Source # | |
type ScanlSym3 (a6989586621679949543 :: (~>) b6989586621679939434 ((~>) a6989586621679939435 b6989586621679939434)) (a6989586621679949544 :: b6989586621679939434) (a6989586621679949545 :: [a6989586621679939435]) = Scanl a6989586621679949543 a6989586621679949544 a6989586621679949545 Source #
data Scanl1Sym0 :: forall a6989586621679939433. (~>) ((~>) a6989586621679939433 ((~>) a6989586621679939433 a6989586621679939433)) ((~>) [a6989586621679939433] [a6989586621679939433]) Source #
Instances
SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Scanl1Sym0 Source # | |
SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a6989586621679939433 ~> (a6989586621679939433 ~> a6989586621679939433)) ([a6989586621679939433] ~> [a6989586621679939433]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym0 :: TyFun (a6989586621679939433 ~> (a6989586621679939433 ~> a6989586621679939433)) ([a6989586621679939433] ~> [a6989586621679939433]) -> Type) (a6989586621679949557 :: a6989586621679939433 ~> (a6989586621679939433 ~> a6989586621679939433)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym0 :: TyFun (a6989586621679939433 ~> (a6989586621679939433 ~> a6989586621679939433)) ([a6989586621679939433] ~> [a6989586621679939433]) -> Type) (a6989586621679949557 :: a6989586621679939433 ~> (a6989586621679939433 ~> a6989586621679939433)) = Scanl1Sym1 a6989586621679949557 |
data Scanl1Sym1 (a6989586621679949557 :: (~>) a6989586621679939433 ((~>) a6989586621679939433 a6989586621679939433)) :: (~>) [a6989586621679939433] [a6989586621679939433] Source #
Instances
SingI d => SingI (Scanl1Sym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (Scanl1Sym1 d) Source # | |
SuppressUnusedWarnings (Scanl1Sym1 a6989586621679949557 :: TyFun [a6989586621679939433] [a6989586621679939433] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym1 a6989586621679949557 :: TyFun [a] [a] -> Type) (a6989586621679949558 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym1 a6989586621679949557 :: TyFun [a] [a] -> Type) (a6989586621679949558 :: [a]) = Scanl1 a6989586621679949557 a6989586621679949558 |
type Scanl1Sym2 (a6989586621679949557 :: (~>) a6989586621679939433 ((~>) a6989586621679939433 a6989586621679939433)) (a6989586621679949558 :: [a6989586621679939433]) = Scanl1 a6989586621679949557 a6989586621679949558 Source #
data ScanrSym0 :: forall a6989586621679939431 b6989586621679939432. (~>) ((~>) a6989586621679939431 ((~>) b6989586621679939432 b6989586621679939432)) ((~>) b6989586621679939432 ((~>) [a6989586621679939431] [b6989586621679939432])) Source #
Instances
SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym0 :: TyFun (a6989586621679939431 ~> (b6989586621679939432 ~> b6989586621679939432)) (b6989586621679939432 ~> ([a6989586621679939431] ~> [b6989586621679939432])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym0 :: TyFun (a6989586621679939431 ~> (b6989586621679939432 ~> b6989586621679939432)) (b6989586621679939432 ~> ([a6989586621679939431] ~> [b6989586621679939432])) -> Type) (a6989586621679949522 :: a6989586621679939431 ~> (b6989586621679939432 ~> b6989586621679939432)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ScanrSym0 :: TyFun (a6989586621679939431 ~> (b6989586621679939432 ~> b6989586621679939432)) (b6989586621679939432 ~> ([a6989586621679939431] ~> [b6989586621679939432])) -> Type) (a6989586621679949522 :: a6989586621679939431 ~> (b6989586621679939432 ~> b6989586621679939432)) = ScanrSym1 a6989586621679949522 |
data ScanrSym1 (a6989586621679949522 :: (~>) a6989586621679939431 ((~>) b6989586621679939432 b6989586621679939432)) :: (~>) b6989586621679939432 ((~>) [a6989586621679939431] [b6989586621679939432]) Source #
Instances
SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym1 a6989586621679949522 :: TyFun b6989586621679939432 ([a6989586621679939431] ~> [b6989586621679939432]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym1 a6989586621679949522 :: TyFun b6989586621679939432 ([a6989586621679939431] ~> [b6989586621679939432]) -> Type) (a6989586621679949523 :: b6989586621679939432) Source # | |
data ScanrSym2 (a6989586621679949522 :: (~>) a6989586621679939431 ((~>) b6989586621679939432 b6989586621679939432)) (a6989586621679949523 :: b6989586621679939432) :: (~>) [a6989586621679939431] [b6989586621679939432] Source #
Instances
(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym2 a6989586621679949523 a6989586621679949522 :: TyFun [a6989586621679939431] [b6989586621679939432] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym2 a6989586621679949523 a6989586621679949522 :: TyFun [a] [b] -> Type) (a6989586621679949524 :: [a]) Source # | |
type ScanrSym3 (a6989586621679949522 :: (~>) a6989586621679939431 ((~>) b6989586621679939432 b6989586621679939432)) (a6989586621679949523 :: b6989586621679939432) (a6989586621679949524 :: [a6989586621679939431]) = Scanr a6989586621679949522 a6989586621679949523 a6989586621679949524 Source #
data Scanr1Sym0 :: forall a6989586621679939430. (~>) ((~>) a6989586621679939430 ((~>) a6989586621679939430 a6989586621679939430)) ((~>) [a6989586621679939430] [a6989586621679939430]) Source #
Instances
SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Scanr1Sym0 Source # | |
SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a6989586621679939430 ~> (a6989586621679939430 ~> a6989586621679939430)) ([a6989586621679939430] ~> [a6989586621679939430]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym0 :: TyFun (a6989586621679939430 ~> (a6989586621679939430 ~> a6989586621679939430)) ([a6989586621679939430] ~> [a6989586621679939430]) -> Type) (a6989586621679949498 :: a6989586621679939430 ~> (a6989586621679939430 ~> a6989586621679939430)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym0 :: TyFun (a6989586621679939430 ~> (a6989586621679939430 ~> a6989586621679939430)) ([a6989586621679939430] ~> [a6989586621679939430]) -> Type) (a6989586621679949498 :: a6989586621679939430 ~> (a6989586621679939430 ~> a6989586621679939430)) = Scanr1Sym1 a6989586621679949498 |
data Scanr1Sym1 (a6989586621679949498 :: (~>) a6989586621679939430 ((~>) a6989586621679939430 a6989586621679939430)) :: (~>) [a6989586621679939430] [a6989586621679939430] Source #
Instances
SingI d => SingI (Scanr1Sym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (Scanr1Sym1 d) Source # | |
SuppressUnusedWarnings (Scanr1Sym1 a6989586621679949498 :: TyFun [a6989586621679939430] [a6989586621679939430] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym1 a6989586621679949498 :: TyFun [a] [a] -> Type) (a6989586621679949499 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym1 a6989586621679949498 :: TyFun [a] [a] -> Type) (a6989586621679949499 :: [a]) = Scanr1 a6989586621679949498 a6989586621679949499 |
type Scanr1Sym2 (a6989586621679949498 :: (~>) a6989586621679939430 ((~>) a6989586621679939430 a6989586621679939430)) (a6989586621679949499 :: [a6989586621679939430]) = Scanr1 a6989586621679949498 a6989586621679949499 Source #
data MapAccumLSym0 :: forall a6989586621680750463 b6989586621680750464 c6989586621680750465 t6989586621680750462. (~>) ((~>) a6989586621680750463 ((~>) b6989586621680750464 (a6989586621680750463, c6989586621680750465))) ((~>) a6989586621680750463 ((~>) (t6989586621680750462 b6989586621680750464) (a6989586621680750463, t6989586621680750462 c6989586621680750465))) 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 Methods sing :: Sing MapAccumLSym0 Source # | |
SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (a6989586621680750463 ~> (b6989586621680750464 ~> (a6989586621680750463, c6989586621680750465))) (a6989586621680750463 ~> (t6989586621680750462 b6989586621680750464 ~> (a6989586621680750463, t6989586621680750462 c6989586621680750465))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym0 :: TyFun (a6989586621680750463 ~> (b6989586621680750464 ~> (a6989586621680750463, c6989586621680750465))) (a6989586621680750463 ~> (t6989586621680750462 b6989586621680750464 ~> (a6989586621680750463, t6989586621680750462 c6989586621680750465))) -> Type) (a6989586621680751002 :: a6989586621680750463 ~> (b6989586621680750464 ~> (a6989586621680750463, c6989586621680750465))) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym0 :: TyFun (a6989586621680750463 ~> (b6989586621680750464 ~> (a6989586621680750463, c6989586621680750465))) (a6989586621680750463 ~> (t6989586621680750462 b6989586621680750464 ~> (a6989586621680750463, t6989586621680750462 c6989586621680750465))) -> Type) (a6989586621680751002 :: a6989586621680750463 ~> (b6989586621680750464 ~> (a6989586621680750463, c6989586621680750465))) = (MapAccumLSym1 a6989586621680751002 t6989586621680750462 :: TyFun a6989586621680750463 (t6989586621680750462 b6989586621680750464 ~> (a6989586621680750463, t6989586621680750462 c6989586621680750465)) -> Type) |
data MapAccumLSym1 (a6989586621680751002 :: (~>) a6989586621680750463 ((~>) b6989586621680750464 (a6989586621680750463, c6989586621680750465))) :: forall t6989586621680750462. (~>) a6989586621680750463 ((~>) (t6989586621680750462 b6989586621680750464) (a6989586621680750463, t6989586621680750462 c6989586621680750465)) Source #
Instances
(STraversable t, SingI d) => SingI (MapAccumLSym1 d t :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods sing :: Sing (MapAccumLSym1 d t) Source # | |
SuppressUnusedWarnings (MapAccumLSym1 a6989586621680751002 t6989586621680750462 :: TyFun a6989586621680750463 (t6989586621680750462 b6989586621680750464 ~> (a6989586621680750463, t6989586621680750462 c6989586621680750465)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym1 a6989586621680751002 t6989586621680750462 :: TyFun a6989586621680750463 (t6989586621680750462 b6989586621680750464 ~> (a6989586621680750463, t6989586621680750462 c6989586621680750465)) -> Type) (a6989586621680751003 :: a6989586621680750463) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym1 a6989586621680751002 t6989586621680750462 :: TyFun a6989586621680750463 (t6989586621680750462 b6989586621680750464 ~> (a6989586621680750463, t6989586621680750462 c6989586621680750465)) -> Type) (a6989586621680751003 :: a6989586621680750463) = (MapAccumLSym2 a6989586621680751002 a6989586621680751003 t6989586621680750462 :: TyFun (t6989586621680750462 b6989586621680750464) (a6989586621680750463, t6989586621680750462 c6989586621680750465) -> Type) |
data MapAccumLSym2 (a6989586621680751002 :: (~>) a6989586621680750463 ((~>) b6989586621680750464 (a6989586621680750463, c6989586621680750465))) (a6989586621680751003 :: a6989586621680750463) :: forall t6989586621680750462. (~>) (t6989586621680750462 b6989586621680750464) (a6989586621680750463, t6989586621680750462 c6989586621680750465) Source #
Instances
(STraversable t, SingI d1, SingI d2) => SingI (MapAccumLSym2 d1 d2 t :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods sing :: Sing (MapAccumLSym2 d1 d2 t) Source # | |
SuppressUnusedWarnings (MapAccumLSym2 a6989586621680751003 a6989586621680751002 t6989586621680750462 :: TyFun (t6989586621680750462 b6989586621680750464) (a6989586621680750463, t6989586621680750462 c6989586621680750465) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym2 a6989586621680751003 a6989586621680751002 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680751004 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym2 a6989586621680751003 a6989586621680751002 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680751004 :: t b) = MapAccumL a6989586621680751003 a6989586621680751002 a6989586621680751004 |
type MapAccumLSym3 (a6989586621680751002 :: (~>) a6989586621680750463 ((~>) b6989586621680750464 (a6989586621680750463, c6989586621680750465))) (a6989586621680751003 :: a6989586621680750463) (a6989586621680751004 :: t6989586621680750462 b6989586621680750464) = MapAccumL a6989586621680751002 a6989586621680751003 a6989586621680751004 Source #
data MapAccumRSym0 :: forall a6989586621680750459 b6989586621680750460 c6989586621680750461 t6989586621680750458. (~>) ((~>) a6989586621680750459 ((~>) b6989586621680750460 (a6989586621680750459, c6989586621680750461))) ((~>) a6989586621680750459 ((~>) (t6989586621680750458 b6989586621680750460) (a6989586621680750459, t6989586621680750458 c6989586621680750461))) 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 Methods sing :: Sing MapAccumRSym0 Source # | |
SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (a6989586621680750459 ~> (b6989586621680750460 ~> (a6989586621680750459, c6989586621680750461))) (a6989586621680750459 ~> (t6989586621680750458 b6989586621680750460 ~> (a6989586621680750459, t6989586621680750458 c6989586621680750461))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym0 :: TyFun (a6989586621680750459 ~> (b6989586621680750460 ~> (a6989586621680750459, c6989586621680750461))) (a6989586621680750459 ~> (t6989586621680750458 b6989586621680750460 ~> (a6989586621680750459, t6989586621680750458 c6989586621680750461))) -> Type) (a6989586621680750985 :: a6989586621680750459 ~> (b6989586621680750460 ~> (a6989586621680750459, c6989586621680750461))) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym0 :: TyFun (a6989586621680750459 ~> (b6989586621680750460 ~> (a6989586621680750459, c6989586621680750461))) (a6989586621680750459 ~> (t6989586621680750458 b6989586621680750460 ~> (a6989586621680750459, t6989586621680750458 c6989586621680750461))) -> Type) (a6989586621680750985 :: a6989586621680750459 ~> (b6989586621680750460 ~> (a6989586621680750459, c6989586621680750461))) = (MapAccumRSym1 a6989586621680750985 t6989586621680750458 :: TyFun a6989586621680750459 (t6989586621680750458 b6989586621680750460 ~> (a6989586621680750459, t6989586621680750458 c6989586621680750461)) -> Type) |
data MapAccumRSym1 (a6989586621680750985 :: (~>) a6989586621680750459 ((~>) b6989586621680750460 (a6989586621680750459, c6989586621680750461))) :: forall t6989586621680750458. (~>) a6989586621680750459 ((~>) (t6989586621680750458 b6989586621680750460) (a6989586621680750459, t6989586621680750458 c6989586621680750461)) Source #
Instances
(STraversable t, SingI d) => SingI (MapAccumRSym1 d t :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods sing :: Sing (MapAccumRSym1 d t) Source # | |
SuppressUnusedWarnings (MapAccumRSym1 a6989586621680750985 t6989586621680750458 :: TyFun a6989586621680750459 (t6989586621680750458 b6989586621680750460 ~> (a6989586621680750459, t6989586621680750458 c6989586621680750461)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym1 a6989586621680750985 t6989586621680750458 :: TyFun a6989586621680750459 (t6989586621680750458 b6989586621680750460 ~> (a6989586621680750459, t6989586621680750458 c6989586621680750461)) -> Type) (a6989586621680750986 :: a6989586621680750459) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym1 a6989586621680750985 t6989586621680750458 :: TyFun a6989586621680750459 (t6989586621680750458 b6989586621680750460 ~> (a6989586621680750459, t6989586621680750458 c6989586621680750461)) -> Type) (a6989586621680750986 :: a6989586621680750459) = (MapAccumRSym2 a6989586621680750985 a6989586621680750986 t6989586621680750458 :: TyFun (t6989586621680750458 b6989586621680750460) (a6989586621680750459, t6989586621680750458 c6989586621680750461) -> Type) |
data MapAccumRSym2 (a6989586621680750985 :: (~>) a6989586621680750459 ((~>) b6989586621680750460 (a6989586621680750459, c6989586621680750461))) (a6989586621680750986 :: a6989586621680750459) :: forall t6989586621680750458. (~>) (t6989586621680750458 b6989586621680750460) (a6989586621680750459, t6989586621680750458 c6989586621680750461) Source #
Instances
(STraversable t, SingI d1, SingI d2) => SingI (MapAccumRSym2 d1 d2 t :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods sing :: Sing (MapAccumRSym2 d1 d2 t) Source # | |
SuppressUnusedWarnings (MapAccumRSym2 a6989586621680750986 a6989586621680750985 t6989586621680750458 :: TyFun (t6989586621680750458 b6989586621680750460) (a6989586621680750459, t6989586621680750458 c6989586621680750461) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym2 a6989586621680750986 a6989586621680750985 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680750987 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym2 a6989586621680750986 a6989586621680750985 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680750987 :: t b) = MapAccumR a6989586621680750986 a6989586621680750985 a6989586621680750987 |
type MapAccumRSym3 (a6989586621680750985 :: (~>) a6989586621680750459 ((~>) b6989586621680750460 (a6989586621680750459, c6989586621680750461))) (a6989586621680750986 :: a6989586621680750459) (a6989586621680750987 :: t6989586621680750458 b6989586621680750460) = MapAccumR a6989586621680750985 a6989586621680750986 a6989586621680750987 Source #
data ReplicateSym0 :: forall a6989586621679939338. (~>) Nat ((~>) a6989586621679939338 [a6989586621679939338]) Source #
Instances
SingI (ReplicateSym0 :: TyFun Nat (a ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing ReplicateSym0 Source # | |
SuppressUnusedWarnings (ReplicateSym0 :: TyFun Nat (a6989586621679939338 ~> [a6989586621679939338]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym0 :: TyFun Nat (a6989586621679939338 ~> [a6989586621679939338]) -> Type) (a6989586621679948640 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym0 :: TyFun Nat (a6989586621679939338 ~> [a6989586621679939338]) -> Type) (a6989586621679948640 :: Nat) = (ReplicateSym1 a6989586621679948640 a6989586621679939338 :: TyFun a6989586621679939338 [a6989586621679939338] -> Type) |
data ReplicateSym1 (a6989586621679948640 :: Nat) :: forall a6989586621679939338. (~>) a6989586621679939338 [a6989586621679939338] Source #
Instances
SingI d => SingI (ReplicateSym1 d a :: TyFun a [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ReplicateSym1 d a) Source # | |
SuppressUnusedWarnings (ReplicateSym1 a6989586621679948640 a6989586621679939338 :: TyFun a6989586621679939338 [a6989586621679939338] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym1 a6989586621679948640 a :: TyFun a [a] -> Type) (a6989586621679948641 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym1 a6989586621679948640 a :: TyFun a [a] -> Type) (a6989586621679948641 :: a) = Replicate a6989586621679948640 a6989586621679948641 |
type ReplicateSym2 (a6989586621679948640 :: Nat) (a6989586621679948641 :: a6989586621679939338) = Replicate a6989586621679948640 a6989586621679948641 Source #
data UnfoldrSym0 :: forall a6989586621679939423 b6989586621679939422. (~>) ((~>) b6989586621679939422 (Maybe (a6989586621679939423, b6989586621679939422))) ((~>) b6989586621679939422 [a6989586621679939423]) Source #
Instances
SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing UnfoldrSym0 Source # | |
SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (b6989586621679939422 ~> Maybe (a6989586621679939423, b6989586621679939422)) (b6989586621679939422 ~> [a6989586621679939423]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym0 :: TyFun (b6989586621679939422 ~> Maybe (a6989586621679939423, b6989586621679939422)) (b6989586621679939422 ~> [a6989586621679939423]) -> Type) (a6989586621679949356 :: b6989586621679939422 ~> Maybe (a6989586621679939423, b6989586621679939422)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym0 :: TyFun (b6989586621679939422 ~> Maybe (a6989586621679939423, b6989586621679939422)) (b6989586621679939422 ~> [a6989586621679939423]) -> Type) (a6989586621679949356 :: b6989586621679939422 ~> Maybe (a6989586621679939423, b6989586621679939422)) = UnfoldrSym1 a6989586621679949356 |
data UnfoldrSym1 (a6989586621679949356 :: (~>) b6989586621679939422 (Maybe (a6989586621679939423, b6989586621679939422))) :: (~>) b6989586621679939422 [a6989586621679939423] Source #
Instances
SingI d => SingI (UnfoldrSym1 d :: TyFun b [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (UnfoldrSym1 d) Source # | |
SuppressUnusedWarnings (UnfoldrSym1 a6989586621679949356 :: TyFun b6989586621679939422 [a6989586621679939423] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym1 a6989586621679949356 :: TyFun b [a] -> Type) (a6989586621679949357 :: b) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym1 a6989586621679949356 :: TyFun b [a] -> Type) (a6989586621679949357 :: b) = Unfoldr a6989586621679949356 a6989586621679949357 |
type UnfoldrSym2 (a6989586621679949356 :: (~>) b6989586621679939422 (Maybe (a6989586621679939423, b6989586621679939422))) (a6989586621679949357 :: b6989586621679939422) = Unfoldr a6989586621679949356 a6989586621679949357 Source #
data TakeSym0 :: forall a6989586621679939354. (~>) Nat ((~>) [a6989586621679939354] [a6989586621679939354]) Source #
Instances
SingI (TakeSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (TakeSym0 :: TyFun Nat ([a6989586621679939354] ~> [a6989586621679939354]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym0 :: TyFun Nat ([a6989586621679939354] ~> [a6989586621679939354]) -> Type) (a6989586621679948736 :: Nat) Source # | |
data TakeSym1 (a6989586621679948736 :: Nat) :: forall a6989586621679939354. (~>) [a6989586621679939354] [a6989586621679939354] Source #
Instances
SingI d => SingI (TakeSym1 d a :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (TakeSym1 a6989586621679948736 a6989586621679939354 :: TyFun [a6989586621679939354] [a6989586621679939354] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym1 a6989586621679948736 a :: TyFun [a] [a] -> Type) (a6989586621679948737 :: [a]) Source # | |
type TakeSym2 (a6989586621679948736 :: Nat) (a6989586621679948737 :: [a6989586621679939354]) = Take a6989586621679948736 a6989586621679948737 Source #
data DropSym0 :: forall a6989586621679939353. (~>) Nat ((~>) [a6989586621679939353] [a6989586621679939353]) Source #
Instances
SingI (DropSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (DropSym0 :: TyFun Nat ([a6989586621679939353] ~> [a6989586621679939353]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropSym0 :: TyFun Nat ([a6989586621679939353] ~> [a6989586621679939353]) -> Type) (a6989586621679948722 :: Nat) Source # | |
data DropSym1 (a6989586621679948722 :: Nat) :: forall a6989586621679939353. (~>) [a6989586621679939353] [a6989586621679939353] Source #
Instances
SingI d => SingI (DropSym1 d a :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (DropSym1 a6989586621679948722 a6989586621679939353 :: TyFun [a6989586621679939353] [a6989586621679939353] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropSym1 a6989586621679948722 a :: TyFun [a] [a] -> Type) (a6989586621679948723 :: [a]) Source # | |
type DropSym2 (a6989586621679948722 :: Nat) (a6989586621679948723 :: [a6989586621679939353]) = Drop a6989586621679948722 a6989586621679948723 Source #
data SplitAtSym0 :: forall a6989586621679939352. (~>) Nat ((~>) [a6989586621679939352] ([a6989586621679939352], [a6989586621679939352])) Source #
Instances
SingI (SplitAtSym0 :: TyFun Nat ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing SplitAtSym0 Source # | |
SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat ([a6989586621679939352] ~> ([a6989586621679939352], [a6989586621679939352])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym0 :: TyFun Nat ([a6989586621679939352] ~> ([a6989586621679939352], [a6989586621679939352])) -> Type) (a6989586621679948750 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym0 :: TyFun Nat ([a6989586621679939352] ~> ([a6989586621679939352], [a6989586621679939352])) -> Type) (a6989586621679948750 :: Nat) = (SplitAtSym1 a6989586621679948750 a6989586621679939352 :: TyFun [a6989586621679939352] ([a6989586621679939352], [a6989586621679939352]) -> Type) |
data SplitAtSym1 (a6989586621679948750 :: Nat) :: forall a6989586621679939352. (~>) [a6989586621679939352] ([a6989586621679939352], [a6989586621679939352]) Source #
Instances
SingI d => SingI (SplitAtSym1 d a :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (SplitAtSym1 d a) Source # | |
SuppressUnusedWarnings (SplitAtSym1 a6989586621679948750 a6989586621679939352 :: TyFun [a6989586621679939352] ([a6989586621679939352], [a6989586621679939352]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym1 a6989586621679948750 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621679948751 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym1 a6989586621679948750 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621679948751 :: [a]) = SplitAt a6989586621679948750 a6989586621679948751 |
type SplitAtSym2 (a6989586621679948750 :: Nat) (a6989586621679948751 :: [a6989586621679939352]) = SplitAt a6989586621679948750 a6989586621679948751 Source #
data TakeWhileSym0 :: forall a6989586621679939359. (~>) ((~>) a6989586621679939359 Bool) ((~>) [a6989586621679939359] [a6989586621679939359]) Source #
Instances
SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing TakeWhileSym0 Source # | |
SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a6989586621679939359 ~> Bool) ([a6989586621679939359] ~> [a6989586621679939359]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym0 :: TyFun (a6989586621679939359 ~> Bool) ([a6989586621679939359] ~> [a6989586621679939359]) -> Type) (a6989586621679948894 :: a6989586621679939359 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym0 :: TyFun (a6989586621679939359 ~> Bool) ([a6989586621679939359] ~> [a6989586621679939359]) -> Type) (a6989586621679948894 :: a6989586621679939359 ~> Bool) = TakeWhileSym1 a6989586621679948894 |
data TakeWhileSym1 (a6989586621679948894 :: (~>) a6989586621679939359 Bool) :: (~>) [a6989586621679939359] [a6989586621679939359] Source #
Instances
SingI d => SingI (TakeWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (TakeWhileSym1 d) Source # | |
SuppressUnusedWarnings (TakeWhileSym1 a6989586621679948894 :: TyFun [a6989586621679939359] [a6989586621679939359] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym1 a6989586621679948894 :: TyFun [a] [a] -> Type) (a6989586621679948895 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym1 a6989586621679948894 :: TyFun [a] [a] -> Type) (a6989586621679948895 :: [a]) = TakeWhile a6989586621679948894 a6989586621679948895 |
type TakeWhileSym2 (a6989586621679948894 :: (~>) a6989586621679939359 Bool) (a6989586621679948895 :: [a6989586621679939359]) = TakeWhile a6989586621679948894 a6989586621679948895 Source #
data DropWhileSym0 :: forall a6989586621679939358. (~>) ((~>) a6989586621679939358 Bool) ((~>) [a6989586621679939358] [a6989586621679939358]) Source #
Instances
SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing DropWhileSym0 Source # | |
SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a6989586621679939358 ~> Bool) ([a6989586621679939358] ~> [a6989586621679939358]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym0 :: TyFun (a6989586621679939358 ~> Bool) ([a6989586621679939358] ~> [a6989586621679939358]) -> Type) (a6989586621679948876 :: a6989586621679939358 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym0 :: TyFun (a6989586621679939358 ~> Bool) ([a6989586621679939358] ~> [a6989586621679939358]) -> Type) (a6989586621679948876 :: a6989586621679939358 ~> Bool) = DropWhileSym1 a6989586621679948876 |
data DropWhileSym1 (a6989586621679948876 :: (~>) a6989586621679939358 Bool) :: (~>) [a6989586621679939358] [a6989586621679939358] Source #
Instances
SingI d => SingI (DropWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DropWhileSym1 d) Source # | |
SuppressUnusedWarnings (DropWhileSym1 a6989586621679948876 :: TyFun [a6989586621679939358] [a6989586621679939358] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym1 a6989586621679948876 :: TyFun [a] [a] -> Type) (a6989586621679948877 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym1 a6989586621679948876 :: TyFun [a] [a] -> Type) (a6989586621679948877 :: [a]) = DropWhile a6989586621679948876 a6989586621679948877 |
type DropWhileSym2 (a6989586621679948876 :: (~>) a6989586621679939358 Bool) (a6989586621679948877 :: [a6989586621679939358]) = DropWhile a6989586621679948876 a6989586621679948877 Source #
data DropWhileEndSym0 :: forall a6989586621679939357. (~>) ((~>) a6989586621679939357 Bool) ((~>) [a6989586621679939357] [a6989586621679939357]) Source #
Instances
SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a6989586621679939357 ~> Bool) ([a6989586621679939357] ~> [a6989586621679939357]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym0 :: TyFun (a6989586621679939357 ~> Bool) ([a6989586621679939357] ~> [a6989586621679939357]) -> Type) (a6989586621679949932 :: a6989586621679939357 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym0 :: TyFun (a6989586621679939357 ~> Bool) ([a6989586621679939357] ~> [a6989586621679939357]) -> Type) (a6989586621679949932 :: a6989586621679939357 ~> Bool) = DropWhileEndSym1 a6989586621679949932 |
data DropWhileEndSym1 (a6989586621679949932 :: (~>) a6989586621679939357 Bool) :: (~>) [a6989586621679939357] [a6989586621679939357] Source #
Instances
SingI d => SingI (DropWhileEndSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DropWhileEndSym1 d) Source # | |
SuppressUnusedWarnings (DropWhileEndSym1 a6989586621679949932 :: TyFun [a6989586621679939357] [a6989586621679939357] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym1 a6989586621679949932 :: TyFun [a] [a] -> Type) (a6989586621679949933 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym1 a6989586621679949932 :: TyFun [a] [a] -> Type) (a6989586621679949933 :: [a]) = DropWhileEnd a6989586621679949932 a6989586621679949933 |
type DropWhileEndSym2 (a6989586621679949932 :: (~>) a6989586621679939357 Bool) (a6989586621679949933 :: [a6989586621679939357]) = DropWhileEnd a6989586621679949932 a6989586621679949933 Source #
data SpanSym0 :: forall a6989586621679939356. (~>) ((~>) a6989586621679939356 Bool) ((~>) [a6989586621679939356] ([a6989586621679939356], [a6989586621679939356])) Source #
Instances
SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym0 :: TyFun (a6989586621679939356 ~> Bool) ([a6989586621679939356] ~> ([a6989586621679939356], [a6989586621679939356])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym0 :: TyFun (a6989586621679939356 ~> Bool) ([a6989586621679939356] ~> ([a6989586621679939356], [a6989586621679939356])) -> Type) (a6989586621679948799 :: a6989586621679939356 ~> Bool) Source # | |
data SpanSym1 (a6989586621679948799 :: (~>) a6989586621679939356 Bool) :: (~>) [a6989586621679939356] ([a6989586621679939356], [a6989586621679939356]) Source #
Instances
SingI d => SingI (SpanSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym1 a6989586621679948799 :: TyFun [a6989586621679939356] ([a6989586621679939356], [a6989586621679939356]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym1 a6989586621679948799 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679948800 :: [a]) Source # | |
type SpanSym2 (a6989586621679948799 :: (~>) a6989586621679939356 Bool) (a6989586621679948800 :: [a6989586621679939356]) = Span a6989586621679948799 a6989586621679948800 Source #
data BreakSym0 :: forall a6989586621679939355. (~>) ((~>) a6989586621679939355 Bool) ((~>) [a6989586621679939355] ([a6989586621679939355], [a6989586621679939355])) Source #
Instances
SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym0 :: TyFun (a6989586621679939355 ~> Bool) ([a6989586621679939355] ~> ([a6989586621679939355], [a6989586621679939355])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym0 :: TyFun (a6989586621679939355 ~> Bool) ([a6989586621679939355] ~> ([a6989586621679939355], [a6989586621679939355])) -> Type) (a6989586621679948756 :: a6989586621679939355 ~> Bool) Source # | |
data BreakSym1 (a6989586621679948756 :: (~>) a6989586621679939355 Bool) :: (~>) [a6989586621679939355] ([a6989586621679939355], [a6989586621679939355]) Source #
Instances
SingI d => SingI (BreakSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym1 a6989586621679948756 :: TyFun [a6989586621679939355] ([a6989586621679939355], [a6989586621679939355]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym1 a6989586621679948756 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679948757 :: [a]) Source # | |
type BreakSym2 (a6989586621679948756 :: (~>) a6989586621679939355 Bool) (a6989586621679948757 :: [a6989586621679939355]) = Break a6989586621679948756 a6989586621679948757 Source #
data StripPrefixSym0 :: forall a6989586621680065581. (~>) [a6989586621680065581] ((~>) [a6989586621680065581] (Maybe [a6989586621680065581])) Source #
Instances
SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a6989586621680065581] ([a6989586621680065581] ~> Maybe [a6989586621680065581]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (StripPrefixSym0 :: TyFun [a6989586621680065581] ([a6989586621680065581] ~> Maybe [a6989586621680065581]) -> Type) (a6989586621680078291 :: [a6989586621680065581]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym0 :: TyFun [a6989586621680065581] ([a6989586621680065581] ~> Maybe [a6989586621680065581]) -> Type) (a6989586621680078291 :: [a6989586621680065581]) = StripPrefixSym1 a6989586621680078291 |
data StripPrefixSym1 (a6989586621680078291 :: [a6989586621680065581]) :: (~>) [a6989586621680065581] (Maybe [a6989586621680065581]) Source #
Instances
SuppressUnusedWarnings (StripPrefixSym1 a6989586621680078291 :: TyFun [a6989586621680065581] (Maybe [a6989586621680065581]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (StripPrefixSym1 a6989586621680078291 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680078292 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym1 a6989586621680078291 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680078292 :: [a]) = StripPrefix a6989586621680078291 a6989586621680078292 |
type StripPrefixSym2 (a6989586621680078291 :: [a6989586621680065581]) (a6989586621680078292 :: [a6989586621680065581]) = StripPrefix a6989586621680078291 a6989586621680078292 Source #
data GroupSym0 :: forall a6989586621679939351. (~>) [a6989586621679939351] [[a6989586621679939351]] Source #
Instances
SEq a => SingI (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621679939351] [[a6989586621679939351]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679948873 :: [a]) Source # | |
type GroupSym1 (a6989586621679948873 :: [a6989586621679939351]) = Group a6989586621679948873 Source #
data InitsSym0 :: forall a6989586621679939421. (~>) [a6989586621679939421] [[a6989586621679939421]] Source #
Instances
SingI (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621679939421] [[a6989586621679939421]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679949348 :: [a]) Source # | |
type InitsSym1 (a6989586621679949348 :: [a6989586621679939421]) = Inits a6989586621679949348 Source #
data TailsSym0 :: forall a6989586621679939420. (~>) [a6989586621679939420] [[a6989586621679939420]] Source #
Instances
SingI (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621679939420] [[a6989586621679939420]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679949341 :: [a]) Source # | |
type TailsSym1 (a6989586621679949341 :: [a6989586621679939420]) = Tails a6989586621679949341 Source #
data IsPrefixOfSym0 :: forall a6989586621679939419. (~>) [a6989586621679939419] ((~>) [a6989586621679939419] Bool) Source #
Instances
SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679939419] ([a6989586621679939419] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679939419] ([a6989586621679939419] ~> Bool) -> Type) (a6989586621679949333 :: [a6989586621679939419]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679939419] ([a6989586621679939419] ~> Bool) -> Type) (a6989586621679949333 :: [a6989586621679939419]) = IsPrefixOfSym1 a6989586621679949333 |
data IsPrefixOfSym1 (a6989586621679949333 :: [a6989586621679939419]) :: (~>) [a6989586621679939419] Bool Source #
Instances
(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IsPrefixOfSym1 d) Source # | |
SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679949333 :: TyFun [a6989586621679939419] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym1 a6989586621679949333 :: TyFun [a] Bool -> Type) (a6989586621679949334 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym1 a6989586621679949333 :: TyFun [a] Bool -> Type) (a6989586621679949334 :: [a]) = IsPrefixOf a6989586621679949333 a6989586621679949334 |
type IsPrefixOfSym2 (a6989586621679949333 :: [a6989586621679939419]) (a6989586621679949334 :: [a6989586621679939419]) = IsPrefixOf a6989586621679949333 a6989586621679949334 Source #
data IsSuffixOfSym0 :: forall a6989586621679939418. (~>) [a6989586621679939418] ((~>) [a6989586621679939418] Bool) Source #
Instances
SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679939418] ([a6989586621679939418] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679939418] ([a6989586621679939418] ~> Bool) -> Type) (a6989586621679949924 :: [a6989586621679939418]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679939418] ([a6989586621679939418] ~> Bool) -> Type) (a6989586621679949924 :: [a6989586621679939418]) = IsSuffixOfSym1 a6989586621679949924 |
data IsSuffixOfSym1 (a6989586621679949924 :: [a6989586621679939418]) :: (~>) [a6989586621679939418] Bool Source #
Instances
(SEq a, SingI d) => SingI (IsSuffixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IsSuffixOfSym1 d) Source # | |
SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679949924 :: TyFun [a6989586621679939418] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym1 a6989586621679949924 :: TyFun [a] Bool -> Type) (a6989586621679949925 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym1 a6989586621679949924 :: TyFun [a] Bool -> Type) (a6989586621679949925 :: [a]) = IsSuffixOf a6989586621679949924 a6989586621679949925 |
type IsSuffixOfSym2 (a6989586621679949924 :: [a6989586621679939418]) (a6989586621679949925 :: [a6989586621679939418]) = IsSuffixOf a6989586621679949924 a6989586621679949925 Source #
data IsInfixOfSym0 :: forall a6989586621679939417. (~>) [a6989586621679939417] ((~>) [a6989586621679939417] Bool) Source #
Instances
SEq a => SingI (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing IsInfixOfSym0 Source # | |
SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a6989586621679939417] ([a6989586621679939417] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym0 :: TyFun [a6989586621679939417] ([a6989586621679939417] ~> Bool) -> Type) (a6989586621679949571 :: [a6989586621679939417]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsInfixOfSym0 :: TyFun [a6989586621679939417] ([a6989586621679939417] ~> Bool) -> Type) (a6989586621679949571 :: [a6989586621679939417]) = IsInfixOfSym1 a6989586621679949571 |
data IsInfixOfSym1 (a6989586621679949571 :: [a6989586621679939417]) :: (~>) [a6989586621679939417] Bool Source #
Instances
(SEq a, SingI d) => SingI (IsInfixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IsInfixOfSym1 d) Source # | |
SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679949571 :: TyFun [a6989586621679939417] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym1 a6989586621679949571 :: TyFun [a] Bool -> Type) (a6989586621679949572 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type IsInfixOfSym2 (a6989586621679949571 :: [a6989586621679939417]) (a6989586621679949572 :: [a6989586621679939417]) = IsInfixOf a6989586621679949571 a6989586621679949572 Source #
data ElemSym0 :: forall a6989586621680448461 t6989586621680448444. (~>) a6989586621680448461 ((~>) (t6989586621680448444 a6989586621680448461) Bool) Source #
Instances
(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621680448461 (t6989586621680448444 a6989586621680448461 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym0 :: TyFun a6989586621680448461 (t6989586621680448444 a6989586621680448461 ~> Bool) -> Type) (arg6989586621680449111 :: a6989586621680448461) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data ElemSym1 (arg6989586621680449111 :: a6989586621680448461) :: forall t6989586621680448444. (~>) (t6989586621680448444 a6989586621680448461) Bool Source #
Instances
(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (ElemSym1 arg6989586621680449111 t6989586621680448444 :: TyFun (t6989586621680448444 a6989586621680448461) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym1 arg6989586621680449111 t :: TyFun (t a) Bool -> Type) (arg6989586621680449112 :: t a) Source # | |
type ElemSym2 (arg6989586621680449111 :: a6989586621680448461) (arg6989586621680449112 :: t6989586621680448444 a6989586621680448461) = Elem arg6989586621680449111 arg6989586621680449112 Source #
data NotElemSym0 :: forall a6989586621680448355 t6989586621680448354. (~>) a6989586621680448355 ((~>) (t6989586621680448354 a6989586621680448355) Bool) Source #
Instances
(SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing NotElemSym0 Source # | |
SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621680448355 (t6989586621680448354 a6989586621680448355 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym0 :: TyFun a6989586621680448355 (t6989586621680448354 a6989586621680448355 ~> Bool) -> Type) (a6989586621680448837 :: a6989586621680448355) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (NotElemSym0 :: TyFun a6989586621680448355 (t6989586621680448354 a6989586621680448355 ~> Bool) -> Type) (a6989586621680448837 :: a6989586621680448355) = (NotElemSym1 a6989586621680448837 t6989586621680448354 :: TyFun (t6989586621680448354 a6989586621680448355) Bool -> Type) |
data NotElemSym1 (a6989586621680448837 :: a6989586621680448355) :: forall t6989586621680448354. (~>) (t6989586621680448354 a6989586621680448355) Bool Source #
Instances
(SFoldable t, SEq a, SingI d) => SingI (NotElemSym1 d t :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (NotElemSym1 d t) Source # | |
SuppressUnusedWarnings (NotElemSym1 a6989586621680448837 t6989586621680448354 :: TyFun (t6989586621680448354 a6989586621680448355) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym1 a6989586621680448837 t :: TyFun (t a) Bool -> Type) (a6989586621680448838 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type NotElemSym2 (a6989586621680448837 :: a6989586621680448355) (a6989586621680448838 :: t6989586621680448354 a6989586621680448355) = NotElem a6989586621680448837 a6989586621680448838 Source #
data LookupSym0 :: forall a6989586621679939344 b6989586621679939345. (~>) a6989586621679939344 ((~>) [(a6989586621679939344, b6989586621679939345)] (Maybe b6989586621679939345)) Source #
Instances
SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing LookupSym0 Source # | |
SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679939344 ([(a6989586621679939344, b6989586621679939345)] ~> Maybe b6989586621679939345) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym0 :: TyFun a6989586621679939344 ([(a6989586621679939344, b6989586621679939345)] ~> Maybe b6989586621679939345) -> Type) (a6989586621679948705 :: a6989586621679939344) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (LookupSym0 :: TyFun a6989586621679939344 ([(a6989586621679939344, b6989586621679939345)] ~> Maybe b6989586621679939345) -> Type) (a6989586621679948705 :: a6989586621679939344) = (LookupSym1 a6989586621679948705 b6989586621679939345 :: TyFun [(a6989586621679939344, b6989586621679939345)] (Maybe b6989586621679939345) -> Type) |
data LookupSym1 (a6989586621679948705 :: a6989586621679939344) :: forall b6989586621679939345. (~>) [(a6989586621679939344, b6989586621679939345)] (Maybe b6989586621679939345) Source #
Instances
(SEq a, SingI d) => SingI (LookupSym1 d b :: TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (LookupSym1 d b) Source # | |
SuppressUnusedWarnings (LookupSym1 a6989586621679948705 b6989586621679939345 :: TyFun [(a6989586621679939344, b6989586621679939345)] (Maybe b6989586621679939345) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym1 a6989586621679948705 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679948706 :: [(a, b)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type LookupSym2 (a6989586621679948705 :: a6989586621679939344) (a6989586621679948706 :: [(a6989586621679939344, b6989586621679939345)]) = Lookup a6989586621679948705 a6989586621679948706 Source #
data FindSym0 :: forall a6989586621680448353 t6989586621680448352. (~>) ((~>) a6989586621680448353 Bool) ((~>) (t6989586621680448352 a6989586621680448353) (Maybe a6989586621680448353)) Source #
Instances
SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # | |
SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680448353 ~> Bool) (t6989586621680448352 a6989586621680448353 ~> Maybe a6989586621680448353) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindSym0 :: TyFun (a6989586621680448353 ~> Bool) (t6989586621680448352 a6989586621680448353 ~> Maybe a6989586621680448353) -> Type) (a6989586621680448810 :: a6989586621680448353 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FindSym0 :: TyFun (a6989586621680448353 ~> Bool) (t6989586621680448352 a6989586621680448353 ~> Maybe a6989586621680448353) -> Type) (a6989586621680448810 :: a6989586621680448353 ~> Bool) = (FindSym1 a6989586621680448810 t6989586621680448352 :: TyFun (t6989586621680448352 a6989586621680448353) (Maybe a6989586621680448353) -> Type) |
data FindSym1 (a6989586621680448810 :: (~>) a6989586621680448353 Bool) :: forall t6989586621680448352. (~>) (t6989586621680448352 a6989586621680448353) (Maybe a6989586621680448353) Source #
Instances
(SFoldable t, SingI d) => SingI (FindSym1 d t :: TyFun (t a) (Maybe a) -> Type) Source # | |
SuppressUnusedWarnings (FindSym1 a6989586621680448810 t6989586621680448352 :: TyFun (t6989586621680448352 a6989586621680448353) (Maybe a6989586621680448353) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindSym1 a6989586621680448810 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680448811 :: t a) Source # | |
type FindSym2 (a6989586621680448810 :: (~>) a6989586621680448353 Bool) (a6989586621680448811 :: t6989586621680448352 a6989586621680448353) = Find a6989586621680448810 a6989586621680448811 Source #
data FilterSym0 :: forall a6989586621679939367. (~>) ((~>) a6989586621679939367 Bool) ((~>) [a6989586621679939367] [a6989586621679939367]) Source #
Instances
SingI (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing FilterSym0 Source # | |
SuppressUnusedWarnings (FilterSym0 :: TyFun (a6989586621679939367 ~> Bool) ([a6989586621679939367] ~> [a6989586621679939367]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym0 :: TyFun (a6989586621679939367 ~> Bool) ([a6989586621679939367] ~> [a6989586621679939367]) -> Type) (a6989586621679948908 :: a6989586621679939367 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym0 :: TyFun (a6989586621679939367 ~> Bool) ([a6989586621679939367] ~> [a6989586621679939367]) -> Type) (a6989586621679948908 :: a6989586621679939367 ~> Bool) = FilterSym1 a6989586621679948908 |
data FilterSym1 (a6989586621679948908 :: (~>) a6989586621679939367 Bool) :: (~>) [a6989586621679939367] [a6989586621679939367] Source #
Instances
SingI d => SingI (FilterSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (FilterSym1 d) Source # | |
SuppressUnusedWarnings (FilterSym1 a6989586621679948908 :: TyFun [a6989586621679939367] [a6989586621679939367] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym1 a6989586621679948908 :: TyFun [a] [a] -> Type) (a6989586621679948909 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym1 a6989586621679948908 :: TyFun [a] [a] -> Type) (a6989586621679948909 :: [a]) = Filter a6989586621679948908 a6989586621679948909 |
type FilterSym2 (a6989586621679948908 :: (~>) a6989586621679939367 Bool) (a6989586621679948909 :: [a6989586621679939367]) = Filter a6989586621679948908 a6989586621679948909 Source #
data PartitionSym0 :: forall a6989586621679939343. (~>) ((~>) a6989586621679939343 Bool) ((~>) [a6989586621679939343] ([a6989586621679939343], [a6989586621679939343])) Source #
Instances
SingI (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing PartitionSym0 Source # | |
SuppressUnusedWarnings (PartitionSym0 :: TyFun (a6989586621679939343 ~> Bool) ([a6989586621679939343] ~> ([a6989586621679939343], [a6989586621679939343])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym0 :: TyFun (a6989586621679939343 ~> Bool) ([a6989586621679939343] ~> ([a6989586621679939343], [a6989586621679939343])) -> Type) (a6989586621679948699 :: a6989586621679939343 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym0 :: TyFun (a6989586621679939343 ~> Bool) ([a6989586621679939343] ~> ([a6989586621679939343], [a6989586621679939343])) -> Type) (a6989586621679948699 :: a6989586621679939343 ~> Bool) = PartitionSym1 a6989586621679948699 |
data PartitionSym1 (a6989586621679948699 :: (~>) a6989586621679939343 Bool) :: (~>) [a6989586621679939343] ([a6989586621679939343], [a6989586621679939343]) Source #
Instances
SingI d => SingI (PartitionSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (PartitionSym1 d) Source # | |
SuppressUnusedWarnings (PartitionSym1 a6989586621679948699 :: TyFun [a6989586621679939343] ([a6989586621679939343], [a6989586621679939343]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym1 a6989586621679948699 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679948700 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym1 a6989586621679948699 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679948700 :: [a]) = Partition a6989586621679948699 a6989586621679948700 |
type PartitionSym2 (a6989586621679948699 :: (~>) a6989586621679939343 Bool) (a6989586621679948700 :: [a6989586621679939343]) = Partition a6989586621679948699 a6989586621679948700 Source #
data (!!@#@$) :: forall a6989586621679939336. (~>) [a6989586621679939336] ((~>) Nat a6989586621679939336) infixl 9 Source #
Instances
SingI ((!!@#@$) :: TyFun [a] (Nat ~> a) -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$) :: TyFun [a6989586621679939336] (Nat ~> a6989586621679939336) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$) :: TyFun [a6989586621679939336] (Nat ~> a6989586621679939336) -> Type) (a6989586621679948626 :: [a6989586621679939336]) Source # | |
data (!!@#@$$) (a6989586621679948626 :: [a6989586621679939336]) :: (~>) Nat a6989586621679939336 infixl 9 Source #
Instances
SingI d => SingI ((!!@#@$$) d :: TyFun Nat a -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$$) a6989586621679948626 :: TyFun Nat a6989586621679939336 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$$) a6989586621679948626 :: TyFun Nat a -> Type) (a6989586621679948627 :: Nat) Source # | |
type (!!@#@$$$) (a6989586621679948626 :: [a6989586621679939336]) (a6989586621679948627 :: Nat) = (!!) a6989586621679948626 a6989586621679948627 Source #
data ElemIndexSym0 :: forall a6989586621679939365. (~>) a6989586621679939365 ((~>) [a6989586621679939365] (Maybe Nat)) Source #
Instances
SEq a => SingI (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing ElemIndexSym0 Source # | |
SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679939365 ([a6989586621679939365] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym0 :: TyFun a6989586621679939365 ([a6989586621679939365] ~> Maybe Nat) -> Type) (a6989586621679949291 :: a6989586621679939365) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndexSym0 :: TyFun a6989586621679939365 ([a6989586621679939365] ~> Maybe Nat) -> Type) (a6989586621679949291 :: a6989586621679939365) = ElemIndexSym1 a6989586621679949291 |
data ElemIndexSym1 (a6989586621679949291 :: a6989586621679939365) :: (~>) [a6989586621679939365] (Maybe Nat) Source #
Instances
(SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ElemIndexSym1 d) Source # | |
SuppressUnusedWarnings (ElemIndexSym1 a6989586621679949291 :: TyFun [a6989586621679939365] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym1 a6989586621679949291 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949292 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type ElemIndexSym2 (a6989586621679949291 :: a6989586621679939365) (a6989586621679949292 :: [a6989586621679939365]) = ElemIndex a6989586621679949291 a6989586621679949292 Source #
data ElemIndicesSym0 :: forall a6989586621679939364. (~>) a6989586621679939364 ((~>) [a6989586621679939364] [Nat]) Source #
Instances
SEq a => SingI (ElemIndicesSym0 :: TyFun a ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a6989586621679939364 ([a6989586621679939364] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym0 :: TyFun a6989586621679939364 ([a6989586621679939364] ~> [Nat]) -> Type) (a6989586621679949275 :: a6989586621679939364) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym0 :: TyFun a6989586621679939364 ([a6989586621679939364] ~> [Nat]) -> Type) (a6989586621679949275 :: a6989586621679939364) = ElemIndicesSym1 a6989586621679949275 |
data ElemIndicesSym1 (a6989586621679949275 :: a6989586621679939364) :: (~>) [a6989586621679939364] [Nat] Source #
Instances
(SEq a, SingI d) => SingI (ElemIndicesSym1 d :: TyFun [a] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ElemIndicesSym1 d) Source # | |
SuppressUnusedWarnings (ElemIndicesSym1 a6989586621679949275 :: TyFun [a6989586621679939364] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym1 a6989586621679949275 :: TyFun [a] [Nat] -> Type) (a6989586621679949276 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym1 a6989586621679949275 :: TyFun [a] [Nat] -> Type) (a6989586621679949276 :: [a]) = ElemIndices a6989586621679949275 a6989586621679949276 |
type ElemIndicesSym2 (a6989586621679949275 :: a6989586621679939364) (a6989586621679949276 :: [a6989586621679939364]) = ElemIndices a6989586621679949275 a6989586621679949276 Source #
data FindIndexSym0 :: forall a6989586621679939363. (~>) ((~>) a6989586621679939363 Bool) ((~>) [a6989586621679939363] (Maybe Nat)) Source #
Instances
SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing FindIndexSym0 Source # | |
SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a6989586621679939363 ~> Bool) ([a6989586621679939363] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym0 :: TyFun (a6989586621679939363 ~> Bool) ([a6989586621679939363] ~> Maybe Nat) -> Type) (a6989586621679949283 :: a6989586621679939363 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data FindIndexSym1 (a6989586621679949283 :: (~>) a6989586621679939363 Bool) :: (~>) [a6989586621679939363] (Maybe Nat) Source #
Instances
SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (FindIndexSym1 d) Source # | |
SuppressUnusedWarnings (FindIndexSym1 a6989586621679949283 :: TyFun [a6989586621679939363] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym1 a6989586621679949283 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949284 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type FindIndexSym2 (a6989586621679949283 :: (~>) a6989586621679939363 Bool) (a6989586621679949284 :: [a6989586621679939363]) = FindIndex a6989586621679949283 a6989586621679949284 Source #
data FindIndicesSym0 :: forall a6989586621679939362. (~>) ((~>) a6989586621679939362 Bool) ((~>) [a6989586621679939362] [Nat]) Source #
Instances
SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (a6989586621679939362 ~> Bool) ([a6989586621679939362] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym0 :: TyFun (a6989586621679939362 ~> Bool) ([a6989586621679939362] ~> [Nat]) -> Type) (a6989586621679949249 :: a6989586621679939362 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data FindIndicesSym1 (a6989586621679949249 :: (~>) a6989586621679939362 Bool) :: (~>) [a6989586621679939362] [Nat] Source #
Instances
SingI d => SingI (FindIndicesSym1 d :: TyFun [a] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (FindIndicesSym1 d) Source # | |
SuppressUnusedWarnings (FindIndicesSym1 a6989586621679949249 :: TyFun [a6989586621679939362] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym1 a6989586621679949249 :: TyFun [a] [Nat] -> Type) (a6989586621679949250 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndicesSym1 a6989586621679949249 :: TyFun [a] [Nat] -> Type) (a6989586621679949250 :: [a]) = FindIndices a6989586621679949249 a6989586621679949250 |
type FindIndicesSym2 (a6989586621679949249 :: (~>) a6989586621679939362 Bool) (a6989586621679949250 :: [a6989586621679939362]) = FindIndices a6989586621679949249 a6989586621679949250 Source #
data ZipSym0 :: forall a6989586621679939413 b6989586621679939414. (~>) [a6989586621679939413] ((~>) [b6989586621679939414] [(a6989586621679939413, b6989586621679939414)]) Source #
Instances
SingI (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # | |
SuppressUnusedWarnings (ZipSym0 :: TyFun [a6989586621679939413] ([b6989586621679939414] ~> [(a6989586621679939413, b6989586621679939414)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym0 :: TyFun [a6989586621679939413] ([b6989586621679939414] ~> [(a6989586621679939413, b6989586621679939414)]) -> Type) (a6989586621679949241 :: [a6989586621679939413]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipSym0 :: TyFun [a6989586621679939413] ([b6989586621679939414] ~> [(a6989586621679939413, b6989586621679939414)]) -> Type) (a6989586621679949241 :: [a6989586621679939413]) = (ZipSym1 a6989586621679949241 b6989586621679939414 :: TyFun [b6989586621679939414] [(a6989586621679939413, b6989586621679939414)] -> Type) |
data ZipSym1 (a6989586621679949241 :: [a6989586621679939413]) :: forall b6989586621679939414. (~>) [b6989586621679939414] [(a6989586621679939413, b6989586621679939414)] Source #
Instances
SingI d => SingI (ZipSym1 d b :: TyFun [b] [(a, b)] -> Type) Source # | |
SuppressUnusedWarnings (ZipSym1 a6989586621679949241 b6989586621679939414 :: TyFun [b6989586621679939414] [(a6989586621679939413, b6989586621679939414)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym1 a6989586621679949241 b :: TyFun [b] [(a, b)] -> Type) (a6989586621679949242 :: [b]) Source # | |
type ZipSym2 (a6989586621679949241 :: [a6989586621679939413]) (a6989586621679949242 :: [b6989586621679939414]) = Zip a6989586621679949241 a6989586621679949242 Source #
data Zip3Sym0 :: forall a6989586621679939410 b6989586621679939411 c6989586621679939412. (~>) [a6989586621679939410] ((~>) [b6989586621679939411] ((~>) [c6989586621679939412] [(a6989586621679939410, b6989586621679939411, c6989586621679939412)])) Source #
Instances
SingI (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a6989586621679939410] ([b6989586621679939411] ~> ([c6989586621679939412] ~> [(a6989586621679939410, b6989586621679939411, c6989586621679939412)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym0 :: TyFun [a6989586621679939410] ([b6989586621679939411] ~> ([c6989586621679939412] ~> [(a6989586621679939410, b6989586621679939411, c6989586621679939412)])) -> Type) (a6989586621679949229 :: [a6989586621679939410]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip3Sym0 :: TyFun [a6989586621679939410] ([b6989586621679939411] ~> ([c6989586621679939412] ~> [(a6989586621679939410, b6989586621679939411, c6989586621679939412)])) -> Type) (a6989586621679949229 :: [a6989586621679939410]) = (Zip3Sym1 a6989586621679949229 b6989586621679939411 c6989586621679939412 :: TyFun [b6989586621679939411] ([c6989586621679939412] ~> [(a6989586621679939410, b6989586621679939411, c6989586621679939412)]) -> Type) |
data Zip3Sym1 (a6989586621679949229 :: [a6989586621679939410]) :: forall b6989586621679939411 c6989586621679939412. (~>) [b6989586621679939411] ((~>) [c6989586621679939412] [(a6989586621679939410, b6989586621679939411, c6989586621679939412)]) Source #
Instances
SingI d => SingI (Zip3Sym1 d b c :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym1 a6989586621679949229 b6989586621679939411 c6989586621679939412 :: TyFun [b6989586621679939411] ([c6989586621679939412] ~> [(a6989586621679939410, b6989586621679939411, c6989586621679939412)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym1 a6989586621679949229 b6989586621679939411 c6989586621679939412 :: TyFun [b6989586621679939411] ([c6989586621679939412] ~> [(a6989586621679939410, b6989586621679939411, c6989586621679939412)]) -> Type) (a6989586621679949230 :: [b6989586621679939411]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip3Sym1 a6989586621679949229 b6989586621679939411 c6989586621679939412 :: TyFun [b6989586621679939411] ([c6989586621679939412] ~> [(a6989586621679939410, b6989586621679939411, c6989586621679939412)]) -> Type) (a6989586621679949230 :: [b6989586621679939411]) = (Zip3Sym2 a6989586621679949229 a6989586621679949230 c6989586621679939412 :: TyFun [c6989586621679939412] [(a6989586621679939410, b6989586621679939411, c6989586621679939412)] -> Type) |
data Zip3Sym2 (a6989586621679949229 :: [a6989586621679939410]) (a6989586621679949230 :: [b6989586621679939411]) :: forall c6989586621679939412. (~>) [c6989586621679939412] [(a6989586621679939410, b6989586621679939411, c6989586621679939412)] Source #
Instances
(SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 c :: TyFun [c] [(a, b, c)] -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym2 a6989586621679949230 a6989586621679949229 c6989586621679939412 :: TyFun [c6989586621679939412] [(a6989586621679939410, b6989586621679939411, c6989586621679939412)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym2 a6989586621679949230 a6989586621679949229 c :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679949231 :: [c]) Source # | |
type Zip3Sym3 (a6989586621679949229 :: [a6989586621679939410]) (a6989586621679949230 :: [b6989586621679939411]) (a6989586621679949231 :: [c6989586621679939412]) = Zip3 a6989586621679949229 a6989586621679949230 a6989586621679949231 Source #
data Zip4Sym0 :: forall a6989586621680065577 b6989586621680065578 c6989586621680065579 d6989586621680065580. (~>) [a6989586621680065577] ((~>) [b6989586621680065578] ((~>) [c6989586621680065579] ((~>) [d6989586621680065580] [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)]))) Source #
Instances
SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a6989586621680065577] ([b6989586621680065578] ~> ([c6989586621680065579] ~> ([d6989586621680065580] ~> [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym0 :: TyFun [a6989586621680065577] ([b6989586621680065578] ~> ([c6989586621680065579] ~> ([d6989586621680065580] ~> [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)]))) -> Type) (a6989586621680078279 :: [a6989586621680065577]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym0 :: TyFun [a6989586621680065577] ([b6989586621680065578] ~> ([c6989586621680065579] ~> ([d6989586621680065580] ~> [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)]))) -> Type) (a6989586621680078279 :: [a6989586621680065577]) = (Zip4Sym1 a6989586621680078279 b6989586621680065578 c6989586621680065579 d6989586621680065580 :: TyFun [b6989586621680065578] ([c6989586621680065579] ~> ([d6989586621680065580] ~> [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)])) -> Type) |
data Zip4Sym1 (a6989586621680078279 :: [a6989586621680065577]) :: forall b6989586621680065578 c6989586621680065579 d6989586621680065580. (~>) [b6989586621680065578] ((~>) [c6989586621680065579] ((~>) [d6989586621680065580] [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)])) Source #
Instances
SuppressUnusedWarnings (Zip4Sym1 a6989586621680078279 b6989586621680065578 c6989586621680065579 d6989586621680065580 :: TyFun [b6989586621680065578] ([c6989586621680065579] ~> ([d6989586621680065580] ~> [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym1 a6989586621680078279 b6989586621680065578 c6989586621680065579 d6989586621680065580 :: TyFun [b6989586621680065578] ([c6989586621680065579] ~> ([d6989586621680065580] ~> [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)])) -> Type) (a6989586621680078280 :: [b6989586621680065578]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym1 a6989586621680078279 b6989586621680065578 c6989586621680065579 d6989586621680065580 :: TyFun [b6989586621680065578] ([c6989586621680065579] ~> ([d6989586621680065580] ~> [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)])) -> Type) (a6989586621680078280 :: [b6989586621680065578]) = (Zip4Sym2 a6989586621680078279 a6989586621680078280 c6989586621680065579 d6989586621680065580 :: TyFun [c6989586621680065579] ([d6989586621680065580] ~> [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)]) -> Type) |
data Zip4Sym2 (a6989586621680078279 :: [a6989586621680065577]) (a6989586621680078280 :: [b6989586621680065578]) :: forall c6989586621680065579 d6989586621680065580. (~>) [c6989586621680065579] ((~>) [d6989586621680065580] [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)]) Source #
Instances
SuppressUnusedWarnings (Zip4Sym2 a6989586621680078280 a6989586621680078279 c6989586621680065579 d6989586621680065580 :: TyFun [c6989586621680065579] ([d6989586621680065580] ~> [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym2 a6989586621680078280 a6989586621680078279 c6989586621680065579 d6989586621680065580 :: TyFun [c6989586621680065579] ([d6989586621680065580] ~> [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)]) -> Type) (a6989586621680078281 :: [c6989586621680065579]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym2 a6989586621680078280 a6989586621680078279 c6989586621680065579 d6989586621680065580 :: TyFun [c6989586621680065579] ([d6989586621680065580] ~> [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)]) -> Type) (a6989586621680078281 :: [c6989586621680065579]) = (Zip4Sym3 a6989586621680078280 a6989586621680078279 a6989586621680078281 d6989586621680065580 :: TyFun [d6989586621680065580] [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)] -> Type) |
data Zip4Sym3 (a6989586621680078279 :: [a6989586621680065577]) (a6989586621680078280 :: [b6989586621680065578]) (a6989586621680078281 :: [c6989586621680065579]) :: forall d6989586621680065580. (~>) [d6989586621680065580] [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)] Source #
Instances
SuppressUnusedWarnings (Zip4Sym3 a6989586621680078281 a6989586621680078280 a6989586621680078279 d6989586621680065580 :: TyFun [d6989586621680065580] [(a6989586621680065577, b6989586621680065578, c6989586621680065579, d6989586621680065580)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym3 a6989586621680078281 a6989586621680078280 a6989586621680078279 d :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621680078282 :: [d]) Source # | |
type Zip4Sym4 (a6989586621680078279 :: [a6989586621680065577]) (a6989586621680078280 :: [b6989586621680065578]) (a6989586621680078281 :: [c6989586621680065579]) (a6989586621680078282 :: [d6989586621680065580]) = Zip4 a6989586621680078279 a6989586621680078280 a6989586621680078281 a6989586621680078282 Source #
data Zip5Sym0 :: forall a6989586621680065572 b6989586621680065573 c6989586621680065574 d6989586621680065575 e6989586621680065576. (~>) [a6989586621680065572] ((~>) [b6989586621680065573] ((~>) [c6989586621680065574] ((~>) [d6989586621680065575] ((~>) [e6989586621680065576] [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)])))) Source #
Instances
SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a6989586621680065572] ([b6989586621680065573] ~> ([c6989586621680065574] ~> ([d6989586621680065575] ~> ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym0 :: TyFun [a6989586621680065572] ([b6989586621680065573] ~> ([c6989586621680065574] ~> ([d6989586621680065575] ~> ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)])))) -> Type) (a6989586621680078256 :: [a6989586621680065572]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym0 :: TyFun [a6989586621680065572] ([b6989586621680065573] ~> ([c6989586621680065574] ~> ([d6989586621680065575] ~> ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)])))) -> Type) (a6989586621680078256 :: [a6989586621680065572]) = (Zip5Sym1 a6989586621680078256 b6989586621680065573 c6989586621680065574 d6989586621680065575 e6989586621680065576 :: TyFun [b6989586621680065573] ([c6989586621680065574] ~> ([d6989586621680065575] ~> ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]))) -> Type) |
data Zip5Sym1 (a6989586621680078256 :: [a6989586621680065572]) :: forall b6989586621680065573 c6989586621680065574 d6989586621680065575 e6989586621680065576. (~>) [b6989586621680065573] ((~>) [c6989586621680065574] ((~>) [d6989586621680065575] ((~>) [e6989586621680065576] [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]))) Source #
Instances
SuppressUnusedWarnings (Zip5Sym1 a6989586621680078256 b6989586621680065573 c6989586621680065574 d6989586621680065575 e6989586621680065576 :: TyFun [b6989586621680065573] ([c6989586621680065574] ~> ([d6989586621680065575] ~> ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym1 a6989586621680078256 b6989586621680065573 c6989586621680065574 d6989586621680065575 e6989586621680065576 :: TyFun [b6989586621680065573] ([c6989586621680065574] ~> ([d6989586621680065575] ~> ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]))) -> Type) (a6989586621680078257 :: [b6989586621680065573]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym1 a6989586621680078256 b6989586621680065573 c6989586621680065574 d6989586621680065575 e6989586621680065576 :: TyFun [b6989586621680065573] ([c6989586621680065574] ~> ([d6989586621680065575] ~> ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]))) -> Type) (a6989586621680078257 :: [b6989586621680065573]) = (Zip5Sym2 a6989586621680078256 a6989586621680078257 c6989586621680065574 d6989586621680065575 e6989586621680065576 :: TyFun [c6989586621680065574] ([d6989586621680065575] ~> ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)])) -> Type) |
data Zip5Sym2 (a6989586621680078256 :: [a6989586621680065572]) (a6989586621680078257 :: [b6989586621680065573]) :: forall c6989586621680065574 d6989586621680065575 e6989586621680065576. (~>) [c6989586621680065574] ((~>) [d6989586621680065575] ((~>) [e6989586621680065576] [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)])) Source #
Instances
SuppressUnusedWarnings (Zip5Sym2 a6989586621680078257 a6989586621680078256 c6989586621680065574 d6989586621680065575 e6989586621680065576 :: TyFun [c6989586621680065574] ([d6989586621680065575] ~> ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym2 a6989586621680078257 a6989586621680078256 c6989586621680065574 d6989586621680065575 e6989586621680065576 :: TyFun [c6989586621680065574] ([d6989586621680065575] ~> ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)])) -> Type) (a6989586621680078258 :: [c6989586621680065574]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym2 a6989586621680078257 a6989586621680078256 c6989586621680065574 d6989586621680065575 e6989586621680065576 :: TyFun [c6989586621680065574] ([d6989586621680065575] ~> ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)])) -> Type) (a6989586621680078258 :: [c6989586621680065574]) = (Zip5Sym3 a6989586621680078257 a6989586621680078256 a6989586621680078258 d6989586621680065575 e6989586621680065576 :: TyFun [d6989586621680065575] ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]) -> Type) |
data Zip5Sym3 (a6989586621680078256 :: [a6989586621680065572]) (a6989586621680078257 :: [b6989586621680065573]) (a6989586621680078258 :: [c6989586621680065574]) :: forall d6989586621680065575 e6989586621680065576. (~>) [d6989586621680065575] ((~>) [e6989586621680065576] [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]) Source #
Instances
SuppressUnusedWarnings (Zip5Sym3 a6989586621680078258 a6989586621680078257 a6989586621680078256 d6989586621680065575 e6989586621680065576 :: TyFun [d6989586621680065575] ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym3 a6989586621680078258 a6989586621680078257 a6989586621680078256 d6989586621680065575 e6989586621680065576 :: TyFun [d6989586621680065575] ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]) -> Type) (a6989586621680078259 :: [d6989586621680065575]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym3 a6989586621680078258 a6989586621680078257 a6989586621680078256 d6989586621680065575 e6989586621680065576 :: TyFun [d6989586621680065575] ([e6989586621680065576] ~> [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)]) -> Type) (a6989586621680078259 :: [d6989586621680065575]) = (Zip5Sym4 a6989586621680078258 a6989586621680078257 a6989586621680078256 a6989586621680078259 e6989586621680065576 :: TyFun [e6989586621680065576] [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)] -> Type) |
data Zip5Sym4 (a6989586621680078256 :: [a6989586621680065572]) (a6989586621680078257 :: [b6989586621680065573]) (a6989586621680078258 :: [c6989586621680065574]) (a6989586621680078259 :: [d6989586621680065575]) :: forall e6989586621680065576. (~>) [e6989586621680065576] [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)] Source #
Instances
SuppressUnusedWarnings (Zip5Sym4 a6989586621680078259 a6989586621680078258 a6989586621680078257 a6989586621680078256 e6989586621680065576 :: TyFun [e6989586621680065576] [(a6989586621680065572, b6989586621680065573, c6989586621680065574, d6989586621680065575, e6989586621680065576)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym4 a6989586621680078259 a6989586621680078258 a6989586621680078257 a6989586621680078256 e :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621680078260 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type Zip5Sym5 (a6989586621680078256 :: [a6989586621680065572]) (a6989586621680078257 :: [b6989586621680065573]) (a6989586621680078258 :: [c6989586621680065574]) (a6989586621680078259 :: [d6989586621680065575]) (a6989586621680078260 :: [e6989586621680065576]) = Zip5 a6989586621680078256 a6989586621680078257 a6989586621680078258 a6989586621680078259 a6989586621680078260 Source #
data Zip6Sym0 :: forall a6989586621680065566 b6989586621680065567 c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571. (~>) [a6989586621680065566] ((~>) [b6989586621680065567] ((~>) [c6989586621680065568] ((~>) [d6989586621680065569] ((~>) [e6989586621680065570] ((~>) [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]))))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a6989586621680065566] ([b6989586621680065567] ~> ([c6989586621680065568] ~> ([d6989586621680065569] ~> ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym0 :: TyFun [a6989586621680065566] ([b6989586621680065567] ~> ([c6989586621680065568] ~> ([d6989586621680065569] ~> ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]))))) -> Type) (a6989586621680078228 :: [a6989586621680065566]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym0 :: TyFun [a6989586621680065566] ([b6989586621680065567] ~> ([c6989586621680065568] ~> ([d6989586621680065569] ~> ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]))))) -> Type) (a6989586621680078228 :: [a6989586621680065566]) = (Zip6Sym1 a6989586621680078228 b6989586621680065567 c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571 :: TyFun [b6989586621680065567] ([c6989586621680065568] ~> ([d6989586621680065569] ~> ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])))) -> Type) |
data Zip6Sym1 (a6989586621680078228 :: [a6989586621680065566]) :: forall b6989586621680065567 c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571. (~>) [b6989586621680065567] ((~>) [c6989586621680065568] ((~>) [d6989586621680065569] ((~>) [e6989586621680065570] ((~>) [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym1 a6989586621680078228 b6989586621680065567 c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571 :: TyFun [b6989586621680065567] ([c6989586621680065568] ~> ([d6989586621680065569] ~> ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym1 a6989586621680078228 b6989586621680065567 c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571 :: TyFun [b6989586621680065567] ([c6989586621680065568] ~> ([d6989586621680065569] ~> ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])))) -> Type) (a6989586621680078229 :: [b6989586621680065567]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym1 a6989586621680078228 b6989586621680065567 c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571 :: TyFun [b6989586621680065567] ([c6989586621680065568] ~> ([d6989586621680065569] ~> ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])))) -> Type) (a6989586621680078229 :: [b6989586621680065567]) = (Zip6Sym2 a6989586621680078228 a6989586621680078229 c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571 :: TyFun [c6989586621680065568] ([d6989586621680065569] ~> ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]))) -> Type) |
data Zip6Sym2 (a6989586621680078228 :: [a6989586621680065566]) (a6989586621680078229 :: [b6989586621680065567]) :: forall c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571. (~>) [c6989586621680065568] ((~>) [d6989586621680065569] ((~>) [e6989586621680065570] ((~>) [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym2 a6989586621680078229 a6989586621680078228 c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571 :: TyFun [c6989586621680065568] ([d6989586621680065569] ~> ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym2 a6989586621680078229 a6989586621680078228 c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571 :: TyFun [c6989586621680065568] ([d6989586621680065569] ~> ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]))) -> Type) (a6989586621680078230 :: [c6989586621680065568]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym2 a6989586621680078229 a6989586621680078228 c6989586621680065568 d6989586621680065569 e6989586621680065570 f6989586621680065571 :: TyFun [c6989586621680065568] ([d6989586621680065569] ~> ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]))) -> Type) (a6989586621680078230 :: [c6989586621680065568]) = (Zip6Sym3 a6989586621680078229 a6989586621680078228 a6989586621680078230 d6989586621680065569 e6989586621680065570 f6989586621680065571 :: TyFun [d6989586621680065569] ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])) -> Type) |
data Zip6Sym3 (a6989586621680078228 :: [a6989586621680065566]) (a6989586621680078229 :: [b6989586621680065567]) (a6989586621680078230 :: [c6989586621680065568]) :: forall d6989586621680065569 e6989586621680065570 f6989586621680065571. (~>) [d6989586621680065569] ((~>) [e6989586621680065570] ((~>) [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])) Source #
Instances
SuppressUnusedWarnings (Zip6Sym3 a6989586621680078230 a6989586621680078229 a6989586621680078228 d6989586621680065569 e6989586621680065570 f6989586621680065571 :: TyFun [d6989586621680065569] ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym3 a6989586621680078230 a6989586621680078229 a6989586621680078228 d6989586621680065569 e6989586621680065570 f6989586621680065571 :: TyFun [d6989586621680065569] ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])) -> Type) (a6989586621680078231 :: [d6989586621680065569]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym3 a6989586621680078230 a6989586621680078229 a6989586621680078228 d6989586621680065569 e6989586621680065570 f6989586621680065571 :: TyFun [d6989586621680065569] ([e6989586621680065570] ~> ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)])) -> Type) (a6989586621680078231 :: [d6989586621680065569]) = (Zip6Sym4 a6989586621680078230 a6989586621680078229 a6989586621680078228 a6989586621680078231 e6989586621680065570 f6989586621680065571 :: TyFun [e6989586621680065570] ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]) -> Type) |
data Zip6Sym4 (a6989586621680078228 :: [a6989586621680065566]) (a6989586621680078229 :: [b6989586621680065567]) (a6989586621680078230 :: [c6989586621680065568]) (a6989586621680078231 :: [d6989586621680065569]) :: forall e6989586621680065570 f6989586621680065571. (~>) [e6989586621680065570] ((~>) [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]) Source #
Instances
SuppressUnusedWarnings (Zip6Sym4 a6989586621680078231 a6989586621680078230 a6989586621680078229 a6989586621680078228 e6989586621680065570 f6989586621680065571 :: TyFun [e6989586621680065570] ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym4 a6989586621680078231 a6989586621680078230 a6989586621680078229 a6989586621680078228 e6989586621680065570 f6989586621680065571 :: TyFun [e6989586621680065570] ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]) -> Type) (a6989586621680078232 :: [e6989586621680065570]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym4 a6989586621680078231 a6989586621680078230 a6989586621680078229 a6989586621680078228 e6989586621680065570 f6989586621680065571 :: TyFun [e6989586621680065570] ([f6989586621680065571] ~> [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)]) -> Type) (a6989586621680078232 :: [e6989586621680065570]) = (Zip6Sym5 a6989586621680078231 a6989586621680078230 a6989586621680078229 a6989586621680078228 a6989586621680078232 f6989586621680065571 :: TyFun [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)] -> Type) |
data Zip6Sym5 (a6989586621680078228 :: [a6989586621680065566]) (a6989586621680078229 :: [b6989586621680065567]) (a6989586621680078230 :: [c6989586621680065568]) (a6989586621680078231 :: [d6989586621680065569]) (a6989586621680078232 :: [e6989586621680065570]) :: forall f6989586621680065571. (~>) [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)] Source #
Instances
SuppressUnusedWarnings (Zip6Sym5 a6989586621680078232 a6989586621680078231 a6989586621680078230 a6989586621680078229 a6989586621680078228 f6989586621680065571 :: TyFun [f6989586621680065571] [(a6989586621680065566, b6989586621680065567, c6989586621680065568, d6989586621680065569, e6989586621680065570, f6989586621680065571)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym5 a6989586621680078232 a6989586621680078231 a6989586621680078230 a6989586621680078229 a6989586621680078228 f :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680078233 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym5 a6989586621680078232 a6989586621680078231 a6989586621680078230 a6989586621680078229 a6989586621680078228 f :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680078233 :: [f]) = Zip6 a6989586621680078232 a6989586621680078231 a6989586621680078230 a6989586621680078229 a6989586621680078228 a6989586621680078233 |
type Zip6Sym6 (a6989586621680078228 :: [a6989586621680065566]) (a6989586621680078229 :: [b6989586621680065567]) (a6989586621680078230 :: [c6989586621680065568]) (a6989586621680078231 :: [d6989586621680065569]) (a6989586621680078232 :: [e6989586621680065570]) (a6989586621680078233 :: [f6989586621680065571]) = Zip6 a6989586621680078228 a6989586621680078229 a6989586621680078230 a6989586621680078231 a6989586621680078232 a6989586621680078233 Source #
data Zip7Sym0 :: forall a6989586621680065559 b6989586621680065560 c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565. (~>) [a6989586621680065559] ((~>) [b6989586621680065560] ((~>) [c6989586621680065561] ((~>) [d6989586621680065562] ((~>) [e6989586621680065563] ((~>) [f6989586621680065564] ((~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])))))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a6989586621680065559] ([b6989586621680065560] ~> ([c6989586621680065561] ~> ([d6989586621680065562] ~> ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym0 :: TyFun [a6989586621680065559] ([b6989586621680065560] ~> ([c6989586621680065561] ~> ([d6989586621680065562] ~> ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])))))) -> Type) (a6989586621680078195 :: [a6989586621680065559]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym0 :: TyFun [a6989586621680065559] ([b6989586621680065560] ~> ([c6989586621680065561] ~> ([d6989586621680065562] ~> ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])))))) -> Type) (a6989586621680078195 :: [a6989586621680065559]) = (Zip7Sym1 a6989586621680078195 b6989586621680065560 c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [b6989586621680065560] ([c6989586621680065561] ~> ([d6989586621680065562] ~> ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))))) -> Type) |
data Zip7Sym1 (a6989586621680078195 :: [a6989586621680065559]) :: forall b6989586621680065560 c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565. (~>) [b6989586621680065560] ((~>) [c6989586621680065561] ((~>) [d6989586621680065562] ((~>) [e6989586621680065563] ((~>) [f6989586621680065564] ((~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym1 a6989586621680078195 b6989586621680065560 c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [b6989586621680065560] ([c6989586621680065561] ~> ([d6989586621680065562] ~> ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym1 a6989586621680078195 b6989586621680065560 c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [b6989586621680065560] ([c6989586621680065561] ~> ([d6989586621680065562] ~> ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))))) -> Type) (a6989586621680078196 :: [b6989586621680065560]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym1 a6989586621680078195 b6989586621680065560 c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [b6989586621680065560] ([c6989586621680065561] ~> ([d6989586621680065562] ~> ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))))) -> Type) (a6989586621680078196 :: [b6989586621680065560]) = (Zip7Sym2 a6989586621680078195 a6989586621680078196 c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [c6989586621680065561] ([d6989586621680065562] ~> ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])))) -> Type) |
data Zip7Sym2 (a6989586621680078195 :: [a6989586621680065559]) (a6989586621680078196 :: [b6989586621680065560]) :: forall c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565. (~>) [c6989586621680065561] ((~>) [d6989586621680065562] ((~>) [e6989586621680065563] ((~>) [f6989586621680065564] ((~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym2 a6989586621680078196 a6989586621680078195 c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [c6989586621680065561] ([d6989586621680065562] ~> ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym2 a6989586621680078196 a6989586621680078195 c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [c6989586621680065561] ([d6989586621680065562] ~> ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])))) -> Type) (a6989586621680078197 :: [c6989586621680065561]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym2 a6989586621680078196 a6989586621680078195 c6989586621680065561 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [c6989586621680065561] ([d6989586621680065562] ~> ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])))) -> Type) (a6989586621680078197 :: [c6989586621680065561]) = (Zip7Sym3 a6989586621680078196 a6989586621680078195 a6989586621680078197 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [d6989586621680065562] ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))) -> Type) |
data Zip7Sym3 (a6989586621680078195 :: [a6989586621680065559]) (a6989586621680078196 :: [b6989586621680065560]) (a6989586621680078197 :: [c6989586621680065561]) :: forall d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565. (~>) [d6989586621680065562] ((~>) [e6989586621680065563] ((~>) [f6989586621680065564] ((~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym3 a6989586621680078197 a6989586621680078196 a6989586621680078195 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [d6989586621680065562] ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym3 a6989586621680078197 a6989586621680078196 a6989586621680078195 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [d6989586621680065562] ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))) -> Type) (a6989586621680078198 :: [d6989586621680065562]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym3 a6989586621680078197 a6989586621680078196 a6989586621680078195 d6989586621680065562 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [d6989586621680065562] ([e6989586621680065563] ~> ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]))) -> Type) (a6989586621680078198 :: [d6989586621680065562]) = (Zip7Sym4 a6989586621680078197 a6989586621680078196 a6989586621680078195 a6989586621680078198 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [e6989586621680065563] ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])) -> Type) |
data Zip7Sym4 (a6989586621680078195 :: [a6989586621680065559]) (a6989586621680078196 :: [b6989586621680065560]) (a6989586621680078197 :: [c6989586621680065561]) (a6989586621680078198 :: [d6989586621680065562]) :: forall e6989586621680065563 f6989586621680065564 g6989586621680065565. (~>) [e6989586621680065563] ((~>) [f6989586621680065564] ((~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])) Source #
Instances
SuppressUnusedWarnings (Zip7Sym4 a6989586621680078198 a6989586621680078197 a6989586621680078196 a6989586621680078195 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [e6989586621680065563] ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym4 a6989586621680078198 a6989586621680078197 a6989586621680078196 a6989586621680078195 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [e6989586621680065563] ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])) -> Type) (a6989586621680078199 :: [e6989586621680065563]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym4 a6989586621680078198 a6989586621680078197 a6989586621680078196 a6989586621680078195 e6989586621680065563 f6989586621680065564 g6989586621680065565 :: TyFun [e6989586621680065563] ([f6989586621680065564] ~> ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)])) -> Type) (a6989586621680078199 :: [e6989586621680065563]) = (Zip7Sym5 a6989586621680078198 a6989586621680078197 a6989586621680078196 a6989586621680078195 a6989586621680078199 f6989586621680065564 g6989586621680065565 :: TyFun [f6989586621680065564] ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]) -> Type) |
data Zip7Sym5 (a6989586621680078195 :: [a6989586621680065559]) (a6989586621680078196 :: [b6989586621680065560]) (a6989586621680078197 :: [c6989586621680065561]) (a6989586621680078198 :: [d6989586621680065562]) (a6989586621680078199 :: [e6989586621680065563]) :: forall f6989586621680065564 g6989586621680065565. (~>) [f6989586621680065564] ((~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]) Source #
Instances
SuppressUnusedWarnings (Zip7Sym5 a6989586621680078199 a6989586621680078198 a6989586621680078197 a6989586621680078196 a6989586621680078195 f6989586621680065564 g6989586621680065565 :: TyFun [f6989586621680065564] ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym5 a6989586621680078199 a6989586621680078198 a6989586621680078197 a6989586621680078196 a6989586621680078195 f6989586621680065564 g6989586621680065565 :: TyFun [f6989586621680065564] ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]) -> Type) (a6989586621680078200 :: [f6989586621680065564]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym5 a6989586621680078199 a6989586621680078198 a6989586621680078197 a6989586621680078196 a6989586621680078195 f6989586621680065564 g6989586621680065565 :: TyFun [f6989586621680065564] ([g6989586621680065565] ~> [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)]) -> Type) (a6989586621680078200 :: [f6989586621680065564]) = (Zip7Sym6 a6989586621680078199 a6989586621680078198 a6989586621680078197 a6989586621680078196 a6989586621680078195 a6989586621680078200 g6989586621680065565 :: TyFun [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)] -> Type) |
data Zip7Sym6 (a6989586621680078195 :: [a6989586621680065559]) (a6989586621680078196 :: [b6989586621680065560]) (a6989586621680078197 :: [c6989586621680065561]) (a6989586621680078198 :: [d6989586621680065562]) (a6989586621680078199 :: [e6989586621680065563]) (a6989586621680078200 :: [f6989586621680065564]) :: forall g6989586621680065565. (~>) [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)] Source #
Instances
SuppressUnusedWarnings (Zip7Sym6 a6989586621680078200 a6989586621680078199 a6989586621680078198 a6989586621680078197 a6989586621680078196 a6989586621680078195 g6989586621680065565 :: TyFun [g6989586621680065565] [(a6989586621680065559, b6989586621680065560, c6989586621680065561, d6989586621680065562, e6989586621680065563, f6989586621680065564, g6989586621680065565)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym6 a6989586621680078200 a6989586621680078199 a6989586621680078198 a6989586621680078197 a6989586621680078196 a6989586621680078195 g :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680078201 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym6 a6989586621680078200 a6989586621680078199 a6989586621680078198 a6989586621680078197 a6989586621680078196 a6989586621680078195 g :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680078201 :: [g]) = Zip7 a6989586621680078200 a6989586621680078199 a6989586621680078198 a6989586621680078197 a6989586621680078196 a6989586621680078195 a6989586621680078201 |
type Zip7Sym7 (a6989586621680078195 :: [a6989586621680065559]) (a6989586621680078196 :: [b6989586621680065560]) (a6989586621680078197 :: [c6989586621680065561]) (a6989586621680078198 :: [d6989586621680065562]) (a6989586621680078199 :: [e6989586621680065563]) (a6989586621680078200 :: [f6989586621680065564]) (a6989586621680078201 :: [g6989586621680065565]) = Zip7 a6989586621680078195 a6989586621680078196 a6989586621680078197 a6989586621680078198 a6989586621680078199 a6989586621680078200 a6989586621680078201 Source #
data ZipWithSym0 :: forall a6989586621679939407 b6989586621679939408 c6989586621679939409. (~>) ((~>) a6989586621679939407 ((~>) b6989586621679939408 c6989586621679939409)) ((~>) [a6989586621679939407] ((~>) [b6989586621679939408] [c6989586621679939409])) Source #
Instances
SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing ZipWithSym0 Source # | |
SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a6989586621679939407 ~> (b6989586621679939408 ~> c6989586621679939409)) ([a6989586621679939407] ~> ([b6989586621679939408] ~> [c6989586621679939409])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym0 :: TyFun (a6989586621679939407 ~> (b6989586621679939408 ~> c6989586621679939409)) ([a6989586621679939407] ~> ([b6989586621679939408] ~> [c6989586621679939409])) -> Type) (a6989586621679949218 :: a6989586621679939407 ~> (b6989586621679939408 ~> c6989586621679939409)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym0 :: TyFun (a6989586621679939407 ~> (b6989586621679939408 ~> c6989586621679939409)) ([a6989586621679939407] ~> ([b6989586621679939408] ~> [c6989586621679939409])) -> Type) (a6989586621679949218 :: a6989586621679939407 ~> (b6989586621679939408 ~> c6989586621679939409)) = ZipWithSym1 a6989586621679949218 |
data ZipWithSym1 (a6989586621679949218 :: (~>) a6989586621679939407 ((~>) b6989586621679939408 c6989586621679939409)) :: (~>) [a6989586621679939407] ((~>) [b6989586621679939408] [c6989586621679939409]) Source #
Instances
SingI d => SingI (ZipWithSym1 d :: TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ZipWithSym1 d) Source # | |
SuppressUnusedWarnings (ZipWithSym1 a6989586621679949218 :: TyFun [a6989586621679939407] ([b6989586621679939408] ~> [c6989586621679939409]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym1 a6989586621679949218 :: TyFun [a6989586621679939407] ([b6989586621679939408] ~> [c6989586621679939409]) -> Type) (a6989586621679949219 :: [a6989586621679939407]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym1 a6989586621679949218 :: TyFun [a6989586621679939407] ([b6989586621679939408] ~> [c6989586621679939409]) -> Type) (a6989586621679949219 :: [a6989586621679939407]) = ZipWithSym2 a6989586621679949218 a6989586621679949219 |
data ZipWithSym2 (a6989586621679949218 :: (~>) a6989586621679939407 ((~>) b6989586621679939408 c6989586621679939409)) (a6989586621679949219 :: [a6989586621679939407]) :: (~>) [b6989586621679939408] [c6989586621679939409] Source #
Instances
(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun [b] [c] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ZipWithSym2 d1 d2) Source # | |
SuppressUnusedWarnings (ZipWithSym2 a6989586621679949219 a6989586621679949218 :: TyFun [b6989586621679939408] [c6989586621679939409] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym2 a6989586621679949219 a6989586621679949218 :: TyFun [b] [c] -> Type) (a6989586621679949220 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym2 a6989586621679949219 a6989586621679949218 :: TyFun [b] [c] -> Type) (a6989586621679949220 :: [b]) = ZipWith a6989586621679949219 a6989586621679949218 a6989586621679949220 |
type ZipWithSym3 (a6989586621679949218 :: (~>) a6989586621679939407 ((~>) b6989586621679939408 c6989586621679939409)) (a6989586621679949219 :: [a6989586621679939407]) (a6989586621679949220 :: [b6989586621679939408]) = ZipWith a6989586621679949218 a6989586621679949219 a6989586621679949220 Source #
data ZipWith3Sym0 :: forall a6989586621679939403 b6989586621679939404 c6989586621679939405 d6989586621679939406. (~>) ((~>) a6989586621679939403 ((~>) b6989586621679939404 ((~>) c6989586621679939405 d6989586621679939406))) ((~>) [a6989586621679939403] ((~>) [b6989586621679939404] ((~>) [c6989586621679939405] [d6989586621679939406]))) Source #
Instances
SingI (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing ZipWith3Sym0 Source # | |
SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (a6989586621679939403 ~> (b6989586621679939404 ~> (c6989586621679939405 ~> d6989586621679939406))) ([a6989586621679939403] ~> ([b6989586621679939404] ~> ([c6989586621679939405] ~> [d6989586621679939406]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym0 :: TyFun (a6989586621679939403 ~> (b6989586621679939404 ~> (c6989586621679939405 ~> d6989586621679939406))) ([a6989586621679939403] ~> ([b6989586621679939404] ~> ([c6989586621679939405] ~> [d6989586621679939406]))) -> Type) (a6989586621679949203 :: a6989586621679939403 ~> (b6989586621679939404 ~> (c6989586621679939405 ~> d6989586621679939406))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym0 :: TyFun (a6989586621679939403 ~> (b6989586621679939404 ~> (c6989586621679939405 ~> d6989586621679939406))) ([a6989586621679939403] ~> ([b6989586621679939404] ~> ([c6989586621679939405] ~> [d6989586621679939406]))) -> Type) (a6989586621679949203 :: a6989586621679939403 ~> (b6989586621679939404 ~> (c6989586621679939405 ~> d6989586621679939406))) = ZipWith3Sym1 a6989586621679949203 |
data ZipWith3Sym1 (a6989586621679949203 :: (~>) a6989586621679939403 ((~>) b6989586621679939404 ((~>) c6989586621679939405 d6989586621679939406))) :: (~>) [a6989586621679939403] ((~>) [b6989586621679939404] ((~>) [c6989586621679939405] [d6989586621679939406])) Source #
Instances
SingI d2 => SingI (ZipWith3Sym1 d2 :: TyFun [a] ([b] ~> ([c] ~> [d1])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ZipWith3Sym1 d2) Source # | |
SuppressUnusedWarnings (ZipWith3Sym1 a6989586621679949203 :: TyFun [a6989586621679939403] ([b6989586621679939404] ~> ([c6989586621679939405] ~> [d6989586621679939406])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym1 a6989586621679949203 :: TyFun [a6989586621679939403] ([b6989586621679939404] ~> ([c6989586621679939405] ~> [d6989586621679939406])) -> Type) (a6989586621679949204 :: [a6989586621679939403]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym1 a6989586621679949203 :: TyFun [a6989586621679939403] ([b6989586621679939404] ~> ([c6989586621679939405] ~> [d6989586621679939406])) -> Type) (a6989586621679949204 :: [a6989586621679939403]) = ZipWith3Sym2 a6989586621679949203 a6989586621679949204 |
data ZipWith3Sym2 (a6989586621679949203 :: (~>) a6989586621679939403 ((~>) b6989586621679939404 ((~>) c6989586621679939405 d6989586621679939406))) (a6989586621679949204 :: [a6989586621679939403]) :: (~>) [b6989586621679939404] ((~>) [c6989586621679939405] [d6989586621679939406]) Source #
Instances
(SingI d2, SingI d3) => SingI (ZipWith3Sym2 d2 d3 :: TyFun [b] ([c] ~> [d1]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ZipWith3Sym2 d2 d3) Source # | |
SuppressUnusedWarnings (ZipWith3Sym2 a6989586621679949204 a6989586621679949203 :: TyFun [b6989586621679939404] ([c6989586621679939405] ~> [d6989586621679939406]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym2 a6989586621679949204 a6989586621679949203 :: TyFun [b6989586621679939404] ([c6989586621679939405] ~> [d6989586621679939406]) -> Type) (a6989586621679949205 :: [b6989586621679939404]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym2 a6989586621679949204 a6989586621679949203 :: TyFun [b6989586621679939404] ([c6989586621679939405] ~> [d6989586621679939406]) -> Type) (a6989586621679949205 :: [b6989586621679939404]) = ZipWith3Sym3 a6989586621679949204 a6989586621679949203 a6989586621679949205 |
data ZipWith3Sym3 (a6989586621679949203 :: (~>) a6989586621679939403 ((~>) b6989586621679939404 ((~>) c6989586621679939405 d6989586621679939406))) (a6989586621679949204 :: [a6989586621679939403]) (a6989586621679949205 :: [b6989586621679939404]) :: (~>) [c6989586621679939405] [d6989586621679939406] 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 Methods sing :: Sing (ZipWith3Sym3 d2 d3 d4) Source # | |
SuppressUnusedWarnings (ZipWith3Sym3 a6989586621679949205 a6989586621679949204 a6989586621679949203 :: TyFun [c6989586621679939405] [d6989586621679939406] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym3 a6989586621679949205 a6989586621679949204 a6989586621679949203 :: TyFun [c] [d] -> Type) (a6989586621679949206 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym3 a6989586621679949205 a6989586621679949204 a6989586621679949203 :: TyFun [c] [d] -> Type) (a6989586621679949206 :: [c]) = ZipWith3 a6989586621679949205 a6989586621679949204 a6989586621679949203 a6989586621679949206 |
type ZipWith3Sym4 (a6989586621679949203 :: (~>) a6989586621679939403 ((~>) b6989586621679939404 ((~>) c6989586621679939405 d6989586621679939406))) (a6989586621679949204 :: [a6989586621679939403]) (a6989586621679949205 :: [b6989586621679939404]) (a6989586621679949206 :: [c6989586621679939405]) = ZipWith3 a6989586621679949203 a6989586621679949204 a6989586621679949205 a6989586621679949206 Source #
data ZipWith4Sym0 :: forall a6989586621680065554 b6989586621680065555 c6989586621680065556 d6989586621680065557 e6989586621680065558. (~>) ((~>) a6989586621680065554 ((~>) b6989586621680065555 ((~>) c6989586621680065556 ((~>) d6989586621680065557 e6989586621680065558)))) ((~>) [a6989586621680065554] ((~>) [b6989586621680065555] ((~>) [c6989586621680065556] ((~>) [d6989586621680065557] [e6989586621680065558])))) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (a6989586621680065554 ~> (b6989586621680065555 ~> (c6989586621680065556 ~> (d6989586621680065557 ~> e6989586621680065558)))) ([a6989586621680065554] ~> ([b6989586621680065555] ~> ([c6989586621680065556] ~> ([d6989586621680065557] ~> [e6989586621680065558])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym0 :: TyFun (a6989586621680065554 ~> (b6989586621680065555 ~> (c6989586621680065556 ~> (d6989586621680065557 ~> e6989586621680065558)))) ([a6989586621680065554] ~> ([b6989586621680065555] ~> ([c6989586621680065556] ~> ([d6989586621680065557] ~> [e6989586621680065558])))) -> Type) (a6989586621680078162 :: a6989586621680065554 ~> (b6989586621680065555 ~> (c6989586621680065556 ~> (d6989586621680065557 ~> e6989586621680065558)))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym0 :: TyFun (a6989586621680065554 ~> (b6989586621680065555 ~> (c6989586621680065556 ~> (d6989586621680065557 ~> e6989586621680065558)))) ([a6989586621680065554] ~> ([b6989586621680065555] ~> ([c6989586621680065556] ~> ([d6989586621680065557] ~> [e6989586621680065558])))) -> Type) (a6989586621680078162 :: a6989586621680065554 ~> (b6989586621680065555 ~> (c6989586621680065556 ~> (d6989586621680065557 ~> e6989586621680065558)))) = ZipWith4Sym1 a6989586621680078162 |
data ZipWith4Sym1 (a6989586621680078162 :: (~>) a6989586621680065554 ((~>) b6989586621680065555 ((~>) c6989586621680065556 ((~>) d6989586621680065557 e6989586621680065558)))) :: (~>) [a6989586621680065554] ((~>) [b6989586621680065555] ((~>) [c6989586621680065556] ((~>) [d6989586621680065557] [e6989586621680065558]))) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym1 a6989586621680078162 :: TyFun [a6989586621680065554] ([b6989586621680065555] ~> ([c6989586621680065556] ~> ([d6989586621680065557] ~> [e6989586621680065558]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym1 a6989586621680078162 :: TyFun [a6989586621680065554] ([b6989586621680065555] ~> ([c6989586621680065556] ~> ([d6989586621680065557] ~> [e6989586621680065558]))) -> Type) (a6989586621680078163 :: [a6989586621680065554]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym1 a6989586621680078162 :: TyFun [a6989586621680065554] ([b6989586621680065555] ~> ([c6989586621680065556] ~> ([d6989586621680065557] ~> [e6989586621680065558]))) -> Type) (a6989586621680078163 :: [a6989586621680065554]) = ZipWith4Sym2 a6989586621680078162 a6989586621680078163 |
data ZipWith4Sym2 (a6989586621680078162 :: (~>) a6989586621680065554 ((~>) b6989586621680065555 ((~>) c6989586621680065556 ((~>) d6989586621680065557 e6989586621680065558)))) (a6989586621680078163 :: [a6989586621680065554]) :: (~>) [b6989586621680065555] ((~>) [c6989586621680065556] ((~>) [d6989586621680065557] [e6989586621680065558])) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym2 a6989586621680078163 a6989586621680078162 :: TyFun [b6989586621680065555] ([c6989586621680065556] ~> ([d6989586621680065557] ~> [e6989586621680065558])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym2 a6989586621680078163 a6989586621680078162 :: TyFun [b6989586621680065555] ([c6989586621680065556] ~> ([d6989586621680065557] ~> [e6989586621680065558])) -> Type) (a6989586621680078164 :: [b6989586621680065555]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym2 a6989586621680078163 a6989586621680078162 :: TyFun [b6989586621680065555] ([c6989586621680065556] ~> ([d6989586621680065557] ~> [e6989586621680065558])) -> Type) (a6989586621680078164 :: [b6989586621680065555]) = ZipWith4Sym3 a6989586621680078163 a6989586621680078162 a6989586621680078164 |
data ZipWith4Sym3 (a6989586621680078162 :: (~>) a6989586621680065554 ((~>) b6989586621680065555 ((~>) c6989586621680065556 ((~>) d6989586621680065557 e6989586621680065558)))) (a6989586621680078163 :: [a6989586621680065554]) (a6989586621680078164 :: [b6989586621680065555]) :: (~>) [c6989586621680065556] ((~>) [d6989586621680065557] [e6989586621680065558]) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym3 a6989586621680078164 a6989586621680078163 a6989586621680078162 :: TyFun [c6989586621680065556] ([d6989586621680065557] ~> [e6989586621680065558]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym3 a6989586621680078164 a6989586621680078163 a6989586621680078162 :: TyFun [c6989586621680065556] ([d6989586621680065557] ~> [e6989586621680065558]) -> Type) (a6989586621680078165 :: [c6989586621680065556]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym3 a6989586621680078164 a6989586621680078163 a6989586621680078162 :: TyFun [c6989586621680065556] ([d6989586621680065557] ~> [e6989586621680065558]) -> Type) (a6989586621680078165 :: [c6989586621680065556]) = ZipWith4Sym4 a6989586621680078164 a6989586621680078163 a6989586621680078162 a6989586621680078165 |
data ZipWith4Sym4 (a6989586621680078162 :: (~>) a6989586621680065554 ((~>) b6989586621680065555 ((~>) c6989586621680065556 ((~>) d6989586621680065557 e6989586621680065558)))) (a6989586621680078163 :: [a6989586621680065554]) (a6989586621680078164 :: [b6989586621680065555]) (a6989586621680078165 :: [c6989586621680065556]) :: (~>) [d6989586621680065557] [e6989586621680065558] Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym4 a6989586621680078165 a6989586621680078164 a6989586621680078163 a6989586621680078162 :: TyFun [d6989586621680065557] [e6989586621680065558] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym4 a6989586621680078165 a6989586621680078164 a6989586621680078163 a6989586621680078162 :: TyFun [d] [e] -> Type) (a6989586621680078166 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym4 a6989586621680078165 a6989586621680078164 a6989586621680078163 a6989586621680078162 :: TyFun [d] [e] -> Type) (a6989586621680078166 :: [d]) = ZipWith4 a6989586621680078165 a6989586621680078164 a6989586621680078163 a6989586621680078162 a6989586621680078166 |
type ZipWith4Sym5 (a6989586621680078162 :: (~>) a6989586621680065554 ((~>) b6989586621680065555 ((~>) c6989586621680065556 ((~>) d6989586621680065557 e6989586621680065558)))) (a6989586621680078163 :: [a6989586621680065554]) (a6989586621680078164 :: [b6989586621680065555]) (a6989586621680078165 :: [c6989586621680065556]) (a6989586621680078166 :: [d6989586621680065557]) = ZipWith4 a6989586621680078162 a6989586621680078163 a6989586621680078164 a6989586621680078165 a6989586621680078166 Source #
data ZipWith5Sym0 :: forall a6989586621680065548 b6989586621680065549 c6989586621680065550 d6989586621680065551 e6989586621680065552 f6989586621680065553. (~>) ((~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) ((~>) [a6989586621680065548] ((~>) [b6989586621680065549] ((~>) [c6989586621680065550] ((~>) [d6989586621680065551] ((~>) [e6989586621680065552] [f6989586621680065553]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (a6989586621680065548 ~> (b6989586621680065549 ~> (c6989586621680065550 ~> (d6989586621680065551 ~> (e6989586621680065552 ~> f6989586621680065553))))) ([a6989586621680065548] ~> ([b6989586621680065549] ~> ([c6989586621680065550] ~> ([d6989586621680065551] ~> ([e6989586621680065552] ~> [f6989586621680065553]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym0 :: TyFun (a6989586621680065548 ~> (b6989586621680065549 ~> (c6989586621680065550 ~> (d6989586621680065551 ~> (e6989586621680065552 ~> f6989586621680065553))))) ([a6989586621680065548] ~> ([b6989586621680065549] ~> ([c6989586621680065550] ~> ([d6989586621680065551] ~> ([e6989586621680065552] ~> [f6989586621680065553]))))) -> Type) (a6989586621680078139 :: a6989586621680065548 ~> (b6989586621680065549 ~> (c6989586621680065550 ~> (d6989586621680065551 ~> (e6989586621680065552 ~> f6989586621680065553))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym0 :: TyFun (a6989586621680065548 ~> (b6989586621680065549 ~> (c6989586621680065550 ~> (d6989586621680065551 ~> (e6989586621680065552 ~> f6989586621680065553))))) ([a6989586621680065548] ~> ([b6989586621680065549] ~> ([c6989586621680065550] ~> ([d6989586621680065551] ~> ([e6989586621680065552] ~> [f6989586621680065553]))))) -> Type) (a6989586621680078139 :: a6989586621680065548 ~> (b6989586621680065549 ~> (c6989586621680065550 ~> (d6989586621680065551 ~> (e6989586621680065552 ~> f6989586621680065553))))) = ZipWith5Sym1 a6989586621680078139 |
data ZipWith5Sym1 (a6989586621680078139 :: (~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) :: (~>) [a6989586621680065548] ((~>) [b6989586621680065549] ((~>) [c6989586621680065550] ((~>) [d6989586621680065551] ((~>) [e6989586621680065552] [f6989586621680065553])))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym1 a6989586621680078139 :: TyFun [a6989586621680065548] ([b6989586621680065549] ~> ([c6989586621680065550] ~> ([d6989586621680065551] ~> ([e6989586621680065552] ~> [f6989586621680065553])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym1 a6989586621680078139 :: TyFun [a6989586621680065548] ([b6989586621680065549] ~> ([c6989586621680065550] ~> ([d6989586621680065551] ~> ([e6989586621680065552] ~> [f6989586621680065553])))) -> Type) (a6989586621680078140 :: [a6989586621680065548]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym1 a6989586621680078139 :: TyFun [a6989586621680065548] ([b6989586621680065549] ~> ([c6989586621680065550] ~> ([d6989586621680065551] ~> ([e6989586621680065552] ~> [f6989586621680065553])))) -> Type) (a6989586621680078140 :: [a6989586621680065548]) = ZipWith5Sym2 a6989586621680078139 a6989586621680078140 |
data ZipWith5Sym2 (a6989586621680078139 :: (~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) (a6989586621680078140 :: [a6989586621680065548]) :: (~>) [b6989586621680065549] ((~>) [c6989586621680065550] ((~>) [d6989586621680065551] ((~>) [e6989586621680065552] [f6989586621680065553]))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym2 a6989586621680078140 a6989586621680078139 :: TyFun [b6989586621680065549] ([c6989586621680065550] ~> ([d6989586621680065551] ~> ([e6989586621680065552] ~> [f6989586621680065553]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym2 a6989586621680078140 a6989586621680078139 :: TyFun [b6989586621680065549] ([c6989586621680065550] ~> ([d6989586621680065551] ~> ([e6989586621680065552] ~> [f6989586621680065553]))) -> Type) (a6989586621680078141 :: [b6989586621680065549]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym2 a6989586621680078140 a6989586621680078139 :: TyFun [b6989586621680065549] ([c6989586621680065550] ~> ([d6989586621680065551] ~> ([e6989586621680065552] ~> [f6989586621680065553]))) -> Type) (a6989586621680078141 :: [b6989586621680065549]) = ZipWith5Sym3 a6989586621680078140 a6989586621680078139 a6989586621680078141 |
data ZipWith5Sym3 (a6989586621680078139 :: (~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) (a6989586621680078140 :: [a6989586621680065548]) (a6989586621680078141 :: [b6989586621680065549]) :: (~>) [c6989586621680065550] ((~>) [d6989586621680065551] ((~>) [e6989586621680065552] [f6989586621680065553])) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym3 a6989586621680078141 a6989586621680078140 a6989586621680078139 :: TyFun [c6989586621680065550] ([d6989586621680065551] ~> ([e6989586621680065552] ~> [f6989586621680065553])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym3 a6989586621680078141 a6989586621680078140 a6989586621680078139 :: TyFun [c6989586621680065550] ([d6989586621680065551] ~> ([e6989586621680065552] ~> [f6989586621680065553])) -> Type) (a6989586621680078142 :: [c6989586621680065550]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym3 a6989586621680078141 a6989586621680078140 a6989586621680078139 :: TyFun [c6989586621680065550] ([d6989586621680065551] ~> ([e6989586621680065552] ~> [f6989586621680065553])) -> Type) (a6989586621680078142 :: [c6989586621680065550]) = ZipWith5Sym4 a6989586621680078141 a6989586621680078140 a6989586621680078139 a6989586621680078142 |
data ZipWith5Sym4 (a6989586621680078139 :: (~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) (a6989586621680078140 :: [a6989586621680065548]) (a6989586621680078141 :: [b6989586621680065549]) (a6989586621680078142 :: [c6989586621680065550]) :: (~>) [d6989586621680065551] ((~>) [e6989586621680065552] [f6989586621680065553]) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym4 a6989586621680078142 a6989586621680078141 a6989586621680078140 a6989586621680078139 :: TyFun [d6989586621680065551] ([e6989586621680065552] ~> [f6989586621680065553]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym4 a6989586621680078142 a6989586621680078141 a6989586621680078140 a6989586621680078139 :: TyFun [d6989586621680065551] ([e6989586621680065552] ~> [f6989586621680065553]) -> Type) (a6989586621680078143 :: [d6989586621680065551]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym4 a6989586621680078142 a6989586621680078141 a6989586621680078140 a6989586621680078139 :: TyFun [d6989586621680065551] ([e6989586621680065552] ~> [f6989586621680065553]) -> Type) (a6989586621680078143 :: [d6989586621680065551]) = ZipWith5Sym5 a6989586621680078142 a6989586621680078141 a6989586621680078140 a6989586621680078139 a6989586621680078143 |
data ZipWith5Sym5 (a6989586621680078139 :: (~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) (a6989586621680078140 :: [a6989586621680065548]) (a6989586621680078141 :: [b6989586621680065549]) (a6989586621680078142 :: [c6989586621680065550]) (a6989586621680078143 :: [d6989586621680065551]) :: (~>) [e6989586621680065552] [f6989586621680065553] Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym5 a6989586621680078143 a6989586621680078142 a6989586621680078141 a6989586621680078140 a6989586621680078139 :: TyFun [e6989586621680065552] [f6989586621680065553] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym5 a6989586621680078143 a6989586621680078142 a6989586621680078141 a6989586621680078140 a6989586621680078139 :: TyFun [e] [f] -> Type) (a6989586621680078144 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym5 a6989586621680078143 a6989586621680078142 a6989586621680078141 a6989586621680078140 a6989586621680078139 :: TyFun [e] [f] -> Type) (a6989586621680078144 :: [e]) = ZipWith5 a6989586621680078143 a6989586621680078142 a6989586621680078141 a6989586621680078140 a6989586621680078139 a6989586621680078144 |
type ZipWith5Sym6 (a6989586621680078139 :: (~>) a6989586621680065548 ((~>) b6989586621680065549 ((~>) c6989586621680065550 ((~>) d6989586621680065551 ((~>) e6989586621680065552 f6989586621680065553))))) (a6989586621680078140 :: [a6989586621680065548]) (a6989586621680078141 :: [b6989586621680065549]) (a6989586621680078142 :: [c6989586621680065550]) (a6989586621680078143 :: [d6989586621680065551]) (a6989586621680078144 :: [e6989586621680065552]) = ZipWith5 a6989586621680078139 a6989586621680078140 a6989586621680078141 a6989586621680078142 a6989586621680078143 a6989586621680078144 Source #
data ZipWith6Sym0 :: forall a6989586621680065541 b6989586621680065542 c6989586621680065543 d6989586621680065544 e6989586621680065545 f6989586621680065546 g6989586621680065547. (~>) ((~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) ((~>) [a6989586621680065541] ((~>) [b6989586621680065542] ((~>) [c6989586621680065543] ((~>) [d6989586621680065544] ((~>) [e6989586621680065545] ((~>) [f6989586621680065546] [g6989586621680065547])))))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (a6989586621680065541 ~> (b6989586621680065542 ~> (c6989586621680065543 ~> (d6989586621680065544 ~> (e6989586621680065545 ~> (f6989586621680065546 ~> g6989586621680065547)))))) ([a6989586621680065541] ~> ([b6989586621680065542] ~> ([c6989586621680065543] ~> ([d6989586621680065544] ~> ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym0 :: TyFun (a6989586621680065541 ~> (b6989586621680065542 ~> (c6989586621680065543 ~> (d6989586621680065544 ~> (e6989586621680065545 ~> (f6989586621680065546 ~> g6989586621680065547)))))) ([a6989586621680065541] ~> ([b6989586621680065542] ~> ([c6989586621680065543] ~> ([d6989586621680065544] ~> ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547])))))) -> Type) (a6989586621680078112 :: a6989586621680065541 ~> (b6989586621680065542 ~> (c6989586621680065543 ~> (d6989586621680065544 ~> (e6989586621680065545 ~> (f6989586621680065546 ~> g6989586621680065547)))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym0 :: TyFun (a6989586621680065541 ~> (b6989586621680065542 ~> (c6989586621680065543 ~> (d6989586621680065544 ~> (e6989586621680065545 ~> (f6989586621680065546 ~> g6989586621680065547)))))) ([a6989586621680065541] ~> ([b6989586621680065542] ~> ([c6989586621680065543] ~> ([d6989586621680065544] ~> ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547])))))) -> Type) (a6989586621680078112 :: a6989586621680065541 ~> (b6989586621680065542 ~> (c6989586621680065543 ~> (d6989586621680065544 ~> (e6989586621680065545 ~> (f6989586621680065546 ~> g6989586621680065547)))))) = ZipWith6Sym1 a6989586621680078112 |
data ZipWith6Sym1 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) :: (~>) [a6989586621680065541] ((~>) [b6989586621680065542] ((~>) [c6989586621680065543] ((~>) [d6989586621680065544] ((~>) [e6989586621680065545] ((~>) [f6989586621680065546] [g6989586621680065547]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym1 a6989586621680078112 :: TyFun [a6989586621680065541] ([b6989586621680065542] ~> ([c6989586621680065543] ~> ([d6989586621680065544] ~> ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym1 a6989586621680078112 :: TyFun [a6989586621680065541] ([b6989586621680065542] ~> ([c6989586621680065543] ~> ([d6989586621680065544] ~> ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547]))))) -> Type) (a6989586621680078113 :: [a6989586621680065541]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym1 a6989586621680078112 :: TyFun [a6989586621680065541] ([b6989586621680065542] ~> ([c6989586621680065543] ~> ([d6989586621680065544] ~> ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547]))))) -> Type) (a6989586621680078113 :: [a6989586621680065541]) = ZipWith6Sym2 a6989586621680078112 a6989586621680078113 |
data ZipWith6Sym2 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) (a6989586621680078113 :: [a6989586621680065541]) :: (~>) [b6989586621680065542] ((~>) [c6989586621680065543] ((~>) [d6989586621680065544] ((~>) [e6989586621680065545] ((~>) [f6989586621680065546] [g6989586621680065547])))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym2 a6989586621680078113 a6989586621680078112 :: TyFun [b6989586621680065542] ([c6989586621680065543] ~> ([d6989586621680065544] ~> ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym2 a6989586621680078113 a6989586621680078112 :: TyFun [b6989586621680065542] ([c6989586621680065543] ~> ([d6989586621680065544] ~> ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547])))) -> Type) (a6989586621680078114 :: [b6989586621680065542]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym2 a6989586621680078113 a6989586621680078112 :: TyFun [b6989586621680065542] ([c6989586621680065543] ~> ([d6989586621680065544] ~> ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547])))) -> Type) (a6989586621680078114 :: [b6989586621680065542]) = ZipWith6Sym3 a6989586621680078113 a6989586621680078112 a6989586621680078114 |
data ZipWith6Sym3 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) (a6989586621680078113 :: [a6989586621680065541]) (a6989586621680078114 :: [b6989586621680065542]) :: (~>) [c6989586621680065543] ((~>) [d6989586621680065544] ((~>) [e6989586621680065545] ((~>) [f6989586621680065546] [g6989586621680065547]))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym3 a6989586621680078114 a6989586621680078113 a6989586621680078112 :: TyFun [c6989586621680065543] ([d6989586621680065544] ~> ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym3 a6989586621680078114 a6989586621680078113 a6989586621680078112 :: TyFun [c6989586621680065543] ([d6989586621680065544] ~> ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547]))) -> Type) (a6989586621680078115 :: [c6989586621680065543]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym3 a6989586621680078114 a6989586621680078113 a6989586621680078112 :: TyFun [c6989586621680065543] ([d6989586621680065544] ~> ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547]))) -> Type) (a6989586621680078115 :: [c6989586621680065543]) = ZipWith6Sym4 a6989586621680078114 a6989586621680078113 a6989586621680078112 a6989586621680078115 |
data ZipWith6Sym4 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) (a6989586621680078113 :: [a6989586621680065541]) (a6989586621680078114 :: [b6989586621680065542]) (a6989586621680078115 :: [c6989586621680065543]) :: (~>) [d6989586621680065544] ((~>) [e6989586621680065545] ((~>) [f6989586621680065546] [g6989586621680065547])) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym4 a6989586621680078115 a6989586621680078114 a6989586621680078113 a6989586621680078112 :: TyFun [d6989586621680065544] ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym4 a6989586621680078115 a6989586621680078114 a6989586621680078113 a6989586621680078112 :: TyFun [d6989586621680065544] ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547])) -> Type) (a6989586621680078116 :: [d6989586621680065544]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym4 a6989586621680078115 a6989586621680078114 a6989586621680078113 a6989586621680078112 :: TyFun [d6989586621680065544] ([e6989586621680065545] ~> ([f6989586621680065546] ~> [g6989586621680065547])) -> Type) (a6989586621680078116 :: [d6989586621680065544]) = ZipWith6Sym5 a6989586621680078115 a6989586621680078114 a6989586621680078113 a6989586621680078112 a6989586621680078116 |
data ZipWith6Sym5 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) (a6989586621680078113 :: [a6989586621680065541]) (a6989586621680078114 :: [b6989586621680065542]) (a6989586621680078115 :: [c6989586621680065543]) (a6989586621680078116 :: [d6989586621680065544]) :: (~>) [e6989586621680065545] ((~>) [f6989586621680065546] [g6989586621680065547]) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym5 a6989586621680078116 a6989586621680078115 a6989586621680078114 a6989586621680078113 a6989586621680078112 :: TyFun [e6989586621680065545] ([f6989586621680065546] ~> [g6989586621680065547]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym5 a6989586621680078116 a6989586621680078115 a6989586621680078114 a6989586621680078113 a6989586621680078112 :: TyFun [e6989586621680065545] ([f6989586621680065546] ~> [g6989586621680065547]) -> Type) (a6989586621680078117 :: [e6989586621680065545]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym5 a6989586621680078116 a6989586621680078115 a6989586621680078114 a6989586621680078113 a6989586621680078112 :: TyFun [e6989586621680065545] ([f6989586621680065546] ~> [g6989586621680065547]) -> Type) (a6989586621680078117 :: [e6989586621680065545]) = ZipWith6Sym6 a6989586621680078116 a6989586621680078115 a6989586621680078114 a6989586621680078113 a6989586621680078112 a6989586621680078117 |
data ZipWith6Sym6 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) (a6989586621680078113 :: [a6989586621680065541]) (a6989586621680078114 :: [b6989586621680065542]) (a6989586621680078115 :: [c6989586621680065543]) (a6989586621680078116 :: [d6989586621680065544]) (a6989586621680078117 :: [e6989586621680065545]) :: (~>) [f6989586621680065546] [g6989586621680065547] Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym6 a6989586621680078117 a6989586621680078116 a6989586621680078115 a6989586621680078114 a6989586621680078113 a6989586621680078112 :: TyFun [f6989586621680065546] [g6989586621680065547] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym6 a6989586621680078117 a6989586621680078116 a6989586621680078115 a6989586621680078114 a6989586621680078113 a6989586621680078112 :: TyFun [f] [g] -> Type) (a6989586621680078118 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym6 a6989586621680078117 a6989586621680078116 a6989586621680078115 a6989586621680078114 a6989586621680078113 a6989586621680078112 :: TyFun [f] [g] -> Type) (a6989586621680078118 :: [f]) = ZipWith6 a6989586621680078117 a6989586621680078116 a6989586621680078115 a6989586621680078114 a6989586621680078113 a6989586621680078112 a6989586621680078118 |
type ZipWith6Sym7 (a6989586621680078112 :: (~>) a6989586621680065541 ((~>) b6989586621680065542 ((~>) c6989586621680065543 ((~>) d6989586621680065544 ((~>) e6989586621680065545 ((~>) f6989586621680065546 g6989586621680065547)))))) (a6989586621680078113 :: [a6989586621680065541]) (a6989586621680078114 :: [b6989586621680065542]) (a6989586621680078115 :: [c6989586621680065543]) (a6989586621680078116 :: [d6989586621680065544]) (a6989586621680078117 :: [e6989586621680065545]) (a6989586621680078118 :: [f6989586621680065546]) = ZipWith6 a6989586621680078112 a6989586621680078113 a6989586621680078114 a6989586621680078115 a6989586621680078116 a6989586621680078117 a6989586621680078118 Source #
data ZipWith7Sym0 :: forall a6989586621680065533 b6989586621680065534 c6989586621680065535 d6989586621680065536 e6989586621680065537 f6989586621680065538 g6989586621680065539 h6989586621680065540. (~>) ((~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) ((~>) [a6989586621680065533] ((~>) [b6989586621680065534] ((~>) [c6989586621680065535] ((~>) [d6989586621680065536] ((~>) [e6989586621680065537] ((~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540]))))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym0 :: TyFun (a6989586621680065533 ~> (b6989586621680065534 ~> (c6989586621680065535 ~> (d6989586621680065536 ~> (e6989586621680065537 ~> (f6989586621680065538 ~> (g6989586621680065539 ~> h6989586621680065540))))))) ([a6989586621680065533] ~> ([b6989586621680065534] ~> ([c6989586621680065535] ~> ([d6989586621680065536] ~> ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540]))))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym0 :: TyFun (a6989586621680065533 ~> (b6989586621680065534 ~> (c6989586621680065535 ~> (d6989586621680065536 ~> (e6989586621680065537 ~> (f6989586621680065538 ~> (g6989586621680065539 ~> h6989586621680065540))))))) ([a6989586621680065533] ~> ([b6989586621680065534] ~> ([c6989586621680065535] ~> ([d6989586621680065536] ~> ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540]))))))) -> Type) (a6989586621680078081 :: a6989586621680065533 ~> (b6989586621680065534 ~> (c6989586621680065535 ~> (d6989586621680065536 ~> (e6989586621680065537 ~> (f6989586621680065538 ~> (g6989586621680065539 ~> h6989586621680065540))))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym0 :: TyFun (a6989586621680065533 ~> (b6989586621680065534 ~> (c6989586621680065535 ~> (d6989586621680065536 ~> (e6989586621680065537 ~> (f6989586621680065538 ~> (g6989586621680065539 ~> h6989586621680065540))))))) ([a6989586621680065533] ~> ([b6989586621680065534] ~> ([c6989586621680065535] ~> ([d6989586621680065536] ~> ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540]))))))) -> Type) (a6989586621680078081 :: a6989586621680065533 ~> (b6989586621680065534 ~> (c6989586621680065535 ~> (d6989586621680065536 ~> (e6989586621680065537 ~> (f6989586621680065538 ~> (g6989586621680065539 ~> h6989586621680065540))))))) = ZipWith7Sym1 a6989586621680078081 |
data ZipWith7Sym1 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) :: (~>) [a6989586621680065533] ((~>) [b6989586621680065534] ((~>) [c6989586621680065535] ((~>) [d6989586621680065536] ((~>) [e6989586621680065537] ((~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540])))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym1 a6989586621680078081 :: TyFun [a6989586621680065533] ([b6989586621680065534] ~> ([c6989586621680065535] ~> ([d6989586621680065536] ~> ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym1 a6989586621680078081 :: TyFun [a6989586621680065533] ([b6989586621680065534] ~> ([c6989586621680065535] ~> ([d6989586621680065536] ~> ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540])))))) -> Type) (a6989586621680078082 :: [a6989586621680065533]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym1 a6989586621680078081 :: TyFun [a6989586621680065533] ([b6989586621680065534] ~> ([c6989586621680065535] ~> ([d6989586621680065536] ~> ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540])))))) -> Type) (a6989586621680078082 :: [a6989586621680065533]) = ZipWith7Sym2 a6989586621680078081 a6989586621680078082 |
data ZipWith7Sym2 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) :: (~>) [b6989586621680065534] ((~>) [c6989586621680065535] ((~>) [d6989586621680065536] ((~>) [e6989586621680065537] ((~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym2 a6989586621680078082 a6989586621680078081 :: TyFun [b6989586621680065534] ([c6989586621680065535] ~> ([d6989586621680065536] ~> ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym2 a6989586621680078082 a6989586621680078081 :: TyFun [b6989586621680065534] ([c6989586621680065535] ~> ([d6989586621680065536] ~> ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540]))))) -> Type) (a6989586621680078083 :: [b6989586621680065534]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym2 a6989586621680078082 a6989586621680078081 :: TyFun [b6989586621680065534] ([c6989586621680065535] ~> ([d6989586621680065536] ~> ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540]))))) -> Type) (a6989586621680078083 :: [b6989586621680065534]) = ZipWith7Sym3 a6989586621680078082 a6989586621680078081 a6989586621680078083 |
data ZipWith7Sym3 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) (a6989586621680078083 :: [b6989586621680065534]) :: (~>) [c6989586621680065535] ((~>) [d6989586621680065536] ((~>) [e6989586621680065537] ((~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540])))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym3 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [c6989586621680065535] ([d6989586621680065536] ~> ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym3 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [c6989586621680065535] ([d6989586621680065536] ~> ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540])))) -> Type) (a6989586621680078084 :: [c6989586621680065535]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym3 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [c6989586621680065535] ([d6989586621680065536] ~> ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540])))) -> Type) (a6989586621680078084 :: [c6989586621680065535]) = ZipWith7Sym4 a6989586621680078083 a6989586621680078082 a6989586621680078081 a6989586621680078084 |
data ZipWith7Sym4 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) (a6989586621680078083 :: [b6989586621680065534]) (a6989586621680078084 :: [c6989586621680065535]) :: (~>) [d6989586621680065536] ((~>) [e6989586621680065537] ((~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540]))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym4 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [d6989586621680065536] ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym4 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [d6989586621680065536] ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540]))) -> Type) (a6989586621680078085 :: [d6989586621680065536]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym4 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [d6989586621680065536] ([e6989586621680065537] ~> ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540]))) -> Type) (a6989586621680078085 :: [d6989586621680065536]) = ZipWith7Sym5 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 a6989586621680078085 |
data ZipWith7Sym5 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) (a6989586621680078083 :: [b6989586621680065534]) (a6989586621680078084 :: [c6989586621680065535]) (a6989586621680078085 :: [d6989586621680065536]) :: (~>) [e6989586621680065537] ((~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540])) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym5 a6989586621680078085 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [e6989586621680065537] ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym5 a6989586621680078085 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [e6989586621680065537] ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540])) -> Type) (a6989586621680078086 :: [e6989586621680065537]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym5 a6989586621680078085 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [e6989586621680065537] ([f6989586621680065538] ~> ([g6989586621680065539] ~> [h6989586621680065540])) -> Type) (a6989586621680078086 :: [e6989586621680065537]) = ZipWith7Sym6 a6989586621680078085 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 a6989586621680078086 |
data ZipWith7Sym6 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) (a6989586621680078083 :: [b6989586621680065534]) (a6989586621680078084 :: [c6989586621680065535]) (a6989586621680078085 :: [d6989586621680065536]) (a6989586621680078086 :: [e6989586621680065537]) :: (~>) [f6989586621680065538] ((~>) [g6989586621680065539] [h6989586621680065540]) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym6 a6989586621680078086 a6989586621680078085 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [f6989586621680065538] ([g6989586621680065539] ~> [h6989586621680065540]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym6 a6989586621680078086 a6989586621680078085 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [f6989586621680065538] ([g6989586621680065539] ~> [h6989586621680065540]) -> Type) (a6989586621680078087 :: [f6989586621680065538]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym6 a6989586621680078086 a6989586621680078085 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [f6989586621680065538] ([g6989586621680065539] ~> [h6989586621680065540]) -> Type) (a6989586621680078087 :: [f6989586621680065538]) = ZipWith7Sym7 a6989586621680078086 a6989586621680078085 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 a6989586621680078087 |
data ZipWith7Sym7 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) (a6989586621680078083 :: [b6989586621680065534]) (a6989586621680078084 :: [c6989586621680065535]) (a6989586621680078085 :: [d6989586621680065536]) (a6989586621680078086 :: [e6989586621680065537]) (a6989586621680078087 :: [f6989586621680065538]) :: (~>) [g6989586621680065539] [h6989586621680065540] Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym7 a6989586621680078087 a6989586621680078086 a6989586621680078085 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [g6989586621680065539] [h6989586621680065540] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym7 a6989586621680078087 a6989586621680078086 a6989586621680078085 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [g] [h] -> Type) (a6989586621680078088 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym7 a6989586621680078087 a6989586621680078086 a6989586621680078085 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 :: TyFun [g] [h] -> Type) (a6989586621680078088 :: [g]) = ZipWith7 a6989586621680078087 a6989586621680078086 a6989586621680078085 a6989586621680078084 a6989586621680078083 a6989586621680078082 a6989586621680078081 a6989586621680078088 |
type ZipWith7Sym8 (a6989586621680078081 :: (~>) a6989586621680065533 ((~>) b6989586621680065534 ((~>) c6989586621680065535 ((~>) d6989586621680065536 ((~>) e6989586621680065537 ((~>) f6989586621680065538 ((~>) g6989586621680065539 h6989586621680065540))))))) (a6989586621680078082 :: [a6989586621680065533]) (a6989586621680078083 :: [b6989586621680065534]) (a6989586621680078084 :: [c6989586621680065535]) (a6989586621680078085 :: [d6989586621680065536]) (a6989586621680078086 :: [e6989586621680065537]) (a6989586621680078087 :: [f6989586621680065538]) (a6989586621680078088 :: [g6989586621680065539]) = ZipWith7 a6989586621680078081 a6989586621680078082 a6989586621680078083 a6989586621680078084 a6989586621680078085 a6989586621680078086 a6989586621680078087 a6989586621680078088 Source #
data UnzipSym0 :: forall a6989586621679939401 b6989586621679939402. (~>) [(a6989586621679939401, b6989586621679939402)] ([a6989586621679939401], [b6989586621679939402]) Source #
Instances
SingI (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # | |
SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a6989586621679939401, b6989586621679939402)] ([a6989586621679939401], [b6989586621679939402]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679949184 :: [(a, b)]) Source # | |
type UnzipSym1 (a6989586621679949184 :: [(a6989586621679939401, b6989586621679939402)]) = Unzip a6989586621679949184 Source #
data Unzip3Sym0 :: forall a6989586621679939398 b6989586621679939399 c6989586621679939400. (~>) [(a6989586621679939398, b6989586621679939399, c6989586621679939400)] ([a6989586621679939398], [b6989586621679939399], [c6989586621679939400]) Source #
Instances
SingI (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Unzip3Sym0 Source # | |
SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a6989586621679939398, b6989586621679939399, c6989586621679939400)] ([a6989586621679939398], [b6989586621679939399], [c6989586621679939400]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679949163 :: [(a, b, c)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679949163 :: [(a, b, c)]) = Unzip3 a6989586621679949163 |
type Unzip3Sym1 (a6989586621679949163 :: [(a6989586621679939398, b6989586621679939399, c6989586621679939400)]) = Unzip3 a6989586621679949163 Source #
data Unzip4Sym0 :: forall a6989586621679939394 b6989586621679939395 c6989586621679939396 d6989586621679939397. (~>) [(a6989586621679939394, b6989586621679939395, c6989586621679939396, d6989586621679939397)] ([a6989586621679939394], [b6989586621679939395], [c6989586621679939396], [d6989586621679939397]) Source #
Instances
SingI (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Unzip4Sym0 Source # | |
SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a6989586621679939394, b6989586621679939395, c6989586621679939396, d6989586621679939397)] ([a6989586621679939394], [b6989586621679939395], [c6989586621679939396], [d6989586621679939397]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679949140 :: [(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) (a6989586621679949140 :: [(a, b, c, d)]) = Unzip4 a6989586621679949140 |
type Unzip4Sym1 (a6989586621679949140 :: [(a6989586621679939394, b6989586621679939395, c6989586621679939396, d6989586621679939397)]) = Unzip4 a6989586621679949140 Source #
data Unzip5Sym0 :: forall a6989586621679939389 b6989586621679939390 c6989586621679939391 d6989586621679939392 e6989586621679939393. (~>) [(a6989586621679939389, b6989586621679939390, c6989586621679939391, d6989586621679939392, e6989586621679939393)] ([a6989586621679939389], [b6989586621679939390], [c6989586621679939391], [d6989586621679939392], [e6989586621679939393]) Source #
Instances
SingI (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Unzip5Sym0 Source # | |
SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a6989586621679939389, b6989586621679939390, c6989586621679939391, d6989586621679939392, e6989586621679939393)] ([a6989586621679939389], [b6989586621679939390], [c6989586621679939391], [d6989586621679939392], [e6989586621679939393]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679949115 :: [(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) (a6989586621679949115 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679949115 |
type Unzip5Sym1 (a6989586621679949115 :: [(a6989586621679939389, b6989586621679939390, c6989586621679939391, d6989586621679939392, e6989586621679939393)]) = Unzip5 a6989586621679949115 Source #
data Unzip6Sym0 :: forall a6989586621679939383 b6989586621679939384 c6989586621679939385 d6989586621679939386 e6989586621679939387 f6989586621679939388. (~>) [(a6989586621679939383, b6989586621679939384, c6989586621679939385, d6989586621679939386, e6989586621679939387, f6989586621679939388)] ([a6989586621679939383], [b6989586621679939384], [c6989586621679939385], [d6989586621679939386], [e6989586621679939387], [f6989586621679939388]) 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 Methods sing :: Sing Unzip6Sym0 Source # | |
SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a6989586621679939383, b6989586621679939384, c6989586621679939385, d6989586621679939386, e6989586621679939387, f6989586621679939388)] ([a6989586621679939383], [b6989586621679939384], [c6989586621679939385], [d6989586621679939386], [e6989586621679939387], [f6989586621679939388]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679949088 :: [(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) (a6989586621679949088 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679949088 |
type Unzip6Sym1 (a6989586621679949088 :: [(a6989586621679939383, b6989586621679939384, c6989586621679939385, d6989586621679939386, e6989586621679939387, f6989586621679939388)]) = Unzip6 a6989586621679949088 Source #
data Unzip7Sym0 :: forall a6989586621679939376 b6989586621679939377 c6989586621679939378 d6989586621679939379 e6989586621679939380 f6989586621679939381 g6989586621679939382. (~>) [(a6989586621679939376, b6989586621679939377, c6989586621679939378, d6989586621679939379, e6989586621679939380, f6989586621679939381, g6989586621679939382)] ([a6989586621679939376], [b6989586621679939377], [c6989586621679939378], [d6989586621679939379], [e6989586621679939380], [f6989586621679939381], [g6989586621679939382]) 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 Methods sing :: Sing Unzip7Sym0 Source # | |
SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a6989586621679939376, b6989586621679939377, c6989586621679939378, d6989586621679939379, e6989586621679939380, f6989586621679939381, g6989586621679939382)] ([a6989586621679939376], [b6989586621679939377], [c6989586621679939378], [d6989586621679939379], [e6989586621679939380], [f6989586621679939381], [g6989586621679939382]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679949059 :: [(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) (a6989586621679949059 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679949059 |
type Unzip7Sym1 (a6989586621679949059 :: [(a6989586621679939376, b6989586621679939377, c6989586621679939378, d6989586621679939379, e6989586621679939380, f6989586621679939381, g6989586621679939382)]) = Unzip7 a6989586621679949059 Source #
data UnlinesSym0 :: (~>) [Symbol] Symbol Source #
Instances
SingI UnlinesSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing UnlinesSym0 Source # | |
SuppressUnusedWarnings UnlinesSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply UnlinesSym0 (a6989586621679949055 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnlinesSym1 (a6989586621679949055 :: [Symbol]) = Unlines a6989586621679949055 Source #
data UnwordsSym0 :: (~>) [Symbol] Symbol Source #
Instances
SingI UnwordsSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing UnwordsSym0 Source # | |
SuppressUnusedWarnings UnwordsSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply UnwordsSym0 (a6989586621679949044 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnwordsSym1 (a6989586621679949044 :: [Symbol]) = Unwords a6989586621679949044 Source #
data NubSym0 :: forall a6989586621679939335. (~>) [a6989586621679939335] [a6989586621679939335] Source #
Instances
SEq a => SingI (NubSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (NubSym0 :: TyFun [a6989586621679939335] [a6989586621679939335] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (NubSym0 :: TyFun [a] [a] -> Type) (a6989586621679949313 :: [a]) Source # | |
data DeleteSym0 :: forall a6989586621679939375. (~>) a6989586621679939375 ((~>) [a6989586621679939375] [a6989586621679939375]) Source #
Instances
SEq a => SingI (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing DeleteSym0 Source # | |
SuppressUnusedWarnings (DeleteSym0 :: TyFun a6989586621679939375 ([a6989586621679939375] ~> [a6989586621679939375]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym0 :: TyFun a6989586621679939375 ([a6989586621679939375] ~> [a6989586621679939375]) -> Type) (a6989586621679949028 :: a6989586621679939375) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym0 :: TyFun a6989586621679939375 ([a6989586621679939375] ~> [a6989586621679939375]) -> Type) (a6989586621679949028 :: a6989586621679939375) = DeleteSym1 a6989586621679949028 |
data DeleteSym1 (a6989586621679949028 :: a6989586621679939375) :: (~>) [a6989586621679939375] [a6989586621679939375] Source #
Instances
(SEq a, SingI d) => SingI (DeleteSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DeleteSym1 d) Source # | |
SuppressUnusedWarnings (DeleteSym1 a6989586621679949028 :: TyFun [a6989586621679939375] [a6989586621679939375] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym1 a6989586621679949028 :: TyFun [a] [a] -> Type) (a6989586621679949029 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym1 a6989586621679949028 :: TyFun [a] [a] -> Type) (a6989586621679949029 :: [a]) = Delete a6989586621679949028 a6989586621679949029 |
type DeleteSym2 (a6989586621679949028 :: a6989586621679939375) (a6989586621679949029 :: [a6989586621679939375]) = Delete a6989586621679949028 a6989586621679949029 Source #
data (\\@#@$) :: forall a6989586621679939374. (~>) [a6989586621679939374] ((~>) [a6989586621679939374] [a6989586621679939374]) infix 5 Source #
Instances
SEq a => SingI ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((\\@#@$) :: TyFun [a6989586621679939374] ([a6989586621679939374] ~> [a6989586621679939374]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$) :: TyFun [a6989586621679939374] ([a6989586621679939374] ~> [a6989586621679939374]) -> Type) (a6989586621679949038 :: [a6989586621679939374]) Source # | |
data (\\@#@$$) (a6989586621679949038 :: [a6989586621679939374]) :: (~>) [a6989586621679939374] [a6989586621679939374] infix 5 Source #
Instances
(SEq a, SingI d) => SingI ((\\@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((\\@#@$$) a6989586621679949038 :: TyFun [a6989586621679939374] [a6989586621679939374] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$$) a6989586621679949038 :: TyFun [a] [a] -> Type) (a6989586621679949039 :: [a]) Source # | |
type (\\@#@$$$) (a6989586621679949038 :: [a6989586621679939374]) (a6989586621679949039 :: [a6989586621679939374]) = (\\) a6989586621679949038 a6989586621679949039 Source #
data UnionSym0 :: forall a6989586621679939331. (~>) [a6989586621679939331] ((~>) [a6989586621679939331] [a6989586621679939331]) Source #
Instances
SEq a => SingI (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (UnionSym0 :: TyFun [a6989586621679939331] ([a6989586621679939331] ~> [a6989586621679939331]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym0 :: TyFun [a6989586621679939331] ([a6989586621679939331] ~> [a6989586621679939331]) -> Type) (a6989586621679949018 :: [a6989586621679939331]) Source # | |
data UnionSym1 (a6989586621679949018 :: [a6989586621679939331]) :: (~>) [a6989586621679939331] [a6989586621679939331] Source #
Instances
(SEq a, SingI d) => SingI (UnionSym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (UnionSym1 a6989586621679949018 :: TyFun [a6989586621679939331] [a6989586621679939331] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym1 a6989586621679949018 :: TyFun [a] [a] -> Type) (a6989586621679949019 :: [a]) Source # | |
type UnionSym2 (a6989586621679949018 :: [a6989586621679939331]) (a6989586621679949019 :: [a6989586621679939331]) = Union a6989586621679949018 a6989586621679949019 Source #
data IntersectSym0 :: forall a6989586621679939361. (~>) [a6989586621679939361] ((~>) [a6989586621679939361] [a6989586621679939361]) Source #
Instances
SEq a => SingI (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing IntersectSym0 Source # | |
SuppressUnusedWarnings (IntersectSym0 :: TyFun [a6989586621679939361] ([a6989586621679939361] ~> [a6989586621679939361]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym0 :: TyFun [a6989586621679939361] ([a6989586621679939361] ~> [a6989586621679939361]) -> Type) (a6989586621679949613 :: [a6989586621679939361]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym0 :: TyFun [a6989586621679939361] ([a6989586621679939361] ~> [a6989586621679939361]) -> Type) (a6989586621679949613 :: [a6989586621679939361]) = IntersectSym1 a6989586621679949613 |
data IntersectSym1 (a6989586621679949613 :: [a6989586621679939361]) :: (~>) [a6989586621679939361] [a6989586621679939361] Source #
Instances
(SEq a, SingI d) => SingI (IntersectSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IntersectSym1 d) Source # | |
SuppressUnusedWarnings (IntersectSym1 a6989586621679949613 :: TyFun [a6989586621679939361] [a6989586621679939361] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym1 a6989586621679949613 :: TyFun [a] [a] -> Type) (a6989586621679949614 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym1 a6989586621679949613 :: TyFun [a] [a] -> Type) (a6989586621679949614 :: [a]) = Intersect a6989586621679949613 a6989586621679949614 |
type IntersectSym2 (a6989586621679949613 :: [a6989586621679939361]) (a6989586621679949614 :: [a6989586621679939361]) = Intersect a6989586621679949613 a6989586621679949614 Source #
data InsertSym0 :: forall a6989586621679939348. (~>) a6989586621679939348 ((~>) [a6989586621679939348] [a6989586621679939348]) Source #
Instances
SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing InsertSym0 Source # | |
SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621679939348 ([a6989586621679939348] ~> [a6989586621679939348]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym0 :: TyFun a6989586621679939348 ([a6989586621679939348] ~> [a6989586621679939348]) -> Type) (a6989586621679948955 :: a6989586621679939348) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym0 :: TyFun a6989586621679939348 ([a6989586621679939348] ~> [a6989586621679939348]) -> Type) (a6989586621679948955 :: a6989586621679939348) = InsertSym1 a6989586621679948955 |
data InsertSym1 (a6989586621679948955 :: a6989586621679939348) :: (~>) [a6989586621679939348] [a6989586621679939348] Source #
Instances
(SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (InsertSym1 d) Source # | |
SuppressUnusedWarnings (InsertSym1 a6989586621679948955 :: TyFun [a6989586621679939348] [a6989586621679939348] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym1 a6989586621679948955 :: TyFun [a] [a] -> Type) (a6989586621679948956 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym1 a6989586621679948955 :: TyFun [a] [a] -> Type) (a6989586621679948956 :: [a]) = Insert a6989586621679948955 a6989586621679948956 |
type InsertSym2 (a6989586621679948955 :: a6989586621679939348) (a6989586621679948956 :: [a6989586621679939348]) = Insert a6989586621679948955 a6989586621679948956 Source #
data SortSym0 :: forall a6989586621679939347. (~>) [a6989586621679939347] [a6989586621679939347] Source #
Instances
SOrd a => SingI (SortSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (SortSym0 :: TyFun [a6989586621679939347] [a6989586621679939347] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SortSym0 :: TyFun [a] [a] -> Type) (a6989586621679948971 :: [a]) Source # | |
data NubBySym0 :: forall a6989586621679939334. (~>) ((~>) a6989586621679939334 ((~>) a6989586621679939334 Bool)) ((~>) [a6989586621679939334] [a6989586621679939334]) Source #
Instances
SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (NubBySym0 :: TyFun (a6989586621679939334 ~> (a6989586621679939334 ~> Bool)) ([a6989586621679939334] ~> [a6989586621679939334]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym0 :: TyFun (a6989586621679939334 ~> (a6989586621679939334 ~> Bool)) ([a6989586621679939334] ~> [a6989586621679939334]) -> Type) (a6989586621679948601 :: a6989586621679939334 ~> (a6989586621679939334 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data NubBySym1 (a6989586621679948601 :: (~>) a6989586621679939334 ((~>) a6989586621679939334 Bool)) :: (~>) [a6989586621679939334] [a6989586621679939334] Source #
Instances
SingI d => SingI (NubBySym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (NubBySym1 a6989586621679948601 :: TyFun [a6989586621679939334] [a6989586621679939334] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym1 a6989586621679948601 :: TyFun [a] [a] -> Type) (a6989586621679948602 :: [a]) Source # | |
type NubBySym2 (a6989586621679948601 :: (~>) a6989586621679939334 ((~>) a6989586621679939334 Bool)) (a6989586621679948602 :: [a6989586621679939334]) = NubBy a6989586621679948601 a6989586621679948602 Source #
data DeleteBySym0 :: forall a6989586621679939373. (~>) ((~>) a6989586621679939373 ((~>) a6989586621679939373 Bool)) ((~>) a6989586621679939373 ((~>) [a6989586621679939373] [a6989586621679939373])) Source #
Instances
SingI (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing DeleteBySym0 Source # | |
SuppressUnusedWarnings (DeleteBySym0 :: TyFun (a6989586621679939373 ~> (a6989586621679939373 ~> Bool)) (a6989586621679939373 ~> ([a6989586621679939373] ~> [a6989586621679939373])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym0 :: TyFun (a6989586621679939373 ~> (a6989586621679939373 ~> Bool)) (a6989586621679939373 ~> ([a6989586621679939373] ~> [a6989586621679939373])) -> Type) (a6989586621679948974 :: a6989586621679939373 ~> (a6989586621679939373 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data DeleteBySym1 (a6989586621679948974 :: (~>) a6989586621679939373 ((~>) a6989586621679939373 Bool)) :: (~>) a6989586621679939373 ((~>) [a6989586621679939373] [a6989586621679939373]) Source #
Instances
SingI d => SingI (DeleteBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DeleteBySym1 d) Source # | |
SuppressUnusedWarnings (DeleteBySym1 a6989586621679948974 :: TyFun a6989586621679939373 ([a6989586621679939373] ~> [a6989586621679939373]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym1 a6989586621679948974 :: TyFun a6989586621679939373 ([a6989586621679939373] ~> [a6989586621679939373]) -> Type) (a6989586621679948975 :: a6989586621679939373) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym1 a6989586621679948974 :: TyFun a6989586621679939373 ([a6989586621679939373] ~> [a6989586621679939373]) -> Type) (a6989586621679948975 :: a6989586621679939373) = DeleteBySym2 a6989586621679948974 a6989586621679948975 |
data DeleteBySym2 (a6989586621679948974 :: (~>) a6989586621679939373 ((~>) a6989586621679939373 Bool)) (a6989586621679948975 :: a6989586621679939373) :: (~>) [a6989586621679939373] [a6989586621679939373] Source #
Instances
(SingI d1, SingI d2) => SingI (DeleteBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DeleteBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (DeleteBySym2 a6989586621679948975 a6989586621679948974 :: TyFun [a6989586621679939373] [a6989586621679939373] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym2 a6989586621679948975 a6989586621679948974 :: TyFun [a] [a] -> Type) (a6989586621679948976 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym2 a6989586621679948975 a6989586621679948974 :: TyFun [a] [a] -> Type) (a6989586621679948976 :: [a]) = DeleteBy a6989586621679948975 a6989586621679948974 a6989586621679948976 |
type DeleteBySym3 (a6989586621679948974 :: (~>) a6989586621679939373 ((~>) a6989586621679939373 Bool)) (a6989586621679948975 :: a6989586621679939373) (a6989586621679948976 :: [a6989586621679939373]) = DeleteBy a6989586621679948974 a6989586621679948975 a6989586621679948976 Source #
data DeleteFirstsBySym0 :: forall a6989586621679939372. (~>) ((~>) a6989586621679939372 ((~>) a6989586621679939372 Bool)) ((~>) [a6989586621679939372] ((~>) [a6989586621679939372] [a6989586621679939372])) Source #
Instances
SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (a6989586621679939372 ~> (a6989586621679939372 ~> Bool)) ([a6989586621679939372] ~> ([a6989586621679939372] ~> [a6989586621679939372])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679939372 ~> (a6989586621679939372 ~> Bool)) ([a6989586621679939372] ~> ([a6989586621679939372] ~> [a6989586621679939372])) -> Type) (a6989586621679948992 :: a6989586621679939372 ~> (a6989586621679939372 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679939372 ~> (a6989586621679939372 ~> Bool)) ([a6989586621679939372] ~> ([a6989586621679939372] ~> [a6989586621679939372])) -> Type) (a6989586621679948992 :: a6989586621679939372 ~> (a6989586621679939372 ~> Bool)) = DeleteFirstsBySym1 a6989586621679948992 |
data DeleteFirstsBySym1 (a6989586621679948992 :: (~>) a6989586621679939372 ((~>) a6989586621679939372 Bool)) :: (~>) [a6989586621679939372] ((~>) [a6989586621679939372] [a6989586621679939372]) Source #
Instances
SingI d => SingI (DeleteFirstsBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DeleteFirstsBySym1 d) Source # | |
SuppressUnusedWarnings (DeleteFirstsBySym1 a6989586621679948992 :: TyFun [a6989586621679939372] ([a6989586621679939372] ~> [a6989586621679939372]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym1 a6989586621679948992 :: TyFun [a6989586621679939372] ([a6989586621679939372] ~> [a6989586621679939372]) -> Type) (a6989586621679948993 :: [a6989586621679939372]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym1 a6989586621679948992 :: TyFun [a6989586621679939372] ([a6989586621679939372] ~> [a6989586621679939372]) -> Type) (a6989586621679948993 :: [a6989586621679939372]) = DeleteFirstsBySym2 a6989586621679948992 a6989586621679948993 |
data DeleteFirstsBySym2 (a6989586621679948992 :: (~>) a6989586621679939372 ((~>) a6989586621679939372 Bool)) (a6989586621679948993 :: [a6989586621679939372]) :: (~>) [a6989586621679939372] [a6989586621679939372] Source #
Instances
(SingI d1, SingI d2) => SingI (DeleteFirstsBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DeleteFirstsBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (DeleteFirstsBySym2 a6989586621679948993 a6989586621679948992 :: TyFun [a6989586621679939372] [a6989586621679939372] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym2 a6989586621679948993 a6989586621679948992 :: TyFun [a] [a] -> Type) (a6989586621679948994 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym2 a6989586621679948993 a6989586621679948992 :: TyFun [a] [a] -> Type) (a6989586621679948994 :: [a]) = DeleteFirstsBy a6989586621679948993 a6989586621679948992 a6989586621679948994 |
type DeleteFirstsBySym3 (a6989586621679948992 :: (~>) a6989586621679939372 ((~>) a6989586621679939372 Bool)) (a6989586621679948993 :: [a6989586621679939372]) (a6989586621679948994 :: [a6989586621679939372]) = DeleteFirstsBy a6989586621679948992 a6989586621679948993 a6989586621679948994 Source #
data UnionBySym0 :: forall a6989586621679939332. (~>) ((~>) a6989586621679939332 ((~>) a6989586621679939332 Bool)) ((~>) [a6989586621679939332] ((~>) [a6989586621679939332] [a6989586621679939332])) Source #
Instances
SingI (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing UnionBySym0 Source # | |
SuppressUnusedWarnings (UnionBySym0 :: TyFun (a6989586621679939332 ~> (a6989586621679939332 ~> Bool)) ([a6989586621679939332] ~> ([a6989586621679939332] ~> [a6989586621679939332])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym0 :: TyFun (a6989586621679939332 ~> (a6989586621679939332 ~> Bool)) ([a6989586621679939332] ~> ([a6989586621679939332] ~> [a6989586621679939332])) -> Type) (a6989586621679949005 :: a6989586621679939332 ~> (a6989586621679939332 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data UnionBySym1 (a6989586621679949005 :: (~>) a6989586621679939332 ((~>) a6989586621679939332 Bool)) :: (~>) [a6989586621679939332] ((~>) [a6989586621679939332] [a6989586621679939332]) Source #
Instances
SingI d => SingI (UnionBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (UnionBySym1 d) Source # | |
SuppressUnusedWarnings (UnionBySym1 a6989586621679949005 :: TyFun [a6989586621679939332] ([a6989586621679939332] ~> [a6989586621679939332]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym1 a6989586621679949005 :: TyFun [a6989586621679939332] ([a6989586621679939332] ~> [a6989586621679939332]) -> Type) (a6989586621679949006 :: [a6989586621679939332]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym1 a6989586621679949005 :: TyFun [a6989586621679939332] ([a6989586621679939332] ~> [a6989586621679939332]) -> Type) (a6989586621679949006 :: [a6989586621679939332]) = UnionBySym2 a6989586621679949005 a6989586621679949006 |
data UnionBySym2 (a6989586621679949005 :: (~>) a6989586621679939332 ((~>) a6989586621679939332 Bool)) (a6989586621679949006 :: [a6989586621679939332]) :: (~>) [a6989586621679939332] [a6989586621679939332] Source #
Instances
(SingI d1, SingI d2) => SingI (UnionBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (UnionBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (UnionBySym2 a6989586621679949006 a6989586621679949005 :: TyFun [a6989586621679939332] [a6989586621679939332] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym2 a6989586621679949006 a6989586621679949005 :: TyFun [a] [a] -> Type) (a6989586621679949007 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym2 a6989586621679949006 a6989586621679949005 :: TyFun [a] [a] -> Type) (a6989586621679949007 :: [a]) = UnionBy a6989586621679949006 a6989586621679949005 a6989586621679949007 |
type UnionBySym3 (a6989586621679949005 :: (~>) a6989586621679939332 ((~>) a6989586621679939332 Bool)) (a6989586621679949006 :: [a6989586621679939332]) (a6989586621679949007 :: [a6989586621679939332]) = UnionBy a6989586621679949005 a6989586621679949006 a6989586621679949007 Source #
data IntersectBySym0 :: forall a6989586621679939360. (~>) ((~>) a6989586621679939360 ((~>) a6989586621679939360 Bool)) ((~>) [a6989586621679939360] ((~>) [a6989586621679939360] [a6989586621679939360])) Source #
Instances
SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IntersectBySym0 :: TyFun (a6989586621679939360 ~> (a6989586621679939360 ~> Bool)) ([a6989586621679939360] ~> ([a6989586621679939360] ~> [a6989586621679939360])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym0 :: TyFun (a6989586621679939360 ~> (a6989586621679939360 ~> Bool)) ([a6989586621679939360] ~> ([a6989586621679939360] ~> [a6989586621679939360])) -> Type) (a6989586621679949577 :: a6989586621679939360 ~> (a6989586621679939360 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym0 :: TyFun (a6989586621679939360 ~> (a6989586621679939360 ~> Bool)) ([a6989586621679939360] ~> ([a6989586621679939360] ~> [a6989586621679939360])) -> Type) (a6989586621679949577 :: a6989586621679939360 ~> (a6989586621679939360 ~> Bool)) = IntersectBySym1 a6989586621679949577 |
data IntersectBySym1 (a6989586621679949577 :: (~>) a6989586621679939360 ((~>) a6989586621679939360 Bool)) :: (~>) [a6989586621679939360] ((~>) [a6989586621679939360] [a6989586621679939360]) Source #
Instances
SingI d => SingI (IntersectBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IntersectBySym1 d) Source # | |
SuppressUnusedWarnings (IntersectBySym1 a6989586621679949577 :: TyFun [a6989586621679939360] ([a6989586621679939360] ~> [a6989586621679939360]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym1 a6989586621679949577 :: TyFun [a6989586621679939360] ([a6989586621679939360] ~> [a6989586621679939360]) -> Type) (a6989586621679949578 :: [a6989586621679939360]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym1 a6989586621679949577 :: TyFun [a6989586621679939360] ([a6989586621679939360] ~> [a6989586621679939360]) -> Type) (a6989586621679949578 :: [a6989586621679939360]) = IntersectBySym2 a6989586621679949577 a6989586621679949578 |
data IntersectBySym2 (a6989586621679949577 :: (~>) a6989586621679939360 ((~>) a6989586621679939360 Bool)) (a6989586621679949578 :: [a6989586621679939360]) :: (~>) [a6989586621679939360] [a6989586621679939360] Source #
Instances
(SingI d1, SingI d2) => SingI (IntersectBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IntersectBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (IntersectBySym2 a6989586621679949578 a6989586621679949577 :: TyFun [a6989586621679939360] [a6989586621679939360] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym2 a6989586621679949578 a6989586621679949577 :: TyFun [a] [a] -> Type) (a6989586621679949579 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym2 a6989586621679949578 a6989586621679949577 :: TyFun [a] [a] -> Type) (a6989586621679949579 :: [a]) = IntersectBy a6989586621679949578 a6989586621679949577 a6989586621679949579 |
type IntersectBySym3 (a6989586621679949577 :: (~>) a6989586621679939360 ((~>) a6989586621679939360 Bool)) (a6989586621679949578 :: [a6989586621679939360]) (a6989586621679949579 :: [a6989586621679939360]) = IntersectBy a6989586621679949577 a6989586621679949578 a6989586621679949579 Source #
data GroupBySym0 :: forall a6989586621679939346. (~>) ((~>) a6989586621679939346 ((~>) a6989586621679939346 Bool)) ((~>) [a6989586621679939346] [[a6989586621679939346]]) Source #
Instances
SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing GroupBySym0 Source # | |
SuppressUnusedWarnings (GroupBySym0 :: TyFun (a6989586621679939346 ~> (a6989586621679939346 ~> Bool)) ([a6989586621679939346] ~> [[a6989586621679939346]]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym0 :: TyFun (a6989586621679939346 ~> (a6989586621679939346 ~> Bool)) ([a6989586621679939346] ~> [[a6989586621679939346]]) -> Type) (a6989586621679948842 :: a6989586621679939346 ~> (a6989586621679939346 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data GroupBySym1 (a6989586621679948842 :: (~>) a6989586621679939346 ((~>) a6989586621679939346 Bool)) :: (~>) [a6989586621679939346] [[a6989586621679939346]] Source #
Instances
SingI d => SingI (GroupBySym1 d :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (GroupBySym1 d) Source # | |
SuppressUnusedWarnings (GroupBySym1 a6989586621679948842 :: TyFun [a6989586621679939346] [[a6989586621679939346]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym1 a6989586621679948842 :: TyFun [a] [[a]] -> Type) (a6989586621679948843 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GroupBySym1 a6989586621679948842 :: TyFun [a] [[a]] -> Type) (a6989586621679948843 :: [a]) = GroupBy a6989586621679948842 a6989586621679948843 |
type GroupBySym2 (a6989586621679948842 :: (~>) a6989586621679939346 ((~>) a6989586621679939346 Bool)) (a6989586621679948843 :: [a6989586621679939346]) = GroupBy a6989586621679948842 a6989586621679948843 Source #
data SortBySym0 :: forall a6989586621679939371. (~>) ((~>) a6989586621679939371 ((~>) a6989586621679939371 Ordering)) ((~>) [a6989586621679939371] [a6989586621679939371]) Source #
Instances
SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing SortBySym0 Source # | |
SuppressUnusedWarnings (SortBySym0 :: TyFun (a6989586621679939371 ~> (a6989586621679939371 ~> Ordering)) ([a6989586621679939371] ~> [a6989586621679939371]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym0 :: TyFun (a6989586621679939371 ~> (a6989586621679939371 ~> Ordering)) ([a6989586621679939371] ~> [a6989586621679939371]) -> Type) (a6989586621679948961 :: a6989586621679939371 ~> (a6989586621679939371 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data SortBySym1 (a6989586621679948961 :: (~>) a6989586621679939371 ((~>) a6989586621679939371 Ordering)) :: (~>) [a6989586621679939371] [a6989586621679939371] Source #
Instances
SingI d => SingI (SortBySym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (SortBySym1 d) Source # | |
SuppressUnusedWarnings (SortBySym1 a6989586621679948961 :: TyFun [a6989586621679939371] [a6989586621679939371] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym1 a6989586621679948961 :: TyFun [a] [a] -> Type) (a6989586621679948962 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SortBySym1 a6989586621679948961 :: TyFun [a] [a] -> Type) (a6989586621679948962 :: [a]) = SortBy a6989586621679948961 a6989586621679948962 |
type SortBySym2 (a6989586621679948961 :: (~>) a6989586621679939371 ((~>) a6989586621679939371 Ordering)) (a6989586621679948962 :: [a6989586621679939371]) = SortBy a6989586621679948961 a6989586621679948962 Source #
data InsertBySym0 :: forall a6989586621679939370. (~>) ((~>) a6989586621679939370 ((~>) a6989586621679939370 Ordering)) ((~>) a6989586621679939370 ((~>) [a6989586621679939370] [a6989586621679939370])) Source #
Instances
SingI (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing InsertBySym0 Source # | |
SuppressUnusedWarnings (InsertBySym0 :: TyFun (a6989586621679939370 ~> (a6989586621679939370 ~> Ordering)) (a6989586621679939370 ~> ([a6989586621679939370] ~> [a6989586621679939370])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym0 :: TyFun (a6989586621679939370 ~> (a6989586621679939370 ~> Ordering)) (a6989586621679939370 ~> ([a6989586621679939370] ~> [a6989586621679939370])) -> Type) (a6989586621679948931 :: a6989586621679939370 ~> (a6989586621679939370 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym0 :: TyFun (a6989586621679939370 ~> (a6989586621679939370 ~> Ordering)) (a6989586621679939370 ~> ([a6989586621679939370] ~> [a6989586621679939370])) -> Type) (a6989586621679948931 :: a6989586621679939370 ~> (a6989586621679939370 ~> Ordering)) = InsertBySym1 a6989586621679948931 |
data InsertBySym1 (a6989586621679948931 :: (~>) a6989586621679939370 ((~>) a6989586621679939370 Ordering)) :: (~>) a6989586621679939370 ((~>) [a6989586621679939370] [a6989586621679939370]) Source #
Instances
SingI d => SingI (InsertBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (InsertBySym1 d) Source # | |
SuppressUnusedWarnings (InsertBySym1 a6989586621679948931 :: TyFun a6989586621679939370 ([a6989586621679939370] ~> [a6989586621679939370]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym1 a6989586621679948931 :: TyFun a6989586621679939370 ([a6989586621679939370] ~> [a6989586621679939370]) -> Type) (a6989586621679948932 :: a6989586621679939370) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym1 a6989586621679948931 :: TyFun a6989586621679939370 ([a6989586621679939370] ~> [a6989586621679939370]) -> Type) (a6989586621679948932 :: a6989586621679939370) = InsertBySym2 a6989586621679948931 a6989586621679948932 |
data InsertBySym2 (a6989586621679948931 :: (~>) a6989586621679939370 ((~>) a6989586621679939370 Ordering)) (a6989586621679948932 :: a6989586621679939370) :: (~>) [a6989586621679939370] [a6989586621679939370] Source #
Instances
(SingI d1, SingI d2) => SingI (InsertBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (InsertBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (InsertBySym2 a6989586621679948932 a6989586621679948931 :: TyFun [a6989586621679939370] [a6989586621679939370] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym2 a6989586621679948932 a6989586621679948931 :: TyFun [a] [a] -> Type) (a6989586621679948933 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym2 a6989586621679948932 a6989586621679948931 :: TyFun [a] [a] -> Type) (a6989586621679948933 :: [a]) = InsertBy a6989586621679948932 a6989586621679948931 a6989586621679948933 |
type InsertBySym3 (a6989586621679948931 :: (~>) a6989586621679939370 ((~>) a6989586621679939370 Ordering)) (a6989586621679948932 :: a6989586621679939370) (a6989586621679948933 :: [a6989586621679939370]) = InsertBy a6989586621679948931 a6989586621679948932 a6989586621679948933 Source #
data MaximumBySym0 :: forall a6989586621680448359 t6989586621680448358. (~>) ((~>) a6989586621680448359 ((~>) a6989586621680448359 Ordering)) ((~>) (t6989586621680448358 a6989586621680448359) a6989586621680448359) Source #
Instances
SFoldable t => SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing MaximumBySym0 Source # | |
SuppressUnusedWarnings (MaximumBySym0 :: TyFun (a6989586621680448359 ~> (a6989586621680448359 ~> Ordering)) (t6989586621680448358 a6989586621680448359 ~> a6989586621680448359) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym0 :: TyFun (a6989586621680448359 ~> (a6989586621680448359 ~> Ordering)) (t6989586621680448358 a6989586621680448359 ~> a6989586621680448359) -> Type) (a6989586621680448870 :: a6989586621680448359 ~> (a6989586621680448359 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym0 :: TyFun (a6989586621680448359 ~> (a6989586621680448359 ~> Ordering)) (t6989586621680448358 a6989586621680448359 ~> a6989586621680448359) -> Type) (a6989586621680448870 :: a6989586621680448359 ~> (a6989586621680448359 ~> Ordering)) = (MaximumBySym1 a6989586621680448870 t6989586621680448358 :: TyFun (t6989586621680448358 a6989586621680448359) a6989586621680448359 -> Type) |
data MaximumBySym1 (a6989586621680448870 :: (~>) a6989586621680448359 ((~>) a6989586621680448359 Ordering)) :: forall t6989586621680448358. (~>) (t6989586621680448358 a6989586621680448359) a6989586621680448359 Source #
Instances
(SFoldable t, SingI d) => SingI (MaximumBySym1 d t :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (MaximumBySym1 d t) Source # | |
SuppressUnusedWarnings (MaximumBySym1 a6989586621680448870 t6989586621680448358 :: TyFun (t6989586621680448358 a6989586621680448359) a6989586621680448359 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym1 a6989586621680448870 t :: TyFun (t a) a -> Type) (a6989586621680448871 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym1 a6989586621680448870 t :: TyFun (t a) a -> Type) (a6989586621680448871 :: t a) = MaximumBy a6989586621680448870 a6989586621680448871 |
type MaximumBySym2 (a6989586621680448870 :: (~>) a6989586621680448359 ((~>) a6989586621680448359 Ordering)) (a6989586621680448871 :: t6989586621680448358 a6989586621680448359) = MaximumBy a6989586621680448870 a6989586621680448871 Source #
data MinimumBySym0 :: forall a6989586621680448357 t6989586621680448356. (~>) ((~>) a6989586621680448357 ((~>) a6989586621680448357 Ordering)) ((~>) (t6989586621680448356 a6989586621680448357) a6989586621680448357) Source #
Instances
SFoldable t => SingI (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing MinimumBySym0 Source # | |
SuppressUnusedWarnings (MinimumBySym0 :: TyFun (a6989586621680448357 ~> (a6989586621680448357 ~> Ordering)) (t6989586621680448356 a6989586621680448357 ~> a6989586621680448357) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym0 :: TyFun (a6989586621680448357 ~> (a6989586621680448357 ~> Ordering)) (t6989586621680448356 a6989586621680448357 ~> a6989586621680448357) -> Type) (a6989586621680448845 :: a6989586621680448357 ~> (a6989586621680448357 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym0 :: TyFun (a6989586621680448357 ~> (a6989586621680448357 ~> Ordering)) (t6989586621680448356 a6989586621680448357 ~> a6989586621680448357) -> Type) (a6989586621680448845 :: a6989586621680448357 ~> (a6989586621680448357 ~> Ordering)) = (MinimumBySym1 a6989586621680448845 t6989586621680448356 :: TyFun (t6989586621680448356 a6989586621680448357) a6989586621680448357 -> Type) |
data MinimumBySym1 (a6989586621680448845 :: (~>) a6989586621680448357 ((~>) a6989586621680448357 Ordering)) :: forall t6989586621680448356. (~>) (t6989586621680448356 a6989586621680448357) a6989586621680448357 Source #
Instances
(SFoldable t, SingI d) => SingI (MinimumBySym1 d t :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (MinimumBySym1 d t) Source # | |
SuppressUnusedWarnings (MinimumBySym1 a6989586621680448845 t6989586621680448356 :: TyFun (t6989586621680448356 a6989586621680448357) a6989586621680448357 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym1 a6989586621680448845 t :: TyFun (t a) a -> Type) (a6989586621680448846 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym1 a6989586621680448845 t :: TyFun (t a) a -> Type) (a6989586621680448846 :: t a) = MinimumBy a6989586621680448845 a6989586621680448846 |
type MinimumBySym2 (a6989586621680448845 :: (~>) a6989586621680448357 ((~>) a6989586621680448357 Ordering)) (a6989586621680448846 :: t6989586621680448356 a6989586621680448357) = MinimumBy a6989586621680448845 a6989586621680448846 Source #
data GenericLengthSym0 :: forall a6989586621679939330 i6989586621679939329. (~>) [a6989586621679939330] i6989586621679939329 Source #
Instances
SNum i => SingI (GenericLengthSym0 :: TyFun [a] i -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a6989586621679939330] i6989586621679939329 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679948588 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679948588 :: [a]) = (GenericLength a6989586621679948588 :: k2) |
type GenericLengthSym1 (a6989586621679948588 :: [a6989586621679939330]) = GenericLength a6989586621679948588 Source #
data GenericTakeSym0 :: forall a6989586621680065532 i6989586621680065531. (~>) i6989586621680065531 ((~>) [a6989586621680065532] [a6989586621680065532]) Source #
Instances
SuppressUnusedWarnings (GenericTakeSym0 :: TyFun i6989586621680065531 ([a6989586621680065532] ~> [a6989586621680065532]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericTakeSym0 :: TyFun i6989586621680065531 ([a6989586621680065532] ~> [a6989586621680065532]) -> Type) (a6989586621680078075 :: i6989586621680065531) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericTakeSym0 :: TyFun i6989586621680065531 ([a6989586621680065532] ~> [a6989586621680065532]) -> Type) (a6989586621680078075 :: i6989586621680065531) = (GenericTakeSym1 a6989586621680078075 a6989586621680065532 :: TyFun [a6989586621680065532] [a6989586621680065532] -> Type) |
data GenericTakeSym1 (a6989586621680078075 :: i6989586621680065531) :: forall a6989586621680065532. (~>) [a6989586621680065532] [a6989586621680065532] Source #
Instances
SuppressUnusedWarnings (GenericTakeSym1 a6989586621680078075 a6989586621680065532 :: TyFun [a6989586621680065532] [a6989586621680065532] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericTakeSym1 a6989586621680078075 a :: TyFun [a] [a] -> Type) (a6989586621680078076 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericTakeSym1 a6989586621680078075 a :: TyFun [a] [a] -> Type) (a6989586621680078076 :: [a]) = GenericTake a6989586621680078075 a6989586621680078076 |
type GenericTakeSym2 (a6989586621680078075 :: i6989586621680065531) (a6989586621680078076 :: [a6989586621680065532]) = GenericTake a6989586621680078075 a6989586621680078076 Source #
data GenericDropSym0 :: forall a6989586621680065530 i6989586621680065529. (~>) i6989586621680065529 ((~>) [a6989586621680065530] [a6989586621680065530]) Source #
Instances
SuppressUnusedWarnings (GenericDropSym0 :: TyFun i6989586621680065529 ([a6989586621680065530] ~> [a6989586621680065530]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericDropSym0 :: TyFun i6989586621680065529 ([a6989586621680065530] ~> [a6989586621680065530]) -> Type) (a6989586621680078065 :: i6989586621680065529) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericDropSym0 :: TyFun i6989586621680065529 ([a6989586621680065530] ~> [a6989586621680065530]) -> Type) (a6989586621680078065 :: i6989586621680065529) = (GenericDropSym1 a6989586621680078065 a6989586621680065530 :: TyFun [a6989586621680065530] [a6989586621680065530] -> Type) |
data GenericDropSym1 (a6989586621680078065 :: i6989586621680065529) :: forall a6989586621680065530. (~>) [a6989586621680065530] [a6989586621680065530] Source #
Instances
SuppressUnusedWarnings (GenericDropSym1 a6989586621680078065 a6989586621680065530 :: TyFun [a6989586621680065530] [a6989586621680065530] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericDropSym1 a6989586621680078065 a :: TyFun [a] [a] -> Type) (a6989586621680078066 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericDropSym1 a6989586621680078065 a :: TyFun [a] [a] -> Type) (a6989586621680078066 :: [a]) = GenericDrop a6989586621680078065 a6989586621680078066 |
type GenericDropSym2 (a6989586621680078065 :: i6989586621680065529) (a6989586621680078066 :: [a6989586621680065530]) = GenericDrop a6989586621680078065 a6989586621680078066 Source #
data GenericSplitAtSym0 :: forall a6989586621680065528 i6989586621680065527. (~>) i6989586621680065527 ((~>) [a6989586621680065528] ([a6989586621680065528], [a6989586621680065528])) Source #
Instances
SuppressUnusedWarnings (GenericSplitAtSym0 :: TyFun i6989586621680065527 ([a6989586621680065528] ~> ([a6989586621680065528], [a6989586621680065528])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericSplitAtSym0 :: TyFun i6989586621680065527 ([a6989586621680065528] ~> ([a6989586621680065528], [a6989586621680065528])) -> Type) (a6989586621680078055 :: i6989586621680065527) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericSplitAtSym0 :: TyFun i6989586621680065527 ([a6989586621680065528] ~> ([a6989586621680065528], [a6989586621680065528])) -> Type) (a6989586621680078055 :: i6989586621680065527) = (GenericSplitAtSym1 a6989586621680078055 a6989586621680065528 :: TyFun [a6989586621680065528] ([a6989586621680065528], [a6989586621680065528]) -> Type) |
data GenericSplitAtSym1 (a6989586621680078055 :: i6989586621680065527) :: forall a6989586621680065528. (~>) [a6989586621680065528] ([a6989586621680065528], [a6989586621680065528]) Source #
Instances
SuppressUnusedWarnings (GenericSplitAtSym1 a6989586621680078055 a6989586621680065528 :: TyFun [a6989586621680065528] ([a6989586621680065528], [a6989586621680065528]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericSplitAtSym1 a6989586621680078055 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621680078056 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericSplitAtSym1 a6989586621680078055 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621680078056 :: [a]) = GenericSplitAt a6989586621680078055 a6989586621680078056 |
type GenericSplitAtSym2 (a6989586621680078055 :: i6989586621680065527) (a6989586621680078056 :: [a6989586621680065528]) = GenericSplitAt a6989586621680078055 a6989586621680078056 Source #
data GenericIndexSym0 :: forall a6989586621680065526 i6989586621680065525. (~>) [a6989586621680065526] ((~>) i6989586621680065525 a6989586621680065526) Source #
Instances
SuppressUnusedWarnings (GenericIndexSym0 :: TyFun [a6989586621680065526] (i6989586621680065525 ~> a6989586621680065526) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericIndexSym0 :: TyFun [a6989586621680065526] (i6989586621680065525 ~> a6989586621680065526) -> Type) (a6989586621680078045 :: [a6989586621680065526]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericIndexSym0 :: TyFun [a6989586621680065526] (i6989586621680065525 ~> a6989586621680065526) -> Type) (a6989586621680078045 :: [a6989586621680065526]) = (GenericIndexSym1 a6989586621680078045 i6989586621680065525 :: TyFun i6989586621680065525 a6989586621680065526 -> Type) |
data GenericIndexSym1 (a6989586621680078045 :: [a6989586621680065526]) :: forall i6989586621680065525. (~>) i6989586621680065525 a6989586621680065526 Source #
Instances
SuppressUnusedWarnings (GenericIndexSym1 a6989586621680078045 i6989586621680065525 :: TyFun i6989586621680065525 a6989586621680065526 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericIndexSym1 a6989586621680078045 i :: TyFun i a -> Type) (a6989586621680078046 :: i) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericIndexSym1 a6989586621680078045 i :: TyFun i a -> Type) (a6989586621680078046 :: i) = GenericIndex a6989586621680078045 a6989586621680078046 |
type GenericIndexSym2 (a6989586621680078045 :: [a6989586621680065526]) (a6989586621680078046 :: i6989586621680065525) = GenericIndex a6989586621680078045 a6989586621680078046 Source #
data GenericReplicateSym0 :: forall a6989586621680065524 i6989586621680065523. (~>) i6989586621680065523 ((~>) a6989586621680065524 [a6989586621680065524]) Source #
Instances
SuppressUnusedWarnings (GenericReplicateSym0 :: TyFun i6989586621680065523 (a6989586621680065524 ~> [a6989586621680065524]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericReplicateSym0 :: TyFun i6989586621680065523 (a6989586621680065524 ~> [a6989586621680065524]) -> Type) (a6989586621680078035 :: i6989586621680065523) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericReplicateSym0 :: TyFun i6989586621680065523 (a6989586621680065524 ~> [a6989586621680065524]) -> Type) (a6989586621680078035 :: i6989586621680065523) = (GenericReplicateSym1 a6989586621680078035 a6989586621680065524 :: TyFun a6989586621680065524 [a6989586621680065524] -> Type) |
data GenericReplicateSym1 (a6989586621680078035 :: i6989586621680065523) :: forall a6989586621680065524. (~>) a6989586621680065524 [a6989586621680065524] Source #
Instances
SuppressUnusedWarnings (GenericReplicateSym1 a6989586621680078035 a6989586621680065524 :: TyFun a6989586621680065524 [a6989586621680065524] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericReplicateSym1 a6989586621680078035 a :: TyFun a [a] -> Type) (a6989586621680078036 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericReplicateSym1 a6989586621680078035 a :: TyFun a [a] -> Type) (a6989586621680078036 :: a) = GenericReplicate a6989586621680078035 a6989586621680078036 |
type GenericReplicateSym2 (a6989586621680078035 :: i6989586621680065523) (a6989586621680078036 :: a6989586621680065524) = GenericReplicate a6989586621680078035 a6989586621680078036 Source #