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
- data family Sing :: k -> Type
- type SList = (Sing :: [a] -> Type)
- type family (a :: [a]) ++ (a :: [a]) :: [a] where ...
- (%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a])
- type family Head (a :: [a]) :: a where ...
- sHead :: forall a (t :: [a]). Sing t -> Sing (Apply HeadSym0 t :: a)
- type family Last (a :: [a]) :: a where ...
- sLast :: forall a (t :: [a]). Sing t -> Sing (Apply LastSym0 t :: a)
- type family Tail (a :: [a]) :: [a] where ...
- sTail :: forall a (t :: [a]). Sing t -> Sing (Apply TailSym0 t :: [a])
- type family Init (a :: [a]) :: [a] where ...
- sInit :: forall a (t :: [a]). Sing t -> Sing (Apply InitSym0 t :: [a])
- type family Null (arg :: t a) :: Bool
- sNull :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply NullSym0 t :: Bool)
- type family Length (arg :: t a) :: Nat
- sLength :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply LengthSym0 t :: Nat)
- type family Map (a :: (~>) a b) (a :: [a]) :: [b] where ...
- sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b])
- type family Reverse (a :: [a]) :: [a] where ...
- sReverse :: forall a (t :: [a]). Sing t -> Sing (Apply ReverseSym0 t :: [a])
- type family Intersperse (a :: a) (a :: [a]) :: [a] where ...
- sIntersperse :: forall a (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a])
- type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ...
- sIntercalate :: forall a (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a])
- type family Transpose (a :: [[a]]) :: [[a]] where ...
- sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]])
- type family Subsequences (a :: [a]) :: [[a]] where ...
- sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]])
- type family Permutations (a :: [a]) :: [[a]] where ...
- sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]])
- type family Foldl (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
- sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b)
- type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
- sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b)
- type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
- sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a)
- type family Foldl1' (a :: (~>) a ((~>) a a)) (a :: [a]) :: a where ...
- sFoldl1' :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a)
- type family Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b
- sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b)
- type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
- sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a)
- type family Concat (a :: t [a]) :: [a] where ...
- sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a])
- type family ConcatMap (a :: (~>) a [b]) (a :: t a) :: [b] where ...
- sConcatMap :: forall t a b (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b])
- type family And (a :: t Bool) :: Bool where ...
- sAnd :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool)
- type family Or (a :: t Bool) :: Bool where ...
- sOr :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool)
- type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ...
- sAny :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool)
- type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ...
- sAll :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool)
- type family Sum (arg :: t a) :: a
- sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a)
- type family Product (arg :: t a) :: a
- sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a)
- type family Maximum (arg :: t a) :: a
- sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a)
- type family Minimum (arg :: t a) :: a
- sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a)
- type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: [b] where ...
- sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b])
- type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
- sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a])
- type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: [b] where ...
- sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b])
- type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
- sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a])
- type family MapAccumL (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
- sMapAccumL :: forall t a b c (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (a, t c))
- type family MapAccumR (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
- sMapAccumR :: forall t a b c (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c))
- type family Replicate (a :: Nat) (a :: a) :: [a] where ...
- sReplicate :: forall a (t :: Nat) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a])
- type family Unfoldr (a :: (~>) b (Maybe (a, b))) (a :: b) :: [a] where ...
- sUnfoldr :: forall b a (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a])
- type family Take (a :: Nat) (a :: [a]) :: [a] where ...
- sTake :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a])
- type family Drop (a :: Nat) (a :: [a]) :: [a] where ...
- sDrop :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a])
- type family SplitAt (a :: Nat) (a :: [a]) :: ([a], [a]) where ...
- sSplitAt :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a]))
- type family TakeWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sTakeWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a])
- type family DropWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sDropWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a])
- type family DropWhileEnd (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sDropWhileEnd :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a])
- type family Span (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sSpan :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a]))
- type family Break (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sBreak :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a]))
- type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ...
- type family Group (a :: [a]) :: [[a]] where ...
- sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [[a]])
- type family Inits (a :: [a]) :: [[a]] where ...
- sInits :: forall a (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: [[a]])
- type family Tails (a :: [a]) :: [[a]] where ...
- sTails :: forall a (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: [[a]])
- type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsPrefixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool)
- type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsSuffixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool)
- type family IsInfixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsInfixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool)
- type family Elem (arg :: a) (arg :: t a) :: Bool
- sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool)
- type family NotElem (a :: a) (a :: t a) :: Bool where ...
- sNotElem :: forall t a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool)
- type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ...
- sLookup :: forall a b (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b)
- type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ...
- sFind :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a)
- type family Filter (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
- type family Partition (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
- type family (a :: [a]) !! (a :: Nat) :: a where ...
- (%!!) :: forall a (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a)
- type family ElemIndex (a :: a) (a :: [a]) :: Maybe Nat where ...
- sElemIndex :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat)
- type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ...
- sElemIndices :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat])
- type family FindIndex (a :: (~>) a Bool) (a :: [a]) :: Maybe Nat where ...
- sFindIndex :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat)
- type family FindIndices (a :: (~>) a Bool) (a :: [a]) :: [Nat] where ...
- sFindIndices :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat])
- type family Zip (a :: [a]) (a :: [b]) :: [(a, b)] where ...
- sZip :: forall a b (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)])
- type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ...
- sZip3 :: forall a b c (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)])
- type family Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ...
- type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ...
- type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ...
- type family Zip7 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [(a, b, c, d, e, f, g)] where ...
- type family ZipWith (a :: (~>) a ((~>) b c)) (a :: [a]) (a :: [b]) :: [c] where ...
- sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c])
- type family ZipWith3 (a :: (~>) a ((~>) b ((~>) c d))) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ...
- sZipWith3 :: forall a b c d (t :: (~>) a ((~>) b ((~>) c d))) (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d])
- type family ZipWith4 (a :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ...
- type family ZipWith5 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ...
- type family ZipWith6 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ...
- type family ZipWith7 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ...
- type family Unzip (a :: [(a, b)]) :: ([a], [b]) where ...
- sUnzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b]))
- type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ...
- sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c]))
- type family Unzip4 (a :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
- sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d]))
- type family Unzip5 (a :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ...
- sUnzip5 :: forall a b c d e (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e]))
- type family Unzip6 (a :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ...
- sUnzip6 :: forall a b c d e f (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f]))
- type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
- sUnzip7 :: forall a b c d e f g (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g]))
- type family Unlines (a :: [Symbol]) :: Symbol where ...
- sUnlines :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnlinesSym0 t :: Symbol)
- type family Unwords (a :: [Symbol]) :: Symbol where ...
- sUnwords :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnwordsSym0 t :: Symbol)
- type family Nub (a :: [a]) :: [a] where ...
- sNub :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply NubSym0 t :: [a])
- type family Delete (a :: a) (a :: [a]) :: [a] where ...
- sDelete :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a])
- type family (a :: [a]) \\ (a :: [a]) :: [a] where ...
- (%\\) :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (\\@#@$) t) t :: [a])
- type family Union (a :: [a]) (a :: [a]) :: [a] where ...
- sUnion :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a])
- type family Intersect (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersect :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a])
- type family Insert (a :: a) (a :: [a]) :: [a] where ...
- sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a])
- type family Sort (a :: [a]) :: [a] where ...
- sSort :: forall a (t :: [a]). SOrd a => Sing t -> Sing (Apply SortSym0 t :: [a])
- type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [a] where ...
- sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a])
- type family DeleteBy (a :: (~>) a ((~>) a Bool)) (a :: a) (a :: [a]) :: [a] where ...
- sDeleteBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a])
- type family DeleteFirstsBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sDeleteFirstsBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a])
- type family UnionBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sUnionBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a])
- type family IntersectBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersectBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a])
- type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [[a]] where ...
- sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]])
- type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: [a]) :: [a] where ...
- sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a])
- type family InsertBy (a :: (~>) a ((~>) a Ordering)) (a :: a) (a :: [a]) :: [a] where ...
- sInsertBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a])
- type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
- sMaximumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a)
- type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
- sMinimumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a)
- type family GenericLength (a :: [a]) :: i where ...
- sGenericLength :: forall i a (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i)
- type family GenericTake (a :: i) (a :: [a]) :: [a] where ...
- type family GenericDrop (a :: i) (a :: [a]) :: [a] where ...
- type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ...
- type family GenericIndex (a :: [a]) (a :: i) :: a where ...
- type family GenericReplicate (a :: i) (a :: a) :: [a] where ...
- type NilSym0 = '[]
- data (:@#@$) :: forall (a3530822107858468865 :: Type). (~>) a3530822107858468865 ((~>) [a3530822107858468865] [(a3530822107858468865 :: Type)])
- data (:@#@$$) (t6989586621679291660 :: (a3530822107858468865 :: Type)) :: (~>) [a3530822107858468865] [(a3530822107858468865 :: Type)]
- type (:@#@$$$) (t6989586621679291660 :: a3530822107858468865) (t6989586621679291661 :: [a3530822107858468865]) = (:) t6989586621679291660 t6989586621679291661
- type (++@#@$$$) (a6989586621679511994 :: [a6989586621679511797]) (a6989586621679511995 :: [a6989586621679511797]) = (++) a6989586621679511994 a6989586621679511995
- data (++@#@$$) (a6989586621679511994 :: [a6989586621679511797]) :: (~>) [a6989586621679511797] [a6989586621679511797]
- data (++@#@$) :: forall a6989586621679511797. (~>) [a6989586621679511797] ((~>) [a6989586621679511797] [a6989586621679511797])
- data HeadSym0 :: forall a6989586621679929539. (~>) [a6989586621679929539] a6989586621679929539
- type HeadSym1 (a6989586621679940062 :: [a6989586621679929539]) = Head a6989586621679940062
- data LastSym0 :: forall a6989586621679929538. (~>) [a6989586621679929538] a6989586621679929538
- type LastSym1 (a6989586621679940057 :: [a6989586621679929538]) = Last a6989586621679940057
- data TailSym0 :: forall a6989586621679929537. (~>) [a6989586621679929537] [a6989586621679929537]
- type TailSym1 (a6989586621679940054 :: [a6989586621679929537]) = Tail a6989586621679940054
- data InitSym0 :: forall a6989586621679929536. (~>) [a6989586621679929536] [a6989586621679929536]
- type InitSym1 (a6989586621679940040 :: [a6989586621679929536]) = Init a6989586621679940040
- data NullSym0 :: forall a6989586621680438541 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438541) Bool
- type NullSym1 (arg6989586621680439189 :: t6989586621680438526 a6989586621680438541) = Null arg6989586621680439189
- data LengthSym0 :: forall a6989586621680438542 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438542) Nat
- type LengthSym1 (arg6989586621680439191 :: t6989586621680438526 a6989586621680438542) = Length arg6989586621680439191
- data MapSym0 :: forall a6989586621679511798 b6989586621679511799. (~>) ((~>) a6989586621679511798 b6989586621679511799) ((~>) [a6989586621679511798] [b6989586621679511799])
- data MapSym1 (a6989586621679512002 :: (~>) a6989586621679511798 b6989586621679511799) :: (~>) [a6989586621679511798] [b6989586621679511799]
- type MapSym2 (a6989586621679512002 :: (~>) a6989586621679511798 b6989586621679511799) (a6989586621679512003 :: [a6989586621679511798]) = Map a6989586621679512002 a6989586621679512003
- data ReverseSym0 :: forall a6989586621679929534. (~>) [a6989586621679929534] [a6989586621679929534]
- type ReverseSym1 (a6989586621679939993 :: [a6989586621679929534]) = Reverse a6989586621679939993
- data IntersperseSym0 :: forall a6989586621679929533. (~>) a6989586621679929533 ((~>) [a6989586621679929533] [a6989586621679929533])
- data IntersperseSym1 (a6989586621679939980 :: a6989586621679929533) :: (~>) [a6989586621679929533] [a6989586621679929533]
- type IntersperseSym2 (a6989586621679939980 :: a6989586621679929533) (a6989586621679939981 :: [a6989586621679929533]) = Intersperse a6989586621679939980 a6989586621679939981
- data IntercalateSym0 :: forall a6989586621679929532. (~>) [a6989586621679929532] ((~>) [[a6989586621679929532]] [a6989586621679929532])
- data IntercalateSym1 (a6989586621679939987 :: [a6989586621679929532]) :: (~>) [[a6989586621679929532]] [a6989586621679929532]
- type IntercalateSym2 (a6989586621679939987 :: [a6989586621679929532]) (a6989586621679939988 :: [[a6989586621679929532]]) = Intercalate a6989586621679939987 a6989586621679939988
- data TransposeSym0 :: forall a6989586621679929419. (~>) [[a6989586621679929419]] [[a6989586621679929419]]
- type TransposeSym1 (a6989586621679940065 :: [[a6989586621679929419]]) = Transpose a6989586621679940065
- data SubsequencesSym0 :: forall a6989586621679929531. (~>) [a6989586621679929531] [[a6989586621679929531]]
- type SubsequencesSym1 (a6989586621679939977 :: [a6989586621679929531]) = Subsequences a6989586621679939977
- data PermutationsSym0 :: forall a6989586621679929528. (~>) [a6989586621679929528] [[a6989586621679929528]]
- type PermutationsSym1 (a6989586621679939859 :: [a6989586621679929528]) = Permutations a6989586621679939859
- data FoldlSym0 :: forall a6989586621680438535 b6989586621680438534 t6989586621680438526. (~>) ((~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) ((~>) b6989586621680438534 ((~>) (t6989586621680438526 a6989586621680438535) b6989586621680438534))
- data FoldlSym1 (arg6989586621680439167 :: (~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) :: forall t6989586621680438526. (~>) b6989586621680438534 ((~>) (t6989586621680438526 a6989586621680438535) b6989586621680438534)
- data FoldlSym2 (arg6989586621680439167 :: (~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) (arg6989586621680439168 :: b6989586621680438534) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438535) b6989586621680438534
- type FoldlSym3 (arg6989586621680439167 :: (~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) (arg6989586621680439168 :: b6989586621680438534) (arg6989586621680439169 :: t6989586621680438526 a6989586621680438535) = Foldl arg6989586621680439167 arg6989586621680439168 arg6989586621680439169
- data Foldl'Sym0 :: forall a6989586621680438537 b6989586621680438536 t6989586621680438526. (~>) ((~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) ((~>) b6989586621680438536 ((~>) (t6989586621680438526 a6989586621680438537) b6989586621680438536))
- data Foldl'Sym1 (arg6989586621680439173 :: (~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) :: forall t6989586621680438526. (~>) b6989586621680438536 ((~>) (t6989586621680438526 a6989586621680438537) b6989586621680438536)
- data Foldl'Sym2 (arg6989586621680439173 :: (~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) (arg6989586621680439174 :: b6989586621680438536) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438537) b6989586621680438536
- type Foldl'Sym3 (arg6989586621680439173 :: (~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) (arg6989586621680439174 :: b6989586621680438536) (arg6989586621680439175 :: t6989586621680438526 a6989586621680438537) = Foldl' arg6989586621680439173 arg6989586621680439174 arg6989586621680439175
- data Foldl1Sym0 :: forall a6989586621680438539 t6989586621680438526. (~>) ((~>) a6989586621680438539 ((~>) a6989586621680438539 a6989586621680438539)) ((~>) (t6989586621680438526 a6989586621680438539) a6989586621680438539)
- data Foldl1Sym1 (arg6989586621680439183 :: (~>) a6989586621680438539 ((~>) a6989586621680438539 a6989586621680438539)) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438539) a6989586621680438539
- type Foldl1Sym2 (arg6989586621680439183 :: (~>) a6989586621680438539 ((~>) a6989586621680438539 a6989586621680438539)) (arg6989586621680439184 :: t6989586621680438526 a6989586621680438539) = Foldl1 arg6989586621680439183 arg6989586621680439184
- data Foldl1'Sym0 :: forall a6989586621679929524. (~>) ((~>) a6989586621679929524 ((~>) a6989586621679929524 a6989586621679929524)) ((~>) [a6989586621679929524] a6989586621679929524)
- data Foldl1'Sym1 (a6989586621679939852 :: (~>) a6989586621679929524 ((~>) a6989586621679929524 a6989586621679929524)) :: (~>) [a6989586621679929524] a6989586621679929524
- type Foldl1'Sym2 (a6989586621679939852 :: (~>) a6989586621679929524 ((~>) a6989586621679929524 a6989586621679929524)) (a6989586621679939853 :: [a6989586621679929524]) = Foldl1' a6989586621679939852 a6989586621679939853
- data FoldrSym0 :: forall a6989586621680438530 b6989586621680438531 t6989586621680438526. (~>) ((~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) ((~>) b6989586621680438531 ((~>) (t6989586621680438526 a6989586621680438530) b6989586621680438531))
- data FoldrSym1 (arg6989586621680439155 :: (~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) :: forall t6989586621680438526. (~>) b6989586621680438531 ((~>) (t6989586621680438526 a6989586621680438530) b6989586621680438531)
- data FoldrSym2 (arg6989586621680439155 :: (~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) (arg6989586621680439156 :: b6989586621680438531) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438530) b6989586621680438531
- type FoldrSym3 (arg6989586621680439155 :: (~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) (arg6989586621680439156 :: b6989586621680438531) (arg6989586621680439157 :: t6989586621680438526 a6989586621680438530) = Foldr arg6989586621680439155 arg6989586621680439156 arg6989586621680439157
- data Foldr1Sym0 :: forall a6989586621680438538 t6989586621680438526. (~>) ((~>) a6989586621680438538 ((~>) a6989586621680438538 a6989586621680438538)) ((~>) (t6989586621680438526 a6989586621680438538) a6989586621680438538)
- data Foldr1Sym1 (arg6989586621680439179 :: (~>) a6989586621680438538 ((~>) a6989586621680438538 a6989586621680438538)) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438538) a6989586621680438538
- type Foldr1Sym2 (arg6989586621680439179 :: (~>) a6989586621680438538 ((~>) a6989586621680438538 a6989586621680438538)) (arg6989586621680439180 :: t6989586621680438526 a6989586621680438538) = Foldr1 arg6989586621680439179 arg6989586621680439180
- data ConcatSym0 :: forall a6989586621680438452 t6989586621680438451. (~>) (t6989586621680438451 [a6989586621680438452]) [a6989586621680438452]
- type ConcatSym1 (a6989586621680439037 :: t6989586621680438451 [a6989586621680438452]) = Concat a6989586621680439037
- data ConcatMapSym0 :: forall a6989586621680438449 b6989586621680438450 t6989586621680438448. (~>) ((~>) a6989586621680438449 [b6989586621680438450]) ((~>) (t6989586621680438448 a6989586621680438449) [b6989586621680438450])
- data ConcatMapSym1 (a6989586621680439021 :: (~>) a6989586621680438449 [b6989586621680438450]) :: forall t6989586621680438448. (~>) (t6989586621680438448 a6989586621680438449) [b6989586621680438450]
- type ConcatMapSym2 (a6989586621680439021 :: (~>) a6989586621680438449 [b6989586621680438450]) (a6989586621680439022 :: t6989586621680438448 a6989586621680438449) = ConcatMap a6989586621680439021 a6989586621680439022
- data AndSym0 :: forall t6989586621680438447. (~>) (t6989586621680438447 Bool) Bool
- type AndSym1 (a6989586621680439012 :: t6989586621680438447 Bool) = And a6989586621680439012
- data OrSym0 :: forall t6989586621680438446. (~>) (t6989586621680438446 Bool) Bool
- type OrSym1 (a6989586621680439003 :: t6989586621680438446 Bool) = Or a6989586621680439003
- data AnySym0 :: forall a6989586621680438445 t6989586621680438444. (~>) ((~>) a6989586621680438445 Bool) ((~>) (t6989586621680438444 a6989586621680438445) Bool)
- data AnySym1 (a6989586621680438990 :: (~>) a6989586621680438445 Bool) :: forall t6989586621680438444. (~>) (t6989586621680438444 a6989586621680438445) Bool
- type AnySym2 (a6989586621680438990 :: (~>) a6989586621680438445 Bool) (a6989586621680438991 :: t6989586621680438444 a6989586621680438445) = Any a6989586621680438990 a6989586621680438991
- data AllSym0 :: forall a6989586621680438443 t6989586621680438442. (~>) ((~>) a6989586621680438443 Bool) ((~>) (t6989586621680438442 a6989586621680438443) Bool)
- data AllSym1 (a6989586621680438977 :: (~>) a6989586621680438443 Bool) :: forall t6989586621680438442. (~>) (t6989586621680438442 a6989586621680438443) Bool
- type AllSym2 (a6989586621680438977 :: (~>) a6989586621680438443 Bool) (a6989586621680438978 :: t6989586621680438442 a6989586621680438443) = All a6989586621680438977 a6989586621680438978
- data SumSym0 :: forall a6989586621680438546 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438546) a6989586621680438546
- type SumSym1 (arg6989586621680439201 :: t6989586621680438526 a6989586621680438546) = Sum arg6989586621680439201
- data ProductSym0 :: forall a6989586621680438547 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438547) a6989586621680438547
- type ProductSym1 (arg6989586621680439203 :: t6989586621680438526 a6989586621680438547) = Product arg6989586621680439203
- data MaximumSym0 :: forall a6989586621680438544 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438544) a6989586621680438544
- type MaximumSym1 (arg6989586621680439197 :: t6989586621680438526 a6989586621680438544) = Maximum arg6989586621680439197
- data MinimumSym0 :: forall a6989586621680438545 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438545) a6989586621680438545
- type MinimumSym1 (arg6989586621680439199 :: t6989586621680438526 a6989586621680438545) = Minimum arg6989586621680439199
- data ScanlSym0 :: forall a6989586621679929517 b6989586621679929516. (~>) ((~>) b6989586621679929516 ((~>) a6989586621679929517 b6989586621679929516)) ((~>) b6989586621679929516 ((~>) [a6989586621679929517] [b6989586621679929516]))
- data ScanlSym1 (a6989586621679939625 :: (~>) b6989586621679929516 ((~>) a6989586621679929517 b6989586621679929516)) :: (~>) b6989586621679929516 ((~>) [a6989586621679929517] [b6989586621679929516])
- data ScanlSym2 (a6989586621679939625 :: (~>) b6989586621679929516 ((~>) a6989586621679929517 b6989586621679929516)) (a6989586621679939626 :: b6989586621679929516) :: (~>) [a6989586621679929517] [b6989586621679929516]
- type ScanlSym3 (a6989586621679939625 :: (~>) b6989586621679929516 ((~>) a6989586621679929517 b6989586621679929516)) (a6989586621679939626 :: b6989586621679929516) (a6989586621679939627 :: [a6989586621679929517]) = Scanl a6989586621679939625 a6989586621679939626 a6989586621679939627
- data Scanl1Sym0 :: forall a6989586621679929515. (~>) ((~>) a6989586621679929515 ((~>) a6989586621679929515 a6989586621679929515)) ((~>) [a6989586621679929515] [a6989586621679929515])
- data Scanl1Sym1 (a6989586621679939639 :: (~>) a6989586621679929515 ((~>) a6989586621679929515 a6989586621679929515)) :: (~>) [a6989586621679929515] [a6989586621679929515]
- type Scanl1Sym2 (a6989586621679939639 :: (~>) a6989586621679929515 ((~>) a6989586621679929515 a6989586621679929515)) (a6989586621679939640 :: [a6989586621679929515]) = Scanl1 a6989586621679939639 a6989586621679939640
- data ScanrSym0 :: forall a6989586621679929513 b6989586621679929514. (~>) ((~>) a6989586621679929513 ((~>) b6989586621679929514 b6989586621679929514)) ((~>) b6989586621679929514 ((~>) [a6989586621679929513] [b6989586621679929514]))
- data ScanrSym1 (a6989586621679939604 :: (~>) a6989586621679929513 ((~>) b6989586621679929514 b6989586621679929514)) :: (~>) b6989586621679929514 ((~>) [a6989586621679929513] [b6989586621679929514])
- data ScanrSym2 (a6989586621679939604 :: (~>) a6989586621679929513 ((~>) b6989586621679929514 b6989586621679929514)) (a6989586621679939605 :: b6989586621679929514) :: (~>) [a6989586621679929513] [b6989586621679929514]
- type ScanrSym3 (a6989586621679939604 :: (~>) a6989586621679929513 ((~>) b6989586621679929514 b6989586621679929514)) (a6989586621679939605 :: b6989586621679929514) (a6989586621679939606 :: [a6989586621679929513]) = Scanr a6989586621679939604 a6989586621679939605 a6989586621679939606
- data Scanr1Sym0 :: forall a6989586621679929512. (~>) ((~>) a6989586621679929512 ((~>) a6989586621679929512 a6989586621679929512)) ((~>) [a6989586621679929512] [a6989586621679929512])
- data Scanr1Sym1 (a6989586621679939580 :: (~>) a6989586621679929512 ((~>) a6989586621679929512 a6989586621679929512)) :: (~>) [a6989586621679929512] [a6989586621679929512]
- type Scanr1Sym2 (a6989586621679939580 :: (~>) a6989586621679929512 ((~>) a6989586621679929512 a6989586621679929512)) (a6989586621679939581 :: [a6989586621679929512]) = Scanr1 a6989586621679939580 a6989586621679939581
- data MapAccumLSym0 :: forall a6989586621680740545 b6989586621680740546 c6989586621680740547 t6989586621680740544. (~>) ((~>) a6989586621680740545 ((~>) b6989586621680740546 (a6989586621680740545, c6989586621680740547))) ((~>) a6989586621680740545 ((~>) (t6989586621680740544 b6989586621680740546) (a6989586621680740545, t6989586621680740544 c6989586621680740547)))
- data MapAccumLSym1 (a6989586621680741084 :: (~>) a6989586621680740545 ((~>) b6989586621680740546 (a6989586621680740545, c6989586621680740547))) :: forall t6989586621680740544. (~>) a6989586621680740545 ((~>) (t6989586621680740544 b6989586621680740546) (a6989586621680740545, t6989586621680740544 c6989586621680740547))
- data MapAccumLSym2 (a6989586621680741084 :: (~>) a6989586621680740545 ((~>) b6989586621680740546 (a6989586621680740545, c6989586621680740547))) (a6989586621680741085 :: a6989586621680740545) :: forall t6989586621680740544. (~>) (t6989586621680740544 b6989586621680740546) (a6989586621680740545, t6989586621680740544 c6989586621680740547)
- type MapAccumLSym3 (a6989586621680741084 :: (~>) a6989586621680740545 ((~>) b6989586621680740546 (a6989586621680740545, c6989586621680740547))) (a6989586621680741085 :: a6989586621680740545) (a6989586621680741086 :: t6989586621680740544 b6989586621680740546) = MapAccumL a6989586621680741084 a6989586621680741085 a6989586621680741086
- data MapAccumRSym0 :: forall a6989586621680740541 b6989586621680740542 c6989586621680740543 t6989586621680740540. (~>) ((~>) a6989586621680740541 ((~>) b6989586621680740542 (a6989586621680740541, c6989586621680740543))) ((~>) a6989586621680740541 ((~>) (t6989586621680740540 b6989586621680740542) (a6989586621680740541, t6989586621680740540 c6989586621680740543)))
- data MapAccumRSym1 (a6989586621680741067 :: (~>) a6989586621680740541 ((~>) b6989586621680740542 (a6989586621680740541, c6989586621680740543))) :: forall t6989586621680740540. (~>) a6989586621680740541 ((~>) (t6989586621680740540 b6989586621680740542) (a6989586621680740541, t6989586621680740540 c6989586621680740543))
- data MapAccumRSym2 (a6989586621680741067 :: (~>) a6989586621680740541 ((~>) b6989586621680740542 (a6989586621680740541, c6989586621680740543))) (a6989586621680741068 :: a6989586621680740541) :: forall t6989586621680740540. (~>) (t6989586621680740540 b6989586621680740542) (a6989586621680740541, t6989586621680740540 c6989586621680740543)
- type MapAccumRSym3 (a6989586621680741067 :: (~>) a6989586621680740541 ((~>) b6989586621680740542 (a6989586621680740541, c6989586621680740543))) (a6989586621680741068 :: a6989586621680740541) (a6989586621680741069 :: t6989586621680740540 b6989586621680740542) = MapAccumR a6989586621680741067 a6989586621680741068 a6989586621680741069
- data ReplicateSym0 :: forall a6989586621679929420. (~>) Nat ((~>) a6989586621679929420 [a6989586621679929420])
- data ReplicateSym1 (a6989586621679938722 :: Nat) :: forall a6989586621679929420. (~>) a6989586621679929420 [a6989586621679929420]
- type ReplicateSym2 (a6989586621679938722 :: Nat) (a6989586621679938723 :: a6989586621679929420) = Replicate a6989586621679938722 a6989586621679938723
- data UnfoldrSym0 :: forall a6989586621679929505 b6989586621679929504. (~>) ((~>) b6989586621679929504 (Maybe (a6989586621679929505, b6989586621679929504))) ((~>) b6989586621679929504 [a6989586621679929505])
- data UnfoldrSym1 (a6989586621679939438 :: (~>) b6989586621679929504 (Maybe (a6989586621679929505, b6989586621679929504))) :: (~>) b6989586621679929504 [a6989586621679929505]
- type UnfoldrSym2 (a6989586621679939438 :: (~>) b6989586621679929504 (Maybe (a6989586621679929505, b6989586621679929504))) (a6989586621679939439 :: b6989586621679929504) = Unfoldr a6989586621679939438 a6989586621679939439
- data TakeSym0 :: forall a6989586621679929436. (~>) Nat ((~>) [a6989586621679929436] [a6989586621679929436])
- data TakeSym1 (a6989586621679938818 :: Nat) :: forall a6989586621679929436. (~>) [a6989586621679929436] [a6989586621679929436]
- type TakeSym2 (a6989586621679938818 :: Nat) (a6989586621679938819 :: [a6989586621679929436]) = Take a6989586621679938818 a6989586621679938819
- data DropSym0 :: forall a6989586621679929435. (~>) Nat ((~>) [a6989586621679929435] [a6989586621679929435])
- data DropSym1 (a6989586621679938804 :: Nat) :: forall a6989586621679929435. (~>) [a6989586621679929435] [a6989586621679929435]
- type DropSym2 (a6989586621679938804 :: Nat) (a6989586621679938805 :: [a6989586621679929435]) = Drop a6989586621679938804 a6989586621679938805
- data SplitAtSym0 :: forall a6989586621679929434. (~>) Nat ((~>) [a6989586621679929434] ([a6989586621679929434], [a6989586621679929434]))
- data SplitAtSym1 (a6989586621679938832 :: Nat) :: forall a6989586621679929434. (~>) [a6989586621679929434] ([a6989586621679929434], [a6989586621679929434])
- type SplitAtSym2 (a6989586621679938832 :: Nat) (a6989586621679938833 :: [a6989586621679929434]) = SplitAt a6989586621679938832 a6989586621679938833
- data TakeWhileSym0 :: forall a6989586621679929441. (~>) ((~>) a6989586621679929441 Bool) ((~>) [a6989586621679929441] [a6989586621679929441])
- data TakeWhileSym1 (a6989586621679938976 :: (~>) a6989586621679929441 Bool) :: (~>) [a6989586621679929441] [a6989586621679929441]
- type TakeWhileSym2 (a6989586621679938976 :: (~>) a6989586621679929441 Bool) (a6989586621679938977 :: [a6989586621679929441]) = TakeWhile a6989586621679938976 a6989586621679938977
- data DropWhileSym0 :: forall a6989586621679929440. (~>) ((~>) a6989586621679929440 Bool) ((~>) [a6989586621679929440] [a6989586621679929440])
- data DropWhileSym1 (a6989586621679938958 :: (~>) a6989586621679929440 Bool) :: (~>) [a6989586621679929440] [a6989586621679929440]
- type DropWhileSym2 (a6989586621679938958 :: (~>) a6989586621679929440 Bool) (a6989586621679938959 :: [a6989586621679929440]) = DropWhile a6989586621679938958 a6989586621679938959
- data DropWhileEndSym0 :: forall a6989586621679929439. (~>) ((~>) a6989586621679929439 Bool) ((~>) [a6989586621679929439] [a6989586621679929439])
- data DropWhileEndSym1 (a6989586621679940014 :: (~>) a6989586621679929439 Bool) :: (~>) [a6989586621679929439] [a6989586621679929439]
- type DropWhileEndSym2 (a6989586621679940014 :: (~>) a6989586621679929439 Bool) (a6989586621679940015 :: [a6989586621679929439]) = DropWhileEnd a6989586621679940014 a6989586621679940015
- data SpanSym0 :: forall a6989586621679929438. (~>) ((~>) a6989586621679929438 Bool) ((~>) [a6989586621679929438] ([a6989586621679929438], [a6989586621679929438]))
- data SpanSym1 (a6989586621679938881 :: (~>) a6989586621679929438 Bool) :: (~>) [a6989586621679929438] ([a6989586621679929438], [a6989586621679929438])
- type SpanSym2 (a6989586621679938881 :: (~>) a6989586621679929438 Bool) (a6989586621679938882 :: [a6989586621679929438]) = Span a6989586621679938881 a6989586621679938882
- data BreakSym0 :: forall a6989586621679929437. (~>) ((~>) a6989586621679929437 Bool) ((~>) [a6989586621679929437] ([a6989586621679929437], [a6989586621679929437]))
- data BreakSym1 (a6989586621679938838 :: (~>) a6989586621679929437 Bool) :: (~>) [a6989586621679929437] ([a6989586621679929437], [a6989586621679929437])
- type BreakSym2 (a6989586621679938838 :: (~>) a6989586621679929437 Bool) (a6989586621679938839 :: [a6989586621679929437]) = Break a6989586621679938838 a6989586621679938839
- data StripPrefixSym0 :: forall a6989586621680055663. (~>) [a6989586621680055663] ((~>) [a6989586621680055663] (Maybe [a6989586621680055663]))
- data StripPrefixSym1 (a6989586621680068373 :: [a6989586621680055663]) :: (~>) [a6989586621680055663] (Maybe [a6989586621680055663])
- type StripPrefixSym2 (a6989586621680068373 :: [a6989586621680055663]) (a6989586621680068374 :: [a6989586621680055663]) = StripPrefix a6989586621680068373 a6989586621680068374
- data GroupSym0 :: forall a6989586621679929433. (~>) [a6989586621679929433] [[a6989586621679929433]]
- type GroupSym1 (a6989586621679938955 :: [a6989586621679929433]) = Group a6989586621679938955
- data InitsSym0 :: forall a6989586621679929503. (~>) [a6989586621679929503] [[a6989586621679929503]]
- type InitsSym1 (a6989586621679939430 :: [a6989586621679929503]) = Inits a6989586621679939430
- data TailsSym0 :: forall a6989586621679929502. (~>) [a6989586621679929502] [[a6989586621679929502]]
- type TailsSym1 (a6989586621679939423 :: [a6989586621679929502]) = Tails a6989586621679939423
- data IsPrefixOfSym0 :: forall a6989586621679929501. (~>) [a6989586621679929501] ((~>) [a6989586621679929501] Bool)
- data IsPrefixOfSym1 (a6989586621679939415 :: [a6989586621679929501]) :: (~>) [a6989586621679929501] Bool
- type IsPrefixOfSym2 (a6989586621679939415 :: [a6989586621679929501]) (a6989586621679939416 :: [a6989586621679929501]) = IsPrefixOf a6989586621679939415 a6989586621679939416
- data IsSuffixOfSym0 :: forall a6989586621679929500. (~>) [a6989586621679929500] ((~>) [a6989586621679929500] Bool)
- data IsSuffixOfSym1 (a6989586621679940006 :: [a6989586621679929500]) :: (~>) [a6989586621679929500] Bool
- type IsSuffixOfSym2 (a6989586621679940006 :: [a6989586621679929500]) (a6989586621679940007 :: [a6989586621679929500]) = IsSuffixOf a6989586621679940006 a6989586621679940007
- data IsInfixOfSym0 :: forall a6989586621679929499. (~>) [a6989586621679929499] ((~>) [a6989586621679929499] Bool)
- data IsInfixOfSym1 (a6989586621679939653 :: [a6989586621679929499]) :: (~>) [a6989586621679929499] Bool
- type IsInfixOfSym2 (a6989586621679939653 :: [a6989586621679929499]) (a6989586621679939654 :: [a6989586621679929499]) = IsInfixOf a6989586621679939653 a6989586621679939654
- data ElemSym0 :: forall a6989586621680438543 t6989586621680438526. (~>) a6989586621680438543 ((~>) (t6989586621680438526 a6989586621680438543) Bool)
- data ElemSym1 (arg6989586621680439193 :: a6989586621680438543) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438543) Bool
- type ElemSym2 (arg6989586621680439193 :: a6989586621680438543) (arg6989586621680439194 :: t6989586621680438526 a6989586621680438543) = Elem arg6989586621680439193 arg6989586621680439194
- data NotElemSym0 :: forall a6989586621680438437 t6989586621680438436. (~>) a6989586621680438437 ((~>) (t6989586621680438436 a6989586621680438437) Bool)
- data NotElemSym1 (a6989586621680438919 :: a6989586621680438437) :: forall t6989586621680438436. (~>) (t6989586621680438436 a6989586621680438437) Bool
- type NotElemSym2 (a6989586621680438919 :: a6989586621680438437) (a6989586621680438920 :: t6989586621680438436 a6989586621680438437) = NotElem a6989586621680438919 a6989586621680438920
- data LookupSym0 :: forall a6989586621679929426 b6989586621679929427. (~>) a6989586621679929426 ((~>) [(a6989586621679929426, b6989586621679929427)] (Maybe b6989586621679929427))
- data LookupSym1 (a6989586621679938787 :: a6989586621679929426) :: forall b6989586621679929427. (~>) [(a6989586621679929426, b6989586621679929427)] (Maybe b6989586621679929427)
- type LookupSym2 (a6989586621679938787 :: a6989586621679929426) (a6989586621679938788 :: [(a6989586621679929426, b6989586621679929427)]) = Lookup a6989586621679938787 a6989586621679938788
- data FindSym0 :: forall a6989586621680438435 t6989586621680438434. (~>) ((~>) a6989586621680438435 Bool) ((~>) (t6989586621680438434 a6989586621680438435) (Maybe a6989586621680438435))
- data FindSym1 (a6989586621680438892 :: (~>) a6989586621680438435 Bool) :: forall t6989586621680438434. (~>) (t6989586621680438434 a6989586621680438435) (Maybe a6989586621680438435)
- type FindSym2 (a6989586621680438892 :: (~>) a6989586621680438435 Bool) (a6989586621680438893 :: t6989586621680438434 a6989586621680438435) = Find a6989586621680438892 a6989586621680438893
- data FilterSym0 :: forall a6989586621679929449. (~>) ((~>) a6989586621679929449 Bool) ((~>) [a6989586621679929449] [a6989586621679929449])
- data FilterSym1 (a6989586621679938990 :: (~>) a6989586621679929449 Bool) :: (~>) [a6989586621679929449] [a6989586621679929449]
- type FilterSym2 (a6989586621679938990 :: (~>) a6989586621679929449 Bool) (a6989586621679938991 :: [a6989586621679929449]) = Filter a6989586621679938990 a6989586621679938991
- data PartitionSym0 :: forall a6989586621679929425. (~>) ((~>) a6989586621679929425 Bool) ((~>) [a6989586621679929425] ([a6989586621679929425], [a6989586621679929425]))
- data PartitionSym1 (a6989586621679938781 :: (~>) a6989586621679929425 Bool) :: (~>) [a6989586621679929425] ([a6989586621679929425], [a6989586621679929425])
- type PartitionSym2 (a6989586621679938781 :: (~>) a6989586621679929425 Bool) (a6989586621679938782 :: [a6989586621679929425]) = Partition a6989586621679938781 a6989586621679938782
- data (!!@#@$) :: forall a6989586621679929418. (~>) [a6989586621679929418] ((~>) Nat a6989586621679929418)
- data (!!@#@$$) (a6989586621679938708 :: [a6989586621679929418]) :: (~>) Nat a6989586621679929418
- type (!!@#@$$$) (a6989586621679938708 :: [a6989586621679929418]) (a6989586621679938709 :: Nat) = (!!) a6989586621679938708 a6989586621679938709
- data ElemIndexSym0 :: forall a6989586621679929447. (~>) a6989586621679929447 ((~>) [a6989586621679929447] (Maybe Nat))
- data ElemIndexSym1 (a6989586621679939373 :: a6989586621679929447) :: (~>) [a6989586621679929447] (Maybe Nat)
- type ElemIndexSym2 (a6989586621679939373 :: a6989586621679929447) (a6989586621679939374 :: [a6989586621679929447]) = ElemIndex a6989586621679939373 a6989586621679939374
- data ElemIndicesSym0 :: forall a6989586621679929446. (~>) a6989586621679929446 ((~>) [a6989586621679929446] [Nat])
- data ElemIndicesSym1 (a6989586621679939357 :: a6989586621679929446) :: (~>) [a6989586621679929446] [Nat]
- type ElemIndicesSym2 (a6989586621679939357 :: a6989586621679929446) (a6989586621679939358 :: [a6989586621679929446]) = ElemIndices a6989586621679939357 a6989586621679939358
- data FindIndexSym0 :: forall a6989586621679929445. (~>) ((~>) a6989586621679929445 Bool) ((~>) [a6989586621679929445] (Maybe Nat))
- data FindIndexSym1 (a6989586621679939365 :: (~>) a6989586621679929445 Bool) :: (~>) [a6989586621679929445] (Maybe Nat)
- type FindIndexSym2 (a6989586621679939365 :: (~>) a6989586621679929445 Bool) (a6989586621679939366 :: [a6989586621679929445]) = FindIndex a6989586621679939365 a6989586621679939366
- data FindIndicesSym0 :: forall a6989586621679929444. (~>) ((~>) a6989586621679929444 Bool) ((~>) [a6989586621679929444] [Nat])
- data FindIndicesSym1 (a6989586621679939331 :: (~>) a6989586621679929444 Bool) :: (~>) [a6989586621679929444] [Nat]
- type FindIndicesSym2 (a6989586621679939331 :: (~>) a6989586621679929444 Bool) (a6989586621679939332 :: [a6989586621679929444]) = FindIndices a6989586621679939331 a6989586621679939332
- data ZipSym0 :: forall a6989586621679929495 b6989586621679929496. (~>) [a6989586621679929495] ((~>) [b6989586621679929496] [(a6989586621679929495, b6989586621679929496)])
- data ZipSym1 (a6989586621679939323 :: [a6989586621679929495]) :: forall b6989586621679929496. (~>) [b6989586621679929496] [(a6989586621679929495, b6989586621679929496)]
- type ZipSym2 (a6989586621679939323 :: [a6989586621679929495]) (a6989586621679939324 :: [b6989586621679929496]) = Zip a6989586621679939323 a6989586621679939324
- data Zip3Sym0 :: forall a6989586621679929492 b6989586621679929493 c6989586621679929494. (~>) [a6989586621679929492] ((~>) [b6989586621679929493] ((~>) [c6989586621679929494] [(a6989586621679929492, b6989586621679929493, c6989586621679929494)]))
- data Zip3Sym1 (a6989586621679939311 :: [a6989586621679929492]) :: forall b6989586621679929493 c6989586621679929494. (~>) [b6989586621679929493] ((~>) [c6989586621679929494] [(a6989586621679929492, b6989586621679929493, c6989586621679929494)])
- data Zip3Sym2 (a6989586621679939311 :: [a6989586621679929492]) (a6989586621679939312 :: [b6989586621679929493]) :: forall c6989586621679929494. (~>) [c6989586621679929494] [(a6989586621679929492, b6989586621679929493, c6989586621679929494)]
- type Zip3Sym3 (a6989586621679939311 :: [a6989586621679929492]) (a6989586621679939312 :: [b6989586621679929493]) (a6989586621679939313 :: [c6989586621679929494]) = Zip3 a6989586621679939311 a6989586621679939312 a6989586621679939313
- data Zip4Sym0 :: forall a6989586621680055659 b6989586621680055660 c6989586621680055661 d6989586621680055662. (~>) [a6989586621680055659] ((~>) [b6989586621680055660] ((~>) [c6989586621680055661] ((~>) [d6989586621680055662] [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)])))
- data Zip4Sym1 (a6989586621680068361 :: [a6989586621680055659]) :: forall b6989586621680055660 c6989586621680055661 d6989586621680055662. (~>) [b6989586621680055660] ((~>) [c6989586621680055661] ((~>) [d6989586621680055662] [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)]))
- data Zip4Sym2 (a6989586621680068361 :: [a6989586621680055659]) (a6989586621680068362 :: [b6989586621680055660]) :: forall c6989586621680055661 d6989586621680055662. (~>) [c6989586621680055661] ((~>) [d6989586621680055662] [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)])
- data Zip4Sym3 (a6989586621680068361 :: [a6989586621680055659]) (a6989586621680068362 :: [b6989586621680055660]) (a6989586621680068363 :: [c6989586621680055661]) :: forall d6989586621680055662. (~>) [d6989586621680055662] [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)]
- type Zip4Sym4 (a6989586621680068361 :: [a6989586621680055659]) (a6989586621680068362 :: [b6989586621680055660]) (a6989586621680068363 :: [c6989586621680055661]) (a6989586621680068364 :: [d6989586621680055662]) = Zip4 a6989586621680068361 a6989586621680068362 a6989586621680068363 a6989586621680068364
- data Zip5Sym0 :: forall a6989586621680055654 b6989586621680055655 c6989586621680055656 d6989586621680055657 e6989586621680055658. (~>) [a6989586621680055654] ((~>) [b6989586621680055655] ((~>) [c6989586621680055656] ((~>) [d6989586621680055657] ((~>) [e6989586621680055658] [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]))))
- data Zip5Sym1 (a6989586621680068338 :: [a6989586621680055654]) :: forall b6989586621680055655 c6989586621680055656 d6989586621680055657 e6989586621680055658. (~>) [b6989586621680055655] ((~>) [c6989586621680055656] ((~>) [d6989586621680055657] ((~>) [e6989586621680055658] [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)])))
- data Zip5Sym2 (a6989586621680068338 :: [a6989586621680055654]) (a6989586621680068339 :: [b6989586621680055655]) :: forall c6989586621680055656 d6989586621680055657 e6989586621680055658. (~>) [c6989586621680055656] ((~>) [d6989586621680055657] ((~>) [e6989586621680055658] [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]))
- data Zip5Sym3 (a6989586621680068338 :: [a6989586621680055654]) (a6989586621680068339 :: [b6989586621680055655]) (a6989586621680068340 :: [c6989586621680055656]) :: forall d6989586621680055657 e6989586621680055658. (~>) [d6989586621680055657] ((~>) [e6989586621680055658] [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)])
- data Zip5Sym4 (a6989586621680068338 :: [a6989586621680055654]) (a6989586621680068339 :: [b6989586621680055655]) (a6989586621680068340 :: [c6989586621680055656]) (a6989586621680068341 :: [d6989586621680055657]) :: forall e6989586621680055658. (~>) [e6989586621680055658] [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]
- type Zip5Sym5 (a6989586621680068338 :: [a6989586621680055654]) (a6989586621680068339 :: [b6989586621680055655]) (a6989586621680068340 :: [c6989586621680055656]) (a6989586621680068341 :: [d6989586621680055657]) (a6989586621680068342 :: [e6989586621680055658]) = Zip5 a6989586621680068338 a6989586621680068339 a6989586621680068340 a6989586621680068341 a6989586621680068342
- data Zip6Sym0 :: forall a6989586621680055648 b6989586621680055649 c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653. (~>) [a6989586621680055648] ((~>) [b6989586621680055649] ((~>) [c6989586621680055650] ((~>) [d6989586621680055651] ((~>) [e6989586621680055652] ((~>) [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])))))
- data Zip6Sym1 (a6989586621680068310 :: [a6989586621680055648]) :: forall b6989586621680055649 c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653. (~>) [b6989586621680055649] ((~>) [c6989586621680055650] ((~>) [d6989586621680055651] ((~>) [e6989586621680055652] ((~>) [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]))))
- data Zip6Sym2 (a6989586621680068310 :: [a6989586621680055648]) (a6989586621680068311 :: [b6989586621680055649]) :: forall c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653. (~>) [c6989586621680055650] ((~>) [d6989586621680055651] ((~>) [e6989586621680055652] ((~>) [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])))
- data Zip6Sym3 (a6989586621680068310 :: [a6989586621680055648]) (a6989586621680068311 :: [b6989586621680055649]) (a6989586621680068312 :: [c6989586621680055650]) :: forall d6989586621680055651 e6989586621680055652 f6989586621680055653. (~>) [d6989586621680055651] ((~>) [e6989586621680055652] ((~>) [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]))
- data Zip6Sym4 (a6989586621680068310 :: [a6989586621680055648]) (a6989586621680068311 :: [b6989586621680055649]) (a6989586621680068312 :: [c6989586621680055650]) (a6989586621680068313 :: [d6989586621680055651]) :: forall e6989586621680055652 f6989586621680055653. (~>) [e6989586621680055652] ((~>) [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])
- data Zip6Sym5 (a6989586621680068310 :: [a6989586621680055648]) (a6989586621680068311 :: [b6989586621680055649]) (a6989586621680068312 :: [c6989586621680055650]) (a6989586621680068313 :: [d6989586621680055651]) (a6989586621680068314 :: [e6989586621680055652]) :: forall f6989586621680055653. (~>) [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]
- type Zip6Sym6 (a6989586621680068310 :: [a6989586621680055648]) (a6989586621680068311 :: [b6989586621680055649]) (a6989586621680068312 :: [c6989586621680055650]) (a6989586621680068313 :: [d6989586621680055651]) (a6989586621680068314 :: [e6989586621680055652]) (a6989586621680068315 :: [f6989586621680055653]) = Zip6 a6989586621680068310 a6989586621680068311 a6989586621680068312 a6989586621680068313 a6989586621680068314 a6989586621680068315
- data Zip7Sym0 :: forall a6989586621680055641 b6989586621680055642 c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647. (~>) [a6989586621680055641] ((~>) [b6989586621680055642] ((~>) [c6989586621680055643] ((~>) [d6989586621680055644] ((~>) [e6989586621680055645] ((~>) [f6989586621680055646] ((~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))))))
- data Zip7Sym1 (a6989586621680068277 :: [a6989586621680055641]) :: forall b6989586621680055642 c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647. (~>) [b6989586621680055642] ((~>) [c6989586621680055643] ((~>) [d6989586621680055644] ((~>) [e6989586621680055645] ((~>) [f6989586621680055646] ((~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])))))
- data Zip7Sym2 (a6989586621680068277 :: [a6989586621680055641]) (a6989586621680068278 :: [b6989586621680055642]) :: forall c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647. (~>) [c6989586621680055643] ((~>) [d6989586621680055644] ((~>) [e6989586621680055645] ((~>) [f6989586621680055646] ((~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))))
- data Zip7Sym3 (a6989586621680068277 :: [a6989586621680055641]) (a6989586621680068278 :: [b6989586621680055642]) (a6989586621680068279 :: [c6989586621680055643]) :: forall d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647. (~>) [d6989586621680055644] ((~>) [e6989586621680055645] ((~>) [f6989586621680055646] ((~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])))
- data Zip7Sym4 (a6989586621680068277 :: [a6989586621680055641]) (a6989586621680068278 :: [b6989586621680055642]) (a6989586621680068279 :: [c6989586621680055643]) (a6989586621680068280 :: [d6989586621680055644]) :: forall e6989586621680055645 f6989586621680055646 g6989586621680055647. (~>) [e6989586621680055645] ((~>) [f6989586621680055646] ((~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))
- data Zip7Sym5 (a6989586621680068277 :: [a6989586621680055641]) (a6989586621680068278 :: [b6989586621680055642]) (a6989586621680068279 :: [c6989586621680055643]) (a6989586621680068280 :: [d6989586621680055644]) (a6989586621680068281 :: [e6989586621680055645]) :: forall f6989586621680055646 g6989586621680055647. (~>) [f6989586621680055646] ((~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])
- data Zip7Sym6 (a6989586621680068277 :: [a6989586621680055641]) (a6989586621680068278 :: [b6989586621680055642]) (a6989586621680068279 :: [c6989586621680055643]) (a6989586621680068280 :: [d6989586621680055644]) (a6989586621680068281 :: [e6989586621680055645]) (a6989586621680068282 :: [f6989586621680055646]) :: forall g6989586621680055647. (~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]
- type Zip7Sym7 (a6989586621680068277 :: [a6989586621680055641]) (a6989586621680068278 :: [b6989586621680055642]) (a6989586621680068279 :: [c6989586621680055643]) (a6989586621680068280 :: [d6989586621680055644]) (a6989586621680068281 :: [e6989586621680055645]) (a6989586621680068282 :: [f6989586621680055646]) (a6989586621680068283 :: [g6989586621680055647]) = Zip7 a6989586621680068277 a6989586621680068278 a6989586621680068279 a6989586621680068280 a6989586621680068281 a6989586621680068282 a6989586621680068283
- data ZipWithSym0 :: forall a6989586621679929489 b6989586621679929490 c6989586621679929491. (~>) ((~>) a6989586621679929489 ((~>) b6989586621679929490 c6989586621679929491)) ((~>) [a6989586621679929489] ((~>) [b6989586621679929490] [c6989586621679929491]))
- data ZipWithSym1 (a6989586621679939300 :: (~>) a6989586621679929489 ((~>) b6989586621679929490 c6989586621679929491)) :: (~>) [a6989586621679929489] ((~>) [b6989586621679929490] [c6989586621679929491])
- data ZipWithSym2 (a6989586621679939300 :: (~>) a6989586621679929489 ((~>) b6989586621679929490 c6989586621679929491)) (a6989586621679939301 :: [a6989586621679929489]) :: (~>) [b6989586621679929490] [c6989586621679929491]
- type ZipWithSym3 (a6989586621679939300 :: (~>) a6989586621679929489 ((~>) b6989586621679929490 c6989586621679929491)) (a6989586621679939301 :: [a6989586621679929489]) (a6989586621679939302 :: [b6989586621679929490]) = ZipWith a6989586621679939300 a6989586621679939301 a6989586621679939302
- data ZipWith3Sym0 :: forall a6989586621679929485 b6989586621679929486 c6989586621679929487 d6989586621679929488. (~>) ((~>) a6989586621679929485 ((~>) b6989586621679929486 ((~>) c6989586621679929487 d6989586621679929488))) ((~>) [a6989586621679929485] ((~>) [b6989586621679929486] ((~>) [c6989586621679929487] [d6989586621679929488])))
- data ZipWith3Sym1 (a6989586621679939285 :: (~>) a6989586621679929485 ((~>) b6989586621679929486 ((~>) c6989586621679929487 d6989586621679929488))) :: (~>) [a6989586621679929485] ((~>) [b6989586621679929486] ((~>) [c6989586621679929487] [d6989586621679929488]))
- data ZipWith3Sym2 (a6989586621679939285 :: (~>) a6989586621679929485 ((~>) b6989586621679929486 ((~>) c6989586621679929487 d6989586621679929488))) (a6989586621679939286 :: [a6989586621679929485]) :: (~>) [b6989586621679929486] ((~>) [c6989586621679929487] [d6989586621679929488])
- data ZipWith3Sym3 (a6989586621679939285 :: (~>) a6989586621679929485 ((~>) b6989586621679929486 ((~>) c6989586621679929487 d6989586621679929488))) (a6989586621679939286 :: [a6989586621679929485]) (a6989586621679939287 :: [b6989586621679929486]) :: (~>) [c6989586621679929487] [d6989586621679929488]
- type ZipWith3Sym4 (a6989586621679939285 :: (~>) a6989586621679929485 ((~>) b6989586621679929486 ((~>) c6989586621679929487 d6989586621679929488))) (a6989586621679939286 :: [a6989586621679929485]) (a6989586621679939287 :: [b6989586621679929486]) (a6989586621679939288 :: [c6989586621679929487]) = ZipWith3 a6989586621679939285 a6989586621679939286 a6989586621679939287 a6989586621679939288
- data ZipWith4Sym0 :: forall a6989586621680055636 b6989586621680055637 c6989586621680055638 d6989586621680055639 e6989586621680055640. (~>) ((~>) a6989586621680055636 ((~>) b6989586621680055637 ((~>) c6989586621680055638 ((~>) d6989586621680055639 e6989586621680055640)))) ((~>) [a6989586621680055636] ((~>) [b6989586621680055637] ((~>) [c6989586621680055638] ((~>) [d6989586621680055639] [e6989586621680055640]))))
- data ZipWith4Sym1 (a6989586621680068244 :: (~>) a6989586621680055636 ((~>) b6989586621680055637 ((~>) c6989586621680055638 ((~>) d6989586621680055639 e6989586621680055640)))) :: (~>) [a6989586621680055636] ((~>) [b6989586621680055637] ((~>) [c6989586621680055638] ((~>) [d6989586621680055639] [e6989586621680055640])))
- data ZipWith4Sym2 (a6989586621680068244 :: (~>) a6989586621680055636 ((~>) b6989586621680055637 ((~>) c6989586621680055638 ((~>) d6989586621680055639 e6989586621680055640)))) (a6989586621680068245 :: [a6989586621680055636]) :: (~>) [b6989586621680055637] ((~>) [c6989586621680055638] ((~>) [d6989586621680055639] [e6989586621680055640]))
- data ZipWith4Sym3 (a6989586621680068244 :: (~>) a6989586621680055636 ((~>) b6989586621680055637 ((~>) c6989586621680055638 ((~>) d6989586621680055639 e6989586621680055640)))) (a6989586621680068245 :: [a6989586621680055636]) (a6989586621680068246 :: [b6989586621680055637]) :: (~>) [c6989586621680055638] ((~>) [d6989586621680055639] [e6989586621680055640])
- data ZipWith4Sym4 (a6989586621680068244 :: (~>) a6989586621680055636 ((~>) b6989586621680055637 ((~>) c6989586621680055638 ((~>) d6989586621680055639 e6989586621680055640)))) (a6989586621680068245 :: [a6989586621680055636]) (a6989586621680068246 :: [b6989586621680055637]) (a6989586621680068247 :: [c6989586621680055638]) :: (~>) [d6989586621680055639] [e6989586621680055640]
- type ZipWith4Sym5 (a6989586621680068244 :: (~>) a6989586621680055636 ((~>) b6989586621680055637 ((~>) c6989586621680055638 ((~>) d6989586621680055639 e6989586621680055640)))) (a6989586621680068245 :: [a6989586621680055636]) (a6989586621680068246 :: [b6989586621680055637]) (a6989586621680068247 :: [c6989586621680055638]) (a6989586621680068248 :: [d6989586621680055639]) = ZipWith4 a6989586621680068244 a6989586621680068245 a6989586621680068246 a6989586621680068247 a6989586621680068248
- data ZipWith5Sym0 :: forall a6989586621680055630 b6989586621680055631 c6989586621680055632 d6989586621680055633 e6989586621680055634 f6989586621680055635. (~>) ((~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) ((~>) [a6989586621680055630] ((~>) [b6989586621680055631] ((~>) [c6989586621680055632] ((~>) [d6989586621680055633] ((~>) [e6989586621680055634] [f6989586621680055635])))))
- data ZipWith5Sym1 (a6989586621680068221 :: (~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) :: (~>) [a6989586621680055630] ((~>) [b6989586621680055631] ((~>) [c6989586621680055632] ((~>) [d6989586621680055633] ((~>) [e6989586621680055634] [f6989586621680055635]))))
- data ZipWith5Sym2 (a6989586621680068221 :: (~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) (a6989586621680068222 :: [a6989586621680055630]) :: (~>) [b6989586621680055631] ((~>) [c6989586621680055632] ((~>) [d6989586621680055633] ((~>) [e6989586621680055634] [f6989586621680055635])))
- data ZipWith5Sym3 (a6989586621680068221 :: (~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) (a6989586621680068222 :: [a6989586621680055630]) (a6989586621680068223 :: [b6989586621680055631]) :: (~>) [c6989586621680055632] ((~>) [d6989586621680055633] ((~>) [e6989586621680055634] [f6989586621680055635]))
- data ZipWith5Sym4 (a6989586621680068221 :: (~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) (a6989586621680068222 :: [a6989586621680055630]) (a6989586621680068223 :: [b6989586621680055631]) (a6989586621680068224 :: [c6989586621680055632]) :: (~>) [d6989586621680055633] ((~>) [e6989586621680055634] [f6989586621680055635])
- data ZipWith5Sym5 (a6989586621680068221 :: (~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) (a6989586621680068222 :: [a6989586621680055630]) (a6989586621680068223 :: [b6989586621680055631]) (a6989586621680068224 :: [c6989586621680055632]) (a6989586621680068225 :: [d6989586621680055633]) :: (~>) [e6989586621680055634] [f6989586621680055635]
- type ZipWith5Sym6 (a6989586621680068221 :: (~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) (a6989586621680068222 :: [a6989586621680055630]) (a6989586621680068223 :: [b6989586621680055631]) (a6989586621680068224 :: [c6989586621680055632]) (a6989586621680068225 :: [d6989586621680055633]) (a6989586621680068226 :: [e6989586621680055634]) = ZipWith5 a6989586621680068221 a6989586621680068222 a6989586621680068223 a6989586621680068224 a6989586621680068225 a6989586621680068226
- data ZipWith6Sym0 :: forall a6989586621680055623 b6989586621680055624 c6989586621680055625 d6989586621680055626 e6989586621680055627 f6989586621680055628 g6989586621680055629. (~>) ((~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) ((~>) [a6989586621680055623] ((~>) [b6989586621680055624] ((~>) [c6989586621680055625] ((~>) [d6989586621680055626] ((~>) [e6989586621680055627] ((~>) [f6989586621680055628] [g6989586621680055629]))))))
- data ZipWith6Sym1 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) :: (~>) [a6989586621680055623] ((~>) [b6989586621680055624] ((~>) [c6989586621680055625] ((~>) [d6989586621680055626] ((~>) [e6989586621680055627] ((~>) [f6989586621680055628] [g6989586621680055629])))))
- data ZipWith6Sym2 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) (a6989586621680068195 :: [a6989586621680055623]) :: (~>) [b6989586621680055624] ((~>) [c6989586621680055625] ((~>) [d6989586621680055626] ((~>) [e6989586621680055627] ((~>) [f6989586621680055628] [g6989586621680055629]))))
- data ZipWith6Sym3 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) (a6989586621680068195 :: [a6989586621680055623]) (a6989586621680068196 :: [b6989586621680055624]) :: (~>) [c6989586621680055625] ((~>) [d6989586621680055626] ((~>) [e6989586621680055627] ((~>) [f6989586621680055628] [g6989586621680055629])))
- data ZipWith6Sym4 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) (a6989586621680068195 :: [a6989586621680055623]) (a6989586621680068196 :: [b6989586621680055624]) (a6989586621680068197 :: [c6989586621680055625]) :: (~>) [d6989586621680055626] ((~>) [e6989586621680055627] ((~>) [f6989586621680055628] [g6989586621680055629]))
- data ZipWith6Sym5 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) (a6989586621680068195 :: [a6989586621680055623]) (a6989586621680068196 :: [b6989586621680055624]) (a6989586621680068197 :: [c6989586621680055625]) (a6989586621680068198 :: [d6989586621680055626]) :: (~>) [e6989586621680055627] ((~>) [f6989586621680055628] [g6989586621680055629])
- data ZipWith6Sym6 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) (a6989586621680068195 :: [a6989586621680055623]) (a6989586621680068196 :: [b6989586621680055624]) (a6989586621680068197 :: [c6989586621680055625]) (a6989586621680068198 :: [d6989586621680055626]) (a6989586621680068199 :: [e6989586621680055627]) :: (~>) [f6989586621680055628] [g6989586621680055629]
- type ZipWith6Sym7 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) (a6989586621680068195 :: [a6989586621680055623]) (a6989586621680068196 :: [b6989586621680055624]) (a6989586621680068197 :: [c6989586621680055625]) (a6989586621680068198 :: [d6989586621680055626]) (a6989586621680068199 :: [e6989586621680055627]) (a6989586621680068200 :: [f6989586621680055628]) = ZipWith6 a6989586621680068194 a6989586621680068195 a6989586621680068196 a6989586621680068197 a6989586621680068198 a6989586621680068199 a6989586621680068200
- data ZipWith7Sym0 :: forall a6989586621680055615 b6989586621680055616 c6989586621680055617 d6989586621680055618 e6989586621680055619 f6989586621680055620 g6989586621680055621 h6989586621680055622. (~>) ((~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) ((~>) [a6989586621680055615] ((~>) [b6989586621680055616] ((~>) [c6989586621680055617] ((~>) [d6989586621680055618] ((~>) [e6989586621680055619] ((~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622])))))))
- data ZipWith7Sym1 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) :: (~>) [a6989586621680055615] ((~>) [b6989586621680055616] ((~>) [c6989586621680055617] ((~>) [d6989586621680055618] ((~>) [e6989586621680055619] ((~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622]))))))
- data ZipWith7Sym2 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) :: (~>) [b6989586621680055616] ((~>) [c6989586621680055617] ((~>) [d6989586621680055618] ((~>) [e6989586621680055619] ((~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622])))))
- data ZipWith7Sym3 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) (a6989586621680068165 :: [b6989586621680055616]) :: (~>) [c6989586621680055617] ((~>) [d6989586621680055618] ((~>) [e6989586621680055619] ((~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622]))))
- data ZipWith7Sym4 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) (a6989586621680068165 :: [b6989586621680055616]) (a6989586621680068166 :: [c6989586621680055617]) :: (~>) [d6989586621680055618] ((~>) [e6989586621680055619] ((~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622])))
- data ZipWith7Sym5 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) (a6989586621680068165 :: [b6989586621680055616]) (a6989586621680068166 :: [c6989586621680055617]) (a6989586621680068167 :: [d6989586621680055618]) :: (~>) [e6989586621680055619] ((~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622]))
- data ZipWith7Sym6 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) (a6989586621680068165 :: [b6989586621680055616]) (a6989586621680068166 :: [c6989586621680055617]) (a6989586621680068167 :: [d6989586621680055618]) (a6989586621680068168 :: [e6989586621680055619]) :: (~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622])
- data ZipWith7Sym7 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) (a6989586621680068165 :: [b6989586621680055616]) (a6989586621680068166 :: [c6989586621680055617]) (a6989586621680068167 :: [d6989586621680055618]) (a6989586621680068168 :: [e6989586621680055619]) (a6989586621680068169 :: [f6989586621680055620]) :: (~>) [g6989586621680055621] [h6989586621680055622]
- type ZipWith7Sym8 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) (a6989586621680068165 :: [b6989586621680055616]) (a6989586621680068166 :: [c6989586621680055617]) (a6989586621680068167 :: [d6989586621680055618]) (a6989586621680068168 :: [e6989586621680055619]) (a6989586621680068169 :: [f6989586621680055620]) (a6989586621680068170 :: [g6989586621680055621]) = ZipWith7 a6989586621680068163 a6989586621680068164 a6989586621680068165 a6989586621680068166 a6989586621680068167 a6989586621680068168 a6989586621680068169 a6989586621680068170
- data UnzipSym0 :: forall a6989586621679929483 b6989586621679929484. (~>) [(a6989586621679929483, b6989586621679929484)] ([a6989586621679929483], [b6989586621679929484])
- type UnzipSym1 (a6989586621679939266 :: [(a6989586621679929483, b6989586621679929484)]) = Unzip a6989586621679939266
- data Unzip3Sym0 :: forall a6989586621679929480 b6989586621679929481 c6989586621679929482. (~>) [(a6989586621679929480, b6989586621679929481, c6989586621679929482)] ([a6989586621679929480], [b6989586621679929481], [c6989586621679929482])
- type Unzip3Sym1 (a6989586621679939245 :: [(a6989586621679929480, b6989586621679929481, c6989586621679929482)]) = Unzip3 a6989586621679939245
- data Unzip4Sym0 :: forall a6989586621679929476 b6989586621679929477 c6989586621679929478 d6989586621679929479. (~>) [(a6989586621679929476, b6989586621679929477, c6989586621679929478, d6989586621679929479)] ([a6989586621679929476], [b6989586621679929477], [c6989586621679929478], [d6989586621679929479])
- type Unzip4Sym1 (a6989586621679939222 :: [(a6989586621679929476, b6989586621679929477, c6989586621679929478, d6989586621679929479)]) = Unzip4 a6989586621679939222
- data Unzip5Sym0 :: forall a6989586621679929471 b6989586621679929472 c6989586621679929473 d6989586621679929474 e6989586621679929475. (~>) [(a6989586621679929471, b6989586621679929472, c6989586621679929473, d6989586621679929474, e6989586621679929475)] ([a6989586621679929471], [b6989586621679929472], [c6989586621679929473], [d6989586621679929474], [e6989586621679929475])
- type Unzip5Sym1 (a6989586621679939197 :: [(a6989586621679929471, b6989586621679929472, c6989586621679929473, d6989586621679929474, e6989586621679929475)]) = Unzip5 a6989586621679939197
- data Unzip6Sym0 :: forall a6989586621679929465 b6989586621679929466 c6989586621679929467 d6989586621679929468 e6989586621679929469 f6989586621679929470. (~>) [(a6989586621679929465, b6989586621679929466, c6989586621679929467, d6989586621679929468, e6989586621679929469, f6989586621679929470)] ([a6989586621679929465], [b6989586621679929466], [c6989586621679929467], [d6989586621679929468], [e6989586621679929469], [f6989586621679929470])
- type Unzip6Sym1 (a6989586621679939170 :: [(a6989586621679929465, b6989586621679929466, c6989586621679929467, d6989586621679929468, e6989586621679929469, f6989586621679929470)]) = Unzip6 a6989586621679939170
- data Unzip7Sym0 :: forall a6989586621679929458 b6989586621679929459 c6989586621679929460 d6989586621679929461 e6989586621679929462 f6989586621679929463 g6989586621679929464. (~>) [(a6989586621679929458, b6989586621679929459, c6989586621679929460, d6989586621679929461, e6989586621679929462, f6989586621679929463, g6989586621679929464)] ([a6989586621679929458], [b6989586621679929459], [c6989586621679929460], [d6989586621679929461], [e6989586621679929462], [f6989586621679929463], [g6989586621679929464])
- type Unzip7Sym1 (a6989586621679939141 :: [(a6989586621679929458, b6989586621679929459, c6989586621679929460, d6989586621679929461, e6989586621679929462, f6989586621679929463, g6989586621679929464)]) = Unzip7 a6989586621679939141
- data UnlinesSym0 :: (~>) [Symbol] Symbol
- type UnlinesSym1 (a6989586621679939137 :: [Symbol]) = Unlines a6989586621679939137
- data UnwordsSym0 :: (~>) [Symbol] Symbol
- type UnwordsSym1 (a6989586621679939126 :: [Symbol]) = Unwords a6989586621679939126
- data NubSym0 :: forall a6989586621679929417. (~>) [a6989586621679929417] [a6989586621679929417]
- type NubSym1 (a6989586621679939395 :: [a6989586621679929417]) = Nub a6989586621679939395
- data DeleteSym0 :: forall a6989586621679929457. (~>) a6989586621679929457 ((~>) [a6989586621679929457] [a6989586621679929457])
- data DeleteSym1 (a6989586621679939110 :: a6989586621679929457) :: (~>) [a6989586621679929457] [a6989586621679929457]
- type DeleteSym2 (a6989586621679939110 :: a6989586621679929457) (a6989586621679939111 :: [a6989586621679929457]) = Delete a6989586621679939110 a6989586621679939111
- data (\\@#@$) :: forall a6989586621679929456. (~>) [a6989586621679929456] ((~>) [a6989586621679929456] [a6989586621679929456])
- data (\\@#@$$) (a6989586621679939120 :: [a6989586621679929456]) :: (~>) [a6989586621679929456] [a6989586621679929456]
- type (\\@#@$$$) (a6989586621679939120 :: [a6989586621679929456]) (a6989586621679939121 :: [a6989586621679929456]) = (\\) a6989586621679939120 a6989586621679939121
- data UnionSym0 :: forall a6989586621679929413. (~>) [a6989586621679929413] ((~>) [a6989586621679929413] [a6989586621679929413])
- data UnionSym1 (a6989586621679939100 :: [a6989586621679929413]) :: (~>) [a6989586621679929413] [a6989586621679929413]
- type UnionSym2 (a6989586621679939100 :: [a6989586621679929413]) (a6989586621679939101 :: [a6989586621679929413]) = Union a6989586621679939100 a6989586621679939101
- data IntersectSym0 :: forall a6989586621679929443. (~>) [a6989586621679929443] ((~>) [a6989586621679929443] [a6989586621679929443])
- data IntersectSym1 (a6989586621679939695 :: [a6989586621679929443]) :: (~>) [a6989586621679929443] [a6989586621679929443]
- type IntersectSym2 (a6989586621679939695 :: [a6989586621679929443]) (a6989586621679939696 :: [a6989586621679929443]) = Intersect a6989586621679939695 a6989586621679939696
- data InsertSym0 :: forall a6989586621679929430. (~>) a6989586621679929430 ((~>) [a6989586621679929430] [a6989586621679929430])
- data InsertSym1 (a6989586621679939037 :: a6989586621679929430) :: (~>) [a6989586621679929430] [a6989586621679929430]
- type InsertSym2 (a6989586621679939037 :: a6989586621679929430) (a6989586621679939038 :: [a6989586621679929430]) = Insert a6989586621679939037 a6989586621679939038
- data SortSym0 :: forall a6989586621679929429. (~>) [a6989586621679929429] [a6989586621679929429]
- type SortSym1 (a6989586621679939053 :: [a6989586621679929429]) = Sort a6989586621679939053
- data NubBySym0 :: forall a6989586621679929416. (~>) ((~>) a6989586621679929416 ((~>) a6989586621679929416 Bool)) ((~>) [a6989586621679929416] [a6989586621679929416])
- data NubBySym1 (a6989586621679938683 :: (~>) a6989586621679929416 ((~>) a6989586621679929416 Bool)) :: (~>) [a6989586621679929416] [a6989586621679929416]
- type NubBySym2 (a6989586621679938683 :: (~>) a6989586621679929416 ((~>) a6989586621679929416 Bool)) (a6989586621679938684 :: [a6989586621679929416]) = NubBy a6989586621679938683 a6989586621679938684
- data DeleteBySym0 :: forall a6989586621679929455. (~>) ((~>) a6989586621679929455 ((~>) a6989586621679929455 Bool)) ((~>) a6989586621679929455 ((~>) [a6989586621679929455] [a6989586621679929455]))
- data DeleteBySym1 (a6989586621679939056 :: (~>) a6989586621679929455 ((~>) a6989586621679929455 Bool)) :: (~>) a6989586621679929455 ((~>) [a6989586621679929455] [a6989586621679929455])
- data DeleteBySym2 (a6989586621679939056 :: (~>) a6989586621679929455 ((~>) a6989586621679929455 Bool)) (a6989586621679939057 :: a6989586621679929455) :: (~>) [a6989586621679929455] [a6989586621679929455]
- type DeleteBySym3 (a6989586621679939056 :: (~>) a6989586621679929455 ((~>) a6989586621679929455 Bool)) (a6989586621679939057 :: a6989586621679929455) (a6989586621679939058 :: [a6989586621679929455]) = DeleteBy a6989586621679939056 a6989586621679939057 a6989586621679939058
- data DeleteFirstsBySym0 :: forall a6989586621679929454. (~>) ((~>) a6989586621679929454 ((~>) a6989586621679929454 Bool)) ((~>) [a6989586621679929454] ((~>) [a6989586621679929454] [a6989586621679929454]))
- data DeleteFirstsBySym1 (a6989586621679939074 :: (~>) a6989586621679929454 ((~>) a6989586621679929454 Bool)) :: (~>) [a6989586621679929454] ((~>) [a6989586621679929454] [a6989586621679929454])
- data DeleteFirstsBySym2 (a6989586621679939074 :: (~>) a6989586621679929454 ((~>) a6989586621679929454 Bool)) (a6989586621679939075 :: [a6989586621679929454]) :: (~>) [a6989586621679929454] [a6989586621679929454]
- type DeleteFirstsBySym3 (a6989586621679939074 :: (~>) a6989586621679929454 ((~>) a6989586621679929454 Bool)) (a6989586621679939075 :: [a6989586621679929454]) (a6989586621679939076 :: [a6989586621679929454]) = DeleteFirstsBy a6989586621679939074 a6989586621679939075 a6989586621679939076
- data UnionBySym0 :: forall a6989586621679929414. (~>) ((~>) a6989586621679929414 ((~>) a6989586621679929414 Bool)) ((~>) [a6989586621679929414] ((~>) [a6989586621679929414] [a6989586621679929414]))
- data UnionBySym1 (a6989586621679939087 :: (~>) a6989586621679929414 ((~>) a6989586621679929414 Bool)) :: (~>) [a6989586621679929414] ((~>) [a6989586621679929414] [a6989586621679929414])
- data UnionBySym2 (a6989586621679939087 :: (~>) a6989586621679929414 ((~>) a6989586621679929414 Bool)) (a6989586621679939088 :: [a6989586621679929414]) :: (~>) [a6989586621679929414] [a6989586621679929414]
- type UnionBySym3 (a6989586621679939087 :: (~>) a6989586621679929414 ((~>) a6989586621679929414 Bool)) (a6989586621679939088 :: [a6989586621679929414]) (a6989586621679939089 :: [a6989586621679929414]) = UnionBy a6989586621679939087 a6989586621679939088 a6989586621679939089
- data IntersectBySym0 :: forall a6989586621679929442. (~>) ((~>) a6989586621679929442 ((~>) a6989586621679929442 Bool)) ((~>) [a6989586621679929442] ((~>) [a6989586621679929442] [a6989586621679929442]))
- data IntersectBySym1 (a6989586621679939659 :: (~>) a6989586621679929442 ((~>) a6989586621679929442 Bool)) :: (~>) [a6989586621679929442] ((~>) [a6989586621679929442] [a6989586621679929442])
- data IntersectBySym2 (a6989586621679939659 :: (~>) a6989586621679929442 ((~>) a6989586621679929442 Bool)) (a6989586621679939660 :: [a6989586621679929442]) :: (~>) [a6989586621679929442] [a6989586621679929442]
- type IntersectBySym3 (a6989586621679939659 :: (~>) a6989586621679929442 ((~>) a6989586621679929442 Bool)) (a6989586621679939660 :: [a6989586621679929442]) (a6989586621679939661 :: [a6989586621679929442]) = IntersectBy a6989586621679939659 a6989586621679939660 a6989586621679939661
- data GroupBySym0 :: forall a6989586621679929428. (~>) ((~>) a6989586621679929428 ((~>) a6989586621679929428 Bool)) ((~>) [a6989586621679929428] [[a6989586621679929428]])
- data GroupBySym1 (a6989586621679938924 :: (~>) a6989586621679929428 ((~>) a6989586621679929428 Bool)) :: (~>) [a6989586621679929428] [[a6989586621679929428]]
- type GroupBySym2 (a6989586621679938924 :: (~>) a6989586621679929428 ((~>) a6989586621679929428 Bool)) (a6989586621679938925 :: [a6989586621679929428]) = GroupBy a6989586621679938924 a6989586621679938925
- data SortBySym0 :: forall a6989586621679929453. (~>) ((~>) a6989586621679929453 ((~>) a6989586621679929453 Ordering)) ((~>) [a6989586621679929453] [a6989586621679929453])
- data SortBySym1 (a6989586621679939043 :: (~>) a6989586621679929453 ((~>) a6989586621679929453 Ordering)) :: (~>) [a6989586621679929453] [a6989586621679929453]
- type SortBySym2 (a6989586621679939043 :: (~>) a6989586621679929453 ((~>) a6989586621679929453 Ordering)) (a6989586621679939044 :: [a6989586621679929453]) = SortBy a6989586621679939043 a6989586621679939044
- data InsertBySym0 :: forall a6989586621679929452. (~>) ((~>) a6989586621679929452 ((~>) a6989586621679929452 Ordering)) ((~>) a6989586621679929452 ((~>) [a6989586621679929452] [a6989586621679929452]))
- data InsertBySym1 (a6989586621679939013 :: (~>) a6989586621679929452 ((~>) a6989586621679929452 Ordering)) :: (~>) a6989586621679929452 ((~>) [a6989586621679929452] [a6989586621679929452])
- data InsertBySym2 (a6989586621679939013 :: (~>) a6989586621679929452 ((~>) a6989586621679929452 Ordering)) (a6989586621679939014 :: a6989586621679929452) :: (~>) [a6989586621679929452] [a6989586621679929452]
- type InsertBySym3 (a6989586621679939013 :: (~>) a6989586621679929452 ((~>) a6989586621679929452 Ordering)) (a6989586621679939014 :: a6989586621679929452) (a6989586621679939015 :: [a6989586621679929452]) = InsertBy a6989586621679939013 a6989586621679939014 a6989586621679939015
- data MaximumBySym0 :: forall a6989586621680438441 t6989586621680438440. (~>) ((~>) a6989586621680438441 ((~>) a6989586621680438441 Ordering)) ((~>) (t6989586621680438440 a6989586621680438441) a6989586621680438441)
- data MaximumBySym1 (a6989586621680438952 :: (~>) a6989586621680438441 ((~>) a6989586621680438441 Ordering)) :: forall t6989586621680438440. (~>) (t6989586621680438440 a6989586621680438441) a6989586621680438441
- type MaximumBySym2 (a6989586621680438952 :: (~>) a6989586621680438441 ((~>) a6989586621680438441 Ordering)) (a6989586621680438953 :: t6989586621680438440 a6989586621680438441) = MaximumBy a6989586621680438952 a6989586621680438953
- data MinimumBySym0 :: forall a6989586621680438439 t6989586621680438438. (~>) ((~>) a6989586621680438439 ((~>) a6989586621680438439 Ordering)) ((~>) (t6989586621680438438 a6989586621680438439) a6989586621680438439)
- data MinimumBySym1 (a6989586621680438927 :: (~>) a6989586621680438439 ((~>) a6989586621680438439 Ordering)) :: forall t6989586621680438438. (~>) (t6989586621680438438 a6989586621680438439) a6989586621680438439
- type MinimumBySym2 (a6989586621680438927 :: (~>) a6989586621680438439 ((~>) a6989586621680438439 Ordering)) (a6989586621680438928 :: t6989586621680438438 a6989586621680438439) = MinimumBy a6989586621680438927 a6989586621680438928
- data GenericLengthSym0 :: forall a6989586621679929412 i6989586621679929411. (~>) [a6989586621679929412] i6989586621679929411
- type GenericLengthSym1 (a6989586621679938670 :: [a6989586621679929412]) = GenericLength a6989586621679938670
- data GenericTakeSym0 :: forall a6989586621680055614 i6989586621680055613. (~>) i6989586621680055613 ((~>) [a6989586621680055614] [a6989586621680055614])
- data GenericTakeSym1 (a6989586621680068157 :: i6989586621680055613) :: forall a6989586621680055614. (~>) [a6989586621680055614] [a6989586621680055614]
- type GenericTakeSym2 (a6989586621680068157 :: i6989586621680055613) (a6989586621680068158 :: [a6989586621680055614]) = GenericTake a6989586621680068157 a6989586621680068158
- data GenericDropSym0 :: forall a6989586621680055612 i6989586621680055611. (~>) i6989586621680055611 ((~>) [a6989586621680055612] [a6989586621680055612])
- data GenericDropSym1 (a6989586621680068147 :: i6989586621680055611) :: forall a6989586621680055612. (~>) [a6989586621680055612] [a6989586621680055612]
- type GenericDropSym2 (a6989586621680068147 :: i6989586621680055611) (a6989586621680068148 :: [a6989586621680055612]) = GenericDrop a6989586621680068147 a6989586621680068148
- data GenericSplitAtSym0 :: forall a6989586621680055610 i6989586621680055609. (~>) i6989586621680055609 ((~>) [a6989586621680055610] ([a6989586621680055610], [a6989586621680055610]))
- data GenericSplitAtSym1 (a6989586621680068137 :: i6989586621680055609) :: forall a6989586621680055610. (~>) [a6989586621680055610] ([a6989586621680055610], [a6989586621680055610])
- type GenericSplitAtSym2 (a6989586621680068137 :: i6989586621680055609) (a6989586621680068138 :: [a6989586621680055610]) = GenericSplitAt a6989586621680068137 a6989586621680068138
- data GenericIndexSym0 :: forall a6989586621680055608 i6989586621680055607. (~>) [a6989586621680055608] ((~>) i6989586621680055607 a6989586621680055608)
- data GenericIndexSym1 (a6989586621680068127 :: [a6989586621680055608]) :: forall i6989586621680055607. (~>) i6989586621680055607 a6989586621680055608
- type GenericIndexSym2 (a6989586621680068127 :: [a6989586621680055608]) (a6989586621680068128 :: i6989586621680055607) = GenericIndex a6989586621680068127 a6989586621680068128
- data GenericReplicateSym0 :: forall a6989586621680055606 i6989586621680055605. (~>) i6989586621680055605 ((~>) a6989586621680055606 [a6989586621680055606])
- data GenericReplicateSym1 (a6989586621680068117 :: i6989586621680055605) :: forall a6989586621680055606. (~>) a6989586621680055606 [a6989586621680055606]
- type GenericReplicateSym2 (a6989586621680068117 :: i6989586621680055605) (a6989586621680068118 :: a6989586621680055606) = GenericReplicate a6989586621680068117 a6989586621680068118
The singleton for lists
data family Sing :: k -> Type infixr 5 Source #
The singleton kind-indexed data family.
Instances
SDecide k => TestCoercion (Sing :: k -> Type) Source # | |
Defined in Data.Singletons.Decide | |
SDecide k => TestEquality (Sing :: k -> Type) Source # | |
Defined in Data.Singletons.Decide | |
Show (SSymbol s) Source # | |
Show (SNat n) Source # | |
Eq (Sing a) Source # | |
Ord (Sing a) Source # | |
Show (Sing z) Source # | |
(ShowSing a, ShowSing [a]) => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
Show (Sing z) Source # | |
(ShowSing a, ShowSing b) => Show (Sing z) Source # | |
Show (Sing a) Source # | |
Show (Sing z) Source # | |
(ShowSing a, ShowSing b) => Show (Sing z) Source # | |
(ShowSing a, ShowSing b, ShowSing c) => Show (Sing z) Source # | |
(ShowSing a, ShowSing b, ShowSing c, ShowSing d) => Show (Sing z) Source # | |
(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e) => Show (Sing z) Source # | |
(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f) => Show (Sing z) Source # | |
(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f, ShowSing g) => Show (Sing z) Source # | |
Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
(ShowSing a, ShowSing b) => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
ShowSing m => Show (Sing z) Source # | |
ShowSing (Maybe a) => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
ShowSing (Maybe a) => Show (Sing z) Source # | |
ShowSing (Maybe a) => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
ShowSing Bool => Show (Sing z) Source # | |
ShowSing Bool => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
ShowSing a => Show (Sing z) Source # | |
(ShowSing a, ShowSing [a]) => Show (Sing z) Source # | |
data Sing (a :: Bool) Source # | |
data Sing (a :: Ordering) Source # | |
data Sing (n :: Nat) Source # | |
data Sing (n :: Symbol) Source # | |
Defined in Data.Singletons.TypeLits.Internal | |
data Sing (a :: ()) Source # | |
Defined in Data.Singletons.Prelude.Instances | |
data Sing (a :: Void) Source # | |
Defined in Data.Singletons.Prelude.Instances | |
data Sing (a :: All) Source # | |
data Sing (a :: Any) Source # | |
data Sing (a :: PErrorMessage) Source # | |
Defined in Data.Singletons.TypeError data Sing (a :: PErrorMessage) where
| |
data Sing (b :: [a]) Source # | |
data Sing (b :: Maybe a) Source # | |
data Sing (a :: TYPE rep) Source # | A choice of singleton for the kind Conceivably, one could generalize this instance to `Sing :: k -> Type` for
any kind We cannot produce explicit singleton values for everything in |
Defined in Data.Singletons.TypeRepTYPE | |
data Sing (b :: Min a) Source # | |
data Sing (b :: Max a) Source # | |
data Sing (b :: First a) Source # | |
data Sing (b :: Last a) Source # | |
data Sing (a :: WrappedMonoid m) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal data Sing (a :: WrappedMonoid m) where
| |
data Sing (b :: Option a) Source # | |
data Sing (b :: Identity a) Source # | |
data Sing (b :: First a) Source # | |
data Sing (b :: Last a) Source # | |
data Sing (b :: Dual a) Source # | |
data Sing (b :: Sum a) Source # | |
data Sing (b :: Product a) Source # | |
data Sing (b :: Down a) Source # | |
data Sing (b :: NonEmpty a) Source # | |
data Sing (c :: Either a b) Source # | |
data Sing (c :: (a, b)) Source # | |
data Sing (c :: Arg a b) Source # | |
data Sing (f :: k1 ~> k2) Source # | |
data Sing (d :: (a, b, c)) Source # | |
data Sing (c :: Const a b) Source # | |
data Sing (e :: (a, b, c, d)) Source # | |
data Sing (f :: (a, b, c, d, e)) Source # | |
data Sing (g :: (a, b, c, d, e, f)) Source # | |
data Sing (h :: (a, b, c, d, e, f, g)) Source # | |
Defined in Data.Singletons.Prelude.Instances |
Though Haddock doesn't show it, the Sing
instance above declares
constructors
SNil :: Sing '[] SCons :: Sing (h :: k) -> Sing (t :: [k]) -> Sing (h ': t)
Basic functions
(%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a]) infixr 5 Source #
type family Null (arg :: t a) :: Bool Source #
Instances
type family Length (arg :: t a) :: Nat Source #
Instances
List transformations
sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b]) Source #
type family Intersperse (a :: a) (a :: [a]) :: [a] where ... Source #
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 ~> (a6989586621680438535 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680438535]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680438535 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680438535) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Min a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Max a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (a1 :: k2 ~> (a6989586621680438535 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680438535) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680438535 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680438535) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680438535 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680438535) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680438535 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680438535) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680438535 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680438535) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Arg a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Const m a) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source #
type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #
Instances
type Foldl' (a1 :: k2 ~> (a6989586621680438537 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680438537]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Min a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Max a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (a1 :: k2 ~> (a6989586621680438537 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680438537) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680438537 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680438537) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680438537 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680438537) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680438537 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680438537) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Arg a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Const m a) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) Source #
type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #
Instances
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Min a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Max a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Arg a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Const m a) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) Source #
sFoldl1' :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a) Source #
type family Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b Source #
Instances
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680438530]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Min a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Max a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a6989586621680438530 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Either a1 a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a6989586621680438530 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: (a1, a6989586621680438530)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a6989586621680438530 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Arg a1 a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680438530 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Const m a6989586621680438530) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source #
type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #
Instances
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Min a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Max a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Arg a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Const m a) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) Source #
Special folds
sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a]) Source #
sConcatMap :: forall t a b (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) Source #
type family And (a :: t Bool) :: Bool where ... Source #
And x = Case_6989586621680439017 x (Let6989586621680439015Scrutinee_6989586621680438773Sym1 x) |
type family Or (a :: t Bool) :: Bool where ... Source #
Or x = Case_6989586621680439008 x (Let6989586621680439006Scrutinee_6989586621680438775Sym1 x) |
type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #
Any p x = Case_6989586621680438999 p x (Let6989586621680438996Scrutinee_6989586621680438777Sym2 p x) |
sAny :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool) Source #
type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #
All p x = Case_6989586621680438986 p x (Let6989586621680438983Scrutinee_6989586621680438779Sym2 p x) |
sAll :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) Source #
type family Sum (arg :: t a) :: a Source #
Instances
sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a) Source #
type family Product (arg :: t a) :: a Source #
Instances
sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a) Source #
type family Maximum (arg :: t a) :: a Source #
Instances
sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a) Source #
type family Minimum (arg :: t a) :: a Source #
Instances
sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a) Source #
Building lists
Scans
sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b]) Source #
sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a]) Source #
sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b]) Source #
type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ... Source #
Scanr1 _ '[] = '[] | |
Scanr1 _ '[x] = Apply (Apply (:@#@$) x) '[] | |
Scanr1 f ((:) x ((:) wild_6989586621679930020 wild_6989586621679930022)) = Case_6989586621679939599 f x wild_6989586621679930020 wild_6989586621679930022 (Let6989586621679939594Scrutinee_6989586621679930014Sym4 f x wild_6989586621679930020 wild_6989586621679930022) |
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_6989586621680741097 f s t (Let6989586621680741093Scrutinee_6989586621680740628Sym3 f s t) |
sMapAccumL :: forall t a b c (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (a, t c)) Source #
type family MapAccumR (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ... Source #
MapAccumR f s t = Case_6989586621680741080 f s t (Let6989586621680741076Scrutinee_6989586621680740632Sym3 f s t) |
sMapAccumR :: forall t a b c (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c)) Source #
Cyclical lists
type family Replicate (a :: Nat) (a :: a) :: [a] where ... Source #
Replicate n x = Case_6989586621679938731 n x (Let6989586621679938728Scrutinee_6989586621679930116Sym2 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_6989586621679939447 f b (Let6989586621679939444Scrutinee_6989586621679930024Sym2 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 Let6989586621679938885XsSym0) Let6989586621679938885XsSym0 | |
Span p ((:) x xs') = Case_6989586621679938897 p x xs' (Let6989586621679938893Scrutinee_6989586621679930096Sym3 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 Let6989586621679938842XsSym0) Let6989586621679938842XsSym0 | |
Break p ((:) x xs') = Case_6989586621679938854 p x xs' (Let6989586621679938850Scrutinee_6989586621679930098Sym3 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_6989586621680055731 arg_6989586621680055733 = Case_6989586621680068380 arg_6989586621680055731 arg_6989586621680055733 (Apply (Apply Tuple2Sym0 arg_6989586621680055731) arg_6989586621680055733) |
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 (a1 :: k1) (a2 :: [k1]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (a1 :: k1) (a2 :: [k1]) | |
type Elem (arg1 :: a) (arg2 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (arg1 :: a) (arg2 :: Min a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a) (arg2 :: Max a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a) (arg2 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a) (arg2 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a) (arg2 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (a1 :: k1) (a2 :: Identity k1) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Elem (arg1 :: a) (arg2 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (arg1 :: a) (arg2 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (a1 :: k1) (a2 :: Dual k1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (a1 :: k1) (a2 :: Sum k1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (a1 :: k1) (a2 :: Product k1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (arg1 :: a) (arg2 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (arg1 :: a1) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (arg1 :: a1) (arg2 :: (a2, a1)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (arg1 :: a1) (arg2 :: (a2, a1)) | |
type Elem (arg1 :: a1) (arg2 :: Arg a2 a1) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Elem (arg1 :: a) (arg2 :: Const m a) Source # | |
Defined in Data.Singletons.Prelude.Const |
sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) Source #
sNotElem :: forall t a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) Source #
type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... Source #
Lookup _key '[] = NothingSym0 | |
Lookup key ((:) '(x, y) xys) = Case_6989586621679938801 key x y xys (Let6989586621679938796Scrutinee_6989586621679930112Sym4 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_6989586621680438915 p y (Let6989586621680438898Scrutinee_6989586621680438785Sym2 p y) |
sFind :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a) Source #
sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) Source #
sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) Source #
Indexing lists
(%!!) :: forall a (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) infixl 9 Source #
sElemIndex :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat) Source #
type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ... Source #
ElemIndices x a_6989586621679939361 = Apply (Apply FindIndicesSym0 (Apply (==@#@$) x)) a_6989586621679939361 |
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_6989586621679939369 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679939369 |
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_6989586621680068353 a_6989586621680068355 a_6989586621680068357 a_6989586621680068359 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621680068353) a_6989586621680068355) a_6989586621680068357) a_6989586621680068359 |
type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ... Source #
Zip5 a_6989586621680068328 a_6989586621680068330 a_6989586621680068332 a_6989586621680068334 a_6989586621680068336 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621680068328) a_6989586621680068330) a_6989586621680068332) a_6989586621680068334) a_6989586621680068336 |
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_6989586621680068298 a_6989586621680068300 a_6989586621680068302 a_6989586621680068304 a_6989586621680068306 a_6989586621680068308 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621680068298) a_6989586621680068300) a_6989586621680068302) a_6989586621680068304) a_6989586621680068306) a_6989586621680068308 |
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_6989586621680068263 a_6989586621680068265 a_6989586621680068267 a_6989586621680068269 a_6989586621680068271 a_6989586621680068273 a_6989586621680068275 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621680068263) a_6989586621680068265) a_6989586621680068267) a_6989586621680068269) a_6989586621680068271) a_6989586621680068273) a_6989586621680068275 |
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_6989586621679939051 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679939051 |
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_6989586621679939080 a_6989586621679939082 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679939080) a_6989586621679939082 |
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_6989586621679930082 wild_6989586621679930084) ((:) wild_6989586621679930086 wild_6989586621679930088) = Apply (Apply (>>=@#@$) (Let6989586621679939670XsSym5 eq wild_6989586621679930082 wild_6989586621679930084 wild_6989586621679930086 wild_6989586621679930088)) (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679939681Sym0 eq) wild_6989586621679930082) wild_6989586621679930084) wild_6989586621679930086) wild_6989586621679930088) |
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_6989586621680438956 = Apply (Apply Foldl1Sym0 (Let6989586621680438960Max'Sym2 cmp a_6989586621680438956)) a_6989586621680438956 |
sMaximumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) Source #
type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #
MinimumBy cmp a_6989586621680438931 = Apply (Apply Foldl1Sym0 (Let6989586621680438935Min'Sym2 cmp a_6989586621680438931)) a_6989586621680438931 |
sMinimumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) Source #
The "generic
" operations
The prefix `generic
' indicates an overloaded function that
is a generalized version of a Prelude function.
type family GenericLength (a :: [a]) :: i where ... Source #
GenericLength '[] = FromInteger 0 | |
GenericLength ((:) _ xs) = Apply (Apply (+@#@$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
sGenericLength :: forall i a (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i) Source #
type family GenericTake (a :: i) (a :: [a]) :: [a] where ... Source #
GenericTake a_6989586621680068153 a_6989586621680068155 = Apply (Apply TakeSym0 a_6989586621680068153) a_6989586621680068155 |
type family GenericDrop (a :: i) (a :: [a]) :: [a] where ... Source #
GenericDrop a_6989586621680068143 a_6989586621680068145 = Apply (Apply DropSym0 a_6989586621680068143) a_6989586621680068145 |
type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ... Source #
GenericSplitAt a_6989586621680068133 a_6989586621680068135 = Apply (Apply SplitAtSym0 a_6989586621680068133) a_6989586621680068135 |
type family GenericIndex (a :: [a]) (a :: i) :: a where ... Source #
GenericIndex a_6989586621680068123 a_6989586621680068125 = Apply (Apply (!!@#@$) a_6989586621680068123) a_6989586621680068125 |
type family GenericReplicate (a :: i) (a :: a) :: [a] where ... Source #
GenericReplicate a_6989586621680068113 a_6989586621680068115 = Apply (Apply ReplicateSym0 a_6989586621680068113) a_6989586621680068115 |
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) (t6989586621679291660 :: a3530822107858468865) Source # | |
data (:@#@$$) (t6989586621679291660 :: (a3530822107858468865 :: Type)) :: (~>) [a3530822107858468865] [(a3530822107858468865 :: Type)] infixr 5 Source #
Instances
SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((:@#@$$) t6989586621679291660 :: TyFun [a3530822107858468865] [a3530822107858468865] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances suppressUnusedWarnings :: () Source # | |
type Apply ((:@#@$$) t6989586621679291660 :: TyFun [a] [a] -> Type) (t6989586621679291661 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Instances |
type (:@#@$$$) (t6989586621679291660 :: a3530822107858468865) (t6989586621679291661 :: [a3530822107858468865]) = (:) t6989586621679291660 t6989586621679291661 Source #
type (++@#@$$$) (a6989586621679511994 :: [a6989586621679511797]) (a6989586621679511995 :: [a6989586621679511797]) = (++) a6989586621679511994 a6989586621679511995 Source #
data (++@#@$$) (a6989586621679511994 :: [a6989586621679511797]) :: (~>) [a6989586621679511797] [a6989586621679511797] infixr 5 Source #
Instances
SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((++@#@$$) a6989586621679511994 :: TyFun [a6989586621679511797] [a6989586621679511797] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$$) a6989586621679511994 :: TyFun [a] [a] -> Type) (a6989586621679511995 :: [a]) Source # | |
data (++@#@$) :: forall a6989586621679511797. (~>) [a6989586621679511797] ((~>) [a6989586621679511797] [a6989586621679511797]) infixr 5 Source #
Instances
SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679511797] ([a6989586621679511797] ~> [a6989586621679511797]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$) :: TyFun [a6989586621679511797] ([a6989586621679511797] ~> [a6989586621679511797]) -> Type) (a6989586621679511994 :: [a6989586621679511797]) Source # | |
data HeadSym0 :: forall a6989586621679929539. (~>) [a6989586621679929539] a6989586621679929539 Source #
Instances
SingI (HeadSym0 :: TyFun [a] a -> Type) Source # | |
SuppressUnusedWarnings (HeadSym0 :: TyFun [a6989586621679929539] a6989586621679929539 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679940062 :: [a]) Source # | |
data LastSym0 :: forall a6989586621679929538. (~>) [a6989586621679929538] a6989586621679929538 Source #
Instances
SingI (LastSym0 :: TyFun [a] a -> Type) Source # | |
SuppressUnusedWarnings (LastSym0 :: TyFun [a6989586621679929538] a6989586621679929538 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679940057 :: [a]) Source # | |
data TailSym0 :: forall a6989586621679929537. (~>) [a6989586621679929537] [a6989586621679929537] Source #
Instances
SingI (TailSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (TailSym0 :: TyFun [a6989586621679929537] [a6989586621679929537] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679940054 :: [a]) Source # | |
data InitSym0 :: forall a6989586621679929536. (~>) [a6989586621679929536] [a6989586621679929536] Source #
Instances
SingI (InitSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (InitSym0 :: TyFun [a6989586621679929536] [a6989586621679929536] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679940040 :: [a]) Source # | |
data NullSym0 :: forall a6989586621680438541 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438541) Bool Source #
Instances
SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680438526 a6989586621680438541) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680439189 :: t a) Source # | |
type NullSym1 (arg6989586621680439189 :: t6989586621680438526 a6989586621680438541) = Null arg6989586621680439189 Source #
data LengthSym0 :: forall a6989586621680438542 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438542) 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 (t6989586621680438526 a6989586621680438542) Nat -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (arg6989586621680439191 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type LengthSym1 (arg6989586621680439191 :: t6989586621680438526 a6989586621680438542) = Length arg6989586621680439191 Source #
data MapSym0 :: forall a6989586621679511798 b6989586621679511799. (~>) ((~>) a6989586621679511798 b6989586621679511799) ((~>) [a6989586621679511798] [b6989586621679511799]) Source #
Instances
SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (MapSym0 :: TyFun (a6989586621679511798 ~> b6989586621679511799) ([a6989586621679511798] ~> [b6989586621679511799]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply (MapSym0 :: TyFun (a6989586621679511798 ~> b6989586621679511799) ([a6989586621679511798] ~> [b6989586621679511799]) -> Type) (a6989586621679512002 :: a6989586621679511798 ~> b6989586621679511799) Source # | |
data MapSym1 (a6989586621679512002 :: (~>) a6989586621679511798 b6989586621679511799) :: (~>) [a6989586621679511798] [b6989586621679511799] Source #
Instances
SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (MapSym1 a6989586621679512002 :: TyFun [a6989586621679511798] [b6989586621679511799] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base suppressUnusedWarnings :: () Source # | |
type Apply (MapSym1 a6989586621679512002 :: TyFun [a] [b] -> Type) (a6989586621679512003 :: [a]) Source # | |
type MapSym2 (a6989586621679512002 :: (~>) a6989586621679511798 b6989586621679511799) (a6989586621679512003 :: [a6989586621679511798]) = Map a6989586621679512002 a6989586621679512003 Source #
data ReverseSym0 :: forall a6989586621679929534. (~>) [a6989586621679929534] [a6989586621679929534] Source #
Instances
SingI (ReverseSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing ReverseSym0 Source # | |
SuppressUnusedWarnings (ReverseSym0 :: TyFun [a6989586621679929534] [a6989586621679929534] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679939993 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679939993 :: [a]) = Reverse a6989586621679939993 |
type ReverseSym1 (a6989586621679939993 :: [a6989586621679929534]) = Reverse a6989586621679939993 Source #
data IntersperseSym0 :: forall a6989586621679929533. (~>) a6989586621679929533 ((~>) [a6989586621679929533] [a6989586621679929533]) Source #
Instances
SingI (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679929533 ([a6989586621679929533] ~> [a6989586621679929533]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym0 :: TyFun a6989586621679929533 ([a6989586621679929533] ~> [a6989586621679929533]) -> Type) (a6989586621679939980 :: a6989586621679929533) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym0 :: TyFun a6989586621679929533 ([a6989586621679929533] ~> [a6989586621679929533]) -> Type) (a6989586621679939980 :: a6989586621679929533) = IntersperseSym1 a6989586621679939980 |
data IntersperseSym1 (a6989586621679939980 :: a6989586621679929533) :: (~>) [a6989586621679929533] [a6989586621679929533] 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 a6989586621679939980 :: TyFun [a6989586621679929533] [a6989586621679929533] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym1 a6989586621679939980 :: TyFun [a] [a] -> Type) (a6989586621679939981 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym1 a6989586621679939980 :: TyFun [a] [a] -> Type) (a6989586621679939981 :: [a]) = Intersperse a6989586621679939980 a6989586621679939981 |
type IntersperseSym2 (a6989586621679939980 :: a6989586621679929533) (a6989586621679939981 :: [a6989586621679929533]) = Intersperse a6989586621679939980 a6989586621679939981 Source #
data IntercalateSym0 :: forall a6989586621679929532. (~>) [a6989586621679929532] ((~>) [[a6989586621679929532]] [a6989586621679929532]) Source #
Instances
SingI (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a6989586621679929532] ([[a6989586621679929532]] ~> [a6989586621679929532]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym0 :: TyFun [a6989586621679929532] ([[a6989586621679929532]] ~> [a6989586621679929532]) -> Type) (a6989586621679939987 :: [a6989586621679929532]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym0 :: TyFun [a6989586621679929532] ([[a6989586621679929532]] ~> [a6989586621679929532]) -> Type) (a6989586621679939987 :: [a6989586621679929532]) = IntercalateSym1 a6989586621679939987 |
data IntercalateSym1 (a6989586621679939987 :: [a6989586621679929532]) :: (~>) [[a6989586621679929532]] [a6989586621679929532] 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 a6989586621679939987 :: TyFun [[a6989586621679929532]] [a6989586621679929532] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym1 a6989586621679939987 :: TyFun [[a]] [a] -> Type) (a6989586621679939988 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym1 a6989586621679939987 :: TyFun [[a]] [a] -> Type) (a6989586621679939988 :: [[a]]) = Intercalate a6989586621679939987 a6989586621679939988 |
type IntercalateSym2 (a6989586621679939987 :: [a6989586621679929532]) (a6989586621679939988 :: [[a6989586621679929532]]) = Intercalate a6989586621679939987 a6989586621679939988 Source #
data TransposeSym0 :: forall a6989586621679929419. (~>) [[a6989586621679929419]] [[a6989586621679929419]] Source #
Instances
SingI (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing TransposeSym0 Source # | |
SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a6989586621679929419]] [[a6989586621679929419]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679940065 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679940065 :: [[a]]) = Transpose a6989586621679940065 |
type TransposeSym1 (a6989586621679940065 :: [[a6989586621679929419]]) = Transpose a6989586621679940065 Source #
data SubsequencesSym0 :: forall a6989586621679929531. (~>) [a6989586621679929531] [[a6989586621679929531]] Source #
Instances
SingI (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a6989586621679929531] [[a6989586621679929531]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679939977 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679939977 :: [a]) = Subsequences a6989586621679939977 |
type SubsequencesSym1 (a6989586621679939977 :: [a6989586621679929531]) = Subsequences a6989586621679939977 Source #
data PermutationsSym0 :: forall a6989586621679929528. (~>) [a6989586621679929528] [[a6989586621679929528]] Source #
Instances
SingI (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a6989586621679929528] [[a6989586621679929528]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679939859 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679939859 :: [a]) = Permutations a6989586621679939859 |
type PermutationsSym1 (a6989586621679939859 :: [a6989586621679929528]) = Permutations a6989586621679939859 Source #
data FoldlSym0 :: forall a6989586621680438535 b6989586621680438534 t6989586621680438526. (~>) ((~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) ((~>) b6989586621680438534 ((~>) (t6989586621680438526 a6989586621680438535) b6989586621680438534)) Source #
Instances
SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym0 :: TyFun (b6989586621680438534 ~> (a6989586621680438535 ~> b6989586621680438534)) (b6989586621680438534 ~> (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym0 :: TyFun (b6989586621680438534 ~> (a6989586621680438535 ~> b6989586621680438534)) (b6989586621680438534 ~> (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534)) -> Type) (arg6989586621680439167 :: b6989586621680438534 ~> (a6989586621680438535 ~> b6989586621680438534)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldlSym0 :: TyFun (b6989586621680438534 ~> (a6989586621680438535 ~> b6989586621680438534)) (b6989586621680438534 ~> (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534)) -> Type) (arg6989586621680439167 :: b6989586621680438534 ~> (a6989586621680438535 ~> b6989586621680438534)) = (FoldlSym1 arg6989586621680439167 t6989586621680438526 :: TyFun b6989586621680438534 (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534) -> Type) |
data FoldlSym1 (arg6989586621680439167 :: (~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) :: forall t6989586621680438526. (~>) b6989586621680438534 ((~>) (t6989586621680438526 a6989586621680438535) b6989586621680438534) Source #
Instances
(SFoldable t, SingI d) => SingI (FoldlSym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym1 arg6989586621680439167 t6989586621680438526 :: TyFun b6989586621680438534 (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym1 arg6989586621680439167 t6989586621680438526 :: TyFun b6989586621680438534 (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534) -> Type) (arg6989586621680439168 :: b6989586621680438534) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldlSym1 arg6989586621680439167 t6989586621680438526 :: TyFun b6989586621680438534 (t6989586621680438526 a6989586621680438535 ~> b6989586621680438534) -> Type) (arg6989586621680439168 :: b6989586621680438534) = (FoldlSym2 arg6989586621680439167 arg6989586621680439168 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438535) b6989586621680438534 -> Type) |
data FoldlSym2 (arg6989586621680439167 :: (~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) (arg6989586621680439168 :: b6989586621680438534) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438535) b6989586621680438534 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym2 arg6989586621680439168 arg6989586621680439167 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438535) b6989586621680438534 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym2 arg6989586621680439168 arg6989586621680439167 t :: TyFun (t a) b -> Type) (arg6989586621680439169 :: t a) Source # | |
type FoldlSym3 (arg6989586621680439167 :: (~>) b6989586621680438534 ((~>) a6989586621680438535 b6989586621680438534)) (arg6989586621680439168 :: b6989586621680438534) (arg6989586621680439169 :: t6989586621680438526 a6989586621680438535) = Foldl arg6989586621680439167 arg6989586621680439168 arg6989586621680439169 Source #
data Foldl'Sym0 :: forall a6989586621680438537 b6989586621680438536 t6989586621680438526. (~>) ((~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) ((~>) b6989586621680438536 ((~>) (t6989586621680438526 a6989586621680438537) b6989586621680438536)) 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 (b6989586621680438536 ~> (a6989586621680438537 ~> b6989586621680438536)) (b6989586621680438536 ~> (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym0 :: TyFun (b6989586621680438536 ~> (a6989586621680438537 ~> b6989586621680438536)) (b6989586621680438536 ~> (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536)) -> Type) (arg6989586621680439173 :: b6989586621680438536 ~> (a6989586621680438537 ~> b6989586621680438536)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym0 :: TyFun (b6989586621680438536 ~> (a6989586621680438537 ~> b6989586621680438536)) (b6989586621680438536 ~> (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536)) -> Type) (arg6989586621680439173 :: b6989586621680438536 ~> (a6989586621680438537 ~> b6989586621680438536)) = (Foldl'Sym1 arg6989586621680439173 t6989586621680438526 :: TyFun b6989586621680438536 (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536) -> Type) |
data Foldl'Sym1 (arg6989586621680439173 :: (~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) :: forall t6989586621680438526. (~>) b6989586621680438536 ((~>) (t6989586621680438526 a6989586621680438537) b6989586621680438536) 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 arg6989586621680439173 t6989586621680438526 :: TyFun b6989586621680438536 (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym1 arg6989586621680439173 t6989586621680438526 :: TyFun b6989586621680438536 (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536) -> Type) (arg6989586621680439174 :: b6989586621680438536) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym1 arg6989586621680439173 t6989586621680438526 :: TyFun b6989586621680438536 (t6989586621680438526 a6989586621680438537 ~> b6989586621680438536) -> Type) (arg6989586621680439174 :: b6989586621680438536) = (Foldl'Sym2 arg6989586621680439173 arg6989586621680439174 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438537) b6989586621680438536 -> Type) |
data Foldl'Sym2 (arg6989586621680439173 :: (~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) (arg6989586621680439174 :: b6989586621680438536) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438537) b6989586621680438536 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 arg6989586621680439174 arg6989586621680439173 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438537) b6989586621680438536 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym2 arg6989586621680439174 arg6989586621680439173 t :: TyFun (t a) b -> Type) (arg6989586621680439175 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym2 arg6989586621680439174 arg6989586621680439173 t :: TyFun (t a) b -> Type) (arg6989586621680439175 :: t a) = Foldl' arg6989586621680439174 arg6989586621680439173 arg6989586621680439175 |
type Foldl'Sym3 (arg6989586621680439173 :: (~>) b6989586621680438536 ((~>) a6989586621680438537 b6989586621680438536)) (arg6989586621680439174 :: b6989586621680438536) (arg6989586621680439175 :: t6989586621680438526 a6989586621680438537) = Foldl' arg6989586621680439173 arg6989586621680439174 arg6989586621680439175 Source #
data Foldl1Sym0 :: forall a6989586621680438539 t6989586621680438526. (~>) ((~>) a6989586621680438539 ((~>) a6989586621680438539 a6989586621680438539)) ((~>) (t6989586621680438526 a6989586621680438539) a6989586621680438539) 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 (a6989586621680438539 ~> (a6989586621680438539 ~> a6989586621680438539)) (t6989586621680438526 a6989586621680438539 ~> a6989586621680438539) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym0 :: TyFun (a6989586621680438539 ~> (a6989586621680438539 ~> a6989586621680438539)) (t6989586621680438526 a6989586621680438539 ~> a6989586621680438539) -> Type) (arg6989586621680439183 :: a6989586621680438539 ~> (a6989586621680438539 ~> a6989586621680438539)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl1Sym0 :: TyFun (a6989586621680438539 ~> (a6989586621680438539 ~> a6989586621680438539)) (t6989586621680438526 a6989586621680438539 ~> a6989586621680438539) -> Type) (arg6989586621680439183 :: a6989586621680438539 ~> (a6989586621680438539 ~> a6989586621680438539)) = (Foldl1Sym1 arg6989586621680439183 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438539) a6989586621680438539 -> Type) |
data Foldl1Sym1 (arg6989586621680439183 :: (~>) a6989586621680438539 ((~>) a6989586621680438539 a6989586621680438539)) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438539) a6989586621680438539 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 arg6989586621680439183 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438539) a6989586621680438539 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym1 arg6989586621680439183 t :: TyFun (t a) a -> Type) (arg6989586621680439184 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl1Sym1 arg6989586621680439183 t :: TyFun (t a) a -> Type) (arg6989586621680439184 :: t a) = Foldl1 arg6989586621680439183 arg6989586621680439184 |
type Foldl1Sym2 (arg6989586621680439183 :: (~>) a6989586621680438539 ((~>) a6989586621680438539 a6989586621680438539)) (arg6989586621680439184 :: t6989586621680438526 a6989586621680438539) = Foldl1 arg6989586621680439183 arg6989586621680439184 Source #
data Foldl1'Sym0 :: forall a6989586621679929524. (~>) ((~>) a6989586621679929524 ((~>) a6989586621679929524 a6989586621679929524)) ((~>) [a6989586621679929524] a6989586621679929524) 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 (a6989586621679929524 ~> (a6989586621679929524 ~> a6989586621679929524)) ([a6989586621679929524] ~> a6989586621679929524) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym0 :: TyFun (a6989586621679929524 ~> (a6989586621679929524 ~> a6989586621679929524)) ([a6989586621679929524] ~> a6989586621679929524) -> Type) (a6989586621679939852 :: a6989586621679929524 ~> (a6989586621679929524 ~> a6989586621679929524)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym0 :: TyFun (a6989586621679929524 ~> (a6989586621679929524 ~> a6989586621679929524)) ([a6989586621679929524] ~> a6989586621679929524) -> Type) (a6989586621679939852 :: a6989586621679929524 ~> (a6989586621679929524 ~> a6989586621679929524)) = Foldl1'Sym1 a6989586621679939852 |
data Foldl1'Sym1 (a6989586621679939852 :: (~>) a6989586621679929524 ((~>) a6989586621679929524 a6989586621679929524)) :: (~>) [a6989586621679929524] a6989586621679929524 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 a6989586621679939852 :: TyFun [a6989586621679929524] a6989586621679929524 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym1 a6989586621679939852 :: TyFun [a] a -> Type) (a6989586621679939853 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym1 a6989586621679939852 :: TyFun [a] a -> Type) (a6989586621679939853 :: [a]) = Foldl1' a6989586621679939852 a6989586621679939853 |
type Foldl1'Sym2 (a6989586621679939852 :: (~>) a6989586621679929524 ((~>) a6989586621679929524 a6989586621679929524)) (a6989586621679939853 :: [a6989586621679929524]) = Foldl1' a6989586621679939852 a6989586621679939853 Source #
data FoldrSym0 :: forall a6989586621680438530 b6989586621680438531 t6989586621680438526. (~>) ((~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) ((~>) b6989586621680438531 ((~>) (t6989586621680438526 a6989586621680438530) b6989586621680438531)) Source #
Instances
SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym0 :: TyFun (a6989586621680438530 ~> (b6989586621680438531 ~> b6989586621680438531)) (b6989586621680438531 ~> (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym0 :: TyFun (a6989586621680438530 ~> (b6989586621680438531 ~> b6989586621680438531)) (b6989586621680438531 ~> (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531)) -> Type) (arg6989586621680439155 :: a6989586621680438530 ~> (b6989586621680438531 ~> b6989586621680438531)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldrSym0 :: TyFun (a6989586621680438530 ~> (b6989586621680438531 ~> b6989586621680438531)) (b6989586621680438531 ~> (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531)) -> Type) (arg6989586621680439155 :: a6989586621680438530 ~> (b6989586621680438531 ~> b6989586621680438531)) = (FoldrSym1 arg6989586621680439155 t6989586621680438526 :: TyFun b6989586621680438531 (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531) -> Type) |
data FoldrSym1 (arg6989586621680439155 :: (~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) :: forall t6989586621680438526. (~>) b6989586621680438531 ((~>) (t6989586621680438526 a6989586621680438530) b6989586621680438531) Source #
Instances
(SFoldable t, SingI d) => SingI (FoldrSym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym1 arg6989586621680439155 t6989586621680438526 :: TyFun b6989586621680438531 (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym1 arg6989586621680439155 t6989586621680438526 :: TyFun b6989586621680438531 (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531) -> Type) (arg6989586621680439156 :: b6989586621680438531) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldrSym1 arg6989586621680439155 t6989586621680438526 :: TyFun b6989586621680438531 (t6989586621680438526 a6989586621680438530 ~> b6989586621680438531) -> Type) (arg6989586621680439156 :: b6989586621680438531) = (FoldrSym2 arg6989586621680439155 arg6989586621680439156 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438530) b6989586621680438531 -> Type) |
data FoldrSym2 (arg6989586621680439155 :: (~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) (arg6989586621680439156 :: b6989586621680438531) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438530) b6989586621680438531 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym2 arg6989586621680439156 arg6989586621680439155 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438530) b6989586621680438531 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym2 arg6989586621680439156 arg6989586621680439155 t :: TyFun (t a) b -> Type) (arg6989586621680439157 :: t a) Source # | |
type FoldrSym3 (arg6989586621680439155 :: (~>) a6989586621680438530 ((~>) b6989586621680438531 b6989586621680438531)) (arg6989586621680439156 :: b6989586621680438531) (arg6989586621680439157 :: t6989586621680438526 a6989586621680438530) = Foldr arg6989586621680439155 arg6989586621680439156 arg6989586621680439157 Source #
data Foldr1Sym0 :: forall a6989586621680438538 t6989586621680438526. (~>) ((~>) a6989586621680438538 ((~>) a6989586621680438538 a6989586621680438538)) ((~>) (t6989586621680438526 a6989586621680438538) a6989586621680438538) 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 (a6989586621680438538 ~> (a6989586621680438538 ~> a6989586621680438538)) (t6989586621680438526 a6989586621680438538 ~> a6989586621680438538) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym0 :: TyFun (a6989586621680438538 ~> (a6989586621680438538 ~> a6989586621680438538)) (t6989586621680438526 a6989586621680438538 ~> a6989586621680438538) -> Type) (arg6989586621680439179 :: a6989586621680438538 ~> (a6989586621680438538 ~> a6989586621680438538)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr1Sym0 :: TyFun (a6989586621680438538 ~> (a6989586621680438538 ~> a6989586621680438538)) (t6989586621680438526 a6989586621680438538 ~> a6989586621680438538) -> Type) (arg6989586621680439179 :: a6989586621680438538 ~> (a6989586621680438538 ~> a6989586621680438538)) = (Foldr1Sym1 arg6989586621680439179 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438538) a6989586621680438538 -> Type) |
data Foldr1Sym1 (arg6989586621680439179 :: (~>) a6989586621680438538 ((~>) a6989586621680438538 a6989586621680438538)) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438538) a6989586621680438538 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 arg6989586621680439179 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438538) a6989586621680438538 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym1 arg6989586621680439179 t :: TyFun (t a) a -> Type) (arg6989586621680439180 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr1Sym1 arg6989586621680439179 t :: TyFun (t a) a -> Type) (arg6989586621680439180 :: t a) = Foldr1 arg6989586621680439179 arg6989586621680439180 |
type Foldr1Sym2 (arg6989586621680439179 :: (~>) a6989586621680438538 ((~>) a6989586621680438538 a6989586621680438538)) (arg6989586621680439180 :: t6989586621680438526 a6989586621680438538) = Foldr1 arg6989586621680439179 arg6989586621680439180 Source #
data ConcatSym0 :: forall a6989586621680438452 t6989586621680438451. (~>) (t6989586621680438451 [a6989586621680438452]) [a6989586621680438452] 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 (t6989586621680438451 [a6989586621680438452]) [a6989586621680438452] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680439037 :: t [a]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680439037 :: t [a]) = Concat a6989586621680439037 |
type ConcatSym1 (a6989586621680439037 :: t6989586621680438451 [a6989586621680438452]) = Concat a6989586621680439037 Source #
data ConcatMapSym0 :: forall a6989586621680438449 b6989586621680438450 t6989586621680438448. (~>) ((~>) a6989586621680438449 [b6989586621680438450]) ((~>) (t6989586621680438448 a6989586621680438449) [b6989586621680438450]) 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 (a6989586621680438449 ~> [b6989586621680438450]) (t6989586621680438448 a6989586621680438449 ~> [b6989586621680438450]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym0 :: TyFun (a6989586621680438449 ~> [b6989586621680438450]) (t6989586621680438448 a6989586621680438449 ~> [b6989586621680438450]) -> Type) (a6989586621680439021 :: a6989586621680438449 ~> [b6989586621680438450]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym0 :: TyFun (a6989586621680438449 ~> [b6989586621680438450]) (t6989586621680438448 a6989586621680438449 ~> [b6989586621680438450]) -> Type) (a6989586621680439021 :: a6989586621680438449 ~> [b6989586621680438450]) = (ConcatMapSym1 a6989586621680439021 t6989586621680438448 :: TyFun (t6989586621680438448 a6989586621680438449) [b6989586621680438450] -> Type) |
data ConcatMapSym1 (a6989586621680439021 :: (~>) a6989586621680438449 [b6989586621680438450]) :: forall t6989586621680438448. (~>) (t6989586621680438448 a6989586621680438449) [b6989586621680438450] 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 a6989586621680439021 t6989586621680438448 :: TyFun (t6989586621680438448 a6989586621680438449) [b6989586621680438450] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym1 a6989586621680439021 t :: TyFun (t a) [b] -> Type) (a6989586621680439022 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym1 a6989586621680439021 t :: TyFun (t a) [b] -> Type) (a6989586621680439022 :: t a) = ConcatMap a6989586621680439021 a6989586621680439022 |
type ConcatMapSym2 (a6989586621680439021 :: (~>) a6989586621680438449 [b6989586621680438450]) (a6989586621680439022 :: t6989586621680438448 a6989586621680438449) = ConcatMap a6989586621680439021 a6989586621680439022 Source #
data AndSym0 :: forall t6989586621680438447. (~>) (t6989586621680438447 Bool) Bool Source #
Instances
SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
SuppressUnusedWarnings (AndSym0 :: TyFun (t6989586621680438447 Bool) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680439012 :: t Bool) Source # | |
type AndSym1 (a6989586621680439012 :: t6989586621680438447 Bool) = And a6989586621680439012 Source #
data OrSym0 :: forall t6989586621680438446. (~>) (t6989586621680438446 Bool) Bool Source #
Instances
SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
SuppressUnusedWarnings (OrSym0 :: TyFun (t6989586621680438446 Bool) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680439003 :: t Bool) Source # | |
data AnySym0 :: forall a6989586621680438445 t6989586621680438444. (~>) ((~>) a6989586621680438445 Bool) ((~>) (t6989586621680438444 a6989586621680438445) Bool) Source #
Instances
SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (AnySym0 :: TyFun (a6989586621680438445 ~> Bool) (t6989586621680438444 a6989586621680438445 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AnySym0 :: TyFun (a6989586621680438445 ~> Bool) (t6989586621680438444 a6989586621680438445 ~> Bool) -> Type) (a6989586621680438990 :: a6989586621680438445 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data AnySym1 (a6989586621680438990 :: (~>) a6989586621680438445 Bool) :: forall t6989586621680438444. (~>) (t6989586621680438444 a6989586621680438445) Bool Source #
Instances
(SFoldable t, SingI d) => SingI (AnySym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (AnySym1 a6989586621680438990 t6989586621680438444 :: TyFun (t6989586621680438444 a6989586621680438445) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AnySym1 a6989586621680438990 t :: TyFun (t a) Bool -> Type) (a6989586621680438991 :: t a) Source # | |
type AnySym2 (a6989586621680438990 :: (~>) a6989586621680438445 Bool) (a6989586621680438991 :: t6989586621680438444 a6989586621680438445) = Any a6989586621680438990 a6989586621680438991 Source #
data AllSym0 :: forall a6989586621680438443 t6989586621680438442. (~>) ((~>) a6989586621680438443 Bool) ((~>) (t6989586621680438442 a6989586621680438443) Bool) Source #
Instances
SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (AllSym0 :: TyFun (a6989586621680438443 ~> Bool) (t6989586621680438442 a6989586621680438443 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AllSym0 :: TyFun (a6989586621680438443 ~> Bool) (t6989586621680438442 a6989586621680438443 ~> Bool) -> Type) (a6989586621680438977 :: a6989586621680438443 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data AllSym1 (a6989586621680438977 :: (~>) a6989586621680438443 Bool) :: forall t6989586621680438442. (~>) (t6989586621680438442 a6989586621680438443) Bool Source #
Instances
(SFoldable t, SingI d) => SingI (AllSym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (AllSym1 a6989586621680438977 t6989586621680438442 :: TyFun (t6989586621680438442 a6989586621680438443) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (AllSym1 a6989586621680438977 t :: TyFun (t a) Bool -> Type) (a6989586621680438978 :: t a) Source # | |
type AllSym2 (a6989586621680438977 :: (~>) a6989586621680438443 Bool) (a6989586621680438978 :: t6989586621680438442 a6989586621680438443) = All a6989586621680438977 a6989586621680438978 Source #
data SumSym0 :: forall a6989586621680438546 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438546) a6989586621680438546 Source #
Instances
(SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # | |
SuppressUnusedWarnings (SumSym0 :: TyFun (t6989586621680438526 a6989586621680438546) a6989586621680438546 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (SumSym0 :: TyFun (t a) a -> Type) (arg6989586621680439201 :: t a) Source # | |
type SumSym1 (arg6989586621680439201 :: t6989586621680438526 a6989586621680438546) = Sum arg6989586621680439201 Source #
data ProductSym0 :: forall a6989586621680438547 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438547) a6989586621680438547 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 (t6989586621680438526 a6989586621680438547) a6989586621680438547 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680439203 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680439203 :: t a) = Product arg6989586621680439203 |
type ProductSym1 (arg6989586621680439203 :: t6989586621680438526 a6989586621680438547) = Product arg6989586621680439203 Source #
data MaximumSym0 :: forall a6989586621680438544 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438544) a6989586621680438544 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 (t6989586621680438526 a6989586621680438544) a6989586621680438544 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680439197 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680439197 :: t a) = Maximum arg6989586621680439197 |
type MaximumSym1 (arg6989586621680439197 :: t6989586621680438526 a6989586621680438544) = Maximum arg6989586621680439197 Source #
data MinimumSym0 :: forall a6989586621680438545 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438545) a6989586621680438545 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 (t6989586621680438526 a6989586621680438545) a6989586621680438545 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680439199 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680439199 :: t a) = Minimum arg6989586621680439199 |
type MinimumSym1 (arg6989586621680439199 :: t6989586621680438526 a6989586621680438545) = Minimum arg6989586621680439199 Source #
data ScanlSym0 :: forall a6989586621679929517 b6989586621679929516. (~>) ((~>) b6989586621679929516 ((~>) a6989586621679929517 b6989586621679929516)) ((~>) b6989586621679929516 ((~>) [a6989586621679929517] [b6989586621679929516])) Source #
Instances
SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym0 :: TyFun (b6989586621679929516 ~> (a6989586621679929517 ~> b6989586621679929516)) (b6989586621679929516 ~> ([a6989586621679929517] ~> [b6989586621679929516])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym0 :: TyFun (b6989586621679929516 ~> (a6989586621679929517 ~> b6989586621679929516)) (b6989586621679929516 ~> ([a6989586621679929517] ~> [b6989586621679929516])) -> Type) (a6989586621679939625 :: b6989586621679929516 ~> (a6989586621679929517 ~> b6989586621679929516)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ScanlSym0 :: TyFun (b6989586621679929516 ~> (a6989586621679929517 ~> b6989586621679929516)) (b6989586621679929516 ~> ([a6989586621679929517] ~> [b6989586621679929516])) -> Type) (a6989586621679939625 :: b6989586621679929516 ~> (a6989586621679929517 ~> b6989586621679929516)) = ScanlSym1 a6989586621679939625 |
data ScanlSym1 (a6989586621679939625 :: (~>) b6989586621679929516 ((~>) a6989586621679929517 b6989586621679929516)) :: (~>) b6989586621679929516 ((~>) [a6989586621679929517] [b6989586621679929516]) Source #
Instances
SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym1 a6989586621679939625 :: TyFun b6989586621679929516 ([a6989586621679929517] ~> [b6989586621679929516]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym1 a6989586621679939625 :: TyFun b6989586621679929516 ([a6989586621679929517] ~> [b6989586621679929516]) -> Type) (a6989586621679939626 :: b6989586621679929516) Source # | |
data ScanlSym2 (a6989586621679939625 :: (~>) b6989586621679929516 ((~>) a6989586621679929517 b6989586621679929516)) (a6989586621679939626 :: b6989586621679929516) :: (~>) [a6989586621679929517] [b6989586621679929516] Source #
Instances
(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym2 a6989586621679939626 a6989586621679939625 :: TyFun [a6989586621679929517] [b6989586621679929516] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym2 a6989586621679939626 a6989586621679939625 :: TyFun [a] [b] -> Type) (a6989586621679939627 :: [a]) Source # | |
type ScanlSym3 (a6989586621679939625 :: (~>) b6989586621679929516 ((~>) a6989586621679929517 b6989586621679929516)) (a6989586621679939626 :: b6989586621679929516) (a6989586621679939627 :: [a6989586621679929517]) = Scanl a6989586621679939625 a6989586621679939626 a6989586621679939627 Source #
data Scanl1Sym0 :: forall a6989586621679929515. (~>) ((~>) a6989586621679929515 ((~>) a6989586621679929515 a6989586621679929515)) ((~>) [a6989586621679929515] [a6989586621679929515]) 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 (a6989586621679929515 ~> (a6989586621679929515 ~> a6989586621679929515)) ([a6989586621679929515] ~> [a6989586621679929515]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym0 :: TyFun (a6989586621679929515 ~> (a6989586621679929515 ~> a6989586621679929515)) ([a6989586621679929515] ~> [a6989586621679929515]) -> Type) (a6989586621679939639 :: a6989586621679929515 ~> (a6989586621679929515 ~> a6989586621679929515)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym0 :: TyFun (a6989586621679929515 ~> (a6989586621679929515 ~> a6989586621679929515)) ([a6989586621679929515] ~> [a6989586621679929515]) -> Type) (a6989586621679939639 :: a6989586621679929515 ~> (a6989586621679929515 ~> a6989586621679929515)) = Scanl1Sym1 a6989586621679939639 |
data Scanl1Sym1 (a6989586621679939639 :: (~>) a6989586621679929515 ((~>) a6989586621679929515 a6989586621679929515)) :: (~>) [a6989586621679929515] [a6989586621679929515] 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 a6989586621679939639 :: TyFun [a6989586621679929515] [a6989586621679929515] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym1 a6989586621679939639 :: TyFun [a] [a] -> Type) (a6989586621679939640 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym1 a6989586621679939639 :: TyFun [a] [a] -> Type) (a6989586621679939640 :: [a]) = Scanl1 a6989586621679939639 a6989586621679939640 |
type Scanl1Sym2 (a6989586621679939639 :: (~>) a6989586621679929515 ((~>) a6989586621679929515 a6989586621679929515)) (a6989586621679939640 :: [a6989586621679929515]) = Scanl1 a6989586621679939639 a6989586621679939640 Source #
data ScanrSym0 :: forall a6989586621679929513 b6989586621679929514. (~>) ((~>) a6989586621679929513 ((~>) b6989586621679929514 b6989586621679929514)) ((~>) b6989586621679929514 ((~>) [a6989586621679929513] [b6989586621679929514])) Source #
Instances
SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym0 :: TyFun (a6989586621679929513 ~> (b6989586621679929514 ~> b6989586621679929514)) (b6989586621679929514 ~> ([a6989586621679929513] ~> [b6989586621679929514])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym0 :: TyFun (a6989586621679929513 ~> (b6989586621679929514 ~> b6989586621679929514)) (b6989586621679929514 ~> ([a6989586621679929513] ~> [b6989586621679929514])) -> Type) (a6989586621679939604 :: a6989586621679929513 ~> (b6989586621679929514 ~> b6989586621679929514)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ScanrSym0 :: TyFun (a6989586621679929513 ~> (b6989586621679929514 ~> b6989586621679929514)) (b6989586621679929514 ~> ([a6989586621679929513] ~> [b6989586621679929514])) -> Type) (a6989586621679939604 :: a6989586621679929513 ~> (b6989586621679929514 ~> b6989586621679929514)) = ScanrSym1 a6989586621679939604 |
data ScanrSym1 (a6989586621679939604 :: (~>) a6989586621679929513 ((~>) b6989586621679929514 b6989586621679929514)) :: (~>) b6989586621679929514 ((~>) [a6989586621679929513] [b6989586621679929514]) Source #
Instances
SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym1 a6989586621679939604 :: TyFun b6989586621679929514 ([a6989586621679929513] ~> [b6989586621679929514]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym1 a6989586621679939604 :: TyFun b6989586621679929514 ([a6989586621679929513] ~> [b6989586621679929514]) -> Type) (a6989586621679939605 :: b6989586621679929514) Source # | |
data ScanrSym2 (a6989586621679939604 :: (~>) a6989586621679929513 ((~>) b6989586621679929514 b6989586621679929514)) (a6989586621679939605 :: b6989586621679929514) :: (~>) [a6989586621679929513] [b6989586621679929514] Source #
Instances
(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym2 a6989586621679939605 a6989586621679939604 :: TyFun [a6989586621679929513] [b6989586621679929514] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym2 a6989586621679939605 a6989586621679939604 :: TyFun [a] [b] -> Type) (a6989586621679939606 :: [a]) Source # | |
type ScanrSym3 (a6989586621679939604 :: (~>) a6989586621679929513 ((~>) b6989586621679929514 b6989586621679929514)) (a6989586621679939605 :: b6989586621679929514) (a6989586621679939606 :: [a6989586621679929513]) = Scanr a6989586621679939604 a6989586621679939605 a6989586621679939606 Source #
data Scanr1Sym0 :: forall a6989586621679929512. (~>) ((~>) a6989586621679929512 ((~>) a6989586621679929512 a6989586621679929512)) ((~>) [a6989586621679929512] [a6989586621679929512]) 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 (a6989586621679929512 ~> (a6989586621679929512 ~> a6989586621679929512)) ([a6989586621679929512] ~> [a6989586621679929512]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym0 :: TyFun (a6989586621679929512 ~> (a6989586621679929512 ~> a6989586621679929512)) ([a6989586621679929512] ~> [a6989586621679929512]) -> Type) (a6989586621679939580 :: a6989586621679929512 ~> (a6989586621679929512 ~> a6989586621679929512)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym0 :: TyFun (a6989586621679929512 ~> (a6989586621679929512 ~> a6989586621679929512)) ([a6989586621679929512] ~> [a6989586621679929512]) -> Type) (a6989586621679939580 :: a6989586621679929512 ~> (a6989586621679929512 ~> a6989586621679929512)) = Scanr1Sym1 a6989586621679939580 |
data Scanr1Sym1 (a6989586621679939580 :: (~>) a6989586621679929512 ((~>) a6989586621679929512 a6989586621679929512)) :: (~>) [a6989586621679929512] [a6989586621679929512] 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 a6989586621679939580 :: TyFun [a6989586621679929512] [a6989586621679929512] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym1 a6989586621679939580 :: TyFun [a] [a] -> Type) (a6989586621679939581 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym1 a6989586621679939580 :: TyFun [a] [a] -> Type) (a6989586621679939581 :: [a]) = Scanr1 a6989586621679939580 a6989586621679939581 |
type Scanr1Sym2 (a6989586621679939580 :: (~>) a6989586621679929512 ((~>) a6989586621679929512 a6989586621679929512)) (a6989586621679939581 :: [a6989586621679929512]) = Scanr1 a6989586621679939580 a6989586621679939581 Source #
data MapAccumLSym0 :: forall a6989586621680740545 b6989586621680740546 c6989586621680740547 t6989586621680740544. (~>) ((~>) a6989586621680740545 ((~>) b6989586621680740546 (a6989586621680740545, c6989586621680740547))) ((~>) a6989586621680740545 ((~>) (t6989586621680740544 b6989586621680740546) (a6989586621680740545, t6989586621680740544 c6989586621680740547))) 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 (a6989586621680740545 ~> (b6989586621680740546 ~> (a6989586621680740545, c6989586621680740547))) (a6989586621680740545 ~> (t6989586621680740544 b6989586621680740546 ~> (a6989586621680740545, t6989586621680740544 c6989586621680740547))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym0 :: TyFun (a6989586621680740545 ~> (b6989586621680740546 ~> (a6989586621680740545, c6989586621680740547))) (a6989586621680740545 ~> (t6989586621680740544 b6989586621680740546 ~> (a6989586621680740545, t6989586621680740544 c6989586621680740547))) -> Type) (a6989586621680741084 :: a6989586621680740545 ~> (b6989586621680740546 ~> (a6989586621680740545, c6989586621680740547))) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym0 :: TyFun (a6989586621680740545 ~> (b6989586621680740546 ~> (a6989586621680740545, c6989586621680740547))) (a6989586621680740545 ~> (t6989586621680740544 b6989586621680740546 ~> (a6989586621680740545, t6989586621680740544 c6989586621680740547))) -> Type) (a6989586621680741084 :: a6989586621680740545 ~> (b6989586621680740546 ~> (a6989586621680740545, c6989586621680740547))) = (MapAccumLSym1 a6989586621680741084 t6989586621680740544 :: TyFun a6989586621680740545 (t6989586621680740544 b6989586621680740546 ~> (a6989586621680740545, t6989586621680740544 c6989586621680740547)) -> Type) |
data MapAccumLSym1 (a6989586621680741084 :: (~>) a6989586621680740545 ((~>) b6989586621680740546 (a6989586621680740545, c6989586621680740547))) :: forall t6989586621680740544. (~>) a6989586621680740545 ((~>) (t6989586621680740544 b6989586621680740546) (a6989586621680740545, t6989586621680740544 c6989586621680740547)) 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 a6989586621680741084 t6989586621680740544 :: TyFun a6989586621680740545 (t6989586621680740544 b6989586621680740546 ~> (a6989586621680740545, t6989586621680740544 c6989586621680740547)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym1 a6989586621680741084 t6989586621680740544 :: TyFun a6989586621680740545 (t6989586621680740544 b6989586621680740546 ~> (a6989586621680740545, t6989586621680740544 c6989586621680740547)) -> Type) (a6989586621680741085 :: a6989586621680740545) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym1 a6989586621680741084 t6989586621680740544 :: TyFun a6989586621680740545 (t6989586621680740544 b6989586621680740546 ~> (a6989586621680740545, t6989586621680740544 c6989586621680740547)) -> Type) (a6989586621680741085 :: a6989586621680740545) = (MapAccumLSym2 a6989586621680741084 a6989586621680741085 t6989586621680740544 :: TyFun (t6989586621680740544 b6989586621680740546) (a6989586621680740545, t6989586621680740544 c6989586621680740547) -> Type) |
data MapAccumLSym2 (a6989586621680741084 :: (~>) a6989586621680740545 ((~>) b6989586621680740546 (a6989586621680740545, c6989586621680740547))) (a6989586621680741085 :: a6989586621680740545) :: forall t6989586621680740544. (~>) (t6989586621680740544 b6989586621680740546) (a6989586621680740545, t6989586621680740544 c6989586621680740547) 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 a6989586621680741085 a6989586621680741084 t6989586621680740544 :: TyFun (t6989586621680740544 b6989586621680740546) (a6989586621680740545, t6989586621680740544 c6989586621680740547) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym2 a6989586621680741085 a6989586621680741084 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680741086 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym2 a6989586621680741085 a6989586621680741084 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680741086 :: t b) = MapAccumL a6989586621680741085 a6989586621680741084 a6989586621680741086 |
type MapAccumLSym3 (a6989586621680741084 :: (~>) a6989586621680740545 ((~>) b6989586621680740546 (a6989586621680740545, c6989586621680740547))) (a6989586621680741085 :: a6989586621680740545) (a6989586621680741086 :: t6989586621680740544 b6989586621680740546) = MapAccumL a6989586621680741084 a6989586621680741085 a6989586621680741086 Source #
data MapAccumRSym0 :: forall a6989586621680740541 b6989586621680740542 c6989586621680740543 t6989586621680740540. (~>) ((~>) a6989586621680740541 ((~>) b6989586621680740542 (a6989586621680740541, c6989586621680740543))) ((~>) a6989586621680740541 ((~>) (t6989586621680740540 b6989586621680740542) (a6989586621680740541, t6989586621680740540 c6989586621680740543))) 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 (a6989586621680740541 ~> (b6989586621680740542 ~> (a6989586621680740541, c6989586621680740543))) (a6989586621680740541 ~> (t6989586621680740540 b6989586621680740542 ~> (a6989586621680740541, t6989586621680740540 c6989586621680740543))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym0 :: TyFun (a6989586621680740541 ~> (b6989586621680740542 ~> (a6989586621680740541, c6989586621680740543))) (a6989586621680740541 ~> (t6989586621680740540 b6989586621680740542 ~> (a6989586621680740541, t6989586621680740540 c6989586621680740543))) -> Type) (a6989586621680741067 :: a6989586621680740541 ~> (b6989586621680740542 ~> (a6989586621680740541, c6989586621680740543))) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym0 :: TyFun (a6989586621680740541 ~> (b6989586621680740542 ~> (a6989586621680740541, c6989586621680740543))) (a6989586621680740541 ~> (t6989586621680740540 b6989586621680740542 ~> (a6989586621680740541, t6989586621680740540 c6989586621680740543))) -> Type) (a6989586621680741067 :: a6989586621680740541 ~> (b6989586621680740542 ~> (a6989586621680740541, c6989586621680740543))) = (MapAccumRSym1 a6989586621680741067 t6989586621680740540 :: TyFun a6989586621680740541 (t6989586621680740540 b6989586621680740542 ~> (a6989586621680740541, t6989586621680740540 c6989586621680740543)) -> Type) |
data MapAccumRSym1 (a6989586621680741067 :: (~>) a6989586621680740541 ((~>) b6989586621680740542 (a6989586621680740541, c6989586621680740543))) :: forall t6989586621680740540. (~>) a6989586621680740541 ((~>) (t6989586621680740540 b6989586621680740542) (a6989586621680740541, t6989586621680740540 c6989586621680740543)) 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 a6989586621680741067 t6989586621680740540 :: TyFun a6989586621680740541 (t6989586621680740540 b6989586621680740542 ~> (a6989586621680740541, t6989586621680740540 c6989586621680740543)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym1 a6989586621680741067 t6989586621680740540 :: TyFun a6989586621680740541 (t6989586621680740540 b6989586621680740542 ~> (a6989586621680740541, t6989586621680740540 c6989586621680740543)) -> Type) (a6989586621680741068 :: a6989586621680740541) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym1 a6989586621680741067 t6989586621680740540 :: TyFun a6989586621680740541 (t6989586621680740540 b6989586621680740542 ~> (a6989586621680740541, t6989586621680740540 c6989586621680740543)) -> Type) (a6989586621680741068 :: a6989586621680740541) = (MapAccumRSym2 a6989586621680741067 a6989586621680741068 t6989586621680740540 :: TyFun (t6989586621680740540 b6989586621680740542) (a6989586621680740541, t6989586621680740540 c6989586621680740543) -> Type) |
data MapAccumRSym2 (a6989586621680741067 :: (~>) a6989586621680740541 ((~>) b6989586621680740542 (a6989586621680740541, c6989586621680740543))) (a6989586621680741068 :: a6989586621680740541) :: forall t6989586621680740540. (~>) (t6989586621680740540 b6989586621680740542) (a6989586621680740541, t6989586621680740540 c6989586621680740543) 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 a6989586621680741068 a6989586621680741067 t6989586621680740540 :: TyFun (t6989586621680740540 b6989586621680740542) (a6989586621680740541, t6989586621680740540 c6989586621680740543) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym2 a6989586621680741068 a6989586621680741067 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680741069 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym2 a6989586621680741068 a6989586621680741067 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680741069 :: t b) = MapAccumR a6989586621680741068 a6989586621680741067 a6989586621680741069 |
type MapAccumRSym3 (a6989586621680741067 :: (~>) a6989586621680740541 ((~>) b6989586621680740542 (a6989586621680740541, c6989586621680740543))) (a6989586621680741068 :: a6989586621680740541) (a6989586621680741069 :: t6989586621680740540 b6989586621680740542) = MapAccumR a6989586621680741067 a6989586621680741068 a6989586621680741069 Source #
data ReplicateSym0 :: forall a6989586621679929420. (~>) Nat ((~>) a6989586621679929420 [a6989586621679929420]) 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 (a6989586621679929420 ~> [a6989586621679929420]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym0 :: TyFun Nat (a6989586621679929420 ~> [a6989586621679929420]) -> Type) (a6989586621679938722 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym0 :: TyFun Nat (a6989586621679929420 ~> [a6989586621679929420]) -> Type) (a6989586621679938722 :: Nat) = (ReplicateSym1 a6989586621679938722 a6989586621679929420 :: TyFun a6989586621679929420 [a6989586621679929420] -> Type) |
data ReplicateSym1 (a6989586621679938722 :: Nat) :: forall a6989586621679929420. (~>) a6989586621679929420 [a6989586621679929420] 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 a6989586621679938722 a6989586621679929420 :: TyFun a6989586621679929420 [a6989586621679929420] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym1 a6989586621679938722 a :: TyFun a [a] -> Type) (a6989586621679938723 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym1 a6989586621679938722 a :: TyFun a [a] -> Type) (a6989586621679938723 :: a) = Replicate a6989586621679938722 a6989586621679938723 |
type ReplicateSym2 (a6989586621679938722 :: Nat) (a6989586621679938723 :: a6989586621679929420) = Replicate a6989586621679938722 a6989586621679938723 Source #
data UnfoldrSym0 :: forall a6989586621679929505 b6989586621679929504. (~>) ((~>) b6989586621679929504 (Maybe (a6989586621679929505, b6989586621679929504))) ((~>) b6989586621679929504 [a6989586621679929505]) 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 (b6989586621679929504 ~> Maybe (a6989586621679929505, b6989586621679929504)) (b6989586621679929504 ~> [a6989586621679929505]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym0 :: TyFun (b6989586621679929504 ~> Maybe (a6989586621679929505, b6989586621679929504)) (b6989586621679929504 ~> [a6989586621679929505]) -> Type) (a6989586621679939438 :: b6989586621679929504 ~> Maybe (a6989586621679929505, b6989586621679929504)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym0 :: TyFun (b6989586621679929504 ~> Maybe (a6989586621679929505, b6989586621679929504)) (b6989586621679929504 ~> [a6989586621679929505]) -> Type) (a6989586621679939438 :: b6989586621679929504 ~> Maybe (a6989586621679929505, b6989586621679929504)) = UnfoldrSym1 a6989586621679939438 |
data UnfoldrSym1 (a6989586621679939438 :: (~>) b6989586621679929504 (Maybe (a6989586621679929505, b6989586621679929504))) :: (~>) b6989586621679929504 [a6989586621679929505] 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 a6989586621679939438 :: TyFun b6989586621679929504 [a6989586621679929505] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym1 a6989586621679939438 :: TyFun b [a] -> Type) (a6989586621679939439 :: b) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym1 a6989586621679939438 :: TyFun b [a] -> Type) (a6989586621679939439 :: b) = Unfoldr a6989586621679939438 a6989586621679939439 |
type UnfoldrSym2 (a6989586621679939438 :: (~>) b6989586621679929504 (Maybe (a6989586621679929505, b6989586621679929504))) (a6989586621679939439 :: b6989586621679929504) = Unfoldr a6989586621679939438 a6989586621679939439 Source #
data TakeSym0 :: forall a6989586621679929436. (~>) Nat ((~>) [a6989586621679929436] [a6989586621679929436]) Source #
Instances
SingI (TakeSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (TakeSym0 :: TyFun Nat ([a6989586621679929436] ~> [a6989586621679929436]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym0 :: TyFun Nat ([a6989586621679929436] ~> [a6989586621679929436]) -> Type) (a6989586621679938818 :: Nat) Source # | |
data TakeSym1 (a6989586621679938818 :: Nat) :: forall a6989586621679929436. (~>) [a6989586621679929436] [a6989586621679929436] Source #
Instances
SingI d => SingI (TakeSym1 d a :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (TakeSym1 a6989586621679938818 a6989586621679929436 :: TyFun [a6989586621679929436] [a6989586621679929436] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym1 a6989586621679938818 a :: TyFun [a] [a] -> Type) (a6989586621679938819 :: [a]) Source # | |
type TakeSym2 (a6989586621679938818 :: Nat) (a6989586621679938819 :: [a6989586621679929436]) = Take a6989586621679938818 a6989586621679938819 Source #
data DropSym0 :: forall a6989586621679929435. (~>) Nat ((~>) [a6989586621679929435] [a6989586621679929435]) Source #
Instances
SingI (DropSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (DropSym0 :: TyFun Nat ([a6989586621679929435] ~> [a6989586621679929435]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropSym0 :: TyFun Nat ([a6989586621679929435] ~> [a6989586621679929435]) -> Type) (a6989586621679938804 :: Nat) Source # | |
data DropSym1 (a6989586621679938804 :: Nat) :: forall a6989586621679929435. (~>) [a6989586621679929435] [a6989586621679929435] Source #
Instances
SingI d => SingI (DropSym1 d a :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (DropSym1 a6989586621679938804 a6989586621679929435 :: TyFun [a6989586621679929435] [a6989586621679929435] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropSym1 a6989586621679938804 a :: TyFun [a] [a] -> Type) (a6989586621679938805 :: [a]) Source # | |
type DropSym2 (a6989586621679938804 :: Nat) (a6989586621679938805 :: [a6989586621679929435]) = Drop a6989586621679938804 a6989586621679938805 Source #
data SplitAtSym0 :: forall a6989586621679929434. (~>) Nat ((~>) [a6989586621679929434] ([a6989586621679929434], [a6989586621679929434])) 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 ([a6989586621679929434] ~> ([a6989586621679929434], [a6989586621679929434])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym0 :: TyFun Nat ([a6989586621679929434] ~> ([a6989586621679929434], [a6989586621679929434])) -> Type) (a6989586621679938832 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym0 :: TyFun Nat ([a6989586621679929434] ~> ([a6989586621679929434], [a6989586621679929434])) -> Type) (a6989586621679938832 :: Nat) = (SplitAtSym1 a6989586621679938832 a6989586621679929434 :: TyFun [a6989586621679929434] ([a6989586621679929434], [a6989586621679929434]) -> Type) |
data SplitAtSym1 (a6989586621679938832 :: Nat) :: forall a6989586621679929434. (~>) [a6989586621679929434] ([a6989586621679929434], [a6989586621679929434]) 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 a6989586621679938832 a6989586621679929434 :: TyFun [a6989586621679929434] ([a6989586621679929434], [a6989586621679929434]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym1 a6989586621679938832 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621679938833 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym1 a6989586621679938832 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621679938833 :: [a]) = SplitAt a6989586621679938832 a6989586621679938833 |
type SplitAtSym2 (a6989586621679938832 :: Nat) (a6989586621679938833 :: [a6989586621679929434]) = SplitAt a6989586621679938832 a6989586621679938833 Source #
data TakeWhileSym0 :: forall a6989586621679929441. (~>) ((~>) a6989586621679929441 Bool) ((~>) [a6989586621679929441] [a6989586621679929441]) 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 (a6989586621679929441 ~> Bool) ([a6989586621679929441] ~> [a6989586621679929441]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym0 :: TyFun (a6989586621679929441 ~> Bool) ([a6989586621679929441] ~> [a6989586621679929441]) -> Type) (a6989586621679938976 :: a6989586621679929441 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym0 :: TyFun (a6989586621679929441 ~> Bool) ([a6989586621679929441] ~> [a6989586621679929441]) -> Type) (a6989586621679938976 :: a6989586621679929441 ~> Bool) = TakeWhileSym1 a6989586621679938976 |
data TakeWhileSym1 (a6989586621679938976 :: (~>) a6989586621679929441 Bool) :: (~>) [a6989586621679929441] [a6989586621679929441] 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 a6989586621679938976 :: TyFun [a6989586621679929441] [a6989586621679929441] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym1 a6989586621679938976 :: TyFun [a] [a] -> Type) (a6989586621679938977 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym1 a6989586621679938976 :: TyFun [a] [a] -> Type) (a6989586621679938977 :: [a]) = TakeWhile a6989586621679938976 a6989586621679938977 |
type TakeWhileSym2 (a6989586621679938976 :: (~>) a6989586621679929441 Bool) (a6989586621679938977 :: [a6989586621679929441]) = TakeWhile a6989586621679938976 a6989586621679938977 Source #
data DropWhileSym0 :: forall a6989586621679929440. (~>) ((~>) a6989586621679929440 Bool) ((~>) [a6989586621679929440] [a6989586621679929440]) 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 (a6989586621679929440 ~> Bool) ([a6989586621679929440] ~> [a6989586621679929440]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym0 :: TyFun (a6989586621679929440 ~> Bool) ([a6989586621679929440] ~> [a6989586621679929440]) -> Type) (a6989586621679938958 :: a6989586621679929440 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym0 :: TyFun (a6989586621679929440 ~> Bool) ([a6989586621679929440] ~> [a6989586621679929440]) -> Type) (a6989586621679938958 :: a6989586621679929440 ~> Bool) = DropWhileSym1 a6989586621679938958 |
data DropWhileSym1 (a6989586621679938958 :: (~>) a6989586621679929440 Bool) :: (~>) [a6989586621679929440] [a6989586621679929440] 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 a6989586621679938958 :: TyFun [a6989586621679929440] [a6989586621679929440] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym1 a6989586621679938958 :: TyFun [a] [a] -> Type) (a6989586621679938959 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym1 a6989586621679938958 :: TyFun [a] [a] -> Type) (a6989586621679938959 :: [a]) = DropWhile a6989586621679938958 a6989586621679938959 |
type DropWhileSym2 (a6989586621679938958 :: (~>) a6989586621679929440 Bool) (a6989586621679938959 :: [a6989586621679929440]) = DropWhile a6989586621679938958 a6989586621679938959 Source #
data DropWhileEndSym0 :: forall a6989586621679929439. (~>) ((~>) a6989586621679929439 Bool) ((~>) [a6989586621679929439] [a6989586621679929439]) Source #
Instances
SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a6989586621679929439 ~> Bool) ([a6989586621679929439] ~> [a6989586621679929439]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym0 :: TyFun (a6989586621679929439 ~> Bool) ([a6989586621679929439] ~> [a6989586621679929439]) -> Type) (a6989586621679940014 :: a6989586621679929439 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym0 :: TyFun (a6989586621679929439 ~> Bool) ([a6989586621679929439] ~> [a6989586621679929439]) -> Type) (a6989586621679940014 :: a6989586621679929439 ~> Bool) = DropWhileEndSym1 a6989586621679940014 |
data DropWhileEndSym1 (a6989586621679940014 :: (~>) a6989586621679929439 Bool) :: (~>) [a6989586621679929439] [a6989586621679929439] 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 a6989586621679940014 :: TyFun [a6989586621679929439] [a6989586621679929439] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym1 a6989586621679940014 :: TyFun [a] [a] -> Type) (a6989586621679940015 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym1 a6989586621679940014 :: TyFun [a] [a] -> Type) (a6989586621679940015 :: [a]) = DropWhileEnd a6989586621679940014 a6989586621679940015 |
type DropWhileEndSym2 (a6989586621679940014 :: (~>) a6989586621679929439 Bool) (a6989586621679940015 :: [a6989586621679929439]) = DropWhileEnd a6989586621679940014 a6989586621679940015 Source #
data SpanSym0 :: forall a6989586621679929438. (~>) ((~>) a6989586621679929438 Bool) ((~>) [a6989586621679929438] ([a6989586621679929438], [a6989586621679929438])) Source #
Instances
SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym0 :: TyFun (a6989586621679929438 ~> Bool) ([a6989586621679929438] ~> ([a6989586621679929438], [a6989586621679929438])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym0 :: TyFun (a6989586621679929438 ~> Bool) ([a6989586621679929438] ~> ([a6989586621679929438], [a6989586621679929438])) -> Type) (a6989586621679938881 :: a6989586621679929438 ~> Bool) Source # | |
data SpanSym1 (a6989586621679938881 :: (~>) a6989586621679929438 Bool) :: (~>) [a6989586621679929438] ([a6989586621679929438], [a6989586621679929438]) Source #
Instances
SingI d => SingI (SpanSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym1 a6989586621679938881 :: TyFun [a6989586621679929438] ([a6989586621679929438], [a6989586621679929438]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym1 a6989586621679938881 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679938882 :: [a]) Source # | |
type SpanSym2 (a6989586621679938881 :: (~>) a6989586621679929438 Bool) (a6989586621679938882 :: [a6989586621679929438]) = Span a6989586621679938881 a6989586621679938882 Source #
data BreakSym0 :: forall a6989586621679929437. (~>) ((~>) a6989586621679929437 Bool) ((~>) [a6989586621679929437] ([a6989586621679929437], [a6989586621679929437])) Source #
Instances
SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym0 :: TyFun (a6989586621679929437 ~> Bool) ([a6989586621679929437] ~> ([a6989586621679929437], [a6989586621679929437])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym0 :: TyFun (a6989586621679929437 ~> Bool) ([a6989586621679929437] ~> ([a6989586621679929437], [a6989586621679929437])) -> Type) (a6989586621679938838 :: a6989586621679929437 ~> Bool) Source # | |
data BreakSym1 (a6989586621679938838 :: (~>) a6989586621679929437 Bool) :: (~>) [a6989586621679929437] ([a6989586621679929437], [a6989586621679929437]) Source #
Instances
SingI d => SingI (BreakSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym1 a6989586621679938838 :: TyFun [a6989586621679929437] ([a6989586621679929437], [a6989586621679929437]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym1 a6989586621679938838 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679938839 :: [a]) Source # | |
type BreakSym2 (a6989586621679938838 :: (~>) a6989586621679929437 Bool) (a6989586621679938839 :: [a6989586621679929437]) = Break a6989586621679938838 a6989586621679938839 Source #
data StripPrefixSym0 :: forall a6989586621680055663. (~>) [a6989586621680055663] ((~>) [a6989586621680055663] (Maybe [a6989586621680055663])) Source #
Instances
SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a6989586621680055663] ([a6989586621680055663] ~> Maybe [a6989586621680055663]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (StripPrefixSym0 :: TyFun [a6989586621680055663] ([a6989586621680055663] ~> Maybe [a6989586621680055663]) -> Type) (a6989586621680068373 :: [a6989586621680055663]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym0 :: TyFun [a6989586621680055663] ([a6989586621680055663] ~> Maybe [a6989586621680055663]) -> Type) (a6989586621680068373 :: [a6989586621680055663]) = StripPrefixSym1 a6989586621680068373 |
data StripPrefixSym1 (a6989586621680068373 :: [a6989586621680055663]) :: (~>) [a6989586621680055663] (Maybe [a6989586621680055663]) Source #
Instances
SuppressUnusedWarnings (StripPrefixSym1 a6989586621680068373 :: TyFun [a6989586621680055663] (Maybe [a6989586621680055663]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (StripPrefixSym1 a6989586621680068373 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680068374 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym1 a6989586621680068373 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680068374 :: [a]) = StripPrefix a6989586621680068373 a6989586621680068374 |
type StripPrefixSym2 (a6989586621680068373 :: [a6989586621680055663]) (a6989586621680068374 :: [a6989586621680055663]) = StripPrefix a6989586621680068373 a6989586621680068374 Source #
data GroupSym0 :: forall a6989586621679929433. (~>) [a6989586621679929433] [[a6989586621679929433]] Source #
Instances
SEq a => SingI (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621679929433] [[a6989586621679929433]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679938955 :: [a]) Source # | |
type GroupSym1 (a6989586621679938955 :: [a6989586621679929433]) = Group a6989586621679938955 Source #
data InitsSym0 :: forall a6989586621679929503. (~>) [a6989586621679929503] [[a6989586621679929503]] Source #
Instances
SingI (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621679929503] [[a6989586621679929503]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679939430 :: [a]) Source # | |
type InitsSym1 (a6989586621679939430 :: [a6989586621679929503]) = Inits a6989586621679939430 Source #
data TailsSym0 :: forall a6989586621679929502. (~>) [a6989586621679929502] [[a6989586621679929502]] Source #
Instances
SingI (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621679929502] [[a6989586621679929502]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679939423 :: [a]) Source # | |
type TailsSym1 (a6989586621679939423 :: [a6989586621679929502]) = Tails a6989586621679939423 Source #
data IsPrefixOfSym0 :: forall a6989586621679929501. (~>) [a6989586621679929501] ((~>) [a6989586621679929501] Bool) Source #
Instances
SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679929501] ([a6989586621679929501] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679929501] ([a6989586621679929501] ~> Bool) -> Type) (a6989586621679939415 :: [a6989586621679929501]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679929501] ([a6989586621679929501] ~> Bool) -> Type) (a6989586621679939415 :: [a6989586621679929501]) = IsPrefixOfSym1 a6989586621679939415 |
data IsPrefixOfSym1 (a6989586621679939415 :: [a6989586621679929501]) :: (~>) [a6989586621679929501] 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 a6989586621679939415 :: TyFun [a6989586621679929501] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym1 a6989586621679939415 :: TyFun [a] Bool -> Type) (a6989586621679939416 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym1 a6989586621679939415 :: TyFun [a] Bool -> Type) (a6989586621679939416 :: [a]) = IsPrefixOf a6989586621679939415 a6989586621679939416 |
type IsPrefixOfSym2 (a6989586621679939415 :: [a6989586621679929501]) (a6989586621679939416 :: [a6989586621679929501]) = IsPrefixOf a6989586621679939415 a6989586621679939416 Source #
data IsSuffixOfSym0 :: forall a6989586621679929500. (~>) [a6989586621679929500] ((~>) [a6989586621679929500] Bool) Source #
Instances
SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679929500] ([a6989586621679929500] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679929500] ([a6989586621679929500] ~> Bool) -> Type) (a6989586621679940006 :: [a6989586621679929500]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679929500] ([a6989586621679929500] ~> Bool) -> Type) (a6989586621679940006 :: [a6989586621679929500]) = IsSuffixOfSym1 a6989586621679940006 |
data IsSuffixOfSym1 (a6989586621679940006 :: [a6989586621679929500]) :: (~>) [a6989586621679929500] 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 a6989586621679940006 :: TyFun [a6989586621679929500] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym1 a6989586621679940006 :: TyFun [a] Bool -> Type) (a6989586621679940007 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym1 a6989586621679940006 :: TyFun [a] Bool -> Type) (a6989586621679940007 :: [a]) = IsSuffixOf a6989586621679940006 a6989586621679940007 |
type IsSuffixOfSym2 (a6989586621679940006 :: [a6989586621679929500]) (a6989586621679940007 :: [a6989586621679929500]) = IsSuffixOf a6989586621679940006 a6989586621679940007 Source #
data IsInfixOfSym0 :: forall a6989586621679929499. (~>) [a6989586621679929499] ((~>) [a6989586621679929499] 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 [a6989586621679929499] ([a6989586621679929499] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym0 :: TyFun [a6989586621679929499] ([a6989586621679929499] ~> Bool) -> Type) (a6989586621679939653 :: [a6989586621679929499]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsInfixOfSym0 :: TyFun [a6989586621679929499] ([a6989586621679929499] ~> Bool) -> Type) (a6989586621679939653 :: [a6989586621679929499]) = IsInfixOfSym1 a6989586621679939653 |
data IsInfixOfSym1 (a6989586621679939653 :: [a6989586621679929499]) :: (~>) [a6989586621679929499] 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 a6989586621679939653 :: TyFun [a6989586621679929499] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym1 a6989586621679939653 :: TyFun [a] Bool -> Type) (a6989586621679939654 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type IsInfixOfSym2 (a6989586621679939653 :: [a6989586621679929499]) (a6989586621679939654 :: [a6989586621679929499]) = IsInfixOf a6989586621679939653 a6989586621679939654 Source #
data ElemSym0 :: forall a6989586621680438543 t6989586621680438526. (~>) a6989586621680438543 ((~>) (t6989586621680438526 a6989586621680438543) Bool) Source #
Instances
(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621680438543 (t6989586621680438526 a6989586621680438543 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym0 :: TyFun a6989586621680438543 (t6989586621680438526 a6989586621680438543 ~> Bool) -> Type) (arg6989586621680439193 :: a6989586621680438543) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data ElemSym1 (arg6989586621680439193 :: a6989586621680438543) :: forall t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438543) Bool Source #
Instances
(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (ElemSym1 arg6989586621680439193 t6989586621680438526 :: TyFun (t6989586621680438526 a6989586621680438543) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym1 arg6989586621680439193 t :: TyFun (t a) Bool -> Type) (arg6989586621680439194 :: t a) Source # | |
type ElemSym2 (arg6989586621680439193 :: a6989586621680438543) (arg6989586621680439194 :: t6989586621680438526 a6989586621680438543) = Elem arg6989586621680439193 arg6989586621680439194 Source #
data NotElemSym0 :: forall a6989586621680438437 t6989586621680438436. (~>) a6989586621680438437 ((~>) (t6989586621680438436 a6989586621680438437) 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 a6989586621680438437 (t6989586621680438436 a6989586621680438437 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym0 :: TyFun a6989586621680438437 (t6989586621680438436 a6989586621680438437 ~> Bool) -> Type) (a6989586621680438919 :: a6989586621680438437) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (NotElemSym0 :: TyFun a6989586621680438437 (t6989586621680438436 a6989586621680438437 ~> Bool) -> Type) (a6989586621680438919 :: a6989586621680438437) = (NotElemSym1 a6989586621680438919 t6989586621680438436 :: TyFun (t6989586621680438436 a6989586621680438437) Bool -> Type) |
data NotElemSym1 (a6989586621680438919 :: a6989586621680438437) :: forall t6989586621680438436. (~>) (t6989586621680438436 a6989586621680438437) 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 a6989586621680438919 t6989586621680438436 :: TyFun (t6989586621680438436 a6989586621680438437) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym1 a6989586621680438919 t :: TyFun (t a) Bool -> Type) (a6989586621680438920 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type NotElemSym2 (a6989586621680438919 :: a6989586621680438437) (a6989586621680438920 :: t6989586621680438436 a6989586621680438437) = NotElem a6989586621680438919 a6989586621680438920 Source #
data LookupSym0 :: forall a6989586621679929426 b6989586621679929427. (~>) a6989586621679929426 ((~>) [(a6989586621679929426, b6989586621679929427)] (Maybe b6989586621679929427)) 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 a6989586621679929426 ([(a6989586621679929426, b6989586621679929427)] ~> Maybe b6989586621679929427) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym0 :: TyFun a6989586621679929426 ([(a6989586621679929426, b6989586621679929427)] ~> Maybe b6989586621679929427) -> Type) (a6989586621679938787 :: a6989586621679929426) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (LookupSym0 :: TyFun a6989586621679929426 ([(a6989586621679929426, b6989586621679929427)] ~> Maybe b6989586621679929427) -> Type) (a6989586621679938787 :: a6989586621679929426) = (LookupSym1 a6989586621679938787 b6989586621679929427 :: TyFun [(a6989586621679929426, b6989586621679929427)] (Maybe b6989586621679929427) -> Type) |
data LookupSym1 (a6989586621679938787 :: a6989586621679929426) :: forall b6989586621679929427. (~>) [(a6989586621679929426, b6989586621679929427)] (Maybe b6989586621679929427) 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 a6989586621679938787 b6989586621679929427 :: TyFun [(a6989586621679929426, b6989586621679929427)] (Maybe b6989586621679929427) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym1 a6989586621679938787 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679938788 :: [(a, b)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type LookupSym2 (a6989586621679938787 :: a6989586621679929426) (a6989586621679938788 :: [(a6989586621679929426, b6989586621679929427)]) = Lookup a6989586621679938787 a6989586621679938788 Source #
data FindSym0 :: forall a6989586621680438435 t6989586621680438434. (~>) ((~>) a6989586621680438435 Bool) ((~>) (t6989586621680438434 a6989586621680438435) (Maybe a6989586621680438435)) Source #
Instances
SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # | |
SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680438435 ~> Bool) (t6989586621680438434 a6989586621680438435 ~> Maybe a6989586621680438435) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FindSym0 :: TyFun (a6989586621680438435 ~> Bool) (t6989586621680438434 a6989586621680438435 ~> Maybe a6989586621680438435) -> Type) (a6989586621680438892 :: a6989586621680438435 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FindSym0 :: TyFun (a6989586621680438435 ~> Bool) (t6989586621680438434 a6989586621680438435 ~> Maybe a6989586621680438435) -> Type) (a6989586621680438892 :: a6989586621680438435 ~> Bool) = (FindSym1 a6989586621680438892 t6989586621680438434 :: TyFun (t6989586621680438434 a6989586621680438435) (Maybe a6989586621680438435) -> Type) |
data FindSym1 (a6989586621680438892 :: (~>) a6989586621680438435 Bool) :: forall t6989586621680438434. (~>) (t6989586621680438434 a6989586621680438435) (Maybe a6989586621680438435) Source #
Instances
(SFoldable t, SingI d) => SingI (FindSym1 d t :: TyFun (t a) (Maybe a) -> Type) Source # | |
SuppressUnusedWarnings (FindSym1 a6989586621680438892 t6989586621680438434 :: TyFun (t6989586621680438434 a6989586621680438435) (Maybe a6989586621680438435) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (FindSym1 a6989586621680438892 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680438893 :: t a) Source # | |
type FindSym2 (a6989586621680438892 :: (~>) a6989586621680438435 Bool) (a6989586621680438893 :: t6989586621680438434 a6989586621680438435) = Find a6989586621680438892 a6989586621680438893 Source #
data FilterSym0 :: forall a6989586621679929449. (~>) ((~>) a6989586621679929449 Bool) ((~>) [a6989586621679929449] [a6989586621679929449]) 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 (a6989586621679929449 ~> Bool) ([a6989586621679929449] ~> [a6989586621679929449]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym0 :: TyFun (a6989586621679929449 ~> Bool) ([a6989586621679929449] ~> [a6989586621679929449]) -> Type) (a6989586621679938990 :: a6989586621679929449 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym0 :: TyFun (a6989586621679929449 ~> Bool) ([a6989586621679929449] ~> [a6989586621679929449]) -> Type) (a6989586621679938990 :: a6989586621679929449 ~> Bool) = FilterSym1 a6989586621679938990 |
data FilterSym1 (a6989586621679938990 :: (~>) a6989586621679929449 Bool) :: (~>) [a6989586621679929449] [a6989586621679929449] 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 a6989586621679938990 :: TyFun [a6989586621679929449] [a6989586621679929449] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym1 a6989586621679938990 :: TyFun [a] [a] -> Type) (a6989586621679938991 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym1 a6989586621679938990 :: TyFun [a] [a] -> Type) (a6989586621679938991 :: [a]) = Filter a6989586621679938990 a6989586621679938991 |
type FilterSym2 (a6989586621679938990 :: (~>) a6989586621679929449 Bool) (a6989586621679938991 :: [a6989586621679929449]) = Filter a6989586621679938990 a6989586621679938991 Source #
data PartitionSym0 :: forall a6989586621679929425. (~>) ((~>) a6989586621679929425 Bool) ((~>) [a6989586621679929425] ([a6989586621679929425], [a6989586621679929425])) 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 (a6989586621679929425 ~> Bool) ([a6989586621679929425] ~> ([a6989586621679929425], [a6989586621679929425])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym0 :: TyFun (a6989586621679929425 ~> Bool) ([a6989586621679929425] ~> ([a6989586621679929425], [a6989586621679929425])) -> Type) (a6989586621679938781 :: a6989586621679929425 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym0 :: TyFun (a6989586621679929425 ~> Bool) ([a6989586621679929425] ~> ([a6989586621679929425], [a6989586621679929425])) -> Type) (a6989586621679938781 :: a6989586621679929425 ~> Bool) = PartitionSym1 a6989586621679938781 |
data PartitionSym1 (a6989586621679938781 :: (~>) a6989586621679929425 Bool) :: (~>) [a6989586621679929425] ([a6989586621679929425], [a6989586621679929425]) 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 a6989586621679938781 :: TyFun [a6989586621679929425] ([a6989586621679929425], [a6989586621679929425]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym1 a6989586621679938781 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679938782 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym1 a6989586621679938781 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679938782 :: [a]) = Partition a6989586621679938781 a6989586621679938782 |
type PartitionSym2 (a6989586621679938781 :: (~>) a6989586621679929425 Bool) (a6989586621679938782 :: [a6989586621679929425]) = Partition a6989586621679938781 a6989586621679938782 Source #
data (!!@#@$) :: forall a6989586621679929418. (~>) [a6989586621679929418] ((~>) Nat a6989586621679929418) infixl 9 Source #
Instances
SingI ((!!@#@$) :: TyFun [a] (Nat ~> a) -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$) :: TyFun [a6989586621679929418] (Nat ~> a6989586621679929418) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$) :: TyFun [a6989586621679929418] (Nat ~> a6989586621679929418) -> Type) (a6989586621679938708 :: [a6989586621679929418]) Source # | |
data (!!@#@$$) (a6989586621679938708 :: [a6989586621679929418]) :: (~>) Nat a6989586621679929418 infixl 9 Source #
Instances
SingI d => SingI ((!!@#@$$) d :: TyFun Nat a -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$$) a6989586621679938708 :: TyFun Nat a6989586621679929418 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$$) a6989586621679938708 :: TyFun Nat a -> Type) (a6989586621679938709 :: Nat) Source # | |
type (!!@#@$$$) (a6989586621679938708 :: [a6989586621679929418]) (a6989586621679938709 :: Nat) = (!!) a6989586621679938708 a6989586621679938709 Source #
data ElemIndexSym0 :: forall a6989586621679929447. (~>) a6989586621679929447 ((~>) [a6989586621679929447] (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 a6989586621679929447 ([a6989586621679929447] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym0 :: TyFun a6989586621679929447 ([a6989586621679929447] ~> Maybe Nat) -> Type) (a6989586621679939373 :: a6989586621679929447) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndexSym0 :: TyFun a6989586621679929447 ([a6989586621679929447] ~> Maybe Nat) -> Type) (a6989586621679939373 :: a6989586621679929447) = ElemIndexSym1 a6989586621679939373 |
data ElemIndexSym1 (a6989586621679939373 :: a6989586621679929447) :: (~>) [a6989586621679929447] (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 a6989586621679939373 :: TyFun [a6989586621679929447] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym1 a6989586621679939373 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679939374 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type ElemIndexSym2 (a6989586621679939373 :: a6989586621679929447) (a6989586621679939374 :: [a6989586621679929447]) = ElemIndex a6989586621679939373 a6989586621679939374 Source #
data ElemIndicesSym0 :: forall a6989586621679929446. (~>) a6989586621679929446 ((~>) [a6989586621679929446] [Nat]) Source #
Instances
SEq a => SingI (ElemIndicesSym0 :: TyFun a ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a6989586621679929446 ([a6989586621679929446] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym0 :: TyFun a6989586621679929446 ([a6989586621679929446] ~> [Nat]) -> Type) (a6989586621679939357 :: a6989586621679929446) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym0 :: TyFun a6989586621679929446 ([a6989586621679929446] ~> [Nat]) -> Type) (a6989586621679939357 :: a6989586621679929446) = ElemIndicesSym1 a6989586621679939357 |
data ElemIndicesSym1 (a6989586621679939357 :: a6989586621679929446) :: (~>) [a6989586621679929446] [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 a6989586621679939357 :: TyFun [a6989586621679929446] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym1 a6989586621679939357 :: TyFun [a] [Nat] -> Type) (a6989586621679939358 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym1 a6989586621679939357 :: TyFun [a] [Nat] -> Type) (a6989586621679939358 :: [a]) = ElemIndices a6989586621679939357 a6989586621679939358 |
type ElemIndicesSym2 (a6989586621679939357 :: a6989586621679929446) (a6989586621679939358 :: [a6989586621679929446]) = ElemIndices a6989586621679939357 a6989586621679939358 Source #
data FindIndexSym0 :: forall a6989586621679929445. (~>) ((~>) a6989586621679929445 Bool) ((~>) [a6989586621679929445] (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 (a6989586621679929445 ~> Bool) ([a6989586621679929445] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym0 :: TyFun (a6989586621679929445 ~> Bool) ([a6989586621679929445] ~> Maybe Nat) -> Type) (a6989586621679939365 :: a6989586621679929445 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data FindIndexSym1 (a6989586621679939365 :: (~>) a6989586621679929445 Bool) :: (~>) [a6989586621679929445] (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 a6989586621679939365 :: TyFun [a6989586621679929445] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym1 a6989586621679939365 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679939366 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type FindIndexSym2 (a6989586621679939365 :: (~>) a6989586621679929445 Bool) (a6989586621679939366 :: [a6989586621679929445]) = FindIndex a6989586621679939365 a6989586621679939366 Source #
data FindIndicesSym0 :: forall a6989586621679929444. (~>) ((~>) a6989586621679929444 Bool) ((~>) [a6989586621679929444] [Nat]) Source #
Instances
SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (a6989586621679929444 ~> Bool) ([a6989586621679929444] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym0 :: TyFun (a6989586621679929444 ~> Bool) ([a6989586621679929444] ~> [Nat]) -> Type) (a6989586621679939331 :: a6989586621679929444 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data FindIndicesSym1 (a6989586621679939331 :: (~>) a6989586621679929444 Bool) :: (~>) [a6989586621679929444] [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 a6989586621679939331 :: TyFun [a6989586621679929444] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym1 a6989586621679939331 :: TyFun [a] [Nat] -> Type) (a6989586621679939332 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndicesSym1 a6989586621679939331 :: TyFun [a] [Nat] -> Type) (a6989586621679939332 :: [a]) = FindIndices a6989586621679939331 a6989586621679939332 |
type FindIndicesSym2 (a6989586621679939331 :: (~>) a6989586621679929444 Bool) (a6989586621679939332 :: [a6989586621679929444]) = FindIndices a6989586621679939331 a6989586621679939332 Source #
data ZipSym0 :: forall a6989586621679929495 b6989586621679929496. (~>) [a6989586621679929495] ((~>) [b6989586621679929496] [(a6989586621679929495, b6989586621679929496)]) Source #
Instances
SingI (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # | |
SuppressUnusedWarnings (ZipSym0 :: TyFun [a6989586621679929495] ([b6989586621679929496] ~> [(a6989586621679929495, b6989586621679929496)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym0 :: TyFun [a6989586621679929495] ([b6989586621679929496] ~> [(a6989586621679929495, b6989586621679929496)]) -> Type) (a6989586621679939323 :: [a6989586621679929495]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipSym0 :: TyFun [a6989586621679929495] ([b6989586621679929496] ~> [(a6989586621679929495, b6989586621679929496)]) -> Type) (a6989586621679939323 :: [a6989586621679929495]) = (ZipSym1 a6989586621679939323 b6989586621679929496 :: TyFun [b6989586621679929496] [(a6989586621679929495, b6989586621679929496)] -> Type) |
data ZipSym1 (a6989586621679939323 :: [a6989586621679929495]) :: forall b6989586621679929496. (~>) [b6989586621679929496] [(a6989586621679929495, b6989586621679929496)] Source #
Instances
SingI d => SingI (ZipSym1 d b :: TyFun [b] [(a, b)] -> Type) Source # | |
SuppressUnusedWarnings (ZipSym1 a6989586621679939323 b6989586621679929496 :: TyFun [b6989586621679929496] [(a6989586621679929495, b6989586621679929496)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym1 a6989586621679939323 b :: TyFun [b] [(a, b)] -> Type) (a6989586621679939324 :: [b]) Source # | |
type ZipSym2 (a6989586621679939323 :: [a6989586621679929495]) (a6989586621679939324 :: [b6989586621679929496]) = Zip a6989586621679939323 a6989586621679939324 Source #
data Zip3Sym0 :: forall a6989586621679929492 b6989586621679929493 c6989586621679929494. (~>) [a6989586621679929492] ((~>) [b6989586621679929493] ((~>) [c6989586621679929494] [(a6989586621679929492, b6989586621679929493, c6989586621679929494)])) Source #
Instances
SingI (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a6989586621679929492] ([b6989586621679929493] ~> ([c6989586621679929494] ~> [(a6989586621679929492, b6989586621679929493, c6989586621679929494)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym0 :: TyFun [a6989586621679929492] ([b6989586621679929493] ~> ([c6989586621679929494] ~> [(a6989586621679929492, b6989586621679929493, c6989586621679929494)])) -> Type) (a6989586621679939311 :: [a6989586621679929492]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip3Sym0 :: TyFun [a6989586621679929492] ([b6989586621679929493] ~> ([c6989586621679929494] ~> [(a6989586621679929492, b6989586621679929493, c6989586621679929494)])) -> Type) (a6989586621679939311 :: [a6989586621679929492]) = (Zip3Sym1 a6989586621679939311 b6989586621679929493 c6989586621679929494 :: TyFun [b6989586621679929493] ([c6989586621679929494] ~> [(a6989586621679929492, b6989586621679929493, c6989586621679929494)]) -> Type) |
data Zip3Sym1 (a6989586621679939311 :: [a6989586621679929492]) :: forall b6989586621679929493 c6989586621679929494. (~>) [b6989586621679929493] ((~>) [c6989586621679929494] [(a6989586621679929492, b6989586621679929493, c6989586621679929494)]) Source #
Instances
SingI d => SingI (Zip3Sym1 d b c :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym1 a6989586621679939311 b6989586621679929493 c6989586621679929494 :: TyFun [b6989586621679929493] ([c6989586621679929494] ~> [(a6989586621679929492, b6989586621679929493, c6989586621679929494)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym1 a6989586621679939311 b6989586621679929493 c6989586621679929494 :: TyFun [b6989586621679929493] ([c6989586621679929494] ~> [(a6989586621679929492, b6989586621679929493, c6989586621679929494)]) -> Type) (a6989586621679939312 :: [b6989586621679929493]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip3Sym1 a6989586621679939311 b6989586621679929493 c6989586621679929494 :: TyFun [b6989586621679929493] ([c6989586621679929494] ~> [(a6989586621679929492, b6989586621679929493, c6989586621679929494)]) -> Type) (a6989586621679939312 :: [b6989586621679929493]) = (Zip3Sym2 a6989586621679939311 a6989586621679939312 c6989586621679929494 :: TyFun [c6989586621679929494] [(a6989586621679929492, b6989586621679929493, c6989586621679929494)] -> Type) |
data Zip3Sym2 (a6989586621679939311 :: [a6989586621679929492]) (a6989586621679939312 :: [b6989586621679929493]) :: forall c6989586621679929494. (~>) [c6989586621679929494] [(a6989586621679929492, b6989586621679929493, c6989586621679929494)] Source #
Instances
(SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 c :: TyFun [c] [(a, b, c)] -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym2 a6989586621679939312 a6989586621679939311 c6989586621679929494 :: TyFun [c6989586621679929494] [(a6989586621679929492, b6989586621679929493, c6989586621679929494)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym2 a6989586621679939312 a6989586621679939311 c :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679939313 :: [c]) Source # | |
type Zip3Sym3 (a6989586621679939311 :: [a6989586621679929492]) (a6989586621679939312 :: [b6989586621679929493]) (a6989586621679939313 :: [c6989586621679929494]) = Zip3 a6989586621679939311 a6989586621679939312 a6989586621679939313 Source #
data Zip4Sym0 :: forall a6989586621680055659 b6989586621680055660 c6989586621680055661 d6989586621680055662. (~>) [a6989586621680055659] ((~>) [b6989586621680055660] ((~>) [c6989586621680055661] ((~>) [d6989586621680055662] [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)]))) Source #
Instances
SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a6989586621680055659] ([b6989586621680055660] ~> ([c6989586621680055661] ~> ([d6989586621680055662] ~> [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym0 :: TyFun [a6989586621680055659] ([b6989586621680055660] ~> ([c6989586621680055661] ~> ([d6989586621680055662] ~> [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)]))) -> Type) (a6989586621680068361 :: [a6989586621680055659]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym0 :: TyFun [a6989586621680055659] ([b6989586621680055660] ~> ([c6989586621680055661] ~> ([d6989586621680055662] ~> [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)]))) -> Type) (a6989586621680068361 :: [a6989586621680055659]) = (Zip4Sym1 a6989586621680068361 b6989586621680055660 c6989586621680055661 d6989586621680055662 :: TyFun [b6989586621680055660] ([c6989586621680055661] ~> ([d6989586621680055662] ~> [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)])) -> Type) |
data Zip4Sym1 (a6989586621680068361 :: [a6989586621680055659]) :: forall b6989586621680055660 c6989586621680055661 d6989586621680055662. (~>) [b6989586621680055660] ((~>) [c6989586621680055661] ((~>) [d6989586621680055662] [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)])) Source #
Instances
SuppressUnusedWarnings (Zip4Sym1 a6989586621680068361 b6989586621680055660 c6989586621680055661 d6989586621680055662 :: TyFun [b6989586621680055660] ([c6989586621680055661] ~> ([d6989586621680055662] ~> [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym1 a6989586621680068361 b6989586621680055660 c6989586621680055661 d6989586621680055662 :: TyFun [b6989586621680055660] ([c6989586621680055661] ~> ([d6989586621680055662] ~> [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)])) -> Type) (a6989586621680068362 :: [b6989586621680055660]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym1 a6989586621680068361 b6989586621680055660 c6989586621680055661 d6989586621680055662 :: TyFun [b6989586621680055660] ([c6989586621680055661] ~> ([d6989586621680055662] ~> [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)])) -> Type) (a6989586621680068362 :: [b6989586621680055660]) = (Zip4Sym2 a6989586621680068361 a6989586621680068362 c6989586621680055661 d6989586621680055662 :: TyFun [c6989586621680055661] ([d6989586621680055662] ~> [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)]) -> Type) |
data Zip4Sym2 (a6989586621680068361 :: [a6989586621680055659]) (a6989586621680068362 :: [b6989586621680055660]) :: forall c6989586621680055661 d6989586621680055662. (~>) [c6989586621680055661] ((~>) [d6989586621680055662] [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)]) Source #
Instances
SuppressUnusedWarnings (Zip4Sym2 a6989586621680068362 a6989586621680068361 c6989586621680055661 d6989586621680055662 :: TyFun [c6989586621680055661] ([d6989586621680055662] ~> [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym2 a6989586621680068362 a6989586621680068361 c6989586621680055661 d6989586621680055662 :: TyFun [c6989586621680055661] ([d6989586621680055662] ~> [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)]) -> Type) (a6989586621680068363 :: [c6989586621680055661]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym2 a6989586621680068362 a6989586621680068361 c6989586621680055661 d6989586621680055662 :: TyFun [c6989586621680055661] ([d6989586621680055662] ~> [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)]) -> Type) (a6989586621680068363 :: [c6989586621680055661]) = (Zip4Sym3 a6989586621680068362 a6989586621680068361 a6989586621680068363 d6989586621680055662 :: TyFun [d6989586621680055662] [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)] -> Type) |
data Zip4Sym3 (a6989586621680068361 :: [a6989586621680055659]) (a6989586621680068362 :: [b6989586621680055660]) (a6989586621680068363 :: [c6989586621680055661]) :: forall d6989586621680055662. (~>) [d6989586621680055662] [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)] Source #
Instances
SuppressUnusedWarnings (Zip4Sym3 a6989586621680068363 a6989586621680068362 a6989586621680068361 d6989586621680055662 :: TyFun [d6989586621680055662] [(a6989586621680055659, b6989586621680055660, c6989586621680055661, d6989586621680055662)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym3 a6989586621680068363 a6989586621680068362 a6989586621680068361 d :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621680068364 :: [d]) Source # | |
type Zip4Sym4 (a6989586621680068361 :: [a6989586621680055659]) (a6989586621680068362 :: [b6989586621680055660]) (a6989586621680068363 :: [c6989586621680055661]) (a6989586621680068364 :: [d6989586621680055662]) = Zip4 a6989586621680068361 a6989586621680068362 a6989586621680068363 a6989586621680068364 Source #
data Zip5Sym0 :: forall a6989586621680055654 b6989586621680055655 c6989586621680055656 d6989586621680055657 e6989586621680055658. (~>) [a6989586621680055654] ((~>) [b6989586621680055655] ((~>) [c6989586621680055656] ((~>) [d6989586621680055657] ((~>) [e6989586621680055658] [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)])))) Source #
Instances
SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a6989586621680055654] ([b6989586621680055655] ~> ([c6989586621680055656] ~> ([d6989586621680055657] ~> ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym0 :: TyFun [a6989586621680055654] ([b6989586621680055655] ~> ([c6989586621680055656] ~> ([d6989586621680055657] ~> ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)])))) -> Type) (a6989586621680068338 :: [a6989586621680055654]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym0 :: TyFun [a6989586621680055654] ([b6989586621680055655] ~> ([c6989586621680055656] ~> ([d6989586621680055657] ~> ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)])))) -> Type) (a6989586621680068338 :: [a6989586621680055654]) = (Zip5Sym1 a6989586621680068338 b6989586621680055655 c6989586621680055656 d6989586621680055657 e6989586621680055658 :: TyFun [b6989586621680055655] ([c6989586621680055656] ~> ([d6989586621680055657] ~> ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]))) -> Type) |
data Zip5Sym1 (a6989586621680068338 :: [a6989586621680055654]) :: forall b6989586621680055655 c6989586621680055656 d6989586621680055657 e6989586621680055658. (~>) [b6989586621680055655] ((~>) [c6989586621680055656] ((~>) [d6989586621680055657] ((~>) [e6989586621680055658] [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]))) Source #
Instances
SuppressUnusedWarnings (Zip5Sym1 a6989586621680068338 b6989586621680055655 c6989586621680055656 d6989586621680055657 e6989586621680055658 :: TyFun [b6989586621680055655] ([c6989586621680055656] ~> ([d6989586621680055657] ~> ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym1 a6989586621680068338 b6989586621680055655 c6989586621680055656 d6989586621680055657 e6989586621680055658 :: TyFun [b6989586621680055655] ([c6989586621680055656] ~> ([d6989586621680055657] ~> ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]))) -> Type) (a6989586621680068339 :: [b6989586621680055655]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym1 a6989586621680068338 b6989586621680055655 c6989586621680055656 d6989586621680055657 e6989586621680055658 :: TyFun [b6989586621680055655] ([c6989586621680055656] ~> ([d6989586621680055657] ~> ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]))) -> Type) (a6989586621680068339 :: [b6989586621680055655]) = (Zip5Sym2 a6989586621680068338 a6989586621680068339 c6989586621680055656 d6989586621680055657 e6989586621680055658 :: TyFun [c6989586621680055656] ([d6989586621680055657] ~> ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)])) -> Type) |
data Zip5Sym2 (a6989586621680068338 :: [a6989586621680055654]) (a6989586621680068339 :: [b6989586621680055655]) :: forall c6989586621680055656 d6989586621680055657 e6989586621680055658. (~>) [c6989586621680055656] ((~>) [d6989586621680055657] ((~>) [e6989586621680055658] [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)])) Source #
Instances
SuppressUnusedWarnings (Zip5Sym2 a6989586621680068339 a6989586621680068338 c6989586621680055656 d6989586621680055657 e6989586621680055658 :: TyFun [c6989586621680055656] ([d6989586621680055657] ~> ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym2 a6989586621680068339 a6989586621680068338 c6989586621680055656 d6989586621680055657 e6989586621680055658 :: TyFun [c6989586621680055656] ([d6989586621680055657] ~> ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)])) -> Type) (a6989586621680068340 :: [c6989586621680055656]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym2 a6989586621680068339 a6989586621680068338 c6989586621680055656 d6989586621680055657 e6989586621680055658 :: TyFun [c6989586621680055656] ([d6989586621680055657] ~> ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)])) -> Type) (a6989586621680068340 :: [c6989586621680055656]) = (Zip5Sym3 a6989586621680068339 a6989586621680068338 a6989586621680068340 d6989586621680055657 e6989586621680055658 :: TyFun [d6989586621680055657] ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]) -> Type) |
data Zip5Sym3 (a6989586621680068338 :: [a6989586621680055654]) (a6989586621680068339 :: [b6989586621680055655]) (a6989586621680068340 :: [c6989586621680055656]) :: forall d6989586621680055657 e6989586621680055658. (~>) [d6989586621680055657] ((~>) [e6989586621680055658] [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]) Source #
Instances
SuppressUnusedWarnings (Zip5Sym3 a6989586621680068340 a6989586621680068339 a6989586621680068338 d6989586621680055657 e6989586621680055658 :: TyFun [d6989586621680055657] ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym3 a6989586621680068340 a6989586621680068339 a6989586621680068338 d6989586621680055657 e6989586621680055658 :: TyFun [d6989586621680055657] ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]) -> Type) (a6989586621680068341 :: [d6989586621680055657]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym3 a6989586621680068340 a6989586621680068339 a6989586621680068338 d6989586621680055657 e6989586621680055658 :: TyFun [d6989586621680055657] ([e6989586621680055658] ~> [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)]) -> Type) (a6989586621680068341 :: [d6989586621680055657]) = (Zip5Sym4 a6989586621680068340 a6989586621680068339 a6989586621680068338 a6989586621680068341 e6989586621680055658 :: TyFun [e6989586621680055658] [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)] -> Type) |
data Zip5Sym4 (a6989586621680068338 :: [a6989586621680055654]) (a6989586621680068339 :: [b6989586621680055655]) (a6989586621680068340 :: [c6989586621680055656]) (a6989586621680068341 :: [d6989586621680055657]) :: forall e6989586621680055658. (~>) [e6989586621680055658] [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)] Source #
Instances
SuppressUnusedWarnings (Zip5Sym4 a6989586621680068341 a6989586621680068340 a6989586621680068339 a6989586621680068338 e6989586621680055658 :: TyFun [e6989586621680055658] [(a6989586621680055654, b6989586621680055655, c6989586621680055656, d6989586621680055657, e6989586621680055658)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym4 a6989586621680068341 a6989586621680068340 a6989586621680068339 a6989586621680068338 e :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621680068342 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type Zip5Sym5 (a6989586621680068338 :: [a6989586621680055654]) (a6989586621680068339 :: [b6989586621680055655]) (a6989586621680068340 :: [c6989586621680055656]) (a6989586621680068341 :: [d6989586621680055657]) (a6989586621680068342 :: [e6989586621680055658]) = Zip5 a6989586621680068338 a6989586621680068339 a6989586621680068340 a6989586621680068341 a6989586621680068342 Source #
data Zip6Sym0 :: forall a6989586621680055648 b6989586621680055649 c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653. (~>) [a6989586621680055648] ((~>) [b6989586621680055649] ((~>) [c6989586621680055650] ((~>) [d6989586621680055651] ((~>) [e6989586621680055652] ((~>) [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]))))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a6989586621680055648] ([b6989586621680055649] ~> ([c6989586621680055650] ~> ([d6989586621680055651] ~> ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym0 :: TyFun [a6989586621680055648] ([b6989586621680055649] ~> ([c6989586621680055650] ~> ([d6989586621680055651] ~> ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]))))) -> Type) (a6989586621680068310 :: [a6989586621680055648]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym0 :: TyFun [a6989586621680055648] ([b6989586621680055649] ~> ([c6989586621680055650] ~> ([d6989586621680055651] ~> ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]))))) -> Type) (a6989586621680068310 :: [a6989586621680055648]) = (Zip6Sym1 a6989586621680068310 b6989586621680055649 c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653 :: TyFun [b6989586621680055649] ([c6989586621680055650] ~> ([d6989586621680055651] ~> ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])))) -> Type) |
data Zip6Sym1 (a6989586621680068310 :: [a6989586621680055648]) :: forall b6989586621680055649 c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653. (~>) [b6989586621680055649] ((~>) [c6989586621680055650] ((~>) [d6989586621680055651] ((~>) [e6989586621680055652] ((~>) [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym1 a6989586621680068310 b6989586621680055649 c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653 :: TyFun [b6989586621680055649] ([c6989586621680055650] ~> ([d6989586621680055651] ~> ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym1 a6989586621680068310 b6989586621680055649 c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653 :: TyFun [b6989586621680055649] ([c6989586621680055650] ~> ([d6989586621680055651] ~> ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])))) -> Type) (a6989586621680068311 :: [b6989586621680055649]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym1 a6989586621680068310 b6989586621680055649 c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653 :: TyFun [b6989586621680055649] ([c6989586621680055650] ~> ([d6989586621680055651] ~> ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])))) -> Type) (a6989586621680068311 :: [b6989586621680055649]) = (Zip6Sym2 a6989586621680068310 a6989586621680068311 c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653 :: TyFun [c6989586621680055650] ([d6989586621680055651] ~> ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]))) -> Type) |
data Zip6Sym2 (a6989586621680068310 :: [a6989586621680055648]) (a6989586621680068311 :: [b6989586621680055649]) :: forall c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653. (~>) [c6989586621680055650] ((~>) [d6989586621680055651] ((~>) [e6989586621680055652] ((~>) [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym2 a6989586621680068311 a6989586621680068310 c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653 :: TyFun [c6989586621680055650] ([d6989586621680055651] ~> ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym2 a6989586621680068311 a6989586621680068310 c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653 :: TyFun [c6989586621680055650] ([d6989586621680055651] ~> ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]))) -> Type) (a6989586621680068312 :: [c6989586621680055650]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym2 a6989586621680068311 a6989586621680068310 c6989586621680055650 d6989586621680055651 e6989586621680055652 f6989586621680055653 :: TyFun [c6989586621680055650] ([d6989586621680055651] ~> ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]))) -> Type) (a6989586621680068312 :: [c6989586621680055650]) = (Zip6Sym3 a6989586621680068311 a6989586621680068310 a6989586621680068312 d6989586621680055651 e6989586621680055652 f6989586621680055653 :: TyFun [d6989586621680055651] ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])) -> Type) |
data Zip6Sym3 (a6989586621680068310 :: [a6989586621680055648]) (a6989586621680068311 :: [b6989586621680055649]) (a6989586621680068312 :: [c6989586621680055650]) :: forall d6989586621680055651 e6989586621680055652 f6989586621680055653. (~>) [d6989586621680055651] ((~>) [e6989586621680055652] ((~>) [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])) Source #
Instances
SuppressUnusedWarnings (Zip6Sym3 a6989586621680068312 a6989586621680068311 a6989586621680068310 d6989586621680055651 e6989586621680055652 f6989586621680055653 :: TyFun [d6989586621680055651] ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym3 a6989586621680068312 a6989586621680068311 a6989586621680068310 d6989586621680055651 e6989586621680055652 f6989586621680055653 :: TyFun [d6989586621680055651] ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])) -> Type) (a6989586621680068313 :: [d6989586621680055651]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym3 a6989586621680068312 a6989586621680068311 a6989586621680068310 d6989586621680055651 e6989586621680055652 f6989586621680055653 :: TyFun [d6989586621680055651] ([e6989586621680055652] ~> ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)])) -> Type) (a6989586621680068313 :: [d6989586621680055651]) = (Zip6Sym4 a6989586621680068312 a6989586621680068311 a6989586621680068310 a6989586621680068313 e6989586621680055652 f6989586621680055653 :: TyFun [e6989586621680055652] ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]) -> Type) |
data Zip6Sym4 (a6989586621680068310 :: [a6989586621680055648]) (a6989586621680068311 :: [b6989586621680055649]) (a6989586621680068312 :: [c6989586621680055650]) (a6989586621680068313 :: [d6989586621680055651]) :: forall e6989586621680055652 f6989586621680055653. (~>) [e6989586621680055652] ((~>) [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]) Source #
Instances
SuppressUnusedWarnings (Zip6Sym4 a6989586621680068313 a6989586621680068312 a6989586621680068311 a6989586621680068310 e6989586621680055652 f6989586621680055653 :: TyFun [e6989586621680055652] ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym4 a6989586621680068313 a6989586621680068312 a6989586621680068311 a6989586621680068310 e6989586621680055652 f6989586621680055653 :: TyFun [e6989586621680055652] ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]) -> Type) (a6989586621680068314 :: [e6989586621680055652]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym4 a6989586621680068313 a6989586621680068312 a6989586621680068311 a6989586621680068310 e6989586621680055652 f6989586621680055653 :: TyFun [e6989586621680055652] ([f6989586621680055653] ~> [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)]) -> Type) (a6989586621680068314 :: [e6989586621680055652]) = (Zip6Sym5 a6989586621680068313 a6989586621680068312 a6989586621680068311 a6989586621680068310 a6989586621680068314 f6989586621680055653 :: TyFun [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)] -> Type) |
data Zip6Sym5 (a6989586621680068310 :: [a6989586621680055648]) (a6989586621680068311 :: [b6989586621680055649]) (a6989586621680068312 :: [c6989586621680055650]) (a6989586621680068313 :: [d6989586621680055651]) (a6989586621680068314 :: [e6989586621680055652]) :: forall f6989586621680055653. (~>) [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)] Source #
Instances
SuppressUnusedWarnings (Zip6Sym5 a6989586621680068314 a6989586621680068313 a6989586621680068312 a6989586621680068311 a6989586621680068310 f6989586621680055653 :: TyFun [f6989586621680055653] [(a6989586621680055648, b6989586621680055649, c6989586621680055650, d6989586621680055651, e6989586621680055652, f6989586621680055653)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym5 a6989586621680068314 a6989586621680068313 a6989586621680068312 a6989586621680068311 a6989586621680068310 f :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680068315 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym5 a6989586621680068314 a6989586621680068313 a6989586621680068312 a6989586621680068311 a6989586621680068310 f :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680068315 :: [f]) = Zip6 a6989586621680068314 a6989586621680068313 a6989586621680068312 a6989586621680068311 a6989586621680068310 a6989586621680068315 |
type Zip6Sym6 (a6989586621680068310 :: [a6989586621680055648]) (a6989586621680068311 :: [b6989586621680055649]) (a6989586621680068312 :: [c6989586621680055650]) (a6989586621680068313 :: [d6989586621680055651]) (a6989586621680068314 :: [e6989586621680055652]) (a6989586621680068315 :: [f6989586621680055653]) = Zip6 a6989586621680068310 a6989586621680068311 a6989586621680068312 a6989586621680068313 a6989586621680068314 a6989586621680068315 Source #
data Zip7Sym0 :: forall a6989586621680055641 b6989586621680055642 c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647. (~>) [a6989586621680055641] ((~>) [b6989586621680055642] ((~>) [c6989586621680055643] ((~>) [d6989586621680055644] ((~>) [e6989586621680055645] ((~>) [f6989586621680055646] ((~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])))))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a6989586621680055641] ([b6989586621680055642] ~> ([c6989586621680055643] ~> ([d6989586621680055644] ~> ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym0 :: TyFun [a6989586621680055641] ([b6989586621680055642] ~> ([c6989586621680055643] ~> ([d6989586621680055644] ~> ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])))))) -> Type) (a6989586621680068277 :: [a6989586621680055641]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym0 :: TyFun [a6989586621680055641] ([b6989586621680055642] ~> ([c6989586621680055643] ~> ([d6989586621680055644] ~> ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])))))) -> Type) (a6989586621680068277 :: [a6989586621680055641]) = (Zip7Sym1 a6989586621680068277 b6989586621680055642 c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [b6989586621680055642] ([c6989586621680055643] ~> ([d6989586621680055644] ~> ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))))) -> Type) |
data Zip7Sym1 (a6989586621680068277 :: [a6989586621680055641]) :: forall b6989586621680055642 c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647. (~>) [b6989586621680055642] ((~>) [c6989586621680055643] ((~>) [d6989586621680055644] ((~>) [e6989586621680055645] ((~>) [f6989586621680055646] ((~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym1 a6989586621680068277 b6989586621680055642 c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [b6989586621680055642] ([c6989586621680055643] ~> ([d6989586621680055644] ~> ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym1 a6989586621680068277 b6989586621680055642 c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [b6989586621680055642] ([c6989586621680055643] ~> ([d6989586621680055644] ~> ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))))) -> Type) (a6989586621680068278 :: [b6989586621680055642]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym1 a6989586621680068277 b6989586621680055642 c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [b6989586621680055642] ([c6989586621680055643] ~> ([d6989586621680055644] ~> ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))))) -> Type) (a6989586621680068278 :: [b6989586621680055642]) = (Zip7Sym2 a6989586621680068277 a6989586621680068278 c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [c6989586621680055643] ([d6989586621680055644] ~> ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])))) -> Type) |
data Zip7Sym2 (a6989586621680068277 :: [a6989586621680055641]) (a6989586621680068278 :: [b6989586621680055642]) :: forall c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647. (~>) [c6989586621680055643] ((~>) [d6989586621680055644] ((~>) [e6989586621680055645] ((~>) [f6989586621680055646] ((~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym2 a6989586621680068278 a6989586621680068277 c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [c6989586621680055643] ([d6989586621680055644] ~> ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym2 a6989586621680068278 a6989586621680068277 c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [c6989586621680055643] ([d6989586621680055644] ~> ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])))) -> Type) (a6989586621680068279 :: [c6989586621680055643]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym2 a6989586621680068278 a6989586621680068277 c6989586621680055643 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [c6989586621680055643] ([d6989586621680055644] ~> ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])))) -> Type) (a6989586621680068279 :: [c6989586621680055643]) = (Zip7Sym3 a6989586621680068278 a6989586621680068277 a6989586621680068279 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [d6989586621680055644] ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))) -> Type) |
data Zip7Sym3 (a6989586621680068277 :: [a6989586621680055641]) (a6989586621680068278 :: [b6989586621680055642]) (a6989586621680068279 :: [c6989586621680055643]) :: forall d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647. (~>) [d6989586621680055644] ((~>) [e6989586621680055645] ((~>) [f6989586621680055646] ((~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym3 a6989586621680068279 a6989586621680068278 a6989586621680068277 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [d6989586621680055644] ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym3 a6989586621680068279 a6989586621680068278 a6989586621680068277 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [d6989586621680055644] ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))) -> Type) (a6989586621680068280 :: [d6989586621680055644]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym3 a6989586621680068279 a6989586621680068278 a6989586621680068277 d6989586621680055644 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [d6989586621680055644] ([e6989586621680055645] ~> ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]))) -> Type) (a6989586621680068280 :: [d6989586621680055644]) = (Zip7Sym4 a6989586621680068279 a6989586621680068278 a6989586621680068277 a6989586621680068280 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [e6989586621680055645] ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])) -> Type) |
data Zip7Sym4 (a6989586621680068277 :: [a6989586621680055641]) (a6989586621680068278 :: [b6989586621680055642]) (a6989586621680068279 :: [c6989586621680055643]) (a6989586621680068280 :: [d6989586621680055644]) :: forall e6989586621680055645 f6989586621680055646 g6989586621680055647. (~>) [e6989586621680055645] ((~>) [f6989586621680055646] ((~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])) Source #
Instances
SuppressUnusedWarnings (Zip7Sym4 a6989586621680068280 a6989586621680068279 a6989586621680068278 a6989586621680068277 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [e6989586621680055645] ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym4 a6989586621680068280 a6989586621680068279 a6989586621680068278 a6989586621680068277 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [e6989586621680055645] ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])) -> Type) (a6989586621680068281 :: [e6989586621680055645]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym4 a6989586621680068280 a6989586621680068279 a6989586621680068278 a6989586621680068277 e6989586621680055645 f6989586621680055646 g6989586621680055647 :: TyFun [e6989586621680055645] ([f6989586621680055646] ~> ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)])) -> Type) (a6989586621680068281 :: [e6989586621680055645]) = (Zip7Sym5 a6989586621680068280 a6989586621680068279 a6989586621680068278 a6989586621680068277 a6989586621680068281 f6989586621680055646 g6989586621680055647 :: TyFun [f6989586621680055646] ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]) -> Type) |
data Zip7Sym5 (a6989586621680068277 :: [a6989586621680055641]) (a6989586621680068278 :: [b6989586621680055642]) (a6989586621680068279 :: [c6989586621680055643]) (a6989586621680068280 :: [d6989586621680055644]) (a6989586621680068281 :: [e6989586621680055645]) :: forall f6989586621680055646 g6989586621680055647. (~>) [f6989586621680055646] ((~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]) Source #
Instances
SuppressUnusedWarnings (Zip7Sym5 a6989586621680068281 a6989586621680068280 a6989586621680068279 a6989586621680068278 a6989586621680068277 f6989586621680055646 g6989586621680055647 :: TyFun [f6989586621680055646] ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym5 a6989586621680068281 a6989586621680068280 a6989586621680068279 a6989586621680068278 a6989586621680068277 f6989586621680055646 g6989586621680055647 :: TyFun [f6989586621680055646] ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]) -> Type) (a6989586621680068282 :: [f6989586621680055646]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym5 a6989586621680068281 a6989586621680068280 a6989586621680068279 a6989586621680068278 a6989586621680068277 f6989586621680055646 g6989586621680055647 :: TyFun [f6989586621680055646] ([g6989586621680055647] ~> [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)]) -> Type) (a6989586621680068282 :: [f6989586621680055646]) = (Zip7Sym6 a6989586621680068281 a6989586621680068280 a6989586621680068279 a6989586621680068278 a6989586621680068277 a6989586621680068282 g6989586621680055647 :: TyFun [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)] -> Type) |
data Zip7Sym6 (a6989586621680068277 :: [a6989586621680055641]) (a6989586621680068278 :: [b6989586621680055642]) (a6989586621680068279 :: [c6989586621680055643]) (a6989586621680068280 :: [d6989586621680055644]) (a6989586621680068281 :: [e6989586621680055645]) (a6989586621680068282 :: [f6989586621680055646]) :: forall g6989586621680055647. (~>) [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)] Source #
Instances
SuppressUnusedWarnings (Zip7Sym6 a6989586621680068282 a6989586621680068281 a6989586621680068280 a6989586621680068279 a6989586621680068278 a6989586621680068277 g6989586621680055647 :: TyFun [g6989586621680055647] [(a6989586621680055641, b6989586621680055642, c6989586621680055643, d6989586621680055644, e6989586621680055645, f6989586621680055646, g6989586621680055647)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym6 a6989586621680068282 a6989586621680068281 a6989586621680068280 a6989586621680068279 a6989586621680068278 a6989586621680068277 g :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680068283 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym6 a6989586621680068282 a6989586621680068281 a6989586621680068280 a6989586621680068279 a6989586621680068278 a6989586621680068277 g :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680068283 :: [g]) = Zip7 a6989586621680068282 a6989586621680068281 a6989586621680068280 a6989586621680068279 a6989586621680068278 a6989586621680068277 a6989586621680068283 |
type Zip7Sym7 (a6989586621680068277 :: [a6989586621680055641]) (a6989586621680068278 :: [b6989586621680055642]) (a6989586621680068279 :: [c6989586621680055643]) (a6989586621680068280 :: [d6989586621680055644]) (a6989586621680068281 :: [e6989586621680055645]) (a6989586621680068282 :: [f6989586621680055646]) (a6989586621680068283 :: [g6989586621680055647]) = Zip7 a6989586621680068277 a6989586621680068278 a6989586621680068279 a6989586621680068280 a6989586621680068281 a6989586621680068282 a6989586621680068283 Source #
data ZipWithSym0 :: forall a6989586621679929489 b6989586621679929490 c6989586621679929491. (~>) ((~>) a6989586621679929489 ((~>) b6989586621679929490 c6989586621679929491)) ((~>) [a6989586621679929489] ((~>) [b6989586621679929490] [c6989586621679929491])) 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 (a6989586621679929489 ~> (b6989586621679929490 ~> c6989586621679929491)) ([a6989586621679929489] ~> ([b6989586621679929490] ~> [c6989586621679929491])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym0 :: TyFun (a6989586621679929489 ~> (b6989586621679929490 ~> c6989586621679929491)) ([a6989586621679929489] ~> ([b6989586621679929490] ~> [c6989586621679929491])) -> Type) (a6989586621679939300 :: a6989586621679929489 ~> (b6989586621679929490 ~> c6989586621679929491)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym0 :: TyFun (a6989586621679929489 ~> (b6989586621679929490 ~> c6989586621679929491)) ([a6989586621679929489] ~> ([b6989586621679929490] ~> [c6989586621679929491])) -> Type) (a6989586621679939300 :: a6989586621679929489 ~> (b6989586621679929490 ~> c6989586621679929491)) = ZipWithSym1 a6989586621679939300 |
data ZipWithSym1 (a6989586621679939300 :: (~>) a6989586621679929489 ((~>) b6989586621679929490 c6989586621679929491)) :: (~>) [a6989586621679929489] ((~>) [b6989586621679929490] [c6989586621679929491]) 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 a6989586621679939300 :: TyFun [a6989586621679929489] ([b6989586621679929490] ~> [c6989586621679929491]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym1 a6989586621679939300 :: TyFun [a6989586621679929489] ([b6989586621679929490] ~> [c6989586621679929491]) -> Type) (a6989586621679939301 :: [a6989586621679929489]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym1 a6989586621679939300 :: TyFun [a6989586621679929489] ([b6989586621679929490] ~> [c6989586621679929491]) -> Type) (a6989586621679939301 :: [a6989586621679929489]) = ZipWithSym2 a6989586621679939300 a6989586621679939301 |
data ZipWithSym2 (a6989586621679939300 :: (~>) a6989586621679929489 ((~>) b6989586621679929490 c6989586621679929491)) (a6989586621679939301 :: [a6989586621679929489]) :: (~>) [b6989586621679929490] [c6989586621679929491] 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 a6989586621679939301 a6989586621679939300 :: TyFun [b6989586621679929490] [c6989586621679929491] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym2 a6989586621679939301 a6989586621679939300 :: TyFun [b] [c] -> Type) (a6989586621679939302 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym2 a6989586621679939301 a6989586621679939300 :: TyFun [b] [c] -> Type) (a6989586621679939302 :: [b]) = ZipWith a6989586621679939301 a6989586621679939300 a6989586621679939302 |
type ZipWithSym3 (a6989586621679939300 :: (~>) a6989586621679929489 ((~>) b6989586621679929490 c6989586621679929491)) (a6989586621679939301 :: [a6989586621679929489]) (a6989586621679939302 :: [b6989586621679929490]) = ZipWith a6989586621679939300 a6989586621679939301 a6989586621679939302 Source #
data ZipWith3Sym0 :: forall a6989586621679929485 b6989586621679929486 c6989586621679929487 d6989586621679929488. (~>) ((~>) a6989586621679929485 ((~>) b6989586621679929486 ((~>) c6989586621679929487 d6989586621679929488))) ((~>) [a6989586621679929485] ((~>) [b6989586621679929486] ((~>) [c6989586621679929487] [d6989586621679929488]))) 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 (a6989586621679929485 ~> (b6989586621679929486 ~> (c6989586621679929487 ~> d6989586621679929488))) ([a6989586621679929485] ~> ([b6989586621679929486] ~> ([c6989586621679929487] ~> [d6989586621679929488]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym0 :: TyFun (a6989586621679929485 ~> (b6989586621679929486 ~> (c6989586621679929487 ~> d6989586621679929488))) ([a6989586621679929485] ~> ([b6989586621679929486] ~> ([c6989586621679929487] ~> [d6989586621679929488]))) -> Type) (a6989586621679939285 :: a6989586621679929485 ~> (b6989586621679929486 ~> (c6989586621679929487 ~> d6989586621679929488))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym0 :: TyFun (a6989586621679929485 ~> (b6989586621679929486 ~> (c6989586621679929487 ~> d6989586621679929488))) ([a6989586621679929485] ~> ([b6989586621679929486] ~> ([c6989586621679929487] ~> [d6989586621679929488]))) -> Type) (a6989586621679939285 :: a6989586621679929485 ~> (b6989586621679929486 ~> (c6989586621679929487 ~> d6989586621679929488))) = ZipWith3Sym1 a6989586621679939285 |
data ZipWith3Sym1 (a6989586621679939285 :: (~>) a6989586621679929485 ((~>) b6989586621679929486 ((~>) c6989586621679929487 d6989586621679929488))) :: (~>) [a6989586621679929485] ((~>) [b6989586621679929486] ((~>) [c6989586621679929487] [d6989586621679929488])) 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 a6989586621679939285 :: TyFun [a6989586621679929485] ([b6989586621679929486] ~> ([c6989586621679929487] ~> [d6989586621679929488])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym1 a6989586621679939285 :: TyFun [a6989586621679929485] ([b6989586621679929486] ~> ([c6989586621679929487] ~> [d6989586621679929488])) -> Type) (a6989586621679939286 :: [a6989586621679929485]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym1 a6989586621679939285 :: TyFun [a6989586621679929485] ([b6989586621679929486] ~> ([c6989586621679929487] ~> [d6989586621679929488])) -> Type) (a6989586621679939286 :: [a6989586621679929485]) = ZipWith3Sym2 a6989586621679939285 a6989586621679939286 |
data ZipWith3Sym2 (a6989586621679939285 :: (~>) a6989586621679929485 ((~>) b6989586621679929486 ((~>) c6989586621679929487 d6989586621679929488))) (a6989586621679939286 :: [a6989586621679929485]) :: (~>) [b6989586621679929486] ((~>) [c6989586621679929487] [d6989586621679929488]) 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 a6989586621679939286 a6989586621679939285 :: TyFun [b6989586621679929486] ([c6989586621679929487] ~> [d6989586621679929488]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym2 a6989586621679939286 a6989586621679939285 :: TyFun [b6989586621679929486] ([c6989586621679929487] ~> [d6989586621679929488]) -> Type) (a6989586621679939287 :: [b6989586621679929486]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym2 a6989586621679939286 a6989586621679939285 :: TyFun [b6989586621679929486] ([c6989586621679929487] ~> [d6989586621679929488]) -> Type) (a6989586621679939287 :: [b6989586621679929486]) = ZipWith3Sym3 a6989586621679939286 a6989586621679939285 a6989586621679939287 |
data ZipWith3Sym3 (a6989586621679939285 :: (~>) a6989586621679929485 ((~>) b6989586621679929486 ((~>) c6989586621679929487 d6989586621679929488))) (a6989586621679939286 :: [a6989586621679929485]) (a6989586621679939287 :: [b6989586621679929486]) :: (~>) [c6989586621679929487] [d6989586621679929488] 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 a6989586621679939287 a6989586621679939286 a6989586621679939285 :: TyFun [c6989586621679929487] [d6989586621679929488] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym3 a6989586621679939287 a6989586621679939286 a6989586621679939285 :: TyFun [c] [d] -> Type) (a6989586621679939288 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym3 a6989586621679939287 a6989586621679939286 a6989586621679939285 :: TyFun [c] [d] -> Type) (a6989586621679939288 :: [c]) = ZipWith3 a6989586621679939287 a6989586621679939286 a6989586621679939285 a6989586621679939288 |
type ZipWith3Sym4 (a6989586621679939285 :: (~>) a6989586621679929485 ((~>) b6989586621679929486 ((~>) c6989586621679929487 d6989586621679929488))) (a6989586621679939286 :: [a6989586621679929485]) (a6989586621679939287 :: [b6989586621679929486]) (a6989586621679939288 :: [c6989586621679929487]) = ZipWith3 a6989586621679939285 a6989586621679939286 a6989586621679939287 a6989586621679939288 Source #
data ZipWith4Sym0 :: forall a6989586621680055636 b6989586621680055637 c6989586621680055638 d6989586621680055639 e6989586621680055640. (~>) ((~>) a6989586621680055636 ((~>) b6989586621680055637 ((~>) c6989586621680055638 ((~>) d6989586621680055639 e6989586621680055640)))) ((~>) [a6989586621680055636] ((~>) [b6989586621680055637] ((~>) [c6989586621680055638] ((~>) [d6989586621680055639] [e6989586621680055640])))) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (a6989586621680055636 ~> (b6989586621680055637 ~> (c6989586621680055638 ~> (d6989586621680055639 ~> e6989586621680055640)))) ([a6989586621680055636] ~> ([b6989586621680055637] ~> ([c6989586621680055638] ~> ([d6989586621680055639] ~> [e6989586621680055640])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym0 :: TyFun (a6989586621680055636 ~> (b6989586621680055637 ~> (c6989586621680055638 ~> (d6989586621680055639 ~> e6989586621680055640)))) ([a6989586621680055636] ~> ([b6989586621680055637] ~> ([c6989586621680055638] ~> ([d6989586621680055639] ~> [e6989586621680055640])))) -> Type) (a6989586621680068244 :: a6989586621680055636 ~> (b6989586621680055637 ~> (c6989586621680055638 ~> (d6989586621680055639 ~> e6989586621680055640)))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym0 :: TyFun (a6989586621680055636 ~> (b6989586621680055637 ~> (c6989586621680055638 ~> (d6989586621680055639 ~> e6989586621680055640)))) ([a6989586621680055636] ~> ([b6989586621680055637] ~> ([c6989586621680055638] ~> ([d6989586621680055639] ~> [e6989586621680055640])))) -> Type) (a6989586621680068244 :: a6989586621680055636 ~> (b6989586621680055637 ~> (c6989586621680055638 ~> (d6989586621680055639 ~> e6989586621680055640)))) = ZipWith4Sym1 a6989586621680068244 |
data ZipWith4Sym1 (a6989586621680068244 :: (~>) a6989586621680055636 ((~>) b6989586621680055637 ((~>) c6989586621680055638 ((~>) d6989586621680055639 e6989586621680055640)))) :: (~>) [a6989586621680055636] ((~>) [b6989586621680055637] ((~>) [c6989586621680055638] ((~>) [d6989586621680055639] [e6989586621680055640]))) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym1 a6989586621680068244 :: TyFun [a6989586621680055636] ([b6989586621680055637] ~> ([c6989586621680055638] ~> ([d6989586621680055639] ~> [e6989586621680055640]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym1 a6989586621680068244 :: TyFun [a6989586621680055636] ([b6989586621680055637] ~> ([c6989586621680055638] ~> ([d6989586621680055639] ~> [e6989586621680055640]))) -> Type) (a6989586621680068245 :: [a6989586621680055636]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym1 a6989586621680068244 :: TyFun [a6989586621680055636] ([b6989586621680055637] ~> ([c6989586621680055638] ~> ([d6989586621680055639] ~> [e6989586621680055640]))) -> Type) (a6989586621680068245 :: [a6989586621680055636]) = ZipWith4Sym2 a6989586621680068244 a6989586621680068245 |
data ZipWith4Sym2 (a6989586621680068244 :: (~>) a6989586621680055636 ((~>) b6989586621680055637 ((~>) c6989586621680055638 ((~>) d6989586621680055639 e6989586621680055640)))) (a6989586621680068245 :: [a6989586621680055636]) :: (~>) [b6989586621680055637] ((~>) [c6989586621680055638] ((~>) [d6989586621680055639] [e6989586621680055640])) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym2 a6989586621680068245 a6989586621680068244 :: TyFun [b6989586621680055637] ([c6989586621680055638] ~> ([d6989586621680055639] ~> [e6989586621680055640])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym2 a6989586621680068245 a6989586621680068244 :: TyFun [b6989586621680055637] ([c6989586621680055638] ~> ([d6989586621680055639] ~> [e6989586621680055640])) -> Type) (a6989586621680068246 :: [b6989586621680055637]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym2 a6989586621680068245 a6989586621680068244 :: TyFun [b6989586621680055637] ([c6989586621680055638] ~> ([d6989586621680055639] ~> [e6989586621680055640])) -> Type) (a6989586621680068246 :: [b6989586621680055637]) = ZipWith4Sym3 a6989586621680068245 a6989586621680068244 a6989586621680068246 |
data ZipWith4Sym3 (a6989586621680068244 :: (~>) a6989586621680055636 ((~>) b6989586621680055637 ((~>) c6989586621680055638 ((~>) d6989586621680055639 e6989586621680055640)))) (a6989586621680068245 :: [a6989586621680055636]) (a6989586621680068246 :: [b6989586621680055637]) :: (~>) [c6989586621680055638] ((~>) [d6989586621680055639] [e6989586621680055640]) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym3 a6989586621680068246 a6989586621680068245 a6989586621680068244 :: TyFun [c6989586621680055638] ([d6989586621680055639] ~> [e6989586621680055640]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym3 a6989586621680068246 a6989586621680068245 a6989586621680068244 :: TyFun [c6989586621680055638] ([d6989586621680055639] ~> [e6989586621680055640]) -> Type) (a6989586621680068247 :: [c6989586621680055638]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym3 a6989586621680068246 a6989586621680068245 a6989586621680068244 :: TyFun [c6989586621680055638] ([d6989586621680055639] ~> [e6989586621680055640]) -> Type) (a6989586621680068247 :: [c6989586621680055638]) = ZipWith4Sym4 a6989586621680068246 a6989586621680068245 a6989586621680068244 a6989586621680068247 |
data ZipWith4Sym4 (a6989586621680068244 :: (~>) a6989586621680055636 ((~>) b6989586621680055637 ((~>) c6989586621680055638 ((~>) d6989586621680055639 e6989586621680055640)))) (a6989586621680068245 :: [a6989586621680055636]) (a6989586621680068246 :: [b6989586621680055637]) (a6989586621680068247 :: [c6989586621680055638]) :: (~>) [d6989586621680055639] [e6989586621680055640] Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym4 a6989586621680068247 a6989586621680068246 a6989586621680068245 a6989586621680068244 :: TyFun [d6989586621680055639] [e6989586621680055640] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym4 a6989586621680068247 a6989586621680068246 a6989586621680068245 a6989586621680068244 :: TyFun [d] [e] -> Type) (a6989586621680068248 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym4 a6989586621680068247 a6989586621680068246 a6989586621680068245 a6989586621680068244 :: TyFun [d] [e] -> Type) (a6989586621680068248 :: [d]) = ZipWith4 a6989586621680068247 a6989586621680068246 a6989586621680068245 a6989586621680068244 a6989586621680068248 |
type ZipWith4Sym5 (a6989586621680068244 :: (~>) a6989586621680055636 ((~>) b6989586621680055637 ((~>) c6989586621680055638 ((~>) d6989586621680055639 e6989586621680055640)))) (a6989586621680068245 :: [a6989586621680055636]) (a6989586621680068246 :: [b6989586621680055637]) (a6989586621680068247 :: [c6989586621680055638]) (a6989586621680068248 :: [d6989586621680055639]) = ZipWith4 a6989586621680068244 a6989586621680068245 a6989586621680068246 a6989586621680068247 a6989586621680068248 Source #
data ZipWith5Sym0 :: forall a6989586621680055630 b6989586621680055631 c6989586621680055632 d6989586621680055633 e6989586621680055634 f6989586621680055635. (~>) ((~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) ((~>) [a6989586621680055630] ((~>) [b6989586621680055631] ((~>) [c6989586621680055632] ((~>) [d6989586621680055633] ((~>) [e6989586621680055634] [f6989586621680055635]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (a6989586621680055630 ~> (b6989586621680055631 ~> (c6989586621680055632 ~> (d6989586621680055633 ~> (e6989586621680055634 ~> f6989586621680055635))))) ([a6989586621680055630] ~> ([b6989586621680055631] ~> ([c6989586621680055632] ~> ([d6989586621680055633] ~> ([e6989586621680055634] ~> [f6989586621680055635]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym0 :: TyFun (a6989586621680055630 ~> (b6989586621680055631 ~> (c6989586621680055632 ~> (d6989586621680055633 ~> (e6989586621680055634 ~> f6989586621680055635))))) ([a6989586621680055630] ~> ([b6989586621680055631] ~> ([c6989586621680055632] ~> ([d6989586621680055633] ~> ([e6989586621680055634] ~> [f6989586621680055635]))))) -> Type) (a6989586621680068221 :: a6989586621680055630 ~> (b6989586621680055631 ~> (c6989586621680055632 ~> (d6989586621680055633 ~> (e6989586621680055634 ~> f6989586621680055635))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym0 :: TyFun (a6989586621680055630 ~> (b6989586621680055631 ~> (c6989586621680055632 ~> (d6989586621680055633 ~> (e6989586621680055634 ~> f6989586621680055635))))) ([a6989586621680055630] ~> ([b6989586621680055631] ~> ([c6989586621680055632] ~> ([d6989586621680055633] ~> ([e6989586621680055634] ~> [f6989586621680055635]))))) -> Type) (a6989586621680068221 :: a6989586621680055630 ~> (b6989586621680055631 ~> (c6989586621680055632 ~> (d6989586621680055633 ~> (e6989586621680055634 ~> f6989586621680055635))))) = ZipWith5Sym1 a6989586621680068221 |
data ZipWith5Sym1 (a6989586621680068221 :: (~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) :: (~>) [a6989586621680055630] ((~>) [b6989586621680055631] ((~>) [c6989586621680055632] ((~>) [d6989586621680055633] ((~>) [e6989586621680055634] [f6989586621680055635])))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym1 a6989586621680068221 :: TyFun [a6989586621680055630] ([b6989586621680055631] ~> ([c6989586621680055632] ~> ([d6989586621680055633] ~> ([e6989586621680055634] ~> [f6989586621680055635])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym1 a6989586621680068221 :: TyFun [a6989586621680055630] ([b6989586621680055631] ~> ([c6989586621680055632] ~> ([d6989586621680055633] ~> ([e6989586621680055634] ~> [f6989586621680055635])))) -> Type) (a6989586621680068222 :: [a6989586621680055630]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym1 a6989586621680068221 :: TyFun [a6989586621680055630] ([b6989586621680055631] ~> ([c6989586621680055632] ~> ([d6989586621680055633] ~> ([e6989586621680055634] ~> [f6989586621680055635])))) -> Type) (a6989586621680068222 :: [a6989586621680055630]) = ZipWith5Sym2 a6989586621680068221 a6989586621680068222 |
data ZipWith5Sym2 (a6989586621680068221 :: (~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) (a6989586621680068222 :: [a6989586621680055630]) :: (~>) [b6989586621680055631] ((~>) [c6989586621680055632] ((~>) [d6989586621680055633] ((~>) [e6989586621680055634] [f6989586621680055635]))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym2 a6989586621680068222 a6989586621680068221 :: TyFun [b6989586621680055631] ([c6989586621680055632] ~> ([d6989586621680055633] ~> ([e6989586621680055634] ~> [f6989586621680055635]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym2 a6989586621680068222 a6989586621680068221 :: TyFun [b6989586621680055631] ([c6989586621680055632] ~> ([d6989586621680055633] ~> ([e6989586621680055634] ~> [f6989586621680055635]))) -> Type) (a6989586621680068223 :: [b6989586621680055631]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym2 a6989586621680068222 a6989586621680068221 :: TyFun [b6989586621680055631] ([c6989586621680055632] ~> ([d6989586621680055633] ~> ([e6989586621680055634] ~> [f6989586621680055635]))) -> Type) (a6989586621680068223 :: [b6989586621680055631]) = ZipWith5Sym3 a6989586621680068222 a6989586621680068221 a6989586621680068223 |
data ZipWith5Sym3 (a6989586621680068221 :: (~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) (a6989586621680068222 :: [a6989586621680055630]) (a6989586621680068223 :: [b6989586621680055631]) :: (~>) [c6989586621680055632] ((~>) [d6989586621680055633] ((~>) [e6989586621680055634] [f6989586621680055635])) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym3 a6989586621680068223 a6989586621680068222 a6989586621680068221 :: TyFun [c6989586621680055632] ([d6989586621680055633] ~> ([e6989586621680055634] ~> [f6989586621680055635])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym3 a6989586621680068223 a6989586621680068222 a6989586621680068221 :: TyFun [c6989586621680055632] ([d6989586621680055633] ~> ([e6989586621680055634] ~> [f6989586621680055635])) -> Type) (a6989586621680068224 :: [c6989586621680055632]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym3 a6989586621680068223 a6989586621680068222 a6989586621680068221 :: TyFun [c6989586621680055632] ([d6989586621680055633] ~> ([e6989586621680055634] ~> [f6989586621680055635])) -> Type) (a6989586621680068224 :: [c6989586621680055632]) = ZipWith5Sym4 a6989586621680068223 a6989586621680068222 a6989586621680068221 a6989586621680068224 |
data ZipWith5Sym4 (a6989586621680068221 :: (~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) (a6989586621680068222 :: [a6989586621680055630]) (a6989586621680068223 :: [b6989586621680055631]) (a6989586621680068224 :: [c6989586621680055632]) :: (~>) [d6989586621680055633] ((~>) [e6989586621680055634] [f6989586621680055635]) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym4 a6989586621680068224 a6989586621680068223 a6989586621680068222 a6989586621680068221 :: TyFun [d6989586621680055633] ([e6989586621680055634] ~> [f6989586621680055635]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym4 a6989586621680068224 a6989586621680068223 a6989586621680068222 a6989586621680068221 :: TyFun [d6989586621680055633] ([e6989586621680055634] ~> [f6989586621680055635]) -> Type) (a6989586621680068225 :: [d6989586621680055633]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym4 a6989586621680068224 a6989586621680068223 a6989586621680068222 a6989586621680068221 :: TyFun [d6989586621680055633] ([e6989586621680055634] ~> [f6989586621680055635]) -> Type) (a6989586621680068225 :: [d6989586621680055633]) = ZipWith5Sym5 a6989586621680068224 a6989586621680068223 a6989586621680068222 a6989586621680068221 a6989586621680068225 |
data ZipWith5Sym5 (a6989586621680068221 :: (~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) (a6989586621680068222 :: [a6989586621680055630]) (a6989586621680068223 :: [b6989586621680055631]) (a6989586621680068224 :: [c6989586621680055632]) (a6989586621680068225 :: [d6989586621680055633]) :: (~>) [e6989586621680055634] [f6989586621680055635] Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym5 a6989586621680068225 a6989586621680068224 a6989586621680068223 a6989586621680068222 a6989586621680068221 :: TyFun [e6989586621680055634] [f6989586621680055635] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym5 a6989586621680068225 a6989586621680068224 a6989586621680068223 a6989586621680068222 a6989586621680068221 :: TyFun [e] [f] -> Type) (a6989586621680068226 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym5 a6989586621680068225 a6989586621680068224 a6989586621680068223 a6989586621680068222 a6989586621680068221 :: TyFun [e] [f] -> Type) (a6989586621680068226 :: [e]) = ZipWith5 a6989586621680068225 a6989586621680068224 a6989586621680068223 a6989586621680068222 a6989586621680068221 a6989586621680068226 |
type ZipWith5Sym6 (a6989586621680068221 :: (~>) a6989586621680055630 ((~>) b6989586621680055631 ((~>) c6989586621680055632 ((~>) d6989586621680055633 ((~>) e6989586621680055634 f6989586621680055635))))) (a6989586621680068222 :: [a6989586621680055630]) (a6989586621680068223 :: [b6989586621680055631]) (a6989586621680068224 :: [c6989586621680055632]) (a6989586621680068225 :: [d6989586621680055633]) (a6989586621680068226 :: [e6989586621680055634]) = ZipWith5 a6989586621680068221 a6989586621680068222 a6989586621680068223 a6989586621680068224 a6989586621680068225 a6989586621680068226 Source #
data ZipWith6Sym0 :: forall a6989586621680055623 b6989586621680055624 c6989586621680055625 d6989586621680055626 e6989586621680055627 f6989586621680055628 g6989586621680055629. (~>) ((~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) ((~>) [a6989586621680055623] ((~>) [b6989586621680055624] ((~>) [c6989586621680055625] ((~>) [d6989586621680055626] ((~>) [e6989586621680055627] ((~>) [f6989586621680055628] [g6989586621680055629])))))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (a6989586621680055623 ~> (b6989586621680055624 ~> (c6989586621680055625 ~> (d6989586621680055626 ~> (e6989586621680055627 ~> (f6989586621680055628 ~> g6989586621680055629)))))) ([a6989586621680055623] ~> ([b6989586621680055624] ~> ([c6989586621680055625] ~> ([d6989586621680055626] ~> ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym0 :: TyFun (a6989586621680055623 ~> (b6989586621680055624 ~> (c6989586621680055625 ~> (d6989586621680055626 ~> (e6989586621680055627 ~> (f6989586621680055628 ~> g6989586621680055629)))))) ([a6989586621680055623] ~> ([b6989586621680055624] ~> ([c6989586621680055625] ~> ([d6989586621680055626] ~> ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629])))))) -> Type) (a6989586621680068194 :: a6989586621680055623 ~> (b6989586621680055624 ~> (c6989586621680055625 ~> (d6989586621680055626 ~> (e6989586621680055627 ~> (f6989586621680055628 ~> g6989586621680055629)))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym0 :: TyFun (a6989586621680055623 ~> (b6989586621680055624 ~> (c6989586621680055625 ~> (d6989586621680055626 ~> (e6989586621680055627 ~> (f6989586621680055628 ~> g6989586621680055629)))))) ([a6989586621680055623] ~> ([b6989586621680055624] ~> ([c6989586621680055625] ~> ([d6989586621680055626] ~> ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629])))))) -> Type) (a6989586621680068194 :: a6989586621680055623 ~> (b6989586621680055624 ~> (c6989586621680055625 ~> (d6989586621680055626 ~> (e6989586621680055627 ~> (f6989586621680055628 ~> g6989586621680055629)))))) = ZipWith6Sym1 a6989586621680068194 |
data ZipWith6Sym1 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) :: (~>) [a6989586621680055623] ((~>) [b6989586621680055624] ((~>) [c6989586621680055625] ((~>) [d6989586621680055626] ((~>) [e6989586621680055627] ((~>) [f6989586621680055628] [g6989586621680055629]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym1 a6989586621680068194 :: TyFun [a6989586621680055623] ([b6989586621680055624] ~> ([c6989586621680055625] ~> ([d6989586621680055626] ~> ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym1 a6989586621680068194 :: TyFun [a6989586621680055623] ([b6989586621680055624] ~> ([c6989586621680055625] ~> ([d6989586621680055626] ~> ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629]))))) -> Type) (a6989586621680068195 :: [a6989586621680055623]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym1 a6989586621680068194 :: TyFun [a6989586621680055623] ([b6989586621680055624] ~> ([c6989586621680055625] ~> ([d6989586621680055626] ~> ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629]))))) -> Type) (a6989586621680068195 :: [a6989586621680055623]) = ZipWith6Sym2 a6989586621680068194 a6989586621680068195 |
data ZipWith6Sym2 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) (a6989586621680068195 :: [a6989586621680055623]) :: (~>) [b6989586621680055624] ((~>) [c6989586621680055625] ((~>) [d6989586621680055626] ((~>) [e6989586621680055627] ((~>) [f6989586621680055628] [g6989586621680055629])))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym2 a6989586621680068195 a6989586621680068194 :: TyFun [b6989586621680055624] ([c6989586621680055625] ~> ([d6989586621680055626] ~> ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym2 a6989586621680068195 a6989586621680068194 :: TyFun [b6989586621680055624] ([c6989586621680055625] ~> ([d6989586621680055626] ~> ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629])))) -> Type) (a6989586621680068196 :: [b6989586621680055624]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym2 a6989586621680068195 a6989586621680068194 :: TyFun [b6989586621680055624] ([c6989586621680055625] ~> ([d6989586621680055626] ~> ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629])))) -> Type) (a6989586621680068196 :: [b6989586621680055624]) = ZipWith6Sym3 a6989586621680068195 a6989586621680068194 a6989586621680068196 |
data ZipWith6Sym3 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) (a6989586621680068195 :: [a6989586621680055623]) (a6989586621680068196 :: [b6989586621680055624]) :: (~>) [c6989586621680055625] ((~>) [d6989586621680055626] ((~>) [e6989586621680055627] ((~>) [f6989586621680055628] [g6989586621680055629]))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym3 a6989586621680068196 a6989586621680068195 a6989586621680068194 :: TyFun [c6989586621680055625] ([d6989586621680055626] ~> ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym3 a6989586621680068196 a6989586621680068195 a6989586621680068194 :: TyFun [c6989586621680055625] ([d6989586621680055626] ~> ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629]))) -> Type) (a6989586621680068197 :: [c6989586621680055625]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym3 a6989586621680068196 a6989586621680068195 a6989586621680068194 :: TyFun [c6989586621680055625] ([d6989586621680055626] ~> ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629]))) -> Type) (a6989586621680068197 :: [c6989586621680055625]) = ZipWith6Sym4 a6989586621680068196 a6989586621680068195 a6989586621680068194 a6989586621680068197 |
data ZipWith6Sym4 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) (a6989586621680068195 :: [a6989586621680055623]) (a6989586621680068196 :: [b6989586621680055624]) (a6989586621680068197 :: [c6989586621680055625]) :: (~>) [d6989586621680055626] ((~>) [e6989586621680055627] ((~>) [f6989586621680055628] [g6989586621680055629])) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym4 a6989586621680068197 a6989586621680068196 a6989586621680068195 a6989586621680068194 :: TyFun [d6989586621680055626] ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym4 a6989586621680068197 a6989586621680068196 a6989586621680068195 a6989586621680068194 :: TyFun [d6989586621680055626] ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629])) -> Type) (a6989586621680068198 :: [d6989586621680055626]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym4 a6989586621680068197 a6989586621680068196 a6989586621680068195 a6989586621680068194 :: TyFun [d6989586621680055626] ([e6989586621680055627] ~> ([f6989586621680055628] ~> [g6989586621680055629])) -> Type) (a6989586621680068198 :: [d6989586621680055626]) = ZipWith6Sym5 a6989586621680068197 a6989586621680068196 a6989586621680068195 a6989586621680068194 a6989586621680068198 |
data ZipWith6Sym5 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) (a6989586621680068195 :: [a6989586621680055623]) (a6989586621680068196 :: [b6989586621680055624]) (a6989586621680068197 :: [c6989586621680055625]) (a6989586621680068198 :: [d6989586621680055626]) :: (~>) [e6989586621680055627] ((~>) [f6989586621680055628] [g6989586621680055629]) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym5 a6989586621680068198 a6989586621680068197 a6989586621680068196 a6989586621680068195 a6989586621680068194 :: TyFun [e6989586621680055627] ([f6989586621680055628] ~> [g6989586621680055629]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym5 a6989586621680068198 a6989586621680068197 a6989586621680068196 a6989586621680068195 a6989586621680068194 :: TyFun [e6989586621680055627] ([f6989586621680055628] ~> [g6989586621680055629]) -> Type) (a6989586621680068199 :: [e6989586621680055627]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym5 a6989586621680068198 a6989586621680068197 a6989586621680068196 a6989586621680068195 a6989586621680068194 :: TyFun [e6989586621680055627] ([f6989586621680055628] ~> [g6989586621680055629]) -> Type) (a6989586621680068199 :: [e6989586621680055627]) = ZipWith6Sym6 a6989586621680068198 a6989586621680068197 a6989586621680068196 a6989586621680068195 a6989586621680068194 a6989586621680068199 |
data ZipWith6Sym6 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) (a6989586621680068195 :: [a6989586621680055623]) (a6989586621680068196 :: [b6989586621680055624]) (a6989586621680068197 :: [c6989586621680055625]) (a6989586621680068198 :: [d6989586621680055626]) (a6989586621680068199 :: [e6989586621680055627]) :: (~>) [f6989586621680055628] [g6989586621680055629] Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym6 a6989586621680068199 a6989586621680068198 a6989586621680068197 a6989586621680068196 a6989586621680068195 a6989586621680068194 :: TyFun [f6989586621680055628] [g6989586621680055629] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym6 a6989586621680068199 a6989586621680068198 a6989586621680068197 a6989586621680068196 a6989586621680068195 a6989586621680068194 :: TyFun [f] [g] -> Type) (a6989586621680068200 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym6 a6989586621680068199 a6989586621680068198 a6989586621680068197 a6989586621680068196 a6989586621680068195 a6989586621680068194 :: TyFun [f] [g] -> Type) (a6989586621680068200 :: [f]) = ZipWith6 a6989586621680068199 a6989586621680068198 a6989586621680068197 a6989586621680068196 a6989586621680068195 a6989586621680068194 a6989586621680068200 |
type ZipWith6Sym7 (a6989586621680068194 :: (~>) a6989586621680055623 ((~>) b6989586621680055624 ((~>) c6989586621680055625 ((~>) d6989586621680055626 ((~>) e6989586621680055627 ((~>) f6989586621680055628 g6989586621680055629)))))) (a6989586621680068195 :: [a6989586621680055623]) (a6989586621680068196 :: [b6989586621680055624]) (a6989586621680068197 :: [c6989586621680055625]) (a6989586621680068198 :: [d6989586621680055626]) (a6989586621680068199 :: [e6989586621680055627]) (a6989586621680068200 :: [f6989586621680055628]) = ZipWith6 a6989586621680068194 a6989586621680068195 a6989586621680068196 a6989586621680068197 a6989586621680068198 a6989586621680068199 a6989586621680068200 Source #
data ZipWith7Sym0 :: forall a6989586621680055615 b6989586621680055616 c6989586621680055617 d6989586621680055618 e6989586621680055619 f6989586621680055620 g6989586621680055621 h6989586621680055622. (~>) ((~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) ((~>) [a6989586621680055615] ((~>) [b6989586621680055616] ((~>) [c6989586621680055617] ((~>) [d6989586621680055618] ((~>) [e6989586621680055619] ((~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622]))))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym0 :: TyFun (a6989586621680055615 ~> (b6989586621680055616 ~> (c6989586621680055617 ~> (d6989586621680055618 ~> (e6989586621680055619 ~> (f6989586621680055620 ~> (g6989586621680055621 ~> h6989586621680055622))))))) ([a6989586621680055615] ~> ([b6989586621680055616] ~> ([c6989586621680055617] ~> ([d6989586621680055618] ~> ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622]))))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym0 :: TyFun (a6989586621680055615 ~> (b6989586621680055616 ~> (c6989586621680055617 ~> (d6989586621680055618 ~> (e6989586621680055619 ~> (f6989586621680055620 ~> (g6989586621680055621 ~> h6989586621680055622))))))) ([a6989586621680055615] ~> ([b6989586621680055616] ~> ([c6989586621680055617] ~> ([d6989586621680055618] ~> ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622]))))))) -> Type) (a6989586621680068163 :: a6989586621680055615 ~> (b6989586621680055616 ~> (c6989586621680055617 ~> (d6989586621680055618 ~> (e6989586621680055619 ~> (f6989586621680055620 ~> (g6989586621680055621 ~> h6989586621680055622))))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym0 :: TyFun (a6989586621680055615 ~> (b6989586621680055616 ~> (c6989586621680055617 ~> (d6989586621680055618 ~> (e6989586621680055619 ~> (f6989586621680055620 ~> (g6989586621680055621 ~> h6989586621680055622))))))) ([a6989586621680055615] ~> ([b6989586621680055616] ~> ([c6989586621680055617] ~> ([d6989586621680055618] ~> ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622]))))))) -> Type) (a6989586621680068163 :: a6989586621680055615 ~> (b6989586621680055616 ~> (c6989586621680055617 ~> (d6989586621680055618 ~> (e6989586621680055619 ~> (f6989586621680055620 ~> (g6989586621680055621 ~> h6989586621680055622))))))) = ZipWith7Sym1 a6989586621680068163 |
data ZipWith7Sym1 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) :: (~>) [a6989586621680055615] ((~>) [b6989586621680055616] ((~>) [c6989586621680055617] ((~>) [d6989586621680055618] ((~>) [e6989586621680055619] ((~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622])))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym1 a6989586621680068163 :: TyFun [a6989586621680055615] ([b6989586621680055616] ~> ([c6989586621680055617] ~> ([d6989586621680055618] ~> ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym1 a6989586621680068163 :: TyFun [a6989586621680055615] ([b6989586621680055616] ~> ([c6989586621680055617] ~> ([d6989586621680055618] ~> ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622])))))) -> Type) (a6989586621680068164 :: [a6989586621680055615]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym1 a6989586621680068163 :: TyFun [a6989586621680055615] ([b6989586621680055616] ~> ([c6989586621680055617] ~> ([d6989586621680055618] ~> ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622])))))) -> Type) (a6989586621680068164 :: [a6989586621680055615]) = ZipWith7Sym2 a6989586621680068163 a6989586621680068164 |
data ZipWith7Sym2 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) :: (~>) [b6989586621680055616] ((~>) [c6989586621680055617] ((~>) [d6989586621680055618] ((~>) [e6989586621680055619] ((~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym2 a6989586621680068164 a6989586621680068163 :: TyFun [b6989586621680055616] ([c6989586621680055617] ~> ([d6989586621680055618] ~> ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym2 a6989586621680068164 a6989586621680068163 :: TyFun [b6989586621680055616] ([c6989586621680055617] ~> ([d6989586621680055618] ~> ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622]))))) -> Type) (a6989586621680068165 :: [b6989586621680055616]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym2 a6989586621680068164 a6989586621680068163 :: TyFun [b6989586621680055616] ([c6989586621680055617] ~> ([d6989586621680055618] ~> ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622]))))) -> Type) (a6989586621680068165 :: [b6989586621680055616]) = ZipWith7Sym3 a6989586621680068164 a6989586621680068163 a6989586621680068165 |
data ZipWith7Sym3 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) (a6989586621680068165 :: [b6989586621680055616]) :: (~>) [c6989586621680055617] ((~>) [d6989586621680055618] ((~>) [e6989586621680055619] ((~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622])))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym3 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [c6989586621680055617] ([d6989586621680055618] ~> ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym3 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [c6989586621680055617] ([d6989586621680055618] ~> ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622])))) -> Type) (a6989586621680068166 :: [c6989586621680055617]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym3 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [c6989586621680055617] ([d6989586621680055618] ~> ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622])))) -> Type) (a6989586621680068166 :: [c6989586621680055617]) = ZipWith7Sym4 a6989586621680068165 a6989586621680068164 a6989586621680068163 a6989586621680068166 |
data ZipWith7Sym4 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) (a6989586621680068165 :: [b6989586621680055616]) (a6989586621680068166 :: [c6989586621680055617]) :: (~>) [d6989586621680055618] ((~>) [e6989586621680055619] ((~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622]))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym4 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [d6989586621680055618] ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym4 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [d6989586621680055618] ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622]))) -> Type) (a6989586621680068167 :: [d6989586621680055618]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym4 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [d6989586621680055618] ([e6989586621680055619] ~> ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622]))) -> Type) (a6989586621680068167 :: [d6989586621680055618]) = ZipWith7Sym5 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 a6989586621680068167 |
data ZipWith7Sym5 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) (a6989586621680068165 :: [b6989586621680055616]) (a6989586621680068166 :: [c6989586621680055617]) (a6989586621680068167 :: [d6989586621680055618]) :: (~>) [e6989586621680055619] ((~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622])) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym5 a6989586621680068167 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [e6989586621680055619] ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym5 a6989586621680068167 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [e6989586621680055619] ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622])) -> Type) (a6989586621680068168 :: [e6989586621680055619]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym5 a6989586621680068167 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [e6989586621680055619] ([f6989586621680055620] ~> ([g6989586621680055621] ~> [h6989586621680055622])) -> Type) (a6989586621680068168 :: [e6989586621680055619]) = ZipWith7Sym6 a6989586621680068167 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 a6989586621680068168 |
data ZipWith7Sym6 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) (a6989586621680068165 :: [b6989586621680055616]) (a6989586621680068166 :: [c6989586621680055617]) (a6989586621680068167 :: [d6989586621680055618]) (a6989586621680068168 :: [e6989586621680055619]) :: (~>) [f6989586621680055620] ((~>) [g6989586621680055621] [h6989586621680055622]) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym6 a6989586621680068168 a6989586621680068167 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [f6989586621680055620] ([g6989586621680055621] ~> [h6989586621680055622]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym6 a6989586621680068168 a6989586621680068167 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [f6989586621680055620] ([g6989586621680055621] ~> [h6989586621680055622]) -> Type) (a6989586621680068169 :: [f6989586621680055620]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym6 a6989586621680068168 a6989586621680068167 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [f6989586621680055620] ([g6989586621680055621] ~> [h6989586621680055622]) -> Type) (a6989586621680068169 :: [f6989586621680055620]) = ZipWith7Sym7 a6989586621680068168 a6989586621680068167 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 a6989586621680068169 |
data ZipWith7Sym7 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) (a6989586621680068165 :: [b6989586621680055616]) (a6989586621680068166 :: [c6989586621680055617]) (a6989586621680068167 :: [d6989586621680055618]) (a6989586621680068168 :: [e6989586621680055619]) (a6989586621680068169 :: [f6989586621680055620]) :: (~>) [g6989586621680055621] [h6989586621680055622] Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym7 a6989586621680068169 a6989586621680068168 a6989586621680068167 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [g6989586621680055621] [h6989586621680055622] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym7 a6989586621680068169 a6989586621680068168 a6989586621680068167 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [g] [h] -> Type) (a6989586621680068170 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym7 a6989586621680068169 a6989586621680068168 a6989586621680068167 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 :: TyFun [g] [h] -> Type) (a6989586621680068170 :: [g]) = ZipWith7 a6989586621680068169 a6989586621680068168 a6989586621680068167 a6989586621680068166 a6989586621680068165 a6989586621680068164 a6989586621680068163 a6989586621680068170 |
type ZipWith7Sym8 (a6989586621680068163 :: (~>) a6989586621680055615 ((~>) b6989586621680055616 ((~>) c6989586621680055617 ((~>) d6989586621680055618 ((~>) e6989586621680055619 ((~>) f6989586621680055620 ((~>) g6989586621680055621 h6989586621680055622))))))) (a6989586621680068164 :: [a6989586621680055615]) (a6989586621680068165 :: [b6989586621680055616]) (a6989586621680068166 :: [c6989586621680055617]) (a6989586621680068167 :: [d6989586621680055618]) (a6989586621680068168 :: [e6989586621680055619]) (a6989586621680068169 :: [f6989586621680055620]) (a6989586621680068170 :: [g6989586621680055621]) = ZipWith7 a6989586621680068163 a6989586621680068164 a6989586621680068165 a6989586621680068166 a6989586621680068167 a6989586621680068168 a6989586621680068169 a6989586621680068170 Source #
data UnzipSym0 :: forall a6989586621679929483 b6989586621679929484. (~>) [(a6989586621679929483, b6989586621679929484)] ([a6989586621679929483], [b6989586621679929484]) Source #
Instances
SingI (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # | |
SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a6989586621679929483, b6989586621679929484)] ([a6989586621679929483], [b6989586621679929484]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679939266 :: [(a, b)]) Source # | |
type UnzipSym1 (a6989586621679939266 :: [(a6989586621679929483, b6989586621679929484)]) = Unzip a6989586621679939266 Source #
data Unzip3Sym0 :: forall a6989586621679929480 b6989586621679929481 c6989586621679929482. (~>) [(a6989586621679929480, b6989586621679929481, c6989586621679929482)] ([a6989586621679929480], [b6989586621679929481], [c6989586621679929482]) 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 [(a6989586621679929480, b6989586621679929481, c6989586621679929482)] ([a6989586621679929480], [b6989586621679929481], [c6989586621679929482]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679939245 :: [(a, b, c)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679939245 :: [(a, b, c)]) = Unzip3 a6989586621679939245 |
type Unzip3Sym1 (a6989586621679939245 :: [(a6989586621679929480, b6989586621679929481, c6989586621679929482)]) = Unzip3 a6989586621679939245 Source #
data Unzip4Sym0 :: forall a6989586621679929476 b6989586621679929477 c6989586621679929478 d6989586621679929479. (~>) [(a6989586621679929476, b6989586621679929477, c6989586621679929478, d6989586621679929479)] ([a6989586621679929476], [b6989586621679929477], [c6989586621679929478], [d6989586621679929479]) 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 [(a6989586621679929476, b6989586621679929477, c6989586621679929478, d6989586621679929479)] ([a6989586621679929476], [b6989586621679929477], [c6989586621679929478], [d6989586621679929479]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679939222 :: [(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) (a6989586621679939222 :: [(a, b, c, d)]) = Unzip4 a6989586621679939222 |
type Unzip4Sym1 (a6989586621679939222 :: [(a6989586621679929476, b6989586621679929477, c6989586621679929478, d6989586621679929479)]) = Unzip4 a6989586621679939222 Source #
data Unzip5Sym0 :: forall a6989586621679929471 b6989586621679929472 c6989586621679929473 d6989586621679929474 e6989586621679929475. (~>) [(a6989586621679929471, b6989586621679929472, c6989586621679929473, d6989586621679929474, e6989586621679929475)] ([a6989586621679929471], [b6989586621679929472], [c6989586621679929473], [d6989586621679929474], [e6989586621679929475]) 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 [(a6989586621679929471, b6989586621679929472, c6989586621679929473, d6989586621679929474, e6989586621679929475)] ([a6989586621679929471], [b6989586621679929472], [c6989586621679929473], [d6989586621679929474], [e6989586621679929475]) -> 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) (a6989586621679939197 :: [(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) (a6989586621679939197 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679939197 |
type Unzip5Sym1 (a6989586621679939197 :: [(a6989586621679929471, b6989586621679929472, c6989586621679929473, d6989586621679929474, e6989586621679929475)]) = Unzip5 a6989586621679939197 Source #
data Unzip6Sym0 :: forall a6989586621679929465 b6989586621679929466 c6989586621679929467 d6989586621679929468 e6989586621679929469 f6989586621679929470. (~>) [(a6989586621679929465, b6989586621679929466, c6989586621679929467, d6989586621679929468, e6989586621679929469, f6989586621679929470)] ([a6989586621679929465], [b6989586621679929466], [c6989586621679929467], [d6989586621679929468], [e6989586621679929469], [f6989586621679929470]) 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 [(a6989586621679929465, b6989586621679929466, c6989586621679929467, d6989586621679929468, e6989586621679929469, f6989586621679929470)] ([a6989586621679929465], [b6989586621679929466], [c6989586621679929467], [d6989586621679929468], [e6989586621679929469], [f6989586621679929470]) -> 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) (a6989586621679939170 :: [(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) (a6989586621679939170 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679939170 |
type Unzip6Sym1 (a6989586621679939170 :: [(a6989586621679929465, b6989586621679929466, c6989586621679929467, d6989586621679929468, e6989586621679929469, f6989586621679929470)]) = Unzip6 a6989586621679939170 Source #
data Unzip7Sym0 :: forall a6989586621679929458 b6989586621679929459 c6989586621679929460 d6989586621679929461 e6989586621679929462 f6989586621679929463 g6989586621679929464. (~>) [(a6989586621679929458, b6989586621679929459, c6989586621679929460, d6989586621679929461, e6989586621679929462, f6989586621679929463, g6989586621679929464)] ([a6989586621679929458], [b6989586621679929459], [c6989586621679929460], [d6989586621679929461], [e6989586621679929462], [f6989586621679929463], [g6989586621679929464]) 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 [(a6989586621679929458, b6989586621679929459, c6989586621679929460, d6989586621679929461, e6989586621679929462, f6989586621679929463, g6989586621679929464)] ([a6989586621679929458], [b6989586621679929459], [c6989586621679929460], [d6989586621679929461], [e6989586621679929462], [f6989586621679929463], [g6989586621679929464]) -> 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) (a6989586621679939141 :: [(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) (a6989586621679939141 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679939141 |
type Unzip7Sym1 (a6989586621679939141 :: [(a6989586621679929458, b6989586621679929459, c6989586621679929460, d6989586621679929461, e6989586621679929462, f6989586621679929463, g6989586621679929464)]) = Unzip7 a6989586621679939141 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 (a6989586621679939137 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnlinesSym1 (a6989586621679939137 :: [Symbol]) = Unlines a6989586621679939137 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 (a6989586621679939126 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnwordsSym1 (a6989586621679939126 :: [Symbol]) = Unwords a6989586621679939126 Source #
data NubSym0 :: forall a6989586621679929417. (~>) [a6989586621679929417] [a6989586621679929417] Source #
Instances
SEq a => SingI (NubSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (NubSym0 :: TyFun [a6989586621679929417] [a6989586621679929417] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (NubSym0 :: TyFun [a] [a] -> Type) (a6989586621679939395 :: [a]) Source # | |
data DeleteSym0 :: forall a6989586621679929457. (~>) a6989586621679929457 ((~>) [a6989586621679929457] [a6989586621679929457]) 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 a6989586621679929457 ([a6989586621679929457] ~> [a6989586621679929457]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym0 :: TyFun a6989586621679929457 ([a6989586621679929457] ~> [a6989586621679929457]) -> Type) (a6989586621679939110 :: a6989586621679929457) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym0 :: TyFun a6989586621679929457 ([a6989586621679929457] ~> [a6989586621679929457]) -> Type) (a6989586621679939110 :: a6989586621679929457) = DeleteSym1 a6989586621679939110 |
data DeleteSym1 (a6989586621679939110 :: a6989586621679929457) :: (~>) [a6989586621679929457] [a6989586621679929457] 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 a6989586621679939110 :: TyFun [a6989586621679929457] [a6989586621679929457] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym1 a6989586621679939110 :: TyFun [a] [a] -> Type) (a6989586621679939111 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym1 a6989586621679939110 :: TyFun [a] [a] -> Type) (a6989586621679939111 :: [a]) = Delete a6989586621679939110 a6989586621679939111 |
type DeleteSym2 (a6989586621679939110 :: a6989586621679929457) (a6989586621679939111 :: [a6989586621679929457]) = Delete a6989586621679939110 a6989586621679939111 Source #
data (\\@#@$) :: forall a6989586621679929456. (~>) [a6989586621679929456] ((~>) [a6989586621679929456] [a6989586621679929456]) infix 5 Source #
Instances
SEq a => SingI ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((\\@#@$) :: TyFun [a6989586621679929456] ([a6989586621679929456] ~> [a6989586621679929456]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$) :: TyFun [a6989586621679929456] ([a6989586621679929456] ~> [a6989586621679929456]) -> Type) (a6989586621679939120 :: [a6989586621679929456]) Source # | |
data (\\@#@$$) (a6989586621679939120 :: [a6989586621679929456]) :: (~>) [a6989586621679929456] [a6989586621679929456] infix 5 Source #
Instances
(SEq a, SingI d) => SingI ((\\@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((\\@#@$$) a6989586621679939120 :: TyFun [a6989586621679929456] [a6989586621679929456] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$$) a6989586621679939120 :: TyFun [a] [a] -> Type) (a6989586621679939121 :: [a]) Source # | |
type (\\@#@$$$) (a6989586621679939120 :: [a6989586621679929456]) (a6989586621679939121 :: [a6989586621679929456]) = (\\) a6989586621679939120 a6989586621679939121 Source #
data UnionSym0 :: forall a6989586621679929413. (~>) [a6989586621679929413] ((~>) [a6989586621679929413] [a6989586621679929413]) Source #
Instances
SEq a => SingI (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (UnionSym0 :: TyFun [a6989586621679929413] ([a6989586621679929413] ~> [a6989586621679929413]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym0 :: TyFun [a6989586621679929413] ([a6989586621679929413] ~> [a6989586621679929413]) -> Type) (a6989586621679939100 :: [a6989586621679929413]) Source # | |
data UnionSym1 (a6989586621679939100 :: [a6989586621679929413]) :: (~>) [a6989586621679929413] [a6989586621679929413] Source #
Instances
(SEq a, SingI d) => SingI (UnionSym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (UnionSym1 a6989586621679939100 :: TyFun [a6989586621679929413] [a6989586621679929413] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym1 a6989586621679939100 :: TyFun [a] [a] -> Type) (a6989586621679939101 :: [a]) Source # | |
type UnionSym2 (a6989586621679939100 :: [a6989586621679929413]) (a6989586621679939101 :: [a6989586621679929413]) = Union a6989586621679939100 a6989586621679939101 Source #
data IntersectSym0 :: forall a6989586621679929443. (~>) [a6989586621679929443] ((~>) [a6989586621679929443] [a6989586621679929443]) 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 [a6989586621679929443] ([a6989586621679929443] ~> [a6989586621679929443]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym0 :: TyFun [a6989586621679929443] ([a6989586621679929443] ~> [a6989586621679929443]) -> Type) (a6989586621679939695 :: [a6989586621679929443]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym0 :: TyFun [a6989586621679929443] ([a6989586621679929443] ~> [a6989586621679929443]) -> Type) (a6989586621679939695 :: [a6989586621679929443]) = IntersectSym1 a6989586621679939695 |
data IntersectSym1 (a6989586621679939695 :: [a6989586621679929443]) :: (~>) [a6989586621679929443] [a6989586621679929443] 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 a6989586621679939695 :: TyFun [a6989586621679929443] [a6989586621679929443] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym1 a6989586621679939695 :: TyFun [a] [a] -> Type) (a6989586621679939696 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym1 a6989586621679939695 :: TyFun [a] [a] -> Type) (a6989586621679939696 :: [a]) = Intersect a6989586621679939695 a6989586621679939696 |
type IntersectSym2 (a6989586621679939695 :: [a6989586621679929443]) (a6989586621679939696 :: [a6989586621679929443]) = Intersect a6989586621679939695 a6989586621679939696 Source #
data InsertSym0 :: forall a6989586621679929430. (~>) a6989586621679929430 ((~>) [a6989586621679929430] [a6989586621679929430]) 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 a6989586621679929430 ([a6989586621679929430] ~> [a6989586621679929430]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym0 :: TyFun a6989586621679929430 ([a6989586621679929430] ~> [a6989586621679929430]) -> Type) (a6989586621679939037 :: a6989586621679929430) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym0 :: TyFun a6989586621679929430 ([a6989586621679929430] ~> [a6989586621679929430]) -> Type) (a6989586621679939037 :: a6989586621679929430) = InsertSym1 a6989586621679939037 |
data InsertSym1 (a6989586621679939037 :: a6989586621679929430) :: (~>) [a6989586621679929430] [a6989586621679929430] 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 a6989586621679939037 :: TyFun [a6989586621679929430] [a6989586621679929430] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym1 a6989586621679939037 :: TyFun [a] [a] -> Type) (a6989586621679939038 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym1 a6989586621679939037 :: TyFun [a] [a] -> Type) (a6989586621679939038 :: [a]) = Insert a6989586621679939037 a6989586621679939038 |
type InsertSym2 (a6989586621679939037 :: a6989586621679929430) (a6989586621679939038 :: [a6989586621679929430]) = Insert a6989586621679939037 a6989586621679939038 Source #
data SortSym0 :: forall a6989586621679929429. (~>) [a6989586621679929429] [a6989586621679929429] Source #
Instances
SOrd a => SingI (SortSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (SortSym0 :: TyFun [a6989586621679929429] [a6989586621679929429] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SortSym0 :: TyFun [a] [a] -> Type) (a6989586621679939053 :: [a]) Source # | |
data NubBySym0 :: forall a6989586621679929416. (~>) ((~>) a6989586621679929416 ((~>) a6989586621679929416 Bool)) ((~>) [a6989586621679929416] [a6989586621679929416]) Source #
Instances
SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (NubBySym0 :: TyFun (a6989586621679929416 ~> (a6989586621679929416 ~> Bool)) ([a6989586621679929416] ~> [a6989586621679929416]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym0 :: TyFun (a6989586621679929416 ~> (a6989586621679929416 ~> Bool)) ([a6989586621679929416] ~> [a6989586621679929416]) -> Type) (a6989586621679938683 :: a6989586621679929416 ~> (a6989586621679929416 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data NubBySym1 (a6989586621679938683 :: (~>) a6989586621679929416 ((~>) a6989586621679929416 Bool)) :: (~>) [a6989586621679929416] [a6989586621679929416] Source #
Instances
SingI d => SingI (NubBySym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (NubBySym1 a6989586621679938683 :: TyFun [a6989586621679929416] [a6989586621679929416] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym1 a6989586621679938683 :: TyFun [a] [a] -> Type) (a6989586621679938684 :: [a]) Source # | |
type NubBySym2 (a6989586621679938683 :: (~>) a6989586621679929416 ((~>) a6989586621679929416 Bool)) (a6989586621679938684 :: [a6989586621679929416]) = NubBy a6989586621679938683 a6989586621679938684 Source #
data DeleteBySym0 :: forall a6989586621679929455. (~>) ((~>) a6989586621679929455 ((~>) a6989586621679929455 Bool)) ((~>) a6989586621679929455 ((~>) [a6989586621679929455] [a6989586621679929455])) 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 (a6989586621679929455 ~> (a6989586621679929455 ~> Bool)) (a6989586621679929455 ~> ([a6989586621679929455] ~> [a6989586621679929455])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym0 :: TyFun (a6989586621679929455 ~> (a6989586621679929455 ~> Bool)) (a6989586621679929455 ~> ([a6989586621679929455] ~> [a6989586621679929455])) -> Type) (a6989586621679939056 :: a6989586621679929455 ~> (a6989586621679929455 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data DeleteBySym1 (a6989586621679939056 :: (~>) a6989586621679929455 ((~>) a6989586621679929455 Bool)) :: (~>) a6989586621679929455 ((~>) [a6989586621679929455] [a6989586621679929455]) 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 a6989586621679939056 :: TyFun a6989586621679929455 ([a6989586621679929455] ~> [a6989586621679929455]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym1 a6989586621679939056 :: TyFun a6989586621679929455 ([a6989586621679929455] ~> [a6989586621679929455]) -> Type) (a6989586621679939057 :: a6989586621679929455) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym1 a6989586621679939056 :: TyFun a6989586621679929455 ([a6989586621679929455] ~> [a6989586621679929455]) -> Type) (a6989586621679939057 :: a6989586621679929455) = DeleteBySym2 a6989586621679939056 a6989586621679939057 |
data DeleteBySym2 (a6989586621679939056 :: (~>) a6989586621679929455 ((~>) a6989586621679929455 Bool)) (a6989586621679939057 :: a6989586621679929455) :: (~>) [a6989586621679929455] [a6989586621679929455] 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 a6989586621679939057 a6989586621679939056 :: TyFun [a6989586621679929455] [a6989586621679929455] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym2 a6989586621679939057 a6989586621679939056 :: TyFun [a] [a] -> Type) (a6989586621679939058 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym2 a6989586621679939057 a6989586621679939056 :: TyFun [a] [a] -> Type) (a6989586621679939058 :: [a]) = DeleteBy a6989586621679939057 a6989586621679939056 a6989586621679939058 |
type DeleteBySym3 (a6989586621679939056 :: (~>) a6989586621679929455 ((~>) a6989586621679929455 Bool)) (a6989586621679939057 :: a6989586621679929455) (a6989586621679939058 :: [a6989586621679929455]) = DeleteBy a6989586621679939056 a6989586621679939057 a6989586621679939058 Source #
data DeleteFirstsBySym0 :: forall a6989586621679929454. (~>) ((~>) a6989586621679929454 ((~>) a6989586621679929454 Bool)) ((~>) [a6989586621679929454] ((~>) [a6989586621679929454] [a6989586621679929454])) Source #
Instances
SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (a6989586621679929454 ~> (a6989586621679929454 ~> Bool)) ([a6989586621679929454] ~> ([a6989586621679929454] ~> [a6989586621679929454])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679929454 ~> (a6989586621679929454 ~> Bool)) ([a6989586621679929454] ~> ([a6989586621679929454] ~> [a6989586621679929454])) -> Type) (a6989586621679939074 :: a6989586621679929454 ~> (a6989586621679929454 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679929454 ~> (a6989586621679929454 ~> Bool)) ([a6989586621679929454] ~> ([a6989586621679929454] ~> [a6989586621679929454])) -> Type) (a6989586621679939074 :: a6989586621679929454 ~> (a6989586621679929454 ~> Bool)) = DeleteFirstsBySym1 a6989586621679939074 |
data DeleteFirstsBySym1 (a6989586621679939074 :: (~>) a6989586621679929454 ((~>) a6989586621679929454 Bool)) :: (~>) [a6989586621679929454] ((~>) [a6989586621679929454] [a6989586621679929454]) 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 a6989586621679939074 :: TyFun [a6989586621679929454] ([a6989586621679929454] ~> [a6989586621679929454]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym1 a6989586621679939074 :: TyFun [a6989586621679929454] ([a6989586621679929454] ~> [a6989586621679929454]) -> Type) (a6989586621679939075 :: [a6989586621679929454]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym1 a6989586621679939074 :: TyFun [a6989586621679929454] ([a6989586621679929454] ~> [a6989586621679929454]) -> Type) (a6989586621679939075 :: [a6989586621679929454]) = DeleteFirstsBySym2 a6989586621679939074 a6989586621679939075 |
data DeleteFirstsBySym2 (a6989586621679939074 :: (~>) a6989586621679929454 ((~>) a6989586621679929454 Bool)) (a6989586621679939075 :: [a6989586621679929454]) :: (~>) [a6989586621679929454] [a6989586621679929454] 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 a6989586621679939075 a6989586621679939074 :: TyFun [a6989586621679929454] [a6989586621679929454] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym2 a6989586621679939075 a6989586621679939074 :: TyFun [a] [a] -> Type) (a6989586621679939076 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym2 a6989586621679939075 a6989586621679939074 :: TyFun [a] [a] -> Type) (a6989586621679939076 :: [a]) = DeleteFirstsBy a6989586621679939075 a6989586621679939074 a6989586621679939076 |
type DeleteFirstsBySym3 (a6989586621679939074 :: (~>) a6989586621679929454 ((~>) a6989586621679929454 Bool)) (a6989586621679939075 :: [a6989586621679929454]) (a6989586621679939076 :: [a6989586621679929454]) = DeleteFirstsBy a6989586621679939074 a6989586621679939075 a6989586621679939076 Source #
data UnionBySym0 :: forall a6989586621679929414. (~>) ((~>) a6989586621679929414 ((~>) a6989586621679929414 Bool)) ((~>) [a6989586621679929414] ((~>) [a6989586621679929414] [a6989586621679929414])) 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 (a6989586621679929414 ~> (a6989586621679929414 ~> Bool)) ([a6989586621679929414] ~> ([a6989586621679929414] ~> [a6989586621679929414])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym0 :: TyFun (a6989586621679929414 ~> (a6989586621679929414 ~> Bool)) ([a6989586621679929414] ~> ([a6989586621679929414] ~> [a6989586621679929414])) -> Type) (a6989586621679939087 :: a6989586621679929414 ~> (a6989586621679929414 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data UnionBySym1 (a6989586621679939087 :: (~>) a6989586621679929414 ((~>) a6989586621679929414 Bool)) :: (~>) [a6989586621679929414] ((~>) [a6989586621679929414] [a6989586621679929414]) 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 a6989586621679939087 :: TyFun [a6989586621679929414] ([a6989586621679929414] ~> [a6989586621679929414]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym1 a6989586621679939087 :: TyFun [a6989586621679929414] ([a6989586621679929414] ~> [a6989586621679929414]) -> Type) (a6989586621679939088 :: [a6989586621679929414]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym1 a6989586621679939087 :: TyFun [a6989586621679929414] ([a6989586621679929414] ~> [a6989586621679929414]) -> Type) (a6989586621679939088 :: [a6989586621679929414]) = UnionBySym2 a6989586621679939087 a6989586621679939088 |
data UnionBySym2 (a6989586621679939087 :: (~>) a6989586621679929414 ((~>) a6989586621679929414 Bool)) (a6989586621679939088 :: [a6989586621679929414]) :: (~>) [a6989586621679929414] [a6989586621679929414] 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 a6989586621679939088 a6989586621679939087 :: TyFun [a6989586621679929414] [a6989586621679929414] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym2 a6989586621679939088 a6989586621679939087 :: TyFun [a] [a] -> Type) (a6989586621679939089 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym2 a6989586621679939088 a6989586621679939087 :: TyFun [a] [a] -> Type) (a6989586621679939089 :: [a]) = UnionBy a6989586621679939088 a6989586621679939087 a6989586621679939089 |
type UnionBySym3 (a6989586621679939087 :: (~>) a6989586621679929414 ((~>) a6989586621679929414 Bool)) (a6989586621679939088 :: [a6989586621679929414]) (a6989586621679939089 :: [a6989586621679929414]) = UnionBy a6989586621679939087 a6989586621679939088 a6989586621679939089 Source #
data IntersectBySym0 :: forall a6989586621679929442. (~>) ((~>) a6989586621679929442 ((~>) a6989586621679929442 Bool)) ((~>) [a6989586621679929442] ((~>) [a6989586621679929442] [a6989586621679929442])) Source #
Instances
SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (IntersectBySym0 :: TyFun (a6989586621679929442 ~> (a6989586621679929442 ~> Bool)) ([a6989586621679929442] ~> ([a6989586621679929442] ~> [a6989586621679929442])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym0 :: TyFun (a6989586621679929442 ~> (a6989586621679929442 ~> Bool)) ([a6989586621679929442] ~> ([a6989586621679929442] ~> [a6989586621679929442])) -> Type) (a6989586621679939659 :: a6989586621679929442 ~> (a6989586621679929442 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym0 :: TyFun (a6989586621679929442 ~> (a6989586621679929442 ~> Bool)) ([a6989586621679929442] ~> ([a6989586621679929442] ~> [a6989586621679929442])) -> Type) (a6989586621679939659 :: a6989586621679929442 ~> (a6989586621679929442 ~> Bool)) = IntersectBySym1 a6989586621679939659 |
data IntersectBySym1 (a6989586621679939659 :: (~>) a6989586621679929442 ((~>) a6989586621679929442 Bool)) :: (~>) [a6989586621679929442] ((~>) [a6989586621679929442] [a6989586621679929442]) 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 a6989586621679939659 :: TyFun [a6989586621679929442] ([a6989586621679929442] ~> [a6989586621679929442]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym1 a6989586621679939659 :: TyFun [a6989586621679929442] ([a6989586621679929442] ~> [a6989586621679929442]) -> Type) (a6989586621679939660 :: [a6989586621679929442]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym1 a6989586621679939659 :: TyFun [a6989586621679929442] ([a6989586621679929442] ~> [a6989586621679929442]) -> Type) (a6989586621679939660 :: [a6989586621679929442]) = IntersectBySym2 a6989586621679939659 a6989586621679939660 |
data IntersectBySym2 (a6989586621679939659 :: (~>) a6989586621679929442 ((~>) a6989586621679929442 Bool)) (a6989586621679939660 :: [a6989586621679929442]) :: (~>) [a6989586621679929442] [a6989586621679929442] 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 a6989586621679939660 a6989586621679939659 :: TyFun [a6989586621679929442] [a6989586621679929442] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym2 a6989586621679939660 a6989586621679939659 :: TyFun [a] [a] -> Type) (a6989586621679939661 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym2 a6989586621679939660 a6989586621679939659 :: TyFun [a] [a] -> Type) (a6989586621679939661 :: [a]) = IntersectBy a6989586621679939660 a6989586621679939659 a6989586621679939661 |
type IntersectBySym3 (a6989586621679939659 :: (~>) a6989586621679929442 ((~>) a6989586621679929442 Bool)) (a6989586621679939660 :: [a6989586621679929442]) (a6989586621679939661 :: [a6989586621679929442]) = IntersectBy a6989586621679939659 a6989586621679939660 a6989586621679939661 Source #
data GroupBySym0 :: forall a6989586621679929428. (~>) ((~>) a6989586621679929428 ((~>) a6989586621679929428 Bool)) ((~>) [a6989586621679929428] [[a6989586621679929428]]) 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 (a6989586621679929428 ~> (a6989586621679929428 ~> Bool)) ([a6989586621679929428] ~> [[a6989586621679929428]]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym0 :: TyFun (a6989586621679929428 ~> (a6989586621679929428 ~> Bool)) ([a6989586621679929428] ~> [[a6989586621679929428]]) -> Type) (a6989586621679938924 :: a6989586621679929428 ~> (a6989586621679929428 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data GroupBySym1 (a6989586621679938924 :: (~>) a6989586621679929428 ((~>) a6989586621679929428 Bool)) :: (~>) [a6989586621679929428] [[a6989586621679929428]] 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 a6989586621679938924 :: TyFun [a6989586621679929428] [[a6989586621679929428]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym1 a6989586621679938924 :: TyFun [a] [[a]] -> Type) (a6989586621679938925 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GroupBySym1 a6989586621679938924 :: TyFun [a] [[a]] -> Type) (a6989586621679938925 :: [a]) = GroupBy a6989586621679938924 a6989586621679938925 |
type GroupBySym2 (a6989586621679938924 :: (~>) a6989586621679929428 ((~>) a6989586621679929428 Bool)) (a6989586621679938925 :: [a6989586621679929428]) = GroupBy a6989586621679938924 a6989586621679938925 Source #
data SortBySym0 :: forall a6989586621679929453. (~>) ((~>) a6989586621679929453 ((~>) a6989586621679929453 Ordering)) ((~>) [a6989586621679929453] [a6989586621679929453]) 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 (a6989586621679929453 ~> (a6989586621679929453 ~> Ordering)) ([a6989586621679929453] ~> [a6989586621679929453]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym0 :: TyFun (a6989586621679929453 ~> (a6989586621679929453 ~> Ordering)) ([a6989586621679929453] ~> [a6989586621679929453]) -> Type) (a6989586621679939043 :: a6989586621679929453 ~> (a6989586621679929453 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data SortBySym1 (a6989586621679939043 :: (~>) a6989586621679929453 ((~>) a6989586621679929453 Ordering)) :: (~>) [a6989586621679929453] [a6989586621679929453] 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 a6989586621679939043 :: TyFun [a6989586621679929453] [a6989586621679929453] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym1 a6989586621679939043 :: TyFun [a] [a] -> Type) (a6989586621679939044 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SortBySym1 a6989586621679939043 :: TyFun [a] [a] -> Type) (a6989586621679939044 :: [a]) = SortBy a6989586621679939043 a6989586621679939044 |
type SortBySym2 (a6989586621679939043 :: (~>) a6989586621679929453 ((~>) a6989586621679929453 Ordering)) (a6989586621679939044 :: [a6989586621679929453]) = SortBy a6989586621679939043 a6989586621679939044 Source #
data InsertBySym0 :: forall a6989586621679929452. (~>) ((~>) a6989586621679929452 ((~>) a6989586621679929452 Ordering)) ((~>) a6989586621679929452 ((~>) [a6989586621679929452] [a6989586621679929452])) 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 (a6989586621679929452 ~> (a6989586621679929452 ~> Ordering)) (a6989586621679929452 ~> ([a6989586621679929452] ~> [a6989586621679929452])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym0 :: TyFun (a6989586621679929452 ~> (a6989586621679929452 ~> Ordering)) (a6989586621679929452 ~> ([a6989586621679929452] ~> [a6989586621679929452])) -> Type) (a6989586621679939013 :: a6989586621679929452 ~> (a6989586621679929452 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym0 :: TyFun (a6989586621679929452 ~> (a6989586621679929452 ~> Ordering)) (a6989586621679929452 ~> ([a6989586621679929452] ~> [a6989586621679929452])) -> Type) (a6989586621679939013 :: a6989586621679929452 ~> (a6989586621679929452 ~> Ordering)) = InsertBySym1 a6989586621679939013 |
data InsertBySym1 (a6989586621679939013 :: (~>) a6989586621679929452 ((~>) a6989586621679929452 Ordering)) :: (~>) a6989586621679929452 ((~>) [a6989586621679929452] [a6989586621679929452]) 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 a6989586621679939013 :: TyFun a6989586621679929452 ([a6989586621679929452] ~> [a6989586621679929452]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym1 a6989586621679939013 :: TyFun a6989586621679929452 ([a6989586621679929452] ~> [a6989586621679929452]) -> Type) (a6989586621679939014 :: a6989586621679929452) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym1 a6989586621679939013 :: TyFun a6989586621679929452 ([a6989586621679929452] ~> [a6989586621679929452]) -> Type) (a6989586621679939014 :: a6989586621679929452) = InsertBySym2 a6989586621679939013 a6989586621679939014 |
data InsertBySym2 (a6989586621679939013 :: (~>) a6989586621679929452 ((~>) a6989586621679929452 Ordering)) (a6989586621679939014 :: a6989586621679929452) :: (~>) [a6989586621679929452] [a6989586621679929452] 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 a6989586621679939014 a6989586621679939013 :: TyFun [a6989586621679929452] [a6989586621679929452] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym2 a6989586621679939014 a6989586621679939013 :: TyFun [a] [a] -> Type) (a6989586621679939015 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym2 a6989586621679939014 a6989586621679939013 :: TyFun [a] [a] -> Type) (a6989586621679939015 :: [a]) = InsertBy a6989586621679939014 a6989586621679939013 a6989586621679939015 |
type InsertBySym3 (a6989586621679939013 :: (~>) a6989586621679929452 ((~>) a6989586621679929452 Ordering)) (a6989586621679939014 :: a6989586621679929452) (a6989586621679939015 :: [a6989586621679929452]) = InsertBy a6989586621679939013 a6989586621679939014 a6989586621679939015 Source #
data MaximumBySym0 :: forall a6989586621680438441 t6989586621680438440. (~>) ((~>) a6989586621680438441 ((~>) a6989586621680438441 Ordering)) ((~>) (t6989586621680438440 a6989586621680438441) a6989586621680438441) 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 (a6989586621680438441 ~> (a6989586621680438441 ~> Ordering)) (t6989586621680438440 a6989586621680438441 ~> a6989586621680438441) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym0 :: TyFun (a6989586621680438441 ~> (a6989586621680438441 ~> Ordering)) (t6989586621680438440 a6989586621680438441 ~> a6989586621680438441) -> Type) (a6989586621680438952 :: a6989586621680438441 ~> (a6989586621680438441 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym0 :: TyFun (a6989586621680438441 ~> (a6989586621680438441 ~> Ordering)) (t6989586621680438440 a6989586621680438441 ~> a6989586621680438441) -> Type) (a6989586621680438952 :: a6989586621680438441 ~> (a6989586621680438441 ~> Ordering)) = (MaximumBySym1 a6989586621680438952 t6989586621680438440 :: TyFun (t6989586621680438440 a6989586621680438441) a6989586621680438441 -> Type) |
data MaximumBySym1 (a6989586621680438952 :: (~>) a6989586621680438441 ((~>) a6989586621680438441 Ordering)) :: forall t6989586621680438440. (~>) (t6989586621680438440 a6989586621680438441) a6989586621680438441 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 a6989586621680438952 t6989586621680438440 :: TyFun (t6989586621680438440 a6989586621680438441) a6989586621680438441 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym1 a6989586621680438952 t :: TyFun (t a) a -> Type) (a6989586621680438953 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym1 a6989586621680438952 t :: TyFun (t a) a -> Type) (a6989586621680438953 :: t a) = MaximumBy a6989586621680438952 a6989586621680438953 |
type MaximumBySym2 (a6989586621680438952 :: (~>) a6989586621680438441 ((~>) a6989586621680438441 Ordering)) (a6989586621680438953 :: t6989586621680438440 a6989586621680438441) = MaximumBy a6989586621680438952 a6989586621680438953 Source #
data MinimumBySym0 :: forall a6989586621680438439 t6989586621680438438. (~>) ((~>) a6989586621680438439 ((~>) a6989586621680438439 Ordering)) ((~>) (t6989586621680438438 a6989586621680438439) a6989586621680438439) 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 (a6989586621680438439 ~> (a6989586621680438439 ~> Ordering)) (t6989586621680438438 a6989586621680438439 ~> a6989586621680438439) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym0 :: TyFun (a6989586621680438439 ~> (a6989586621680438439 ~> Ordering)) (t6989586621680438438 a6989586621680438439 ~> a6989586621680438439) -> Type) (a6989586621680438927 :: a6989586621680438439 ~> (a6989586621680438439 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym0 :: TyFun (a6989586621680438439 ~> (a6989586621680438439 ~> Ordering)) (t6989586621680438438 a6989586621680438439 ~> a6989586621680438439) -> Type) (a6989586621680438927 :: a6989586621680438439 ~> (a6989586621680438439 ~> Ordering)) = (MinimumBySym1 a6989586621680438927 t6989586621680438438 :: TyFun (t6989586621680438438 a6989586621680438439) a6989586621680438439 -> Type) |
data MinimumBySym1 (a6989586621680438927 :: (~>) a6989586621680438439 ((~>) a6989586621680438439 Ordering)) :: forall t6989586621680438438. (~>) (t6989586621680438438 a6989586621680438439) a6989586621680438439 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 a6989586621680438927 t6989586621680438438 :: TyFun (t6989586621680438438 a6989586621680438439) a6989586621680438439 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym1 a6989586621680438927 t :: TyFun (t a) a -> Type) (a6989586621680438928 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym1 a6989586621680438927 t :: TyFun (t a) a -> Type) (a6989586621680438928 :: t a) = MinimumBy a6989586621680438927 a6989586621680438928 |
type MinimumBySym2 (a6989586621680438927 :: (~>) a6989586621680438439 ((~>) a6989586621680438439 Ordering)) (a6989586621680438928 :: t6989586621680438438 a6989586621680438439) = MinimumBy a6989586621680438927 a6989586621680438928 Source #
data GenericLengthSym0 :: forall a6989586621679929412 i6989586621679929411. (~>) [a6989586621679929412] i6989586621679929411 Source #
Instances
SNum i => SingI (GenericLengthSym0 :: TyFun [a] i -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a6989586621679929412] i6989586621679929411 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679938670 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679938670 :: [a]) = (GenericLength a6989586621679938670 :: k2) |
type GenericLengthSym1 (a6989586621679938670 :: [a6989586621679929412]) = GenericLength a6989586621679938670 Source #
data GenericTakeSym0 :: forall a6989586621680055614 i6989586621680055613. (~>) i6989586621680055613 ((~>) [a6989586621680055614] [a6989586621680055614]) Source #
Instances
SuppressUnusedWarnings (GenericTakeSym0 :: TyFun i6989586621680055613 ([a6989586621680055614] ~> [a6989586621680055614]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericTakeSym0 :: TyFun i6989586621680055613 ([a6989586621680055614] ~> [a6989586621680055614]) -> Type) (a6989586621680068157 :: i6989586621680055613) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericTakeSym0 :: TyFun i6989586621680055613 ([a6989586621680055614] ~> [a6989586621680055614]) -> Type) (a6989586621680068157 :: i6989586621680055613) = (GenericTakeSym1 a6989586621680068157 a6989586621680055614 :: TyFun [a6989586621680055614] [a6989586621680055614] -> Type) |
data GenericTakeSym1 (a6989586621680068157 :: i6989586621680055613) :: forall a6989586621680055614. (~>) [a6989586621680055614] [a6989586621680055614] Source #
Instances
SuppressUnusedWarnings (GenericTakeSym1 a6989586621680068157 a6989586621680055614 :: TyFun [a6989586621680055614] [a6989586621680055614] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericTakeSym1 a6989586621680068157 a :: TyFun [a] [a] -> Type) (a6989586621680068158 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericTakeSym1 a6989586621680068157 a :: TyFun [a] [a] -> Type) (a6989586621680068158 :: [a]) = GenericTake a6989586621680068157 a6989586621680068158 |
type GenericTakeSym2 (a6989586621680068157 :: i6989586621680055613) (a6989586621680068158 :: [a6989586621680055614]) = GenericTake a6989586621680068157 a6989586621680068158 Source #
data GenericDropSym0 :: forall a6989586621680055612 i6989586621680055611. (~>) i6989586621680055611 ((~>) [a6989586621680055612] [a6989586621680055612]) Source #
Instances
SuppressUnusedWarnings (GenericDropSym0 :: TyFun i6989586621680055611 ([a6989586621680055612] ~> [a6989586621680055612]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericDropSym0 :: TyFun i6989586621680055611 ([a6989586621680055612] ~> [a6989586621680055612]) -> Type) (a6989586621680068147 :: i6989586621680055611) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericDropSym0 :: TyFun i6989586621680055611 ([a6989586621680055612] ~> [a6989586621680055612]) -> Type) (a6989586621680068147 :: i6989586621680055611) = (GenericDropSym1 a6989586621680068147 a6989586621680055612 :: TyFun [a6989586621680055612] [a6989586621680055612] -> Type) |
data GenericDropSym1 (a6989586621680068147 :: i6989586621680055611) :: forall a6989586621680055612. (~>) [a6989586621680055612] [a6989586621680055612] Source #
Instances
SuppressUnusedWarnings (GenericDropSym1 a6989586621680068147 a6989586621680055612 :: TyFun [a6989586621680055612] [a6989586621680055612] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericDropSym1 a6989586621680068147 a :: TyFun [a] [a] -> Type) (a6989586621680068148 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericDropSym1 a6989586621680068147 a :: TyFun [a] [a] -> Type) (a6989586621680068148 :: [a]) = GenericDrop a6989586621680068147 a6989586621680068148 |
type GenericDropSym2 (a6989586621680068147 :: i6989586621680055611) (a6989586621680068148 :: [a6989586621680055612]) = GenericDrop a6989586621680068147 a6989586621680068148 Source #
data GenericSplitAtSym0 :: forall a6989586621680055610 i6989586621680055609. (~>) i6989586621680055609 ((~>) [a6989586621680055610] ([a6989586621680055610], [a6989586621680055610])) Source #
Instances
SuppressUnusedWarnings (GenericSplitAtSym0 :: TyFun i6989586621680055609 ([a6989586621680055610] ~> ([a6989586621680055610], [a6989586621680055610])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericSplitAtSym0 :: TyFun i6989586621680055609 ([a6989586621680055610] ~> ([a6989586621680055610], [a6989586621680055610])) -> Type) (a6989586621680068137 :: i6989586621680055609) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericSplitAtSym0 :: TyFun i6989586621680055609 ([a6989586621680055610] ~> ([a6989586621680055610], [a6989586621680055610])) -> Type) (a6989586621680068137 :: i6989586621680055609) = (GenericSplitAtSym1 a6989586621680068137 a6989586621680055610 :: TyFun [a6989586621680055610] ([a6989586621680055610], [a6989586621680055610]) -> Type) |
data GenericSplitAtSym1 (a6989586621680068137 :: i6989586621680055609) :: forall a6989586621680055610. (~>) [a6989586621680055610] ([a6989586621680055610], [a6989586621680055610]) Source #
Instances
SuppressUnusedWarnings (GenericSplitAtSym1 a6989586621680068137 a6989586621680055610 :: TyFun [a6989586621680055610] ([a6989586621680055610], [a6989586621680055610]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericSplitAtSym1 a6989586621680068137 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621680068138 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericSplitAtSym1 a6989586621680068137 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621680068138 :: [a]) = GenericSplitAt a6989586621680068137 a6989586621680068138 |
type GenericSplitAtSym2 (a6989586621680068137 :: i6989586621680055609) (a6989586621680068138 :: [a6989586621680055610]) = GenericSplitAt a6989586621680068137 a6989586621680068138 Source #
data GenericIndexSym0 :: forall a6989586621680055608 i6989586621680055607. (~>) [a6989586621680055608] ((~>) i6989586621680055607 a6989586621680055608) Source #
Instances
SuppressUnusedWarnings (GenericIndexSym0 :: TyFun [a6989586621680055608] (i6989586621680055607 ~> a6989586621680055608) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericIndexSym0 :: TyFun [a6989586621680055608] (i6989586621680055607 ~> a6989586621680055608) -> Type) (a6989586621680068127 :: [a6989586621680055608]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericIndexSym0 :: TyFun [a6989586621680055608] (i6989586621680055607 ~> a6989586621680055608) -> Type) (a6989586621680068127 :: [a6989586621680055608]) = (GenericIndexSym1 a6989586621680068127 i6989586621680055607 :: TyFun i6989586621680055607 a6989586621680055608 -> Type) |
data GenericIndexSym1 (a6989586621680068127 :: [a6989586621680055608]) :: forall i6989586621680055607. (~>) i6989586621680055607 a6989586621680055608 Source #
Instances
SuppressUnusedWarnings (GenericIndexSym1 a6989586621680068127 i6989586621680055607 :: TyFun i6989586621680055607 a6989586621680055608 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericIndexSym1 a6989586621680068127 i :: TyFun i a -> Type) (a6989586621680068128 :: i) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericIndexSym1 a6989586621680068127 i :: TyFun i a -> Type) (a6989586621680068128 :: i) = GenericIndex a6989586621680068127 a6989586621680068128 |
type GenericIndexSym2 (a6989586621680068127 :: [a6989586621680055608]) (a6989586621680068128 :: i6989586621680055607) = GenericIndex a6989586621680068127 a6989586621680068128 Source #
data GenericReplicateSym0 :: forall a6989586621680055606 i6989586621680055605. (~>) i6989586621680055605 ((~>) a6989586621680055606 [a6989586621680055606]) Source #
Instances
SuppressUnusedWarnings (GenericReplicateSym0 :: TyFun i6989586621680055605 (a6989586621680055606 ~> [a6989586621680055606]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericReplicateSym0 :: TyFun i6989586621680055605 (a6989586621680055606 ~> [a6989586621680055606]) -> Type) (a6989586621680068117 :: i6989586621680055605) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericReplicateSym0 :: TyFun i6989586621680055605 (a6989586621680055606 ~> [a6989586621680055606]) -> Type) (a6989586621680068117 :: i6989586621680055605) = (GenericReplicateSym1 a6989586621680068117 a6989586621680055606 :: TyFun a6989586621680055606 [a6989586621680055606] -> Type) |
data GenericReplicateSym1 (a6989586621680068117 :: i6989586621680055605) :: forall a6989586621680055606. (~>) a6989586621680055606 [a6989586621680055606] Source #
Instances
SuppressUnusedWarnings (GenericReplicateSym1 a6989586621680068117 a6989586621680055606 :: TyFun a6989586621680055606 [a6989586621680055606] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () Source # | |
type Apply (GenericReplicateSym1 a6989586621680068117 a :: TyFun a [a] -> Type) (a6989586621680068118 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericReplicateSym1 a6989586621680068117 a :: TyFun a [a] -> Type) (a6989586621680068118 :: a) = GenericReplicate a6989586621680068117 a6989586621680068118 |
type GenericReplicateSym2 (a6989586621680068117 :: i6989586621680055605) (a6989586621680068118 :: a6989586621680055606) = GenericReplicate a6989586621680068117 a6989586621680068118 Source #