Copyright | (C) 2013-2014 Richard Eisenberg Jan Stolarek |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Defines functions and datatypes relating to the singleton for '[]',
including a singletons version of a few of the definitions in Data.List
.
Because many of these definitions are produced by Template Haskell,
it is not possible to create proper Haddock documentation. Please look
up the corresponding operation in Data.List
. Also, please excuse
the apparent repeated variable names. This is due to an interaction
between Template Haskell and Haddock.
Synopsis
- type family Sing :: k -> Type
- data SList :: forall a. [a] -> Type where
- type family (a :: [a]) ++ (a :: [a]) :: [a] where ...
- (%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a])
- type family Head (a :: [a]) :: a where ...
- sHead :: forall a (t :: [a]). Sing t -> Sing (Apply HeadSym0 t :: a)
- type family Last (a :: [a]) :: a where ...
- sLast :: forall a (t :: [a]). Sing t -> Sing (Apply LastSym0 t :: a)
- type family Tail (a :: [a]) :: [a] where ...
- sTail :: forall a (t :: [a]). Sing t -> Sing (Apply TailSym0 t :: [a])
- type family Init (a :: [a]) :: [a] where ...
- sInit :: forall a (t :: [a]). Sing t -> Sing (Apply InitSym0 t :: [a])
- type family Null (arg :: t a) :: Bool
- sNull :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply NullSym0 t :: Bool)
- type family Length (arg :: t a) :: 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 a b t (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b])
- type family And (a :: t Bool) :: Bool where ...
- sAnd :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool)
- type family Or (a :: t Bool) :: Bool where ...
- sOr :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool)
- type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ...
- sAny :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool)
- type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ...
- sAll :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool)
- type family Sum (arg :: t a) :: a
- sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a)
- type family Product (arg :: t a) :: a
- sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a)
- type family Maximum (arg :: t a) :: a
- sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a)
- type family Minimum (arg :: t a) :: a
- sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a)
- type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: [b] where ...
- sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b])
- type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
- sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a])
- type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: [b] where ...
- sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b])
- type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
- sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a])
- type family MapAccumL (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
- sMapAccumL :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (a, t c))
- type family MapAccumR (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
- sMapAccumR :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c))
- type family Replicate (a :: 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 a t (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool)
- type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ...
- sLookup :: forall a b (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b)
- type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ...
- sFind :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a)
- type family Filter (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
- type family Partition (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
- type family (a :: [a]) !! (a :: 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 a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a)
- type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
- sMinimumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a)
- type family GenericLength (a :: [a]) :: i where ...
- sGenericLength :: forall a i (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i)
- type family 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 (:@#@$$) (t6989586621679315156 :: a3530822107858468865 :: Type) :: (~>) [a3530822107858468865] [a3530822107858468865 :: Type]
- type (:@#@$$$) (t6989586621679315156 :: a3530822107858468865) (t6989586621679315157 :: [a3530822107858468865]) = '(:) t6989586621679315156 t6989586621679315157
- type (++@#@$$$) (a6989586621679545630 :: [a6989586621679545433]) (a6989586621679545631 :: [a6989586621679545433]) = (++) a6989586621679545630 a6989586621679545631
- data (++@#@$$) (a6989586621679545630 :: [a6989586621679545433]) :: (~>) [a6989586621679545433] [a6989586621679545433]
- data (++@#@$) :: forall a6989586621679545433. (~>) [a6989586621679545433] ((~>) [a6989586621679545433] [a6989586621679545433])
- data HeadSym0 :: forall a6989586621679974183. (~>) [a6989586621679974183] a6989586621679974183
- type HeadSym1 (a6989586621679979530 :: [a6989586621679974183]) = Head a6989586621679979530
- data LastSym0 :: forall a6989586621679974182. (~>) [a6989586621679974182] a6989586621679974182
- type LastSym1 (a6989586621679979525 :: [a6989586621679974182]) = Last a6989586621679979525
- data TailSym0 :: forall a6989586621679974181. (~>) [a6989586621679974181] [a6989586621679974181]
- type TailSym1 (a6989586621679979522 :: [a6989586621679974181]) = Tail a6989586621679979522
- data InitSym0 :: forall a6989586621679974180. (~>) [a6989586621679974180] [a6989586621679974180]
- type InitSym1 (a6989586621679979508 :: [a6989586621679974180]) = Init a6989586621679979508
- data NullSym0 :: forall t6989586621680490502 a6989586621680490517. (~>) (t6989586621680490502 a6989586621680490517) Bool
- type NullSym1 (arg6989586621680491161 :: t6989586621680490502 a6989586621680490517) = Null arg6989586621680491161
- data LengthSym0 :: forall t6989586621680490502 a6989586621680490518. (~>) (t6989586621680490502 a6989586621680490518) Nat
- type LengthSym1 (arg6989586621680491163 :: t6989586621680490502 a6989586621680490518) = Length arg6989586621680491163
- data MapSym0 :: forall a6989586621679545434 b6989586621679545435. (~>) ((~>) a6989586621679545434 b6989586621679545435) ((~>) [a6989586621679545434] [b6989586621679545435])
- data MapSym1 (a6989586621679545638 :: (~>) a6989586621679545434 b6989586621679545435) :: (~>) [a6989586621679545434] [b6989586621679545435]
- type MapSym2 (a6989586621679545638 :: (~>) a6989586621679545434 b6989586621679545435) (a6989586621679545639 :: [a6989586621679545434]) = Map a6989586621679545638 a6989586621679545639
- data ReverseSym0 :: forall a6989586621679974178. (~>) [a6989586621679974178] [a6989586621679974178]
- type ReverseSym1 (a6989586621679979493 :: [a6989586621679974178]) = Reverse a6989586621679979493
- data IntersperseSym0 :: forall a6989586621679974177. (~>) a6989586621679974177 ((~>) [a6989586621679974177] [a6989586621679974177])
- data IntersperseSym1 (a6989586621679979486 :: a6989586621679974177) :: (~>) [a6989586621679974177] [a6989586621679974177]
- type IntersperseSym2 (a6989586621679979486 :: a6989586621679974177) (a6989586621679979487 :: [a6989586621679974177]) = Intersperse a6989586621679979486 a6989586621679979487
- data IntercalateSym0 :: forall a6989586621679974176. (~>) [a6989586621679974176] ((~>) [[a6989586621679974176]] [a6989586621679974176])
- data IntercalateSym1 (a6989586621679979480 :: [a6989586621679974176]) :: (~>) [[a6989586621679974176]] [a6989586621679974176]
- type IntercalateSym2 (a6989586621679979480 :: [a6989586621679974176]) (a6989586621679979481 :: [[a6989586621679974176]]) = Intercalate a6989586621679979480 a6989586621679979481
- data TransposeSym0 :: forall a6989586621679974063. (~>) [[a6989586621679974063]] [[a6989586621679974063]]
- type TransposeSym1 (a6989586621679978223 :: [[a6989586621679974063]]) = Transpose a6989586621679978223
- data SubsequencesSym0 :: forall a6989586621679974175. (~>) [a6989586621679974175] [[a6989586621679974175]]
- type SubsequencesSym1 (a6989586621679979477 :: [a6989586621679974175]) = Subsequences a6989586621679979477
- data PermutationsSym0 :: forall a6989586621679974172. (~>) [a6989586621679974172] [[a6989586621679974172]]
- type PermutationsSym1 (a6989586621679979359 :: [a6989586621679974172]) = Permutations a6989586621679979359
- data FoldlSym0 :: forall b6989586621680490510 a6989586621680490511 t6989586621680490502. (~>) ((~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) ((~>) b6989586621680490510 ((~>) (t6989586621680490502 a6989586621680490511) b6989586621680490510))
- data FoldlSym1 (arg6989586621680491139 :: (~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) :: forall t6989586621680490502. (~>) b6989586621680490510 ((~>) (t6989586621680490502 a6989586621680490511) b6989586621680490510)
- data FoldlSym2 (arg6989586621680491139 :: (~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) (arg6989586621680491140 :: b6989586621680490510) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490511) b6989586621680490510
- type FoldlSym3 (arg6989586621680491139 :: (~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) (arg6989586621680491140 :: b6989586621680490510) (arg6989586621680491141 :: t6989586621680490502 a6989586621680490511) = Foldl arg6989586621680491139 arg6989586621680491140 arg6989586621680491141
- data Foldl'Sym0 :: forall b6989586621680490512 a6989586621680490513 t6989586621680490502. (~>) ((~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) ((~>) b6989586621680490512 ((~>) (t6989586621680490502 a6989586621680490513) b6989586621680490512))
- data Foldl'Sym1 (arg6989586621680491145 :: (~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) :: forall t6989586621680490502. (~>) b6989586621680490512 ((~>) (t6989586621680490502 a6989586621680490513) b6989586621680490512)
- data Foldl'Sym2 (arg6989586621680491145 :: (~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) (arg6989586621680491146 :: b6989586621680490512) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490513) b6989586621680490512
- type Foldl'Sym3 (arg6989586621680491145 :: (~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) (arg6989586621680491146 :: b6989586621680490512) (arg6989586621680491147 :: t6989586621680490502 a6989586621680490513) = Foldl' arg6989586621680491145 arg6989586621680491146 arg6989586621680491147
- data Foldl1Sym0 :: forall a6989586621680490515 t6989586621680490502. (~>) ((~>) a6989586621680490515 ((~>) a6989586621680490515 a6989586621680490515)) ((~>) (t6989586621680490502 a6989586621680490515) a6989586621680490515)
- data Foldl1Sym1 (arg6989586621680491155 :: (~>) a6989586621680490515 ((~>) a6989586621680490515 a6989586621680490515)) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490515) a6989586621680490515
- type Foldl1Sym2 (arg6989586621680491155 :: (~>) a6989586621680490515 ((~>) a6989586621680490515 a6989586621680490515)) (arg6989586621680491156 :: t6989586621680490502 a6989586621680490515) = Foldl1 arg6989586621680491155 arg6989586621680491156
- data Foldl1'Sym0 :: forall a6989586621679974168. (~>) ((~>) a6989586621679974168 ((~>) a6989586621679974168 a6989586621679974168)) ((~>) [a6989586621679974168] a6989586621679974168)
- data Foldl1'Sym1 (a6989586621679979317 :: (~>) a6989586621679974168 ((~>) a6989586621679974168 a6989586621679974168)) :: (~>) [a6989586621679974168] a6989586621679974168
- type Foldl1'Sym2 (a6989586621679979317 :: (~>) a6989586621679974168 ((~>) a6989586621679974168 a6989586621679974168)) (a6989586621679979318 :: [a6989586621679974168]) = Foldl1' a6989586621679979317 a6989586621679979318
- data FoldrSym0 :: forall a6989586621680490506 b6989586621680490507 t6989586621680490502. (~>) ((~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) ((~>) b6989586621680490507 ((~>) (t6989586621680490502 a6989586621680490506) b6989586621680490507))
- data FoldrSym1 (arg6989586621680491127 :: (~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) :: forall t6989586621680490502. (~>) b6989586621680490507 ((~>) (t6989586621680490502 a6989586621680490506) b6989586621680490507)
- data FoldrSym2 (arg6989586621680491127 :: (~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) (arg6989586621680491128 :: b6989586621680490507) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490506) b6989586621680490507
- type FoldrSym3 (arg6989586621680491127 :: (~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) (arg6989586621680491128 :: b6989586621680490507) (arg6989586621680491129 :: t6989586621680490502 a6989586621680490506) = Foldr arg6989586621680491127 arg6989586621680491128 arg6989586621680491129
- data Foldr1Sym0 :: forall a6989586621680490514 t6989586621680490502. (~>) ((~>) a6989586621680490514 ((~>) a6989586621680490514 a6989586621680490514)) ((~>) (t6989586621680490502 a6989586621680490514) a6989586621680490514)
- data Foldr1Sym1 (arg6989586621680491151 :: (~>) a6989586621680490514 ((~>) a6989586621680490514 a6989586621680490514)) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490514) a6989586621680490514
- type Foldr1Sym2 (arg6989586621680491151 :: (~>) a6989586621680490514 ((~>) a6989586621680490514 a6989586621680490514)) (arg6989586621680491152 :: t6989586621680490502 a6989586621680490514) = Foldr1 arg6989586621680491151 arg6989586621680491152
- data ConcatSym0 :: forall t6989586621680490427 a6989586621680490428. (~>) (t6989586621680490427 [a6989586621680490428]) [a6989586621680490428]
- type ConcatSym1 (a6989586621680491009 :: t6989586621680490427 [a6989586621680490428]) = Concat a6989586621680491009
- data ConcatMapSym0 :: forall a6989586621680490425 b6989586621680490426 t6989586621680490424. (~>) ((~>) a6989586621680490425 [b6989586621680490426]) ((~>) (t6989586621680490424 a6989586621680490425) [b6989586621680490426])
- data ConcatMapSym1 (a6989586621680490993 :: (~>) a6989586621680490425 [b6989586621680490426]) :: forall t6989586621680490424. (~>) (t6989586621680490424 a6989586621680490425) [b6989586621680490426]
- type ConcatMapSym2 (a6989586621680490993 :: (~>) a6989586621680490425 [b6989586621680490426]) (a6989586621680490994 :: t6989586621680490424 a6989586621680490425) = ConcatMap a6989586621680490993 a6989586621680490994
- data AndSym0 :: forall t6989586621680490423. (~>) (t6989586621680490423 Bool) Bool
- type AndSym1 (a6989586621680490984 :: t6989586621680490423 Bool) = And a6989586621680490984
- data OrSym0 :: forall t6989586621680490422. (~>) (t6989586621680490422 Bool) Bool
- type OrSym1 (a6989586621680490975 :: t6989586621680490422 Bool) = Or a6989586621680490975
- data AnySym0 :: forall a6989586621680490421 t6989586621680490420. (~>) ((~>) a6989586621680490421 Bool) ((~>) (t6989586621680490420 a6989586621680490421) Bool)
- data AnySym1 (a6989586621680490962 :: (~>) a6989586621680490421 Bool) :: forall t6989586621680490420. (~>) (t6989586621680490420 a6989586621680490421) Bool
- type AnySym2 (a6989586621680490962 :: (~>) a6989586621680490421 Bool) (a6989586621680490963 :: t6989586621680490420 a6989586621680490421) = Any a6989586621680490962 a6989586621680490963
- data AllSym0 :: forall a6989586621680490419 t6989586621680490418. (~>) ((~>) a6989586621680490419 Bool) ((~>) (t6989586621680490418 a6989586621680490419) Bool)
- data AllSym1 (a6989586621680490949 :: (~>) a6989586621680490419 Bool) :: forall t6989586621680490418. (~>) (t6989586621680490418 a6989586621680490419) Bool
- type AllSym2 (a6989586621680490949 :: (~>) a6989586621680490419 Bool) (a6989586621680490950 :: t6989586621680490418 a6989586621680490419) = All a6989586621680490949 a6989586621680490950
- data SumSym0 :: forall t6989586621680490502 a6989586621680490522. (~>) (t6989586621680490502 a6989586621680490522) a6989586621680490522
- type SumSym1 (arg6989586621680491173 :: t6989586621680490502 a6989586621680490522) = Sum arg6989586621680491173
- data ProductSym0 :: forall t6989586621680490502 a6989586621680490523. (~>) (t6989586621680490502 a6989586621680490523) a6989586621680490523
- type ProductSym1 (arg6989586621680491175 :: t6989586621680490502 a6989586621680490523) = Product arg6989586621680491175
- data MaximumSym0 :: forall t6989586621680490502 a6989586621680490520. (~>) (t6989586621680490502 a6989586621680490520) a6989586621680490520
- type MaximumSym1 (arg6989586621680491169 :: t6989586621680490502 a6989586621680490520) = Maximum arg6989586621680491169
- data MinimumSym0 :: forall t6989586621680490502 a6989586621680490521. (~>) (t6989586621680490502 a6989586621680490521) a6989586621680490521
- type MinimumSym1 (arg6989586621680491171 :: t6989586621680490502 a6989586621680490521) = Minimum arg6989586621680491171
- data ScanlSym0 :: forall b6989586621679974160 a6989586621679974161. (~>) ((~>) b6989586621679974160 ((~>) a6989586621679974161 b6989586621679974160)) ((~>) b6989586621679974160 ((~>) [a6989586621679974161] [b6989586621679974160]))
- data ScanlSym1 (a6989586621679979254 :: (~>) b6989586621679974160 ((~>) a6989586621679974161 b6989586621679974160)) :: (~>) b6989586621679974160 ((~>) [a6989586621679974161] [b6989586621679974160])
- data ScanlSym2 (a6989586621679979254 :: (~>) b6989586621679974160 ((~>) a6989586621679974161 b6989586621679974160)) (a6989586621679979255 :: b6989586621679974160) :: (~>) [a6989586621679974161] [b6989586621679974160]
- type ScanlSym3 (a6989586621679979254 :: (~>) b6989586621679974160 ((~>) a6989586621679974161 b6989586621679974160)) (a6989586621679979255 :: b6989586621679974160) (a6989586621679979256 :: [a6989586621679974161]) = Scanl a6989586621679979254 a6989586621679979255 a6989586621679979256
- data Scanl1Sym0 :: forall a6989586621679974159. (~>) ((~>) a6989586621679974159 ((~>) a6989586621679974159 a6989586621679974159)) ((~>) [a6989586621679974159] [a6989586621679974159])
- data Scanl1Sym1 (a6989586621679979247 :: (~>) a6989586621679974159 ((~>) a6989586621679974159 a6989586621679974159)) :: (~>) [a6989586621679974159] [a6989586621679974159]
- type Scanl1Sym2 (a6989586621679979247 :: (~>) a6989586621679974159 ((~>) a6989586621679974159 a6989586621679974159)) (a6989586621679979248 :: [a6989586621679974159]) = Scanl1 a6989586621679979247 a6989586621679979248
- data ScanrSym0 :: forall a6989586621679974157 b6989586621679974158. (~>) ((~>) a6989586621679974157 ((~>) b6989586621679974158 b6989586621679974158)) ((~>) b6989586621679974158 ((~>) [a6989586621679974157] [b6989586621679974158]))
- data ScanrSym1 (a6989586621679979226 :: (~>) a6989586621679974157 ((~>) b6989586621679974158 b6989586621679974158)) :: (~>) b6989586621679974158 ((~>) [a6989586621679974157] [b6989586621679974158])
- data ScanrSym2 (a6989586621679979226 :: (~>) a6989586621679974157 ((~>) b6989586621679974158 b6989586621679974158)) (a6989586621679979227 :: b6989586621679974158) :: (~>) [a6989586621679974157] [b6989586621679974158]
- type ScanrSym3 (a6989586621679979226 :: (~>) a6989586621679974157 ((~>) b6989586621679974158 b6989586621679974158)) (a6989586621679979227 :: b6989586621679974158) (a6989586621679979228 :: [a6989586621679974157]) = Scanr a6989586621679979226 a6989586621679979227 a6989586621679979228
- data Scanr1Sym0 :: forall a6989586621679974156. (~>) ((~>) a6989586621679974156 ((~>) a6989586621679974156 a6989586621679974156)) ((~>) [a6989586621679974156] [a6989586621679974156])
- data Scanr1Sym1 (a6989586621679979202 :: (~>) a6989586621679974156 ((~>) a6989586621679974156 a6989586621679974156)) :: (~>) [a6989586621679974156] [a6989586621679974156]
- type Scanr1Sym2 (a6989586621679979202 :: (~>) a6989586621679974156 ((~>) a6989586621679974156 a6989586621679974156)) (a6989586621679979203 :: [a6989586621679974156]) = Scanr1 a6989586621679979202 a6989586621679979203
- data MapAccumLSym0 :: forall a6989586621680804227 b6989586621680804228 c6989586621680804229 t6989586621680804226. (~>) ((~>) a6989586621680804227 ((~>) b6989586621680804228 (a6989586621680804227, c6989586621680804229))) ((~>) a6989586621680804227 ((~>) (t6989586621680804226 b6989586621680804228) (a6989586621680804227, t6989586621680804226 c6989586621680804229)))
- data MapAccumLSym1 (a6989586621680804730 :: (~>) a6989586621680804227 ((~>) b6989586621680804228 (a6989586621680804227, c6989586621680804229))) :: forall t6989586621680804226. (~>) a6989586621680804227 ((~>) (t6989586621680804226 b6989586621680804228) (a6989586621680804227, t6989586621680804226 c6989586621680804229))
- data MapAccumLSym2 (a6989586621680804730 :: (~>) a6989586621680804227 ((~>) b6989586621680804228 (a6989586621680804227, c6989586621680804229))) (a6989586621680804731 :: a6989586621680804227) :: forall t6989586621680804226. (~>) (t6989586621680804226 b6989586621680804228) (a6989586621680804227, t6989586621680804226 c6989586621680804229)
- type MapAccumLSym3 (a6989586621680804730 :: (~>) a6989586621680804227 ((~>) b6989586621680804228 (a6989586621680804227, c6989586621680804229))) (a6989586621680804731 :: a6989586621680804227) (a6989586621680804732 :: t6989586621680804226 b6989586621680804228) = MapAccumL a6989586621680804730 a6989586621680804731 a6989586621680804732
- data MapAccumRSym0 :: forall a6989586621680804223 b6989586621680804224 c6989586621680804225 t6989586621680804222. (~>) ((~>) a6989586621680804223 ((~>) b6989586621680804224 (a6989586621680804223, c6989586621680804225))) ((~>) a6989586621680804223 ((~>) (t6989586621680804222 b6989586621680804224) (a6989586621680804223, t6989586621680804222 c6989586621680804225)))
- data MapAccumRSym1 (a6989586621680804713 :: (~>) a6989586621680804223 ((~>) b6989586621680804224 (a6989586621680804223, c6989586621680804225))) :: forall t6989586621680804222. (~>) a6989586621680804223 ((~>) (t6989586621680804222 b6989586621680804224) (a6989586621680804223, t6989586621680804222 c6989586621680804225))
- data MapAccumRSym2 (a6989586621680804713 :: (~>) a6989586621680804223 ((~>) b6989586621680804224 (a6989586621680804223, c6989586621680804225))) (a6989586621680804714 :: a6989586621680804223) :: forall t6989586621680804222. (~>) (t6989586621680804222 b6989586621680804224) (a6989586621680804223, t6989586621680804222 c6989586621680804225)
- type MapAccumRSym3 (a6989586621680804713 :: (~>) a6989586621680804223 ((~>) b6989586621680804224 (a6989586621680804223, c6989586621680804225))) (a6989586621680804714 :: a6989586621680804223) (a6989586621680804715 :: t6989586621680804222 b6989586621680804224) = MapAccumR a6989586621680804713 a6989586621680804714 a6989586621680804715
- data ReplicateSym0 :: forall a6989586621679974064. (~>) Nat ((~>) a6989586621679974064 [a6989586621679974064])
- data ReplicateSym1 (a6989586621679978229 :: Nat) :: forall a6989586621679974064. (~>) a6989586621679974064 [a6989586621679974064]
- type ReplicateSym2 (a6989586621679978229 :: Nat) (a6989586621679978230 :: a6989586621679974064) = Replicate a6989586621679978229 a6989586621679978230
- data UnfoldrSym0 :: forall b6989586621679974148 a6989586621679974149. (~>) ((~>) b6989586621679974148 (Maybe (a6989586621679974149, b6989586621679974148))) ((~>) b6989586621679974148 [a6989586621679974149])
- data UnfoldrSym1 (a6989586621679979060 :: (~>) b6989586621679974148 (Maybe (a6989586621679974149, b6989586621679974148))) :: (~>) b6989586621679974148 [a6989586621679974149]
- type UnfoldrSym2 (a6989586621679979060 :: (~>) b6989586621679974148 (Maybe (a6989586621679974149, b6989586621679974148))) (a6989586621679979061 :: b6989586621679974148) = Unfoldr a6989586621679979060 a6989586621679979061
- data TakeSym0 :: forall a6989586621679974080. (~>) Nat ((~>) [a6989586621679974080] [a6989586621679974080])
- data TakeSym1 (a6989586621679978390 :: Nat) :: forall a6989586621679974080. (~>) [a6989586621679974080] [a6989586621679974080]
- type TakeSym2 (a6989586621679978390 :: Nat) (a6989586621679978391 :: [a6989586621679974080]) = Take a6989586621679978390 a6989586621679978391
- data DropSym0 :: forall a6989586621679974079. (~>) Nat ((~>) [a6989586621679974079] [a6989586621679974079])
- data DropSym1 (a6989586621679978376 :: Nat) :: forall a6989586621679974079. (~>) [a6989586621679974079] [a6989586621679974079]
- type DropSym2 (a6989586621679978376 :: Nat) (a6989586621679978377 :: [a6989586621679974079]) = Drop a6989586621679978376 a6989586621679978377
- data SplitAtSym0 :: forall a6989586621679974078. (~>) Nat ((~>) [a6989586621679974078] ([a6989586621679974078], [a6989586621679974078]))
- data SplitAtSym1 (a6989586621679978370 :: Nat) :: forall a6989586621679974078. (~>) [a6989586621679974078] ([a6989586621679974078], [a6989586621679974078])
- type SplitAtSym2 (a6989586621679978370 :: Nat) (a6989586621679978371 :: [a6989586621679974078]) = SplitAt a6989586621679978370 a6989586621679978371
- data TakeWhileSym0 :: forall a6989586621679974085. (~>) ((~>) a6989586621679974085 Bool) ((~>) [a6989586621679974085] [a6989586621679974085])
- data TakeWhileSym1 (a6989586621679978534 :: (~>) a6989586621679974085 Bool) :: (~>) [a6989586621679974085] [a6989586621679974085]
- type TakeWhileSym2 (a6989586621679978534 :: (~>) a6989586621679974085 Bool) (a6989586621679978535 :: [a6989586621679974085]) = TakeWhile a6989586621679978534 a6989586621679978535
- data DropWhileSym0 :: forall a6989586621679974084. (~>) ((~>) a6989586621679974084 Bool) ((~>) [a6989586621679974084] [a6989586621679974084])
- data DropWhileSym1 (a6989586621679978516 :: (~>) a6989586621679974084 Bool) :: (~>) [a6989586621679974084] [a6989586621679974084]
- type DropWhileSym2 (a6989586621679978516 :: (~>) a6989586621679974084 Bool) (a6989586621679978517 :: [a6989586621679974084]) = DropWhile a6989586621679978516 a6989586621679978517
- data DropWhileEndSym0 :: forall a6989586621679974083. (~>) ((~>) a6989586621679974083 Bool) ((~>) [a6989586621679974083] [a6989586621679974083])
- data DropWhileEndSym1 (a6989586621679978490 :: (~>) a6989586621679974083 Bool) :: (~>) [a6989586621679974083] [a6989586621679974083]
- type DropWhileEndSym2 (a6989586621679978490 :: (~>) a6989586621679974083 Bool) (a6989586621679978491 :: [a6989586621679974083]) = DropWhileEnd a6989586621679978490 a6989586621679978491
- data SpanSym0 :: forall a6989586621679974082. (~>) ((~>) a6989586621679974082 Bool) ((~>) [a6989586621679974082] ([a6989586621679974082], [a6989586621679974082]))
- data SpanSym1 (a6989586621679978447 :: (~>) a6989586621679974082 Bool) :: (~>) [a6989586621679974082] ([a6989586621679974082], [a6989586621679974082])
- type SpanSym2 (a6989586621679978447 :: (~>) a6989586621679974082 Bool) (a6989586621679978448 :: [a6989586621679974082]) = Span a6989586621679978447 a6989586621679978448
- data BreakSym0 :: forall a6989586621679974081. (~>) ((~>) a6989586621679974081 Bool) ((~>) [a6989586621679974081] ([a6989586621679974081], [a6989586621679974081]))
- data BreakSym1 (a6989586621679978404 :: (~>) a6989586621679974081 Bool) :: (~>) [a6989586621679974081] ([a6989586621679974081], [a6989586621679974081])
- type BreakSym2 (a6989586621679978404 :: (~>) a6989586621679974081 Bool) (a6989586621679978405 :: [a6989586621679974081]) = Break a6989586621679978404 a6989586621679978405
- data StripPrefixSym0 :: forall a6989586621680096271. (~>) [a6989586621680096271] ((~>) [a6989586621680096271] (Maybe [a6989586621680096271]))
- data StripPrefixSym1 (a6989586621680097967 :: [a6989586621680096271]) :: (~>) [a6989586621680096271] (Maybe [a6989586621680096271])
- type StripPrefixSym2 (a6989586621680097967 :: [a6989586621680096271]) (a6989586621680097968 :: [a6989586621680096271]) = StripPrefix a6989586621680097967 a6989586621680097968
- data GroupSym0 :: forall a6989586621679974077. (~>) [a6989586621679974077] [[a6989586621679974077]]
- type GroupSym1 (a6989586621679978367 :: [a6989586621679974077]) = Group a6989586621679978367
- data InitsSym0 :: forall a6989586621679974147. (~>) [a6989586621679974147] [[a6989586621679974147]]
- type InitsSym1 (a6989586621679979052 :: [a6989586621679974147]) = Inits a6989586621679979052
- data TailsSym0 :: forall a6989586621679974146. (~>) [a6989586621679974146] [[a6989586621679974146]]
- type TailsSym1 (a6989586621679979045 :: [a6989586621679974146]) = Tails a6989586621679979045
- data IsPrefixOfSym0 :: forall a6989586621679974145. (~>) [a6989586621679974145] ((~>) [a6989586621679974145] Bool)
- data IsPrefixOfSym1 (a6989586621679979037 :: [a6989586621679974145]) :: (~>) [a6989586621679974145] Bool
- type IsPrefixOfSym2 (a6989586621679979037 :: [a6989586621679974145]) (a6989586621679979038 :: [a6989586621679974145]) = IsPrefixOf a6989586621679979037 a6989586621679979038
- data IsSuffixOfSym0 :: forall a6989586621679974144. (~>) [a6989586621679974144] ((~>) [a6989586621679974144] Bool)
- data IsSuffixOfSym1 (a6989586621679979031 :: [a6989586621679974144]) :: (~>) [a6989586621679974144] Bool
- type IsSuffixOfSym2 (a6989586621679979031 :: [a6989586621679974144]) (a6989586621679979032 :: [a6989586621679974144]) = IsSuffixOf a6989586621679979031 a6989586621679979032
- data IsInfixOfSym0 :: forall a6989586621679974143. (~>) [a6989586621679974143] ((~>) [a6989586621679974143] Bool)
- data IsInfixOfSym1 (a6989586621679979025 :: [a6989586621679974143]) :: (~>) [a6989586621679974143] Bool
- type IsInfixOfSym2 (a6989586621679979025 :: [a6989586621679974143]) (a6989586621679979026 :: [a6989586621679974143]) = IsInfixOf a6989586621679979025 a6989586621679979026
- data ElemSym0 :: forall a6989586621680490519 t6989586621680490502. (~>) a6989586621680490519 ((~>) (t6989586621680490502 a6989586621680490519) Bool)
- data ElemSym1 (arg6989586621680491165 :: a6989586621680490519) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490519) Bool
- type ElemSym2 (arg6989586621680491165 :: a6989586621680490519) (arg6989586621680491166 :: t6989586621680490502 a6989586621680490519) = Elem arg6989586621680491165 arg6989586621680491166
- data NotElemSym0 :: forall a6989586621680490413 t6989586621680490412. (~>) a6989586621680490413 ((~>) (t6989586621680490412 a6989586621680490413) Bool)
- data NotElemSym1 (a6989586621680490891 :: a6989586621680490413) :: forall t6989586621680490412. (~>) (t6989586621680490412 a6989586621680490413) Bool
- type NotElemSym2 (a6989586621680490891 :: a6989586621680490413) (a6989586621680490892 :: t6989586621680490412 a6989586621680490413) = NotElem a6989586621680490891 a6989586621680490892
- data LookupSym0 :: forall a6989586621679974070 b6989586621679974071. (~>) a6989586621679974070 ((~>) [(a6989586621679974070, b6989586621679974071)] (Maybe b6989586621679974071))
- data LookupSym1 (a6989586621679978294 :: a6989586621679974070) :: forall b6989586621679974071. (~>) [(a6989586621679974070, b6989586621679974071)] (Maybe b6989586621679974071)
- type LookupSym2 (a6989586621679978294 :: a6989586621679974070) (a6989586621679978295 :: [(a6989586621679974070, b6989586621679974071)]) = Lookup a6989586621679978294 a6989586621679978295
- data FindSym0 :: forall a6989586621680490411 t6989586621680490410. (~>) ((~>) a6989586621680490411 Bool) ((~>) (t6989586621680490410 a6989586621680490411) (Maybe a6989586621680490411))
- data FindSym1 (a6989586621680490864 :: (~>) a6989586621680490411 Bool) :: forall t6989586621680490410. (~>) (t6989586621680490410 a6989586621680490411) (Maybe a6989586621680490411)
- type FindSym2 (a6989586621680490864 :: (~>) a6989586621680490411 Bool) (a6989586621680490865 :: t6989586621680490410 a6989586621680490411) = Find a6989586621680490864 a6989586621680490865
- data FilterSym0 :: forall a6989586621679974093. (~>) ((~>) a6989586621679974093 Bool) ((~>) [a6989586621679974093] [a6989586621679974093])
- data FilterSym1 (a6989586621679978648 :: (~>) a6989586621679974093 Bool) :: (~>) [a6989586621679974093] [a6989586621679974093]
- type FilterSym2 (a6989586621679978648 :: (~>) a6989586621679974093 Bool) (a6989586621679978649 :: [a6989586621679974093]) = Filter a6989586621679978648 a6989586621679978649
- data PartitionSym0 :: forall a6989586621679974069. (~>) ((~>) a6989586621679974069 Bool) ((~>) [a6989586621679974069] ([a6989586621679974069], [a6989586621679974069]))
- data PartitionSym1 (a6989586621679978288 :: (~>) a6989586621679974069 Bool) :: (~>) [a6989586621679974069] ([a6989586621679974069], [a6989586621679974069])
- type PartitionSym2 (a6989586621679978288 :: (~>) a6989586621679974069 Bool) (a6989586621679978289 :: [a6989586621679974069]) = Partition a6989586621679978288 a6989586621679978289
- data (!!@#@$) :: forall a6989586621679974062. (~>) [a6989586621679974062] ((~>) Nat a6989586621679974062)
- data (!!@#@$$) (a6989586621679978209 :: [a6989586621679974062]) :: (~>) Nat a6989586621679974062
- type (!!@#@$$$) (a6989586621679978209 :: [a6989586621679974062]) (a6989586621679978210 :: Nat) = (!!) a6989586621679978209 a6989586621679978210
- data ElemIndexSym0 :: forall a6989586621679974091. (~>) a6989586621679974091 ((~>) [a6989586621679974091] (Maybe Nat))
- data ElemIndexSym1 (a6989586621679978632 :: a6989586621679974091) :: (~>) [a6989586621679974091] (Maybe Nat)
- type ElemIndexSym2 (a6989586621679978632 :: a6989586621679974091) (a6989586621679978633 :: [a6989586621679974091]) = ElemIndex a6989586621679978632 a6989586621679978633
- data ElemIndicesSym0 :: forall a6989586621679974090. (~>) a6989586621679974090 ((~>) [a6989586621679974090] [Nat])
- data ElemIndicesSym1 (a6989586621679978624 :: a6989586621679974090) :: (~>) [a6989586621679974090] [Nat]
- type ElemIndicesSym2 (a6989586621679978624 :: a6989586621679974090) (a6989586621679978625 :: [a6989586621679974090]) = ElemIndices a6989586621679978624 a6989586621679978625
- data FindIndexSym0 :: forall a6989586621679974089. (~>) ((~>) a6989586621679974089 Bool) ((~>) [a6989586621679974089] (Maybe Nat))
- data FindIndexSym1 (a6989586621679978616 :: (~>) a6989586621679974089 Bool) :: (~>) [a6989586621679974089] (Maybe Nat)
- type FindIndexSym2 (a6989586621679978616 :: (~>) a6989586621679974089 Bool) (a6989586621679978617 :: [a6989586621679974089]) = FindIndex a6989586621679978616 a6989586621679978617
- data FindIndicesSym0 :: forall a6989586621679974088. (~>) ((~>) a6989586621679974088 Bool) ((~>) [a6989586621679974088] [Nat])
- data FindIndicesSym1 (a6989586621679978590 :: (~>) a6989586621679974088 Bool) :: (~>) [a6989586621679974088] [Nat]
- type FindIndicesSym2 (a6989586621679978590 :: (~>) a6989586621679974088 Bool) (a6989586621679978591 :: [a6989586621679974088]) = FindIndices a6989586621679978590 a6989586621679978591
- data ZipSym0 :: forall a6989586621679974139 b6989586621679974140. (~>) [a6989586621679974139] ((~>) [b6989586621679974140] [(a6989586621679974139, b6989586621679974140)])
- data ZipSym1 (a6989586621679979003 :: [a6989586621679974139]) :: forall b6989586621679974140. (~>) [b6989586621679974140] [(a6989586621679974139, b6989586621679974140)]
- type ZipSym2 (a6989586621679979003 :: [a6989586621679974139]) (a6989586621679979004 :: [b6989586621679974140]) = Zip a6989586621679979003 a6989586621679979004
- data Zip3Sym0 :: forall a6989586621679974136 b6989586621679974137 c6989586621679974138. (~>) [a6989586621679974136] ((~>) [b6989586621679974137] ((~>) [c6989586621679974138] [(a6989586621679974136, b6989586621679974137, c6989586621679974138)]))
- data Zip3Sym1 (a6989586621679978991 :: [a6989586621679974136]) :: forall b6989586621679974137 c6989586621679974138. (~>) [b6989586621679974137] ((~>) [c6989586621679974138] [(a6989586621679974136, b6989586621679974137, c6989586621679974138)])
- data Zip3Sym2 (a6989586621679978991 :: [a6989586621679974136]) (a6989586621679978992 :: [b6989586621679974137]) :: forall c6989586621679974138. (~>) [c6989586621679974138] [(a6989586621679974136, b6989586621679974137, c6989586621679974138)]
- type Zip3Sym3 (a6989586621679978991 :: [a6989586621679974136]) (a6989586621679978992 :: [b6989586621679974137]) (a6989586621679978993 :: [c6989586621679974138]) = Zip3 a6989586621679978991 a6989586621679978992 a6989586621679978993
- data Zip4Sym0 :: forall a6989586621680096267 b6989586621680096268 c6989586621680096269 d6989586621680096270. (~>) [a6989586621680096267] ((~>) [b6989586621680096268] ((~>) [c6989586621680096269] ((~>) [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)])))
- data Zip4Sym1 (a6989586621680097955 :: [a6989586621680096267]) :: forall b6989586621680096268 c6989586621680096269 d6989586621680096270. (~>) [b6989586621680096268] ((~>) [c6989586621680096269] ((~>) [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]))
- data Zip4Sym2 (a6989586621680097955 :: [a6989586621680096267]) (a6989586621680097956 :: [b6989586621680096268]) :: forall c6989586621680096269 d6989586621680096270. (~>) [c6989586621680096269] ((~>) [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)])
- data Zip4Sym3 (a6989586621680097955 :: [a6989586621680096267]) (a6989586621680097956 :: [b6989586621680096268]) (a6989586621680097957 :: [c6989586621680096269]) :: forall d6989586621680096270. (~>) [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]
- type Zip4Sym4 (a6989586621680097955 :: [a6989586621680096267]) (a6989586621680097956 :: [b6989586621680096268]) (a6989586621680097957 :: [c6989586621680096269]) (a6989586621680097958 :: [d6989586621680096270]) = Zip4 a6989586621680097955 a6989586621680097956 a6989586621680097957 a6989586621680097958
- data Zip5Sym0 :: forall a6989586621680096262 b6989586621680096263 c6989586621680096264 d6989586621680096265 e6989586621680096266. (~>) [a6989586621680096262] ((~>) [b6989586621680096263] ((~>) [c6989586621680096264] ((~>) [d6989586621680096265] ((~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]))))
- data Zip5Sym1 (a6989586621680097932 :: [a6989586621680096262]) :: forall b6989586621680096263 c6989586621680096264 d6989586621680096265 e6989586621680096266. (~>) [b6989586621680096263] ((~>) [c6989586621680096264] ((~>) [d6989586621680096265] ((~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])))
- data Zip5Sym2 (a6989586621680097932 :: [a6989586621680096262]) (a6989586621680097933 :: [b6989586621680096263]) :: forall c6989586621680096264 d6989586621680096265 e6989586621680096266. (~>) [c6989586621680096264] ((~>) [d6989586621680096265] ((~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]))
- data Zip5Sym3 (a6989586621680097932 :: [a6989586621680096262]) (a6989586621680097933 :: [b6989586621680096263]) (a6989586621680097934 :: [c6989586621680096264]) :: forall d6989586621680096265 e6989586621680096266. (~>) [d6989586621680096265] ((~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])
- data Zip5Sym4 (a6989586621680097932 :: [a6989586621680096262]) (a6989586621680097933 :: [b6989586621680096263]) (a6989586621680097934 :: [c6989586621680096264]) (a6989586621680097935 :: [d6989586621680096265]) :: forall e6989586621680096266. (~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]
- type Zip5Sym5 (a6989586621680097932 :: [a6989586621680096262]) (a6989586621680097933 :: [b6989586621680096263]) (a6989586621680097934 :: [c6989586621680096264]) (a6989586621680097935 :: [d6989586621680096265]) (a6989586621680097936 :: [e6989586621680096266]) = Zip5 a6989586621680097932 a6989586621680097933 a6989586621680097934 a6989586621680097935 a6989586621680097936
- data Zip6Sym0 :: forall a6989586621680096256 b6989586621680096257 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261. (~>) [a6989586621680096256] ((~>) [b6989586621680096257] ((~>) [c6989586621680096258] ((~>) [d6989586621680096259] ((~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])))))
- data Zip6Sym1 (a6989586621680097904 :: [a6989586621680096256]) :: forall b6989586621680096257 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261. (~>) [b6989586621680096257] ((~>) [c6989586621680096258] ((~>) [d6989586621680096259] ((~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))))
- data Zip6Sym2 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) :: forall c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261. (~>) [c6989586621680096258] ((~>) [d6989586621680096259] ((~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])))
- data Zip6Sym3 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) (a6989586621680097906 :: [c6989586621680096258]) :: forall d6989586621680096259 e6989586621680096260 f6989586621680096261. (~>) [d6989586621680096259] ((~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))
- data Zip6Sym4 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) (a6989586621680097906 :: [c6989586621680096258]) (a6989586621680097907 :: [d6989586621680096259]) :: forall e6989586621680096260 f6989586621680096261. (~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])
- data Zip6Sym5 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) (a6989586621680097906 :: [c6989586621680096258]) (a6989586621680097907 :: [d6989586621680096259]) (a6989586621680097908 :: [e6989586621680096260]) :: forall f6989586621680096261. (~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]
- type Zip6Sym6 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) (a6989586621680097906 :: [c6989586621680096258]) (a6989586621680097907 :: [d6989586621680096259]) (a6989586621680097908 :: [e6989586621680096260]) (a6989586621680097909 :: [f6989586621680096261]) = Zip6 a6989586621680097904 a6989586621680097905 a6989586621680097906 a6989586621680097907 a6989586621680097908 a6989586621680097909
- data Zip7Sym0 :: forall a6989586621680096249 b6989586621680096250 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [a6989586621680096249] ((~>) [b6989586621680096250] ((~>) [c6989586621680096251] ((~>) [d6989586621680096252] ((~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))))))
- data Zip7Sym1 (a6989586621680097871 :: [a6989586621680096249]) :: forall b6989586621680096250 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [b6989586621680096250] ((~>) [c6989586621680096251] ((~>) [d6989586621680096252] ((~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))))
- data Zip7Sym2 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) :: forall c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [c6989586621680096251] ((~>) [d6989586621680096252] ((~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))))
- data Zip7Sym3 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) :: forall d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [d6989586621680096252] ((~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))
- data Zip7Sym4 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) (a6989586621680097874 :: [d6989586621680096252]) :: forall e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))
- data Zip7Sym5 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) (a6989586621680097874 :: [d6989586621680096252]) (a6989586621680097875 :: [e6989586621680096253]) :: forall f6989586621680096254 g6989586621680096255. (~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])
- data Zip7Sym6 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) (a6989586621680097874 :: [d6989586621680096252]) (a6989586621680097875 :: [e6989586621680096253]) (a6989586621680097876 :: [f6989586621680096254]) :: forall g6989586621680096255. (~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]
- type Zip7Sym7 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) (a6989586621680097874 :: [d6989586621680096252]) (a6989586621680097875 :: [e6989586621680096253]) (a6989586621680097876 :: [f6989586621680096254]) (a6989586621680097877 :: [g6989586621680096255]) = Zip7 a6989586621680097871 a6989586621680097872 a6989586621680097873 a6989586621680097874 a6989586621680097875 a6989586621680097876 a6989586621680097877
- data ZipWithSym0 :: forall a6989586621679974133 b6989586621679974134 c6989586621679974135. (~>) ((~>) a6989586621679974133 ((~>) b6989586621679974134 c6989586621679974135)) ((~>) [a6989586621679974133] ((~>) [b6989586621679974134] [c6989586621679974135]))
- data ZipWithSym1 (a6989586621679978980 :: (~>) a6989586621679974133 ((~>) b6989586621679974134 c6989586621679974135)) :: (~>) [a6989586621679974133] ((~>) [b6989586621679974134] [c6989586621679974135])
- data ZipWithSym2 (a6989586621679978980 :: (~>) a6989586621679974133 ((~>) b6989586621679974134 c6989586621679974135)) (a6989586621679978981 :: [a6989586621679974133]) :: (~>) [b6989586621679974134] [c6989586621679974135]
- type ZipWithSym3 (a6989586621679978980 :: (~>) a6989586621679974133 ((~>) b6989586621679974134 c6989586621679974135)) (a6989586621679978981 :: [a6989586621679974133]) (a6989586621679978982 :: [b6989586621679974134]) = ZipWith a6989586621679978980 a6989586621679978981 a6989586621679978982
- data ZipWith3Sym0 :: forall a6989586621679974129 b6989586621679974130 c6989586621679974131 d6989586621679974132. (~>) ((~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) ((~>) [a6989586621679974129] ((~>) [b6989586621679974130] ((~>) [c6989586621679974131] [d6989586621679974132])))
- data ZipWith3Sym1 (a6989586621679978965 :: (~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) :: (~>) [a6989586621679974129] ((~>) [b6989586621679974130] ((~>) [c6989586621679974131] [d6989586621679974132]))
- data ZipWith3Sym2 (a6989586621679978965 :: (~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) (a6989586621679978966 :: [a6989586621679974129]) :: (~>) [b6989586621679974130] ((~>) [c6989586621679974131] [d6989586621679974132])
- data ZipWith3Sym3 (a6989586621679978965 :: (~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) (a6989586621679978966 :: [a6989586621679974129]) (a6989586621679978967 :: [b6989586621679974130]) :: (~>) [c6989586621679974131] [d6989586621679974132]
- type ZipWith3Sym4 (a6989586621679978965 :: (~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) (a6989586621679978966 :: [a6989586621679974129]) (a6989586621679978967 :: [b6989586621679974130]) (a6989586621679978968 :: [c6989586621679974131]) = ZipWith3 a6989586621679978965 a6989586621679978966 a6989586621679978967 a6989586621679978968
- data ZipWith4Sym0 :: forall a6989586621680096244 b6989586621680096245 c6989586621680096246 d6989586621680096247 e6989586621680096248. (~>) ((~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) ((~>) [a6989586621680096244] ((~>) [b6989586621680096245] ((~>) [c6989586621680096246] ((~>) [d6989586621680096247] [e6989586621680096248]))))
- data ZipWith4Sym1 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) :: (~>) [a6989586621680096244] ((~>) [b6989586621680096245] ((~>) [c6989586621680096246] ((~>) [d6989586621680096247] [e6989586621680096248])))
- data ZipWith4Sym2 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) (a6989586621680097839 :: [a6989586621680096244]) :: (~>) [b6989586621680096245] ((~>) [c6989586621680096246] ((~>) [d6989586621680096247] [e6989586621680096248]))
- data ZipWith4Sym3 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) (a6989586621680097839 :: [a6989586621680096244]) (a6989586621680097840 :: [b6989586621680096245]) :: (~>) [c6989586621680096246] ((~>) [d6989586621680096247] [e6989586621680096248])
- data ZipWith4Sym4 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) (a6989586621680097839 :: [a6989586621680096244]) (a6989586621680097840 :: [b6989586621680096245]) (a6989586621680097841 :: [c6989586621680096246]) :: (~>) [d6989586621680096247] [e6989586621680096248]
- type ZipWith4Sym5 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) (a6989586621680097839 :: [a6989586621680096244]) (a6989586621680097840 :: [b6989586621680096245]) (a6989586621680097841 :: [c6989586621680096246]) (a6989586621680097842 :: [d6989586621680096247]) = ZipWith4 a6989586621680097838 a6989586621680097839 a6989586621680097840 a6989586621680097841 a6989586621680097842
- data ZipWith5Sym0 :: forall a6989586621680096238 b6989586621680096239 c6989586621680096240 d6989586621680096241 e6989586621680096242 f6989586621680096243. (~>) ((~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) ((~>) [a6989586621680096238] ((~>) [b6989586621680096239] ((~>) [c6989586621680096240] ((~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243])))))
- data ZipWith5Sym1 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) :: (~>) [a6989586621680096238] ((~>) [b6989586621680096239] ((~>) [c6989586621680096240] ((~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243]))))
- data ZipWith5Sym2 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) :: (~>) [b6989586621680096239] ((~>) [c6989586621680096240] ((~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243])))
- data ZipWith5Sym3 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) (a6989586621680097817 :: [b6989586621680096239]) :: (~>) [c6989586621680096240] ((~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243]))
- data ZipWith5Sym4 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) (a6989586621680097817 :: [b6989586621680096239]) (a6989586621680097818 :: [c6989586621680096240]) :: (~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243])
- data ZipWith5Sym5 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) (a6989586621680097817 :: [b6989586621680096239]) (a6989586621680097818 :: [c6989586621680096240]) (a6989586621680097819 :: [d6989586621680096241]) :: (~>) [e6989586621680096242] [f6989586621680096243]
- type ZipWith5Sym6 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) (a6989586621680097817 :: [b6989586621680096239]) (a6989586621680097818 :: [c6989586621680096240]) (a6989586621680097819 :: [d6989586621680096241]) (a6989586621680097820 :: [e6989586621680096242]) = ZipWith5 a6989586621680097815 a6989586621680097816 a6989586621680097817 a6989586621680097818 a6989586621680097819 a6989586621680097820
- data ZipWith6Sym0 :: forall a6989586621680096231 b6989586621680096232 c6989586621680096233 d6989586621680096234 e6989586621680096235 f6989586621680096236 g6989586621680096237. (~>) ((~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) ((~>) [a6989586621680096231] ((~>) [b6989586621680096232] ((~>) [c6989586621680096233] ((~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237]))))))
- data ZipWith6Sym1 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) :: (~>) [a6989586621680096231] ((~>) [b6989586621680096232] ((~>) [c6989586621680096233] ((~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237])))))
- data ZipWith6Sym2 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) :: (~>) [b6989586621680096232] ((~>) [c6989586621680096233] ((~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237]))))
- data ZipWith6Sym3 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) :: (~>) [c6989586621680096233] ((~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237])))
- data ZipWith6Sym4 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) (a6989586621680097791 :: [c6989586621680096233]) :: (~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237]))
- data ZipWith6Sym5 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) (a6989586621680097791 :: [c6989586621680096233]) (a6989586621680097792 :: [d6989586621680096234]) :: (~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237])
- data ZipWith6Sym6 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) (a6989586621680097791 :: [c6989586621680096233]) (a6989586621680097792 :: [d6989586621680096234]) (a6989586621680097793 :: [e6989586621680096235]) :: (~>) [f6989586621680096236] [g6989586621680096237]
- type ZipWith6Sym7 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) (a6989586621680097791 :: [c6989586621680096233]) (a6989586621680097792 :: [d6989586621680096234]) (a6989586621680097793 :: [e6989586621680096235]) (a6989586621680097794 :: [f6989586621680096236]) = ZipWith6 a6989586621680097788 a6989586621680097789 a6989586621680097790 a6989586621680097791 a6989586621680097792 a6989586621680097793 a6989586621680097794
- data ZipWith7Sym0 :: forall a6989586621680096223 b6989586621680096224 c6989586621680096225 d6989586621680096226 e6989586621680096227 f6989586621680096228 g6989586621680096229 h6989586621680096230. (~>) ((~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) ((~>) [a6989586621680096223] ((~>) [b6989586621680096224] ((~>) [c6989586621680096225] ((~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230])))))))
- data ZipWith7Sym1 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) :: (~>) [a6989586621680096223] ((~>) [b6989586621680096224] ((~>) [c6989586621680096225] ((~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230]))))))
- data ZipWith7Sym2 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) :: (~>) [b6989586621680096224] ((~>) [c6989586621680096225] ((~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230])))))
- data ZipWith7Sym3 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) :: (~>) [c6989586621680096225] ((~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230]))))
- data ZipWith7Sym4 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) :: (~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230])))
- data ZipWith7Sym5 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) (a6989586621680097761 :: [d6989586621680096226]) :: (~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230]))
- data ZipWith7Sym6 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) (a6989586621680097761 :: [d6989586621680096226]) (a6989586621680097762 :: [e6989586621680096227]) :: (~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230])
- data ZipWith7Sym7 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) (a6989586621680097761 :: [d6989586621680096226]) (a6989586621680097762 :: [e6989586621680096227]) (a6989586621680097763 :: [f6989586621680096228]) :: (~>) [g6989586621680096229] [h6989586621680096230]
- type ZipWith7Sym8 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) (a6989586621680097761 :: [d6989586621680096226]) (a6989586621680097762 :: [e6989586621680096227]) (a6989586621680097763 :: [f6989586621680096228]) (a6989586621680097764 :: [g6989586621680096229]) = ZipWith7 a6989586621680097757 a6989586621680097758 a6989586621680097759 a6989586621680097760 a6989586621680097761 a6989586621680097762 a6989586621680097763 a6989586621680097764
- data UnzipSym0 :: forall a6989586621679974127 b6989586621679974128. (~>) [(a6989586621679974127, b6989586621679974128)] ([a6989586621679974127], [b6989586621679974128])
- type UnzipSym1 (a6989586621679978946 :: [(a6989586621679974127, b6989586621679974128)]) = Unzip a6989586621679978946
- data Unzip3Sym0 :: forall a6989586621679974124 b6989586621679974125 c6989586621679974126. (~>) [(a6989586621679974124, b6989586621679974125, c6989586621679974126)] ([a6989586621679974124], [b6989586621679974125], [c6989586621679974126])
- type Unzip3Sym1 (a6989586621679978925 :: [(a6989586621679974124, b6989586621679974125, c6989586621679974126)]) = Unzip3 a6989586621679978925
- data Unzip4Sym0 :: forall a6989586621679974120 b6989586621679974121 c6989586621679974122 d6989586621679974123. (~>) [(a6989586621679974120, b6989586621679974121, c6989586621679974122, d6989586621679974123)] ([a6989586621679974120], [b6989586621679974121], [c6989586621679974122], [d6989586621679974123])
- type Unzip4Sym1 (a6989586621679978902 :: [(a6989586621679974120, b6989586621679974121, c6989586621679974122, d6989586621679974123)]) = Unzip4 a6989586621679978902
- data Unzip5Sym0 :: forall a6989586621679974115 b6989586621679974116 c6989586621679974117 d6989586621679974118 e6989586621679974119. (~>) [(a6989586621679974115, b6989586621679974116, c6989586621679974117, d6989586621679974118, e6989586621679974119)] ([a6989586621679974115], [b6989586621679974116], [c6989586621679974117], [d6989586621679974118], [e6989586621679974119])
- type Unzip5Sym1 (a6989586621679978877 :: [(a6989586621679974115, b6989586621679974116, c6989586621679974117, d6989586621679974118, e6989586621679974119)]) = Unzip5 a6989586621679978877
- data Unzip6Sym0 :: forall a6989586621679974109 b6989586621679974110 c6989586621679974111 d6989586621679974112 e6989586621679974113 f6989586621679974114. (~>) [(a6989586621679974109, b6989586621679974110, c6989586621679974111, d6989586621679974112, e6989586621679974113, f6989586621679974114)] ([a6989586621679974109], [b6989586621679974110], [c6989586621679974111], [d6989586621679974112], [e6989586621679974113], [f6989586621679974114])
- type Unzip6Sym1 (a6989586621679978850 :: [(a6989586621679974109, b6989586621679974110, c6989586621679974111, d6989586621679974112, e6989586621679974113, f6989586621679974114)]) = Unzip6 a6989586621679978850
- data Unzip7Sym0 :: forall a6989586621679974102 b6989586621679974103 c6989586621679974104 d6989586621679974105 e6989586621679974106 f6989586621679974107 g6989586621679974108. (~>) [(a6989586621679974102, b6989586621679974103, c6989586621679974104, d6989586621679974105, e6989586621679974106, f6989586621679974107, g6989586621679974108)] ([a6989586621679974102], [b6989586621679974103], [c6989586621679974104], [d6989586621679974105], [e6989586621679974106], [f6989586621679974107], [g6989586621679974108])
- type Unzip7Sym1 (a6989586621679978821 :: [(a6989586621679974102, b6989586621679974103, c6989586621679974104, d6989586621679974105, e6989586621679974106, f6989586621679974107, g6989586621679974108)]) = Unzip7 a6989586621679978821
- data UnlinesSym0 :: (~>) [Symbol] Symbol
- type UnlinesSym1 (a6989586621679978817 :: [Symbol]) = Unlines a6989586621679978817
- data UnwordsSym0 :: (~>) [Symbol] Symbol
- type UnwordsSym1 (a6989586621679978806 :: [Symbol]) = Unwords a6989586621679978806
- data NubSym0 :: forall a6989586621679974061. (~>) [a6989586621679974061] [a6989586621679974061]
- type NubSym1 (a6989586621679978189 :: [a6989586621679974061]) = Nub a6989586621679978189
- data DeleteSym0 :: forall a6989586621679974101. (~>) a6989586621679974101 ((~>) [a6989586621679974101] [a6989586621679974101])
- data DeleteSym1 (a6989586621679978800 :: a6989586621679974101) :: (~>) [a6989586621679974101] [a6989586621679974101]
- type DeleteSym2 (a6989586621679978800 :: a6989586621679974101) (a6989586621679978801 :: [a6989586621679974101]) = Delete a6989586621679978800 a6989586621679978801
- data (\\@#@$) :: forall a6989586621679974100. (~>) [a6989586621679974100] ((~>) [a6989586621679974100] [a6989586621679974100])
- data (\\@#@$$) (a6989586621679978790 :: [a6989586621679974100]) :: (~>) [a6989586621679974100] [a6989586621679974100]
- type (\\@#@$$$) (a6989586621679978790 :: [a6989586621679974100]) (a6989586621679978791 :: [a6989586621679974100]) = (\\) a6989586621679978790 a6989586621679978791
- data UnionSym0 :: forall a6989586621679974057. (~>) [a6989586621679974057] ((~>) [a6989586621679974057] [a6989586621679974057])
- data UnionSym1 (a6989586621679978139 :: [a6989586621679974057]) :: (~>) [a6989586621679974057] [a6989586621679974057]
- type UnionSym2 (a6989586621679978139 :: [a6989586621679974057]) (a6989586621679978140 :: [a6989586621679974057]) = Union a6989586621679978139 a6989586621679978140
- data IntersectSym0 :: forall a6989586621679974087. (~>) [a6989586621679974087] ((~>) [a6989586621679974087] [a6989586621679974087])
- data IntersectSym1 (a6989586621679978584 :: [a6989586621679974087]) :: (~>) [a6989586621679974087] [a6989586621679974087]
- type IntersectSym2 (a6989586621679978584 :: [a6989586621679974087]) (a6989586621679978585 :: [a6989586621679974087]) = Intersect a6989586621679978584 a6989586621679978585
- data InsertSym0 :: forall a6989586621679974074. (~>) a6989586621679974074 ((~>) [a6989586621679974074] [a6989586621679974074])
- data InsertSym1 (a6989586621679978347 :: a6989586621679974074) :: (~>) [a6989586621679974074] [a6989586621679974074]
- type InsertSym2 (a6989586621679978347 :: a6989586621679974074) (a6989586621679978348 :: [a6989586621679974074]) = Insert a6989586621679978347 a6989586621679978348
- data SortSym0 :: forall a6989586621679974073. (~>) [a6989586621679974073] [a6989586621679974073]
- type SortSym1 (a6989586621679978344 :: [a6989586621679974073]) = Sort a6989586621679978344
- data NubBySym0 :: forall a6989586621679974060. (~>) ((~>) a6989586621679974060 ((~>) a6989586621679974060 Bool)) ((~>) [a6989586621679974060] [a6989586621679974060])
- data NubBySym1 (a6989586621679978164 :: (~>) a6989586621679974060 ((~>) a6989586621679974060 Bool)) :: (~>) [a6989586621679974060] [a6989586621679974060]
- type NubBySym2 (a6989586621679978164 :: (~>) a6989586621679974060 ((~>) a6989586621679974060 Bool)) (a6989586621679978165 :: [a6989586621679974060]) = NubBy a6989586621679978164 a6989586621679978165
- data DeleteBySym0 :: forall a6989586621679974099. (~>) ((~>) a6989586621679974099 ((~>) a6989586621679974099 Bool)) ((~>) a6989586621679974099 ((~>) [a6989586621679974099] [a6989586621679974099]))
- data DeleteBySym1 (a6989586621679978768 :: (~>) a6989586621679974099 ((~>) a6989586621679974099 Bool)) :: (~>) a6989586621679974099 ((~>) [a6989586621679974099] [a6989586621679974099])
- data DeleteBySym2 (a6989586621679978768 :: (~>) a6989586621679974099 ((~>) a6989586621679974099 Bool)) (a6989586621679978769 :: a6989586621679974099) :: (~>) [a6989586621679974099] [a6989586621679974099]
- type DeleteBySym3 (a6989586621679978768 :: (~>) a6989586621679974099 ((~>) a6989586621679974099 Bool)) (a6989586621679978769 :: a6989586621679974099) (a6989586621679978770 :: [a6989586621679974099]) = DeleteBy a6989586621679978768 a6989586621679978769 a6989586621679978770
- data DeleteFirstsBySym0 :: forall a6989586621679974098. (~>) ((~>) a6989586621679974098 ((~>) a6989586621679974098 Bool)) ((~>) [a6989586621679974098] ((~>) [a6989586621679974098] [a6989586621679974098]))
- data DeleteFirstsBySym1 (a6989586621679978755 :: (~>) a6989586621679974098 ((~>) a6989586621679974098 Bool)) :: (~>) [a6989586621679974098] ((~>) [a6989586621679974098] [a6989586621679974098])
- data DeleteFirstsBySym2 (a6989586621679978755 :: (~>) a6989586621679974098 ((~>) a6989586621679974098 Bool)) (a6989586621679978756 :: [a6989586621679974098]) :: (~>) [a6989586621679974098] [a6989586621679974098]
- type DeleteFirstsBySym3 (a6989586621679978755 :: (~>) a6989586621679974098 ((~>) a6989586621679974098 Bool)) (a6989586621679978756 :: [a6989586621679974098]) (a6989586621679978757 :: [a6989586621679974098]) = DeleteFirstsBy a6989586621679978755 a6989586621679978756 a6989586621679978757
- data UnionBySym0 :: forall a6989586621679974058. (~>) ((~>) a6989586621679974058 ((~>) a6989586621679974058 Bool)) ((~>) [a6989586621679974058] ((~>) [a6989586621679974058] [a6989586621679974058]))
- data UnionBySym1 (a6989586621679978145 :: (~>) a6989586621679974058 ((~>) a6989586621679974058 Bool)) :: (~>) [a6989586621679974058] ((~>) [a6989586621679974058] [a6989586621679974058])
- data UnionBySym2 (a6989586621679978145 :: (~>) a6989586621679974058 ((~>) a6989586621679974058 Bool)) (a6989586621679978146 :: [a6989586621679974058]) :: (~>) [a6989586621679974058] [a6989586621679974058]
- type UnionBySym3 (a6989586621679978145 :: (~>) a6989586621679974058 ((~>) a6989586621679974058 Bool)) (a6989586621679978146 :: [a6989586621679974058]) (a6989586621679978147 :: [a6989586621679974058]) = UnionBy a6989586621679978145 a6989586621679978146 a6989586621679978147
- data IntersectBySym0 :: forall a6989586621679974086. (~>) ((~>) a6989586621679974086 ((~>) a6989586621679974086 Bool)) ((~>) [a6989586621679974086] ((~>) [a6989586621679974086] [a6989586621679974086]))
- data IntersectBySym1 (a6989586621679978548 :: (~>) a6989586621679974086 ((~>) a6989586621679974086 Bool)) :: (~>) [a6989586621679974086] ((~>) [a6989586621679974086] [a6989586621679974086])
- data IntersectBySym2 (a6989586621679978548 :: (~>) a6989586621679974086 ((~>) a6989586621679974086 Bool)) (a6989586621679978549 :: [a6989586621679974086]) :: (~>) [a6989586621679974086] [a6989586621679974086]
- type IntersectBySym3 (a6989586621679978548 :: (~>) a6989586621679974086 ((~>) a6989586621679974086 Bool)) (a6989586621679978549 :: [a6989586621679974086]) (a6989586621679978550 :: [a6989586621679974086]) = IntersectBy a6989586621679978548 a6989586621679978549 a6989586621679978550
- data GroupBySym0 :: forall a6989586621679974072. (~>) ((~>) a6989586621679974072 ((~>) a6989586621679974072 Bool)) ((~>) [a6989586621679974072] [[a6989586621679974072]])
- data GroupBySym1 (a6989586621679978311 :: (~>) a6989586621679974072 ((~>) a6989586621679974072 Bool)) :: (~>) [a6989586621679974072] [[a6989586621679974072]]
- type GroupBySym2 (a6989586621679978311 :: (~>) a6989586621679974072 ((~>) a6989586621679974072 Bool)) (a6989586621679978312 :: [a6989586621679974072]) = GroupBy a6989586621679978311 a6989586621679978312
- data SortBySym0 :: forall a6989586621679974097. (~>) ((~>) a6989586621679974097 ((~>) a6989586621679974097 Ordering)) ((~>) [a6989586621679974097] [a6989586621679974097])
- data SortBySym1 (a6989586621679978747 :: (~>) a6989586621679974097 ((~>) a6989586621679974097 Ordering)) :: (~>) [a6989586621679974097] [a6989586621679974097]
- type SortBySym2 (a6989586621679978747 :: (~>) a6989586621679974097 ((~>) a6989586621679974097 Ordering)) (a6989586621679978748 :: [a6989586621679974097]) = SortBy a6989586621679978747 a6989586621679978748
- data InsertBySym0 :: forall a6989586621679974096. (~>) ((~>) a6989586621679974096 ((~>) a6989586621679974096 Ordering)) ((~>) a6989586621679974096 ((~>) [a6989586621679974096] [a6989586621679974096]))
- data InsertBySym1 (a6989586621679978723 :: (~>) a6989586621679974096 ((~>) a6989586621679974096 Ordering)) :: (~>) a6989586621679974096 ((~>) [a6989586621679974096] [a6989586621679974096])
- data InsertBySym2 (a6989586621679978723 :: (~>) a6989586621679974096 ((~>) a6989586621679974096 Ordering)) (a6989586621679978724 :: a6989586621679974096) :: (~>) [a6989586621679974096] [a6989586621679974096]
- type InsertBySym3 (a6989586621679978723 :: (~>) a6989586621679974096 ((~>) a6989586621679974096 Ordering)) (a6989586621679978724 :: a6989586621679974096) (a6989586621679978725 :: [a6989586621679974096]) = InsertBy a6989586621679978723 a6989586621679978724 a6989586621679978725
- data MaximumBySym0 :: forall a6989586621680490417 t6989586621680490416. (~>) ((~>) a6989586621680490417 ((~>) a6989586621680490417 Ordering)) ((~>) (t6989586621680490416 a6989586621680490417) a6989586621680490417)
- data MaximumBySym1 (a6989586621680490924 :: (~>) a6989586621680490417 ((~>) a6989586621680490417 Ordering)) :: forall t6989586621680490416. (~>) (t6989586621680490416 a6989586621680490417) a6989586621680490417
- type MaximumBySym2 (a6989586621680490924 :: (~>) a6989586621680490417 ((~>) a6989586621680490417 Ordering)) (a6989586621680490925 :: t6989586621680490416 a6989586621680490417) = MaximumBy a6989586621680490924 a6989586621680490925
- data MinimumBySym0 :: forall a6989586621680490415 t6989586621680490414. (~>) ((~>) a6989586621680490415 ((~>) a6989586621680490415 Ordering)) ((~>) (t6989586621680490414 a6989586621680490415) a6989586621680490415)
- data MinimumBySym1 (a6989586621680490899 :: (~>) a6989586621680490415 ((~>) a6989586621680490415 Ordering)) :: forall t6989586621680490414. (~>) (t6989586621680490414 a6989586621680490415) a6989586621680490415
- type MinimumBySym2 (a6989586621680490899 :: (~>) a6989586621680490415 ((~>) a6989586621680490415 Ordering)) (a6989586621680490900 :: t6989586621680490414 a6989586621680490415) = MinimumBy a6989586621680490899 a6989586621680490900
- data GenericLengthSym0 :: forall a6989586621679974056 i6989586621679974055. (~>) [a6989586621679974056] i6989586621679974055
- type GenericLengthSym1 (a6989586621679978132 :: [a6989586621679974056]) = GenericLength a6989586621679978132
- data GenericTakeSym0 :: forall i6989586621680096221 a6989586621680096222. (~>) i6989586621680096221 ((~>) [a6989586621680096222] [a6989586621680096222])
- data GenericTakeSym1 (a6989586621680097751 :: i6989586621680096221) :: forall a6989586621680096222. (~>) [a6989586621680096222] [a6989586621680096222]
- type GenericTakeSym2 (a6989586621680097751 :: i6989586621680096221) (a6989586621680097752 :: [a6989586621680096222]) = GenericTake a6989586621680097751 a6989586621680097752
- data GenericDropSym0 :: forall i6989586621680096219 a6989586621680096220. (~>) i6989586621680096219 ((~>) [a6989586621680096220] [a6989586621680096220])
- data GenericDropSym1 (a6989586621680097741 :: i6989586621680096219) :: forall a6989586621680096220. (~>) [a6989586621680096220] [a6989586621680096220]
- type GenericDropSym2 (a6989586621680097741 :: i6989586621680096219) (a6989586621680097742 :: [a6989586621680096220]) = GenericDrop a6989586621680097741 a6989586621680097742
- data GenericSplitAtSym0 :: forall i6989586621680096217 a6989586621680096218. (~>) i6989586621680096217 ((~>) [a6989586621680096218] ([a6989586621680096218], [a6989586621680096218]))
- data GenericSplitAtSym1 (a6989586621680097731 :: i6989586621680096217) :: forall a6989586621680096218. (~>) [a6989586621680096218] ([a6989586621680096218], [a6989586621680096218])
- type GenericSplitAtSym2 (a6989586621680097731 :: i6989586621680096217) (a6989586621680097732 :: [a6989586621680096218]) = GenericSplitAt a6989586621680097731 a6989586621680097732
- data GenericIndexSym0 :: forall a6989586621680096216 i6989586621680096215. (~>) [a6989586621680096216] ((~>) i6989586621680096215 a6989586621680096216)
- data GenericIndexSym1 (a6989586621680097721 :: [a6989586621680096216]) :: forall i6989586621680096215. (~>) i6989586621680096215 a6989586621680096216
- type GenericIndexSym2 (a6989586621680097721 :: [a6989586621680096216]) (a6989586621680097722 :: i6989586621680096215) = GenericIndex a6989586621680097721 a6989586621680097722
- data GenericReplicateSym0 :: forall i6989586621680096213 a6989586621680096214. (~>) i6989586621680096213 ((~>) a6989586621680096214 [a6989586621680096214])
- data GenericReplicateSym1 (a6989586621680097711 :: i6989586621680096213) :: forall a6989586621680096214. (~>) a6989586621680096214 [a6989586621680096214]
- type GenericReplicateSym2 (a6989586621680097711 :: i6989586621680096213) (a6989586621680097712 :: a6989586621680096214) = GenericReplicate a6989586621680097711 a6989586621680097712
The singleton for lists
type family Sing :: k -> Type Source #
The singleton kind-indexed type family.
Instances
data SList :: forall a. [a] -> Type where Source #
SNil :: SList '[] | |
SCons :: forall a (n :: a) (n :: [a]). (Sing (n :: a)) -> (Sing (n :: [a])) -> SList ('(:) n n) infixr 5 |
Basic functions
(%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a]) infixr 5 Source #
type family Null (arg :: t a) :: Bool Source #
Instances
type family Length (arg :: t a) :: Nat Source #
Instances
List transformations
sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b]) Source #
type family Intersperse (a :: a) (a :: [a]) :: [a] where ... Source #
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 #
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 #
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 ~> (a6989586621680490511 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680490511) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680490511 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680490511]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680490511 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680490511) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680490511 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680490511) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680490511 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680490511) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680490511 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680490511) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680490511 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680490511) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source #
type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #
Instances
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680490513 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680490513]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: NonEmpty a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680490513 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680490513) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680490513 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680490513) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680490513 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680490513) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680490513 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680490513) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) Source #
type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #
Instances
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Const m a0) 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 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680490506]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Min a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Max a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (arg1 :: a0 ~> (b0 ~> b0)) (arg2 :: b0) (arg3 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a2 :: a6989586621680490506 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Either a1 a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a6989586621680490506 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: (a1, a6989586621680490506)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a6989586621680490506 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Arg a1 a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Const m a6989586621680490506) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source #
type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #
Instances
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) Source #
Special folds
sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a]) Source #
sConcatMap :: forall a b t (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) Source #
type family And (a :: t Bool) :: Bool where ... Source #
And x = Case_6989586621680490989 x (Let6989586621680490987Scrutinee_6989586621680490749Sym1 x) |
type family Or (a :: t Bool) :: Bool where ... Source #
Or x = Case_6989586621680490980 x (Let6989586621680490978Scrutinee_6989586621680490751Sym1 x) |
type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #
Any p x = Case_6989586621680490971 p x (Let6989586621680490968Scrutinee_6989586621680490753Sym2 p x) |
sAny :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool) Source #
type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #
All p x = Case_6989586621680490958 p x (Let6989586621680490955Scrutinee_6989586621680490755Sym2 p x) |
sAll :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) Source #
type family Sum (arg :: t a) :: a Source #
Instances
sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a) Source #
type family Product (arg :: t a) :: a Source #
Instances
sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a) Source #
type family Maximum (arg :: t a) :: a Source #
Instances
sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a) Source #
type family Minimum (arg :: t a) :: a Source #
Instances
sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a) Source #
Building lists
Scans
sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b]) Source #
sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a]) Source #
sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b]) Source #
type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ... Source #
Scanr1 _ '[] = '[] | |
Scanr1 _ '[x] = Apply (Apply (:@#@$) x) '[] | |
Scanr1 f ('(:) x ('(:) wild_6989586621679974663 wild_6989586621679974665)) = Case_6989586621679979221 f x wild_6989586621679974663 wild_6989586621679974665 (Let6989586621679979216Scrutinee_6989586621679974657Sym4 f x wild_6989586621679974663 wild_6989586621679974665) |
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 #
MapAccumL f s t = Case_6989586621680804743 f s t (Let6989586621680804739Scrutinee_6989586621680804310Sym3 f s t) |
sMapAccumL :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply 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 #
MapAccumR f s t = Case_6989586621680804726 f s t (Let6989586621680804722Scrutinee_6989586621680804314Sym3 f s t) |
sMapAccumR :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c)) Source #
Cyclical lists
type family Replicate (a :: Nat) (a :: a) :: [a] where ... Source #
Replicate n x = Case_6989586621679978238 n x (Let6989586621679978235Scrutinee_6989586621679974759Sym2 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 #
Unfoldr f b = Case_6989586621679979069 f b (Let6989586621679979066Scrutinee_6989586621679974667Sym2 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 #
Span _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679978451XsSym0) Let6989586621679978451XsSym0 | |
Span p ('(:) x xs') = Case_6989586621679978463 p x xs' (Let6989586621679978459Scrutinee_6989586621679974739Sym3 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 #
Break _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679978408XsSym0) Let6989586621679978408XsSym0 | |
Break p ('(:) x xs') = Case_6989586621679978420 p x xs' (Let6989586621679978416Scrutinee_6989586621679974741Sym3 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 #
StripPrefix '[] ys = Apply JustSym0 ys | |
StripPrefix arg_6989586621680096339 arg_6989586621680096341 = Case_6989586621680097974 arg_6989586621680096339 arg_6989586621680096341 (Apply (Apply Tuple2Sym0 arg_6989586621680096339) arg_6989586621680096341) |
type family Group (a :: [a]) :: [[a]] where ... Source #
Group xs = Apply (Apply GroupBySym0 (==@#@$)) xs |
Predicates
type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
IsPrefixOf '[] '[] = TrueSym0 | |
IsPrefixOf '[] ('(:) _ _) = TrueSym0 | |
IsPrefixOf ('(:) _ _) '[] = FalseSym0 | |
IsPrefixOf ('(:) x xs) ('(:) y ys) = Apply (Apply (&&@#@$) (Apply (Apply (==@#@$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) |
sIsPrefixOf :: forall 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 #
IsSuffixOf x y = Apply (Apply IsPrefixOfSym0 (Apply ReverseSym0 x)) (Apply ReverseSym0 y) |
sIsSuffixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) Source #
sIsInfixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool) Source #
Searching lists
Searching by equality
type family Elem (arg :: a) (arg :: t a) :: Bool Source #
Instances
type Elem (arg1 :: a0) (arg2 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (a1 :: k1) (a2 :: [k1]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (a1 :: k1) (a2 :: [k1]) | |
type Elem (arg1 :: a0) (arg2 :: NonEmpty a0) 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 :: a0) (arg2 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (arg1 :: a0) (arg2 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (a1 :: k1) (a2 :: Identity k1) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Elem (arg1 :: a0) (arg2 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a0) (arg2 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a0) (arg2 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a0) (arg2 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a0) (arg2 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a0) (arg2 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (arg1 :: a0) (arg2 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (arg1 :: a0) (arg2 :: (a, a0)) | |
type Elem (arg1 :: a0) (arg2 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a0) (arg2 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) Source #
sNotElem :: forall a t (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) Source #
type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... Source #
Lookup _key '[] = NothingSym0 | |
Lookup key ('(:) '(x, y) xys) = Case_6989586621679978308 key x y xys (Let6989586621679978303Scrutinee_6989586621679974755Sym4 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 #
Find p y = Case_6989586621680490887 p y (Let6989586621680490870Scrutinee_6989586621680490761Sym2 p y) |
sFind :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a) Source #
sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) Source #
sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) Source #
Indexing lists
(%!!) :: forall a (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) infixl 9 Source #
sElemIndex :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat) Source #
type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ... Source #
ElemIndices x a_6989586621679978628 = Apply (Apply FindIndicesSym0 (Apply (==@#@$) x)) a_6989586621679978628 |
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 #
FindIndex p a_6989586621679978620 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679978620 |
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 #
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 #
Zip4 a_6989586621680097947 a_6989586621680097949 a_6989586621680097951 a_6989586621680097953 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621680097947) a_6989586621680097949) a_6989586621680097951) a_6989586621680097953 |
type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ... Source #
Zip5 a_6989586621680097922 a_6989586621680097924 a_6989586621680097926 a_6989586621680097928 a_6989586621680097930 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621680097922) a_6989586621680097924) a_6989586621680097926) a_6989586621680097928) a_6989586621680097930 |
type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ... Source #
Zip6 a_6989586621680097892 a_6989586621680097894 a_6989586621680097896 a_6989586621680097898 a_6989586621680097900 a_6989586621680097902 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621680097892) a_6989586621680097894) a_6989586621680097896) a_6989586621680097898) a_6989586621680097900) a_6989586621680097902 |
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 #
Zip7 a_6989586621680097857 a_6989586621680097859 a_6989586621680097861 a_6989586621680097863 a_6989586621680097865 a_6989586621680097867 a_6989586621680097869 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621680097857) a_6989586621680097859) a_6989586621680097861) a_6989586621680097863) a_6989586621680097865) a_6989586621680097867) a_6989586621680097869 |
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 #
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 #
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 #
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 #
Sort a_6989586621679978342 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679978342 |
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 #
DeleteFirstsBy eq a_6989586621679978761 a_6989586621679978763 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679978761) a_6989586621679978763 |
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 #
IntersectBy _ '[] '[] = '[] | |
IntersectBy _ '[] ('(:) _ _) = '[] | |
IntersectBy _ ('(:) _ _) '[] = '[] | |
IntersectBy eq ('(:) wild_6989586621679974725 wild_6989586621679974727) ('(:) wild_6989586621679974729 wild_6989586621679974731) = Apply (Apply (>>=@#@$) (Let6989586621679978559XsSym5 eq wild_6989586621679974725 wild_6989586621679974727 wild_6989586621679974729 wild_6989586621679974731)) (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679978570Sym0 eq) wild_6989586621679974725) wild_6989586621679974727) wild_6989586621679974729) wild_6989586621679974731) |
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 #
MaximumBy cmp a_6989586621680490928 = Apply (Apply Foldl1Sym0 (Let6989586621680490932Max'Sym2 cmp a_6989586621680490928)) a_6989586621680490928 |
sMaximumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) Source #
type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #
MinimumBy cmp a_6989586621680490903 = Apply (Apply Foldl1Sym0 (Let6989586621680490907Min'Sym2 cmp a_6989586621680490903)) a_6989586621680490903 |
sMinimumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) Source #
The "generic
" operations
The prefix `generic
' indicates an overloaded function that
is a generalized version of a Prelude function.
type family GenericLength (a :: [a]) :: i where ... Source #
GenericLength '[] = FromInteger 0 | |
GenericLength ('(:) _ xs) = Apply (Apply (+@#@$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
sGenericLength :: forall a i (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i) Source #
type family GenericTake (a :: i) (a :: [a]) :: [a] where ... Source #
GenericTake a_6989586621680097747 a_6989586621680097749 = Apply (Apply TakeSym0 a_6989586621680097747) a_6989586621680097749 |
type family GenericDrop (a :: i) (a :: [a]) :: [a] where ... Source #
GenericDrop a_6989586621680097737 a_6989586621680097739 = Apply (Apply DropSym0 a_6989586621680097737) a_6989586621680097739 |
type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ... Source #
GenericSplitAt a_6989586621680097727 a_6989586621680097729 = Apply (Apply SplitAtSym0 a_6989586621680097727) a_6989586621680097729 |
type family GenericIndex (a :: [a]) (a :: i) :: a where ... Source #
GenericIndex a_6989586621680097717 a_6989586621680097719 = Apply (Apply (!!@#@$) a_6989586621680097717) a_6989586621680097719 |
type family GenericReplicate (a :: i) (a :: a) :: [a] where ... Source #
GenericReplicate a_6989586621680097707 a_6989586621680097709 = Apply (Apply ReplicateSym0 a_6989586621680097707) a_6989586621680097709 |
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 suppressUnusedWarnings :: () Source # | |
type Apply ((:@#@$) :: TyFun a3530822107858468865 ([a3530822107858468865] ~> [a3530822107858468865]) -> Type) (t6989586621679315156 :: a3530822107858468865) Source # | |
data (:@#@$$) (t6989586621679315156 :: a3530822107858468865 :: Type) :: (~>) [a3530822107858468865] [a3530822107858468865 :: Type] infixr 5 Source #
Instances
SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((:@#@$$) t6989586621679315156 :: TyFun [a3530822107858468865] [a3530822107858468865] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances suppressUnusedWarnings :: () Source # | |
type Apply ((:@#@$$) t6989586621679315156 :: TyFun [a] [a] -> Type) (t6989586621679315157 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Instances |
type (:@#@$$$) (t6989586621679315156 :: a3530822107858468865) (t6989586621679315157 :: [a3530822107858468865]) = '(:) t6989586621679315156 t6989586621679315157 Source #
type (++@#@$$$) (a6989586621679545630 :: [a6989586621679545433]) (a6989586621679545631 :: [a6989586621679545433]) = (++) a6989586621679545630 a6989586621679545631 Source #
data (++@#@$$) (a6989586621679545630 :: [a6989586621679545433]) :: (~>) [a6989586621679545433] [a6989586621679545433] infixr 5 Source #
Instances
SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((++@#@$$) a6989586621679545630 :: TyFun [a6989586621679545433] [a6989586621679545433] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$$) a6989586621679545630 :: TyFun [a] [a] -> Type) (a6989586621679545631 :: [a]) Source # | |
data (++@#@$) :: forall a6989586621679545433. (~>) [a6989586621679545433] ((~>) [a6989586621679545433] [a6989586621679545433]) infixr 5 Source #
Instances
SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679545433] ([a6989586621679545433] ~> [a6989586621679545433]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$) :: TyFun [a6989586621679545433] ([a6989586621679545433] ~> [a6989586621679545433]) -> Type) (a6989586621679545630 :: [a6989586621679545433]) Source # | |
data HeadSym0 :: forall a6989586621679974183. (~>) [a6989586621679974183] a6989586621679974183 Source #
Instances
SingI (HeadSym0 :: TyFun [a] a -> Type) Source # | |
SuppressUnusedWarnings (HeadSym0 :: TyFun [a6989586621679974183] a6989586621679974183 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679979530 :: [a]) Source # | |
data LastSym0 :: forall a6989586621679974182. (~>) [a6989586621679974182] a6989586621679974182 Source #
Instances
SingI (LastSym0 :: TyFun [a] a -> Type) Source # | |
SuppressUnusedWarnings (LastSym0 :: TyFun [a6989586621679974182] a6989586621679974182 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679979525 :: [a]) Source # | |
data TailSym0 :: forall a6989586621679974181. (~>) [a6989586621679974181] [a6989586621679974181] Source #
Instances
SingI (TailSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (TailSym0 :: TyFun [a6989586621679974181] [a6989586621679974181] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679979522 :: [a]) Source # | |
data InitSym0 :: forall a6989586621679974180. (~>) [a6989586621679974180] [a6989586621679974180] Source #
Instances
SingI (InitSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (InitSym0 :: TyFun [a6989586621679974180] [a6989586621679974180] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679979508 :: [a]) Source # | |
data NullSym0 :: forall t6989586621680490502 a6989586621680490517. (~>) (t6989586621680490502 a6989586621680490517) Bool Source #
Instances
SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680490502 a6989586621680490517) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680491161 :: t a) Source # | |
type NullSym1 (arg6989586621680491161 :: t6989586621680490502 a6989586621680490517) = Null arg6989586621680491161 Source #
data LengthSym0 :: forall t6989586621680490502 a6989586621680490518. (~>) (t6989586621680490502 a6989586621680490518) Nat Source #
Instances
SFoldable t => SingI (LengthSym0 :: TyFun (t a) Nat -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing LengthSym0 Source # | |
SuppressUnusedWarnings (LengthSym0 :: TyFun (t6989586621680490502 a6989586621680490518) Nat -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (arg6989586621680491163 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type LengthSym1 (arg6989586621680491163 :: t6989586621680490502 a6989586621680490518) = Length arg6989586621680491163 Source #
data MapSym0 :: forall a6989586621679545434 b6989586621679545435. (~>) ((~>) a6989586621679545434 b6989586621679545435) ((~>) [a6989586621679545434] [b6989586621679545435]) Source #
Instances
SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (MapSym0 :: TyFun (a6989586621679545434 ~> b6989586621679545435) ([a6989586621679545434] ~> [b6989586621679545435]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply (MapSym0 :: TyFun (a6989586621679545434 ~> b6989586621679545435) ([a6989586621679545434] ~> [b6989586621679545435]) -> Type) (a6989586621679545638 :: a6989586621679545434 ~> b6989586621679545435) Source # | |
data MapSym1 (a6989586621679545638 :: (~>) a6989586621679545434 b6989586621679545435) :: (~>) [a6989586621679545434] [b6989586621679545435] Source #
Instances
SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (MapSym1 a6989586621679545638 :: TyFun [a6989586621679545434] [b6989586621679545435] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply (MapSym1 a6989586621679545638 :: TyFun [a] [b] -> Type) (a6989586621679545639 :: [a]) Source # | |
type MapSym2 (a6989586621679545638 :: (~>) a6989586621679545434 b6989586621679545435) (a6989586621679545639 :: [a6989586621679545434]) = Map a6989586621679545638 a6989586621679545639 Source #
data ReverseSym0 :: forall a6989586621679974178. (~>) [a6989586621679974178] [a6989586621679974178] Source #
Instances
SingI (ReverseSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing ReverseSym0 Source # | |
SuppressUnusedWarnings (ReverseSym0 :: TyFun [a6989586621679974178] [a6989586621679974178] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679979493 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679979493 :: [a]) = Reverse a6989586621679979493 |
type ReverseSym1 (a6989586621679979493 :: [a6989586621679974178]) = Reverse a6989586621679979493 Source #
data IntersperseSym0 :: forall a6989586621679974177. (~>) a6989586621679974177 ((~>) [a6989586621679974177] [a6989586621679974177]) Source #
Instances
SingI (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679974177 ([a6989586621679974177] ~> [a6989586621679974177]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym0 :: TyFun a6989586621679974177 ([a6989586621679974177] ~> [a6989586621679974177]) -> Type) (a6989586621679979486 :: a6989586621679974177) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym0 :: TyFun a6989586621679974177 ([a6989586621679974177] ~> [a6989586621679974177]) -> Type) (a6989586621679979486 :: a6989586621679974177) = IntersperseSym1 a6989586621679979486 |
data IntersperseSym1 (a6989586621679979486 :: a6989586621679974177) :: (~>) [a6989586621679974177] [a6989586621679974177] Source #
Instances
SingI d => SingI (IntersperseSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IntersperseSym1 d) Source # | |
SuppressUnusedWarnings (IntersperseSym1 a6989586621679979486 :: TyFun [a6989586621679974177] [a6989586621679974177] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym1 a6989586621679979486 :: TyFun [a] [a] -> Type) (a6989586621679979487 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym1 a6989586621679979486 :: TyFun [a] [a] -> Type) (a6989586621679979487 :: [a]) = Intersperse a6989586621679979486 a6989586621679979487 |
type IntersperseSym2 (a6989586621679979486 :: a6989586621679974177) (a6989586621679979487 :: [a6989586621679974177]) = Intersperse a6989586621679979486 a6989586621679979487 Source #
data IntercalateSym0 :: forall a6989586621679974176. (~>) [a6989586621679974176] ((~>) [[a6989586621679974176]] [a6989586621679974176]) Source #
Instances
SingI (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a6989586621679974176] ([[a6989586621679974176]] ~> [a6989586621679974176]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym0 :: TyFun [a6989586621679974176] ([[a6989586621679974176]] ~> [a6989586621679974176]) -> Type) (a6989586621679979480 :: [a6989586621679974176]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym0 :: TyFun [a6989586621679974176] ([[a6989586621679974176]] ~> [a6989586621679974176]) -> Type) (a6989586621679979480 :: [a6989586621679974176]) = IntercalateSym1 a6989586621679979480 |
data IntercalateSym1 (a6989586621679979480 :: [a6989586621679974176]) :: (~>) [[a6989586621679974176]] [a6989586621679974176] Source #
Instances
SingI d => SingI (IntercalateSym1 d :: TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IntercalateSym1 d) Source # | |
SuppressUnusedWarnings (IntercalateSym1 a6989586621679979480 :: TyFun [[a6989586621679974176]] [a6989586621679974176] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym1 a6989586621679979480 :: TyFun [[a]] [a] -> Type) (a6989586621679979481 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym1 a6989586621679979480 :: TyFun [[a]] [a] -> Type) (a6989586621679979481 :: [[a]]) = Intercalate a6989586621679979480 a6989586621679979481 |
type IntercalateSym2 (a6989586621679979480 :: [a6989586621679974176]) (a6989586621679979481 :: [[a6989586621679974176]]) = Intercalate a6989586621679979480 a6989586621679979481 Source #
data TransposeSym0 :: forall a6989586621679974063. (~>) [[a6989586621679974063]] [[a6989586621679974063]] Source #
Instances
SingI (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing TransposeSym0 Source # | |
SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a6989586621679974063]] [[a6989586621679974063]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679978223 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679978223 :: [[a]]) = Transpose a6989586621679978223 |
type TransposeSym1 (a6989586621679978223 :: [[a6989586621679974063]]) = Transpose a6989586621679978223 Source #
data SubsequencesSym0 :: forall a6989586621679974175. (~>) [a6989586621679974175] [[a6989586621679974175]] Source #
Instances
SingI (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a6989586621679974175] [[a6989586621679974175]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679979477 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679979477 :: [a]) = Subsequences a6989586621679979477 |
type SubsequencesSym1 (a6989586621679979477 :: [a6989586621679974175]) = Subsequences a6989586621679979477 Source #
data PermutationsSym0 :: forall a6989586621679974172. (~>) [a6989586621679974172] [[a6989586621679974172]] Source #
Instances
SingI (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a6989586621679974172] [[a6989586621679974172]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679979359 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679979359 :: [a]) = Permutations a6989586621679979359 |
type PermutationsSym1 (a6989586621679979359 :: [a6989586621679974172]) = Permutations a6989586621679979359 Source #
data FoldlSym0 :: forall b6989586621680490510 a6989586621680490511 t6989586621680490502. (~>) ((~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) ((~>) b6989586621680490510 ((~>) (t6989586621680490502 a6989586621680490511) b6989586621680490510)) Source #
Instances
SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym0 :: TyFun (b6989586621680490510 ~> (a6989586621680490511 ~> b6989586621680490510)) (b6989586621680490510 ~> (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym0 :: TyFun (b6989586621680490510 ~> (a6989586621680490511 ~> b6989586621680490510)) (b6989586621680490510 ~> (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510)) -> Type) (arg6989586621680491139 :: b6989586621680490510 ~> (a6989586621680490511 ~> b6989586621680490510)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldlSym0 :: TyFun (b6989586621680490510 ~> (a6989586621680490511 ~> b6989586621680490510)) (b6989586621680490510 ~> (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510)) -> Type) (arg6989586621680491139 :: b6989586621680490510 ~> (a6989586621680490511 ~> b6989586621680490510)) = FoldlSym1 arg6989586621680491139 t6989586621680490502 :: TyFun b6989586621680490510 (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510) -> Type |
data FoldlSym1 (arg6989586621680491139 :: (~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) :: forall t6989586621680490502. (~>) b6989586621680490510 ((~>) (t6989586621680490502 a6989586621680490511) b6989586621680490510) Source #
Instances
(SFoldable t, SingI d) => SingI (FoldlSym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym1 arg6989586621680491139 t6989586621680490502 :: TyFun b6989586621680490510 (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym1 arg6989586621680491139 t6989586621680490502 :: TyFun b6989586621680490510 (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510) -> Type) (arg6989586621680491140 :: b6989586621680490510) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldlSym1 arg6989586621680491139 t6989586621680490502 :: TyFun b6989586621680490510 (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510) -> Type) (arg6989586621680491140 :: b6989586621680490510) = FoldlSym2 arg6989586621680491139 arg6989586621680491140 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490511) b6989586621680490510 -> Type |
data FoldlSym2 (arg6989586621680491139 :: (~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) (arg6989586621680491140 :: b6989586621680490510) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490511) b6989586621680490510 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym2 arg6989586621680491140 arg6989586621680491139 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490511) b6989586621680490510 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym2 arg6989586621680491140 arg6989586621680491139 t :: TyFun (t a) b -> Type) (arg6989586621680491141 :: t a) Source # | |
type FoldlSym3 (arg6989586621680491139 :: (~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) (arg6989586621680491140 :: b6989586621680490510) (arg6989586621680491141 :: t6989586621680490502 a6989586621680490511) = Foldl arg6989586621680491139 arg6989586621680491140 arg6989586621680491141 Source #
data Foldl'Sym0 :: forall b6989586621680490512 a6989586621680490513 t6989586621680490502. (~>) ((~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) ((~>) b6989586621680490512 ((~>) (t6989586621680490502 a6989586621680490513) b6989586621680490512)) Source #
Instances
SFoldable t => SingI (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing Foldl'Sym0 Source # | |
SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (b6989586621680490512 ~> (a6989586621680490513 ~> b6989586621680490512)) (b6989586621680490512 ~> (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym0 :: TyFun (b6989586621680490512 ~> (a6989586621680490513 ~> b6989586621680490512)) (b6989586621680490512 ~> (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512)) -> Type) (arg6989586621680491145 :: b6989586621680490512 ~> (a6989586621680490513 ~> b6989586621680490512)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym0 :: TyFun (b6989586621680490512 ~> (a6989586621680490513 ~> b6989586621680490512)) (b6989586621680490512 ~> (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512)) -> Type) (arg6989586621680491145 :: b6989586621680490512 ~> (a6989586621680490513 ~> b6989586621680490512)) = Foldl'Sym1 arg6989586621680491145 t6989586621680490502 :: TyFun b6989586621680490512 (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512) -> Type |
data Foldl'Sym1 (arg6989586621680491145 :: (~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) :: forall t6989586621680490502. (~>) b6989586621680490512 ((~>) (t6989586621680490502 a6989586621680490513) b6989586621680490512) Source #
Instances
(SFoldable t, SingI d) => SingI (Foldl'Sym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (Foldl'Sym1 d t) Source # | |
SuppressUnusedWarnings (Foldl'Sym1 arg6989586621680491145 t6989586621680490502 :: TyFun b6989586621680490512 (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym1 arg6989586621680491145 t6989586621680490502 :: TyFun b6989586621680490512 (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512) -> Type) (arg6989586621680491146 :: b6989586621680490512) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym1 arg6989586621680491145 t6989586621680490502 :: TyFun b6989586621680490512 (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512) -> Type) (arg6989586621680491146 :: b6989586621680490512) = Foldl'Sym2 arg6989586621680491145 arg6989586621680491146 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490513) b6989586621680490512 -> Type |
data Foldl'Sym2 (arg6989586621680491145 :: (~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) (arg6989586621680491146 :: b6989586621680490512) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490513) b6989586621680490512 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 sing :: Sing (Foldl'Sym2 d1 d2 t) Source # | |
SuppressUnusedWarnings (Foldl'Sym2 arg6989586621680491146 arg6989586621680491145 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490513) b6989586621680490512 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym2 arg6989586621680491146 arg6989586621680491145 t :: TyFun (t a) b -> Type) (arg6989586621680491147 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym2 arg6989586621680491146 arg6989586621680491145 t :: TyFun (t a) b -> Type) (arg6989586621680491147 :: t a) = Foldl' arg6989586621680491146 arg6989586621680491145 arg6989586621680491147 |
type Foldl'Sym3 (arg6989586621680491145 :: (~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) (arg6989586621680491146 :: b6989586621680490512) (arg6989586621680491147 :: t6989586621680490502 a6989586621680490513) = Foldl' arg6989586621680491145 arg6989586621680491146 arg6989586621680491147 Source #
data Foldl1Sym0 :: forall a6989586621680490515 t6989586621680490502. (~>) ((~>) a6989586621680490515 ((~>) a6989586621680490515 a6989586621680490515)) ((~>) (t6989586621680490502 a6989586621680490515) a6989586621680490515) Source #
Instances
SFoldable t => SingI (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing Foldl1Sym0 Source # | |
SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (a6989586621680490515 ~> (a6989586621680490515 ~> a6989586621680490515)) (t6989586621680490502 a6989586621680490515 ~> a6989586621680490515) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym0 :: TyFun (a6989586621680490515 ~> (a6989586621680490515 ~> a6989586621680490515)) (t6989586621680490502 a6989586621680490515 ~> a6989586621680490515) -> Type) (arg6989586621680491155 :: a6989586621680490515 ~> (a6989586621680490515 ~> a6989586621680490515)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl1Sym0 :: TyFun (a6989586621680490515 ~> (a6989586621680490515 ~> a6989586621680490515)) (t6989586621680490502 a6989586621680490515 ~> a6989586621680490515) -> Type) (arg6989586621680491155 :: a6989586621680490515 ~> (a6989586621680490515 ~> a6989586621680490515)) = Foldl1Sym1 arg6989586621680491155 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490515) a6989586621680490515 -> Type |
data Foldl1Sym1 (arg6989586621680491155 :: (~>) a6989586621680490515 ((~>) a6989586621680490515 a6989586621680490515)) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490515) a6989586621680490515 Source #
Instances
(SFoldable t, SingI d) => SingI (Foldl1Sym1 d t :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (Foldl1Sym1 d t) Source # | |
SuppressUnusedWarnings (Foldl1Sym1 arg6989586621680491155 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490515) a6989586621680490515 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym1 arg6989586621680491155 t :: TyFun (t a) a -> Type) (arg6989586621680491156 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl1Sym1 arg6989586621680491155 t :: TyFun (t a) a -> Type) (arg6989586621680491156 :: t a) = Foldl1 arg6989586621680491155 arg6989586621680491156 |
type Foldl1Sym2 (arg6989586621680491155 :: (~>) a6989586621680490515 ((~>) a6989586621680490515 a6989586621680490515)) (arg6989586621680491156 :: t6989586621680490502 a6989586621680490515) = Foldl1 arg6989586621680491155 arg6989586621680491156 Source #
data Foldl1'Sym0 :: forall a6989586621679974168. (~>) ((~>) a6989586621679974168 ((~>) a6989586621679974168 a6989586621679974168)) ((~>) [a6989586621679974168] a6989586621679974168) Source #
Instances
SingI (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Foldl1'Sym0 Source # | |
SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (a6989586621679974168 ~> (a6989586621679974168 ~> a6989586621679974168)) ([a6989586621679974168] ~> a6989586621679974168) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym0 :: TyFun (a6989586621679974168 ~> (a6989586621679974168 ~> a6989586621679974168)) ([a6989586621679974168] ~> a6989586621679974168) -> Type) (a6989586621679979317 :: a6989586621679974168 ~> (a6989586621679974168 ~> a6989586621679974168)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym0 :: TyFun (a6989586621679974168 ~> (a6989586621679974168 ~> a6989586621679974168)) ([a6989586621679974168] ~> a6989586621679974168) -> Type) (a6989586621679979317 :: a6989586621679974168 ~> (a6989586621679974168 ~> a6989586621679974168)) = Foldl1'Sym1 a6989586621679979317 |
data Foldl1'Sym1 (a6989586621679979317 :: (~>) a6989586621679974168 ((~>) a6989586621679974168 a6989586621679974168)) :: (~>) [a6989586621679974168] a6989586621679974168 Source #
Instances
SingI d => SingI (Foldl1'Sym1 d :: TyFun [a] a -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (Foldl1'Sym1 d) Source # | |
SuppressUnusedWarnings (Foldl1'Sym1 a6989586621679979317 :: TyFun [a6989586621679974168] a6989586621679974168 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym1 a6989586621679979317 :: TyFun [a] a -> Type) (a6989586621679979318 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym1 a6989586621679979317 :: TyFun [a] a -> Type) (a6989586621679979318 :: [a]) = Foldl1' a6989586621679979317 a6989586621679979318 |
type Foldl1'Sym2 (a6989586621679979317 :: (~>) a6989586621679974168 ((~>) a6989586621679974168 a6989586621679974168)) (a6989586621679979318 :: [a6989586621679974168]) = Foldl1' a6989586621679979317 a6989586621679979318 Source #
data FoldrSym0 :: forall a6989586621680490506 b6989586621680490507 t6989586621680490502. (~>) ((~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) ((~>) b6989586621680490507 ((~>) (t6989586621680490502 a6989586621680490506) b6989586621680490507)) Source #
Instances
SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym0 :: TyFun (a6989586621680490506 ~> (b6989586621680490507 ~> b6989586621680490507)) (b6989586621680490507 ~> (t6989586621680490502 a6989586621680490506 ~> b6989586621680490507)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym0 :: TyFun (a6989586621680490506 ~> (b6989586621680490507 ~> b6989586621680490507)) (b6989586621680490507 ~> (t6989586621680490502 a6989586621680490506 ~> b6989586621680490507)) -> Type) (arg6989586621680491127 :: a6989586621680490506 ~> (b6989586621680490507 ~> b6989586621680490507)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldrSym0 :: TyFun (a6989586621680490506 ~> (b6989586621680490507 ~> b6989586621680490507)) (b6989586621680490507 ~> (t6989586621680490502 a6989586621680490506 ~> b6989586621680490507)) -> Type) (arg6989586621680491127 :: a6989586621680490506 ~> (b6989586621680490507 ~> b6989586621680490507)) = FoldrSym1 arg6989586621680491127 t6989586621680490502 :: TyFun b6989586621680490507 (t6989586621680490502 a6989586621680490506 ~> b6989586621680490507) -> Type |
data FoldrSym1 (arg6989586621680491127 :: (~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) :: forall t6989586621680490502. (~>) b6989586621680490507 ((~>) (t6989586621680490502 a6989586621680490506) b6989586621680490507) Source #
Instances
(SFoldable t, SingI d) => SingI (FoldrSym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym1 arg6989586621680491127 t6989586621680490502 :: TyFun b6989586621680490507 (t6989586621680490502 a6989586621680490506 ~> b6989586621680490507) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym1 arg6989586621680491127 t6989586621680490502 :: TyFun b6989586621680490507 (t6989586621680490502 a6989586621680490506 ~> b6989586621680490507) -> Type) (arg6989586621680491128 :: b6989586621680490507) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldrSym1 arg6989586621680491127 t6989586621680490502 :: TyFun b6989586621680490507 (t6989586621680490502 a6989586621680490506 ~> b6989586621680490507) -> Type) (arg6989586621680491128 :: b6989586621680490507) = FoldrSym2 arg6989586621680491127 arg6989586621680491128 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490506) b6989586621680490507 -> Type |
data FoldrSym2 (arg6989586621680491127 :: (~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) (arg6989586621680491128 :: b6989586621680490507) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490506) b6989586621680490507 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym2 arg6989586621680491128 arg6989586621680491127 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490506) b6989586621680490507 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym2 arg6989586621680491128 arg6989586621680491127 t :: TyFun (t a) b -> Type) (arg6989586621680491129 :: t a) Source # | |
type FoldrSym3 (arg6989586621680491127 :: (~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) (arg6989586621680491128 :: b6989586621680490507) (arg6989586621680491129 :: t6989586621680490502 a6989586621680490506) = Foldr arg6989586621680491127 arg6989586621680491128 arg6989586621680491129 Source #
data Foldr1Sym0 :: forall a6989586621680490514 t6989586621680490502. (~>) ((~>) a6989586621680490514 ((~>) a6989586621680490514 a6989586621680490514)) ((~>) (t6989586621680490502 a6989586621680490514) a6989586621680490514) Source #
Instances
SFoldable t => SingI (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing Foldr1Sym0 Source # | |
SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (a6989586621680490514 ~> (a6989586621680490514 ~> a6989586621680490514)) (t6989586621680490502 a6989586621680490514 ~> a6989586621680490514) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym0 :: TyFun (a6989586621680490514 ~> (a6989586621680490514 ~> a6989586621680490514)) (t6989586621680490502 a6989586621680490514 ~> a6989586621680490514) -> Type) (arg6989586621680491151 :: a6989586621680490514 ~> (a6989586621680490514 ~> a6989586621680490514)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr1Sym0 :: TyFun (a6989586621680490514 ~> (a6989586621680490514 ~> a6989586621680490514)) (t6989586621680490502 a6989586621680490514 ~> a6989586621680490514) -> Type) (arg6989586621680491151 :: a6989586621680490514 ~> (a6989586621680490514 ~> a6989586621680490514)) = Foldr1Sym1 arg6989586621680491151 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490514) a6989586621680490514 -> Type |
data Foldr1Sym1 (arg6989586621680491151 :: (~>) a6989586621680490514 ((~>) a6989586621680490514 a6989586621680490514)) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490514) a6989586621680490514 Source #
Instances
(SFoldable t, SingI d) => SingI (Foldr1Sym1 d t :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (Foldr1Sym1 d t) Source # | |
SuppressUnusedWarnings (Foldr1Sym1 arg6989586621680491151 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490514) a6989586621680490514 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym1 arg6989586621680491151 t :: TyFun (t a) a -> Type) (arg6989586621680491152 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr1Sym1 arg6989586621680491151 t :: TyFun (t a) a -> Type) (arg6989586621680491152 :: t a) = Foldr1 arg6989586621680491151 arg6989586621680491152 |
type Foldr1Sym2 (arg6989586621680491151 :: (~>) a6989586621680490514 ((~>) a6989586621680490514 a6989586621680490514)) (arg6989586621680491152 :: t6989586621680490502 a6989586621680490514) = Foldr1 arg6989586621680491151 arg6989586621680491152 Source #
data ConcatSym0 :: forall t6989586621680490427 a6989586621680490428. (~>) (t6989586621680490427 [a6989586621680490428]) [a6989586621680490428] Source #
Instances
SFoldable t => SingI (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing ConcatSym0 Source # | |
SuppressUnusedWarnings (ConcatSym0 :: TyFun (t6989586621680490427 [a6989586621680490428]) [a6989586621680490428] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680491009 :: t [a]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680491009 :: t [a]) = Concat a6989586621680491009 |
type ConcatSym1 (a6989586621680491009 :: t6989586621680490427 [a6989586621680490428]) = Concat a6989586621680491009 Source #
data ConcatMapSym0 :: forall a6989586621680490425 b6989586621680490426 t6989586621680490424. (~>) ((~>) a6989586621680490425 [b6989586621680490426]) ((~>) (t6989586621680490424 a6989586621680490425) [b6989586621680490426]) Source #
Instances
SFoldable t => SingI (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing ConcatMapSym0 Source # | |
SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (a6989586621680490425 ~> [b6989586621680490426]) (t6989586621680490424 a6989586621680490425 ~> [b6989586621680490426]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym0 :: TyFun (a6989586621680490425 ~> [b6989586621680490426]) (t6989586621680490424 a6989586621680490425 ~> [b6989586621680490426]) -> Type) (a6989586621680490993 :: a6989586621680490425 ~> [b6989586621680490426]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym0 :: TyFun (a6989586621680490425 ~> [b6989586621680490426]) (t6989586621680490424 a6989586621680490425 ~> [b6989586621680490426]) -> Type) (a6989586621680490993 :: a6989586621680490425 ~> [b6989586621680490426]) = ConcatMapSym1 a6989586621680490993 t6989586621680490424 :: TyFun (t6989586621680490424 a6989586621680490425) [b6989586621680490426] -> Type |
data ConcatMapSym1 (a6989586621680490993 :: (~>) a6989586621680490425 [b6989586621680490426]) :: forall t6989586621680490424. (~>) (t6989586621680490424 a6989586621680490425) [b6989586621680490426] Source #
Instances
(SFoldable t, SingI d) => SingI (ConcatMapSym1 d t :: TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (ConcatMapSym1 d t) Source # | |
SuppressUnusedWarnings (ConcatMapSym1 a6989586621680490993 t6989586621680490424 :: TyFun (t6989586621680490424 a6989586621680490425) [b6989586621680490426] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym1 a6989586621680490993 t :: TyFun (t a) [b] -> Type) (a6989586621680490994 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym1 a6989586621680490993 t :: TyFun (t a) [b] -> Type) (a6989586621680490994 :: t a) = ConcatMap a6989586621680490993 a6989586621680490994 |
type ConcatMapSym2 (a6989586621680490993 :: (~>) a6989586621680490425 [b6989586621680490426]) (a6989586621680490994 :: t6989586621680490424 a6989586621680490425) = ConcatMap a6989586621680490993 a6989586621680490994 Source #
data AndSym0 :: forall t6989586621680490423. (~>) (t6989586621680490423 Bool) Bool Source #
Instances
SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
SuppressUnusedWarnings (AndSym0 :: TyFun (t6989586621680490423 Bool) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680490984 :: t Bool) Source # | |
type AndSym1 (a6989586621680490984 :: t6989586621680490423 Bool) = And a6989586621680490984 Source #
data OrSym0 :: forall t6989586621680490422. (~>) (t6989586621680490422 Bool) Bool Source #
Instances
SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
SuppressUnusedWarnings (OrSym0 :: TyFun (t6989586621680490422 Bool) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680490975 :: t Bool) Source # | |
data AnySym0 :: forall a6989586621680490421 t6989586621680490420. (~>) ((~>) a6989586621680490421 Bool) ((~>) (t6989586621680490420 a6989586621680490421) Bool) Source #
Instances
SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (AnySym0 :: TyFun (a6989586621680490421 ~> Bool) (t6989586621680490420 a6989586621680490421 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AnySym0 :: TyFun (a6989586621680490421 ~> Bool) (t6989586621680490420 a6989586621680490421 ~> Bool) -> Type) (a6989586621680490962 :: a6989586621680490421 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data AnySym1 (a6989586621680490962 :: (~>) a6989586621680490421 Bool) :: forall t6989586621680490420. (~>) (t6989586621680490420 a6989586621680490421) Bool Source #
Instances
(SFoldable t, SingI d) => SingI (AnySym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (AnySym1 a6989586621680490962 t6989586621680490420 :: TyFun (t6989586621680490420 a6989586621680490421) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AnySym1 a6989586621680490962 t :: TyFun (t a) Bool -> Type) (a6989586621680490963 :: t a) Source # | |
type AnySym2 (a6989586621680490962 :: (~>) a6989586621680490421 Bool) (a6989586621680490963 :: t6989586621680490420 a6989586621680490421) = Any a6989586621680490962 a6989586621680490963 Source #
data AllSym0 :: forall a6989586621680490419 t6989586621680490418. (~>) ((~>) a6989586621680490419 Bool) ((~>) (t6989586621680490418 a6989586621680490419) Bool) Source #
Instances
SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (AllSym0 :: TyFun (a6989586621680490419 ~> Bool) (t6989586621680490418 a6989586621680490419 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AllSym0 :: TyFun (a6989586621680490419 ~> Bool) (t6989586621680490418 a6989586621680490419 ~> Bool) -> Type) (a6989586621680490949 :: a6989586621680490419 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data AllSym1 (a6989586621680490949 :: (~>) a6989586621680490419 Bool) :: forall t6989586621680490418. (~>) (t6989586621680490418 a6989586621680490419) Bool Source #
Instances
(SFoldable t, SingI d) => SingI (AllSym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (AllSym1 a6989586621680490949 t6989586621680490418 :: TyFun (t6989586621680490418 a6989586621680490419) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AllSym1 a6989586621680490949 t :: TyFun (t a) Bool -> Type) (a6989586621680490950 :: t a) Source # | |
type AllSym2 (a6989586621680490949 :: (~>) a6989586621680490419 Bool) (a6989586621680490950 :: t6989586621680490418 a6989586621680490419) = All a6989586621680490949 a6989586621680490950 Source #
data SumSym0 :: forall t6989586621680490502 a6989586621680490522. (~>) (t6989586621680490502 a6989586621680490522) a6989586621680490522 Source #
Instances
(SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # | |
SuppressUnusedWarnings (SumSym0 :: TyFun (t6989586621680490502 a6989586621680490522) a6989586621680490522 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (SumSym0 :: TyFun (t a) a -> Type) (arg6989586621680491173 :: t a) Source # | |
type SumSym1 (arg6989586621680491173 :: t6989586621680490502 a6989586621680490522) = Sum arg6989586621680491173 Source #
data ProductSym0 :: forall t6989586621680490502 a6989586621680490523. (~>) (t6989586621680490502 a6989586621680490523) a6989586621680490523 Source #
Instances
(SFoldable t, SNum a) => SingI (ProductSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing ProductSym0 Source # | |
SuppressUnusedWarnings (ProductSym0 :: TyFun (t6989586621680490502 a6989586621680490523) a6989586621680490523 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680491175 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680491175 :: t a) = Product arg6989586621680491175 |
type ProductSym1 (arg6989586621680491175 :: t6989586621680490502 a6989586621680490523) = Product arg6989586621680491175 Source #
data MaximumSym0 :: forall t6989586621680490502 a6989586621680490520. (~>) (t6989586621680490502 a6989586621680490520) a6989586621680490520 Source #
Instances
(SFoldable t, SOrd a) => SingI (MaximumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing MaximumSym0 Source # | |
SuppressUnusedWarnings (MaximumSym0 :: TyFun (t6989586621680490502 a6989586621680490520) a6989586621680490520 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680491169 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680491169 :: t a) = Maximum arg6989586621680491169 |
type MaximumSym1 (arg6989586621680491169 :: t6989586621680490502 a6989586621680490520) = Maximum arg6989586621680491169 Source #
data MinimumSym0 :: forall t6989586621680490502 a6989586621680490521. (~>) (t6989586621680490502 a6989586621680490521) a6989586621680490521 Source #
Instances
(SFoldable t, SOrd a) => SingI (MinimumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing MinimumSym0 Source # | |
SuppressUnusedWarnings (MinimumSym0 :: TyFun (t6989586621680490502 a6989586621680490521) a6989586621680490521 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680491171 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680491171 :: t a) = Minimum arg6989586621680491171 |
type MinimumSym1 (arg6989586621680491171 :: t6989586621680490502 a6989586621680490521) = Minimum arg6989586621680491171 Source #
data ScanlSym0 :: forall b6989586621679974160 a6989586621679974161. (~>) ((~>) b6989586621679974160 ((~>) a6989586621679974161 b6989586621679974160)) ((~>) b6989586621679974160 ((~>) [a6989586621679974161] [b6989586621679974160])) Source #
Instances
SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym0 :: TyFun (b6989586621679974160 ~> (a6989586621679974161 ~> b6989586621679974160)) (b6989586621679974160 ~> ([a6989586621679974161] ~> [b6989586621679974160])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym0 :: TyFun (b6989586621679974160 ~> (a6989586621679974161 ~> b6989586621679974160)) (b6989586621679974160 ~> ([a6989586621679974161] ~> [b6989586621679974160])) -> Type) (a6989586621679979254 :: b6989586621679974160 ~> (a6989586621679974161 ~> b6989586621679974160)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ScanlSym0 :: TyFun (b6989586621679974160 ~> (a6989586621679974161 ~> b6989586621679974160)) (b6989586621679974160 ~> ([a6989586621679974161] ~> [b6989586621679974160])) -> Type) (a6989586621679979254 :: b6989586621679974160 ~> (a6989586621679974161 ~> b6989586621679974160)) = ScanlSym1 a6989586621679979254 |
data ScanlSym1 (a6989586621679979254 :: (~>) b6989586621679974160 ((~>) a6989586621679974161 b6989586621679974160)) :: (~>) b6989586621679974160 ((~>) [a6989586621679974161] [b6989586621679974160]) Source #
Instances
SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym1 a6989586621679979254 :: TyFun b6989586621679974160 ([a6989586621679974161] ~> [b6989586621679974160]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym1 a6989586621679979254 :: TyFun b6989586621679974160 ([a6989586621679974161] ~> [b6989586621679974160]) -> Type) (a6989586621679979255 :: b6989586621679974160) Source # | |
data ScanlSym2 (a6989586621679979254 :: (~>) b6989586621679974160 ((~>) a6989586621679974161 b6989586621679974160)) (a6989586621679979255 :: b6989586621679974160) :: (~>) [a6989586621679974161] [b6989586621679974160] Source #
Instances
(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym2 a6989586621679979255 a6989586621679979254 :: TyFun [a6989586621679974161] [b6989586621679974160] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym2 a6989586621679979255 a6989586621679979254 :: TyFun [a] [b] -> Type) (a6989586621679979256 :: [a]) Source # | |
type ScanlSym3 (a6989586621679979254 :: (~>) b6989586621679974160 ((~>) a6989586621679974161 b6989586621679974160)) (a6989586621679979255 :: b6989586621679974160) (a6989586621679979256 :: [a6989586621679974161]) = Scanl a6989586621679979254 a6989586621679979255 a6989586621679979256 Source #
data Scanl1Sym0 :: forall a6989586621679974159. (~>) ((~>) a6989586621679974159 ((~>) a6989586621679974159 a6989586621679974159)) ((~>) [a6989586621679974159] [a6989586621679974159]) Source #
Instances
SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Scanl1Sym0 Source # | |
SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a6989586621679974159 ~> (a6989586621679974159 ~> a6989586621679974159)) ([a6989586621679974159] ~> [a6989586621679974159]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym0 :: TyFun (a6989586621679974159 ~> (a6989586621679974159 ~> a6989586621679974159)) ([a6989586621679974159] ~> [a6989586621679974159]) -> Type) (a6989586621679979247 :: a6989586621679974159 ~> (a6989586621679974159 ~> a6989586621679974159)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym0 :: TyFun (a6989586621679974159 ~> (a6989586621679974159 ~> a6989586621679974159)) ([a6989586621679974159] ~> [a6989586621679974159]) -> Type) (a6989586621679979247 :: a6989586621679974159 ~> (a6989586621679974159 ~> a6989586621679974159)) = Scanl1Sym1 a6989586621679979247 |
data Scanl1Sym1 (a6989586621679979247 :: (~>) a6989586621679974159 ((~>) a6989586621679974159 a6989586621679974159)) :: (~>) [a6989586621679974159] [a6989586621679974159] Source #
Instances
SingI d => SingI (Scanl1Sym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (Scanl1Sym1 d) Source # | |
SuppressUnusedWarnings (Scanl1Sym1 a6989586621679979247 :: TyFun [a6989586621679974159] [a6989586621679974159] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym1 a6989586621679979247 :: TyFun [a] [a] -> Type) (a6989586621679979248 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym1 a6989586621679979247 :: TyFun [a] [a] -> Type) (a6989586621679979248 :: [a]) = Scanl1 a6989586621679979247 a6989586621679979248 |
type Scanl1Sym2 (a6989586621679979247 :: (~>) a6989586621679974159 ((~>) a6989586621679974159 a6989586621679974159)) (a6989586621679979248 :: [a6989586621679974159]) = Scanl1 a6989586621679979247 a6989586621679979248 Source #
data ScanrSym0 :: forall a6989586621679974157 b6989586621679974158. (~>) ((~>) a6989586621679974157 ((~>) b6989586621679974158 b6989586621679974158)) ((~>) b6989586621679974158 ((~>) [a6989586621679974157] [b6989586621679974158])) Source #
Instances
SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym0 :: TyFun (a6989586621679974157 ~> (b6989586621679974158 ~> b6989586621679974158)) (b6989586621679974158 ~> ([a6989586621679974157] ~> [b6989586621679974158])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym0 :: TyFun (a6989586621679974157 ~> (b6989586621679974158 ~> b6989586621679974158)) (b6989586621679974158 ~> ([a6989586621679974157] ~> [b6989586621679974158])) -> Type) (a6989586621679979226 :: a6989586621679974157 ~> (b6989586621679974158 ~> b6989586621679974158)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ScanrSym0 :: TyFun (a6989586621679974157 ~> (b6989586621679974158 ~> b6989586621679974158)) (b6989586621679974158 ~> ([a6989586621679974157] ~> [b6989586621679974158])) -> Type) (a6989586621679979226 :: a6989586621679974157 ~> (b6989586621679974158 ~> b6989586621679974158)) = ScanrSym1 a6989586621679979226 |
data ScanrSym1 (a6989586621679979226 :: (~>) a6989586621679974157 ((~>) b6989586621679974158 b6989586621679974158)) :: (~>) b6989586621679974158 ((~>) [a6989586621679974157] [b6989586621679974158]) Source #
Instances
SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym1 a6989586621679979226 :: TyFun b6989586621679974158 ([a6989586621679974157] ~> [b6989586621679974158]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym1 a6989586621679979226 :: TyFun b6989586621679974158 ([a6989586621679974157] ~> [b6989586621679974158]) -> Type) (a6989586621679979227 :: b6989586621679974158) Source # | |
data ScanrSym2 (a6989586621679979226 :: (~>) a6989586621679974157 ((~>) b6989586621679974158 b6989586621679974158)) (a6989586621679979227 :: b6989586621679974158) :: (~>) [a6989586621679974157] [b6989586621679974158] Source #
Instances
(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym2 a6989586621679979227 a6989586621679979226 :: TyFun [a6989586621679974157] [b6989586621679974158] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym2 a6989586621679979227 a6989586621679979226 :: TyFun [a] [b] -> Type) (a6989586621679979228 :: [a]) Source # | |
type ScanrSym3 (a6989586621679979226 :: (~>) a6989586621679974157 ((~>) b6989586621679974158 b6989586621679974158)) (a6989586621679979227 :: b6989586621679974158) (a6989586621679979228 :: [a6989586621679974157]) = Scanr a6989586621679979226 a6989586621679979227 a6989586621679979228 Source #
data Scanr1Sym0 :: forall a6989586621679974156. (~>) ((~>) a6989586621679974156 ((~>) a6989586621679974156 a6989586621679974156)) ((~>) [a6989586621679974156] [a6989586621679974156]) Source #
Instances
SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Scanr1Sym0 Source # | |
SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a6989586621679974156 ~> (a6989586621679974156 ~> a6989586621679974156)) ([a6989586621679974156] ~> [a6989586621679974156]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym0 :: TyFun (a6989586621679974156 ~> (a6989586621679974156 ~> a6989586621679974156)) ([a6989586621679974156] ~> [a6989586621679974156]) -> Type) (a6989586621679979202 :: a6989586621679974156 ~> (a6989586621679974156 ~> a6989586621679974156)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym0 :: TyFun (a6989586621679974156 ~> (a6989586621679974156 ~> a6989586621679974156)) ([a6989586621679974156] ~> [a6989586621679974156]) -> Type) (a6989586621679979202 :: a6989586621679974156 ~> (a6989586621679974156 ~> a6989586621679974156)) = Scanr1Sym1 a6989586621679979202 |
data Scanr1Sym1 (a6989586621679979202 :: (~>) a6989586621679974156 ((~>) a6989586621679974156 a6989586621679974156)) :: (~>) [a6989586621679974156] [a6989586621679974156] Source #
Instances
SingI d => SingI (Scanr1Sym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (Scanr1Sym1 d) Source # | |
SuppressUnusedWarnings (Scanr1Sym1 a6989586621679979202 :: TyFun [a6989586621679974156] [a6989586621679974156] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym1 a6989586621679979202 :: TyFun [a] [a] -> Type) (a6989586621679979203 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym1 a6989586621679979202 :: TyFun [a] [a] -> Type) (a6989586621679979203 :: [a]) = Scanr1 a6989586621679979202 a6989586621679979203 |
type Scanr1Sym2 (a6989586621679979202 :: (~>) a6989586621679974156 ((~>) a6989586621679974156 a6989586621679974156)) (a6989586621679979203 :: [a6989586621679974156]) = Scanr1 a6989586621679979202 a6989586621679979203 Source #
data MapAccumLSym0 :: forall a6989586621680804227 b6989586621680804228 c6989586621680804229 t6989586621680804226. (~>) ((~>) a6989586621680804227 ((~>) b6989586621680804228 (a6989586621680804227, c6989586621680804229))) ((~>) a6989586621680804227 ((~>) (t6989586621680804226 b6989586621680804228) (a6989586621680804227, t6989586621680804226 c6989586621680804229))) Source #
Instances
STraversable t => SingI (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable sing :: Sing MapAccumLSym0 Source # | |
SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (a6989586621680804227 ~> (b6989586621680804228 ~> (a6989586621680804227, c6989586621680804229))) (a6989586621680804227 ~> (t6989586621680804226 b6989586621680804228 ~> (a6989586621680804227, t6989586621680804226 c6989586621680804229))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym0 :: TyFun (a6989586621680804227 ~> (b6989586621680804228 ~> (a6989586621680804227, c6989586621680804229))) (a6989586621680804227 ~> (t6989586621680804226 b6989586621680804228 ~> (a6989586621680804227, t6989586621680804226 c6989586621680804229))) -> Type) (a6989586621680804730 :: a6989586621680804227 ~> (b6989586621680804228 ~> (a6989586621680804227, c6989586621680804229))) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym0 :: TyFun (a6989586621680804227 ~> (b6989586621680804228 ~> (a6989586621680804227, c6989586621680804229))) (a6989586621680804227 ~> (t6989586621680804226 b6989586621680804228 ~> (a6989586621680804227, t6989586621680804226 c6989586621680804229))) -> Type) (a6989586621680804730 :: a6989586621680804227 ~> (b6989586621680804228 ~> (a6989586621680804227, c6989586621680804229))) = MapAccumLSym1 a6989586621680804730 t6989586621680804226 :: TyFun a6989586621680804227 (t6989586621680804226 b6989586621680804228 ~> (a6989586621680804227, t6989586621680804226 c6989586621680804229)) -> Type |
data MapAccumLSym1 (a6989586621680804730 :: (~>) a6989586621680804227 ((~>) b6989586621680804228 (a6989586621680804227, c6989586621680804229))) :: forall t6989586621680804226. (~>) a6989586621680804227 ((~>) (t6989586621680804226 b6989586621680804228) (a6989586621680804227, t6989586621680804226 c6989586621680804229)) 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 sing :: Sing (MapAccumLSym1 d t) Source # | |
SuppressUnusedWarnings (MapAccumLSym1 a6989586621680804730 t6989586621680804226 :: TyFun a6989586621680804227 (t6989586621680804226 b6989586621680804228 ~> (a6989586621680804227, t6989586621680804226 c6989586621680804229)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym1 a6989586621680804730 t6989586621680804226 :: TyFun a6989586621680804227 (t6989586621680804226 b6989586621680804228 ~> (a6989586621680804227, t6989586621680804226 c6989586621680804229)) -> Type) (a6989586621680804731 :: a6989586621680804227) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym1 a6989586621680804730 t6989586621680804226 :: TyFun a6989586621680804227 (t6989586621680804226 b6989586621680804228 ~> (a6989586621680804227, t6989586621680804226 c6989586621680804229)) -> Type) (a6989586621680804731 :: a6989586621680804227) = MapAccumLSym2 a6989586621680804730 a6989586621680804731 t6989586621680804226 :: TyFun (t6989586621680804226 b6989586621680804228) (a6989586621680804227, t6989586621680804226 c6989586621680804229) -> Type |
data MapAccumLSym2 (a6989586621680804730 :: (~>) a6989586621680804227 ((~>) b6989586621680804228 (a6989586621680804227, c6989586621680804229))) (a6989586621680804731 :: a6989586621680804227) :: forall t6989586621680804226. (~>) (t6989586621680804226 b6989586621680804228) (a6989586621680804227, t6989586621680804226 c6989586621680804229) 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 sing :: Sing (MapAccumLSym2 d1 d2 t) Source # | |
SuppressUnusedWarnings (MapAccumLSym2 a6989586621680804731 a6989586621680804730 t6989586621680804226 :: TyFun (t6989586621680804226 b6989586621680804228) (a6989586621680804227, t6989586621680804226 c6989586621680804229) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym2 a6989586621680804731 a6989586621680804730 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680804732 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym2 a6989586621680804731 a6989586621680804730 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680804732 :: t b) = MapAccumL a6989586621680804731 a6989586621680804730 a6989586621680804732 |
type MapAccumLSym3 (a6989586621680804730 :: (~>) a6989586621680804227 ((~>) b6989586621680804228 (a6989586621680804227, c6989586621680804229))) (a6989586621680804731 :: a6989586621680804227) (a6989586621680804732 :: t6989586621680804226 b6989586621680804228) = MapAccumL a6989586621680804730 a6989586621680804731 a6989586621680804732 Source #
data MapAccumRSym0 :: forall a6989586621680804223 b6989586621680804224 c6989586621680804225 t6989586621680804222. (~>) ((~>) a6989586621680804223 ((~>) b6989586621680804224 (a6989586621680804223, c6989586621680804225))) ((~>) a6989586621680804223 ((~>) (t6989586621680804222 b6989586621680804224) (a6989586621680804223, t6989586621680804222 c6989586621680804225))) Source #
Instances
STraversable t => SingI (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable sing :: Sing MapAccumRSym0 Source # | |
SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (a6989586621680804223 ~> (b6989586621680804224 ~> (a6989586621680804223, c6989586621680804225))) (a6989586621680804223 ~> (t6989586621680804222 b6989586621680804224 ~> (a6989586621680804223, t6989586621680804222 c6989586621680804225))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym0 :: TyFun (a6989586621680804223 ~> (b6989586621680804224 ~> (a6989586621680804223, c6989586621680804225))) (a6989586621680804223 ~> (t6989586621680804222 b6989586621680804224 ~> (a6989586621680804223, t6989586621680804222 c6989586621680804225))) -> Type) (a6989586621680804713 :: a6989586621680804223 ~> (b6989586621680804224 ~> (a6989586621680804223, c6989586621680804225))) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym0 :: TyFun (a6989586621680804223 ~> (b6989586621680804224 ~> (a6989586621680804223, c6989586621680804225))) (a6989586621680804223 ~> (t6989586621680804222 b6989586621680804224 ~> (a6989586621680804223, t6989586621680804222 c6989586621680804225))) -> Type) (a6989586621680804713 :: a6989586621680804223 ~> (b6989586621680804224 ~> (a6989586621680804223, c6989586621680804225))) = MapAccumRSym1 a6989586621680804713 t6989586621680804222 :: TyFun a6989586621680804223 (t6989586621680804222 b6989586621680804224 ~> (a6989586621680804223, t6989586621680804222 c6989586621680804225)) -> Type |
data MapAccumRSym1 (a6989586621680804713 :: (~>) a6989586621680804223 ((~>) b6989586621680804224 (a6989586621680804223, c6989586621680804225))) :: forall t6989586621680804222. (~>) a6989586621680804223 ((~>) (t6989586621680804222 b6989586621680804224) (a6989586621680804223, t6989586621680804222 c6989586621680804225)) 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 sing :: Sing (MapAccumRSym1 d t) Source # | |
SuppressUnusedWarnings (MapAccumRSym1 a6989586621680804713 t6989586621680804222 :: TyFun a6989586621680804223 (t6989586621680804222 b6989586621680804224 ~> (a6989586621680804223, t6989586621680804222 c6989586621680804225)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym1 a6989586621680804713 t6989586621680804222 :: TyFun a6989586621680804223 (t6989586621680804222 b6989586621680804224 ~> (a6989586621680804223, t6989586621680804222 c6989586621680804225)) -> Type) (a6989586621680804714 :: a6989586621680804223) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym1 a6989586621680804713 t6989586621680804222 :: TyFun a6989586621680804223 (t6989586621680804222 b6989586621680804224 ~> (a6989586621680804223, t6989586621680804222 c6989586621680804225)) -> Type) (a6989586621680804714 :: a6989586621680804223) = MapAccumRSym2 a6989586621680804713 a6989586621680804714 t6989586621680804222 :: TyFun (t6989586621680804222 b6989586621680804224) (a6989586621680804223, t6989586621680804222 c6989586621680804225) -> Type |
data MapAccumRSym2 (a6989586621680804713 :: (~>) a6989586621680804223 ((~>) b6989586621680804224 (a6989586621680804223, c6989586621680804225))) (a6989586621680804714 :: a6989586621680804223) :: forall t6989586621680804222. (~>) (t6989586621680804222 b6989586621680804224) (a6989586621680804223, t6989586621680804222 c6989586621680804225) 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 sing :: Sing (MapAccumRSym2 d1 d2 t) Source # | |
SuppressUnusedWarnings (MapAccumRSym2 a6989586621680804714 a6989586621680804713 t6989586621680804222 :: TyFun (t6989586621680804222 b6989586621680804224) (a6989586621680804223, t6989586621680804222 c6989586621680804225) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym2 a6989586621680804714 a6989586621680804713 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680804715 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym2 a6989586621680804714 a6989586621680804713 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680804715 :: t b) = MapAccumR a6989586621680804714 a6989586621680804713 a6989586621680804715 |
type MapAccumRSym3 (a6989586621680804713 :: (~>) a6989586621680804223 ((~>) b6989586621680804224 (a6989586621680804223, c6989586621680804225))) (a6989586621680804714 :: a6989586621680804223) (a6989586621680804715 :: t6989586621680804222 b6989586621680804224) = MapAccumR a6989586621680804713 a6989586621680804714 a6989586621680804715 Source #
data ReplicateSym0 :: forall a6989586621679974064. (~>) Nat ((~>) a6989586621679974064 [a6989586621679974064]) Source #
Instances
SingI (ReplicateSym0 :: TyFun Nat (a ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing ReplicateSym0 Source # | |
SuppressUnusedWarnings (ReplicateSym0 :: TyFun Nat (a6989586621679974064 ~> [a6989586621679974064]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym0 :: TyFun Nat (a6989586621679974064 ~> [a6989586621679974064]) -> Type) (a6989586621679978229 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym0 :: TyFun Nat (a6989586621679974064 ~> [a6989586621679974064]) -> Type) (a6989586621679978229 :: Nat) = ReplicateSym1 a6989586621679978229 a6989586621679974064 :: TyFun a6989586621679974064 [a6989586621679974064] -> Type |
data ReplicateSym1 (a6989586621679978229 :: Nat) :: forall a6989586621679974064. (~>) a6989586621679974064 [a6989586621679974064] Source #
Instances
SingI d => SingI (ReplicateSym1 d a :: TyFun a [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ReplicateSym1 d a) Source # | |
SuppressUnusedWarnings (ReplicateSym1 a6989586621679978229 a6989586621679974064 :: TyFun a6989586621679974064 [a6989586621679974064] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym1 a6989586621679978229 a :: TyFun a [a] -> Type) (a6989586621679978230 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym1 a6989586621679978229 a :: TyFun a [a] -> Type) (a6989586621679978230 :: a) = Replicate a6989586621679978229 a6989586621679978230 |
type ReplicateSym2 (a6989586621679978229 :: Nat) (a6989586621679978230 :: a6989586621679974064) = Replicate a6989586621679978229 a6989586621679978230 Source #
data UnfoldrSym0 :: forall b6989586621679974148 a6989586621679974149. (~>) ((~>) b6989586621679974148 (Maybe (a6989586621679974149, b6989586621679974148))) ((~>) b6989586621679974148 [a6989586621679974149]) Source #
Instances
SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing UnfoldrSym0 Source # | |
SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (b6989586621679974148 ~> Maybe (a6989586621679974149, b6989586621679974148)) (b6989586621679974148 ~> [a6989586621679974149]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym0 :: TyFun (b6989586621679974148 ~> Maybe (a6989586621679974149, b6989586621679974148)) (b6989586621679974148 ~> [a6989586621679974149]) -> Type) (a6989586621679979060 :: b6989586621679974148 ~> Maybe (a6989586621679974149, b6989586621679974148)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym0 :: TyFun (b6989586621679974148 ~> Maybe (a6989586621679974149, b6989586621679974148)) (b6989586621679974148 ~> [a6989586621679974149]) -> Type) (a6989586621679979060 :: b6989586621679974148 ~> Maybe (a6989586621679974149, b6989586621679974148)) = UnfoldrSym1 a6989586621679979060 |
data UnfoldrSym1 (a6989586621679979060 :: (~>) b6989586621679974148 (Maybe (a6989586621679974149, b6989586621679974148))) :: (~>) b6989586621679974148 [a6989586621679974149] Source #
Instances
SingI d => SingI (UnfoldrSym1 d :: TyFun b [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (UnfoldrSym1 d) Source # | |
SuppressUnusedWarnings (UnfoldrSym1 a6989586621679979060 :: TyFun b6989586621679974148 [a6989586621679974149] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym1 a6989586621679979060 :: TyFun b [a] -> Type) (a6989586621679979061 :: b) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym1 a6989586621679979060 :: TyFun b [a] -> Type) (a6989586621679979061 :: b) = Unfoldr a6989586621679979060 a6989586621679979061 |
type UnfoldrSym2 (a6989586621679979060 :: (~>) b6989586621679974148 (Maybe (a6989586621679974149, b6989586621679974148))) (a6989586621679979061 :: b6989586621679974148) = Unfoldr a6989586621679979060 a6989586621679979061 Source #
data TakeSym0 :: forall a6989586621679974080. (~>) Nat ((~>) [a6989586621679974080] [a6989586621679974080]) Source #
Instances
SingI (TakeSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (TakeSym0 :: TyFun Nat ([a6989586621679974080] ~> [a6989586621679974080]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym0 :: TyFun Nat ([a6989586621679974080] ~> [a6989586621679974080]) -> Type) (a6989586621679978390 :: Nat) Source # | |
data TakeSym1 (a6989586621679978390 :: Nat) :: forall a6989586621679974080. (~>) [a6989586621679974080] [a6989586621679974080] Source #
Instances
SingI d => SingI (TakeSym1 d a :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (TakeSym1 a6989586621679978390 a6989586621679974080 :: TyFun [a6989586621679974080] [a6989586621679974080] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym1 a6989586621679978390 a :: TyFun [a] [a] -> Type) (a6989586621679978391 :: [a]) Source # | |
type TakeSym2 (a6989586621679978390 :: Nat) (a6989586621679978391 :: [a6989586621679974080]) = Take a6989586621679978390 a6989586621679978391 Source #
data DropSym0 :: forall a6989586621679974079. (~>) Nat ((~>) [a6989586621679974079] [a6989586621679974079]) Source #
Instances
SingI (DropSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (DropSym0 :: TyFun Nat ([a6989586621679974079] ~> [a6989586621679974079]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropSym0 :: TyFun Nat ([a6989586621679974079] ~> [a6989586621679974079]) -> Type) (a6989586621679978376 :: Nat) Source # | |
data DropSym1 (a6989586621679978376 :: Nat) :: forall a6989586621679974079. (~>) [a6989586621679974079] [a6989586621679974079] Source #
Instances
SingI d => SingI (DropSym1 d a :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (DropSym1 a6989586621679978376 a6989586621679974079 :: TyFun [a6989586621679974079] [a6989586621679974079] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropSym1 a6989586621679978376 a :: TyFun [a] [a] -> Type) (a6989586621679978377 :: [a]) Source # | |
type DropSym2 (a6989586621679978376 :: Nat) (a6989586621679978377 :: [a6989586621679974079]) = Drop a6989586621679978376 a6989586621679978377 Source #
data SplitAtSym0 :: forall a6989586621679974078. (~>) Nat ((~>) [a6989586621679974078] ([a6989586621679974078], [a6989586621679974078])) Source #
Instances
SingI (SplitAtSym0 :: TyFun Nat ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing SplitAtSym0 Source # | |
SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat ([a6989586621679974078] ~> ([a6989586621679974078], [a6989586621679974078])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym0 :: TyFun Nat ([a6989586621679974078] ~> ([a6989586621679974078], [a6989586621679974078])) -> Type) (a6989586621679978370 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym0 :: TyFun Nat ([a6989586621679974078] ~> ([a6989586621679974078], [a6989586621679974078])) -> Type) (a6989586621679978370 :: Nat) = SplitAtSym1 a6989586621679978370 a6989586621679974078 :: TyFun [a6989586621679974078] ([a6989586621679974078], [a6989586621679974078]) -> Type |
data SplitAtSym1 (a6989586621679978370 :: Nat) :: forall a6989586621679974078. (~>) [a6989586621679974078] ([a6989586621679974078], [a6989586621679974078]) Source #
Instances
SingI d => SingI (SplitAtSym1 d a :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (SplitAtSym1 d a) Source # | |
SuppressUnusedWarnings (SplitAtSym1 a6989586621679978370 a6989586621679974078 :: TyFun [a6989586621679974078] ([a6989586621679974078], [a6989586621679974078]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym1 a6989586621679978370 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621679978371 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym1 a6989586621679978370 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621679978371 :: [a]) = SplitAt a6989586621679978370 a6989586621679978371 |
type SplitAtSym2 (a6989586621679978370 :: Nat) (a6989586621679978371 :: [a6989586621679974078]) = SplitAt a6989586621679978370 a6989586621679978371 Source #
data TakeWhileSym0 :: forall a6989586621679974085. (~>) ((~>) a6989586621679974085 Bool) ((~>) [a6989586621679974085] [a6989586621679974085]) Source #
Instances
SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing TakeWhileSym0 Source # | |
SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a6989586621679974085 ~> Bool) ([a6989586621679974085] ~> [a6989586621679974085]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym0 :: TyFun (a6989586621679974085 ~> Bool) ([a6989586621679974085] ~> [a6989586621679974085]) -> Type) (a6989586621679978534 :: a6989586621679974085 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym0 :: TyFun (a6989586621679974085 ~> Bool) ([a6989586621679974085] ~> [a6989586621679974085]) -> Type) (a6989586621679978534 :: a6989586621679974085 ~> Bool) = TakeWhileSym1 a6989586621679978534 |
data TakeWhileSym1 (a6989586621679978534 :: (~>) a6989586621679974085 Bool) :: (~>) [a6989586621679974085] [a6989586621679974085] Source #
Instances
SingI d => SingI (TakeWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (TakeWhileSym1 d) Source # | |
SuppressUnusedWarnings (TakeWhileSym1 a6989586621679978534 :: TyFun [a6989586621679974085] [a6989586621679974085] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym1 a6989586621679978534 :: TyFun [a] [a] -> Type) (a6989586621679978535 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym1 a6989586621679978534 :: TyFun [a] [a] -> Type) (a6989586621679978535 :: [a]) = TakeWhile a6989586621679978534 a6989586621679978535 |
type TakeWhileSym2 (a6989586621679978534 :: (~>) a6989586621679974085 Bool) (a6989586621679978535 :: [a6989586621679974085]) = TakeWhile a6989586621679978534 a6989586621679978535 Source #
data DropWhileSym0 :: forall a6989586621679974084. (~>) ((~>) a6989586621679974084 Bool) ((~>) [a6989586621679974084] [a6989586621679974084]) Source #
Instances
SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing DropWhileSym0 Source # | |
SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a6989586621679974084 ~> Bool) ([a6989586621679974084] ~> [a6989586621679974084]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym0 :: TyFun (a6989586621679974084 ~> Bool) ([a6989586621679974084] ~> [a6989586621679974084]) -> Type) (a6989586621679978516 :: a6989586621679974084 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym0 :: TyFun (a6989586621679974084 ~> Bool) ([a6989586621679974084] ~> [a6989586621679974084]) -> Type) (a6989586621679978516 :: a6989586621679974084 ~> Bool) = DropWhileSym1 a6989586621679978516 |
data DropWhileSym1 (a6989586621679978516 :: (~>) a6989586621679974084 Bool) :: (~>) [a6989586621679974084] [a6989586621679974084] Source #
Instances
SingI d => SingI (DropWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DropWhileSym1 d) Source # | |
SuppressUnusedWarnings (DropWhileSym1 a6989586621679978516 :: TyFun [a6989586621679974084] [a6989586621679974084] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym1 a6989586621679978516 :: TyFun [a] [a] -> Type) (a6989586621679978517 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym1 a6989586621679978516 :: TyFun [a] [a] -> Type) (a6989586621679978517 :: [a]) = DropWhile a6989586621679978516 a6989586621679978517 |
type DropWhileSym2 (a6989586621679978516 :: (~>) a6989586621679974084 Bool) (a6989586621679978517 :: [a6989586621679974084]) = DropWhile a6989586621679978516 a6989586621679978517 Source #
data DropWhileEndSym0 :: forall a6989586621679974083. (~>) ((~>) a6989586621679974083 Bool) ((~>) [a6989586621679974083] [a6989586621679974083]) Source #
Instances
SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a6989586621679974083 ~> Bool) ([a6989586621679974083] ~> [a6989586621679974083]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym0 :: TyFun (a6989586621679974083 ~> Bool) ([a6989586621679974083] ~> [a6989586621679974083]) -> Type) (a6989586621679978490 :: a6989586621679974083 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym0 :: TyFun (a6989586621679974083 ~> Bool) ([a6989586621679974083] ~> [a6989586621679974083]) -> Type) (a6989586621679978490 :: a6989586621679974083 ~> Bool) = DropWhileEndSym1 a6989586621679978490 |
data DropWhileEndSym1 (a6989586621679978490 :: (~>) a6989586621679974083 Bool) :: (~>) [a6989586621679974083] [a6989586621679974083] Source #
Instances
SingI d => SingI (DropWhileEndSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DropWhileEndSym1 d) Source # | |
SuppressUnusedWarnings (DropWhileEndSym1 a6989586621679978490 :: TyFun [a6989586621679974083] [a6989586621679974083] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym1 a6989586621679978490 :: TyFun [a] [a] -> Type) (a6989586621679978491 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym1 a6989586621679978490 :: TyFun [a] [a] -> Type) (a6989586621679978491 :: [a]) = DropWhileEnd a6989586621679978490 a6989586621679978491 |
type DropWhileEndSym2 (a6989586621679978490 :: (~>) a6989586621679974083 Bool) (a6989586621679978491 :: [a6989586621679974083]) = DropWhileEnd a6989586621679978490 a6989586621679978491 Source #
data SpanSym0 :: forall a6989586621679974082. (~>) ((~>) a6989586621679974082 Bool) ((~>) [a6989586621679974082] ([a6989586621679974082], [a6989586621679974082])) Source #
Instances
SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym0 :: TyFun (a6989586621679974082 ~> Bool) ([a6989586621679974082] ~> ([a6989586621679974082], [a6989586621679974082])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym0 :: TyFun (a6989586621679974082 ~> Bool) ([a6989586621679974082] ~> ([a6989586621679974082], [a6989586621679974082])) -> Type) (a6989586621679978447 :: a6989586621679974082 ~> Bool) Source # | |
data SpanSym1 (a6989586621679978447 :: (~>) a6989586621679974082 Bool) :: (~>) [a6989586621679974082] ([a6989586621679974082], [a6989586621679974082]) Source #
Instances
SingI d => SingI (SpanSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym1 a6989586621679978447 :: TyFun [a6989586621679974082] ([a6989586621679974082], [a6989586621679974082]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym1 a6989586621679978447 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679978448 :: [a]) Source # | |
type SpanSym2 (a6989586621679978447 :: (~>) a6989586621679974082 Bool) (a6989586621679978448 :: [a6989586621679974082]) = Span a6989586621679978447 a6989586621679978448 Source #
data BreakSym0 :: forall a6989586621679974081. (~>) ((~>) a6989586621679974081 Bool) ((~>) [a6989586621679974081] ([a6989586621679974081], [a6989586621679974081])) Source #
Instances
SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym0 :: TyFun (a6989586621679974081 ~> Bool) ([a6989586621679974081] ~> ([a6989586621679974081], [a6989586621679974081])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym0 :: TyFun (a6989586621679974081 ~> Bool) ([a6989586621679974081] ~> ([a6989586621679974081], [a6989586621679974081])) -> Type) (a6989586621679978404 :: a6989586621679974081 ~> Bool) Source # | |
data BreakSym1 (a6989586621679978404 :: (~>) a6989586621679974081 Bool) :: (~>) [a6989586621679974081] ([a6989586621679974081], [a6989586621679974081]) Source #
Instances
SingI d => SingI (BreakSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym1 a6989586621679978404 :: TyFun [a6989586621679974081] ([a6989586621679974081], [a6989586621679974081]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym1 a6989586621679978404 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679978405 :: [a]) Source # | |
type BreakSym2 (a6989586621679978404 :: (~>) a6989586621679974081 Bool) (a6989586621679978405 :: [a6989586621679974081]) = Break a6989586621679978404 a6989586621679978405 Source #
data StripPrefixSym0 :: forall a6989586621680096271. (~>) [a6989586621680096271] ((~>) [a6989586621680096271] (Maybe [a6989586621680096271])) Source #
Instances
SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a6989586621680096271] ([a6989586621680096271] ~> Maybe [a6989586621680096271]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (StripPrefixSym0 :: TyFun [a6989586621680096271] ([a6989586621680096271] ~> Maybe [a6989586621680096271]) -> Type) (a6989586621680097967 :: [a6989586621680096271]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym0 :: TyFun [a6989586621680096271] ([a6989586621680096271] ~> Maybe [a6989586621680096271]) -> Type) (a6989586621680097967 :: [a6989586621680096271]) = StripPrefixSym1 a6989586621680097967 |
data StripPrefixSym1 (a6989586621680097967 :: [a6989586621680096271]) :: (~>) [a6989586621680096271] (Maybe [a6989586621680096271]) Source #
Instances
SuppressUnusedWarnings (StripPrefixSym1 a6989586621680097967 :: TyFun [a6989586621680096271] (Maybe [a6989586621680096271]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (StripPrefixSym1 a6989586621680097967 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680097968 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym1 a6989586621680097967 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680097968 :: [a]) = StripPrefix a6989586621680097967 a6989586621680097968 |
type StripPrefixSym2 (a6989586621680097967 :: [a6989586621680096271]) (a6989586621680097968 :: [a6989586621680096271]) = StripPrefix a6989586621680097967 a6989586621680097968 Source #
data GroupSym0 :: forall a6989586621679974077. (~>) [a6989586621679974077] [[a6989586621679974077]] Source #
Instances
SEq a => SingI (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621679974077] [[a6989586621679974077]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679978367 :: [a]) Source # | |
type GroupSym1 (a6989586621679978367 :: [a6989586621679974077]) = Group a6989586621679978367 Source #
data InitsSym0 :: forall a6989586621679974147. (~>) [a6989586621679974147] [[a6989586621679974147]] Source #
Instances
SingI (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621679974147] [[a6989586621679974147]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679979052 :: [a]) Source # | |
type InitsSym1 (a6989586621679979052 :: [a6989586621679974147]) = Inits a6989586621679979052 Source #
data TailsSym0 :: forall a6989586621679974146. (~>) [a6989586621679974146] [[a6989586621679974146]] Source #
Instances
SingI (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621679974146] [[a6989586621679974146]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679979045 :: [a]) Source # | |
type TailsSym1 (a6989586621679979045 :: [a6989586621679974146]) = Tails a6989586621679979045 Source #
data IsPrefixOfSym0 :: forall a6989586621679974145. (~>) [a6989586621679974145] ((~>) [a6989586621679974145] Bool) Source #
Instances
SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679974145] ([a6989586621679974145] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679974145] ([a6989586621679974145] ~> Bool) -> Type) (a6989586621679979037 :: [a6989586621679974145]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679974145] ([a6989586621679974145] ~> Bool) -> Type) (a6989586621679979037 :: [a6989586621679974145]) = IsPrefixOfSym1 a6989586621679979037 |
data IsPrefixOfSym1 (a6989586621679979037 :: [a6989586621679974145]) :: (~>) [a6989586621679974145] Bool Source #
Instances
(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IsPrefixOfSym1 d) Source # | |
SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679979037 :: TyFun [a6989586621679974145] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym1 a6989586621679979037 :: TyFun [a] Bool -> Type) (a6989586621679979038 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym1 a6989586621679979037 :: TyFun [a] Bool -> Type) (a6989586621679979038 :: [a]) = IsPrefixOf a6989586621679979037 a6989586621679979038 |
type IsPrefixOfSym2 (a6989586621679979037 :: [a6989586621679974145]) (a6989586621679979038 :: [a6989586621679974145]) = IsPrefixOf a6989586621679979037 a6989586621679979038 Source #
data IsSuffixOfSym0 :: forall a6989586621679974144. (~>) [a6989586621679974144] ((~>) [a6989586621679974144] Bool) Source #
Instances
SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679974144] ([a6989586621679974144] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679974144] ([a6989586621679974144] ~> Bool) -> Type) (a6989586621679979031 :: [a6989586621679974144]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679974144] ([a6989586621679974144] ~> Bool) -> Type) (a6989586621679979031 :: [a6989586621679974144]) = IsSuffixOfSym1 a6989586621679979031 |
data IsSuffixOfSym1 (a6989586621679979031 :: [a6989586621679974144]) :: (~>) [a6989586621679974144] Bool Source #
Instances
(SEq a, SingI d) => SingI (IsSuffixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IsSuffixOfSym1 d) Source # | |
SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679979031 :: TyFun [a6989586621679974144] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym1 a6989586621679979031 :: TyFun [a] Bool -> Type) (a6989586621679979032 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym1 a6989586621679979031 :: TyFun [a] Bool -> Type) (a6989586621679979032 :: [a]) = IsSuffixOf a6989586621679979031 a6989586621679979032 |
type IsSuffixOfSym2 (a6989586621679979031 :: [a6989586621679974144]) (a6989586621679979032 :: [a6989586621679974144]) = IsSuffixOf a6989586621679979031 a6989586621679979032 Source #
data IsInfixOfSym0 :: forall a6989586621679974143. (~>) [a6989586621679974143] ((~>) [a6989586621679974143] Bool) Source #
Instances
SEq a => SingI (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing IsInfixOfSym0 Source # | |
SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a6989586621679974143] ([a6989586621679974143] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym0 :: TyFun [a6989586621679974143] ([a6989586621679974143] ~> Bool) -> Type) (a6989586621679979025 :: [a6989586621679974143]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsInfixOfSym0 :: TyFun [a6989586621679974143] ([a6989586621679974143] ~> Bool) -> Type) (a6989586621679979025 :: [a6989586621679974143]) = IsInfixOfSym1 a6989586621679979025 |
data IsInfixOfSym1 (a6989586621679979025 :: [a6989586621679974143]) :: (~>) [a6989586621679974143] Bool Source #
Instances
(SEq a, SingI d) => SingI (IsInfixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IsInfixOfSym1 d) Source # | |
SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679979025 :: TyFun [a6989586621679974143] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym1 a6989586621679979025 :: TyFun [a] Bool -> Type) (a6989586621679979026 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type IsInfixOfSym2 (a6989586621679979025 :: [a6989586621679974143]) (a6989586621679979026 :: [a6989586621679974143]) = IsInfixOf a6989586621679979025 a6989586621679979026 Source #
data ElemSym0 :: forall a6989586621680490519 t6989586621680490502. (~>) a6989586621680490519 ((~>) (t6989586621680490502 a6989586621680490519) Bool) Source #
Instances
(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621680490519 (t6989586621680490502 a6989586621680490519 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym0 :: TyFun a6989586621680490519 (t6989586621680490502 a6989586621680490519 ~> Bool) -> Type) (arg6989586621680491165 :: a6989586621680490519) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data ElemSym1 (arg6989586621680491165 :: a6989586621680490519) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490519) Bool Source #
Instances
(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (ElemSym1 arg6989586621680491165 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490519) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym1 arg6989586621680491165 t :: TyFun (t a) Bool -> Type) (arg6989586621680491166 :: t a) Source # | |
type ElemSym2 (arg6989586621680491165 :: a6989586621680490519) (arg6989586621680491166 :: t6989586621680490502 a6989586621680490519) = Elem arg6989586621680491165 arg6989586621680491166 Source #
data NotElemSym0 :: forall a6989586621680490413 t6989586621680490412. (~>) a6989586621680490413 ((~>) (t6989586621680490412 a6989586621680490413) Bool) Source #
Instances
(SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing NotElemSym0 Source # | |
SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621680490413 (t6989586621680490412 a6989586621680490413 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym0 :: TyFun a6989586621680490413 (t6989586621680490412 a6989586621680490413 ~> Bool) -> Type) (a6989586621680490891 :: a6989586621680490413) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (NotElemSym0 :: TyFun a6989586621680490413 (t6989586621680490412 a6989586621680490413 ~> Bool) -> Type) (a6989586621680490891 :: a6989586621680490413) = NotElemSym1 a6989586621680490891 t6989586621680490412 :: TyFun (t6989586621680490412 a6989586621680490413) Bool -> Type |
data NotElemSym1 (a6989586621680490891 :: a6989586621680490413) :: forall t6989586621680490412. (~>) (t6989586621680490412 a6989586621680490413) 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 sing :: Sing (NotElemSym1 d t) Source # | |
SuppressUnusedWarnings (NotElemSym1 a6989586621680490891 t6989586621680490412 :: TyFun (t6989586621680490412 a6989586621680490413) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym1 a6989586621680490891 t :: TyFun (t a) Bool -> Type) (a6989586621680490892 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type NotElemSym2 (a6989586621680490891 :: a6989586621680490413) (a6989586621680490892 :: t6989586621680490412 a6989586621680490413) = NotElem a6989586621680490891 a6989586621680490892 Source #
data LookupSym0 :: forall a6989586621679974070 b6989586621679974071. (~>) a6989586621679974070 ((~>) [(a6989586621679974070, b6989586621679974071)] (Maybe b6989586621679974071)) Source #
Instances
SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing LookupSym0 Source # | |
SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679974070 ([(a6989586621679974070, b6989586621679974071)] ~> Maybe b6989586621679974071) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym0 :: TyFun a6989586621679974070 ([(a6989586621679974070, b6989586621679974071)] ~> Maybe b6989586621679974071) -> Type) (a6989586621679978294 :: a6989586621679974070) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (LookupSym0 :: TyFun a6989586621679974070 ([(a6989586621679974070, b6989586621679974071)] ~> Maybe b6989586621679974071) -> Type) (a6989586621679978294 :: a6989586621679974070) = LookupSym1 a6989586621679978294 b6989586621679974071 :: TyFun [(a6989586621679974070, b6989586621679974071)] (Maybe b6989586621679974071) -> Type |
data LookupSym1 (a6989586621679978294 :: a6989586621679974070) :: forall b6989586621679974071. (~>) [(a6989586621679974070, b6989586621679974071)] (Maybe b6989586621679974071) Source #
Instances
(SEq a, SingI d) => SingI (LookupSym1 d b :: TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (LookupSym1 d b) Source # | |
SuppressUnusedWarnings (LookupSym1 a6989586621679978294 b6989586621679974071 :: TyFun [(a6989586621679974070, b6989586621679974071)] (Maybe b6989586621679974071) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym1 a6989586621679978294 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679978295 :: [(a, b)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type LookupSym2 (a6989586621679978294 :: a6989586621679974070) (a6989586621679978295 :: [(a6989586621679974070, b6989586621679974071)]) = Lookup a6989586621679978294 a6989586621679978295 Source #
data FindSym0 :: forall a6989586621680490411 t6989586621680490410. (~>) ((~>) a6989586621680490411 Bool) ((~>) (t6989586621680490410 a6989586621680490411) (Maybe a6989586621680490411)) Source #
Instances
SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # | |
SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680490411 ~> Bool) (t6989586621680490410 a6989586621680490411 ~> Maybe a6989586621680490411) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FindSym0 :: TyFun (a6989586621680490411 ~> Bool) (t6989586621680490410 a6989586621680490411 ~> Maybe a6989586621680490411) -> Type) (a6989586621680490864 :: a6989586621680490411 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FindSym0 :: TyFun (a6989586621680490411 ~> Bool) (t6989586621680490410 a6989586621680490411 ~> Maybe a6989586621680490411) -> Type) (a6989586621680490864 :: a6989586621680490411 ~> Bool) = FindSym1 a6989586621680490864 t6989586621680490410 :: TyFun (t6989586621680490410 a6989586621680490411) (Maybe a6989586621680490411) -> Type |
data FindSym1 (a6989586621680490864 :: (~>) a6989586621680490411 Bool) :: forall t6989586621680490410. (~>) (t6989586621680490410 a6989586621680490411) (Maybe a6989586621680490411) Source #
Instances
(SFoldable t, SingI d) => SingI (FindSym1 d t :: TyFun (t a) (Maybe a) -> Type) Source # | |
SuppressUnusedWarnings (FindSym1 a6989586621680490864 t6989586621680490410 :: TyFun (t6989586621680490410 a6989586621680490411) (Maybe a6989586621680490411) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FindSym1 a6989586621680490864 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680490865 :: t a) Source # | |
type FindSym2 (a6989586621680490864 :: (~>) a6989586621680490411 Bool) (a6989586621680490865 :: t6989586621680490410 a6989586621680490411) = Find a6989586621680490864 a6989586621680490865 Source #
data FilterSym0 :: forall a6989586621679974093. (~>) ((~>) a6989586621679974093 Bool) ((~>) [a6989586621679974093] [a6989586621679974093]) Source #
Instances
SingI (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing FilterSym0 Source # | |
SuppressUnusedWarnings (FilterSym0 :: TyFun (a6989586621679974093 ~> Bool) ([a6989586621679974093] ~> [a6989586621679974093]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym0 :: TyFun (a6989586621679974093 ~> Bool) ([a6989586621679974093] ~> [a6989586621679974093]) -> Type) (a6989586621679978648 :: a6989586621679974093 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym0 :: TyFun (a6989586621679974093 ~> Bool) ([a6989586621679974093] ~> [a6989586621679974093]) -> Type) (a6989586621679978648 :: a6989586621679974093 ~> Bool) = FilterSym1 a6989586621679978648 |
data FilterSym1 (a6989586621679978648 :: (~>) a6989586621679974093 Bool) :: (~>) [a6989586621679974093] [a6989586621679974093] Source #
Instances
SingI d => SingI (FilterSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (FilterSym1 d) Source # | |
SuppressUnusedWarnings (FilterSym1 a6989586621679978648 :: TyFun [a6989586621679974093] [a6989586621679974093] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym1 a6989586621679978648 :: TyFun [a] [a] -> Type) (a6989586621679978649 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym1 a6989586621679978648 :: TyFun [a] [a] -> Type) (a6989586621679978649 :: [a]) = Filter a6989586621679978648 a6989586621679978649 |
type FilterSym2 (a6989586621679978648 :: (~>) a6989586621679974093 Bool) (a6989586621679978649 :: [a6989586621679974093]) = Filter a6989586621679978648 a6989586621679978649 Source #
data PartitionSym0 :: forall a6989586621679974069. (~>) ((~>) a6989586621679974069 Bool) ((~>) [a6989586621679974069] ([a6989586621679974069], [a6989586621679974069])) Source #
Instances
SingI (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing PartitionSym0 Source # | |
SuppressUnusedWarnings (PartitionSym0 :: TyFun (a6989586621679974069 ~> Bool) ([a6989586621679974069] ~> ([a6989586621679974069], [a6989586621679974069])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym0 :: TyFun (a6989586621679974069 ~> Bool) ([a6989586621679974069] ~> ([a6989586621679974069], [a6989586621679974069])) -> Type) (a6989586621679978288 :: a6989586621679974069 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym0 :: TyFun (a6989586621679974069 ~> Bool) ([a6989586621679974069] ~> ([a6989586621679974069], [a6989586621679974069])) -> Type) (a6989586621679978288 :: a6989586621679974069 ~> Bool) = PartitionSym1 a6989586621679978288 |
data PartitionSym1 (a6989586621679978288 :: (~>) a6989586621679974069 Bool) :: (~>) [a6989586621679974069] ([a6989586621679974069], [a6989586621679974069]) Source #
Instances
SingI d => SingI (PartitionSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (PartitionSym1 d) Source # | |
SuppressUnusedWarnings (PartitionSym1 a6989586621679978288 :: TyFun [a6989586621679974069] ([a6989586621679974069], [a6989586621679974069]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym1 a6989586621679978288 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679978289 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym1 a6989586621679978288 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679978289 :: [a]) = Partition a6989586621679978288 a6989586621679978289 |
type PartitionSym2 (a6989586621679978288 :: (~>) a6989586621679974069 Bool) (a6989586621679978289 :: [a6989586621679974069]) = Partition a6989586621679978288 a6989586621679978289 Source #
data (!!@#@$) :: forall a6989586621679974062. (~>) [a6989586621679974062] ((~>) Nat a6989586621679974062) infixl 9 Source #
Instances
SingI ((!!@#@$) :: TyFun [a] (Nat ~> a) -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$) :: TyFun [a6989586621679974062] (Nat ~> a6989586621679974062) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$) :: TyFun [a6989586621679974062] (Nat ~> a6989586621679974062) -> Type) (a6989586621679978209 :: [a6989586621679974062]) Source # | |
data (!!@#@$$) (a6989586621679978209 :: [a6989586621679974062]) :: (~>) Nat a6989586621679974062 infixl 9 Source #
Instances
SingI d => SingI ((!!@#@$$) d :: TyFun Nat a -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$$) a6989586621679978209 :: TyFun Nat a6989586621679974062 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$$) a6989586621679978209 :: TyFun Nat a -> Type) (a6989586621679978210 :: Nat) Source # | |
type (!!@#@$$$) (a6989586621679978209 :: [a6989586621679974062]) (a6989586621679978210 :: Nat) = (!!) a6989586621679978209 a6989586621679978210 Source #
data ElemIndexSym0 :: forall a6989586621679974091. (~>) a6989586621679974091 ((~>) [a6989586621679974091] (Maybe Nat)) Source #
Instances
SEq a => SingI (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing ElemIndexSym0 Source # | |
SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679974091 ([a6989586621679974091] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym0 :: TyFun a6989586621679974091 ([a6989586621679974091] ~> Maybe Nat) -> Type) (a6989586621679978632 :: a6989586621679974091) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndexSym0 :: TyFun a6989586621679974091 ([a6989586621679974091] ~> Maybe Nat) -> Type) (a6989586621679978632 :: a6989586621679974091) = ElemIndexSym1 a6989586621679978632 |
data ElemIndexSym1 (a6989586621679978632 :: a6989586621679974091) :: (~>) [a6989586621679974091] (Maybe Nat) Source #
Instances
(SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ElemIndexSym1 d) Source # | |
SuppressUnusedWarnings (ElemIndexSym1 a6989586621679978632 :: TyFun [a6989586621679974091] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym1 a6989586621679978632 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679978633 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type ElemIndexSym2 (a6989586621679978632 :: a6989586621679974091) (a6989586621679978633 :: [a6989586621679974091]) = ElemIndex a6989586621679978632 a6989586621679978633 Source #
data ElemIndicesSym0 :: forall a6989586621679974090. (~>) a6989586621679974090 ((~>) [a6989586621679974090] [Nat]) Source #
Instances
SEq a => SingI (ElemIndicesSym0 :: TyFun a ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a6989586621679974090 ([a6989586621679974090] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym0 :: TyFun a6989586621679974090 ([a6989586621679974090] ~> [Nat]) -> Type) (a6989586621679978624 :: a6989586621679974090) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym0 :: TyFun a6989586621679974090 ([a6989586621679974090] ~> [Nat]) -> Type) (a6989586621679978624 :: a6989586621679974090) = ElemIndicesSym1 a6989586621679978624 |
data ElemIndicesSym1 (a6989586621679978624 :: a6989586621679974090) :: (~>) [a6989586621679974090] [Nat] Source #
Instances
(SEq a, SingI d) => SingI (ElemIndicesSym1 d :: TyFun [a] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ElemIndicesSym1 d) Source # | |
SuppressUnusedWarnings (ElemIndicesSym1 a6989586621679978624 :: TyFun [a6989586621679974090] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym1 a6989586621679978624 :: TyFun [a] [Nat] -> Type) (a6989586621679978625 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym1 a6989586621679978624 :: TyFun [a] [Nat] -> Type) (a6989586621679978625 :: [a]) = ElemIndices a6989586621679978624 a6989586621679978625 |
type ElemIndicesSym2 (a6989586621679978624 :: a6989586621679974090) (a6989586621679978625 :: [a6989586621679974090]) = ElemIndices a6989586621679978624 a6989586621679978625 Source #
data FindIndexSym0 :: forall a6989586621679974089. (~>) ((~>) a6989586621679974089 Bool) ((~>) [a6989586621679974089] (Maybe Nat)) Source #
Instances
SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing FindIndexSym0 Source # | |
SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a6989586621679974089 ~> Bool) ([a6989586621679974089] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym0 :: TyFun (a6989586621679974089 ~> Bool) ([a6989586621679974089] ~> Maybe Nat) -> Type) (a6989586621679978616 :: a6989586621679974089 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data FindIndexSym1 (a6989586621679978616 :: (~>) a6989586621679974089 Bool) :: (~>) [a6989586621679974089] (Maybe Nat) Source #
Instances
SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (FindIndexSym1 d) Source # | |
SuppressUnusedWarnings (FindIndexSym1 a6989586621679978616 :: TyFun [a6989586621679974089] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym1 a6989586621679978616 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679978617 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type FindIndexSym2 (a6989586621679978616 :: (~>) a6989586621679974089 Bool) (a6989586621679978617 :: [a6989586621679974089]) = FindIndex a6989586621679978616 a6989586621679978617 Source #
data FindIndicesSym0 :: forall a6989586621679974088. (~>) ((~>) a6989586621679974088 Bool) ((~>) [a6989586621679974088] [Nat]) Source #
Instances
SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (a6989586621679974088 ~> Bool) ([a6989586621679974088] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym0 :: TyFun (a6989586621679974088 ~> Bool) ([a6989586621679974088] ~> [Nat]) -> Type) (a6989586621679978590 :: a6989586621679974088 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data FindIndicesSym1 (a6989586621679978590 :: (~>) a6989586621679974088 Bool) :: (~>) [a6989586621679974088] [Nat] Source #
Instances
SingI d => SingI (FindIndicesSym1 d :: TyFun [a] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (FindIndicesSym1 d) Source # | |
SuppressUnusedWarnings (FindIndicesSym1 a6989586621679978590 :: TyFun [a6989586621679974088] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym1 a6989586621679978590 :: TyFun [a] [Nat] -> Type) (a6989586621679978591 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndicesSym1 a6989586621679978590 :: TyFun [a] [Nat] -> Type) (a6989586621679978591 :: [a]) = FindIndices a6989586621679978590 a6989586621679978591 |
type FindIndicesSym2 (a6989586621679978590 :: (~>) a6989586621679974088 Bool) (a6989586621679978591 :: [a6989586621679974088]) = FindIndices a6989586621679978590 a6989586621679978591 Source #
data ZipSym0 :: forall a6989586621679974139 b6989586621679974140. (~>) [a6989586621679974139] ((~>) [b6989586621679974140] [(a6989586621679974139, b6989586621679974140)]) Source #
Instances
SingI (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # | |
SuppressUnusedWarnings (ZipSym0 :: TyFun [a6989586621679974139] ([b6989586621679974140] ~> [(a6989586621679974139, b6989586621679974140)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym0 :: TyFun [a6989586621679974139] ([b6989586621679974140] ~> [(a6989586621679974139, b6989586621679974140)]) -> Type) (a6989586621679979003 :: [a6989586621679974139]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipSym0 :: TyFun [a6989586621679974139] ([b6989586621679974140] ~> [(a6989586621679974139, b6989586621679974140)]) -> Type) (a6989586621679979003 :: [a6989586621679974139]) = ZipSym1 a6989586621679979003 b6989586621679974140 :: TyFun [b6989586621679974140] [(a6989586621679974139, b6989586621679974140)] -> Type |
data ZipSym1 (a6989586621679979003 :: [a6989586621679974139]) :: forall b6989586621679974140. (~>) [b6989586621679974140] [(a6989586621679974139, b6989586621679974140)] Source #
Instances
SingI d => SingI (ZipSym1 d b :: TyFun [b] [(a, b)] -> Type) Source # | |
SuppressUnusedWarnings (ZipSym1 a6989586621679979003 b6989586621679974140 :: TyFun [b6989586621679974140] [(a6989586621679974139, b6989586621679974140)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym1 a6989586621679979003 b :: TyFun [b] [(a, b)] -> Type) (a6989586621679979004 :: [b]) Source # | |
type ZipSym2 (a6989586621679979003 :: [a6989586621679974139]) (a6989586621679979004 :: [b6989586621679974140]) = Zip a6989586621679979003 a6989586621679979004 Source #
data Zip3Sym0 :: forall a6989586621679974136 b6989586621679974137 c6989586621679974138. (~>) [a6989586621679974136] ((~>) [b6989586621679974137] ((~>) [c6989586621679974138] [(a6989586621679974136, b6989586621679974137, c6989586621679974138)])) Source #
Instances
SingI (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a6989586621679974136] ([b6989586621679974137] ~> ([c6989586621679974138] ~> [(a6989586621679974136, b6989586621679974137, c6989586621679974138)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym0 :: TyFun [a6989586621679974136] ([b6989586621679974137] ~> ([c6989586621679974138] ~> [(a6989586621679974136, b6989586621679974137, c6989586621679974138)])) -> Type) (a6989586621679978991 :: [a6989586621679974136]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip3Sym0 :: TyFun [a6989586621679974136] ([b6989586621679974137] ~> ([c6989586621679974138] ~> [(a6989586621679974136, b6989586621679974137, c6989586621679974138)])) -> Type) (a6989586621679978991 :: [a6989586621679974136]) = Zip3Sym1 a6989586621679978991 b6989586621679974137 c6989586621679974138 :: TyFun [b6989586621679974137] ([c6989586621679974138] ~> [(a6989586621679974136, b6989586621679974137, c6989586621679974138)]) -> Type |
data Zip3Sym1 (a6989586621679978991 :: [a6989586621679974136]) :: forall b6989586621679974137 c6989586621679974138. (~>) [b6989586621679974137] ((~>) [c6989586621679974138] [(a6989586621679974136, b6989586621679974137, c6989586621679974138)]) Source #
Instances
SingI d => SingI (Zip3Sym1 d b c :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym1 a6989586621679978991 b6989586621679974137 c6989586621679974138 :: TyFun [b6989586621679974137] ([c6989586621679974138] ~> [(a6989586621679974136, b6989586621679974137, c6989586621679974138)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym1 a6989586621679978991 b6989586621679974137 c6989586621679974138 :: TyFun [b6989586621679974137] ([c6989586621679974138] ~> [(a6989586621679974136, b6989586621679974137, c6989586621679974138)]) -> Type) (a6989586621679978992 :: [b6989586621679974137]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip3Sym1 a6989586621679978991 b6989586621679974137 c6989586621679974138 :: TyFun [b6989586621679974137] ([c6989586621679974138] ~> [(a6989586621679974136, b6989586621679974137, c6989586621679974138)]) -> Type) (a6989586621679978992 :: [b6989586621679974137]) = Zip3Sym2 a6989586621679978991 a6989586621679978992 c6989586621679974138 :: TyFun [c6989586621679974138] [(a6989586621679974136, b6989586621679974137, c6989586621679974138)] -> Type |
data Zip3Sym2 (a6989586621679978991 :: [a6989586621679974136]) (a6989586621679978992 :: [b6989586621679974137]) :: forall c6989586621679974138. (~>) [c6989586621679974138] [(a6989586621679974136, b6989586621679974137, c6989586621679974138)] Source #
Instances
(SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 c :: TyFun [c] [(a, b, c)] -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym2 a6989586621679978992 a6989586621679978991 c6989586621679974138 :: TyFun [c6989586621679974138] [(a6989586621679974136, b6989586621679974137, c6989586621679974138)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym2 a6989586621679978992 a6989586621679978991 c :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679978993 :: [c]) Source # | |
type Zip3Sym3 (a6989586621679978991 :: [a6989586621679974136]) (a6989586621679978992 :: [b6989586621679974137]) (a6989586621679978993 :: [c6989586621679974138]) = Zip3 a6989586621679978991 a6989586621679978992 a6989586621679978993 Source #
data Zip4Sym0 :: forall a6989586621680096267 b6989586621680096268 c6989586621680096269 d6989586621680096270. (~>) [a6989586621680096267] ((~>) [b6989586621680096268] ((~>) [c6989586621680096269] ((~>) [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]))) Source #
Instances
SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a6989586621680096267] ([b6989586621680096268] ~> ([c6989586621680096269] ~> ([d6989586621680096270] ~> [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym0 :: TyFun [a6989586621680096267] ([b6989586621680096268] ~> ([c6989586621680096269] ~> ([d6989586621680096270] ~> [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]))) -> Type) (a6989586621680097955 :: [a6989586621680096267]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym0 :: TyFun [a6989586621680096267] ([b6989586621680096268] ~> ([c6989586621680096269] ~> ([d6989586621680096270] ~> [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]))) -> Type) (a6989586621680097955 :: [a6989586621680096267]) = Zip4Sym1 a6989586621680097955 b6989586621680096268 c6989586621680096269 d6989586621680096270 :: TyFun [b6989586621680096268] ([c6989586621680096269] ~> ([d6989586621680096270] ~> [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)])) -> Type |
data Zip4Sym1 (a6989586621680097955 :: [a6989586621680096267]) :: forall b6989586621680096268 c6989586621680096269 d6989586621680096270. (~>) [b6989586621680096268] ((~>) [c6989586621680096269] ((~>) [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)])) Source #
Instances
SuppressUnusedWarnings (Zip4Sym1 a6989586621680097955 b6989586621680096268 c6989586621680096269 d6989586621680096270 :: TyFun [b6989586621680096268] ([c6989586621680096269] ~> ([d6989586621680096270] ~> [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym1 a6989586621680097955 b6989586621680096268 c6989586621680096269 d6989586621680096270 :: TyFun [b6989586621680096268] ([c6989586621680096269] ~> ([d6989586621680096270] ~> [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)])) -> Type) (a6989586621680097956 :: [b6989586621680096268]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym1 a6989586621680097955 b6989586621680096268 c6989586621680096269 d6989586621680096270 :: TyFun [b6989586621680096268] ([c6989586621680096269] ~> ([d6989586621680096270] ~> [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)])) -> Type) (a6989586621680097956 :: [b6989586621680096268]) = Zip4Sym2 a6989586621680097955 a6989586621680097956 c6989586621680096269 d6989586621680096270 :: TyFun [c6989586621680096269] ([d6989586621680096270] ~> [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]) -> Type |
data Zip4Sym2 (a6989586621680097955 :: [a6989586621680096267]) (a6989586621680097956 :: [b6989586621680096268]) :: forall c6989586621680096269 d6989586621680096270. (~>) [c6989586621680096269] ((~>) [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]) Source #
Instances
SuppressUnusedWarnings (Zip4Sym2 a6989586621680097956 a6989586621680097955 c6989586621680096269 d6989586621680096270 :: TyFun [c6989586621680096269] ([d6989586621680096270] ~> [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym2 a6989586621680097956 a6989586621680097955 c6989586621680096269 d6989586621680096270 :: TyFun [c6989586621680096269] ([d6989586621680096270] ~> [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]) -> Type) (a6989586621680097957 :: [c6989586621680096269]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym2 a6989586621680097956 a6989586621680097955 c6989586621680096269 d6989586621680096270 :: TyFun [c6989586621680096269] ([d6989586621680096270] ~> [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]) -> Type) (a6989586621680097957 :: [c6989586621680096269]) = Zip4Sym3 a6989586621680097956 a6989586621680097955 a6989586621680097957 d6989586621680096270 :: TyFun [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)] -> Type |
data Zip4Sym3 (a6989586621680097955 :: [a6989586621680096267]) (a6989586621680097956 :: [b6989586621680096268]) (a6989586621680097957 :: [c6989586621680096269]) :: forall d6989586621680096270. (~>) [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)] Source #
Instances
SuppressUnusedWarnings (Zip4Sym3 a6989586621680097957 a6989586621680097956 a6989586621680097955 d6989586621680096270 :: TyFun [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym3 a6989586621680097957 a6989586621680097956 a6989586621680097955 d :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621680097958 :: [d]) Source # | |
type Zip4Sym4 (a6989586621680097955 :: [a6989586621680096267]) (a6989586621680097956 :: [b6989586621680096268]) (a6989586621680097957 :: [c6989586621680096269]) (a6989586621680097958 :: [d6989586621680096270]) = Zip4 a6989586621680097955 a6989586621680097956 a6989586621680097957 a6989586621680097958 Source #
data Zip5Sym0 :: forall a6989586621680096262 b6989586621680096263 c6989586621680096264 d6989586621680096265 e6989586621680096266. (~>) [a6989586621680096262] ((~>) [b6989586621680096263] ((~>) [c6989586621680096264] ((~>) [d6989586621680096265] ((~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])))) Source #
Instances
SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a6989586621680096262] ([b6989586621680096263] ~> ([c6989586621680096264] ~> ([d6989586621680096265] ~> ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym0 :: TyFun [a6989586621680096262] ([b6989586621680096263] ~> ([c6989586621680096264] ~> ([d6989586621680096265] ~> ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])))) -> Type) (a6989586621680097932 :: [a6989586621680096262]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym0 :: TyFun [a6989586621680096262] ([b6989586621680096263] ~> ([c6989586621680096264] ~> ([d6989586621680096265] ~> ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])))) -> Type) (a6989586621680097932 :: [a6989586621680096262]) = Zip5Sym1 a6989586621680097932 b6989586621680096263 c6989586621680096264 d6989586621680096265 e6989586621680096266 :: TyFun [b6989586621680096263] ([c6989586621680096264] ~> ([d6989586621680096265] ~> ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]))) -> Type |
data Zip5Sym1 (a6989586621680097932 :: [a6989586621680096262]) :: forall b6989586621680096263 c6989586621680096264 d6989586621680096265 e6989586621680096266. (~>) [b6989586621680096263] ((~>) [c6989586621680096264] ((~>) [d6989586621680096265] ((~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]))) Source #
Instances
SuppressUnusedWarnings (Zip5Sym1 a6989586621680097932 b6989586621680096263 c6989586621680096264 d6989586621680096265 e6989586621680096266 :: TyFun [b6989586621680096263] ([c6989586621680096264] ~> ([d6989586621680096265] ~> ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym1 a6989586621680097932 b6989586621680096263 c6989586621680096264 d6989586621680096265 e6989586621680096266 :: TyFun [b6989586621680096263] ([c6989586621680096264] ~> ([d6989586621680096265] ~> ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]))) -> Type) (a6989586621680097933 :: [b6989586621680096263]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym1 a6989586621680097932 b6989586621680096263 c6989586621680096264 d6989586621680096265 e6989586621680096266 :: TyFun [b6989586621680096263] ([c6989586621680096264] ~> ([d6989586621680096265] ~> ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]))) -> Type) (a6989586621680097933 :: [b6989586621680096263]) = Zip5Sym2 a6989586621680097932 a6989586621680097933 c6989586621680096264 d6989586621680096265 e6989586621680096266 :: TyFun [c6989586621680096264] ([d6989586621680096265] ~> ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])) -> Type |
data Zip5Sym2 (a6989586621680097932 :: [a6989586621680096262]) (a6989586621680097933 :: [b6989586621680096263]) :: forall c6989586621680096264 d6989586621680096265 e6989586621680096266. (~>) [c6989586621680096264] ((~>) [d6989586621680096265] ((~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])) Source #
Instances
SuppressUnusedWarnings (Zip5Sym2 a6989586621680097933 a6989586621680097932 c6989586621680096264 d6989586621680096265 e6989586621680096266 :: TyFun [c6989586621680096264] ([d6989586621680096265] ~> ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym2 a6989586621680097933 a6989586621680097932 c6989586621680096264 d6989586621680096265 e6989586621680096266 :: TyFun [c6989586621680096264] ([d6989586621680096265] ~> ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])) -> Type) (a6989586621680097934 :: [c6989586621680096264]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym2 a6989586621680097933 a6989586621680097932 c6989586621680096264 d6989586621680096265 e6989586621680096266 :: TyFun [c6989586621680096264] ([d6989586621680096265] ~> ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])) -> Type) (a6989586621680097934 :: [c6989586621680096264]) = Zip5Sym3 a6989586621680097933 a6989586621680097932 a6989586621680097934 d6989586621680096265 e6989586621680096266 :: TyFun [d6989586621680096265] ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]) -> Type |
data Zip5Sym3 (a6989586621680097932 :: [a6989586621680096262]) (a6989586621680097933 :: [b6989586621680096263]) (a6989586621680097934 :: [c6989586621680096264]) :: forall d6989586621680096265 e6989586621680096266. (~>) [d6989586621680096265] ((~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]) Source #
Instances
SuppressUnusedWarnings (Zip5Sym3 a6989586621680097934 a6989586621680097933 a6989586621680097932 d6989586621680096265 e6989586621680096266 :: TyFun [d6989586621680096265] ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym3 a6989586621680097934 a6989586621680097933 a6989586621680097932 d6989586621680096265 e6989586621680096266 :: TyFun [d6989586621680096265] ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]) -> Type) (a6989586621680097935 :: [d6989586621680096265]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym3 a6989586621680097934 a6989586621680097933 a6989586621680097932 d6989586621680096265 e6989586621680096266 :: TyFun [d6989586621680096265] ([e6989586621680096266] ~> [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]) -> Type) (a6989586621680097935 :: [d6989586621680096265]) = Zip5Sym4 a6989586621680097934 a6989586621680097933 a6989586621680097932 a6989586621680097935 e6989586621680096266 :: TyFun [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)] -> Type |
data Zip5Sym4 (a6989586621680097932 :: [a6989586621680096262]) (a6989586621680097933 :: [b6989586621680096263]) (a6989586621680097934 :: [c6989586621680096264]) (a6989586621680097935 :: [d6989586621680096265]) :: forall e6989586621680096266. (~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)] Source #
Instances
SuppressUnusedWarnings (Zip5Sym4 a6989586621680097935 a6989586621680097934 a6989586621680097933 a6989586621680097932 e6989586621680096266 :: TyFun [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym4 a6989586621680097935 a6989586621680097934 a6989586621680097933 a6989586621680097932 e :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621680097936 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type Zip5Sym5 (a6989586621680097932 :: [a6989586621680096262]) (a6989586621680097933 :: [b6989586621680096263]) (a6989586621680097934 :: [c6989586621680096264]) (a6989586621680097935 :: [d6989586621680096265]) (a6989586621680097936 :: [e6989586621680096266]) = Zip5 a6989586621680097932 a6989586621680097933 a6989586621680097934 a6989586621680097935 a6989586621680097936 Source #
data Zip6Sym0 :: forall a6989586621680096256 b6989586621680096257 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261. (~>) [a6989586621680096256] ((~>) [b6989586621680096257] ((~>) [c6989586621680096258] ((~>) [d6989586621680096259] ((~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a6989586621680096256] ([b6989586621680096257] ~> ([c6989586621680096258] ~> ([d6989586621680096259] ~> ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym0 :: TyFun [a6989586621680096256] ([b6989586621680096257] ~> ([c6989586621680096258] ~> ([d6989586621680096259] ~> ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))))) -> Type) (a6989586621680097904 :: [a6989586621680096256]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym0 :: TyFun [a6989586621680096256] ([b6989586621680096257] ~> ([c6989586621680096258] ~> ([d6989586621680096259] ~> ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))))) -> Type) (a6989586621680097904 :: [a6989586621680096256]) = Zip6Sym1 a6989586621680097904 b6989586621680096257 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261 :: TyFun [b6989586621680096257] ([c6989586621680096258] ~> ([d6989586621680096259] ~> ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])))) -> Type |
data Zip6Sym1 (a6989586621680097904 :: [a6989586621680096256]) :: forall b6989586621680096257 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261. (~>) [b6989586621680096257] ((~>) [c6989586621680096258] ((~>) [d6989586621680096259] ((~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym1 a6989586621680097904 b6989586621680096257 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261 :: TyFun [b6989586621680096257] ([c6989586621680096258] ~> ([d6989586621680096259] ~> ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym1 a6989586621680097904 b6989586621680096257 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261 :: TyFun [b6989586621680096257] ([c6989586621680096258] ~> ([d6989586621680096259] ~> ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])))) -> Type) (a6989586621680097905 :: [b6989586621680096257]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym1 a6989586621680097904 b6989586621680096257 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261 :: TyFun [b6989586621680096257] ([c6989586621680096258] ~> ([d6989586621680096259] ~> ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])))) -> Type) (a6989586621680097905 :: [b6989586621680096257]) = Zip6Sym2 a6989586621680097904 a6989586621680097905 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261 :: TyFun [c6989586621680096258] ([d6989586621680096259] ~> ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))) -> Type |
data Zip6Sym2 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) :: forall c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261. (~>) [c6989586621680096258] ((~>) [d6989586621680096259] ((~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym2 a6989586621680097905 a6989586621680097904 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261 :: TyFun [c6989586621680096258] ([d6989586621680096259] ~> ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym2 a6989586621680097905 a6989586621680097904 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261 :: TyFun [c6989586621680096258] ([d6989586621680096259] ~> ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))) -> Type) (a6989586621680097906 :: [c6989586621680096258]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym2 a6989586621680097905 a6989586621680097904 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261 :: TyFun [c6989586621680096258] ([d6989586621680096259] ~> ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))) -> Type) (a6989586621680097906 :: [c6989586621680096258]) = Zip6Sym3 a6989586621680097905 a6989586621680097904 a6989586621680097906 d6989586621680096259 e6989586621680096260 f6989586621680096261 :: TyFun [d6989586621680096259] ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])) -> Type |
data Zip6Sym3 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) (a6989586621680097906 :: [c6989586621680096258]) :: forall d6989586621680096259 e6989586621680096260 f6989586621680096261. (~>) [d6989586621680096259] ((~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])) Source #
Instances
SuppressUnusedWarnings (Zip6Sym3 a6989586621680097906 a6989586621680097905 a6989586621680097904 d6989586621680096259 e6989586621680096260 f6989586621680096261 :: TyFun [d6989586621680096259] ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym3 a6989586621680097906 a6989586621680097905 a6989586621680097904 d6989586621680096259 e6989586621680096260 f6989586621680096261 :: TyFun [d6989586621680096259] ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])) -> Type) (a6989586621680097907 :: [d6989586621680096259]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym3 a6989586621680097906 a6989586621680097905 a6989586621680097904 d6989586621680096259 e6989586621680096260 f6989586621680096261 :: TyFun [d6989586621680096259] ([e6989586621680096260] ~> ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])) -> Type) (a6989586621680097907 :: [d6989586621680096259]) = Zip6Sym4 a6989586621680097906 a6989586621680097905 a6989586621680097904 a6989586621680097907 e6989586621680096260 f6989586621680096261 :: TyFun [e6989586621680096260] ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]) -> Type |
data Zip6Sym4 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) (a6989586621680097906 :: [c6989586621680096258]) (a6989586621680097907 :: [d6989586621680096259]) :: forall e6989586621680096260 f6989586621680096261. (~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]) Source #
Instances
SuppressUnusedWarnings (Zip6Sym4 a6989586621680097907 a6989586621680097906 a6989586621680097905 a6989586621680097904 e6989586621680096260 f6989586621680096261 :: TyFun [e6989586621680096260] ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym4 a6989586621680097907 a6989586621680097906 a6989586621680097905 a6989586621680097904 e6989586621680096260 f6989586621680096261 :: TyFun [e6989586621680096260] ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]) -> Type) (a6989586621680097908 :: [e6989586621680096260]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym4 a6989586621680097907 a6989586621680097906 a6989586621680097905 a6989586621680097904 e6989586621680096260 f6989586621680096261 :: TyFun [e6989586621680096260] ([f6989586621680096261] ~> [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]) -> Type) (a6989586621680097908 :: [e6989586621680096260]) = Zip6Sym5 a6989586621680097907 a6989586621680097906 a6989586621680097905 a6989586621680097904 a6989586621680097908 f6989586621680096261 :: TyFun [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)] -> Type |
data Zip6Sym5 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) (a6989586621680097906 :: [c6989586621680096258]) (a6989586621680097907 :: [d6989586621680096259]) (a6989586621680097908 :: [e6989586621680096260]) :: forall f6989586621680096261. (~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)] Source #
Instances
SuppressUnusedWarnings (Zip6Sym5 a6989586621680097908 a6989586621680097907 a6989586621680097906 a6989586621680097905 a6989586621680097904 f6989586621680096261 :: TyFun [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym5 a6989586621680097908 a6989586621680097907 a6989586621680097906 a6989586621680097905 a6989586621680097904 f :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680097909 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym5 a6989586621680097908 a6989586621680097907 a6989586621680097906 a6989586621680097905 a6989586621680097904 f :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680097909 :: [f]) = Zip6 a6989586621680097908 a6989586621680097907 a6989586621680097906 a6989586621680097905 a6989586621680097904 a6989586621680097909 |
type Zip6Sym6 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) (a6989586621680097906 :: [c6989586621680096258]) (a6989586621680097907 :: [d6989586621680096259]) (a6989586621680097908 :: [e6989586621680096260]) (a6989586621680097909 :: [f6989586621680096261]) = Zip6 a6989586621680097904 a6989586621680097905 a6989586621680097906 a6989586621680097907 a6989586621680097908 a6989586621680097909 Source #
data Zip7Sym0 :: forall a6989586621680096249 b6989586621680096250 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [a6989586621680096249] ((~>) [b6989586621680096250] ((~>) [c6989586621680096251] ((~>) [d6989586621680096252] ((~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a6989586621680096249] ([b6989586621680096250] ~> ([c6989586621680096251] ~> ([d6989586621680096252] ~> ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym0 :: TyFun [a6989586621680096249] ([b6989586621680096250] ~> ([c6989586621680096251] ~> ([d6989586621680096252] ~> ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))))) -> Type) (a6989586621680097871 :: [a6989586621680096249]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym0 :: TyFun [a6989586621680096249] ([b6989586621680096250] ~> ([c6989586621680096251] ~> ([d6989586621680096252] ~> ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))))) -> Type) (a6989586621680097871 :: [a6989586621680096249]) = Zip7Sym1 a6989586621680097871 b6989586621680096250 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [b6989586621680096250] ([c6989586621680096251] ~> ([d6989586621680096252] ~> ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))))) -> Type |
data Zip7Sym1 (a6989586621680097871 :: [a6989586621680096249]) :: forall b6989586621680096250 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [b6989586621680096250] ((~>) [c6989586621680096251] ((~>) [d6989586621680096252] ((~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym1 a6989586621680097871 b6989586621680096250 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [b6989586621680096250] ([c6989586621680096251] ~> ([d6989586621680096252] ~> ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym1 a6989586621680097871 b6989586621680096250 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [b6989586621680096250] ([c6989586621680096251] ~> ([d6989586621680096252] ~> ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))))) -> Type) (a6989586621680097872 :: [b6989586621680096250]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym1 a6989586621680097871 b6989586621680096250 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [b6989586621680096250] ([c6989586621680096251] ~> ([d6989586621680096252] ~> ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))))) -> Type) (a6989586621680097872 :: [b6989586621680096250]) = Zip7Sym2 a6989586621680097871 a6989586621680097872 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [c6989586621680096251] ([d6989586621680096252] ~> ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))) -> Type |
data Zip7Sym2 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) :: forall c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [c6989586621680096251] ((~>) [d6989586621680096252] ((~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym2 a6989586621680097872 a6989586621680097871 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [c6989586621680096251] ([d6989586621680096252] ~> ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym2 a6989586621680097872 a6989586621680097871 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [c6989586621680096251] ([d6989586621680096252] ~> ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))) -> Type) (a6989586621680097873 :: [c6989586621680096251]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym2 a6989586621680097872 a6989586621680097871 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [c6989586621680096251] ([d6989586621680096252] ~> ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))) -> Type) (a6989586621680097873 :: [c6989586621680096251]) = Zip7Sym3 a6989586621680097872 a6989586621680097871 a6989586621680097873 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [d6989586621680096252] ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))) -> Type |
data Zip7Sym3 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) :: forall d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [d6989586621680096252] ((~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym3 a6989586621680097873 a6989586621680097872 a6989586621680097871 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [d6989586621680096252] ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym3 a6989586621680097873 a6989586621680097872 a6989586621680097871 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [d6989586621680096252] ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))) -> Type) (a6989586621680097874 :: [d6989586621680096252]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym3 a6989586621680097873 a6989586621680097872 a6989586621680097871 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [d6989586621680096252] ([e6989586621680096253] ~> ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))) -> Type) (a6989586621680097874 :: [d6989586621680096252]) = Zip7Sym4 a6989586621680097873 a6989586621680097872 a6989586621680097871 a6989586621680097874 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [e6989586621680096253] ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])) -> Type |
data Zip7Sym4 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) (a6989586621680097874 :: [d6989586621680096252]) :: forall e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])) Source #
Instances
SuppressUnusedWarnings (Zip7Sym4 a6989586621680097874 a6989586621680097873 a6989586621680097872 a6989586621680097871 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [e6989586621680096253] ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym4 a6989586621680097874 a6989586621680097873 a6989586621680097872 a6989586621680097871 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [e6989586621680096253] ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])) -> Type) (a6989586621680097875 :: [e6989586621680096253]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym4 a6989586621680097874 a6989586621680097873 a6989586621680097872 a6989586621680097871 e6989586621680096253 f6989586621680096254 g6989586621680096255 :: TyFun [e6989586621680096253] ([f6989586621680096254] ~> ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])) -> Type) (a6989586621680097875 :: [e6989586621680096253]) = Zip7Sym5 a6989586621680097874 a6989586621680097873 a6989586621680097872 a6989586621680097871 a6989586621680097875 f6989586621680096254 g6989586621680096255 :: TyFun [f6989586621680096254] ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]) -> Type |
data Zip7Sym5 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) (a6989586621680097874 :: [d6989586621680096252]) (a6989586621680097875 :: [e6989586621680096253]) :: forall f6989586621680096254 g6989586621680096255. (~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]) Source #
Instances
SuppressUnusedWarnings (Zip7Sym5 a6989586621680097875 a6989586621680097874 a6989586621680097873 a6989586621680097872 a6989586621680097871 f6989586621680096254 g6989586621680096255 :: TyFun [f6989586621680096254] ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym5 a6989586621680097875 a6989586621680097874 a6989586621680097873 a6989586621680097872 a6989586621680097871 f6989586621680096254 g6989586621680096255 :: TyFun [f6989586621680096254] ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]) -> Type) (a6989586621680097876 :: [f6989586621680096254]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym5 a6989586621680097875 a6989586621680097874 a6989586621680097873 a6989586621680097872 a6989586621680097871 f6989586621680096254 g6989586621680096255 :: TyFun [f6989586621680096254] ([g6989586621680096255] ~> [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]) -> Type) (a6989586621680097876 :: [f6989586621680096254]) = Zip7Sym6 a6989586621680097875 a6989586621680097874 a6989586621680097873 a6989586621680097872 a6989586621680097871 a6989586621680097876 g6989586621680096255 :: TyFun [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)] -> Type |
data Zip7Sym6 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) (a6989586621680097874 :: [d6989586621680096252]) (a6989586621680097875 :: [e6989586621680096253]) (a6989586621680097876 :: [f6989586621680096254]) :: forall g6989586621680096255. (~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)] Source #
Instances
SuppressUnusedWarnings (Zip7Sym6 a6989586621680097876 a6989586621680097875 a6989586621680097874 a6989586621680097873 a6989586621680097872 a6989586621680097871 g6989586621680096255 :: TyFun [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym6 a6989586621680097876 a6989586621680097875 a6989586621680097874 a6989586621680097873 a6989586621680097872 a6989586621680097871 g :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680097877 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym6 a6989586621680097876 a6989586621680097875 a6989586621680097874 a6989586621680097873 a6989586621680097872 a6989586621680097871 g :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680097877 :: [g]) = Zip7 a6989586621680097876 a6989586621680097875 a6989586621680097874 a6989586621680097873 a6989586621680097872 a6989586621680097871 a6989586621680097877 |
type Zip7Sym7 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) (a6989586621680097874 :: [d6989586621680096252]) (a6989586621680097875 :: [e6989586621680096253]) (a6989586621680097876 :: [f6989586621680096254]) (a6989586621680097877 :: [g6989586621680096255]) = Zip7 a6989586621680097871 a6989586621680097872 a6989586621680097873 a6989586621680097874 a6989586621680097875 a6989586621680097876 a6989586621680097877 Source #
data ZipWithSym0 :: forall a6989586621679974133 b6989586621679974134 c6989586621679974135. (~>) ((~>) a6989586621679974133 ((~>) b6989586621679974134 c6989586621679974135)) ((~>) [a6989586621679974133] ((~>) [b6989586621679974134] [c6989586621679974135])) Source #
Instances
SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing ZipWithSym0 Source # | |
SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a6989586621679974133 ~> (b6989586621679974134 ~> c6989586621679974135)) ([a6989586621679974133] ~> ([b6989586621679974134] ~> [c6989586621679974135])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym0 :: TyFun (a6989586621679974133 ~> (b6989586621679974134 ~> c6989586621679974135)) ([a6989586621679974133] ~> ([b6989586621679974134] ~> [c6989586621679974135])) -> Type) (a6989586621679978980 :: a6989586621679974133 ~> (b6989586621679974134 ~> c6989586621679974135)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym0 :: TyFun (a6989586621679974133 ~> (b6989586621679974134 ~> c6989586621679974135)) ([a6989586621679974133] ~> ([b6989586621679974134] ~> [c6989586621679974135])) -> Type) (a6989586621679978980 :: a6989586621679974133 ~> (b6989586621679974134 ~> c6989586621679974135)) = ZipWithSym1 a6989586621679978980 |
data ZipWithSym1 (a6989586621679978980 :: (~>) a6989586621679974133 ((~>) b6989586621679974134 c6989586621679974135)) :: (~>) [a6989586621679974133] ((~>) [b6989586621679974134] [c6989586621679974135]) Source #
Instances
SingI d => SingI (ZipWithSym1 d :: TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ZipWithSym1 d) Source # | |
SuppressUnusedWarnings (ZipWithSym1 a6989586621679978980 :: TyFun [a6989586621679974133] ([b6989586621679974134] ~> [c6989586621679974135]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym1 a6989586621679978980 :: TyFun [a6989586621679974133] ([b6989586621679974134] ~> [c6989586621679974135]) -> Type) (a6989586621679978981 :: [a6989586621679974133]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym1 a6989586621679978980 :: TyFun [a6989586621679974133] ([b6989586621679974134] ~> [c6989586621679974135]) -> Type) (a6989586621679978981 :: [a6989586621679974133]) = ZipWithSym2 a6989586621679978980 a6989586621679978981 |
data ZipWithSym2 (a6989586621679978980 :: (~>) a6989586621679974133 ((~>) b6989586621679974134 c6989586621679974135)) (a6989586621679978981 :: [a6989586621679974133]) :: (~>) [b6989586621679974134] [c6989586621679974135] Source #
Instances
(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun [b] [c] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ZipWithSym2 d1 d2) Source # | |
SuppressUnusedWarnings (ZipWithSym2 a6989586621679978981 a6989586621679978980 :: TyFun [b6989586621679974134] [c6989586621679974135] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym2 a6989586621679978981 a6989586621679978980 :: TyFun [b] [c] -> Type) (a6989586621679978982 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym2 a6989586621679978981 a6989586621679978980 :: TyFun [b] [c] -> Type) (a6989586621679978982 :: [b]) = ZipWith a6989586621679978981 a6989586621679978980 a6989586621679978982 |
type ZipWithSym3 (a6989586621679978980 :: (~>) a6989586621679974133 ((~>) b6989586621679974134 c6989586621679974135)) (a6989586621679978981 :: [a6989586621679974133]) (a6989586621679978982 :: [b6989586621679974134]) = ZipWith a6989586621679978980 a6989586621679978981 a6989586621679978982 Source #
data ZipWith3Sym0 :: forall a6989586621679974129 b6989586621679974130 c6989586621679974131 d6989586621679974132. (~>) ((~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) ((~>) [a6989586621679974129] ((~>) [b6989586621679974130] ((~>) [c6989586621679974131] [d6989586621679974132]))) Source #
Instances
SingI (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing ZipWith3Sym0 Source # | |
SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (a6989586621679974129 ~> (b6989586621679974130 ~> (c6989586621679974131 ~> d6989586621679974132))) ([a6989586621679974129] ~> ([b6989586621679974130] ~> ([c6989586621679974131] ~> [d6989586621679974132]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym0 :: TyFun (a6989586621679974129 ~> (b6989586621679974130 ~> (c6989586621679974131 ~> d6989586621679974132))) ([a6989586621679974129] ~> ([b6989586621679974130] ~> ([c6989586621679974131] ~> [d6989586621679974132]))) -> Type) (a6989586621679978965 :: a6989586621679974129 ~> (b6989586621679974130 ~> (c6989586621679974131 ~> d6989586621679974132))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym0 :: TyFun (a6989586621679974129 ~> (b6989586621679974130 ~> (c6989586621679974131 ~> d6989586621679974132))) ([a6989586621679974129] ~> ([b6989586621679974130] ~> ([c6989586621679974131] ~> [d6989586621679974132]))) -> Type) (a6989586621679978965 :: a6989586621679974129 ~> (b6989586621679974130 ~> (c6989586621679974131 ~> d6989586621679974132))) = ZipWith3Sym1 a6989586621679978965 |
data ZipWith3Sym1 (a6989586621679978965 :: (~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) :: (~>) [a6989586621679974129] ((~>) [b6989586621679974130] ((~>) [c6989586621679974131] [d6989586621679974132])) Source #
Instances
SingI d2 => SingI (ZipWith3Sym1 d2 :: TyFun [a] ([b] ~> ([c] ~> [d1])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ZipWith3Sym1 d2) Source # | |
SuppressUnusedWarnings (ZipWith3Sym1 a6989586621679978965 :: TyFun [a6989586621679974129] ([b6989586621679974130] ~> ([c6989586621679974131] ~> [d6989586621679974132])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym1 a6989586621679978965 :: TyFun [a6989586621679974129] ([b6989586621679974130] ~> ([c6989586621679974131] ~> [d6989586621679974132])) -> Type) (a6989586621679978966 :: [a6989586621679974129]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym1 a6989586621679978965 :: TyFun [a6989586621679974129] ([b6989586621679974130] ~> ([c6989586621679974131] ~> [d6989586621679974132])) -> Type) (a6989586621679978966 :: [a6989586621679974129]) = ZipWith3Sym2 a6989586621679978965 a6989586621679978966 |
data ZipWith3Sym2 (a6989586621679978965 :: (~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) (a6989586621679978966 :: [a6989586621679974129]) :: (~>) [b6989586621679974130] ((~>) [c6989586621679974131] [d6989586621679974132]) Source #
Instances
(SingI d2, SingI d3) => SingI (ZipWith3Sym2 d2 d3 :: TyFun [b] ([c] ~> [d1]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ZipWith3Sym2 d2 d3) Source # | |
SuppressUnusedWarnings (ZipWith3Sym2 a6989586621679978966 a6989586621679978965 :: TyFun [b6989586621679974130] ([c6989586621679974131] ~> [d6989586621679974132]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym2 a6989586621679978966 a6989586621679978965 :: TyFun [b6989586621679974130] ([c6989586621679974131] ~> [d6989586621679974132]) -> Type) (a6989586621679978967 :: [b6989586621679974130]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym2 a6989586621679978966 a6989586621679978965 :: TyFun [b6989586621679974130] ([c6989586621679974131] ~> [d6989586621679974132]) -> Type) (a6989586621679978967 :: [b6989586621679974130]) = ZipWith3Sym3 a6989586621679978966 a6989586621679978965 a6989586621679978967 |
data ZipWith3Sym3 (a6989586621679978965 :: (~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) (a6989586621679978966 :: [a6989586621679974129]) (a6989586621679978967 :: [b6989586621679974130]) :: (~>) [c6989586621679974131] [d6989586621679974132] Source #
Instances
(SingI d2, SingI d3, SingI d4) => SingI (ZipWith3Sym3 d2 d3 d4 :: TyFun [c] [d1] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (ZipWith3Sym3 d2 d3 d4) Source # | |
SuppressUnusedWarnings (ZipWith3Sym3 a6989586621679978967 a6989586621679978966 a6989586621679978965 :: TyFun [c6989586621679974131] [d6989586621679974132] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym3 a6989586621679978967 a6989586621679978966 a6989586621679978965 :: TyFun [c] [d] -> Type) (a6989586621679978968 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym3 a6989586621679978967 a6989586621679978966 a6989586621679978965 :: TyFun [c] [d] -> Type) (a6989586621679978968 :: [c]) = ZipWith3 a6989586621679978967 a6989586621679978966 a6989586621679978965 a6989586621679978968 |
type ZipWith3Sym4 (a6989586621679978965 :: (~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) (a6989586621679978966 :: [a6989586621679974129]) (a6989586621679978967 :: [b6989586621679974130]) (a6989586621679978968 :: [c6989586621679974131]) = ZipWith3 a6989586621679978965 a6989586621679978966 a6989586621679978967 a6989586621679978968 Source #
data ZipWith4Sym0 :: forall a6989586621680096244 b6989586621680096245 c6989586621680096246 d6989586621680096247 e6989586621680096248. (~>) ((~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) ((~>) [a6989586621680096244] ((~>) [b6989586621680096245] ((~>) [c6989586621680096246] ((~>) [d6989586621680096247] [e6989586621680096248])))) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (a6989586621680096244 ~> (b6989586621680096245 ~> (c6989586621680096246 ~> (d6989586621680096247 ~> e6989586621680096248)))) ([a6989586621680096244] ~> ([b6989586621680096245] ~> ([c6989586621680096246] ~> ([d6989586621680096247] ~> [e6989586621680096248])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym0 :: TyFun (a6989586621680096244 ~> (b6989586621680096245 ~> (c6989586621680096246 ~> (d6989586621680096247 ~> e6989586621680096248)))) ([a6989586621680096244] ~> ([b6989586621680096245] ~> ([c6989586621680096246] ~> ([d6989586621680096247] ~> [e6989586621680096248])))) -> Type) (a6989586621680097838 :: a6989586621680096244 ~> (b6989586621680096245 ~> (c6989586621680096246 ~> (d6989586621680096247 ~> e6989586621680096248)))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym0 :: TyFun (a6989586621680096244 ~> (b6989586621680096245 ~> (c6989586621680096246 ~> (d6989586621680096247 ~> e6989586621680096248)))) ([a6989586621680096244] ~> ([b6989586621680096245] ~> ([c6989586621680096246] ~> ([d6989586621680096247] ~> [e6989586621680096248])))) -> Type) (a6989586621680097838 :: a6989586621680096244 ~> (b6989586621680096245 ~> (c6989586621680096246 ~> (d6989586621680096247 ~> e6989586621680096248)))) = ZipWith4Sym1 a6989586621680097838 |
data ZipWith4Sym1 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) :: (~>) [a6989586621680096244] ((~>) [b6989586621680096245] ((~>) [c6989586621680096246] ((~>) [d6989586621680096247] [e6989586621680096248]))) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym1 a6989586621680097838 :: TyFun [a6989586621680096244] ([b6989586621680096245] ~> ([c6989586621680096246] ~> ([d6989586621680096247] ~> [e6989586621680096248]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym1 a6989586621680097838 :: TyFun [a6989586621680096244] ([b6989586621680096245] ~> ([c6989586621680096246] ~> ([d6989586621680096247] ~> [e6989586621680096248]))) -> Type) (a6989586621680097839 :: [a6989586621680096244]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym1 a6989586621680097838 :: TyFun [a6989586621680096244] ([b6989586621680096245] ~> ([c6989586621680096246] ~> ([d6989586621680096247] ~> [e6989586621680096248]))) -> Type) (a6989586621680097839 :: [a6989586621680096244]) = ZipWith4Sym2 a6989586621680097838 a6989586621680097839 |
data ZipWith4Sym2 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) (a6989586621680097839 :: [a6989586621680096244]) :: (~>) [b6989586621680096245] ((~>) [c6989586621680096246] ((~>) [d6989586621680096247] [e6989586621680096248])) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym2 a6989586621680097839 a6989586621680097838 :: TyFun [b6989586621680096245] ([c6989586621680096246] ~> ([d6989586621680096247] ~> [e6989586621680096248])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym2 a6989586621680097839 a6989586621680097838 :: TyFun [b6989586621680096245] ([c6989586621680096246] ~> ([d6989586621680096247] ~> [e6989586621680096248])) -> Type) (a6989586621680097840 :: [b6989586621680096245]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym2 a6989586621680097839 a6989586621680097838 :: TyFun [b6989586621680096245] ([c6989586621680096246] ~> ([d6989586621680096247] ~> [e6989586621680096248])) -> Type) (a6989586621680097840 :: [b6989586621680096245]) = ZipWith4Sym3 a6989586621680097839 a6989586621680097838 a6989586621680097840 |
data ZipWith4Sym3 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) (a6989586621680097839 :: [a6989586621680096244]) (a6989586621680097840 :: [b6989586621680096245]) :: (~>) [c6989586621680096246] ((~>) [d6989586621680096247] [e6989586621680096248]) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym3 a6989586621680097840 a6989586621680097839 a6989586621680097838 :: TyFun [c6989586621680096246] ([d6989586621680096247] ~> [e6989586621680096248]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym3 a6989586621680097840 a6989586621680097839 a6989586621680097838 :: TyFun [c6989586621680096246] ([d6989586621680096247] ~> [e6989586621680096248]) -> Type) (a6989586621680097841 :: [c6989586621680096246]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym3 a6989586621680097840 a6989586621680097839 a6989586621680097838 :: TyFun [c6989586621680096246] ([d6989586621680096247] ~> [e6989586621680096248]) -> Type) (a6989586621680097841 :: [c6989586621680096246]) = ZipWith4Sym4 a6989586621680097840 a6989586621680097839 a6989586621680097838 a6989586621680097841 |
data ZipWith4Sym4 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) (a6989586621680097839 :: [a6989586621680096244]) (a6989586621680097840 :: [b6989586621680096245]) (a6989586621680097841 :: [c6989586621680096246]) :: (~>) [d6989586621680096247] [e6989586621680096248] Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym4 a6989586621680097841 a6989586621680097840 a6989586621680097839 a6989586621680097838 :: TyFun [d6989586621680096247] [e6989586621680096248] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym4 a6989586621680097841 a6989586621680097840 a6989586621680097839 a6989586621680097838 :: TyFun [d] [e] -> Type) (a6989586621680097842 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym4 a6989586621680097841 a6989586621680097840 a6989586621680097839 a6989586621680097838 :: TyFun [d] [e] -> Type) (a6989586621680097842 :: [d]) = ZipWith4 a6989586621680097841 a6989586621680097840 a6989586621680097839 a6989586621680097838 a6989586621680097842 |
type ZipWith4Sym5 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) (a6989586621680097839 :: [a6989586621680096244]) (a6989586621680097840 :: [b6989586621680096245]) (a6989586621680097841 :: [c6989586621680096246]) (a6989586621680097842 :: [d6989586621680096247]) = ZipWith4 a6989586621680097838 a6989586621680097839 a6989586621680097840 a6989586621680097841 a6989586621680097842 Source #
data ZipWith5Sym0 :: forall a6989586621680096238 b6989586621680096239 c6989586621680096240 d6989586621680096241 e6989586621680096242 f6989586621680096243. (~>) ((~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) ((~>) [a6989586621680096238] ((~>) [b6989586621680096239] ((~>) [c6989586621680096240] ((~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (a6989586621680096238 ~> (b6989586621680096239 ~> (c6989586621680096240 ~> (d6989586621680096241 ~> (e6989586621680096242 ~> f6989586621680096243))))) ([a6989586621680096238] ~> ([b6989586621680096239] ~> ([c6989586621680096240] ~> ([d6989586621680096241] ~> ([e6989586621680096242] ~> [f6989586621680096243]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym0 :: TyFun (a6989586621680096238 ~> (b6989586621680096239 ~> (c6989586621680096240 ~> (d6989586621680096241 ~> (e6989586621680096242 ~> f6989586621680096243))))) ([a6989586621680096238] ~> ([b6989586621680096239] ~> ([c6989586621680096240] ~> ([d6989586621680096241] ~> ([e6989586621680096242] ~> [f6989586621680096243]))))) -> Type) (a6989586621680097815 :: a6989586621680096238 ~> (b6989586621680096239 ~> (c6989586621680096240 ~> (d6989586621680096241 ~> (e6989586621680096242 ~> f6989586621680096243))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym0 :: TyFun (a6989586621680096238 ~> (b6989586621680096239 ~> (c6989586621680096240 ~> (d6989586621680096241 ~> (e6989586621680096242 ~> f6989586621680096243))))) ([a6989586621680096238] ~> ([b6989586621680096239] ~> ([c6989586621680096240] ~> ([d6989586621680096241] ~> ([e6989586621680096242] ~> [f6989586621680096243]))))) -> Type) (a6989586621680097815 :: a6989586621680096238 ~> (b6989586621680096239 ~> (c6989586621680096240 ~> (d6989586621680096241 ~> (e6989586621680096242 ~> f6989586621680096243))))) = ZipWith5Sym1 a6989586621680097815 |
data ZipWith5Sym1 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) :: (~>) [a6989586621680096238] ((~>) [b6989586621680096239] ((~>) [c6989586621680096240] ((~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243])))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym1 a6989586621680097815 :: TyFun [a6989586621680096238] ([b6989586621680096239] ~> ([c6989586621680096240] ~> ([d6989586621680096241] ~> ([e6989586621680096242] ~> [f6989586621680096243])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym1 a6989586621680097815 :: TyFun [a6989586621680096238] ([b6989586621680096239] ~> ([c6989586621680096240] ~> ([d6989586621680096241] ~> ([e6989586621680096242] ~> [f6989586621680096243])))) -> Type) (a6989586621680097816 :: [a6989586621680096238]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym1 a6989586621680097815 :: TyFun [a6989586621680096238] ([b6989586621680096239] ~> ([c6989586621680096240] ~> ([d6989586621680096241] ~> ([e6989586621680096242] ~> [f6989586621680096243])))) -> Type) (a6989586621680097816 :: [a6989586621680096238]) = ZipWith5Sym2 a6989586621680097815 a6989586621680097816 |
data ZipWith5Sym2 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) :: (~>) [b6989586621680096239] ((~>) [c6989586621680096240] ((~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243]))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym2 a6989586621680097816 a6989586621680097815 :: TyFun [b6989586621680096239] ([c6989586621680096240] ~> ([d6989586621680096241] ~> ([e6989586621680096242] ~> [f6989586621680096243]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym2 a6989586621680097816 a6989586621680097815 :: TyFun [b6989586621680096239] ([c6989586621680096240] ~> ([d6989586621680096241] ~> ([e6989586621680096242] ~> [f6989586621680096243]))) -> Type) (a6989586621680097817 :: [b6989586621680096239]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym2 a6989586621680097816 a6989586621680097815 :: TyFun [b6989586621680096239] ([c6989586621680096240] ~> ([d6989586621680096241] ~> ([e6989586621680096242] ~> [f6989586621680096243]))) -> Type) (a6989586621680097817 :: [b6989586621680096239]) = ZipWith5Sym3 a6989586621680097816 a6989586621680097815 a6989586621680097817 |
data ZipWith5Sym3 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) (a6989586621680097817 :: [b6989586621680096239]) :: (~>) [c6989586621680096240] ((~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243])) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym3 a6989586621680097817 a6989586621680097816 a6989586621680097815 :: TyFun [c6989586621680096240] ([d6989586621680096241] ~> ([e6989586621680096242] ~> [f6989586621680096243])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym3 a6989586621680097817 a6989586621680097816 a6989586621680097815 :: TyFun [c6989586621680096240] ([d6989586621680096241] ~> ([e6989586621680096242] ~> [f6989586621680096243])) -> Type) (a6989586621680097818 :: [c6989586621680096240]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym3 a6989586621680097817 a6989586621680097816 a6989586621680097815 :: TyFun [c6989586621680096240] ([d6989586621680096241] ~> ([e6989586621680096242] ~> [f6989586621680096243])) -> Type) (a6989586621680097818 :: [c6989586621680096240]) = ZipWith5Sym4 a6989586621680097817 a6989586621680097816 a6989586621680097815 a6989586621680097818 |
data ZipWith5Sym4 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) (a6989586621680097817 :: [b6989586621680096239]) (a6989586621680097818 :: [c6989586621680096240]) :: (~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243]) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym4 a6989586621680097818 a6989586621680097817 a6989586621680097816 a6989586621680097815 :: TyFun [d6989586621680096241] ([e6989586621680096242] ~> [f6989586621680096243]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym4 a6989586621680097818 a6989586621680097817 a6989586621680097816 a6989586621680097815 :: TyFun [d6989586621680096241] ([e6989586621680096242] ~> [f6989586621680096243]) -> Type) (a6989586621680097819 :: [d6989586621680096241]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym4 a6989586621680097818 a6989586621680097817 a6989586621680097816 a6989586621680097815 :: TyFun [d6989586621680096241] ([e6989586621680096242] ~> [f6989586621680096243]) -> Type) (a6989586621680097819 :: [d6989586621680096241]) = ZipWith5Sym5 a6989586621680097818 a6989586621680097817 a6989586621680097816 a6989586621680097815 a6989586621680097819 |
data ZipWith5Sym5 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) (a6989586621680097817 :: [b6989586621680096239]) (a6989586621680097818 :: [c6989586621680096240]) (a6989586621680097819 :: [d6989586621680096241]) :: (~>) [e6989586621680096242] [f6989586621680096243] Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym5 a6989586621680097819 a6989586621680097818 a6989586621680097817 a6989586621680097816 a6989586621680097815 :: TyFun [e6989586621680096242] [f6989586621680096243] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym5 a6989586621680097819 a6989586621680097818 a6989586621680097817 a6989586621680097816 a6989586621680097815 :: TyFun [e] [f] -> Type) (a6989586621680097820 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym5 a6989586621680097819 a6989586621680097818 a6989586621680097817 a6989586621680097816 a6989586621680097815 :: TyFun [e] [f] -> Type) (a6989586621680097820 :: [e]) = ZipWith5 a6989586621680097819 a6989586621680097818 a6989586621680097817 a6989586621680097816 a6989586621680097815 a6989586621680097820 |
type ZipWith5Sym6 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) (a6989586621680097817 :: [b6989586621680096239]) (a6989586621680097818 :: [c6989586621680096240]) (a6989586621680097819 :: [d6989586621680096241]) (a6989586621680097820 :: [e6989586621680096242]) = ZipWith5 a6989586621680097815 a6989586621680097816 a6989586621680097817 a6989586621680097818 a6989586621680097819 a6989586621680097820 Source #
data ZipWith6Sym0 :: forall a6989586621680096231 b6989586621680096232 c6989586621680096233 d6989586621680096234 e6989586621680096235 f6989586621680096236 g6989586621680096237. (~>) ((~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) ((~>) [a6989586621680096231] ((~>) [b6989586621680096232] ((~>) [c6989586621680096233] ((~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237])))))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (a6989586621680096231 ~> (b6989586621680096232 ~> (c6989586621680096233 ~> (d6989586621680096234 ~> (e6989586621680096235 ~> (f6989586621680096236 ~> g6989586621680096237)))))) ([a6989586621680096231] ~> ([b6989586621680096232] ~> ([c6989586621680096233] ~> ([d6989586621680096234] ~> ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym0 :: TyFun (a6989586621680096231 ~> (b6989586621680096232 ~> (c6989586621680096233 ~> (d6989586621680096234 ~> (e6989586621680096235 ~> (f6989586621680096236 ~> g6989586621680096237)))))) ([a6989586621680096231] ~> ([b6989586621680096232] ~> ([c6989586621680096233] ~> ([d6989586621680096234] ~> ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237])))))) -> Type) (a6989586621680097788 :: a6989586621680096231 ~> (b6989586621680096232 ~> (c6989586621680096233 ~> (d6989586621680096234 ~> (e6989586621680096235 ~> (f6989586621680096236 ~> g6989586621680096237)))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym0 :: TyFun (a6989586621680096231 ~> (b6989586621680096232 ~> (c6989586621680096233 ~> (d6989586621680096234 ~> (e6989586621680096235 ~> (f6989586621680096236 ~> g6989586621680096237)))))) ([a6989586621680096231] ~> ([b6989586621680096232] ~> ([c6989586621680096233] ~> ([d6989586621680096234] ~> ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237])))))) -> Type) (a6989586621680097788 :: a6989586621680096231 ~> (b6989586621680096232 ~> (c6989586621680096233 ~> (d6989586621680096234 ~> (e6989586621680096235 ~> (f6989586621680096236 ~> g6989586621680096237)))))) = ZipWith6Sym1 a6989586621680097788 |
data ZipWith6Sym1 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) :: (~>) [a6989586621680096231] ((~>) [b6989586621680096232] ((~>) [c6989586621680096233] ((~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym1 a6989586621680097788 :: TyFun [a6989586621680096231] ([b6989586621680096232] ~> ([c6989586621680096233] ~> ([d6989586621680096234] ~> ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym1 a6989586621680097788 :: TyFun [a6989586621680096231] ([b6989586621680096232] ~> ([c6989586621680096233] ~> ([d6989586621680096234] ~> ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237]))))) -> Type) (a6989586621680097789 :: [a6989586621680096231]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym1 a6989586621680097788 :: TyFun [a6989586621680096231] ([b6989586621680096232] ~> ([c6989586621680096233] ~> ([d6989586621680096234] ~> ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237]))))) -> Type) (a6989586621680097789 :: [a6989586621680096231]) = ZipWith6Sym2 a6989586621680097788 a6989586621680097789 |
data ZipWith6Sym2 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) :: (~>) [b6989586621680096232] ((~>) [c6989586621680096233] ((~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237])))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym2 a6989586621680097789 a6989586621680097788 :: TyFun [b6989586621680096232] ([c6989586621680096233] ~> ([d6989586621680096234] ~> ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym2 a6989586621680097789 a6989586621680097788 :: TyFun [b6989586621680096232] ([c6989586621680096233] ~> ([d6989586621680096234] ~> ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237])))) -> Type) (a6989586621680097790 :: [b6989586621680096232]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym2 a6989586621680097789 a6989586621680097788 :: TyFun [b6989586621680096232] ([c6989586621680096233] ~> ([d6989586621680096234] ~> ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237])))) -> Type) (a6989586621680097790 :: [b6989586621680096232]) = ZipWith6Sym3 a6989586621680097789 a6989586621680097788 a6989586621680097790 |
data ZipWith6Sym3 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) :: (~>) [c6989586621680096233] ((~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237]))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym3 a6989586621680097790 a6989586621680097789 a6989586621680097788 :: TyFun [c6989586621680096233] ([d6989586621680096234] ~> ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym3 a6989586621680097790 a6989586621680097789 a6989586621680097788 :: TyFun [c6989586621680096233] ([d6989586621680096234] ~> ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237]))) -> Type) (a6989586621680097791 :: [c6989586621680096233]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym3 a6989586621680097790 a6989586621680097789 a6989586621680097788 :: TyFun [c6989586621680096233] ([d6989586621680096234] ~> ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237]))) -> Type) (a6989586621680097791 :: [c6989586621680096233]) = ZipWith6Sym4 a6989586621680097790 a6989586621680097789 a6989586621680097788 a6989586621680097791 |
data ZipWith6Sym4 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) (a6989586621680097791 :: [c6989586621680096233]) :: (~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237])) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym4 a6989586621680097791 a6989586621680097790 a6989586621680097789 a6989586621680097788 :: TyFun [d6989586621680096234] ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym4 a6989586621680097791 a6989586621680097790 a6989586621680097789 a6989586621680097788 :: TyFun [d6989586621680096234] ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237])) -> Type) (a6989586621680097792 :: [d6989586621680096234]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym4 a6989586621680097791 a6989586621680097790 a6989586621680097789 a6989586621680097788 :: TyFun [d6989586621680096234] ([e6989586621680096235] ~> ([f6989586621680096236] ~> [g6989586621680096237])) -> Type) (a6989586621680097792 :: [d6989586621680096234]) = ZipWith6Sym5 a6989586621680097791 a6989586621680097790 a6989586621680097789 a6989586621680097788 a6989586621680097792 |
data ZipWith6Sym5 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) (a6989586621680097791 :: [c6989586621680096233]) (a6989586621680097792 :: [d6989586621680096234]) :: (~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237]) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym5 a6989586621680097792 a6989586621680097791 a6989586621680097790 a6989586621680097789 a6989586621680097788 :: TyFun [e6989586621680096235] ([f6989586621680096236] ~> [g6989586621680096237]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym5 a6989586621680097792 a6989586621680097791 a6989586621680097790 a6989586621680097789 a6989586621680097788 :: TyFun [e6989586621680096235] ([f6989586621680096236] ~> [g6989586621680096237]) -> Type) (a6989586621680097793 :: [e6989586621680096235]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym5 a6989586621680097792 a6989586621680097791 a6989586621680097790 a6989586621680097789 a6989586621680097788 :: TyFun [e6989586621680096235] ([f6989586621680096236] ~> [g6989586621680096237]) -> Type) (a6989586621680097793 :: [e6989586621680096235]) = ZipWith6Sym6 a6989586621680097792 a6989586621680097791 a6989586621680097790 a6989586621680097789 a6989586621680097788 a6989586621680097793 |
data ZipWith6Sym6 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) (a6989586621680097791 :: [c6989586621680096233]) (a6989586621680097792 :: [d6989586621680096234]) (a6989586621680097793 :: [e6989586621680096235]) :: (~>) [f6989586621680096236] [g6989586621680096237] Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym6 a6989586621680097793 a6989586621680097792 a6989586621680097791 a6989586621680097790 a6989586621680097789 a6989586621680097788 :: TyFun [f6989586621680096236] [g6989586621680096237] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym6 a6989586621680097793 a6989586621680097792 a6989586621680097791 a6989586621680097790 a6989586621680097789 a6989586621680097788 :: TyFun [f] [g] -> Type) (a6989586621680097794 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym6 a6989586621680097793 a6989586621680097792 a6989586621680097791 a6989586621680097790 a6989586621680097789 a6989586621680097788 :: TyFun [f] [g] -> Type) (a6989586621680097794 :: [f]) = ZipWith6 a6989586621680097793 a6989586621680097792 a6989586621680097791 a6989586621680097790 a6989586621680097789 a6989586621680097788 a6989586621680097794 |
type ZipWith6Sym7 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) (a6989586621680097791 :: [c6989586621680096233]) (a6989586621680097792 :: [d6989586621680096234]) (a6989586621680097793 :: [e6989586621680096235]) (a6989586621680097794 :: [f6989586621680096236]) = ZipWith6 a6989586621680097788 a6989586621680097789 a6989586621680097790 a6989586621680097791 a6989586621680097792 a6989586621680097793 a6989586621680097794 Source #
data ZipWith7Sym0 :: forall a6989586621680096223 b6989586621680096224 c6989586621680096225 d6989586621680096226 e6989586621680096227 f6989586621680096228 g6989586621680096229 h6989586621680096230. (~>) ((~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) ((~>) [a6989586621680096223] ((~>) [b6989586621680096224] ((~>) [c6989586621680096225] ((~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230]))))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym0 :: TyFun (a6989586621680096223 ~> (b6989586621680096224 ~> (c6989586621680096225 ~> (d6989586621680096226 ~> (e6989586621680096227 ~> (f6989586621680096228 ~> (g6989586621680096229 ~> h6989586621680096230))))))) ([a6989586621680096223] ~> ([b6989586621680096224] ~> ([c6989586621680096225] ~> ([d6989586621680096226] ~> ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230]))))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym0 :: TyFun (a6989586621680096223 ~> (b6989586621680096224 ~> (c6989586621680096225 ~> (d6989586621680096226 ~> (e6989586621680096227 ~> (f6989586621680096228 ~> (g6989586621680096229 ~> h6989586621680096230))))))) ([a6989586621680096223] ~> ([b6989586621680096224] ~> ([c6989586621680096225] ~> ([d6989586621680096226] ~> ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230]))))))) -> Type) (a6989586621680097757 :: a6989586621680096223 ~> (b6989586621680096224 ~> (c6989586621680096225 ~> (d6989586621680096226 ~> (e6989586621680096227 ~> (f6989586621680096228 ~> (g6989586621680096229 ~> h6989586621680096230))))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym0 :: TyFun (a6989586621680096223 ~> (b6989586621680096224 ~> (c6989586621680096225 ~> (d6989586621680096226 ~> (e6989586621680096227 ~> (f6989586621680096228 ~> (g6989586621680096229 ~> h6989586621680096230))))))) ([a6989586621680096223] ~> ([b6989586621680096224] ~> ([c6989586621680096225] ~> ([d6989586621680096226] ~> ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230]))))))) -> Type) (a6989586621680097757 :: a6989586621680096223 ~> (b6989586621680096224 ~> (c6989586621680096225 ~> (d6989586621680096226 ~> (e6989586621680096227 ~> (f6989586621680096228 ~> (g6989586621680096229 ~> h6989586621680096230))))))) = ZipWith7Sym1 a6989586621680097757 |
data ZipWith7Sym1 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) :: (~>) [a6989586621680096223] ((~>) [b6989586621680096224] ((~>) [c6989586621680096225] ((~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230])))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym1 a6989586621680097757 :: TyFun [a6989586621680096223] ([b6989586621680096224] ~> ([c6989586621680096225] ~> ([d6989586621680096226] ~> ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym1 a6989586621680097757 :: TyFun [a6989586621680096223] ([b6989586621680096224] ~> ([c6989586621680096225] ~> ([d6989586621680096226] ~> ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230])))))) -> Type) (a6989586621680097758 :: [a6989586621680096223]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym1 a6989586621680097757 :: TyFun [a6989586621680096223] ([b6989586621680096224] ~> ([c6989586621680096225] ~> ([d6989586621680096226] ~> ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230])))))) -> Type) (a6989586621680097758 :: [a6989586621680096223]) = ZipWith7Sym2 a6989586621680097757 a6989586621680097758 |
data ZipWith7Sym2 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) :: (~>) [b6989586621680096224] ((~>) [c6989586621680096225] ((~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym2 a6989586621680097758 a6989586621680097757 :: TyFun [b6989586621680096224] ([c6989586621680096225] ~> ([d6989586621680096226] ~> ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym2 a6989586621680097758 a6989586621680097757 :: TyFun [b6989586621680096224] ([c6989586621680096225] ~> ([d6989586621680096226] ~> ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230]))))) -> Type) (a6989586621680097759 :: [b6989586621680096224]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym2 a6989586621680097758 a6989586621680097757 :: TyFun [b6989586621680096224] ([c6989586621680096225] ~> ([d6989586621680096226] ~> ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230]))))) -> Type) (a6989586621680097759 :: [b6989586621680096224]) = ZipWith7Sym3 a6989586621680097758 a6989586621680097757 a6989586621680097759 |
data ZipWith7Sym3 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) :: (~>) [c6989586621680096225] ((~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230])))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym3 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [c6989586621680096225] ([d6989586621680096226] ~> ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym3 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [c6989586621680096225] ([d6989586621680096226] ~> ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230])))) -> Type) (a6989586621680097760 :: [c6989586621680096225]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym3 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [c6989586621680096225] ([d6989586621680096226] ~> ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230])))) -> Type) (a6989586621680097760 :: [c6989586621680096225]) = ZipWith7Sym4 a6989586621680097759 a6989586621680097758 a6989586621680097757 a6989586621680097760 |
data ZipWith7Sym4 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) :: (~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230]))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym4 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [d6989586621680096226] ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym4 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [d6989586621680096226] ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230]))) -> Type) (a6989586621680097761 :: [d6989586621680096226]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym4 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [d6989586621680096226] ([e6989586621680096227] ~> ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230]))) -> Type) (a6989586621680097761 :: [d6989586621680096226]) = ZipWith7Sym5 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 a6989586621680097761 |
data ZipWith7Sym5 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) (a6989586621680097761 :: [d6989586621680096226]) :: (~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230])) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym5 a6989586621680097761 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [e6989586621680096227] ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym5 a6989586621680097761 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [e6989586621680096227] ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230])) -> Type) (a6989586621680097762 :: [e6989586621680096227]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym5 a6989586621680097761 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [e6989586621680096227] ([f6989586621680096228] ~> ([g6989586621680096229] ~> [h6989586621680096230])) -> Type) (a6989586621680097762 :: [e6989586621680096227]) = ZipWith7Sym6 a6989586621680097761 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 a6989586621680097762 |
data ZipWith7Sym6 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) (a6989586621680097761 :: [d6989586621680096226]) (a6989586621680097762 :: [e6989586621680096227]) :: (~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230]) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym6 a6989586621680097762 a6989586621680097761 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [f6989586621680096228] ([g6989586621680096229] ~> [h6989586621680096230]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym6 a6989586621680097762 a6989586621680097761 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [f6989586621680096228] ([g6989586621680096229] ~> [h6989586621680096230]) -> Type) (a6989586621680097763 :: [f6989586621680096228]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym6 a6989586621680097762 a6989586621680097761 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [f6989586621680096228] ([g6989586621680096229] ~> [h6989586621680096230]) -> Type) (a6989586621680097763 :: [f6989586621680096228]) = ZipWith7Sym7 a6989586621680097762 a6989586621680097761 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 a6989586621680097763 |
data ZipWith7Sym7 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) (a6989586621680097761 :: [d6989586621680096226]) (a6989586621680097762 :: [e6989586621680096227]) (a6989586621680097763 :: [f6989586621680096228]) :: (~>) [g6989586621680096229] [h6989586621680096230] Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym7 a6989586621680097763 a6989586621680097762 a6989586621680097761 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [g6989586621680096229] [h6989586621680096230] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym7 a6989586621680097763 a6989586621680097762 a6989586621680097761 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [g] [h] -> Type) (a6989586621680097764 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym7 a6989586621680097763 a6989586621680097762 a6989586621680097761 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 :: TyFun [g] [h] -> Type) (a6989586621680097764 :: [g]) = ZipWith7 a6989586621680097763 a6989586621680097762 a6989586621680097761 a6989586621680097760 a6989586621680097759 a6989586621680097758 a6989586621680097757 a6989586621680097764 |
type ZipWith7Sym8 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) (a6989586621680097761 :: [d6989586621680096226]) (a6989586621680097762 :: [e6989586621680096227]) (a6989586621680097763 :: [f6989586621680096228]) (a6989586621680097764 :: [g6989586621680096229]) = ZipWith7 a6989586621680097757 a6989586621680097758 a6989586621680097759 a6989586621680097760 a6989586621680097761 a6989586621680097762 a6989586621680097763 a6989586621680097764 Source #
data UnzipSym0 :: forall a6989586621679974127 b6989586621679974128. (~>) [(a6989586621679974127, b6989586621679974128)] ([a6989586621679974127], [b6989586621679974128]) Source #
Instances
SingI (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # | |
SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a6989586621679974127, b6989586621679974128)] ([a6989586621679974127], [b6989586621679974128]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679978946 :: [(a, b)]) Source # | |
type UnzipSym1 (a6989586621679978946 :: [(a6989586621679974127, b6989586621679974128)]) = Unzip a6989586621679978946 Source #
data Unzip3Sym0 :: forall a6989586621679974124 b6989586621679974125 c6989586621679974126. (~>) [(a6989586621679974124, b6989586621679974125, c6989586621679974126)] ([a6989586621679974124], [b6989586621679974125], [c6989586621679974126]) Source #
Instances
SingI (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Unzip3Sym0 Source # | |
SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a6989586621679974124, b6989586621679974125, c6989586621679974126)] ([a6989586621679974124], [b6989586621679974125], [c6989586621679974126]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679978925 :: [(a, b, c)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679978925 :: [(a, b, c)]) = Unzip3 a6989586621679978925 |
type Unzip3Sym1 (a6989586621679978925 :: [(a6989586621679974124, b6989586621679974125, c6989586621679974126)]) = Unzip3 a6989586621679978925 Source #
data Unzip4Sym0 :: forall a6989586621679974120 b6989586621679974121 c6989586621679974122 d6989586621679974123. (~>) [(a6989586621679974120, b6989586621679974121, c6989586621679974122, d6989586621679974123)] ([a6989586621679974120], [b6989586621679974121], [c6989586621679974122], [d6989586621679974123]) Source #
Instances
SingI (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Unzip4Sym0 Source # | |
SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a6989586621679974120, b6989586621679974121, c6989586621679974122, d6989586621679974123)] ([a6989586621679974120], [b6989586621679974121], [c6989586621679974122], [d6989586621679974123]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679978902 :: [(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) (a6989586621679978902 :: [(a, b, c, d)]) = Unzip4 a6989586621679978902 |
type Unzip4Sym1 (a6989586621679978902 :: [(a6989586621679974120, b6989586621679974121, c6989586621679974122, d6989586621679974123)]) = Unzip4 a6989586621679978902 Source #
data Unzip5Sym0 :: forall a6989586621679974115 b6989586621679974116 c6989586621679974117 d6989586621679974118 e6989586621679974119. (~>) [(a6989586621679974115, b6989586621679974116, c6989586621679974117, d6989586621679974118, e6989586621679974119)] ([a6989586621679974115], [b6989586621679974116], [c6989586621679974117], [d6989586621679974118], [e6989586621679974119]) Source #
Instances
SingI (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Unzip5Sym0 Source # | |
SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a6989586621679974115, b6989586621679974116, c6989586621679974117, d6989586621679974118, e6989586621679974119)] ([a6989586621679974115], [b6989586621679974116], [c6989586621679974117], [d6989586621679974118], [e6989586621679974119]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679978877 :: [(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) (a6989586621679978877 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679978877 |
type Unzip5Sym1 (a6989586621679978877 :: [(a6989586621679974115, b6989586621679974116, c6989586621679974117, d6989586621679974118, e6989586621679974119)]) = Unzip5 a6989586621679978877 Source #
data Unzip6Sym0 :: forall a6989586621679974109 b6989586621679974110 c6989586621679974111 d6989586621679974112 e6989586621679974113 f6989586621679974114. (~>) [(a6989586621679974109, b6989586621679974110, c6989586621679974111, d6989586621679974112, e6989586621679974113, f6989586621679974114)] ([a6989586621679974109], [b6989586621679974110], [c6989586621679974111], [d6989586621679974112], [e6989586621679974113], [f6989586621679974114]) Source #
Instances
SingI (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Unzip6Sym0 Source # | |
SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a6989586621679974109, b6989586621679974110, c6989586621679974111, d6989586621679974112, e6989586621679974113, f6989586621679974114)] ([a6989586621679974109], [b6989586621679974110], [c6989586621679974111], [d6989586621679974112], [e6989586621679974113], [f6989586621679974114]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679978850 :: [(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) (a6989586621679978850 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679978850 |
type Unzip6Sym1 (a6989586621679978850 :: [(a6989586621679974109, b6989586621679974110, c6989586621679974111, d6989586621679974112, e6989586621679974113, f6989586621679974114)]) = Unzip6 a6989586621679978850 Source #
data Unzip7Sym0 :: forall a6989586621679974102 b6989586621679974103 c6989586621679974104 d6989586621679974105 e6989586621679974106 f6989586621679974107 g6989586621679974108. (~>) [(a6989586621679974102, b6989586621679974103, c6989586621679974104, d6989586621679974105, e6989586621679974106, f6989586621679974107, g6989586621679974108)] ([a6989586621679974102], [b6989586621679974103], [c6989586621679974104], [d6989586621679974105], [e6989586621679974106], [f6989586621679974107], [g6989586621679974108]) Source #
Instances
SingI (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing Unzip7Sym0 Source # | |
SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a6989586621679974102, b6989586621679974103, c6989586621679974104, d6989586621679974105, e6989586621679974106, f6989586621679974107, g6989586621679974108)] ([a6989586621679974102], [b6989586621679974103], [c6989586621679974104], [d6989586621679974105], [e6989586621679974106], [f6989586621679974107], [g6989586621679974108]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679978821 :: [(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) (a6989586621679978821 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679978821 |
type Unzip7Sym1 (a6989586621679978821 :: [(a6989586621679974102, b6989586621679974103, c6989586621679974104, d6989586621679974105, e6989586621679974106, f6989586621679974107, g6989586621679974108)]) = Unzip7 a6989586621679978821 Source #
data UnlinesSym0 :: (~>) [Symbol] Symbol Source #
Instances
SingI UnlinesSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing UnlinesSym0 Source # | |
SuppressUnusedWarnings UnlinesSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply UnlinesSym0 (a6989586621679978817 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnlinesSym1 (a6989586621679978817 :: [Symbol]) = Unlines a6989586621679978817 Source #
data UnwordsSym0 :: (~>) [Symbol] Symbol Source #
Instances
SingI UnwordsSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing UnwordsSym0 Source # | |
SuppressUnusedWarnings UnwordsSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply UnwordsSym0 (a6989586621679978806 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnwordsSym1 (a6989586621679978806 :: [Symbol]) = Unwords a6989586621679978806 Source #
data NubSym0 :: forall a6989586621679974061. (~>) [a6989586621679974061] [a6989586621679974061] Source #
Instances
SEq a => SingI (NubSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (NubSym0 :: TyFun [a6989586621679974061] [a6989586621679974061] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (NubSym0 :: TyFun [a] [a] -> Type) (a6989586621679978189 :: [a]) Source # | |
data DeleteSym0 :: forall a6989586621679974101. (~>) a6989586621679974101 ((~>) [a6989586621679974101] [a6989586621679974101]) Source #
Instances
SEq a => SingI (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing DeleteSym0 Source # | |
SuppressUnusedWarnings (DeleteSym0 :: TyFun a6989586621679974101 ([a6989586621679974101] ~> [a6989586621679974101]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym0 :: TyFun a6989586621679974101 ([a6989586621679974101] ~> [a6989586621679974101]) -> Type) (a6989586621679978800 :: a6989586621679974101) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym0 :: TyFun a6989586621679974101 ([a6989586621679974101] ~> [a6989586621679974101]) -> Type) (a6989586621679978800 :: a6989586621679974101) = DeleteSym1 a6989586621679978800 |
data DeleteSym1 (a6989586621679978800 :: a6989586621679974101) :: (~>) [a6989586621679974101] [a6989586621679974101] Source #
Instances
(SEq a, SingI d) => SingI (DeleteSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DeleteSym1 d) Source # | |
SuppressUnusedWarnings (DeleteSym1 a6989586621679978800 :: TyFun [a6989586621679974101] [a6989586621679974101] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym1 a6989586621679978800 :: TyFun [a] [a] -> Type) (a6989586621679978801 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym1 a6989586621679978800 :: TyFun [a] [a] -> Type) (a6989586621679978801 :: [a]) = Delete a6989586621679978800 a6989586621679978801 |
type DeleteSym2 (a6989586621679978800 :: a6989586621679974101) (a6989586621679978801 :: [a6989586621679974101]) = Delete a6989586621679978800 a6989586621679978801 Source #
data (\\@#@$) :: forall a6989586621679974100. (~>) [a6989586621679974100] ((~>) [a6989586621679974100] [a6989586621679974100]) infix 5 Source #
Instances
SEq a => SingI ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((\\@#@$) :: TyFun [a6989586621679974100] ([a6989586621679974100] ~> [a6989586621679974100]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$) :: TyFun [a6989586621679974100] ([a6989586621679974100] ~> [a6989586621679974100]) -> Type) (a6989586621679978790 :: [a6989586621679974100]) Source # | |
data (\\@#@$$) (a6989586621679978790 :: [a6989586621679974100]) :: (~>) [a6989586621679974100] [a6989586621679974100] infix 5 Source #
Instances
(SEq a, SingI d) => SingI ((\\@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((\\@#@$$) a6989586621679978790 :: TyFun [a6989586621679974100] [a6989586621679974100] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$$) a6989586621679978790 :: TyFun [a] [a] -> Type) (a6989586621679978791 :: [a]) Source # | |
type (\\@#@$$$) (a6989586621679978790 :: [a6989586621679974100]) (a6989586621679978791 :: [a6989586621679974100]) = (\\) a6989586621679978790 a6989586621679978791 Source #
data UnionSym0 :: forall a6989586621679974057. (~>) [a6989586621679974057] ((~>) [a6989586621679974057] [a6989586621679974057]) Source #
Instances
SEq a => SingI (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (UnionSym0 :: TyFun [a6989586621679974057] ([a6989586621679974057] ~> [a6989586621679974057]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym0 :: TyFun [a6989586621679974057] ([a6989586621679974057] ~> [a6989586621679974057]) -> Type) (a6989586621679978139 :: [a6989586621679974057]) Source # | |
data UnionSym1 (a6989586621679978139 :: [a6989586621679974057]) :: (~>) [a6989586621679974057] [a6989586621679974057] Source #
Instances
(SEq a, SingI d) => SingI (UnionSym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (UnionSym1 a6989586621679978139 :: TyFun [a6989586621679974057] [a6989586621679974057] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym1 a6989586621679978139 :: TyFun [a] [a] -> Type) (a6989586621679978140 :: [a]) Source # | |
type UnionSym2 (a6989586621679978139 :: [a6989586621679974057]) (a6989586621679978140 :: [a6989586621679974057]) = Union a6989586621679978139 a6989586621679978140 Source #
data IntersectSym0 :: forall a6989586621679974087. (~>) [a6989586621679974087] ((~>) [a6989586621679974087] [a6989586621679974087]) Source #
Instances
SEq a => SingI (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing IntersectSym0 Source # | |
SuppressUnusedWarnings (IntersectSym0 :: TyFun [a6989586621679974087] ([a6989586621679974087] ~> [a6989586621679974087]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym0 :: TyFun [a6989586621679974087] ([a6989586621679974087] ~> [a6989586621679974087]) -> Type) (a6989586621679978584 :: [a6989586621679974087]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym0 :: TyFun [a6989586621679974087] ([a6989586621679974087] ~> [a6989586621679974087]) -> Type) (a6989586621679978584 :: [a6989586621679974087]) = IntersectSym1 a6989586621679978584 |
data IntersectSym1 (a6989586621679978584 :: [a6989586621679974087]) :: (~>) [a6989586621679974087] [a6989586621679974087] Source #
Instances
(SEq a, SingI d) => SingI (IntersectSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IntersectSym1 d) Source # | |
SuppressUnusedWarnings (IntersectSym1 a6989586621679978584 :: TyFun [a6989586621679974087] [a6989586621679974087] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym1 a6989586621679978584 :: TyFun [a] [a] -> Type) (a6989586621679978585 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym1 a6989586621679978584 :: TyFun [a] [a] -> Type) (a6989586621679978585 :: [a]) = Intersect a6989586621679978584 a6989586621679978585 |
type IntersectSym2 (a6989586621679978584 :: [a6989586621679974087]) (a6989586621679978585 :: [a6989586621679974087]) = Intersect a6989586621679978584 a6989586621679978585 Source #
data InsertSym0 :: forall a6989586621679974074. (~>) a6989586621679974074 ((~>) [a6989586621679974074] [a6989586621679974074]) Source #
Instances
SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing InsertSym0 Source # | |
SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621679974074 ([a6989586621679974074] ~> [a6989586621679974074]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym0 :: TyFun a6989586621679974074 ([a6989586621679974074] ~> [a6989586621679974074]) -> Type) (a6989586621679978347 :: a6989586621679974074) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym0 :: TyFun a6989586621679974074 ([a6989586621679974074] ~> [a6989586621679974074]) -> Type) (a6989586621679978347 :: a6989586621679974074) = InsertSym1 a6989586621679978347 |
data InsertSym1 (a6989586621679978347 :: a6989586621679974074) :: (~>) [a6989586621679974074] [a6989586621679974074] Source #
Instances
(SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (InsertSym1 d) Source # | |
SuppressUnusedWarnings (InsertSym1 a6989586621679978347 :: TyFun [a6989586621679974074] [a6989586621679974074] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym1 a6989586621679978347 :: TyFun [a] [a] -> Type) (a6989586621679978348 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym1 a6989586621679978347 :: TyFun [a] [a] -> Type) (a6989586621679978348 :: [a]) = Insert a6989586621679978347 a6989586621679978348 |
type InsertSym2 (a6989586621679978347 :: a6989586621679974074) (a6989586621679978348 :: [a6989586621679974074]) = Insert a6989586621679978347 a6989586621679978348 Source #
data SortSym0 :: forall a6989586621679974073. (~>) [a6989586621679974073] [a6989586621679974073] Source #
Instances
SOrd a => SingI (SortSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (SortSym0 :: TyFun [a6989586621679974073] [a6989586621679974073] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SortSym0 :: TyFun [a] [a] -> Type) (a6989586621679978344 :: [a]) Source # | |
data NubBySym0 :: forall a6989586621679974060. (~>) ((~>) a6989586621679974060 ((~>) a6989586621679974060 Bool)) ((~>) [a6989586621679974060] [a6989586621679974060]) Source #
Instances
SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (NubBySym0 :: TyFun (a6989586621679974060 ~> (a6989586621679974060 ~> Bool)) ([a6989586621679974060] ~> [a6989586621679974060]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym0 :: TyFun (a6989586621679974060 ~> (a6989586621679974060 ~> Bool)) ([a6989586621679974060] ~> [a6989586621679974060]) -> Type) (a6989586621679978164 :: a6989586621679974060 ~> (a6989586621679974060 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data NubBySym1 (a6989586621679978164 :: (~>) a6989586621679974060 ((~>) a6989586621679974060 Bool)) :: (~>) [a6989586621679974060] [a6989586621679974060] Source #
Instances
SingI d => SingI (NubBySym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (NubBySym1 a6989586621679978164 :: TyFun [a6989586621679974060] [a6989586621679974060] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym1 a6989586621679978164 :: TyFun [a] [a] -> Type) (a6989586621679978165 :: [a]) Source # | |
type NubBySym2 (a6989586621679978164 :: (~>) a6989586621679974060 ((~>) a6989586621679974060 Bool)) (a6989586621679978165 :: [a6989586621679974060]) = NubBy a6989586621679978164 a6989586621679978165 Source #
data DeleteBySym0 :: forall a6989586621679974099. (~>) ((~>) a6989586621679974099 ((~>) a6989586621679974099 Bool)) ((~>) a6989586621679974099 ((~>) [a6989586621679974099] [a6989586621679974099])) Source #
Instances
SingI (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing DeleteBySym0 Source # | |
SuppressUnusedWarnings (DeleteBySym0 :: TyFun (a6989586621679974099 ~> (a6989586621679974099 ~> Bool)) (a6989586621679974099 ~> ([a6989586621679974099] ~> [a6989586621679974099])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym0 :: TyFun (a6989586621679974099 ~> (a6989586621679974099 ~> Bool)) (a6989586621679974099 ~> ([a6989586621679974099] ~> [a6989586621679974099])) -> Type) (a6989586621679978768 :: a6989586621679974099 ~> (a6989586621679974099 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data DeleteBySym1 (a6989586621679978768 :: (~>) a6989586621679974099 ((~>) a6989586621679974099 Bool)) :: (~>) a6989586621679974099 ((~>) [a6989586621679974099] [a6989586621679974099]) Source #
Instances
SingI d => SingI (DeleteBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DeleteBySym1 d) Source # | |
SuppressUnusedWarnings (DeleteBySym1 a6989586621679978768 :: TyFun a6989586621679974099 ([a6989586621679974099] ~> [a6989586621679974099]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym1 a6989586621679978768 :: TyFun a6989586621679974099 ([a6989586621679974099] ~> [a6989586621679974099]) -> Type) (a6989586621679978769 :: a6989586621679974099) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym1 a6989586621679978768 :: TyFun a6989586621679974099 ([a6989586621679974099] ~> [a6989586621679974099]) -> Type) (a6989586621679978769 :: a6989586621679974099) = DeleteBySym2 a6989586621679978768 a6989586621679978769 |
data DeleteBySym2 (a6989586621679978768 :: (~>) a6989586621679974099 ((~>) a6989586621679974099 Bool)) (a6989586621679978769 :: a6989586621679974099) :: (~>) [a6989586621679974099] [a6989586621679974099] Source #
Instances
(SingI d1, SingI d2) => SingI (DeleteBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DeleteBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (DeleteBySym2 a6989586621679978769 a6989586621679978768 :: TyFun [a6989586621679974099] [a6989586621679974099] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym2 a6989586621679978769 a6989586621679978768 :: TyFun [a] [a] -> Type) (a6989586621679978770 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym2 a6989586621679978769 a6989586621679978768 :: TyFun [a] [a] -> Type) (a6989586621679978770 :: [a]) = DeleteBy a6989586621679978769 a6989586621679978768 a6989586621679978770 |
type DeleteBySym3 (a6989586621679978768 :: (~>) a6989586621679974099 ((~>) a6989586621679974099 Bool)) (a6989586621679978769 :: a6989586621679974099) (a6989586621679978770 :: [a6989586621679974099]) = DeleteBy a6989586621679978768 a6989586621679978769 a6989586621679978770 Source #
data DeleteFirstsBySym0 :: forall a6989586621679974098. (~>) ((~>) a6989586621679974098 ((~>) a6989586621679974098 Bool)) ((~>) [a6989586621679974098] ((~>) [a6989586621679974098] [a6989586621679974098])) Source #
Instances
SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (a6989586621679974098 ~> (a6989586621679974098 ~> Bool)) ([a6989586621679974098] ~> ([a6989586621679974098] ~> [a6989586621679974098])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679974098 ~> (a6989586621679974098 ~> Bool)) ([a6989586621679974098] ~> ([a6989586621679974098] ~> [a6989586621679974098])) -> Type) (a6989586621679978755 :: a6989586621679974098 ~> (a6989586621679974098 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679974098 ~> (a6989586621679974098 ~> Bool)) ([a6989586621679974098] ~> ([a6989586621679974098] ~> [a6989586621679974098])) -> Type) (a6989586621679978755 :: a6989586621679974098 ~> (a6989586621679974098 ~> Bool)) = DeleteFirstsBySym1 a6989586621679978755 |
data DeleteFirstsBySym1 (a6989586621679978755 :: (~>) a6989586621679974098 ((~>) a6989586621679974098 Bool)) :: (~>) [a6989586621679974098] ((~>) [a6989586621679974098] [a6989586621679974098]) Source #
Instances
SingI d => SingI (DeleteFirstsBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DeleteFirstsBySym1 d) Source # | |
SuppressUnusedWarnings (DeleteFirstsBySym1 a6989586621679978755 :: TyFun [a6989586621679974098] ([a6989586621679974098] ~> [a6989586621679974098]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym1 a6989586621679978755 :: TyFun [a6989586621679974098] ([a6989586621679974098] ~> [a6989586621679974098]) -> Type) (a6989586621679978756 :: [a6989586621679974098]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym1 a6989586621679978755 :: TyFun [a6989586621679974098] ([a6989586621679974098] ~> [a6989586621679974098]) -> Type) (a6989586621679978756 :: [a6989586621679974098]) = DeleteFirstsBySym2 a6989586621679978755 a6989586621679978756 |
data DeleteFirstsBySym2 (a6989586621679978755 :: (~>) a6989586621679974098 ((~>) a6989586621679974098 Bool)) (a6989586621679978756 :: [a6989586621679974098]) :: (~>) [a6989586621679974098] [a6989586621679974098] Source #
Instances
(SingI d1, SingI d2) => SingI (DeleteFirstsBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (DeleteFirstsBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (DeleteFirstsBySym2 a6989586621679978756 a6989586621679978755 :: TyFun [a6989586621679974098] [a6989586621679974098] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym2 a6989586621679978756 a6989586621679978755 :: TyFun [a] [a] -> Type) (a6989586621679978757 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym2 a6989586621679978756 a6989586621679978755 :: TyFun [a] [a] -> Type) (a6989586621679978757 :: [a]) = DeleteFirstsBy a6989586621679978756 a6989586621679978755 a6989586621679978757 |
type DeleteFirstsBySym3 (a6989586621679978755 :: (~>) a6989586621679974098 ((~>) a6989586621679974098 Bool)) (a6989586621679978756 :: [a6989586621679974098]) (a6989586621679978757 :: [a6989586621679974098]) = DeleteFirstsBy a6989586621679978755 a6989586621679978756 a6989586621679978757 Source #
data UnionBySym0 :: forall a6989586621679974058. (~>) ((~>) a6989586621679974058 ((~>) a6989586621679974058 Bool)) ((~>) [a6989586621679974058] ((~>) [a6989586621679974058] [a6989586621679974058])) Source #
Instances
SingI (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing UnionBySym0 Source # | |
SuppressUnusedWarnings (UnionBySym0 :: TyFun (a6989586621679974058 ~> (a6989586621679974058 ~> Bool)) ([a6989586621679974058] ~> ([a6989586621679974058] ~> [a6989586621679974058])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym0 :: TyFun (a6989586621679974058 ~> (a6989586621679974058 ~> Bool)) ([a6989586621679974058] ~> ([a6989586621679974058] ~> [a6989586621679974058])) -> Type) (a6989586621679978145 :: a6989586621679974058 ~> (a6989586621679974058 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data UnionBySym1 (a6989586621679978145 :: (~>) a6989586621679974058 ((~>) a6989586621679974058 Bool)) :: (~>) [a6989586621679974058] ((~>) [a6989586621679974058] [a6989586621679974058]) Source #
Instances
SingI d => SingI (UnionBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (UnionBySym1 d) Source # | |
SuppressUnusedWarnings (UnionBySym1 a6989586621679978145 :: TyFun [a6989586621679974058] ([a6989586621679974058] ~> [a6989586621679974058]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym1 a6989586621679978145 :: TyFun [a6989586621679974058] ([a6989586621679974058] ~> [a6989586621679974058]) -> Type) (a6989586621679978146 :: [a6989586621679974058]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym1 a6989586621679978145 :: TyFun [a6989586621679974058] ([a6989586621679974058] ~> [a6989586621679974058]) -> Type) (a6989586621679978146 :: [a6989586621679974058]) = UnionBySym2 a6989586621679978145 a6989586621679978146 |
data UnionBySym2 (a6989586621679978145 :: (~>) a6989586621679974058 ((~>) a6989586621679974058 Bool)) (a6989586621679978146 :: [a6989586621679974058]) :: (~>) [a6989586621679974058] [a6989586621679974058] Source #
Instances
(SingI d1, SingI d2) => SingI (UnionBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (UnionBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (UnionBySym2 a6989586621679978146 a6989586621679978145 :: TyFun [a6989586621679974058] [a6989586621679974058] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym2 a6989586621679978146 a6989586621679978145 :: TyFun [a] [a] -> Type) (a6989586621679978147 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym2 a6989586621679978146 a6989586621679978145 :: TyFun [a] [a] -> Type) (a6989586621679978147 :: [a]) = UnionBy a6989586621679978146 a6989586621679978145 a6989586621679978147 |
type UnionBySym3 (a6989586621679978145 :: (~>) a6989586621679974058 ((~>) a6989586621679974058 Bool)) (a6989586621679978146 :: [a6989586621679974058]) (a6989586621679978147 :: [a6989586621679974058]) = UnionBy a6989586621679978145 a6989586621679978146 a6989586621679978147 Source #
data IntersectBySym0 :: forall a6989586621679974086. (~>) ((~>) a6989586621679974086 ((~>) a6989586621679974086 Bool)) ((~>) [a6989586621679974086] ((~>) [a6989586621679974086] [a6989586621679974086])) Source #
Instances
SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IntersectBySym0 :: TyFun (a6989586621679974086 ~> (a6989586621679974086 ~> Bool)) ([a6989586621679974086] ~> ([a6989586621679974086] ~> [a6989586621679974086])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym0 :: TyFun (a6989586621679974086 ~> (a6989586621679974086 ~> Bool)) ([a6989586621679974086] ~> ([a6989586621679974086] ~> [a6989586621679974086])) -> Type) (a6989586621679978548 :: a6989586621679974086 ~> (a6989586621679974086 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym0 :: TyFun (a6989586621679974086 ~> (a6989586621679974086 ~> Bool)) ([a6989586621679974086] ~> ([a6989586621679974086] ~> [a6989586621679974086])) -> Type) (a6989586621679978548 :: a6989586621679974086 ~> (a6989586621679974086 ~> Bool)) = IntersectBySym1 a6989586621679978548 |
data IntersectBySym1 (a6989586621679978548 :: (~>) a6989586621679974086 ((~>) a6989586621679974086 Bool)) :: (~>) [a6989586621679974086] ((~>) [a6989586621679974086] [a6989586621679974086]) Source #
Instances
SingI d => SingI (IntersectBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IntersectBySym1 d) Source # | |
SuppressUnusedWarnings (IntersectBySym1 a6989586621679978548 :: TyFun [a6989586621679974086] ([a6989586621679974086] ~> [a6989586621679974086]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym1 a6989586621679978548 :: TyFun [a6989586621679974086] ([a6989586621679974086] ~> [a6989586621679974086]) -> Type) (a6989586621679978549 :: [a6989586621679974086]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym1 a6989586621679978548 :: TyFun [a6989586621679974086] ([a6989586621679974086] ~> [a6989586621679974086]) -> Type) (a6989586621679978549 :: [a6989586621679974086]) = IntersectBySym2 a6989586621679978548 a6989586621679978549 |
data IntersectBySym2 (a6989586621679978548 :: (~>) a6989586621679974086 ((~>) a6989586621679974086 Bool)) (a6989586621679978549 :: [a6989586621679974086]) :: (~>) [a6989586621679974086] [a6989586621679974086] Source #
Instances
(SingI d1, SingI d2) => SingI (IntersectBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (IntersectBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (IntersectBySym2 a6989586621679978549 a6989586621679978548 :: TyFun [a6989586621679974086] [a6989586621679974086] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym2 a6989586621679978549 a6989586621679978548 :: TyFun [a] [a] -> Type) (a6989586621679978550 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym2 a6989586621679978549 a6989586621679978548 :: TyFun [a] [a] -> Type) (a6989586621679978550 :: [a]) = IntersectBy a6989586621679978549 a6989586621679978548 a6989586621679978550 |
type IntersectBySym3 (a6989586621679978548 :: (~>) a6989586621679974086 ((~>) a6989586621679974086 Bool)) (a6989586621679978549 :: [a6989586621679974086]) (a6989586621679978550 :: [a6989586621679974086]) = IntersectBy a6989586621679978548 a6989586621679978549 a6989586621679978550 Source #
data GroupBySym0 :: forall a6989586621679974072. (~>) ((~>) a6989586621679974072 ((~>) a6989586621679974072 Bool)) ((~>) [a6989586621679974072] [[a6989586621679974072]]) Source #
Instances
SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing GroupBySym0 Source # | |
SuppressUnusedWarnings (GroupBySym0 :: TyFun (a6989586621679974072 ~> (a6989586621679974072 ~> Bool)) ([a6989586621679974072] ~> [[a6989586621679974072]]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym0 :: TyFun (a6989586621679974072 ~> (a6989586621679974072 ~> Bool)) ([a6989586621679974072] ~> [[a6989586621679974072]]) -> Type) (a6989586621679978311 :: a6989586621679974072 ~> (a6989586621679974072 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data GroupBySym1 (a6989586621679978311 :: (~>) a6989586621679974072 ((~>) a6989586621679974072 Bool)) :: (~>) [a6989586621679974072] [[a6989586621679974072]] Source #
Instances
SingI d => SingI (GroupBySym1 d :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (GroupBySym1 d) Source # | |
SuppressUnusedWarnings (GroupBySym1 a6989586621679978311 :: TyFun [a6989586621679974072] [[a6989586621679974072]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym1 a6989586621679978311 :: TyFun [a] [[a]] -> Type) (a6989586621679978312 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GroupBySym1 a6989586621679978311 :: TyFun [a] [[a]] -> Type) (a6989586621679978312 :: [a]) = GroupBy a6989586621679978311 a6989586621679978312 |
type GroupBySym2 (a6989586621679978311 :: (~>) a6989586621679974072 ((~>) a6989586621679974072 Bool)) (a6989586621679978312 :: [a6989586621679974072]) = GroupBy a6989586621679978311 a6989586621679978312 Source #
data SortBySym0 :: forall a6989586621679974097. (~>) ((~>) a6989586621679974097 ((~>) a6989586621679974097 Ordering)) ((~>) [a6989586621679974097] [a6989586621679974097]) Source #
Instances
SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing SortBySym0 Source # | |
SuppressUnusedWarnings (SortBySym0 :: TyFun (a6989586621679974097 ~> (a6989586621679974097 ~> Ordering)) ([a6989586621679974097] ~> [a6989586621679974097]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym0 :: TyFun (a6989586621679974097 ~> (a6989586621679974097 ~> Ordering)) ([a6989586621679974097] ~> [a6989586621679974097]) -> Type) (a6989586621679978747 :: a6989586621679974097 ~> (a6989586621679974097 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data SortBySym1 (a6989586621679978747 :: (~>) a6989586621679974097 ((~>) a6989586621679974097 Ordering)) :: (~>) [a6989586621679974097] [a6989586621679974097] Source #
Instances
SingI d => SingI (SortBySym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (SortBySym1 d) Source # | |
SuppressUnusedWarnings (SortBySym1 a6989586621679978747 :: TyFun [a6989586621679974097] [a6989586621679974097] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym1 a6989586621679978747 :: TyFun [a] [a] -> Type) (a6989586621679978748 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SortBySym1 a6989586621679978747 :: TyFun [a] [a] -> Type) (a6989586621679978748 :: [a]) = SortBy a6989586621679978747 a6989586621679978748 |
type SortBySym2 (a6989586621679978747 :: (~>) a6989586621679974097 ((~>) a6989586621679974097 Ordering)) (a6989586621679978748 :: [a6989586621679974097]) = SortBy a6989586621679978747 a6989586621679978748 Source #
data InsertBySym0 :: forall a6989586621679974096. (~>) ((~>) a6989586621679974096 ((~>) a6989586621679974096 Ordering)) ((~>) a6989586621679974096 ((~>) [a6989586621679974096] [a6989586621679974096])) Source #
Instances
SingI (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing InsertBySym0 Source # | |
SuppressUnusedWarnings (InsertBySym0 :: TyFun (a6989586621679974096 ~> (a6989586621679974096 ~> Ordering)) (a6989586621679974096 ~> ([a6989586621679974096] ~> [a6989586621679974096])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym0 :: TyFun (a6989586621679974096 ~> (a6989586621679974096 ~> Ordering)) (a6989586621679974096 ~> ([a6989586621679974096] ~> [a6989586621679974096])) -> Type) (a6989586621679978723 :: a6989586621679974096 ~> (a6989586621679974096 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym0 :: TyFun (a6989586621679974096 ~> (a6989586621679974096 ~> Ordering)) (a6989586621679974096 ~> ([a6989586621679974096] ~> [a6989586621679974096])) -> Type) (a6989586621679978723 :: a6989586621679974096 ~> (a6989586621679974096 ~> Ordering)) = InsertBySym1 a6989586621679978723 |
data InsertBySym1 (a6989586621679978723 :: (~>) a6989586621679974096 ((~>) a6989586621679974096 Ordering)) :: (~>) a6989586621679974096 ((~>) [a6989586621679974096] [a6989586621679974096]) Source #
Instances
SingI d => SingI (InsertBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (InsertBySym1 d) Source # | |
SuppressUnusedWarnings (InsertBySym1 a6989586621679978723 :: TyFun a6989586621679974096 ([a6989586621679974096] ~> [a6989586621679974096]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym1 a6989586621679978723 :: TyFun a6989586621679974096 ([a6989586621679974096] ~> [a6989586621679974096]) -> Type) (a6989586621679978724 :: a6989586621679974096) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym1 a6989586621679978723 :: TyFun a6989586621679974096 ([a6989586621679974096] ~> [a6989586621679974096]) -> Type) (a6989586621679978724 :: a6989586621679974096) = InsertBySym2 a6989586621679978723 a6989586621679978724 |
data InsertBySym2 (a6989586621679978723 :: (~>) a6989586621679974096 ((~>) a6989586621679974096 Ordering)) (a6989586621679978724 :: a6989586621679974096) :: (~>) [a6989586621679974096] [a6989586621679974096] Source #
Instances
(SingI d1, SingI d2) => SingI (InsertBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing (InsertBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (InsertBySym2 a6989586621679978724 a6989586621679978723 :: TyFun [a6989586621679974096] [a6989586621679974096] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym2 a6989586621679978724 a6989586621679978723 :: TyFun [a] [a] -> Type) (a6989586621679978725 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym2 a6989586621679978724 a6989586621679978723 :: TyFun [a] [a] -> Type) (a6989586621679978725 :: [a]) = InsertBy a6989586621679978724 a6989586621679978723 a6989586621679978725 |
type InsertBySym3 (a6989586621679978723 :: (~>) a6989586621679974096 ((~>) a6989586621679974096 Ordering)) (a6989586621679978724 :: a6989586621679974096) (a6989586621679978725 :: [a6989586621679974096]) = InsertBy a6989586621679978723 a6989586621679978724 a6989586621679978725 Source #
data MaximumBySym0 :: forall a6989586621680490417 t6989586621680490416. (~>) ((~>) a6989586621680490417 ((~>) a6989586621680490417 Ordering)) ((~>) (t6989586621680490416 a6989586621680490417) a6989586621680490417) Source #
Instances
SFoldable t => SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing MaximumBySym0 Source # | |
SuppressUnusedWarnings (MaximumBySym0 :: TyFun (a6989586621680490417 ~> (a6989586621680490417 ~> Ordering)) (t6989586621680490416 a6989586621680490417 ~> a6989586621680490417) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym0 :: TyFun (a6989586621680490417 ~> (a6989586621680490417 ~> Ordering)) (t6989586621680490416 a6989586621680490417 ~> a6989586621680490417) -> Type) (a6989586621680490924 :: a6989586621680490417 ~> (a6989586621680490417 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym0 :: TyFun (a6989586621680490417 ~> (a6989586621680490417 ~> Ordering)) (t6989586621680490416 a6989586621680490417 ~> a6989586621680490417) -> Type) (a6989586621680490924 :: a6989586621680490417 ~> (a6989586621680490417 ~> Ordering)) = MaximumBySym1 a6989586621680490924 t6989586621680490416 :: TyFun (t6989586621680490416 a6989586621680490417) a6989586621680490417 -> Type |
data MaximumBySym1 (a6989586621680490924 :: (~>) a6989586621680490417 ((~>) a6989586621680490417 Ordering)) :: forall t6989586621680490416. (~>) (t6989586621680490416 a6989586621680490417) a6989586621680490417 Source #
Instances
(SFoldable t, SingI d) => SingI (MaximumBySym1 d t :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (MaximumBySym1 d t) Source # | |
SuppressUnusedWarnings (MaximumBySym1 a6989586621680490924 t6989586621680490416 :: TyFun (t6989586621680490416 a6989586621680490417) a6989586621680490417 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym1 a6989586621680490924 t :: TyFun (t a) a -> Type) (a6989586621680490925 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym1 a6989586621680490924 t :: TyFun (t a) a -> Type) (a6989586621680490925 :: t a) = MaximumBy a6989586621680490924 a6989586621680490925 |
type MaximumBySym2 (a6989586621680490924 :: (~>) a6989586621680490417 ((~>) a6989586621680490417 Ordering)) (a6989586621680490925 :: t6989586621680490416 a6989586621680490417) = MaximumBy a6989586621680490924 a6989586621680490925 Source #
data MinimumBySym0 :: forall a6989586621680490415 t6989586621680490414. (~>) ((~>) a6989586621680490415 ((~>) a6989586621680490415 Ordering)) ((~>) (t6989586621680490414 a6989586621680490415) a6989586621680490415) Source #
Instances
SFoldable t => SingI (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing MinimumBySym0 Source # | |
SuppressUnusedWarnings (MinimumBySym0 :: TyFun (a6989586621680490415 ~> (a6989586621680490415 ~> Ordering)) (t6989586621680490414 a6989586621680490415 ~> a6989586621680490415) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym0 :: TyFun (a6989586621680490415 ~> (a6989586621680490415 ~> Ordering)) (t6989586621680490414 a6989586621680490415 ~> a6989586621680490415) -> Type) (a6989586621680490899 :: a6989586621680490415 ~> (a6989586621680490415 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym0 :: TyFun (a6989586621680490415 ~> (a6989586621680490415 ~> Ordering)) (t6989586621680490414 a6989586621680490415 ~> a6989586621680490415) -> Type) (a6989586621680490899 :: a6989586621680490415 ~> (a6989586621680490415 ~> Ordering)) = MinimumBySym1 a6989586621680490899 t6989586621680490414 :: TyFun (t6989586621680490414 a6989586621680490415) a6989586621680490415 -> Type |
data MinimumBySym1 (a6989586621680490899 :: (~>) a6989586621680490415 ((~>) a6989586621680490415 Ordering)) :: forall t6989586621680490414. (~>) (t6989586621680490414 a6989586621680490415) a6989586621680490415 Source #
Instances
(SFoldable t, SingI d) => SingI (MinimumBySym1 d t :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable sing :: Sing (MinimumBySym1 d t) Source # | |
SuppressUnusedWarnings (MinimumBySym1 a6989586621680490899 t6989586621680490414 :: TyFun (t6989586621680490414 a6989586621680490415) a6989586621680490415 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym1 a6989586621680490899 t :: TyFun (t a) a -> Type) (a6989586621680490900 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym1 a6989586621680490899 t :: TyFun (t a) a -> Type) (a6989586621680490900 :: t a) = MinimumBy a6989586621680490899 a6989586621680490900 |
type MinimumBySym2 (a6989586621680490899 :: (~>) a6989586621680490415 ((~>) a6989586621680490415 Ordering)) (a6989586621680490900 :: t6989586621680490414 a6989586621680490415) = MinimumBy a6989586621680490899 a6989586621680490900 Source #
data GenericLengthSym0 :: forall a6989586621679974056 i6989586621679974055. (~>) [a6989586621679974056] i6989586621679974055 Source #
Instances
SNum i => SingI (GenericLengthSym0 :: TyFun [a] i -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a6989586621679974056] i6989586621679974055 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679978132 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679978132 :: [a]) = GenericLength a6989586621679978132 :: k2 |
type GenericLengthSym1 (a6989586621679978132 :: [a6989586621679974056]) = GenericLength a6989586621679978132 Source #
data GenericTakeSym0 :: forall i6989586621680096221 a6989586621680096222. (~>) i6989586621680096221 ((~>) [a6989586621680096222] [a6989586621680096222]) Source #
Instances
SuppressUnusedWarnings (GenericTakeSym0 :: TyFun i6989586621680096221 ([a6989586621680096222] ~> [a6989586621680096222]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericTakeSym0 :: TyFun i6989586621680096221 ([a6989586621680096222] ~> [a6989586621680096222]) -> Type) (a6989586621680097751 :: i6989586621680096221) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericTakeSym0 :: TyFun i6989586621680096221 ([a6989586621680096222] ~> [a6989586621680096222]) -> Type) (a6989586621680097751 :: i6989586621680096221) = GenericTakeSym1 a6989586621680097751 a6989586621680096222 :: TyFun [a6989586621680096222] [a6989586621680096222] -> Type |
data GenericTakeSym1 (a6989586621680097751 :: i6989586621680096221) :: forall a6989586621680096222. (~>) [a6989586621680096222] [a6989586621680096222] Source #
Instances
SuppressUnusedWarnings (GenericTakeSym1 a6989586621680097751 a6989586621680096222 :: TyFun [a6989586621680096222] [a6989586621680096222] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericTakeSym1 a6989586621680097751 a :: TyFun [a] [a] -> Type) (a6989586621680097752 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericTakeSym1 a6989586621680097751 a :: TyFun [a] [a] -> Type) (a6989586621680097752 :: [a]) = GenericTake a6989586621680097751 a6989586621680097752 |
type GenericTakeSym2 (a6989586621680097751 :: i6989586621680096221) (a6989586621680097752 :: [a6989586621680096222]) = GenericTake a6989586621680097751 a6989586621680097752 Source #
data GenericDropSym0 :: forall i6989586621680096219 a6989586621680096220. (~>) i6989586621680096219 ((~>) [a6989586621680096220] [a6989586621680096220]) Source #
Instances
SuppressUnusedWarnings (GenericDropSym0 :: TyFun i6989586621680096219 ([a6989586621680096220] ~> [a6989586621680096220]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericDropSym0 :: TyFun i6989586621680096219 ([a6989586621680096220] ~> [a6989586621680096220]) -> Type) (a6989586621680097741 :: i6989586621680096219) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericDropSym0 :: TyFun i6989586621680096219 ([a6989586621680096220] ~> [a6989586621680096220]) -> Type) (a6989586621680097741 :: i6989586621680096219) = GenericDropSym1 a6989586621680097741 a6989586621680096220 :: TyFun [a6989586621680096220] [a6989586621680096220] -> Type |
data GenericDropSym1 (a6989586621680097741 :: i6989586621680096219) :: forall a6989586621680096220. (~>) [a6989586621680096220] [a6989586621680096220] Source #
Instances
SuppressUnusedWarnings (GenericDropSym1 a6989586621680097741 a6989586621680096220 :: TyFun [a6989586621680096220] [a6989586621680096220] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericDropSym1 a6989586621680097741 a :: TyFun [a] [a] -> Type) (a6989586621680097742 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericDropSym1 a6989586621680097741 a :: TyFun [a] [a] -> Type) (a6989586621680097742 :: [a]) = GenericDrop a6989586621680097741 a6989586621680097742 |
type GenericDropSym2 (a6989586621680097741 :: i6989586621680096219) (a6989586621680097742 :: [a6989586621680096220]) = GenericDrop a6989586621680097741 a6989586621680097742 Source #
data GenericSplitAtSym0 :: forall i6989586621680096217 a6989586621680096218. (~>) i6989586621680096217 ((~>) [a6989586621680096218] ([a6989586621680096218], [a6989586621680096218])) Source #
Instances
SuppressUnusedWarnings (GenericSplitAtSym0 :: TyFun i6989586621680096217 ([a6989586621680096218] ~> ([a6989586621680096218], [a6989586621680096218])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericSplitAtSym0 :: TyFun i6989586621680096217 ([a6989586621680096218] ~> ([a6989586621680096218], [a6989586621680096218])) -> Type) (a6989586621680097731 :: i6989586621680096217) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericSplitAtSym0 :: TyFun i6989586621680096217 ([a6989586621680096218] ~> ([a6989586621680096218], [a6989586621680096218])) -> Type) (a6989586621680097731 :: i6989586621680096217) = GenericSplitAtSym1 a6989586621680097731 a6989586621680096218 :: TyFun [a6989586621680096218] ([a6989586621680096218], [a6989586621680096218]) -> Type |
data GenericSplitAtSym1 (a6989586621680097731 :: i6989586621680096217) :: forall a6989586621680096218. (~>) [a6989586621680096218] ([a6989586621680096218], [a6989586621680096218]) Source #
Instances
SuppressUnusedWarnings (GenericSplitAtSym1 a6989586621680097731 a6989586621680096218 :: TyFun [a6989586621680096218] ([a6989586621680096218], [a6989586621680096218]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericSplitAtSym1 a6989586621680097731 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621680097732 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericSplitAtSym1 a6989586621680097731 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621680097732 :: [a]) = GenericSplitAt a6989586621680097731 a6989586621680097732 |
type GenericSplitAtSym2 (a6989586621680097731 :: i6989586621680096217) (a6989586621680097732 :: [a6989586621680096218]) = GenericSplitAt a6989586621680097731 a6989586621680097732 Source #
data GenericIndexSym0 :: forall a6989586621680096216 i6989586621680096215. (~>) [a6989586621680096216] ((~>) i6989586621680096215 a6989586621680096216) Source #
Instances
SuppressUnusedWarnings (GenericIndexSym0 :: TyFun [a6989586621680096216] (i6989586621680096215 ~> a6989586621680096216) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericIndexSym0 :: TyFun [a6989586621680096216] (i6989586621680096215 ~> a6989586621680096216) -> Type) (a6989586621680097721 :: [a6989586621680096216]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericIndexSym0 :: TyFun [a6989586621680096216] (i6989586621680096215 ~> a6989586621680096216) -> Type) (a6989586621680097721 :: [a6989586621680096216]) = GenericIndexSym1 a6989586621680097721 i6989586621680096215 :: TyFun i6989586621680096215 a6989586621680096216 -> Type |
data GenericIndexSym1 (a6989586621680097721 :: [a6989586621680096216]) :: forall i6989586621680096215. (~>) i6989586621680096215 a6989586621680096216 Source #
Instances
SuppressUnusedWarnings (GenericIndexSym1 a6989586621680097721 i6989586621680096215 :: TyFun i6989586621680096215 a6989586621680096216 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericIndexSym1 a6989586621680097721 i :: TyFun i a -> Type) (a6989586621680097722 :: i) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericIndexSym1 a6989586621680097721 i :: TyFun i a -> Type) (a6989586621680097722 :: i) = GenericIndex a6989586621680097721 a6989586621680097722 |
type GenericIndexSym2 (a6989586621680097721 :: [a6989586621680096216]) (a6989586621680097722 :: i6989586621680096215) = GenericIndex a6989586621680097721 a6989586621680097722 Source #
data GenericReplicateSym0 :: forall i6989586621680096213 a6989586621680096214. (~>) i6989586621680096213 ((~>) a6989586621680096214 [a6989586621680096214]) Source #
Instances
SuppressUnusedWarnings (GenericReplicateSym0 :: TyFun i6989586621680096213 (a6989586621680096214 ~> [a6989586621680096214]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericReplicateSym0 :: TyFun i6989586621680096213 (a6989586621680096214 ~> [a6989586621680096214]) -> Type) (a6989586621680097711 :: i6989586621680096213) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericReplicateSym0 :: TyFun i6989586621680096213 (a6989586621680096214 ~> [a6989586621680096214]) -> Type) (a6989586621680097711 :: i6989586621680096213) = GenericReplicateSym1 a6989586621680097711 a6989586621680096214 :: TyFun a6989586621680096214 [a6989586621680096214] -> Type |
data GenericReplicateSym1 (a6989586621680097711 :: i6989586621680096213) :: forall a6989586621680096214. (~>) a6989586621680096214 [a6989586621680096214] Source #
Instances
SuppressUnusedWarnings (GenericReplicateSym1 a6989586621680097711 a6989586621680096214 :: TyFun a6989586621680096214 [a6989586621680096214] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericReplicateSym1 a6989586621680097711 a :: TyFun a [a] -> Type) (a6989586621680097712 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericReplicateSym1 a6989586621680097711 a :: TyFun a [a] -> Type) (a6989586621680097712 :: a) = GenericReplicate a6989586621680097711 a6989586621680097712 |
type GenericReplicateSym2 (a6989586621680097711 :: i6989586621680096213) (a6989586621680097712 :: a6989586621680096214) = GenericReplicate a6989586621680097711 a6989586621680097712 Source #