Copyright | (C) 2013-2014 Richard Eisenberg Jan Stolarek |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Data.Singletons.Prelude.List
Description
Defines functions and datatypes relating to the singleton for '[]',
including a singletons version of a few of the definitions in Data.List
.
Because many of these definitions are produced by Template Haskell,
it is not possible to create proper Haddock documentation. Please look
up the corresponding operation in Data.List
. Also, please excuse
the apparent repeated variable names. This is due to an interaction
between Template Haskell and Haddock.
Synopsis
- type family Sing :: k -> Type
- data SList :: forall a. [a] -> Type where
- type family (a :: [a]) ++ (a :: [a]) :: [a] where ...
- (%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a])
- type family Head (a :: [a]) :: a where ...
- sHead :: forall a (t :: [a]). Sing t -> Sing (Apply HeadSym0 t :: a)
- type family Last (a :: [a]) :: a where ...
- sLast :: forall a (t :: [a]). Sing t -> Sing (Apply LastSym0 t :: a)
- type family Tail (a :: [a]) :: [a] where ...
- sTail :: forall a (t :: [a]). Sing t -> Sing (Apply TailSym0 t :: [a])
- type family Init (a :: [a]) :: [a] where ...
- sInit :: forall a (t :: [a]). Sing t -> Sing (Apply InitSym0 t :: [a])
- type family Null (arg :: t a) :: Bool
- sNull :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply NullSym0 t :: Bool)
- type family Length (arg :: t a) :: Nat
- sLength :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply LengthSym0 t :: Nat)
- type family Map (a :: (~>) a b) (a :: [a]) :: [b] where ...
- sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b])
- type family Reverse (a :: [a]) :: [a] where ...
- sReverse :: forall a (t :: [a]). Sing t -> Sing (Apply ReverseSym0 t :: [a])
- type family Intersperse (a :: a) (a :: [a]) :: [a] where ...
- sIntersperse :: forall a (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a])
- type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ...
- sIntercalate :: forall a (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a])
- type family Transpose (a :: [[a]]) :: [[a]] where ...
- sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]])
- type family Subsequences (a :: [a]) :: [[a]] where ...
- sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]])
- type family Permutations (a :: [a]) :: [[a]] where ...
- sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]])
- type family Foldl (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
- sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b)
- type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
- sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b)
- type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
- sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a)
- type family Foldl1' (a :: (~>) a ((~>) a a)) (a :: [a]) :: a where ...
- sFoldl1' :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a)
- type family Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b
- sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b)
- type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
- sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a)
- type family Concat (a :: t [a]) :: [a] where ...
- sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a])
- type family ConcatMap (a :: (~>) a [b]) (a :: t a) :: [b] where ...
- sConcatMap :: forall a b t (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b])
- type family And (a :: t Bool) :: Bool where ...
- sAnd :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool)
- type family Or (a :: t Bool) :: Bool where ...
- sOr :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool)
- type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ...
- sAny :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool)
- type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ...
- sAll :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool)
- type family Sum (arg :: t a) :: a
- sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a)
- type family Product (arg :: t a) :: a
- sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a)
- type family Maximum (arg :: t a) :: a
- sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a)
- type family Minimum (arg :: t a) :: a
- sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a)
- type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: [b] where ...
- sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b])
- type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
- sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a])
- type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: [b] where ...
- sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b])
- type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
- sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a])
- type family MapAccumL (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
- sMapAccumL :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (a, t c))
- type family MapAccumR (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
- sMapAccumR :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c))
- type family Replicate (a :: Nat) (a :: a) :: [a] where ...
- sReplicate :: forall a (t :: Nat) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a])
- type family Unfoldr (a :: (~>) b (Maybe (a, b))) (a :: b) :: [a] where ...
- sUnfoldr :: forall b a (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a])
- type family Take (a :: Nat) (a :: [a]) :: [a] where ...
- sTake :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a])
- type family Drop (a :: Nat) (a :: [a]) :: [a] where ...
- sDrop :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a])
- type family SplitAt (a :: Nat) (a :: [a]) :: ([a], [a]) where ...
- sSplitAt :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a]))
- type family TakeWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sTakeWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a])
- type family DropWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sDropWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a])
- type family DropWhileEnd (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sDropWhileEnd :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a])
- type family Span (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sSpan :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a]))
- type family Break (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sBreak :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a]))
- type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ...
- type family Group (a :: [a]) :: [[a]] where ...
- sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [[a]])
- type family Inits (a :: [a]) :: [[a]] where ...
- sInits :: forall a (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: [[a]])
- type family Tails (a :: [a]) :: [[a]] where ...
- sTails :: forall a (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: [[a]])
- type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsPrefixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool)
- type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsSuffixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool)
- type family IsInfixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsInfixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool)
- type family Elem (arg :: a) (arg :: t a) :: Bool
- sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool)
- type family NotElem (a :: a) (a :: t a) :: Bool where ...
- sNotElem :: forall a t (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool)
- type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ...
- sLookup :: forall a b (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b)
- type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ...
- sFind :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a)
- type family Filter (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
- sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
- type family Partition (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
- sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
- type family (a :: [a]) !! (a :: Nat) :: a where ...
- (%!!) :: forall a (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a)
- type family ElemIndex (a :: a) (a :: [a]) :: Maybe Nat where ...
- sElemIndex :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat)
- type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ...
- sElemIndices :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat])
- type family FindIndex (a :: (~>) a Bool) (a :: [a]) :: Maybe Nat where ...
- sFindIndex :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat)
- type family FindIndices (a :: (~>) a Bool) (a :: [a]) :: [Nat] where ...
- sFindIndices :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat])
- type family Zip (a :: [a]) (a :: [b]) :: [(a, b)] where ...
- sZip :: forall a b (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)])
- type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ...
- sZip3 :: forall a b c (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)])
- type family Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ...
- type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ...
- type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ...
- type family Zip7 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [(a, b, c, d, e, f, g)] where ...
- type family ZipWith (a :: (~>) a ((~>) b c)) (a :: [a]) (a :: [b]) :: [c] where ...
- sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c])
- type family ZipWith3 (a :: (~>) a ((~>) b ((~>) c d))) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ...
- sZipWith3 :: forall a b c d (t :: (~>) a ((~>) b ((~>) c d))) (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d])
- type family ZipWith4 (a :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ...
- type family ZipWith5 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ...
- type family ZipWith6 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ...
- type family ZipWith7 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ...
- type family Unzip (a :: [(a, b)]) :: ([a], [b]) where ...
- sUnzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b]))
- type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ...
- sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c]))
- type family Unzip4 (a :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
- sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d]))
- type family Unzip5 (a :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ...
- sUnzip5 :: forall a b c d e (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e]))
- type family Unzip6 (a :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ...
- sUnzip6 :: forall a b c d e f (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f]))
- type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
- sUnzip7 :: forall a b c d e f g (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g]))
- type family Unlines (a :: [Symbol]) :: Symbol where ...
- sUnlines :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnlinesSym0 t :: Symbol)
- type family Unwords (a :: [Symbol]) :: Symbol where ...
- sUnwords :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnwordsSym0 t :: Symbol)
- type family Nub (a :: [a]) :: [a] where ...
- sNub :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply NubSym0 t :: [a])
- type family Delete (a :: a) (a :: [a]) :: [a] where ...
- sDelete :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a])
- type family (a :: [a]) \\ (a :: [a]) :: [a] where ...
- (%\\) :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (\\@#@$) t) t :: [a])
- type family Union (a :: [a]) (a :: [a]) :: [a] where ...
- sUnion :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a])
- type family Intersect (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersect :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a])
- type family Insert (a :: a) (a :: [a]) :: [a] where ...
- sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a])
- type family Sort (a :: [a]) :: [a] where ...
- sSort :: forall a (t :: [a]). SOrd a => Sing t -> Sing (Apply SortSym0 t :: [a])
- type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [a] where ...
- sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a])
- type family DeleteBy (a :: (~>) a ((~>) a Bool)) (a :: a) (a :: [a]) :: [a] where ...
- sDeleteBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a])
- type family DeleteFirstsBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sDeleteFirstsBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a])
- type family UnionBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sUnionBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a])
- type family IntersectBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersectBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a])
- type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [[a]] where ...
- sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]])
- type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: [a]) :: [a] where ...
- sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a])
- type family InsertBy (a :: (~>) a ((~>) a Ordering)) (a :: a) (a :: [a]) :: [a] where ...
- sInsertBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a])
- type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
- sMaximumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a)
- type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
- sMinimumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a)
- type family GenericLength (a :: [a]) :: i where ...
- sGenericLength :: forall a i (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i)
- type family GenericTake (a :: i) (a :: [a]) :: [a] where ...
- type family GenericDrop (a :: i) (a :: [a]) :: [a] where ...
- type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ...
- type family GenericIndex (a :: [a]) (a :: i) :: a where ...
- type family GenericReplicate (a :: i) (a :: a) :: [a] where ...
- type NilSym0 = '[]
- data (:@#@$) :: forall (a3530822107858468865 :: Type). (~>) a3530822107858468865 ((~>) [a3530822107858468865] [a3530822107858468865 :: Type])
- data (:@#@$$) (t6989586621679310906 :: a3530822107858468865 :: Type) :: (~>) [a3530822107858468865] [a3530822107858468865 :: Type]
- type (:@#@$$$) (t6989586621679310906 :: a3530822107858468865) (t6989586621679310907 :: [a3530822107858468865]) = '(:) t6989586621679310906 t6989586621679310907
- type (++@#@$$$) (a6989586621679541707 :: [a6989586621679541510]) (a6989586621679541708 :: [a6989586621679541510]) = (++) a6989586621679541707 a6989586621679541708
- data (++@#@$$) (a6989586621679541707 :: [a6989586621679541510]) :: (~>) [a6989586621679541510] [a6989586621679541510]
- data (++@#@$) :: forall a6989586621679541510. (~>) [a6989586621679541510] ((~>) [a6989586621679541510] [a6989586621679541510])
- data HeadSym0 :: forall a6989586621679970260. (~>) [a6989586621679970260] a6989586621679970260
- type HeadSym1 (a6989586621679975607 :: [a6989586621679970260]) = Head a6989586621679975607
- data LastSym0 :: forall a6989586621679970259. (~>) [a6989586621679970259] a6989586621679970259
- type LastSym1 (a6989586621679975602 :: [a6989586621679970259]) = Last a6989586621679975602
- data TailSym0 :: forall a6989586621679970258. (~>) [a6989586621679970258] [a6989586621679970258]
- type TailSym1 (a6989586621679975599 :: [a6989586621679970258]) = Tail a6989586621679975599
- data InitSym0 :: forall a6989586621679970257. (~>) [a6989586621679970257] [a6989586621679970257]
- type InitSym1 (a6989586621679975585 :: [a6989586621679970257]) = Init a6989586621679975585
- data NullSym0 :: forall t6989586621680486579 a6989586621680486594. (~>) (t6989586621680486579 a6989586621680486594) Bool
- type NullSym1 (arg6989586621680487238 :: t6989586621680486579 a6989586621680486594) = Null arg6989586621680487238
- data LengthSym0 :: forall t6989586621680486579 a6989586621680486595. (~>) (t6989586621680486579 a6989586621680486595) Nat
- type LengthSym1 (arg6989586621680487240 :: t6989586621680486579 a6989586621680486595) = Length arg6989586621680487240
- data MapSym0 :: forall a6989586621679541511 b6989586621679541512. (~>) ((~>) a6989586621679541511 b6989586621679541512) ((~>) [a6989586621679541511] [b6989586621679541512])
- data MapSym1 (a6989586621679541715 :: (~>) a6989586621679541511 b6989586621679541512) :: (~>) [a6989586621679541511] [b6989586621679541512]
- type MapSym2 (a6989586621679541715 :: (~>) a6989586621679541511 b6989586621679541512) (a6989586621679541716 :: [a6989586621679541511]) = Map a6989586621679541715 a6989586621679541716
- data ReverseSym0 :: forall a6989586621679970255. (~>) [a6989586621679970255] [a6989586621679970255]
- type ReverseSym1 (a6989586621679975570 :: [a6989586621679970255]) = Reverse a6989586621679975570
- data IntersperseSym0 :: forall a6989586621679970254. (~>) a6989586621679970254 ((~>) [a6989586621679970254] [a6989586621679970254])
- data IntersperseSym1 (a6989586621679975563 :: a6989586621679970254) :: (~>) [a6989586621679970254] [a6989586621679970254]
- type IntersperseSym2 (a6989586621679975563 :: a6989586621679970254) (a6989586621679975564 :: [a6989586621679970254]) = Intersperse a6989586621679975563 a6989586621679975564
- data IntercalateSym0 :: forall a6989586621679970253. (~>) [a6989586621679970253] ((~>) [[a6989586621679970253]] [a6989586621679970253])
- data IntercalateSym1 (a6989586621679975557 :: [a6989586621679970253]) :: (~>) [[a6989586621679970253]] [a6989586621679970253]
- type IntercalateSym2 (a6989586621679975557 :: [a6989586621679970253]) (a6989586621679975558 :: [[a6989586621679970253]]) = Intercalate a6989586621679975557 a6989586621679975558
- data TransposeSym0 :: forall a6989586621679970140. (~>) [[a6989586621679970140]] [[a6989586621679970140]]
- type TransposeSym1 (a6989586621679974300 :: [[a6989586621679970140]]) = Transpose a6989586621679974300
- data SubsequencesSym0 :: forall a6989586621679970252. (~>) [a6989586621679970252] [[a6989586621679970252]]
- type SubsequencesSym1 (a6989586621679975554 :: [a6989586621679970252]) = Subsequences a6989586621679975554
- data PermutationsSym0 :: forall a6989586621679970249. (~>) [a6989586621679970249] [[a6989586621679970249]]
- type PermutationsSym1 (a6989586621679975436 :: [a6989586621679970249]) = Permutations a6989586621679975436
- data FoldlSym0 :: forall b6989586621680486587 a6989586621680486588 t6989586621680486579. (~>) ((~>) b6989586621680486587 ((~>) a6989586621680486588 b6989586621680486587)) ((~>) b6989586621680486587 ((~>) (t6989586621680486579 a6989586621680486588) b6989586621680486587))
- data FoldlSym1 (arg6989586621680487216 :: (~>) b6989586621680486587 ((~>) a6989586621680486588 b6989586621680486587)) :: forall t6989586621680486579. (~>) b6989586621680486587 ((~>) (t6989586621680486579 a6989586621680486588) b6989586621680486587)
- data FoldlSym2 (arg6989586621680487216 :: (~>) b6989586621680486587 ((~>) a6989586621680486588 b6989586621680486587)) (arg6989586621680487217 :: b6989586621680486587) :: forall t6989586621680486579. (~>) (t6989586621680486579 a6989586621680486588) b6989586621680486587
- type FoldlSym3 (arg6989586621680487216 :: (~>) b6989586621680486587 ((~>) a6989586621680486588 b6989586621680486587)) (arg6989586621680487217 :: b6989586621680486587) (arg6989586621680487218 :: t6989586621680486579 a6989586621680486588) = Foldl arg6989586621680487216 arg6989586621680487217 arg6989586621680487218
- data Foldl'Sym0 :: forall b6989586621680486589 a6989586621680486590 t6989586621680486579. (~>) ((~>) b6989586621680486589 ((~>) a6989586621680486590 b6989586621680486589)) ((~>) b6989586621680486589 ((~>) (t6989586621680486579 a6989586621680486590) b6989586621680486589))
- data Foldl'Sym1 (arg6989586621680487222 :: (~>) b6989586621680486589 ((~>) a6989586621680486590 b6989586621680486589)) :: forall t6989586621680486579. (~>) b6989586621680486589 ((~>) (t6989586621680486579 a6989586621680486590) b6989586621680486589)
- data Foldl'Sym2 (arg6989586621680487222 :: (~>) b6989586621680486589 ((~>) a6989586621680486590 b6989586621680486589)) (arg6989586621680487223 :: b6989586621680486589) :: forall t6989586621680486579. (~>) (t6989586621680486579 a6989586621680486590) b6989586621680486589
- type Foldl'Sym3 (arg6989586621680487222 :: (~>) b6989586621680486589 ((~>) a6989586621680486590 b6989586621680486589)) (arg6989586621680487223 :: b6989586621680486589) (arg6989586621680487224 :: t6989586621680486579 a6989586621680486590) = Foldl' arg6989586621680487222 arg6989586621680487223 arg6989586621680487224
- data Foldl1Sym0 :: forall a6989586621680486592 t6989586621680486579. (~>) ((~>) a6989586621680486592 ((~>) a6989586621680486592 a6989586621680486592)) ((~>) (t6989586621680486579 a6989586621680486592) a6989586621680486592)
- data Foldl1Sym1 (arg6989586621680487232 :: (~>) a6989586621680486592 ((~>) a6989586621680486592 a6989586621680486592)) :: forall t6989586621680486579. (~>) (t6989586621680486579 a6989586621680486592) a6989586621680486592
- type Foldl1Sym2 (arg6989586621680487232 :: (~>) a6989586621680486592 ((~>) a6989586621680486592 a6989586621680486592)) (arg6989586621680487233 :: t6989586621680486579 a6989586621680486592) = Foldl1 arg6989586621680487232 arg6989586621680487233
- data Foldl1'Sym0 :: forall a6989586621679970245. (~>) ((~>) a6989586621679970245 ((~>) a6989586621679970245 a6989586621679970245)) ((~>) [a6989586621679970245] a6989586621679970245)
- data Foldl1'Sym1 (a6989586621679975394 :: (~>) a6989586621679970245 ((~>) a6989586621679970245 a6989586621679970245)) :: (~>) [a6989586621679970245] a6989586621679970245
- type Foldl1'Sym2 (a6989586621679975394 :: (~>) a6989586621679970245 ((~>) a6989586621679970245 a6989586621679970245)) (a6989586621679975395 :: [a6989586621679970245]) = Foldl1' a6989586621679975394 a6989586621679975395
- data FoldrSym0 :: forall a6989586621680486583 b6989586621680486584 t6989586621680486579. (~>) ((~>) a6989586621680486583 ((~>) b6989586621680486584 b6989586621680486584)) ((~>) b6989586621680486584 ((~>) (t6989586621680486579 a6989586621680486583) b6989586621680486584))
- data FoldrSym1 (arg6989586621680487204 :: (~>) a6989586621680486583 ((~>) b6989586621680486584 b6989586621680486584)) :: forall t6989586621680486579. (~>) b6989586621680486584 ((~>) (t6989586621680486579 a6989586621680486583) b6989586621680486584)
- data FoldrSym2 (arg6989586621680487204 :: (~>) a6989586621680486583 ((~>) b6989586621680486584 b6989586621680486584)) (arg6989586621680487205 :: b6989586621680486584) :: forall t6989586621680486579. (~>) (t6989586621680486579 a6989586621680486583) b6989586621680486584
- type FoldrSym3 (arg6989586621680487204 :: (~>) a6989586621680486583 ((~>) b6989586621680486584 b6989586621680486584)) (arg6989586621680487205 :: b6989586621680486584) (arg6989586621680487206 :: t6989586621680486579 a6989586621680486583) = Foldr arg6989586621680487204 arg6989586621680487205 arg6989586621680487206
- data Foldr1Sym0 :: forall a6989586621680486591 t6989586621680486579. (~>) ((~>) a6989586621680486591 ((~>) a6989586621680486591 a6989586621680486591)) ((~>) (t6989586621680486579 a6989586621680486591) a6989586621680486591)
- data Foldr1Sym1 (arg6989586621680487228 :: (~>) a6989586621680486591 ((~>) a6989586621680486591 a6989586621680486591)) :: forall t6989586621680486579. (~>) (t6989586621680486579 a6989586621680486591) a6989586621680486591
- type Foldr1Sym2 (arg6989586621680487228 :: (~>) a6989586621680486591 ((~>) a6989586621680486591 a6989586621680486591)) (arg6989586621680487229 :: t6989586621680486579 a6989586621680486591) = Foldr1 arg6989586621680487228 arg6989586621680487229
- data ConcatSym0 :: forall t6989586621680486504 a6989586621680486505. (~>) (t6989586621680486504 [a6989586621680486505]) [a6989586621680486505]
- type ConcatSym1 (a6989586621680487086 :: t6989586621680486504 [a6989586621680486505]) = Concat a6989586621680487086
- data ConcatMapSym0 :: forall a6989586621680486502 b6989586621680486503 t6989586621680486501. (~>) ((~>) a6989586621680486502 [b6989586621680486503]) ((~>) (t6989586621680486501 a6989586621680486502) [b6989586621680486503])
- data ConcatMapSym1 (a6989586621680487070 :: (~>) a6989586621680486502 [b6989586621680486503]) :: forall t6989586621680486501. (~>) (t6989586621680486501 a6989586621680486502) [b6989586621680486503]
- type ConcatMapSym2 (a6989586621680487070 :: (~>) a6989586621680486502 [b6989586621680486503]) (a6989586621680487071 :: t6989586621680486501 a6989586621680486502) = ConcatMap a6989586621680487070 a6989586621680487071
- data AndSym0 :: forall t6989586621680486500. (~>) (t6989586621680486500 Bool) Bool
- type AndSym1 (a6989586621680487061 :: t6989586621680486500 Bool) = And a6989586621680487061
- data OrSym0 :: forall t6989586621680486499. (~>) (t6989586621680486499 Bool) Bool
- type OrSym1 (a6989586621680487052 :: t6989586621680486499 Bool) = Or a6989586621680487052
- data AnySym0 :: forall a6989586621680486498 t6989586621680486497. (~>) ((~>) a6989586621680486498 Bool) ((~>) (t6989586621680486497 a6989586621680486498) Bool)
- data AnySym1 (a6989586621680487039 :: (~>) a6989586621680486498 Bool) :: forall t6989586621680486497. (~>) (t6989586621680486497 a6989586621680486498) Bool
- type AnySym2 (a6989586621680487039 :: (~>) a6989586621680486498 Bool) (a6989586621680487040 :: t6989586621680486497 a6989586621680486498) = Any a6989586621680487039 a6989586621680487040
- data AllSym0 :: forall a6989586621680486496 t6989586621680486495. (~>) ((~>) a6989586621680486496 Bool) ((~>) (t6989586621680486495 a6989586621680486496) Bool)
- data AllSym1 (a6989586621680487026 :: (~>) a6989586621680486496 Bool) :: forall t6989586621680486495. (~>) (t6989586621680486495 a6989586621680486496) Bool
- type AllSym2 (a6989586621680487026 :: (~>) a6989586621680486496 Bool) (a6989586621680487027 :: t6989586621680486495 a6989586621680486496) = All a6989586621680487026 a6989586621680487027
- data SumSym0 :: forall t6989586621680486579 a6989586621680486599. (~>) (t6989586621680486579 a6989586621680486599) a6989586621680486599
- type SumSym1 (arg6989586621680487250 :: t6989586621680486579 a6989586621680486599) = Sum arg6989586621680487250
- data ProductSym0 :: forall t6989586621680486579 a6989586621680486600. (~>) (t6989586621680486579 a6989586621680486600) a6989586621680486600
- type ProductSym1 (arg6989586621680487252 :: t6989586621680486579 a6989586621680486600) = Product arg6989586621680487252
- data MaximumSym0 :: forall t6989586621680486579 a6989586621680486597. (~>) (t6989586621680486579 a6989586621680486597) a6989586621680486597
- type MaximumSym1 (arg6989586621680487246 :: t6989586621680486579 a6989586621680486597) = Maximum arg6989586621680487246
- data MinimumSym0 :: forall t6989586621680486579 a6989586621680486598. (~>) (t6989586621680486579 a6989586621680486598) a6989586621680486598
- type MinimumSym1 (arg6989586621680487248 :: t6989586621680486579 a6989586621680486598) = Minimum arg6989586621680487248
- data ScanlSym0 :: forall b6989586621679970237 a6989586621679970238. (~>) ((~>) b6989586621679970237 ((~>) a6989586621679970238 b6989586621679970237)) ((~>) b6989586621679970237 ((~>) [a6989586621679970238] [b6989586621679970237]))
- data ScanlSym1 (a6989586621679975331 :: (~>) b6989586621679970237 ((~>) a6989586621679970238 b6989586621679970237)) :: (~>) b6989586621679970237 ((~>) [a6989586621679970238] [b6989586621679970237])
- data ScanlSym2 (a6989586621679975331 :: (~>) b6989586621679970237 ((~>) a6989586621679970238 b6989586621679970237)) (a6989586621679975332 :: b6989586621679970237) :: (~>) [a6989586621679970238] [b6989586621679970237]
- type ScanlSym3 (a6989586621679975331 :: (~>) b6989586621679970237 ((~>) a6989586621679970238 b6989586621679970237)) (a6989586621679975332 :: b6989586621679970237) (a6989586621679975333 :: [a6989586621679970238]) = Scanl a6989586621679975331 a6989586621679975332 a6989586621679975333
- data Scanl1Sym0 :: forall a6989586621679970236. (~>) ((~>) a6989586621679970236 ((~>) a6989586621679970236 a6989586621679970236)) ((~>) [a6989586621679970236] [a6989586621679970236])
- data Scanl1Sym1 (a6989586621679975324 :: (~>) a6989586621679970236 ((~>) a6989586621679970236 a6989586621679970236)) :: (~>) [a6989586621679970236] [a6989586621679970236]
- type Scanl1Sym2 (a6989586621679975324 :: (~>) a6989586621679970236 ((~>) a6989586621679970236 a6989586621679970236)) (a6989586621679975325 :: [a6989586621679970236]) = Scanl1 a6989586621679975324 a6989586621679975325
- data ScanrSym0 :: forall a6989586621679970234 b6989586621679970235. (~>) ((~>) a6989586621679970234 ((~>) b6989586621679970235 b6989586621679970235)) ((~>) b6989586621679970235 ((~>) [a6989586621679970234] [b6989586621679970235]))
- data ScanrSym1 (a6989586621679975303 :: (~>) a6989586621679970234 ((~>) b6989586621679970235 b6989586621679970235)) :: (~>) b6989586621679970235 ((~>) [a6989586621679970234] [b6989586621679970235])
- data ScanrSym2 (a6989586621679975303 :: (~>) a6989586621679970234 ((~>) b6989586621679970235 b6989586621679970235)) (a6989586621679975304 :: b6989586621679970235) :: (~>) [a6989586621679970234] [b6989586621679970235]
- type ScanrSym3 (a6989586621679975303 :: (~>) a6989586621679970234 ((~>) b6989586621679970235 b6989586621679970235)) (a6989586621679975304 :: b6989586621679970235) (a6989586621679975305 :: [a6989586621679970234]) = Scanr a6989586621679975303 a6989586621679975304 a6989586621679975305
- data Scanr1Sym0 :: forall a6989586621679970233. (~>) ((~>) a6989586621679970233 ((~>) a6989586621679970233 a6989586621679970233)) ((~>) [a6989586621679970233] [a6989586621679970233])
- data Scanr1Sym1 (a6989586621679975279 :: (~>) a6989586621679970233 ((~>) a6989586621679970233 a6989586621679970233)) :: (~>) [a6989586621679970233] [a6989586621679970233]
- type Scanr1Sym2 (a6989586621679975279 :: (~>) a6989586621679970233 ((~>) a6989586621679970233 a6989586621679970233)) (a6989586621679975280 :: [a6989586621679970233]) = Scanr1 a6989586621679975279 a6989586621679975280
- data MapAccumLSym0 :: forall a6989586621680800304 b6989586621680800305 c6989586621680800306 t6989586621680800303. (~>) ((~>) a6989586621680800304 ((~>) b6989586621680800305 (a6989586621680800304, c6989586621680800306))) ((~>) a6989586621680800304 ((~>) (t6989586621680800303 b6989586621680800305) (a6989586621680800304, t6989586621680800303 c6989586621680800306)))
- data MapAccumLSym1 (a6989586621680800807 :: (~>) a6989586621680800304 ((~>) b6989586621680800305 (a6989586621680800304, c6989586621680800306))) :: forall t6989586621680800303. (~>) a6989586621680800304 ((~>) (t6989586621680800303 b6989586621680800305) (a6989586621680800304, t6989586621680800303 c6989586621680800306))
- data MapAccumLSym2 (a6989586621680800807 :: (~>) a6989586621680800304 ((~>) b6989586621680800305 (a6989586621680800304, c6989586621680800306))) (a6989586621680800808 :: a6989586621680800304) :: forall t6989586621680800303. (~>) (t6989586621680800303 b6989586621680800305) (a6989586621680800304, t6989586621680800303 c6989586621680800306)
- type MapAccumLSym3 (a6989586621680800807 :: (~>) a6989586621680800304 ((~>) b6989586621680800305 (a6989586621680800304, c6989586621680800306))) (a6989586621680800808 :: a6989586621680800304) (a6989586621680800809 :: t6989586621680800303 b6989586621680800305) = MapAccumL a6989586621680800807 a6989586621680800808 a6989586621680800809
- data MapAccumRSym0 :: forall a6989586621680800300 b6989586621680800301 c6989586621680800302 t6989586621680800299. (~>) ((~>) a6989586621680800300 ((~>) b6989586621680800301 (a6989586621680800300, c6989586621680800302))) ((~>) a6989586621680800300 ((~>) (t6989586621680800299 b6989586621680800301) (a6989586621680800300, t6989586621680800299 c6989586621680800302)))
- data MapAccumRSym1 (a6989586621680800790 :: (~>) a6989586621680800300 ((~>) b6989586621680800301 (a6989586621680800300, c6989586621680800302))) :: forall t6989586621680800299. (~>) a6989586621680800300 ((~>) (t6989586621680800299 b6989586621680800301) (a6989586621680800300, t6989586621680800299 c6989586621680800302))
- data MapAccumRSym2 (a6989586621680800790 :: (~>) a6989586621680800300 ((~>) b6989586621680800301 (a6989586621680800300, c6989586621680800302))) (a6989586621680800791 :: a6989586621680800300) :: forall t6989586621680800299. (~>) (t6989586621680800299 b6989586621680800301) (a6989586621680800300, t6989586621680800299 c6989586621680800302)
- type MapAccumRSym3 (a6989586621680800790 :: (~>) a6989586621680800300 ((~>) b6989586621680800301 (a6989586621680800300, c6989586621680800302))) (a6989586621680800791 :: a6989586621680800300) (a6989586621680800792 :: t6989586621680800299 b6989586621680800301) = MapAccumR a6989586621680800790 a6989586621680800791 a6989586621680800792
- data ReplicateSym0 :: forall a6989586621679970141. (~>) Nat ((~>) a6989586621679970141 [a6989586621679970141])
- data ReplicateSym1 (a6989586621679974306 :: Nat) :: forall a6989586621679970141. (~>) a6989586621679970141 [a6989586621679970141]
- type ReplicateSym2 (a6989586621679974306 :: Nat) (a6989586621679974307 :: a6989586621679970141) = Replicate a6989586621679974306 a6989586621679974307
- data UnfoldrSym0 :: forall b6989586621679970225 a6989586621679970226. (~>) ((~>) b6989586621679970225 (Maybe (a6989586621679970226, b6989586621679970225))) ((~>) b6989586621679970225 [a6989586621679970226])
- data UnfoldrSym1 (a6989586621679975137 :: (~>) b6989586621679970225 (Maybe (a6989586621679970226, b6989586621679970225))) :: (~>) b6989586621679970225 [a6989586621679970226]
- type UnfoldrSym2 (a6989586621679975137 :: (~>) b6989586621679970225 (Maybe (a6989586621679970226, b6989586621679970225))) (a6989586621679975138 :: b6989586621679970225) = Unfoldr a6989586621679975137 a6989586621679975138
- data TakeSym0 :: forall a6989586621679970157. (~>) Nat ((~>) [a6989586621679970157] [a6989586621679970157])
- data TakeSym1 (a6989586621679974467 :: Nat) :: forall a6989586621679970157. (~>) [a6989586621679970157] [a6989586621679970157]
- type TakeSym2 (a6989586621679974467 :: Nat) (a6989586621679974468 :: [a6989586621679970157]) = Take a6989586621679974467 a6989586621679974468
- data DropSym0 :: forall a6989586621679970156. (~>) Nat ((~>) [a6989586621679970156] [a6989586621679970156])
- data DropSym1 (a6989586621679974453 :: Nat) :: forall a6989586621679970156. (~>) [a6989586621679970156] [a6989586621679970156]
- type DropSym2 (a6989586621679974453 :: Nat) (a6989586621679974454 :: [a6989586621679970156]) = Drop a6989586621679974453 a6989586621679974454
- data SplitAtSym0 :: forall a6989586621679970155. (~>) Nat ((~>) [a6989586621679970155] ([a6989586621679970155], [a6989586621679970155]))
- data SplitAtSym1 (a6989586621679974447 :: Nat) :: forall a6989586621679970155. (~>) [a6989586621679970155] ([a6989586621679970155], [a6989586621679970155])
- type SplitAtSym2 (a6989586621679974447 :: Nat) (a6989586621679974448 :: [a6989586621679970155]) = SplitAt a6989586621679974447 a6989586621679974448
- data TakeWhileSym0 :: forall a6989586621679970162. (~>) ((~>) a6989586621679970162 Bool) ((~>) [a6989586621679970162] [a6989586621679970162])
- data TakeWhileSym1 (a6989586621679974611 :: (~>) a6989586621679970162 Bool) :: (~>) [a6989586621679970162] [a6989586621679970162]
- type TakeWhileSym2 (a6989586621679974611 :: (~>) a6989586621679970162 Bool) (a6989586621679974612 :: [a6989586621679970162]) = TakeWhile a6989586621679974611 a6989586621679974612
- data DropWhileSym0 :: forall a6989586621679970161. (~>) ((~>) a6989586621679970161 Bool) ((~>) [a6989586621679970161] [a6989586621679970161])
- data DropWhileSym1 (a6989586621679974593 :: (~>) a6989586621679970161 Bool) :: (~>) [a6989586621679970161] [a6989586621679970161]
- type DropWhileSym2 (a6989586621679974593 :: (~>) a6989586621679970161 Bool) (a6989586621679974594 :: [a6989586621679970161]) = DropWhile a6989586621679974593 a6989586621679974594
- data DropWhileEndSym0 :: forall a6989586621679970160. (~>) ((~>) a6989586621679970160 Bool) ((~>) [a6989586621679970160] [a6989586621679970160])
- data DropWhileEndSym1 (a6989586621679974567 :: (~>) a6989586621679970160 Bool) :: (~>) [a6989586621679970160] [a6989586621679970160]
- type DropWhileEndSym2 (a6989586621679974567 :: (~>) a6989586621679970160 Bool) (a6989586621679974568 :: [a6989586621679970160]) = DropWhileEnd a6989586621679974567 a6989586621679974568
- data SpanSym0 :: forall a6989586621679970159. (~>) ((~>) a6989586621679970159 Bool) ((~>) [a6989586621679970159] ([a6989586621679970159], [a6989586621679970159]))
- data SpanSym1 (a6989586621679974524 :: (~>) a6989586621679970159 Bool) :: (~>) [a6989586621679970159] ([a6989586621679970159], [a6989586621679970159])
- type SpanSym2 (a6989586621679974524 :: (~>) a6989586621679970159 Bool) (a6989586621679974525 :: [a6989586621679970159]) = Span a6989586621679974524 a6989586621679974525
- data BreakSym0 :: forall a6989586621679970158. (~>) ((~>) a6989586621679970158 Bool) ((~>) [a6989586621679970158] ([a6989586621679970158], [a6989586621679970158]))
- data BreakSym1 (a6989586621679974481 :: (~>) a6989586621679970158 Bool) :: (~>) [a6989586621679970158] ([a6989586621679970158], [a6989586621679970158])
- type BreakSym2 (a6989586621679974481 :: (~>) a6989586621679970158 Bool) (a6989586621679974482 :: [a6989586621679970158]) = Break a6989586621679974481 a6989586621679974482
- data StripPrefixSym0 :: forall a6989586621680092348. (~>) [a6989586621680092348] ((~>) [a6989586621680092348] (Maybe [a6989586621680092348]))
- data StripPrefixSym1 (a6989586621680094044 :: [a6989586621680092348]) :: (~>) [a6989586621680092348] (Maybe [a6989586621680092348])
- type StripPrefixSym2 (a6989586621680094044 :: [a6989586621680092348]) (a6989586621680094045 :: [a6989586621680092348]) = StripPrefix a6989586621680094044 a6989586621680094045
- data GroupSym0 :: forall a6989586621679970154. (~>) [a6989586621679970154] [[a6989586621679970154]]
- type GroupSym1 (a6989586621679974444 :: [a6989586621679970154]) = Group a6989586621679974444
- data InitsSym0 :: forall a6989586621679970224. (~>) [a6989586621679970224] [[a6989586621679970224]]
- type InitsSym1 (a6989586621679975129 :: [a6989586621679970224]) = Inits a6989586621679975129
- data TailsSym0 :: forall a6989586621679970223. (~>) [a6989586621679970223] [[a6989586621679970223]]
- type TailsSym1 (a6989586621679975122 :: [a6989586621679970223]) = Tails a6989586621679975122
- data IsPrefixOfSym0 :: forall a6989586621679970222. (~>) [a6989586621679970222] ((~>) [a6989586621679970222] Bool)
- data IsPrefixOfSym1 (a6989586621679975114 :: [a6989586621679970222]) :: (~>) [a6989586621679970222] Bool
- type IsPrefixOfSym2 (a6989586621679975114 :: [a6989586621679970222]) (a6989586621679975115 :: [a6989586621679970222]) = IsPrefixOf a6989586621679975114 a6989586621679975115
- data IsSuffixOfSym0 :: forall a6989586621679970221. (~>) [a6989586621679970221] ((~>) [a6989586621679970221] Bool)
- data IsSuffixOfSym1 (a6989586621679975108 :: [a6989586621679970221]) :: (~>) [a6989586621679970221] Bool
- type IsSuffixOfSym2 (a6989586621679975108 :: [a6989586621679970221]) (a6989586621679975109 :: [a6989586621679970221]) = IsSuffixOf a6989586621679975108 a6989586621679975109
- data IsInfixOfSym0 :: forall a6989586621679970220. (~>) [a6989586621679970220] ((~>) [a6989586621679970220] Bool)
- data IsInfixOfSym1 (a6989586621679975102 :: [a6989586621679970220]) :: (~>) [a6989586621679970220] Bool
- type IsInfixOfSym2 (a6989586621679975102 :: [a6989586621679970220]) (a6989586621679975103 :: [a6989586621679970220]) = IsInfixOf a6989586621679975102 a6989586621679975103
- data ElemSym0 :: forall a6989586621680486596 t6989586621680486579. (~>) a6989586621680486596 ((~>) (t6989586621680486579 a6989586621680486596) Bool)
- data ElemSym1 (arg6989586621680487242 :: a6989586621680486596) :: forall t6989586621680486579. (~>) (t6989586621680486579 a6989586621680486596) Bool
- type ElemSym2 (arg6989586621680487242 :: a6989586621680486596) (arg6989586621680487243 :: t6989586621680486579 a6989586621680486596) = Elem arg6989586621680487242 arg6989586621680487243
- data NotElemSym0 :: forall a6989586621680486490 t6989586621680486489. (~>) a6989586621680486490 ((~>) (t6989586621680486489 a6989586621680486490) Bool)
- data NotElemSym1 (a6989586621680486968 :: a6989586621680486490) :: forall t6989586621680486489. (~>) (t6989586621680486489 a6989586621680486490) Bool
- type NotElemSym2 (a6989586621680486968 :: a6989586621680486490) (a6989586621680486969 :: t6989586621680486489 a6989586621680486490) = NotElem a6989586621680486968 a6989586621680486969
- data LookupSym0 :: forall a6989586621679970147 b6989586621679970148. (~>) a6989586621679970147 ((~>) [(a6989586621679970147, b6989586621679970148)] (Maybe b6989586621679970148))
- data LookupSym1 (a6989586621679974371 :: a6989586621679970147) :: forall b6989586621679970148. (~>) [(a6989586621679970147, b6989586621679970148)] (Maybe b6989586621679970148)
- type LookupSym2 (a6989586621679974371 :: a6989586621679970147) (a6989586621679974372 :: [(a6989586621679970147, b6989586621679970148)]) = Lookup a6989586621679974371 a6989586621679974372
- data FindSym0 :: forall a6989586621680486488 t6989586621680486487. (~>) ((~>) a6989586621680486488 Bool) ((~>) (t6989586621680486487 a6989586621680486488) (Maybe a6989586621680486488))
- data FindSym1 (a6989586621680486941 :: (~>) a6989586621680486488 Bool) :: forall t6989586621680486487. (~>) (t6989586621680486487 a6989586621680486488) (Maybe a6989586621680486488)
- type FindSym2 (a6989586621680486941 :: (~>) a6989586621680486488 Bool) (a6989586621680486942 :: t6989586621680486487 a6989586621680486488) = Find a6989586621680486941 a6989586621680486942
- data FilterSym0 :: forall a6989586621679970170. (~>) ((~>) a6989586621679970170 Bool) ((~>) [a6989586621679970170] [a6989586621679970170])
- data FilterSym1 (a6989586621679974725 :: (~>) a6989586621679970170 Bool) :: (~>) [a6989586621679970170] [a6989586621679970170]
- type FilterSym2 (a6989586621679974725 :: (~>) a6989586621679970170 Bool) (a6989586621679974726 :: [a6989586621679970170]) = Filter a6989586621679974725 a6989586621679974726
- data PartitionSym0 :: forall a6989586621679970146. (~>) ((~>) a6989586621679970146 Bool) ((~>) [a6989586621679970146] ([a6989586621679970146], [a6989586621679970146]))
- data PartitionSym1 (a6989586621679974365 :: (~>) a6989586621679970146 Bool) :: (~>) [a6989586621679970146] ([a6989586621679970146], [a6989586621679970146])
- type PartitionSym2 (a6989586621679974365 :: (~>) a6989586621679970146 Bool) (a6989586621679974366 :: [a6989586621679970146]) = Partition a6989586621679974365 a6989586621679974366
- data (!!@#@$) :: forall a6989586621679970139. (~>) [a6989586621679970139] ((~>) Nat a6989586621679970139)
- data (!!@#@$$) (a6989586621679974286 :: [a6989586621679970139]) :: (~>) Nat a6989586621679970139
- type (!!@#@$$$) (a6989586621679974286 :: [a6989586621679970139]) (a6989586621679974287 :: Nat) = (!!) a6989586621679974286 a6989586621679974287
- data ElemIndexSym0 :: forall a6989586621679970168. (~>) a6989586621679970168 ((~>) [a6989586621679970168] (Maybe Nat))
- data ElemIndexSym1 (a6989586621679974709 :: a6989586621679970168) :: (~>) [a6989586621679970168] (Maybe Nat)
- type ElemIndexSym2 (a6989586621679974709 :: a6989586621679970168) (a6989586621679974710 :: [a6989586621679970168]) = ElemIndex a6989586621679974709 a6989586621679974710
- data ElemIndicesSym0 :: forall a6989586621679970167. (~>) a6989586621679970167 ((~>) [a6989586621679970167] [Nat])
- data ElemIndicesSym1 (a6989586621679974701 :: a6989586621679970167) :: (~>) [a6989586621679970167] [Nat]
- type ElemIndicesSym2 (a6989586621679974701 :: a6989586621679970167) (a6989586621679974702 :: [a6989586621679970167]) = ElemIndices a6989586621679974701 a6989586621679974702
- data FindIndexSym0 :: forall a6989586621679970166. (~>) ((~>) a6989586621679970166 Bool) ((~>) [a6989586621679970166] (Maybe Nat))
- data FindIndexSym1 (a6989586621679974693 :: (~>) a6989586621679970166 Bool) :: (~>) [a6989586621679970166] (Maybe Nat)
- type FindIndexSym2 (a6989586621679974693 :: (~>) a6989586621679970166 Bool) (a6989586621679974694 :: [a6989586621679970166]) = FindIndex a6989586621679974693 a6989586621679974694
- data FindIndicesSym0 :: forall a6989586621679970165. (~>) ((~>) a6989586621679970165 Bool) ((~>) [a6989586621679970165] [Nat])
- data FindIndicesSym1 (a6989586621679974667 :: (~>) a6989586621679970165 Bool) :: (~>) [a6989586621679970165] [Nat]
- type FindIndicesSym2 (a6989586621679974667 :: (~>) a6989586621679970165 Bool) (a6989586621679974668 :: [a6989586621679970165]) = FindIndices a6989586621679974667 a6989586621679974668
- data ZipSym0 :: forall a6989586621679970216 b6989586621679970217. (~>) [a6989586621679970216] ((~>) [b6989586621679970217] [(a6989586621679970216, b6989586621679970217)])
- data ZipSym1 (a6989586621679975080 :: [a6989586621679970216]) :: forall b6989586621679970217. (~>) [b6989586621679970217] [(a6989586621679970216, b6989586621679970217)]
- type ZipSym2 (a6989586621679975080 :: [a6989586621679970216]) (a6989586621679975081 :: [b6989586621679970217]) = Zip a6989586621679975080 a6989586621679975081
- data Zip3Sym0 :: forall a6989586621679970213 b6989586621679970214 c6989586621679970215. (~>) [a6989586621679970213] ((~>) [b6989586621679970214] ((~>) [c6989586621679970215] [(a6989586621679970213, b6989586621679970214, c6989586621679970215)]))
- data Zip3Sym1 (a6989586621679975068 :: [a6989586621679970213]) :: forall b6989586621679970214 c6989586621679970215. (~>) [b6989586621679970214] ((~>) [c6989586621679970215] [(a6989586621679970213, b6989586621679970214, c6989586621679970215)])
- data Zip3Sym2 (a6989586621679975068 :: [a6989586621679970213]) (a6989586621679975069 :: [b6989586621679970214]) :: forall c6989586621679970215. (~>) [c6989586621679970215] [(a6989586621679970213, b6989586621679970214, c6989586621679970215)]
- type Zip3Sym3 (a6989586621679975068 :: [a6989586621679970213]) (a6989586621679975069 :: [b6989586621679970214]) (a6989586621679975070 :: [c6989586621679970215]) = Zip3 a6989586621679975068 a6989586621679975069 a6989586621679975070
- data Zip4Sym0 :: forall a6989586621680092344 b6989586621680092345 c6989586621680092346 d6989586621680092347. (~>) [a6989586621680092344] ((~>) [b6989586621680092345] ((~>) [c6989586621680092346] ((~>) [d6989586621680092347] [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)])))
- data Zip4Sym1 (a6989586621680094032 :: [a6989586621680092344]) :: forall b6989586621680092345 c6989586621680092346 d6989586621680092347. (~>) [b6989586621680092345] ((~>) [c6989586621680092346] ((~>) [d6989586621680092347] [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)]))
- data Zip4Sym2 (a6989586621680094032 :: [a6989586621680092344]) (a6989586621680094033 :: [b6989586621680092345]) :: forall c6989586621680092346 d6989586621680092347. (~>) [c6989586621680092346] ((~>) [d6989586621680092347] [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)])
- data Zip4Sym3 (a6989586621680094032 :: [a6989586621680092344]) (a6989586621680094033 :: [b6989586621680092345]) (a6989586621680094034 :: [c6989586621680092346]) :: forall d6989586621680092347. (~>) [d6989586621680092347] [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)]
- type Zip4Sym4 (a6989586621680094032 :: [a6989586621680092344]) (a6989586621680094033 :: [b6989586621680092345]) (a6989586621680094034 :: [c6989586621680092346]) (a6989586621680094035 :: [d6989586621680092347]) = Zip4 a6989586621680094032 a6989586621680094033 a6989586621680094034 a6989586621680094035
- data Zip5Sym0 :: forall a6989586621680092339 b6989586621680092340 c6989586621680092341 d6989586621680092342 e6989586621680092343. (~>) [a6989586621680092339] ((~>) [b6989586621680092340] ((~>) [c6989586621680092341] ((~>) [d6989586621680092342] ((~>) [e6989586621680092343] [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]))))
- data Zip5Sym1 (a6989586621680094009 :: [a6989586621680092339]) :: forall b6989586621680092340 c6989586621680092341 d6989586621680092342 e6989586621680092343. (~>) [b6989586621680092340] ((~>) [c6989586621680092341] ((~>) [d6989586621680092342] ((~>) [e6989586621680092343] [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)])))
- data Zip5Sym2 (a6989586621680094009 :: [a6989586621680092339]) (a6989586621680094010 :: [b6989586621680092340]) :: forall c6989586621680092341 d6989586621680092342 e6989586621680092343. (~>) [c6989586621680092341] ((~>) [d6989586621680092342] ((~>) [e6989586621680092343] [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]))
- data Zip5Sym3 (a6989586621680094009 :: [a6989586621680092339]) (a6989586621680094010 :: [b6989586621680092340]) (a6989586621680094011 :: [c6989586621680092341]) :: forall d6989586621680092342 e6989586621680092343. (~>) [d6989586621680092342] ((~>) [e6989586621680092343] [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)])
- data Zip5Sym4 (a6989586621680094009 :: [a6989586621680092339]) (a6989586621680094010 :: [b6989586621680092340]) (a6989586621680094011 :: [c6989586621680092341]) (a6989586621680094012 :: [d6989586621680092342]) :: forall e6989586621680092343. (~>) [e6989586621680092343] [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]
- type Zip5Sym5 (a6989586621680094009 :: [a6989586621680092339]) (a6989586621680094010 :: [b6989586621680092340]) (a6989586621680094011 :: [c6989586621680092341]) (a6989586621680094012 :: [d6989586621680092342]) (a6989586621680094013 :: [e6989586621680092343]) = Zip5 a6989586621680094009 a6989586621680094010 a6989586621680094011 a6989586621680094012 a6989586621680094013
- data Zip6Sym0 :: forall a6989586621680092333 b6989586621680092334 c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338. (~>) [a6989586621680092333] ((~>) [b6989586621680092334] ((~>) [c6989586621680092335] ((~>) [d6989586621680092336] ((~>) [e6989586621680092337] ((~>) [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])))))
- data Zip6Sym1 (a6989586621680093981 :: [a6989586621680092333]) :: forall b6989586621680092334 c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338. (~>) [b6989586621680092334] ((~>) [c6989586621680092335] ((~>) [d6989586621680092336] ((~>) [e6989586621680092337] ((~>) [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]))))
- data Zip6Sym2 (a6989586621680093981 :: [a6989586621680092333]) (a6989586621680093982 :: [b6989586621680092334]) :: forall c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338. (~>) [c6989586621680092335] ((~>) [d6989586621680092336] ((~>) [e6989586621680092337] ((~>) [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])))
- data Zip6Sym3 (a6989586621680093981 :: [a6989586621680092333]) (a6989586621680093982 :: [b6989586621680092334]) (a6989586621680093983 :: [c6989586621680092335]) :: forall d6989586621680092336 e6989586621680092337 f6989586621680092338. (~>) [d6989586621680092336] ((~>) [e6989586621680092337] ((~>) [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]))
- data Zip6Sym4 (a6989586621680093981 :: [a6989586621680092333]) (a6989586621680093982 :: [b6989586621680092334]) (a6989586621680093983 :: [c6989586621680092335]) (a6989586621680093984 :: [d6989586621680092336]) :: forall e6989586621680092337 f6989586621680092338. (~>) [e6989586621680092337] ((~>) [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])
- data Zip6Sym5 (a6989586621680093981 :: [a6989586621680092333]) (a6989586621680093982 :: [b6989586621680092334]) (a6989586621680093983 :: [c6989586621680092335]) (a6989586621680093984 :: [d6989586621680092336]) (a6989586621680093985 :: [e6989586621680092337]) :: forall f6989586621680092338. (~>) [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]
- type Zip6Sym6 (a6989586621680093981 :: [a6989586621680092333]) (a6989586621680093982 :: [b6989586621680092334]) (a6989586621680093983 :: [c6989586621680092335]) (a6989586621680093984 :: [d6989586621680092336]) (a6989586621680093985 :: [e6989586621680092337]) (a6989586621680093986 :: [f6989586621680092338]) = Zip6 a6989586621680093981 a6989586621680093982 a6989586621680093983 a6989586621680093984 a6989586621680093985 a6989586621680093986
- data Zip7Sym0 :: forall a6989586621680092326 b6989586621680092327 c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332. (~>) [a6989586621680092326] ((~>) [b6989586621680092327] ((~>) [c6989586621680092328] ((~>) [d6989586621680092329] ((~>) [e6989586621680092330] ((~>) [f6989586621680092331] ((~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))))))
- data Zip7Sym1 (a6989586621680093948 :: [a6989586621680092326]) :: forall b6989586621680092327 c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332. (~>) [b6989586621680092327] ((~>) [c6989586621680092328] ((~>) [d6989586621680092329] ((~>) [e6989586621680092330] ((~>) [f6989586621680092331] ((~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])))))
- data Zip7Sym2 (a6989586621680093948 :: [a6989586621680092326]) (a6989586621680093949 :: [b6989586621680092327]) :: forall c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332. (~>) [c6989586621680092328] ((~>) [d6989586621680092329] ((~>) [e6989586621680092330] ((~>) [f6989586621680092331] ((~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))))
- data Zip7Sym3 (a6989586621680093948 :: [a6989586621680092326]) (a6989586621680093949 :: [b6989586621680092327]) (a6989586621680093950 :: [c6989586621680092328]) :: forall d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332. (~>) [d6989586621680092329] ((~>) [e6989586621680092330] ((~>) [f6989586621680092331] ((~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])))
- data Zip7Sym4 (a6989586621680093948 :: [a6989586621680092326]) (a6989586621680093949 :: [b6989586621680092327]) (a6989586621680093950 :: [c6989586621680092328]) (a6989586621680093951 :: [d6989586621680092329]) :: forall e6989586621680092330 f6989586621680092331 g6989586621680092332. (~>) [e6989586621680092330] ((~>) [f6989586621680092331] ((~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))
- data Zip7Sym5 (a6989586621680093948 :: [a6989586621680092326]) (a6989586621680093949 :: [b6989586621680092327]) (a6989586621680093950 :: [c6989586621680092328]) (a6989586621680093951 :: [d6989586621680092329]) (a6989586621680093952 :: [e6989586621680092330]) :: forall f6989586621680092331 g6989586621680092332. (~>) [f6989586621680092331] ((~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])
- data Zip7Sym6 (a6989586621680093948 :: [a6989586621680092326]) (a6989586621680093949 :: [b6989586621680092327]) (a6989586621680093950 :: [c6989586621680092328]) (a6989586621680093951 :: [d6989586621680092329]) (a6989586621680093952 :: [e6989586621680092330]) (a6989586621680093953 :: [f6989586621680092331]) :: forall g6989586621680092332. (~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]
- type Zip7Sym7 (a6989586621680093948 :: [a6989586621680092326]) (a6989586621680093949 :: [b6989586621680092327]) (a6989586621680093950 :: [c6989586621680092328]) (a6989586621680093951 :: [d6989586621680092329]) (a6989586621680093952 :: [e6989586621680092330]) (a6989586621680093953 :: [f6989586621680092331]) (a6989586621680093954 :: [g6989586621680092332]) = Zip7 a6989586621680093948 a6989586621680093949 a6989586621680093950 a6989586621680093951 a6989586621680093952 a6989586621680093953 a6989586621680093954
- data ZipWithSym0 :: forall a6989586621679970210 b6989586621679970211 c6989586621679970212. (~>) ((~>) a6989586621679970210 ((~>) b6989586621679970211 c6989586621679970212)) ((~>) [a6989586621679970210] ((~>) [b6989586621679970211] [c6989586621679970212]))
- data ZipWithSym1 (a6989586621679975057 :: (~>) a6989586621679970210 ((~>) b6989586621679970211 c6989586621679970212)) :: (~>) [a6989586621679970210] ((~>) [b6989586621679970211] [c6989586621679970212])
- data ZipWithSym2 (a6989586621679975057 :: (~>) a6989586621679970210 ((~>) b6989586621679970211 c6989586621679970212)) (a6989586621679975058 :: [a6989586621679970210]) :: (~>) [b6989586621679970211] [c6989586621679970212]
- type ZipWithSym3 (a6989586621679975057 :: (~>) a6989586621679970210 ((~>) b6989586621679970211 c6989586621679970212)) (a6989586621679975058 :: [a6989586621679970210]) (a6989586621679975059 :: [b6989586621679970211]) = ZipWith a6989586621679975057 a6989586621679975058 a6989586621679975059
- data ZipWith3Sym0 :: forall a6989586621679970206 b6989586621679970207 c6989586621679970208 d6989586621679970209. (~>) ((~>) a6989586621679970206 ((~>) b6989586621679970207 ((~>) c6989586621679970208 d6989586621679970209))) ((~>) [a6989586621679970206] ((~>) [b6989586621679970207] ((~>) [c6989586621679970208] [d6989586621679970209])))
- data ZipWith3Sym1 (a6989586621679975042 :: (~>) a6989586621679970206 ((~>) b6989586621679970207 ((~>) c6989586621679970208 d6989586621679970209))) :: (~>) [a6989586621679970206] ((~>) [b6989586621679970207] ((~>) [c6989586621679970208] [d6989586621679970209]))
- data ZipWith3Sym2 (a6989586621679975042 :: (~>) a6989586621679970206 ((~>) b6989586621679970207 ((~>) c6989586621679970208 d6989586621679970209))) (a6989586621679975043 :: [a6989586621679970206]) :: (~>) [b6989586621679970207] ((~>) [c6989586621679970208] [d6989586621679970209])
- data ZipWith3Sym3 (a6989586621679975042 :: (~>) a6989586621679970206 ((~>) b6989586621679970207 ((~>) c6989586621679970208 d6989586621679970209))) (a6989586621679975043 :: [a6989586621679970206]) (a6989586621679975044 :: [b6989586621679970207]) :: (~>) [c6989586621679970208] [d6989586621679970209]
- type ZipWith3Sym4 (a6989586621679975042 :: (~>) a6989586621679970206 ((~>) b6989586621679970207 ((~>) c6989586621679970208 d6989586621679970209))) (a6989586621679975043 :: [a6989586621679970206]) (a6989586621679975044 :: [b6989586621679970207]) (a6989586621679975045 :: [c6989586621679970208]) = ZipWith3 a6989586621679975042 a6989586621679975043 a6989586621679975044 a6989586621679975045
- data ZipWith4Sym0 :: forall a6989586621680092321 b6989586621680092322 c6989586621680092323 d6989586621680092324 e6989586621680092325. (~>) ((~>) a6989586621680092321 ((~>) b6989586621680092322 ((~>) c6989586621680092323 ((~>) d6989586621680092324 e6989586621680092325)))) ((~>) [a6989586621680092321] ((~>) [b6989586621680092322] ((~>) [c6989586621680092323] ((~>) [d6989586621680092324] [e6989586621680092325]))))
- data ZipWith4Sym1 (a6989586621680093915 :: (~>) a6989586621680092321 ((~>) b6989586621680092322 ((~>) c6989586621680092323 ((~>) d6989586621680092324 e6989586621680092325)))) :: (~>) [a6989586621680092321] ((~>) [b6989586621680092322] ((~>) [c6989586621680092323] ((~>) [d6989586621680092324] [e6989586621680092325])))
- data ZipWith4Sym2 (a6989586621680093915 :: (~>) a6989586621680092321 ((~>) b6989586621680092322 ((~>) c6989586621680092323 ((~>) d6989586621680092324 e6989586621680092325)))) (a6989586621680093916 :: [a6989586621680092321]) :: (~>) [b6989586621680092322] ((~>) [c6989586621680092323] ((~>) [d6989586621680092324] [e6989586621680092325]))
- data ZipWith4Sym3 (a6989586621680093915 :: (~>) a6989586621680092321 ((~>) b6989586621680092322 ((~>) c6989586621680092323 ((~>) d6989586621680092324 e6989586621680092325)))) (a6989586621680093916 :: [a6989586621680092321]) (a6989586621680093917 :: [b6989586621680092322]) :: (~>) [c6989586621680092323] ((~>) [d6989586621680092324] [e6989586621680092325])
- data ZipWith4Sym4 (a6989586621680093915 :: (~>) a6989586621680092321 ((~>) b6989586621680092322 ((~>) c6989586621680092323 ((~>) d6989586621680092324 e6989586621680092325)))) (a6989586621680093916 :: [a6989586621680092321]) (a6989586621680093917 :: [b6989586621680092322]) (a6989586621680093918 :: [c6989586621680092323]) :: (~>) [d6989586621680092324] [e6989586621680092325]
- type ZipWith4Sym5 (a6989586621680093915 :: (~>) a6989586621680092321 ((~>) b6989586621680092322 ((~>) c6989586621680092323 ((~>) d6989586621680092324 e6989586621680092325)))) (a6989586621680093916 :: [a6989586621680092321]) (a6989586621680093917 :: [b6989586621680092322]) (a6989586621680093918 :: [c6989586621680092323]) (a6989586621680093919 :: [d6989586621680092324]) = ZipWith4 a6989586621680093915 a6989586621680093916 a6989586621680093917 a6989586621680093918 a6989586621680093919
- data ZipWith5Sym0 :: forall a6989586621680092315 b6989586621680092316 c6989586621680092317 d6989586621680092318 e6989586621680092319 f6989586621680092320. (~>) ((~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) ((~>) [a6989586621680092315] ((~>) [b6989586621680092316] ((~>) [c6989586621680092317] ((~>) [d6989586621680092318] ((~>) [e6989586621680092319] [f6989586621680092320])))))
- data ZipWith5Sym1 (a6989586621680093892 :: (~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) :: (~>) [a6989586621680092315] ((~>) [b6989586621680092316] ((~>) [c6989586621680092317] ((~>) [d6989586621680092318] ((~>) [e6989586621680092319] [f6989586621680092320]))))
- data ZipWith5Sym2 (a6989586621680093892 :: (~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) (a6989586621680093893 :: [a6989586621680092315]) :: (~>) [b6989586621680092316] ((~>) [c6989586621680092317] ((~>) [d6989586621680092318] ((~>) [e6989586621680092319] [f6989586621680092320])))
- data ZipWith5Sym3 (a6989586621680093892 :: (~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) (a6989586621680093893 :: [a6989586621680092315]) (a6989586621680093894 :: [b6989586621680092316]) :: (~>) [c6989586621680092317] ((~>) [d6989586621680092318] ((~>) [e6989586621680092319] [f6989586621680092320]))
- data ZipWith5Sym4 (a6989586621680093892 :: (~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) (a6989586621680093893 :: [a6989586621680092315]) (a6989586621680093894 :: [b6989586621680092316]) (a6989586621680093895 :: [c6989586621680092317]) :: (~>) [d6989586621680092318] ((~>) [e6989586621680092319] [f6989586621680092320])
- data ZipWith5Sym5 (a6989586621680093892 :: (~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) (a6989586621680093893 :: [a6989586621680092315]) (a6989586621680093894 :: [b6989586621680092316]) (a6989586621680093895 :: [c6989586621680092317]) (a6989586621680093896 :: [d6989586621680092318]) :: (~>) [e6989586621680092319] [f6989586621680092320]
- type ZipWith5Sym6 (a6989586621680093892 :: (~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) (a6989586621680093893 :: [a6989586621680092315]) (a6989586621680093894 :: [b6989586621680092316]) (a6989586621680093895 :: [c6989586621680092317]) (a6989586621680093896 :: [d6989586621680092318]) (a6989586621680093897 :: [e6989586621680092319]) = ZipWith5 a6989586621680093892 a6989586621680093893 a6989586621680093894 a6989586621680093895 a6989586621680093896 a6989586621680093897
- data ZipWith6Sym0 :: forall a6989586621680092308 b6989586621680092309 c6989586621680092310 d6989586621680092311 e6989586621680092312 f6989586621680092313 g6989586621680092314. (~>) ((~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) ((~>) [a6989586621680092308] ((~>) [b6989586621680092309] ((~>) [c6989586621680092310] ((~>) [d6989586621680092311] ((~>) [e6989586621680092312] ((~>) [f6989586621680092313] [g6989586621680092314]))))))
- data ZipWith6Sym1 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) :: (~>) [a6989586621680092308] ((~>) [b6989586621680092309] ((~>) [c6989586621680092310] ((~>) [d6989586621680092311] ((~>) [e6989586621680092312] ((~>) [f6989586621680092313] [g6989586621680092314])))))
- data ZipWith6Sym2 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) (a6989586621680093866 :: [a6989586621680092308]) :: (~>) [b6989586621680092309] ((~>) [c6989586621680092310] ((~>) [d6989586621680092311] ((~>) [e6989586621680092312] ((~>) [f6989586621680092313] [g6989586621680092314]))))
- data ZipWith6Sym3 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) (a6989586621680093866 :: [a6989586621680092308]) (a6989586621680093867 :: [b6989586621680092309]) :: (~>) [c6989586621680092310] ((~>) [d6989586621680092311] ((~>) [e6989586621680092312] ((~>) [f6989586621680092313] [g6989586621680092314])))
- data ZipWith6Sym4 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) (a6989586621680093866 :: [a6989586621680092308]) (a6989586621680093867 :: [b6989586621680092309]) (a6989586621680093868 :: [c6989586621680092310]) :: (~>) [d6989586621680092311] ((~>) [e6989586621680092312] ((~>) [f6989586621680092313] [g6989586621680092314]))
- data ZipWith6Sym5 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) (a6989586621680093866 :: [a6989586621680092308]) (a6989586621680093867 :: [b6989586621680092309]) (a6989586621680093868 :: [c6989586621680092310]) (a6989586621680093869 :: [d6989586621680092311]) :: (~>) [e6989586621680092312] ((~>) [f6989586621680092313] [g6989586621680092314])
- data ZipWith6Sym6 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) (a6989586621680093866 :: [a6989586621680092308]) (a6989586621680093867 :: [b6989586621680092309]) (a6989586621680093868 :: [c6989586621680092310]) (a6989586621680093869 :: [d6989586621680092311]) (a6989586621680093870 :: [e6989586621680092312]) :: (~>) [f6989586621680092313] [g6989586621680092314]
- type ZipWith6Sym7 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) (a6989586621680093866 :: [a6989586621680092308]) (a6989586621680093867 :: [b6989586621680092309]) (a6989586621680093868 :: [c6989586621680092310]) (a6989586621680093869 :: [d6989586621680092311]) (a6989586621680093870 :: [e6989586621680092312]) (a6989586621680093871 :: [f6989586621680092313]) = ZipWith6 a6989586621680093865 a6989586621680093866 a6989586621680093867 a6989586621680093868 a6989586621680093869 a6989586621680093870 a6989586621680093871
- data ZipWith7Sym0 :: forall a6989586621680092300 b6989586621680092301 c6989586621680092302 d6989586621680092303 e6989586621680092304 f6989586621680092305 g6989586621680092306 h6989586621680092307. (~>) ((~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) ((~>) [a6989586621680092300] ((~>) [b6989586621680092301] ((~>) [c6989586621680092302] ((~>) [d6989586621680092303] ((~>) [e6989586621680092304] ((~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307])))))))
- data ZipWith7Sym1 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) :: (~>) [a6989586621680092300] ((~>) [b6989586621680092301] ((~>) [c6989586621680092302] ((~>) [d6989586621680092303] ((~>) [e6989586621680092304] ((~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307]))))))
- data ZipWith7Sym2 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) :: (~>) [b6989586621680092301] ((~>) [c6989586621680092302] ((~>) [d6989586621680092303] ((~>) [e6989586621680092304] ((~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307])))))
- data ZipWith7Sym3 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) (a6989586621680093836 :: [b6989586621680092301]) :: (~>) [c6989586621680092302] ((~>) [d6989586621680092303] ((~>) [e6989586621680092304] ((~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307]))))
- data ZipWith7Sym4 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) (a6989586621680093836 :: [b6989586621680092301]) (a6989586621680093837 :: [c6989586621680092302]) :: (~>) [d6989586621680092303] ((~>) [e6989586621680092304] ((~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307])))
- data ZipWith7Sym5 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) (a6989586621680093836 :: [b6989586621680092301]) (a6989586621680093837 :: [c6989586621680092302]) (a6989586621680093838 :: [d6989586621680092303]) :: (~>) [e6989586621680092304] ((~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307]))
- data ZipWith7Sym6 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) (a6989586621680093836 :: [b6989586621680092301]) (a6989586621680093837 :: [c6989586621680092302]) (a6989586621680093838 :: [d6989586621680092303]) (a6989586621680093839 :: [e6989586621680092304]) :: (~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307])
- data ZipWith7Sym7 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) (a6989586621680093836 :: [b6989586621680092301]) (a6989586621680093837 :: [c6989586621680092302]) (a6989586621680093838 :: [d6989586621680092303]) (a6989586621680093839 :: [e6989586621680092304]) (a6989586621680093840 :: [f6989586621680092305]) :: (~>) [g6989586621680092306] [h6989586621680092307]
- type ZipWith7Sym8 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) (a6989586621680093836 :: [b6989586621680092301]) (a6989586621680093837 :: [c6989586621680092302]) (a6989586621680093838 :: [d6989586621680092303]) (a6989586621680093839 :: [e6989586621680092304]) (a6989586621680093840 :: [f6989586621680092305]) (a6989586621680093841 :: [g6989586621680092306]) = ZipWith7 a6989586621680093834 a6989586621680093835 a6989586621680093836 a6989586621680093837 a6989586621680093838 a6989586621680093839 a6989586621680093840 a6989586621680093841
- data UnzipSym0 :: forall a6989586621679970204 b6989586621679970205. (~>) [(a6989586621679970204, b6989586621679970205)] ([a6989586621679970204], [b6989586621679970205])
- type UnzipSym1 (a6989586621679975023 :: [(a6989586621679970204, b6989586621679970205)]) = Unzip a6989586621679975023
- data Unzip3Sym0 :: forall a6989586621679970201 b6989586621679970202 c6989586621679970203. (~>) [(a6989586621679970201, b6989586621679970202, c6989586621679970203)] ([a6989586621679970201], [b6989586621679970202], [c6989586621679970203])
- type Unzip3Sym1 (a6989586621679975002 :: [(a6989586621679970201, b6989586621679970202, c6989586621679970203)]) = Unzip3 a6989586621679975002
- data Unzip4Sym0 :: forall a6989586621679970197 b6989586621679970198 c6989586621679970199 d6989586621679970200. (~>) [(a6989586621679970197, b6989586621679970198, c6989586621679970199, d6989586621679970200)] ([a6989586621679970197], [b6989586621679970198], [c6989586621679970199], [d6989586621679970200])
- type Unzip4Sym1 (a6989586621679974979 :: [(a6989586621679970197, b6989586621679970198, c6989586621679970199, d6989586621679970200)]) = Unzip4 a6989586621679974979
- data Unzip5Sym0 :: forall a6989586621679970192 b6989586621679970193 c6989586621679970194 d6989586621679970195 e6989586621679970196. (~>) [(a6989586621679970192, b6989586621679970193, c6989586621679970194, d6989586621679970195, e6989586621679970196)] ([a6989586621679970192], [b6989586621679970193], [c6989586621679970194], [d6989586621679970195], [e6989586621679970196])
- type Unzip5Sym1 (a6989586621679974954 :: [(a6989586621679970192, b6989586621679970193, c6989586621679970194, d6989586621679970195, e6989586621679970196)]) = Unzip5 a6989586621679974954
- data Unzip6Sym0 :: forall a6989586621679970186 b6989586621679970187 c6989586621679970188 d6989586621679970189 e6989586621679970190 f6989586621679970191. (~>) [(a6989586621679970186, b6989586621679970187, c6989586621679970188, d6989586621679970189, e6989586621679970190, f6989586621679970191)] ([a6989586621679970186], [b6989586621679970187], [c6989586621679970188], [d6989586621679970189], [e6989586621679970190], [f6989586621679970191])
- type Unzip6Sym1 (a6989586621679974927 :: [(a6989586621679970186, b6989586621679970187, c6989586621679970188, d6989586621679970189, e6989586621679970190, f6989586621679970191)]) = Unzip6 a6989586621679974927
- data Unzip7Sym0 :: forall a6989586621679970179 b6989586621679970180 c6989586621679970181 d6989586621679970182 e6989586621679970183 f6989586621679970184 g6989586621679970185. (~>) [(a6989586621679970179, b6989586621679970180, c6989586621679970181, d6989586621679970182, e6989586621679970183, f6989586621679970184, g6989586621679970185)] ([a6989586621679970179], [b6989586621679970180], [c6989586621679970181], [d6989586621679970182], [e6989586621679970183], [f6989586621679970184], [g6989586621679970185])
- type Unzip7Sym1 (a6989586621679974898 :: [(a6989586621679970179, b6989586621679970180, c6989586621679970181, d6989586621679970182, e6989586621679970183, f6989586621679970184, g6989586621679970185)]) = Unzip7 a6989586621679974898
- data UnlinesSym0 :: (~>) [Symbol] Symbol
- type UnlinesSym1 (a6989586621679974894 :: [Symbol]) = Unlines a6989586621679974894
- data UnwordsSym0 :: (~>) [Symbol] Symbol
- type UnwordsSym1 (a6989586621679974883 :: [Symbol]) = Unwords a6989586621679974883
- data NubSym0 :: forall a6989586621679970138. (~>) [a6989586621679970138] [a6989586621679970138]
- type NubSym1 (a6989586621679974266 :: [a6989586621679970138]) = Nub a6989586621679974266
- data DeleteSym0 :: forall a6989586621679970178. (~>) a6989586621679970178 ((~>) [a6989586621679970178] [a6989586621679970178])
- data DeleteSym1 (a6989586621679974877 :: a6989586621679970178) :: (~>) [a6989586621679970178] [a6989586621679970178]
- type DeleteSym2 (a6989586621679974877 :: a6989586621679970178) (a6989586621679974878 :: [a6989586621679970178]) = Delete a6989586621679974877 a6989586621679974878
- data (\\@#@$) :: forall a6989586621679970177. (~>) [a6989586621679970177] ((~>) [a6989586621679970177] [a6989586621679970177])
- data (\\@#@$$) (a6989586621679974867 :: [a6989586621679970177]) :: (~>) [a6989586621679970177] [a6989586621679970177]
- type (\\@#@$$$) (a6989586621679974867 :: [a6989586621679970177]) (a6989586621679974868 :: [a6989586621679970177]) = (\\) a6989586621679974867 a6989586621679974868
- data UnionSym0 :: forall a6989586621679970134. (~>) [a6989586621679970134] ((~>) [a6989586621679970134] [a6989586621679970134])
- data UnionSym1 (a6989586621679974216 :: [a6989586621679970134]) :: (~>) [a6989586621679970134] [a6989586621679970134]
- type UnionSym2 (a6989586621679974216 :: [a6989586621679970134]) (a6989586621679974217 :: [a6989586621679970134]) = Union a6989586621679974216 a6989586621679974217
- data IntersectSym0 :: forall a6989586621679970164. (~>) [a6989586621679970164] ((~>) [a6989586621679970164] [a6989586621679970164])
- data IntersectSym1 (a6989586621679974661 :: [a6989586621679970164]) :: (~>) [a6989586621679970164] [a6989586621679970164]
- type IntersectSym2 (a6989586621679974661 :: [a6989586621679970164]) (a6989586621679974662 :: [a6989586621679970164]) = Intersect a6989586621679974661 a6989586621679974662
- data InsertSym0 :: forall a6989586621679970151. (~>) a6989586621679970151 ((~>) [a6989586621679970151] [a6989586621679970151])
- data InsertSym1 (a6989586621679974424 :: a6989586621679970151) :: (~>) [a6989586621679970151] [a6989586621679970151]
- type InsertSym2 (a6989586621679974424 :: a6989586621679970151) (a6989586621679974425 :: [a6989586621679970151]) = Insert a6989586621679974424 a6989586621679974425
- data SortSym0 :: forall a6989586621679970150. (~>) [a6989586621679970150] [a6989586621679970150]
- type SortSym1 (a6989586621679974421 :: [a6989586621679970150]) = Sort a6989586621679974421
- data NubBySym0 :: forall a6989586621679970137. (~>) ((~>) a6989586621679970137 ((~>) a6989586621679970137 Bool)) ((~>) [a6989586621679970137] [a6989586621679970137])
- data NubBySym1 (a6989586621679974241 :: (~>) a6989586621679970137 ((~>) a6989586621679970137 Bool)) :: (~>) [a6989586621679970137] [a6989586621679970137]
- type NubBySym2 (a6989586621679974241 :: (~>) a6989586621679970137 ((~>) a6989586621679970137 Bool)) (a6989586621679974242 :: [a6989586621679970137]) = NubBy a6989586621679974241 a6989586621679974242
- data DeleteBySym0 :: forall a6989586621679970176. (~>) ((~>) a6989586621679970176 ((~>) a6989586621679970176 Bool)) ((~>) a6989586621679970176 ((~>) [a6989586621679970176] [a6989586621679970176]))
- data DeleteBySym1 (a6989586621679974845 :: (~>) a6989586621679970176 ((~>) a6989586621679970176 Bool)) :: (~>) a6989586621679970176 ((~>) [a6989586621679970176] [a6989586621679970176])
- data DeleteBySym2 (a6989586621679974845 :: (~>) a6989586621679970176 ((~>) a6989586621679970176 Bool)) (a6989586621679974846 :: a6989586621679970176) :: (~>) [a6989586621679970176] [a6989586621679970176]
- type DeleteBySym3 (a6989586621679974845 :: (~>) a6989586621679970176 ((~>) a6989586621679970176 Bool)) (a6989586621679974846 :: a6989586621679970176) (a6989586621679974847 :: [a6989586621679970176]) = DeleteBy a6989586621679974845 a6989586621679974846 a6989586621679974847
- data DeleteFirstsBySym0 :: forall a6989586621679970175. (~>) ((~>) a6989586621679970175 ((~>) a6989586621679970175 Bool)) ((~>) [a6989586621679970175] ((~>) [a6989586621679970175] [a6989586621679970175]))
- data DeleteFirstsBySym1 (a6989586621679974832 :: (~>) a6989586621679970175 ((~>) a6989586621679970175 Bool)) :: (~>) [a6989586621679970175] ((~>) [a6989586621679970175] [a6989586621679970175])
- data DeleteFirstsBySym2 (a6989586621679974832 :: (~>) a6989586621679970175 ((~>) a6989586621679970175 Bool)) (a6989586621679974833 :: [a6989586621679970175]) :: (~>) [a6989586621679970175] [a6989586621679970175]
- type DeleteFirstsBySym3 (a6989586621679974832 :: (~>) a6989586621679970175 ((~>) a6989586621679970175 Bool)) (a6989586621679974833 :: [a6989586621679970175]) (a6989586621679974834 :: [a6989586621679970175]) = DeleteFirstsBy a6989586621679974832 a6989586621679974833 a6989586621679974834
- data UnionBySym0 :: forall a6989586621679970135. (~>) ((~>) a6989586621679970135 ((~>) a6989586621679970135 Bool)) ((~>) [a6989586621679970135] ((~>) [a6989586621679970135] [a6989586621679970135]))
- data UnionBySym1 (a6989586621679974222 :: (~>) a6989586621679970135 ((~>) a6989586621679970135 Bool)) :: (~>) [a6989586621679970135] ((~>) [a6989586621679970135] [a6989586621679970135])
- data UnionBySym2 (a6989586621679974222 :: (~>) a6989586621679970135 ((~>) a6989586621679970135 Bool)) (a6989586621679974223 :: [a6989586621679970135]) :: (~>) [a6989586621679970135] [a6989586621679970135]
- type UnionBySym3 (a6989586621679974222 :: (~>) a6989586621679970135 ((~>) a6989586621679970135 Bool)) (a6989586621679974223 :: [a6989586621679970135]) (a6989586621679974224 :: [a6989586621679970135]) = UnionBy a6989586621679974222 a6989586621679974223 a6989586621679974224
- data IntersectBySym0 :: forall a6989586621679970163. (~>) ((~>) a6989586621679970163 ((~>) a6989586621679970163 Bool)) ((~>) [a6989586621679970163] ((~>) [a6989586621679970163] [a6989586621679970163]))
- data IntersectBySym1 (a6989586621679974625 :: (~>) a6989586621679970163 ((~>) a6989586621679970163 Bool)) :: (~>) [a6989586621679970163] ((~>) [a6989586621679970163] [a6989586621679970163])
- data IntersectBySym2 (a6989586621679974625 :: (~>) a6989586621679970163 ((~>) a6989586621679970163 Bool)) (a6989586621679974626 :: [a6989586621679970163]) :: (~>) [a6989586621679970163] [a6989586621679970163]
- type IntersectBySym3 (a6989586621679974625 :: (~>) a6989586621679970163 ((~>) a6989586621679970163 Bool)) (a6989586621679974626 :: [a6989586621679970163]) (a6989586621679974627 :: [a6989586621679970163]) = IntersectBy a6989586621679974625 a6989586621679974626 a6989586621679974627
- data GroupBySym0 :: forall a6989586621679970149. (~>) ((~>) a6989586621679970149 ((~>) a6989586621679970149 Bool)) ((~>) [a6989586621679970149] [[a6989586621679970149]])
- data GroupBySym1 (a6989586621679974388 :: (~>) a6989586621679970149 ((~>) a6989586621679970149 Bool)) :: (~>) [a6989586621679970149] [[a6989586621679970149]]
- type GroupBySym2 (a6989586621679974388 :: (~>) a6989586621679970149 ((~>) a6989586621679970149 Bool)) (a6989586621679974389 :: [a6989586621679970149]) = GroupBy a6989586621679974388 a6989586621679974389
- data SortBySym0 :: forall a6989586621679970174. (~>) ((~>) a6989586621679970174 ((~>) a6989586621679970174 Ordering)) ((~>) [a6989586621679970174] [a6989586621679970174])
- data SortBySym1 (a6989586621679974824 :: (~>) a6989586621679970174 ((~>) a6989586621679970174 Ordering)) :: (~>) [a6989586621679970174] [a6989586621679970174]
- type SortBySym2 (a6989586621679974824 :: (~>) a6989586621679970174 ((~>) a6989586621679970174 Ordering)) (a6989586621679974825 :: [a6989586621679970174]) = SortBy a6989586621679974824 a6989586621679974825
- data InsertBySym0 :: forall a6989586621679970173. (~>) ((~>) a6989586621679970173 ((~>) a6989586621679970173 Ordering)) ((~>) a6989586621679970173 ((~>) [a6989586621679970173] [a6989586621679970173]))
- data InsertBySym1 (a6989586621679974800 :: (~>) a6989586621679970173 ((~>) a6989586621679970173 Ordering)) :: (~>) a6989586621679970173 ((~>) [a6989586621679970173] [a6989586621679970173])
- data InsertBySym2 (a6989586621679974800 :: (~>) a6989586621679970173 ((~>) a6989586621679970173 Ordering)) (a6989586621679974801 :: a6989586621679970173) :: (~>) [a6989586621679970173] [a6989586621679970173]
- type InsertBySym3 (a6989586621679974800 :: (~>) a6989586621679970173 ((~>) a6989586621679970173 Ordering)) (a6989586621679974801 :: a6989586621679970173) (a6989586621679974802 :: [a6989586621679970173]) = InsertBy a6989586621679974800 a6989586621679974801 a6989586621679974802
- data MaximumBySym0 :: forall a6989586621680486494 t6989586621680486493. (~>) ((~>) a6989586621680486494 ((~>) a6989586621680486494 Ordering)) ((~>) (t6989586621680486493 a6989586621680486494) a6989586621680486494)
- data MaximumBySym1 (a6989586621680487001 :: (~>) a6989586621680486494 ((~>) a6989586621680486494 Ordering)) :: forall t6989586621680486493. (~>) (t6989586621680486493 a6989586621680486494) a6989586621680486494
- type MaximumBySym2 (a6989586621680487001 :: (~>) a6989586621680486494 ((~>) a6989586621680486494 Ordering)) (a6989586621680487002 :: t6989586621680486493 a6989586621680486494) = MaximumBy a6989586621680487001 a6989586621680487002
- data MinimumBySym0 :: forall a6989586621680486492 t6989586621680486491. (~>) ((~>) a6989586621680486492 ((~>) a6989586621680486492 Ordering)) ((~>) (t6989586621680486491 a6989586621680486492) a6989586621680486492)
- data MinimumBySym1 (a6989586621680486976 :: (~>) a6989586621680486492 ((~>) a6989586621680486492 Ordering)) :: forall t6989586621680486491. (~>) (t6989586621680486491 a6989586621680486492) a6989586621680486492
- type MinimumBySym2 (a6989586621680486976 :: (~>) a6989586621680486492 ((~>) a6989586621680486492 Ordering)) (a6989586621680486977 :: t6989586621680486491 a6989586621680486492) = MinimumBy a6989586621680486976 a6989586621680486977
- data GenericLengthSym0 :: forall a6989586621679970133 i6989586621679970132. (~>) [a6989586621679970133] i6989586621679970132
- type GenericLengthSym1 (a6989586621679974209 :: [a6989586621679970133]) = GenericLength a6989586621679974209
- data GenericTakeSym0 :: forall i6989586621680092298 a6989586621680092299. (~>) i6989586621680092298 ((~>) [a6989586621680092299] [a6989586621680092299])
- data GenericTakeSym1 (a6989586621680093828 :: i6989586621680092298) :: forall a6989586621680092299. (~>) [a6989586621680092299] [a6989586621680092299]
- type GenericTakeSym2 (a6989586621680093828 :: i6989586621680092298) (a6989586621680093829 :: [a6989586621680092299]) = GenericTake a6989586621680093828 a6989586621680093829
- data GenericDropSym0 :: forall i6989586621680092296 a6989586621680092297. (~>) i6989586621680092296 ((~>) [a6989586621680092297] [a6989586621680092297])
- data GenericDropSym1 (a6989586621680093818 :: i6989586621680092296) :: forall a6989586621680092297. (~>) [a6989586621680092297] [a6989586621680092297]
- type GenericDropSym2 (a6989586621680093818 :: i6989586621680092296) (a6989586621680093819 :: [a6989586621680092297]) = GenericDrop a6989586621680093818 a6989586621680093819
- data GenericSplitAtSym0 :: forall i6989586621680092294 a6989586621680092295. (~>) i6989586621680092294 ((~>) [a6989586621680092295] ([a6989586621680092295], [a6989586621680092295]))
- data GenericSplitAtSym1 (a6989586621680093808 :: i6989586621680092294) :: forall a6989586621680092295. (~>) [a6989586621680092295] ([a6989586621680092295], [a6989586621680092295])
- type GenericSplitAtSym2 (a6989586621680093808 :: i6989586621680092294) (a6989586621680093809 :: [a6989586621680092295]) = GenericSplitAt a6989586621680093808 a6989586621680093809
- data GenericIndexSym0 :: forall a6989586621680092293 i6989586621680092292. (~>) [a6989586621680092293] ((~>) i6989586621680092292 a6989586621680092293)
- data GenericIndexSym1 (a6989586621680093798 :: [a6989586621680092293]) :: forall i6989586621680092292. (~>) i6989586621680092292 a6989586621680092293
- type GenericIndexSym2 (a6989586621680093798 :: [a6989586621680092293]) (a6989586621680093799 :: i6989586621680092292) = GenericIndex a6989586621680093798 a6989586621680093799
- data GenericReplicateSym0 :: forall i6989586621680092290 a6989586621680092291. (~>) i6989586621680092290 ((~>) a6989586621680092291 [a6989586621680092291])
- data GenericReplicateSym1 (a6989586621680093788 :: i6989586621680092290) :: forall a6989586621680092291. (~>) a6989586621680092291 [a6989586621680092291]
- type GenericReplicateSym2 (a6989586621680093788 :: i6989586621680092290) (a6989586621680093789 :: a6989586621680092291) = GenericReplicate a6989586621680093788 a6989586621680093789
The singleton for lists
type family Sing :: k -> Type Source #
The singleton kind-indexed type family.
Instances
data SList :: forall a. [a] -> Type where Source #
Constructors
SNil :: SList '[] | |
SCons :: forall a (n :: a) (n :: [a]). (Sing (n :: a)) -> (Sing (n :: [a])) -> SList ('(:) n n) infixr 5 |
Instances
(SDecide a, SDecide [a]) => TestCoercion (SList :: [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances Methods testCoercion :: forall (a0 :: k) (b :: k). SList a0 -> SList b -> Maybe (Coercion a0 b) | |
(SDecide a, SDecide [a]) => TestEquality (SList :: [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances Methods testEquality :: forall (a0 :: k) (b :: k). SList a0 -> SList b -> Maybe (a0 :~: b) | |
(ShowSing a, ShowSing [a]) => Show (SList z) | |
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 Null (a :: [a6989586621680486594]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (a :: [a6989586621680486594]) | |
type Null (arg0 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (arg0 :: Maybe a0) | |
type Null (arg0 :: NonEmpty a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (arg0 :: NonEmpty a0) | |
type Null (a :: Identity a6989586621680486594) Source # | |
Defined in Data.Singletons.Prelude.Identity type Null (a :: Identity a6989586621680486594) | |
type Null (arg0 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Null (arg0 :: First a0) | |
type Null (arg0 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Null (arg0 :: Last a0) | |
type Null (arg0 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Null (arg0 :: Max a0) | |
type Null (arg0 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Null (arg0 :: Min a0) | |
type Null (arg0 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Null (arg0 :: Option a0) | |
type Null (a :: Dual a6989586621680486594) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (a :: Dual a6989586621680486594) | |
type Null (a :: Product a6989586621680486594) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (a :: Product a6989586621680486594) | |
type Null (a :: Sum a6989586621680486594) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (a :: Sum a6989586621680486594) | |
type Null (arg0 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (arg0 :: First a0) | |
type Null (arg0 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (arg0 :: Last a0) | |
type Null (a2 :: Either a1 a6989586621680486594) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (a2 :: Either a1 a6989586621680486594) | |
type Null (arg0 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (arg0 :: (a, a0)) | |
type Null (arg0 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Null (arg0 :: Arg a a0) | |
type Null (arg0 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
type family Length (arg :: t a) :: Nat Source #
Instances
type Length (a :: [a6989586621680486595]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (a :: [a6989586621680486595]) | |
type Length (arg0 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (arg0 :: Maybe a0) | |
type Length (arg0 :: NonEmpty a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (arg0 :: NonEmpty a0) | |
type Length (a :: Identity a6989586621680486595) Source # | |
Defined in Data.Singletons.Prelude.Identity type Length (a :: Identity a6989586621680486595) | |
type Length (arg0 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Length (arg0 :: First a0) | |
type Length (arg0 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Length (arg0 :: Last a0) | |
type Length (arg0 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Length (arg0 :: Max a0) | |
type Length (arg0 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Length (arg0 :: Min a0) | |
type Length (arg0 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Length (arg0 :: Option a0) | |
type Length (a :: Dual a6989586621680486595) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (a :: Dual a6989586621680486595) | |
type Length (a :: Product a6989586621680486595) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (a :: Product a6989586621680486595) | |
type Length (a :: Sum a6989586621680486595) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (a :: Sum a6989586621680486595) | |
type Length (arg0 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (arg0 :: First a0) | |
type Length (arg0 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (arg0 :: Last a0) | |
type Length (a2 :: Either a1 a6989586621680486595) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (a2 :: Either a1 a6989586621680486595) | |
type Length (arg0 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (arg0 :: (a, a0)) | |
type Length (arg0 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Length (arg0 :: Arg a a0) | |
type Length (arg0 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
List transformations
sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b]) Source #
type family Intersperse (a :: a) (a :: [a]) :: [a] where ... Source #
Equations
Intersperse _ '[] = '[] | |
Intersperse sep ('(:) x xs) = Apply (Apply (:@#@$) x) (Apply (Apply PrependToAllSym0 sep) xs) |
sIntersperse :: forall a (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a]) Source #
type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ... Source #
Equations
Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) |
sIntercalate :: forall a (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a]) Source #
sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]]) Source #
type family Subsequences (a :: [a]) :: [[a]] where ... Source #
Equations
Subsequences xs = Apply (Apply (:@#@$) '[]) (Apply NonEmptySubsequencesSym0 xs) |
sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]]) Source #
type family Permutations (a :: [a]) :: [[a]] where ... Source #
sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]]) Source #
Reducing lists (folds)
type family Foldl (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #
Instances
type Foldl (a1 :: k2 ~> (a6989586621680486588 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680486588) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680486588 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680486588]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680486588 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680486588) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680486588 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680486588) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680486588 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680486588) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680486588 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680486588) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680486588 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680486588) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source #
type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #
Instances
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680486590 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680486590]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: NonEmpty a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680486590 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680486590) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680486590 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680486590) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680486590 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680486590) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680486590 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680486590) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) Source #
type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #
Instances
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) Source #
sFoldl1' :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a) Source #
type family Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b Source #
Instances
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680486583]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Min a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Max a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (arg1 :: a0 ~> (b0 ~> b0)) (arg2 :: b0) (arg3 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a2 :: a6989586621680486583 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Either a1 a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a6989586621680486583 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: (a1, a6989586621680486583)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a6989586621680486583 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Arg a1 a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680486583 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Const m a6989586621680486583) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source #
type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #
Instances
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) Source #
Special folds
sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a]) Source #
sConcatMap :: forall a b t (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) Source #
type family And (a :: t Bool) :: Bool where ... Source #
Equations
And x = Case_6989586621680487066 x (Let6989586621680487064Scrutinee_6989586621680486826Sym1 x) |
type family Or (a :: t Bool) :: Bool where ... Source #
Equations
Or x = Case_6989586621680487057 x (Let6989586621680487055Scrutinee_6989586621680486828Sym1 x) |
type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #
Equations
Any p x = Case_6989586621680487048 p x (Let6989586621680487045Scrutinee_6989586621680486830Sym2 p x) |
sAny :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool) Source #
type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #
Equations
All p x = Case_6989586621680487035 p x (Let6989586621680487032Scrutinee_6989586621680486832Sym2 p x) |
sAll :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) Source #
type family Sum (arg :: t a) :: a Source #
Instances
type Sum (a :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Sum (a :: [k2]) | |
type Sum (arg0 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Sum (arg0 :: Maybe a0) | |
type Sum (arg0 :: NonEmpty a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Sum (arg0 :: NonEmpty a0) | |
type Sum (a :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity type Sum (a :: Identity k2) | |
type Sum (arg0 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Sum (arg0 :: First a0) | |
type Sum (arg0 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Sum (arg0 :: Last a0) | |
type Sum (arg0 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Sum (arg0 :: Max a0) | |
type Sum (arg0 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Sum (arg0 :: Min a0) | |
type Sum (arg0 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Sum (arg0 :: Option a0) | |
type Sum (a :: Dual k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Sum (a :: Dual k2) | |
type Sum (a :: Product k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Sum (a :: Product k2) | |
type Sum (a :: Sum k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Sum (a :: Sum k2) | |
type Sum (arg0 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Sum (arg0 :: First a0) | |
type Sum (arg0 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Sum (arg0 :: Last a0) | |
type Sum (arg0 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Sum (arg0 :: Either a a0) | |
type Sum (arg0 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Sum (arg0 :: (a, a0)) | |
type Sum (arg0 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Sum (arg0 :: Arg a a0) | |
type Sum (arg0 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
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
type Product (a :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Product (a :: [k2]) | |
type Product (arg0 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Product (arg0 :: Maybe a0) | |
type Product (arg0 :: NonEmpty a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Product (arg0 :: NonEmpty a0) | |
type Product (a :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity type Product (a :: Identity k2) | |
type Product (arg0 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Product (arg0 :: First a0) | |
type Product (arg0 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Product (arg0 :: Last a0) | |
type Product (arg0 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Product (arg0 :: Max a0) | |
type Product (arg0 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Product (arg0 :: Min a0) | |
type Product (arg0 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Product (arg0 :: Option a0) | |
type Product (a :: Dual k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Product (a :: Dual k2) | |
type Product (a :: Product k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Product (a :: Product k2) | |
type Product (a :: Sum k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Product (a :: Sum k2) | |
type Product (arg0 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Product (arg0 :: First a0) | |
type Product (arg0 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Product (arg0 :: Last a0) | |
type Product (arg0 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Product (arg0 :: Either a a0) | |
type Product (arg0 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Product (arg0 :: (a, a0)) | |
type Product (arg0 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Product (arg0 :: Arg a a0) | |
type Product (arg0 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
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
type Maximum (a :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Maximum (a :: [k2]) | |
type Maximum (arg0 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Maximum (arg0 :: Maybe a0) | |
type Maximum (arg0 :: NonEmpty a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Maximum (arg0 :: NonEmpty a0) | |
type Maximum (a :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity type Maximum (a :: Identity k2) | |
type Maximum (arg0 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Maximum (arg0 :: First a0) | |
type Maximum (arg0 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Maximum (arg0 :: Last a0) | |
type Maximum (arg0 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Maximum (arg0 :: Max a0) | |
type Maximum (arg0 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Maximum (arg0 :: Min a0) | |
type Maximum (arg0 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Maximum (arg0 :: Option a0) | |
type Maximum (a :: Dual k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Maximum (a :: Dual k2) | |
type Maximum (a :: Product k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Maximum (a :: Product k2) | |
type Maximum (a :: Sum k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Maximum (a :: Sum k2) | |
type Maximum (arg0 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Maximum (arg0 :: First a0) | |
type Maximum (arg0 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Maximum (arg0 :: Last a0) | |
type Maximum (arg0 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Maximum (arg0 :: Either a a0) | |
type Maximum (arg0 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Maximum (arg0 :: (a, a0)) | |
type Maximum (arg0 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Maximum (arg0 :: Arg a a0) | |
type Maximum (arg0 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a) Source #
type family Minimum (arg :: t a) :: a Source #
Instances
type Minimum (a :: [k2]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Minimum (a :: [k2]) | |
type Minimum (arg0 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Minimum (arg0 :: Maybe a0) | |
type Minimum (arg0 :: NonEmpty a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Minimum (arg0 :: NonEmpty a0) | |
type Minimum (a :: Identity k2) Source # | |
Defined in Data.Singletons.Prelude.Identity type Minimum (a :: Identity k2) | |
type Minimum (arg0 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Minimum (arg0 :: First a0) | |
type Minimum (arg0 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Minimum (arg0 :: Last a0) | |
type Minimum (arg0 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Minimum (arg0 :: Max a0) | |
type Minimum (arg0 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Minimum (arg0 :: Min a0) | |
type Minimum (arg0 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Minimum (arg0 :: Option a0) | |
type Minimum (a :: Dual k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Minimum (a :: Dual k2) | |
type Minimum (a :: Product k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Minimum (a :: Product k2) | |
type Minimum (a :: Sum k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Minimum (a :: Sum k2) | |
type Minimum (arg0 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Minimum (arg0 :: First a0) | |
type Minimum (arg0 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Minimum (arg0 :: Last a0) | |
type Minimum (arg0 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Minimum (arg0 :: Either a a0) | |
type Minimum (arg0 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Minimum (arg0 :: (a, a0)) | |
type Minimum (arg0 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Minimum (arg0 :: Arg a a0) | |
type Minimum (arg0 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a) Source #
Building lists
Scans
sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b]) Source #
sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a]) Source #
sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b]) Source #
type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ... Source #
Equations
Scanr1 _ '[] = '[] | |
Scanr1 _ '[x] = Apply (Apply (:@#@$) x) '[] | |
Scanr1 f ('(:) x ('(:) wild_6989586621679970740 wild_6989586621679970742)) = Case_6989586621679975298 f x wild_6989586621679970740 wild_6989586621679970742 (Let6989586621679975293Scrutinee_6989586621679970734Sym4 f x wild_6989586621679970740 wild_6989586621679970742) |
sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a]) Source #
Accumulating maps
type family MapAccumL (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ... Source #
Equations
MapAccumL f s t = Case_6989586621680800820 f s t (Let6989586621680800816Scrutinee_6989586621680800387Sym3 f s t) |
sMapAccumL :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (a, t c)) Source #
type family MapAccumR (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ... Source #
Equations
MapAccumR f s t = Case_6989586621680800803 f s t (Let6989586621680800799Scrutinee_6989586621680800391Sym3 f s t) |
sMapAccumR :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c)) Source #
Cyclical lists
type family Replicate (a :: Nat) (a :: a) :: [a] where ... Source #
Equations
Replicate n x = Case_6989586621679974315 n x (Let6989586621679974312Scrutinee_6989586621679970836Sym2 n x) |
sReplicate :: forall a (t :: Nat) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a]) Source #
Unfolding
type family Unfoldr (a :: (~>) b (Maybe (a, b))) (a :: b) :: [a] where ... Source #
Equations
Unfoldr f b = Case_6989586621679975146 f b (Let6989586621679975143Scrutinee_6989586621679970744Sym2 f b) |
sUnfoldr :: forall b a (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a]) Source #
Sublists
Extracting sublists
sTake :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) Source #
sDrop :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) Source #
sSplitAt :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) Source #
sTakeWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) Source #
sDropWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) Source #
type family DropWhileEnd (a :: (~>) a Bool) (a :: [a]) :: [a] where ... Source #
sDropWhileEnd :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a]) Source #
type family Span (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
Span _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679974528XsSym0) Let6989586621679974528XsSym0 | |
Span p ('(:) x xs') = Case_6989586621679974540 p x xs' (Let6989586621679974536Scrutinee_6989586621679970816Sym3 p x xs') |
sSpan :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) Source #
type family Break (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
Break _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679974485XsSym0) Let6989586621679974485XsSym0 | |
Break p ('(:) x xs') = Case_6989586621679974497 p x xs' (Let6989586621679974493Scrutinee_6989586621679970818Sym3 p x xs') |
sBreak :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) Source #
type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ... Source #
Equations
StripPrefix '[] ys = Apply JustSym0 ys | |
StripPrefix arg_6989586621680092416 arg_6989586621680092418 = Case_6989586621680094051 arg_6989586621680092416 arg_6989586621680092418 (Apply (Apply Tuple2Sym0 arg_6989586621680092416) arg_6989586621680092418) |
type family Group (a :: [a]) :: [[a]] where ... Source #
Equations
Group xs = Apply (Apply GroupBySym0 (==@#@$)) xs |
Predicates
type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
Equations
IsPrefixOf '[] '[] = TrueSym0 | |
IsPrefixOf '[] ('(:) _ _) = TrueSym0 | |
IsPrefixOf ('(:) _ _) '[] = FalseSym0 | |
IsPrefixOf ('(:) x xs) ('(:) y ys) = Apply (Apply (&&@#@$) (Apply (Apply (==@#@$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) |
sIsPrefixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) Source #
type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
Equations
IsSuffixOf x y = Apply (Apply IsPrefixOfSym0 (Apply ReverseSym0 x)) (Apply ReverseSym0 y) |
sIsSuffixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) Source #
sIsInfixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool) Source #
Searching lists
Searching by equality
type family Elem (arg :: a) (arg :: t a) :: Bool Source #
Instances
type Elem (arg1 :: a0) (arg2 :: Maybe a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (arg1 :: a0) (arg2 :: Maybe a0) | |
type Elem (a1 :: k1) (a2 :: [k1]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (a1 :: k1) (a2 :: [k1]) | |
type Elem (arg1 :: a0) (arg2 :: NonEmpty a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (arg1 :: a0) (arg2 :: NonEmpty a0) | |
type Elem (a1 :: k1) (a2 :: Dual k1) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (a1 :: k1) (a2 :: Dual k1) | |
type Elem (a1 :: k1) (a2 :: Sum k1) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (a1 :: k1) (a2 :: Sum k1) | |
type Elem (a1 :: k1) (a2 :: Product k1) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (a1 :: k1) (a2 :: Product k1) | |
type Elem (arg1 :: a0) (arg2 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (arg1 :: a0) (arg2 :: First a0) | |
type Elem (arg1 :: a0) (arg2 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (arg1 :: a0) (arg2 :: Last a0) | |
type Elem (a1 :: k1) (a2 :: Identity k1) Source # | |
Defined in Data.Singletons.Prelude.Identity type Elem (a1 :: k1) (a2 :: Identity k1) | |
type Elem (arg1 :: a0) (arg2 :: Min a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Elem (arg1 :: a0) (arg2 :: Min a0) | |
type Elem (arg1 :: a0) (arg2 :: Max a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Elem (arg1 :: a0) (arg2 :: Max a0) | |
type Elem (arg1 :: a0) (arg2 :: First a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Elem (arg1 :: a0) (arg2 :: First a0) | |
type Elem (arg1 :: a0) (arg2 :: Last a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Elem (arg1 :: a0) (arg2 :: Last a0) | |
type Elem (arg1 :: a0) (arg2 :: Option a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Elem (arg1 :: a0) (arg2 :: Option a0) | |
type Elem (arg1 :: a0) (arg2 :: Either a a0) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (arg1 :: a0) (arg2 :: Either a a0) | |
type Elem (arg1 :: a0) (arg2 :: (a, a0)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Elem (arg1 :: a0) (arg2 :: (a, a0)) | |
type Elem (arg1 :: a0) (arg2 :: Arg a a0) Source # | |
Defined in Data.Singletons.Prelude.Semigroup type Elem (arg1 :: a0) (arg2 :: Arg a a0) | |
type Elem (arg1 :: a0) (arg2 :: Const m a0) Source # | |
Defined in Data.Singletons.Prelude.Const |
sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) Source #
sNotElem :: forall a t (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) Source #
type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... Source #
Equations
Lookup _key '[] = NothingSym0 | |
Lookup key ('(:) '(x, y) xys) = Case_6989586621679974385 key x y xys (Let6989586621679974380Scrutinee_6989586621679970832Sym4 key x y xys) |
sLookup :: forall a b (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b) Source #
Searching with a predicate
type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ... Source #
Equations
Find p y = Case_6989586621680486964 p y (Let6989586621680486947Scrutinee_6989586621680486838Sym2 p y) |
sFind :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a) Source #
sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) Source #
sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) Source #
Indexing lists
(%!!) :: forall a (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) infixl 9 Source #
sElemIndex :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat) Source #
type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ... Source #
Equations
ElemIndices x a_6989586621679974705 = Apply (Apply FindIndicesSym0 (Apply (==@#@$) x)) a_6989586621679974705 |
sElemIndices :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat]) Source #
type family FindIndex (a :: (~>) a Bool) (a :: [a]) :: Maybe Nat where ... Source #
Equations
FindIndex p a_6989586621679974697 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679974697 |
sFindIndex :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat) Source #
type family FindIndices (a :: (~>) a Bool) (a :: [a]) :: [Nat] where ... Source #
sFindIndices :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat]) Source #
Zipping and unzipping lists
sZip :: forall a b (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)]) Source #
type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ... Source #
Equations
Zip3 ('(:) a as) ('(:) b bs) ('(:) c cs) = Apply (Apply (:@#@$) (Apply (Apply (Apply Tuple3Sym0 a) b) c)) (Apply (Apply (Apply Zip3Sym0 as) bs) cs) | |
Zip3 '[] '[] '[] = '[] | |
Zip3 '[] '[] ('(:) _ _) = '[] | |
Zip3 '[] ('(:) _ _) '[] = '[] | |
Zip3 '[] ('(:) _ _) ('(:) _ _) = '[] | |
Zip3 ('(:) _ _) '[] '[] = '[] | |
Zip3 ('(:) _ _) '[] ('(:) _ _) = '[] | |
Zip3 ('(:) _ _) ('(:) _ _) '[] = '[] |
sZip3 :: forall a b c (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)]) Source #
type family Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ... Source #
Equations
Zip4 a_6989586621680094024 a_6989586621680094026 a_6989586621680094028 a_6989586621680094030 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621680094024) a_6989586621680094026) a_6989586621680094028) a_6989586621680094030 |
type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ... Source #
Equations
Zip5 a_6989586621680093999 a_6989586621680094001 a_6989586621680094003 a_6989586621680094005 a_6989586621680094007 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621680093999) a_6989586621680094001) a_6989586621680094003) a_6989586621680094005) a_6989586621680094007 |
type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ... Source #
Equations
Zip6 a_6989586621680093969 a_6989586621680093971 a_6989586621680093973 a_6989586621680093975 a_6989586621680093977 a_6989586621680093979 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621680093969) a_6989586621680093971) a_6989586621680093973) a_6989586621680093975) a_6989586621680093977) a_6989586621680093979 |
type family Zip7 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [(a, b, c, d, e, f, g)] where ... Source #
Equations
Zip7 a_6989586621680093934 a_6989586621680093936 a_6989586621680093938 a_6989586621680093940 a_6989586621680093942 a_6989586621680093944 a_6989586621680093946 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621680093934) a_6989586621680093936) a_6989586621680093938) a_6989586621680093940) a_6989586621680093942) a_6989586621680093944) a_6989586621680093946 |
sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c]) Source #
type family ZipWith3 (a :: (~>) a ((~>) b ((~>) c d))) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ... Source #
Equations
ZipWith3 z ('(:) a as) ('(:) b bs) ('(:) c cs) = Apply (Apply (:@#@$) (Apply (Apply (Apply z a) b) c)) (Apply (Apply (Apply (Apply ZipWith3Sym0 z) as) bs) cs) | |
ZipWith3 _ '[] '[] '[] = '[] | |
ZipWith3 _ '[] '[] ('(:) _ _) = '[] | |
ZipWith3 _ '[] ('(:) _ _) '[] = '[] | |
ZipWith3 _ '[] ('(:) _ _) ('(:) _ _) = '[] | |
ZipWith3 _ ('(:) _ _) '[] '[] = '[] | |
ZipWith3 _ ('(:) _ _) '[] ('(:) _ _) = '[] | |
ZipWith3 _ ('(:) _ _) ('(:) _ _) '[] = '[] |
sZipWith3 :: forall a b c d (t :: (~>) a ((~>) b ((~>) c d))) (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d]) Source #
type family ZipWith4 (a :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ... Source #
type family ZipWith5 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ... Source #
type family ZipWith6 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ... Source #
type family ZipWith7 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ... Source #
Equations
ZipWith7 z ('(:) a as) ('(:) b bs) ('(:) c cs) ('(:) d ds) ('(:) e es) ('(:) f fs) ('(:) g gs) = Apply (Apply (:@#@$) (Apply (Apply (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e) f) g)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 z) as) bs) cs) ds) es) fs) gs) | |
ZipWith7 _ _ _ _ _ _ _ _ = '[] |
sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c])) Source #
sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d])) Source #
sUnzip5 :: forall a b c d e (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e])) Source #
sUnzip6 :: forall a b c d e f (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f])) Source #
type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... Source #
sUnzip7 :: forall a b c d e f g (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g])) Source #
Special lists
Functions on Symbol
s
"Set" operations
sDelete :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a]) Source #
(%\\) :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (\\@#@$) t) t :: [a]) infix 5 Source #
sUnion :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a]) Source #
sIntersect :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a]) Source #
Ordered lists
type family Insert (a :: a) (a :: [a]) :: [a] where ... Source #
Equations
Insert e ls = Apply (Apply (Apply InsertBySym0 CompareSym0) e) ls |
sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a]) Source #
type family Sort (a :: [a]) :: [a] where ... Source #
Equations
Sort a_6989586621679974419 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679974419 |
Generalized functions
The "By
" operations
User-supplied equality (replacing an Eq
context)
The predicate is assumed to define an equivalence.
sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a]) Source #
sDeleteBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a]) Source #
type family DeleteFirstsBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ... Source #
Equations
DeleteFirstsBy eq a_6989586621679974838 a_6989586621679974840 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679974838) a_6989586621679974840 |
sDeleteFirstsBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a]) Source #
sUnionBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a]) Source #
type family IntersectBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ... Source #
Equations
IntersectBy _ '[] '[] = '[] | |
IntersectBy _ '[] ('(:) _ _) = '[] | |
IntersectBy _ ('(:) _ _) '[] = '[] | |
IntersectBy eq ('(:) wild_6989586621679970802 wild_6989586621679970804) ('(:) wild_6989586621679970806 wild_6989586621679970808) = Apply (Apply (>>=@#@$) (Let6989586621679974636XsSym5 eq wild_6989586621679970802 wild_6989586621679970804 wild_6989586621679970806 wild_6989586621679970808)) (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679974647Sym0 eq) wild_6989586621679970802) wild_6989586621679970804) wild_6989586621679970806) wild_6989586621679970808) |
sIntersectBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a]) Source #
sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]]) Source #
User-supplied comparison (replacing an Ord
context)
The function is assumed to define a total ordering.
sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a]) Source #
sInsertBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a]) Source #
type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #
Equations
MaximumBy cmp a_6989586621680487005 = Apply (Apply Foldl1Sym0 (Let6989586621680487009Max'Sym2 cmp a_6989586621680487005)) a_6989586621680487005 |
sMaximumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) Source #
type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #
Equations
MinimumBy cmp a_6989586621680486980 = Apply (Apply Foldl1Sym0 (Let6989586621680486984Min'Sym2 cmp a_6989586621680486980)) a_6989586621680486980 |
sMinimumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) Source #
The "generic
" operations
The prefix `generic
' indicates an overloaded function that
is a generalized version of a Prelude function.
type family GenericLength (a :: [a]) :: i where ... Source #
Equations
GenericLength '[] = FromInteger 0 | |
GenericLength ('(:) _ xs) = Apply (Apply (+@#@$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
sGenericLength :: forall a i (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i) Source #
type family GenericTake (a :: i) (a :: [a]) :: [a] where ... Source #
Equations
GenericTake a_6989586621680093824 a_6989586621680093826 = Apply (Apply TakeSym0 a_6989586621680093824) a_6989586621680093826 |
type family GenericDrop (a :: i) (a :: [a]) :: [a] where ... Source #
Equations
GenericDrop a_6989586621680093814 a_6989586621680093816 = Apply (Apply DropSym0 a_6989586621680093814) a_6989586621680093816 |
type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
GenericSplitAt a_6989586621680093804 a_6989586621680093806 = Apply (Apply SplitAtSym0 a_6989586621680093804) a_6989586621680093806 |
type family GenericIndex (a :: [a]) (a :: i) :: a where ... Source #
Equations
GenericIndex a_6989586621680093794 a_6989586621680093796 = Apply (Apply (!!@#@$) a_6989586621680093794) a_6989586621680093796 |
type family GenericReplicate (a :: i) (a :: a) :: [a] where ... Source #
Equations
GenericReplicate a_6989586621680093784 a_6989586621680093786 = Apply (Apply ReplicateSym0 a_6989586621680093784) a_6989586621680093786 |
Defunctionalization symbols
data (:@#@$) :: forall (a3530822107858468865 :: Type). (~>) a3530822107858468865 ((~>) [a3530822107858468865] [a3530822107858468865 :: Type]) infixr 5 Source #
Instances
SingI ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((:@#@$) :: TyFun a3530822107858468865 ([a3530822107858468865] ~> [a3530822107858468865]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances Methods suppressUnusedWarnings :: () Source # | |
type Apply ((:@#@$) :: TyFun a3530822107858468865 ([a3530822107858468865] ~> [a3530822107858468865]) -> Type) (t6989586621679310906 :: a3530822107858468865) Source # | |
data (:@#@$$) (t6989586621679310906 :: a3530822107858468865 :: Type) :: (~>) [a3530822107858468865] [a3530822107858468865 :: Type] infixr 5 Source #
Instances
SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((:@#@$$) t6989586621679310906 :: TyFun [a3530822107858468865] [a3530822107858468865] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances Methods suppressUnusedWarnings :: () Source # | |
type Apply ((:@#@$$) t6989586621679310906 :: TyFun [a] [a] -> Type) (t6989586621679310907 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Instances |
type (:@#@$$$) (t6989586621679310906 :: a3530822107858468865) (t6989586621679310907 :: [a3530822107858468865]) = '(:) t6989586621679310906 t6989586621679310907 Source #
type (++@#@$$$) (a6989586621679541707 :: [a6989586621679541510]) (a6989586621679541708 :: [a6989586621679541510]) = (++) a6989586621679541707 a6989586621679541708 Source #
data (++@#@$$) (a6989586621679541707 :: [a6989586621679541510]) :: (~>) [a6989586621679541510] [a6989586621679541510] infixr 5 Source #
Instances
SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((++@#@$$) a6989586621679541707 :: TyFun [a6989586621679541510] [a6989586621679541510] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$$) a6989586621679541707 :: TyFun [a] [a] -> Type) (a6989586621679541708 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Base |
data (++@#@$) :: forall a6989586621679541510. (~>) [a6989586621679541510] ((~>) [a6989586621679541510] [a6989586621679541510]) infixr 5 Source #
Instances
SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679541510] ([a6989586621679541510] ~> [a6989586621679541510]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$) :: TyFun [a6989586621679541510] ([a6989586621679541510] ~> [a6989586621679541510]) -> Type) (a6989586621679541707 :: [a6989586621679541510]) Source # | |
data HeadSym0 :: forall a6989586621679970260. (~>) [a6989586621679970260] a6989586621679970260 Source #
Instances
SingI (HeadSym0 :: TyFun [a] a -> Type) Source # | |
SuppressUnusedWarnings (HeadSym0 :: TyFun [a6989586621679970260] a6989586621679970260 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679975607 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data LastSym0 :: forall a6989586621679970259. (~>) [a6989586621679970259] a6989586621679970259 Source #
Instances
SingI (LastSym0 :: TyFun [a] a -> Type) Source # | |
SuppressUnusedWarnings (LastSym0 :: TyFun [a6989586621679970259] a6989586621679970259 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679975602 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data TailSym0 :: forall a6989586621679970258. (~>) [a6989586621679970258] [a6989586621679970258] Source #
Instances
SingI (TailSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (TailSym0 :: TyFun [a6989586621679970258] [a6989586621679970258] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679975599 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data InitSym0 :: forall a6989586621679970257. (~>) [a6989586621679970257] [a6989586621679970257] Source #
Instances
SingI (InitSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (InitSym0 :: TyFun [a6989586621679970257] [a6989586621679970257] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679975585 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data NullSym0 :: forall t6989586621680486579 a6989586621680486594. (~>) (t6989586621680486579 a6989586621680486594) Bool Source #
Instances
SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680486579 a6989586621680486594) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680487238 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type NullSym1 (arg6989586621680487238 :: t6989586621680486579 a6989586621680486594) = Null arg6989586621680487238 Source #
data LengthSym0 :: forall t6989586621680486579 a6989586621680486595. (~>) (t6989586621680486579 a6989586621680486595) Nat Source #
Instances
SFoldable t => SingI (LengthSym0 :: TyFun (t a) Nat -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing LengthSym0 Source # | |
SuppressUnusedWarnings (LengthSym0 :: TyFun (t6989586621680486579 a6989586621680486595) Nat -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (arg6989586621680487240 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (arg6989586621680487240 :: t a) = Length arg6989586621680487240 |
type LengthSym1 (arg6989586621680487240 :: t6989586621680486579 a6989586621680486595) = Length arg6989586621680487240 Source #
data MapSym0 :: forall a6989586621679541511 b6989586621679541512. (~>) ((~>) a6989586621679541511 b6989586621679541512) ((~>) [a6989586621679541511] [b6989586621679541512]) Source #
Instances
SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (MapSym0 :: TyFun (a6989586621679541511 ~> b6989586621679541512) ([a6989586621679541511] ~> [b6989586621679541512]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapSym0 :: TyFun (a6989586621679541511 ~> b6989586621679541512) ([a6989586621679541511] ~> [b6989586621679541512]) -> Type) (a6989586621679541715 :: a6989586621679541511 ~> b6989586621679541512) Source # | |
data MapSym1 (a6989586621679541715 :: (~>) a6989586621679541511 b6989586621679541512) :: (~>) [a6989586621679541511] [b6989586621679541512] Source #
Instances
SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (MapSym1 a6989586621679541715 :: TyFun [a6989586621679541511] [b6989586621679541512] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapSym1 a6989586621679541715 :: TyFun [a] [b] -> Type) (a6989586621679541716 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Base |
type MapSym2 (a6989586621679541715 :: (~>) a6989586621679541511 b6989586621679541512) (a6989586621679541716 :: [a6989586621679541511]) = Map a6989586621679541715 a6989586621679541716 Source #
data ReverseSym0 :: forall a6989586621679970255. (~>) [a6989586621679970255] [a6989586621679970255] Source #
Instances
SingI (ReverseSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing ReverseSym0 Source # | |
SuppressUnusedWarnings (ReverseSym0 :: TyFun [a6989586621679970255] [a6989586621679970255] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679975570 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679975570 :: [a]) = Reverse a6989586621679975570 |
type ReverseSym1 (a6989586621679975570 :: [a6989586621679970255]) = Reverse a6989586621679975570 Source #
data IntersperseSym0 :: forall a6989586621679970254. (~>) a6989586621679970254 ((~>) [a6989586621679970254] [a6989586621679970254]) Source #
Instances
SingI (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679970254 ([a6989586621679970254] ~> [a6989586621679970254]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym0 :: TyFun a6989586621679970254 ([a6989586621679970254] ~> [a6989586621679970254]) -> Type) (a6989586621679975563 :: a6989586621679970254) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym0 :: TyFun a6989586621679970254 ([a6989586621679970254] ~> [a6989586621679970254]) -> Type) (a6989586621679975563 :: a6989586621679970254) = IntersperseSym1 a6989586621679975563 |
data IntersperseSym1 (a6989586621679975563 :: a6989586621679970254) :: (~>) [a6989586621679970254] [a6989586621679970254] Source #
Instances
SingI d => SingI (IntersperseSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IntersperseSym1 d) Source # | |
SuppressUnusedWarnings (IntersperseSym1 a6989586621679975563 :: TyFun [a6989586621679970254] [a6989586621679970254] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym1 a6989586621679975563 :: TyFun [a] [a] -> Type) (a6989586621679975564 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym1 a6989586621679975563 :: TyFun [a] [a] -> Type) (a6989586621679975564 :: [a]) = Intersperse a6989586621679975563 a6989586621679975564 |
type IntersperseSym2 (a6989586621679975563 :: a6989586621679970254) (a6989586621679975564 :: [a6989586621679970254]) = Intersperse a6989586621679975563 a6989586621679975564 Source #
data IntercalateSym0 :: forall a6989586621679970253. (~>) [a6989586621679970253] ((~>) [[a6989586621679970253]] [a6989586621679970253]) Source #
Instances
SingI (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a6989586621679970253] ([[a6989586621679970253]] ~> [a6989586621679970253]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym0 :: TyFun [a6989586621679970253] ([[a6989586621679970253]] ~> [a6989586621679970253]) -> Type) (a6989586621679975557 :: [a6989586621679970253]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym0 :: TyFun [a6989586621679970253] ([[a6989586621679970253]] ~> [a6989586621679970253]) -> Type) (a6989586621679975557 :: [a6989586621679970253]) = IntercalateSym1 a6989586621679975557 |
data IntercalateSym1 (a6989586621679975557 :: [a6989586621679970253]) :: (~>) [[a6989586621679970253]] [a6989586621679970253] Source #
Instances
SingI d => SingI (IntercalateSym1 d :: TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IntercalateSym1 d) Source # | |
SuppressUnusedWarnings (IntercalateSym1 a6989586621679975557 :: TyFun [[a6989586621679970253]] [a6989586621679970253] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym1 a6989586621679975557 :: TyFun [[a]] [a] -> Type) (a6989586621679975558 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym1 a6989586621679975557 :: TyFun [[a]] [a] -> Type) (a6989586621679975558 :: [[a]]) = Intercalate a6989586621679975557 a6989586621679975558 |
type IntercalateSym2 (a6989586621679975557 :: [a6989586621679970253]) (a6989586621679975558 :: [[a6989586621679970253]]) = Intercalate a6989586621679975557 a6989586621679975558 Source #
data TransposeSym0 :: forall a6989586621679970140. (~>) [[a6989586621679970140]] [[a6989586621679970140]] Source #
Instances
SingI (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing TransposeSym0 Source # | |
SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a6989586621679970140]] [[a6989586621679970140]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679974300 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679974300 :: [[a]]) = Transpose a6989586621679974300 |
type TransposeSym1 (a6989586621679974300 :: [[a6989586621679970140]]) = Transpose a6989586621679974300 Source #
data SubsequencesSym0 :: forall a6989586621679970252. (~>) [a6989586621679970252] [[a6989586621679970252]] Source #
Instances
SingI (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a6989586621679970252] [[a6989586621679970252]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679975554 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679975554 :: [a]) = Subsequences a6989586621679975554 |
type SubsequencesSym1 (a6989586621679975554 :: [a6989586621679970252]) = Subsequences a6989586621679975554 Source #
data PermutationsSym0 :: forall a6989586621679970249. (~>) [a6989586621679970249] [[a6989586621679970249]] Source #
Instances
SingI (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a6989586621679970249] [[a6989586621679970249]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679975436 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679975436 :: [a]) = Permutations a6989586621679975436 |
type PermutationsSym1 (a6989586621679975436 :: [a6989586621679970249]) = Permutations a6989586621679975436 Source #
data FoldlSym0 :: forall b6989586621680486587 a6989586621680486588 t6989586621680486579. (~>) ((~>) b6989586621680486587 ((~>) a6989586621680486588 b6989586621680486587)) ((~>) b6989586621680486587 ((~>) (t6989586621680486579 a6989586621680486588) b6989586621680486587)) Source #
Instances
SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym0 :: TyFun (b6989586621680486587 ~> (a6989586621680486588 ~> b6989586621680486587)) (b6989586621680486587 ~> (t6989586621680486579 a6989586621680486588 ~> b6989586621680486587)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym0 :: TyFun (b6989586621680486587 ~> (a6989586621680486588 ~> b6989586621680486587)) (b6989586621680486587 ~> (t6989586621680486579 a6989586621680486588 ~> b6989586621680486587)) -> Type) (arg6989586621680487216 :: b6989586621680486587 ~> (a6989586621680486588 ~> b6989586621680486587)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldlSym0 :: TyFun (b6989586621680486587 ~> (a6989586621680486588 ~> b6989586621680486587)) (b6989586621680486587 ~> (t6989586621680486579 a6989586621680486588 ~> b6989586621680486587)) -> Type) (arg6989586621680487216 :: b6989586621680486587 ~> (a6989586621680486588 ~> b6989586621680486587)) = FoldlSym1 arg6989586621680487216 t6989586621680486579 :: TyFun b6989586621680486587 (t6989586621680486579 a6989586621680486588 ~> b6989586621680486587) -> Type |
data FoldlSym1 (arg6989586621680487216 :: (~>) b6989586621680486587 ((~>) a6989586621680486588 b6989586621680486587)) :: forall t6989586621680486579. (~>) b6989586621680486587 ((~>) (t6989586621680486579 a6989586621680486588) b6989586621680486587) Source #
Instances
(SFoldable t, SingI d) => SingI (FoldlSym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym1 arg6989586621680487216 t6989586621680486579 :: TyFun b6989586621680486587 (t6989586621680486579 a6989586621680486588 ~> b6989586621680486587) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym1 arg6989586621680487216 t6989586621680486579 :: TyFun b6989586621680486587 (t6989586621680486579 a6989586621680486588 ~> b6989586621680486587) -> Type) (arg6989586621680487217 :: b6989586621680486587) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldlSym1 arg6989586621680487216 t6989586621680486579 :: TyFun b6989586621680486587 (t6989586621680486579 a6989586621680486588 ~> b6989586621680486587) -> Type) (arg6989586621680487217 :: b6989586621680486587) = FoldlSym2 arg6989586621680487216 arg6989586621680487217 t6989586621680486579 :: TyFun (t6989586621680486579 a6989586621680486588) b6989586621680486587 -> Type |
data FoldlSym2 (arg6989586621680487216 :: (~>) b6989586621680486587 ((~>) a6989586621680486588 b6989586621680486587)) (arg6989586621680487217 :: b6989586621680486587) :: forall t6989586621680486579. (~>) (t6989586621680486579 a6989586621680486588) b6989586621680486587 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym2 arg6989586621680487217 arg6989586621680487216 t6989586621680486579 :: TyFun (t6989586621680486579 a6989586621680486588) b6989586621680486587 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym2 arg6989586621680487217 arg6989586621680487216 t :: TyFun (t a) b -> Type) (arg6989586621680487218 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type FoldlSym3 (arg6989586621680487216 :: (~>) b6989586621680486587 ((~>) a6989586621680486588 b6989586621680486587)) (arg6989586621680487217 :: b6989586621680486587) (arg6989586621680487218 :: t6989586621680486579 a6989586621680486588) = Foldl arg6989586621680487216 arg6989586621680487217 arg6989586621680487218 Source #
data Foldl'Sym0 :: forall b6989586621680486589 a6989586621680486590 t6989586621680486579. (~>) ((~>) b6989586621680486589 ((~>) a6989586621680486590 b6989586621680486589)) ((~>) b6989586621680486589 ((~>) (t6989586621680486579 a6989586621680486590) b6989586621680486589)) Source #
Instances
SFoldable t => SingI (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing Foldl'Sym0 Source # | |
SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (b6989586621680486589 ~> (a6989586621680486590 ~> b6989586621680486589)) (b6989586621680486589 ~> (t6989586621680486579 a6989586621680486590 ~> b6989586621680486589)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym0 :: TyFun (b6989586621680486589 ~> (a6989586621680486590 ~> b6989586621680486589)) (b6989586621680486589 ~> (t6989586621680486579 a6989586621680486590 ~> b6989586621680486589)) -> Type) (arg6989586621680487222 :: b6989586621680486589 ~> (a6989586621680486590 ~> b6989586621680486589)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym0 :: TyFun (b6989586621680486589 ~> (a6989586621680486590 ~> b6989586621680486589)) (b6989586621680486589 ~> (t6989586621680486579 a6989586621680486590 ~> b6989586621680486589)) -> Type) (arg6989586621680487222 :: b6989586621680486589 ~> (a6989586621680486590 ~> b6989586621680486589)) = Foldl'Sym1 arg6989586621680487222 t6989586621680486579 :: TyFun b6989586621680486589 (t6989586621680486579 a6989586621680486590 ~> b6989586621680486589) -> Type |
data Foldl'Sym1 (arg6989586621680487222 :: (~>) b6989586621680486589 ((~>) a6989586621680486590 b6989586621680486589)) :: forall t6989586621680486579. (~>) b6989586621680486589 ((~>) (t6989586621680486579 a6989586621680486590) b6989586621680486589) Source #
Instances
(SFoldable t, SingI d) => SingI (Foldl'Sym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (Foldl'Sym1 d t) Source # | |
SuppressUnusedWarnings (Foldl'Sym1 arg6989586621680487222 t6989586621680486579 :: TyFun b6989586621680486589 (t6989586621680486579 a6989586621680486590 ~> b6989586621680486589) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym1 arg6989586621680487222 t6989586621680486579 :: TyFun b6989586621680486589 (t6989586621680486579 a6989586621680486590 ~> b6989586621680486589) -> Type) (arg6989586621680487223 :: b6989586621680486589) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym1 arg6989586621680487222 t6989586621680486579 :: TyFun b6989586621680486589 (t6989586621680486579 a6989586621680486590 ~> b6989586621680486589) -> Type) (arg6989586621680487223 :: b6989586621680486589) = Foldl'Sym2 arg6989586621680487222 arg6989586621680487223 t6989586621680486579 :: TyFun (t6989586621680486579 a6989586621680486590) b6989586621680486589 -> Type |
data Foldl'Sym2 (arg6989586621680487222 :: (~>) b6989586621680486589 ((~>) a6989586621680486590 b6989586621680486589)) (arg6989586621680487223 :: b6989586621680486589) :: forall t6989586621680486579. (~>) (t6989586621680486579 a6989586621680486590) b6989586621680486589 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (Foldl'Sym2 d1 d2 t :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (Foldl'Sym2 d1 d2 t) Source # | |
SuppressUnusedWarnings (Foldl'Sym2 arg6989586621680487223 arg6989586621680487222 t6989586621680486579 :: TyFun (t6989586621680486579 a6989586621680486590) b6989586621680486589 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym2 arg6989586621680487223 arg6989586621680487222 t :: TyFun (t a) b -> Type) (arg6989586621680487224 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym2 arg6989586621680487223 arg6989586621680487222 t :: TyFun (t a) b -> Type) (arg6989586621680487224 :: t a) = Foldl' arg6989586621680487223 arg6989586621680487222 arg6989586621680487224 |
type Foldl'Sym3 (arg6989586621680487222 :: (~>) b6989586621680486589 ((~>) a6989586621680486590 b6989586621680486589)) (arg6989586621680487223 :: b6989586621680486589) (arg6989586621680487224 :: t6989586621680486579 a6989586621680486590) = Foldl' arg6989586621680487222 arg6989586621680487223 arg6989586621680487224 Source #
data Foldl1Sym0 :: forall a6989586621680486592 t6989586621680486579. (~>) ((~>) a6989586621680486592 ((~>) a6989586621680486592 a6989586621680486592)) ((~>) (t6989586621680486579 a6989586621680486592) a6989586621680486592) Source #
Instances
SFoldable t => SingI (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing Foldl1Sym0 Source # | |
SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (a6989586621680486592 ~> (a6989586621680486592 ~> a6989586621680486592)) (t6989586621680486579 a6989586621680486592 ~> a6989586621680486592) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym0 :: TyFun (a6989586621680486592 ~> (a6989586621680486592 ~> a6989586621680486592)) (t6989586621680486579 a6989586621680486592 ~> a6989586621680486592) -> Type) (arg6989586621680487232 :: a6989586621680486592 ~> (a6989586621680486592 ~> a6989586621680486592)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl1Sym0 :: TyFun (a6989586621680486592 ~> (a6989586621680486592 ~> a6989586621680486592)) (t6989586621680486579 a6989586621680486592 ~> a6989586621680486592) -> Type) (arg6989586621680487232 :: a6989586621680486592 ~> (a6989586621680486592 ~> a6989586621680486592)) = Foldl1Sym1 arg6989586621680487232 t6989586621680486579 :: TyFun (t6989586621680486579 a6989586621680486592) a6989586621680486592 -> Type |
data Foldl1Sym1 (arg6989586621680487232 :: (~>) a6989586621680486592 ((~>) a6989586621680486592 a6989586621680486592)) :: forall t6989586621680486579. (~>) (t6989586621680486579 a6989586621680486592) a6989586621680486592 Source #
Instances
(SFoldable t, SingI d) => SingI (Foldl1Sym1 d t :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (Foldl1Sym1 d t) Source # | |
SuppressUnusedWarnings (Foldl1Sym1 arg6989586621680487232 t6989586621680486579 :: TyFun (t6989586621680486579 a6989586621680486592) a6989586621680486592 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym1 arg6989586621680487232 t :: TyFun (t a) a -> Type) (arg6989586621680487233 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl1Sym1 arg6989586621680487232 t :: TyFun (t a) a -> Type) (arg6989586621680487233 :: t a) = Foldl1 arg6989586621680487232 arg6989586621680487233 |
type Foldl1Sym2 (arg6989586621680487232 :: (~>) a6989586621680486592 ((~>) a6989586621680486592 a6989586621680486592)) (arg6989586621680487233 :: t6989586621680486579 a6989586621680486592) = Foldl1 arg6989586621680487232 arg6989586621680487233 Source #
data Foldl1'Sym0 :: forall a6989586621679970245. (~>) ((~>) a6989586621679970245 ((~>) a6989586621679970245 a6989586621679970245)) ((~>) [a6989586621679970245] a6989586621679970245) Source #
Instances
SingI (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Foldl1'Sym0 Source # | |
SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (a6989586621679970245 ~> (a6989586621679970245 ~> a6989586621679970245)) ([a6989586621679970245] ~> a6989586621679970245) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym0 :: TyFun (a6989586621679970245 ~> (a6989586621679970245 ~> a6989586621679970245)) ([a6989586621679970245] ~> a6989586621679970245) -> Type) (a6989586621679975394 :: a6989586621679970245 ~> (a6989586621679970245 ~> a6989586621679970245)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym0 :: TyFun (a6989586621679970245 ~> (a6989586621679970245 ~> a6989586621679970245)) ([a6989586621679970245] ~> a6989586621679970245) -> Type) (a6989586621679975394 :: a6989586621679970245 ~> (a6989586621679970245 ~> a6989586621679970245)) = Foldl1'Sym1 a6989586621679975394 |
data Foldl1'Sym1 (a6989586621679975394 :: (~>) a6989586621679970245 ((~>) a6989586621679970245 a6989586621679970245)) :: (~>) [a6989586621679970245] a6989586621679970245 Source #
Instances
SingI d => SingI (Foldl1'Sym1 d :: TyFun [a] a -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (Foldl1'Sym1 d) Source # | |
SuppressUnusedWarnings (Foldl1'Sym1 a6989586621679975394 :: TyFun [a6989586621679970245] a6989586621679970245 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym1 a6989586621679975394 :: TyFun [a] a -> Type) (a6989586621679975395 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym1 a6989586621679975394 :: TyFun [a] a -> Type) (a6989586621679975395 :: [a]) = Foldl1' a6989586621679975394 a6989586621679975395 |
type Foldl1'Sym2 (a6989586621679975394 :: (~>) a6989586621679970245 ((~>) a6989586621679970245 a6989586621679970245)) (a6989586621679975395 :: [a6989586621679970245]) = Foldl1' a6989586621679975394 a6989586621679975395 Source #
data FoldrSym0 :: forall a6989586621680486583 b6989586621680486584 t6989586621680486579. (~>) ((~>) a6989586621680486583 ((~>) b6989586621680486584 b6989586621680486584)) ((~>) b6989586621680486584 ((~>) (t6989586621680486579 a6989586621680486583) b6989586621680486584)) Source #
Instances
SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym0 :: TyFun (a6989586621680486583 ~> (b6989586621680486584 ~> b6989586621680486584)) (b6989586621680486584 ~> (t6989586621680486579 a6989586621680486583 ~> b6989586621680486584)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym0 :: TyFun (a6989586621680486583 ~> (b6989586621680486584 ~> b6989586621680486584)) (b6989586621680486584 ~> (t6989586621680486579 a6989586621680486583 ~> b6989586621680486584)) -> Type) (arg6989586621680487204 :: a6989586621680486583 ~> (b6989586621680486584 ~> b6989586621680486584)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldrSym0 :: TyFun (a6989586621680486583 ~> (b6989586621680486584 ~> b6989586621680486584)) (b6989586621680486584 ~> (t6989586621680486579 a6989586621680486583 ~> b6989586621680486584)) -> Type) (arg6989586621680487204 :: a6989586621680486583 ~> (b6989586621680486584 ~> b6989586621680486584)) = FoldrSym1 arg6989586621680487204 t6989586621680486579 :: TyFun b6989586621680486584 (t6989586621680486579 a6989586621680486583 ~> b6989586621680486584) -> Type |
data FoldrSym1 (arg6989586621680487204 :: (~>) a6989586621680486583 ((~>) b6989586621680486584 b6989586621680486584)) :: forall t6989586621680486579. (~>) b6989586621680486584 ((~>) (t6989586621680486579 a6989586621680486583) b6989586621680486584) Source #
Instances
(SFoldable t, SingI d) => SingI (FoldrSym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym1 arg6989586621680487204 t6989586621680486579 :: TyFun b6989586621680486584 (t6989586621680486579 a6989586621680486583 ~> b6989586621680486584) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym1 arg6989586621680487204 t6989586621680486579 :: TyFun b6989586621680486584 (t6989586621680486579 a6989586621680486583 ~> b6989586621680486584) -> Type) (arg6989586621680487205 :: b6989586621680486584) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldrSym1 arg6989586621680487204 t6989586621680486579 :: TyFun b6989586621680486584 (t6989586621680486579 a6989586621680486583 ~> b6989586621680486584) -> Type) (arg6989586621680487205 :: b6989586621680486584) = FoldrSym2 arg6989586621680487204 arg6989586621680487205 t6989586621680486579 :: TyFun (t6989586621680486579 a6989586621680486583) b6989586621680486584 -> Type |
data FoldrSym2 (arg6989586621680487204 :: (~>) a6989586621680486583 ((~>) b6989586621680486584 b6989586621680486584)) (arg6989586621680487205 :: b6989586621680486584) :: forall t6989586621680486579. (~>) (t6989586621680486579 a6989586621680486583) b6989586621680486584 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym2 arg6989586621680487205 arg6989586621680487204 t6989586621680486579 :: TyFun (t6989586621680486579 a6989586621680486583) b6989586621680486584 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym2 arg6989586621680487205 arg6989586621680487204 t :: TyFun (t a) b -> Type) (arg6989586621680487206 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type FoldrSym3 (arg6989586621680487204 :: (~>) a6989586621680486583 ((~>) b6989586621680486584 b6989586621680486584)) (arg6989586621680487205 :: b6989586621680486584) (arg6989586621680487206 :: t6989586621680486579 a6989586621680486583) = Foldr arg6989586621680487204 arg6989586621680487205 arg6989586621680487206 Source #
data Foldr1Sym0 :: forall a6989586621680486591 t6989586621680486579. (~>) ((~>) a6989586621680486591 ((~>) a6989586621680486591 a6989586621680486591)) ((~>) (t6989586621680486579 a6989586621680486591) a6989586621680486591) Source #
Instances
SFoldable t => SingI (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing Foldr1Sym0 Source # | |
SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (a6989586621680486591 ~> (a6989586621680486591 ~> a6989586621680486591)) (t6989586621680486579 a6989586621680486591 ~> a6989586621680486591) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym0 :: TyFun (a6989586621680486591 ~> (a6989586621680486591 ~> a6989586621680486591)) (t6989586621680486579 a6989586621680486591 ~> a6989586621680486591) -> Type) (arg6989586621680487228 :: a6989586621680486591 ~> (a6989586621680486591 ~> a6989586621680486591)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr1Sym0 :: TyFun (a6989586621680486591 ~> (a6989586621680486591 ~> a6989586621680486591)) (t6989586621680486579 a6989586621680486591 ~> a6989586621680486591) -> Type) (arg6989586621680487228 :: a6989586621680486591 ~> (a6989586621680486591 ~> a6989586621680486591)) = Foldr1Sym1 arg6989586621680487228 t6989586621680486579 :: TyFun (t6989586621680486579 a6989586621680486591) a6989586621680486591 -> Type |
data Foldr1Sym1 (arg6989586621680487228 :: (~>) a6989586621680486591 ((~>) a6989586621680486591 a6989586621680486591)) :: forall t6989586621680486579. (~>) (t6989586621680486579 a6989586621680486591) a6989586621680486591 Source #
Instances
(SFoldable t, SingI d) => SingI (Foldr1Sym1 d t :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (Foldr1Sym1 d t) Source # | |
SuppressUnusedWarnings (Foldr1Sym1 arg6989586621680487228 t6989586621680486579 :: TyFun (t6989586621680486579 a6989586621680486591) a6989586621680486591 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym1 arg6989586621680487228 t :: TyFun (t a) a -> Type) (arg6989586621680487229 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr1Sym1 arg6989586621680487228 t :: TyFun (t a) a -> Type) (arg6989586621680487229 :: t a) = Foldr1 arg6989586621680487228 arg6989586621680487229 |
type Foldr1Sym2 (arg6989586621680487228 :: (~>) a6989586621680486591 ((~>) a6989586621680486591 a6989586621680486591)) (arg6989586621680487229 :: t6989586621680486579 a6989586621680486591) = Foldr1 arg6989586621680487228 arg6989586621680487229 Source #
data ConcatSym0 :: forall t6989586621680486504 a6989586621680486505. (~>) (t6989586621680486504 [a6989586621680486505]) [a6989586621680486505] Source #
Instances
SFoldable t => SingI (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing ConcatSym0 Source # | |
SuppressUnusedWarnings (ConcatSym0 :: TyFun (t6989586621680486504 [a6989586621680486505]) [a6989586621680486505] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680487086 :: t [a]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680487086 :: t [a]) = Concat a6989586621680487086 |
type ConcatSym1 (a6989586621680487086 :: t6989586621680486504 [a6989586621680486505]) = Concat a6989586621680487086 Source #
data ConcatMapSym0 :: forall a6989586621680486502 b6989586621680486503 t6989586621680486501. (~>) ((~>) a6989586621680486502 [b6989586621680486503]) ((~>) (t6989586621680486501 a6989586621680486502) [b6989586621680486503]) Source #
Instances
SFoldable t => SingI (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing ConcatMapSym0 Source # | |
SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (a6989586621680486502 ~> [b6989586621680486503]) (t6989586621680486501 a6989586621680486502 ~> [b6989586621680486503]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym0 :: TyFun (a6989586621680486502 ~> [b6989586621680486503]) (t6989586621680486501 a6989586621680486502 ~> [b6989586621680486503]) -> Type) (a6989586621680487070 :: a6989586621680486502 ~> [b6989586621680486503]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym0 :: TyFun (a6989586621680486502 ~> [b6989586621680486503]) (t6989586621680486501 a6989586621680486502 ~> [b6989586621680486503]) -> Type) (a6989586621680487070 :: a6989586621680486502 ~> [b6989586621680486503]) = ConcatMapSym1 a6989586621680487070 t6989586621680486501 :: TyFun (t6989586621680486501 a6989586621680486502) [b6989586621680486503] -> Type |
data ConcatMapSym1 (a6989586621680487070 :: (~>) a6989586621680486502 [b6989586621680486503]) :: forall t6989586621680486501. (~>) (t6989586621680486501 a6989586621680486502) [b6989586621680486503] Source #
Instances
(SFoldable t, SingI d) => SingI (ConcatMapSym1 d t :: TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (ConcatMapSym1 d t) Source # | |
SuppressUnusedWarnings (ConcatMapSym1 a6989586621680487070 t6989586621680486501 :: TyFun (t6989586621680486501 a6989586621680486502) [b6989586621680486503] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym1 a6989586621680487070 t :: TyFun (t a) [b] -> Type) (a6989586621680487071 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym1 a6989586621680487070 t :: TyFun (t a) [b] -> Type) (a6989586621680487071 :: t a) = ConcatMap a6989586621680487070 a6989586621680487071 |
type ConcatMapSym2 (a6989586621680487070 :: (~>) a6989586621680486502 [b6989586621680486503]) (a6989586621680487071 :: t6989586621680486501 a6989586621680486502) = ConcatMap a6989586621680487070 a6989586621680487071 Source #
data AndSym0 :: forall t6989586621680486500. (~>) (t6989586621680486500 Bool) Bool Source #
Instances
SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
SuppressUnusedWarnings (AndSym0 :: TyFun (t6989586621680486500 Bool) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680487061 :: t Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type AndSym1 (a6989586621680487061 :: t6989586621680486500 Bool) = And a6989586621680487061 Source #
data OrSym0 :: forall t6989586621680486499. (~>) (t6989586621680486499 Bool) Bool Source #
Instances
SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
SuppressUnusedWarnings (OrSym0 :: TyFun (t6989586621680486499 Bool) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680487052 :: t Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data AnySym0 :: forall a6989586621680486498 t6989586621680486497. (~>) ((~>) a6989586621680486498 Bool) ((~>) (t6989586621680486497 a6989586621680486498) Bool) Source #
Instances
SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (AnySym0 :: TyFun (a6989586621680486498 ~> Bool) (t6989586621680486497 a6989586621680486498 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AnySym0 :: TyFun (a6989586621680486498 ~> Bool) (t6989586621680486497 a6989586621680486498 ~> Bool) -> Type) (a6989586621680487039 :: a6989586621680486498 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data AnySym1 (a6989586621680487039 :: (~>) a6989586621680486498 Bool) :: forall t6989586621680486497. (~>) (t6989586621680486497 a6989586621680486498) Bool Source #
Instances
(SFoldable t, SingI d) => SingI (AnySym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (AnySym1 a6989586621680487039 t6989586621680486497 :: TyFun (t6989586621680486497 a6989586621680486498) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AnySym1 a6989586621680487039 t :: TyFun (t a) Bool -> Type) (a6989586621680487040 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type AnySym2 (a6989586621680487039 :: (~>) a6989586621680486498 Bool) (a6989586621680487040 :: t6989586621680486497 a6989586621680486498) = Any a6989586621680487039 a6989586621680487040 Source #
data AllSym0 :: forall a6989586621680486496 t6989586621680486495. (~>) ((~>) a6989586621680486496 Bool) ((~>) (t6989586621680486495 a6989586621680486496) Bool) Source #
Instances
SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (AllSym0 :: TyFun (a6989586621680486496 ~> Bool) (t6989586621680486495 a6989586621680486496 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AllSym0 :: TyFun (a6989586621680486496 ~> Bool) (t6989586621680486495 a6989586621680486496 ~> Bool) -> Type) (a6989586621680487026 :: a6989586621680486496 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data AllSym1 (a6989586621680487026 :: (~>) a6989586621680486496 Bool) :: forall t6989586621680486495. (~>) (t6989586621680486495 a6989586621680486496) Bool Source #
Instances
(SFoldable t, SingI d) => SingI (AllSym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (AllSym1 a6989586621680487026 t6989586621680486495 :: TyFun (t6989586621680486495 a6989586621680486496) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AllSym1 a6989586621680487026 t :: TyFun (t a) Bool -> Type) (a6989586621680487027 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type AllSym2 (a6989586621680487026 :: (~>) a6989586621680486496 Bool) (a6989586621680487027 :: t6989586621680486495 a6989586621680486496) = All a6989586621680487026 a6989586621680487027 Source #
data SumSym0 :: forall t6989586621680486579 a6989586621680486599. (~>) (t6989586621680486579 a6989586621680486599) a6989586621680486599 Source #
Instances
(SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # | |
SuppressUnusedWarnings (SumSym0 :: TyFun (t6989586621680486579 a6989586621680486599) a6989586621680486599 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (SumSym0 :: TyFun (t a) a -> Type) (arg6989586621680487250 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type SumSym1 (arg6989586621680487250 :: t6989586621680486579 a6989586621680486599) = Sum arg6989586621680487250 Source #
data ProductSym0 :: forall t6989586621680486579 a6989586621680486600. (~>) (t6989586621680486579 a6989586621680486600) a6989586621680486600 Source #
Instances
(SFoldable t, SNum a) => SingI (ProductSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing ProductSym0 Source # | |
SuppressUnusedWarnings (ProductSym0 :: TyFun (t6989586621680486579 a6989586621680486600) a6989586621680486600 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680487252 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680487252 :: t a) = Product arg6989586621680487252 |
type ProductSym1 (arg6989586621680487252 :: t6989586621680486579 a6989586621680486600) = Product arg6989586621680487252 Source #
data MaximumSym0 :: forall t6989586621680486579 a6989586621680486597. (~>) (t6989586621680486579 a6989586621680486597) a6989586621680486597 Source #
Instances
(SFoldable t, SOrd a) => SingI (MaximumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing MaximumSym0 Source # | |
SuppressUnusedWarnings (MaximumSym0 :: TyFun (t6989586621680486579 a6989586621680486597) a6989586621680486597 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680487246 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680487246 :: t a) = Maximum arg6989586621680487246 |
type MaximumSym1 (arg6989586621680487246 :: t6989586621680486579 a6989586621680486597) = Maximum arg6989586621680487246 Source #
data MinimumSym0 :: forall t6989586621680486579 a6989586621680486598. (~>) (t6989586621680486579 a6989586621680486598) a6989586621680486598 Source #
Instances
(SFoldable t, SOrd a) => SingI (MinimumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing MinimumSym0 Source # | |
SuppressUnusedWarnings (MinimumSym0 :: TyFun (t6989586621680486579 a6989586621680486598) a6989586621680486598 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680487248 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680487248 :: t a) = Minimum arg6989586621680487248 |
type MinimumSym1 (arg6989586621680487248 :: t6989586621680486579 a6989586621680486598) = Minimum arg6989586621680487248 Source #
data ScanlSym0 :: forall b6989586621679970237 a6989586621679970238. (~>) ((~>) b6989586621679970237 ((~>) a6989586621679970238 b6989586621679970237)) ((~>) b6989586621679970237 ((~>) [a6989586621679970238] [b6989586621679970237])) Source #
Instances
SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym0 :: TyFun (b6989586621679970237 ~> (a6989586621679970238 ~> b6989586621679970237)) (b6989586621679970237 ~> ([a6989586621679970238] ~> [b6989586621679970237])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym0 :: TyFun (b6989586621679970237 ~> (a6989586621679970238 ~> b6989586621679970237)) (b6989586621679970237 ~> ([a6989586621679970238] ~> [b6989586621679970237])) -> Type) (a6989586621679975331 :: b6989586621679970237 ~> (a6989586621679970238 ~> b6989586621679970237)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ScanlSym0 :: TyFun (b6989586621679970237 ~> (a6989586621679970238 ~> b6989586621679970237)) (b6989586621679970237 ~> ([a6989586621679970238] ~> [b6989586621679970237])) -> Type) (a6989586621679975331 :: b6989586621679970237 ~> (a6989586621679970238 ~> b6989586621679970237)) = ScanlSym1 a6989586621679975331 |
data ScanlSym1 (a6989586621679975331 :: (~>) b6989586621679970237 ((~>) a6989586621679970238 b6989586621679970237)) :: (~>) b6989586621679970237 ((~>) [a6989586621679970238] [b6989586621679970237]) Source #
Instances
SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym1 a6989586621679975331 :: TyFun b6989586621679970237 ([a6989586621679970238] ~> [b6989586621679970237]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym1 a6989586621679975331 :: TyFun b6989586621679970237 ([a6989586621679970238] ~> [b6989586621679970237]) -> Type) (a6989586621679975332 :: b6989586621679970237) Source # | |
data ScanlSym2 (a6989586621679975331 :: (~>) b6989586621679970237 ((~>) a6989586621679970238 b6989586621679970237)) (a6989586621679975332 :: b6989586621679970237) :: (~>) [a6989586621679970238] [b6989586621679970237] Source #
Instances
(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym2 a6989586621679975332 a6989586621679975331 :: TyFun [a6989586621679970238] [b6989586621679970237] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym2 a6989586621679975332 a6989586621679975331 :: TyFun [a] [b] -> Type) (a6989586621679975333 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type ScanlSym3 (a6989586621679975331 :: (~>) b6989586621679970237 ((~>) a6989586621679970238 b6989586621679970237)) (a6989586621679975332 :: b6989586621679970237) (a6989586621679975333 :: [a6989586621679970238]) = Scanl a6989586621679975331 a6989586621679975332 a6989586621679975333 Source #
data Scanl1Sym0 :: forall a6989586621679970236. (~>) ((~>) a6989586621679970236 ((~>) a6989586621679970236 a6989586621679970236)) ((~>) [a6989586621679970236] [a6989586621679970236]) Source #
Instances
SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Scanl1Sym0 Source # | |
SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a6989586621679970236 ~> (a6989586621679970236 ~> a6989586621679970236)) ([a6989586621679970236] ~> [a6989586621679970236]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym0 :: TyFun (a6989586621679970236 ~> (a6989586621679970236 ~> a6989586621679970236)) ([a6989586621679970236] ~> [a6989586621679970236]) -> Type) (a6989586621679975324 :: a6989586621679970236 ~> (a6989586621679970236 ~> a6989586621679970236)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym0 :: TyFun (a6989586621679970236 ~> (a6989586621679970236 ~> a6989586621679970236)) ([a6989586621679970236] ~> [a6989586621679970236]) -> Type) (a6989586621679975324 :: a6989586621679970236 ~> (a6989586621679970236 ~> a6989586621679970236)) = Scanl1Sym1 a6989586621679975324 |
data Scanl1Sym1 (a6989586621679975324 :: (~>) a6989586621679970236 ((~>) a6989586621679970236 a6989586621679970236)) :: (~>) [a6989586621679970236] [a6989586621679970236] Source #
Instances
SingI d => SingI (Scanl1Sym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (Scanl1Sym1 d) Source # | |
SuppressUnusedWarnings (Scanl1Sym1 a6989586621679975324 :: TyFun [a6989586621679970236] [a6989586621679970236] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym1 a6989586621679975324 :: TyFun [a] [a] -> Type) (a6989586621679975325 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym1 a6989586621679975324 :: TyFun [a] [a] -> Type) (a6989586621679975325 :: [a]) = Scanl1 a6989586621679975324 a6989586621679975325 |
type Scanl1Sym2 (a6989586621679975324 :: (~>) a6989586621679970236 ((~>) a6989586621679970236 a6989586621679970236)) (a6989586621679975325 :: [a6989586621679970236]) = Scanl1 a6989586621679975324 a6989586621679975325 Source #
data ScanrSym0 :: forall a6989586621679970234 b6989586621679970235. (~>) ((~>) a6989586621679970234 ((~>) b6989586621679970235 b6989586621679970235)) ((~>) b6989586621679970235 ((~>) [a6989586621679970234] [b6989586621679970235])) Source #
Instances
SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym0 :: TyFun (a6989586621679970234 ~> (b6989586621679970235 ~> b6989586621679970235)) (b6989586621679970235 ~> ([a6989586621679970234] ~> [b6989586621679970235])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym0 :: TyFun (a6989586621679970234 ~> (b6989586621679970235 ~> b6989586621679970235)) (b6989586621679970235 ~> ([a6989586621679970234] ~> [b6989586621679970235])) -> Type) (a6989586621679975303 :: a6989586621679970234 ~> (b6989586621679970235 ~> b6989586621679970235)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ScanrSym0 :: TyFun (a6989586621679970234 ~> (b6989586621679970235 ~> b6989586621679970235)) (b6989586621679970235 ~> ([a6989586621679970234] ~> [b6989586621679970235])) -> Type) (a6989586621679975303 :: a6989586621679970234 ~> (b6989586621679970235 ~> b6989586621679970235)) = ScanrSym1 a6989586621679975303 |
data ScanrSym1 (a6989586621679975303 :: (~>) a6989586621679970234 ((~>) b6989586621679970235 b6989586621679970235)) :: (~>) b6989586621679970235 ((~>) [a6989586621679970234] [b6989586621679970235]) Source #
Instances
SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym1 a6989586621679975303 :: TyFun b6989586621679970235 ([a6989586621679970234] ~> [b6989586621679970235]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym1 a6989586621679975303 :: TyFun b6989586621679970235 ([a6989586621679970234] ~> [b6989586621679970235]) -> Type) (a6989586621679975304 :: b6989586621679970235) Source # | |
data ScanrSym2 (a6989586621679975303 :: (~>) a6989586621679970234 ((~>) b6989586621679970235 b6989586621679970235)) (a6989586621679975304 :: b6989586621679970235) :: (~>) [a6989586621679970234] [b6989586621679970235] Source #
Instances
(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym2 a6989586621679975304 a6989586621679975303 :: TyFun [a6989586621679970234] [b6989586621679970235] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym2 a6989586621679975304 a6989586621679975303 :: TyFun [a] [b] -> Type) (a6989586621679975305 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type ScanrSym3 (a6989586621679975303 :: (~>) a6989586621679970234 ((~>) b6989586621679970235 b6989586621679970235)) (a6989586621679975304 :: b6989586621679970235) (a6989586621679975305 :: [a6989586621679970234]) = Scanr a6989586621679975303 a6989586621679975304 a6989586621679975305 Source #
data Scanr1Sym0 :: forall a6989586621679970233. (~>) ((~>) a6989586621679970233 ((~>) a6989586621679970233 a6989586621679970233)) ((~>) [a6989586621679970233] [a6989586621679970233]) Source #
Instances
SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Scanr1Sym0 Source # | |
SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a6989586621679970233 ~> (a6989586621679970233 ~> a6989586621679970233)) ([a6989586621679970233] ~> [a6989586621679970233]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym0 :: TyFun (a6989586621679970233 ~> (a6989586621679970233 ~> a6989586621679970233)) ([a6989586621679970233] ~> [a6989586621679970233]) -> Type) (a6989586621679975279 :: a6989586621679970233 ~> (a6989586621679970233 ~> a6989586621679970233)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym0 :: TyFun (a6989586621679970233 ~> (a6989586621679970233 ~> a6989586621679970233)) ([a6989586621679970233] ~> [a6989586621679970233]) -> Type) (a6989586621679975279 :: a6989586621679970233 ~> (a6989586621679970233 ~> a6989586621679970233)) = Scanr1Sym1 a6989586621679975279 |
data Scanr1Sym1 (a6989586621679975279 :: (~>) a6989586621679970233 ((~>) a6989586621679970233 a6989586621679970233)) :: (~>) [a6989586621679970233] [a6989586621679970233] Source #
Instances
SingI d => SingI (Scanr1Sym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (Scanr1Sym1 d) Source # | |
SuppressUnusedWarnings (Scanr1Sym1 a6989586621679975279 :: TyFun [a6989586621679970233] [a6989586621679970233] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym1 a6989586621679975279 :: TyFun [a] [a] -> Type) (a6989586621679975280 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym1 a6989586621679975279 :: TyFun [a] [a] -> Type) (a6989586621679975280 :: [a]) = Scanr1 a6989586621679975279 a6989586621679975280 |
type Scanr1Sym2 (a6989586621679975279 :: (~>) a6989586621679970233 ((~>) a6989586621679970233 a6989586621679970233)) (a6989586621679975280 :: [a6989586621679970233]) = Scanr1 a6989586621679975279 a6989586621679975280 Source #
data MapAccumLSym0 :: forall a6989586621680800304 b6989586621680800305 c6989586621680800306 t6989586621680800303. (~>) ((~>) a6989586621680800304 ((~>) b6989586621680800305 (a6989586621680800304, c6989586621680800306))) ((~>) a6989586621680800304 ((~>) (t6989586621680800303 b6989586621680800305) (a6989586621680800304, t6989586621680800303 c6989586621680800306))) Source #
Instances
STraversable t => SingI (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods sing :: Sing MapAccumLSym0 Source # | |
SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (a6989586621680800304 ~> (b6989586621680800305 ~> (a6989586621680800304, c6989586621680800306))) (a6989586621680800304 ~> (t6989586621680800303 b6989586621680800305 ~> (a6989586621680800304, t6989586621680800303 c6989586621680800306))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym0 :: TyFun (a6989586621680800304 ~> (b6989586621680800305 ~> (a6989586621680800304, c6989586621680800306))) (a6989586621680800304 ~> (t6989586621680800303 b6989586621680800305 ~> (a6989586621680800304, t6989586621680800303 c6989586621680800306))) -> Type) (a6989586621680800807 :: a6989586621680800304 ~> (b6989586621680800305 ~> (a6989586621680800304, c6989586621680800306))) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym0 :: TyFun (a6989586621680800304 ~> (b6989586621680800305 ~> (a6989586621680800304, c6989586621680800306))) (a6989586621680800304 ~> (t6989586621680800303 b6989586621680800305 ~> (a6989586621680800304, t6989586621680800303 c6989586621680800306))) -> Type) (a6989586621680800807 :: a6989586621680800304 ~> (b6989586621680800305 ~> (a6989586621680800304, c6989586621680800306))) = MapAccumLSym1 a6989586621680800807 t6989586621680800303 :: TyFun a6989586621680800304 (t6989586621680800303 b6989586621680800305 ~> (a6989586621680800304, t6989586621680800303 c6989586621680800306)) -> Type |
data MapAccumLSym1 (a6989586621680800807 :: (~>) a6989586621680800304 ((~>) b6989586621680800305 (a6989586621680800304, c6989586621680800306))) :: forall t6989586621680800303. (~>) a6989586621680800304 ((~>) (t6989586621680800303 b6989586621680800305) (a6989586621680800304, t6989586621680800303 c6989586621680800306)) Source #
Instances
(STraversable t, SingI d) => SingI (MapAccumLSym1 d t :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods sing :: Sing (MapAccumLSym1 d t) Source # | |
SuppressUnusedWarnings (MapAccumLSym1 a6989586621680800807 t6989586621680800303 :: TyFun a6989586621680800304 (t6989586621680800303 b6989586621680800305 ~> (a6989586621680800304, t6989586621680800303 c6989586621680800306)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym1 a6989586621680800807 t6989586621680800303 :: TyFun a6989586621680800304 (t6989586621680800303 b6989586621680800305 ~> (a6989586621680800304, t6989586621680800303 c6989586621680800306)) -> Type) (a6989586621680800808 :: a6989586621680800304) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym1 a6989586621680800807 t6989586621680800303 :: TyFun a6989586621680800304 (t6989586621680800303 b6989586621680800305 ~> (a6989586621680800304, t6989586621680800303 c6989586621680800306)) -> Type) (a6989586621680800808 :: a6989586621680800304) = MapAccumLSym2 a6989586621680800807 a6989586621680800808 t6989586621680800303 :: TyFun (t6989586621680800303 b6989586621680800305) (a6989586621680800304, t6989586621680800303 c6989586621680800306) -> Type |
data MapAccumLSym2 (a6989586621680800807 :: (~>) a6989586621680800304 ((~>) b6989586621680800305 (a6989586621680800304, c6989586621680800306))) (a6989586621680800808 :: a6989586621680800304) :: forall t6989586621680800303. (~>) (t6989586621680800303 b6989586621680800305) (a6989586621680800304, t6989586621680800303 c6989586621680800306) Source #
Instances
(STraversable t, SingI d1, SingI d2) => SingI (MapAccumLSym2 d1 d2 t :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods sing :: Sing (MapAccumLSym2 d1 d2 t) Source # | |
SuppressUnusedWarnings (MapAccumLSym2 a6989586621680800808 a6989586621680800807 t6989586621680800303 :: TyFun (t6989586621680800303 b6989586621680800305) (a6989586621680800304, t6989586621680800303 c6989586621680800306) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym2 a6989586621680800808 a6989586621680800807 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680800809 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym2 a6989586621680800808 a6989586621680800807 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680800809 :: t b) = MapAccumL a6989586621680800808 a6989586621680800807 a6989586621680800809 |
type MapAccumLSym3 (a6989586621680800807 :: (~>) a6989586621680800304 ((~>) b6989586621680800305 (a6989586621680800304, c6989586621680800306))) (a6989586621680800808 :: a6989586621680800304) (a6989586621680800809 :: t6989586621680800303 b6989586621680800305) = MapAccumL a6989586621680800807 a6989586621680800808 a6989586621680800809 Source #
data MapAccumRSym0 :: forall a6989586621680800300 b6989586621680800301 c6989586621680800302 t6989586621680800299. (~>) ((~>) a6989586621680800300 ((~>) b6989586621680800301 (a6989586621680800300, c6989586621680800302))) ((~>) a6989586621680800300 ((~>) (t6989586621680800299 b6989586621680800301) (a6989586621680800300, t6989586621680800299 c6989586621680800302))) Source #
Instances
STraversable t => SingI (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods sing :: Sing MapAccumRSym0 Source # | |
SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (a6989586621680800300 ~> (b6989586621680800301 ~> (a6989586621680800300, c6989586621680800302))) (a6989586621680800300 ~> (t6989586621680800299 b6989586621680800301 ~> (a6989586621680800300, t6989586621680800299 c6989586621680800302))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym0 :: TyFun (a6989586621680800300 ~> (b6989586621680800301 ~> (a6989586621680800300, c6989586621680800302))) (a6989586621680800300 ~> (t6989586621680800299 b6989586621680800301 ~> (a6989586621680800300, t6989586621680800299 c6989586621680800302))) -> Type) (a6989586621680800790 :: a6989586621680800300 ~> (b6989586621680800301 ~> (a6989586621680800300, c6989586621680800302))) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym0 :: TyFun (a6989586621680800300 ~> (b6989586621680800301 ~> (a6989586621680800300, c6989586621680800302))) (a6989586621680800300 ~> (t6989586621680800299 b6989586621680800301 ~> (a6989586621680800300, t6989586621680800299 c6989586621680800302))) -> Type) (a6989586621680800790 :: a6989586621680800300 ~> (b6989586621680800301 ~> (a6989586621680800300, c6989586621680800302))) = MapAccumRSym1 a6989586621680800790 t6989586621680800299 :: TyFun a6989586621680800300 (t6989586621680800299 b6989586621680800301 ~> (a6989586621680800300, t6989586621680800299 c6989586621680800302)) -> Type |
data MapAccumRSym1 (a6989586621680800790 :: (~>) a6989586621680800300 ((~>) b6989586621680800301 (a6989586621680800300, c6989586621680800302))) :: forall t6989586621680800299. (~>) a6989586621680800300 ((~>) (t6989586621680800299 b6989586621680800301) (a6989586621680800300, t6989586621680800299 c6989586621680800302)) Source #
Instances
(STraversable t, SingI d) => SingI (MapAccumRSym1 d t :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods sing :: Sing (MapAccumRSym1 d t) Source # | |
SuppressUnusedWarnings (MapAccumRSym1 a6989586621680800790 t6989586621680800299 :: TyFun a6989586621680800300 (t6989586621680800299 b6989586621680800301 ~> (a6989586621680800300, t6989586621680800299 c6989586621680800302)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym1 a6989586621680800790 t6989586621680800299 :: TyFun a6989586621680800300 (t6989586621680800299 b6989586621680800301 ~> (a6989586621680800300, t6989586621680800299 c6989586621680800302)) -> Type) (a6989586621680800791 :: a6989586621680800300) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym1 a6989586621680800790 t6989586621680800299 :: TyFun a6989586621680800300 (t6989586621680800299 b6989586621680800301 ~> (a6989586621680800300, t6989586621680800299 c6989586621680800302)) -> Type) (a6989586621680800791 :: a6989586621680800300) = MapAccumRSym2 a6989586621680800790 a6989586621680800791 t6989586621680800299 :: TyFun (t6989586621680800299 b6989586621680800301) (a6989586621680800300, t6989586621680800299 c6989586621680800302) -> Type |
data MapAccumRSym2 (a6989586621680800790 :: (~>) a6989586621680800300 ((~>) b6989586621680800301 (a6989586621680800300, c6989586621680800302))) (a6989586621680800791 :: a6989586621680800300) :: forall t6989586621680800299. (~>) (t6989586621680800299 b6989586621680800301) (a6989586621680800300, t6989586621680800299 c6989586621680800302) Source #
Instances
(STraversable t, SingI d1, SingI d2) => SingI (MapAccumRSym2 d1 d2 t :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods sing :: Sing (MapAccumRSym2 d1 d2 t) Source # | |
SuppressUnusedWarnings (MapAccumRSym2 a6989586621680800791 a6989586621680800790 t6989586621680800299 :: TyFun (t6989586621680800299 b6989586621680800301) (a6989586621680800300, t6989586621680800299 c6989586621680800302) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym2 a6989586621680800791 a6989586621680800790 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680800792 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym2 a6989586621680800791 a6989586621680800790 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680800792 :: t b) = MapAccumR a6989586621680800791 a6989586621680800790 a6989586621680800792 |
type MapAccumRSym3 (a6989586621680800790 :: (~>) a6989586621680800300 ((~>) b6989586621680800301 (a6989586621680800300, c6989586621680800302))) (a6989586621680800791 :: a6989586621680800300) (a6989586621680800792 :: t6989586621680800299 b6989586621680800301) = MapAccumR a6989586621680800790 a6989586621680800791 a6989586621680800792 Source #
data ReplicateSym0 :: forall a6989586621679970141. (~>) Nat ((~>) a6989586621679970141 [a6989586621679970141]) Source #
Instances
SingI (ReplicateSym0 :: TyFun Nat (a ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing ReplicateSym0 Source # | |
SuppressUnusedWarnings (ReplicateSym0 :: TyFun Nat (a6989586621679970141 ~> [a6989586621679970141]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym0 :: TyFun Nat (a6989586621679970141 ~> [a6989586621679970141]) -> Type) (a6989586621679974306 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym0 :: TyFun Nat (a6989586621679970141 ~> [a6989586621679970141]) -> Type) (a6989586621679974306 :: Nat) = ReplicateSym1 a6989586621679974306 a6989586621679970141 :: TyFun a6989586621679970141 [a6989586621679970141] -> Type |
data ReplicateSym1 (a6989586621679974306 :: Nat) :: forall a6989586621679970141. (~>) a6989586621679970141 [a6989586621679970141] Source #
Instances
SingI d => SingI (ReplicateSym1 d a :: TyFun a [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ReplicateSym1 d a) Source # | |
SuppressUnusedWarnings (ReplicateSym1 a6989586621679974306 a6989586621679970141 :: TyFun a6989586621679970141 [a6989586621679970141] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym1 a6989586621679974306 a :: TyFun a [a] -> Type) (a6989586621679974307 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym1 a6989586621679974306 a :: TyFun a [a] -> Type) (a6989586621679974307 :: a) = Replicate a6989586621679974306 a6989586621679974307 |
type ReplicateSym2 (a6989586621679974306 :: Nat) (a6989586621679974307 :: a6989586621679970141) = Replicate a6989586621679974306 a6989586621679974307 Source #
data UnfoldrSym0 :: forall b6989586621679970225 a6989586621679970226. (~>) ((~>) b6989586621679970225 (Maybe (a6989586621679970226, b6989586621679970225))) ((~>) b6989586621679970225 [a6989586621679970226]) Source #
Instances
SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing UnfoldrSym0 Source # | |
SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (b6989586621679970225 ~> Maybe (a6989586621679970226, b6989586621679970225)) (b6989586621679970225 ~> [a6989586621679970226]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym0 :: TyFun (b6989586621679970225 ~> Maybe (a6989586621679970226, b6989586621679970225)) (b6989586621679970225 ~> [a6989586621679970226]) -> Type) (a6989586621679975137 :: b6989586621679970225 ~> Maybe (a6989586621679970226, b6989586621679970225)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym0 :: TyFun (b6989586621679970225 ~> Maybe (a6989586621679970226, b6989586621679970225)) (b6989586621679970225 ~> [a6989586621679970226]) -> Type) (a6989586621679975137 :: b6989586621679970225 ~> Maybe (a6989586621679970226, b6989586621679970225)) = UnfoldrSym1 a6989586621679975137 |
data UnfoldrSym1 (a6989586621679975137 :: (~>) b6989586621679970225 (Maybe (a6989586621679970226, b6989586621679970225))) :: (~>) b6989586621679970225 [a6989586621679970226] Source #
Instances
SingI d => SingI (UnfoldrSym1 d :: TyFun b [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (UnfoldrSym1 d) Source # | |
SuppressUnusedWarnings (UnfoldrSym1 a6989586621679975137 :: TyFun b6989586621679970225 [a6989586621679970226] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym1 a6989586621679975137 :: TyFun b [a] -> Type) (a6989586621679975138 :: b) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym1 a6989586621679975137 :: TyFun b [a] -> Type) (a6989586621679975138 :: b) = Unfoldr a6989586621679975137 a6989586621679975138 |
type UnfoldrSym2 (a6989586621679975137 :: (~>) b6989586621679970225 (Maybe (a6989586621679970226, b6989586621679970225))) (a6989586621679975138 :: b6989586621679970225) = Unfoldr a6989586621679975137 a6989586621679975138 Source #
data TakeSym0 :: forall a6989586621679970157. (~>) Nat ((~>) [a6989586621679970157] [a6989586621679970157]) Source #
Instances
SingI (TakeSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (TakeSym0 :: TyFun Nat ([a6989586621679970157] ~> [a6989586621679970157]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym0 :: TyFun Nat ([a6989586621679970157] ~> [a6989586621679970157]) -> Type) (a6989586621679974467 :: Nat) Source # | |
data TakeSym1 (a6989586621679974467 :: Nat) :: forall a6989586621679970157. (~>) [a6989586621679970157] [a6989586621679970157] Source #
Instances
SingI d => SingI (TakeSym1 d a :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (TakeSym1 a6989586621679974467 a6989586621679970157 :: TyFun [a6989586621679970157] [a6989586621679970157] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym1 a6989586621679974467 a :: TyFun [a] [a] -> Type) (a6989586621679974468 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type TakeSym2 (a6989586621679974467 :: Nat) (a6989586621679974468 :: [a6989586621679970157]) = Take a6989586621679974467 a6989586621679974468 Source #
data DropSym0 :: forall a6989586621679970156. (~>) Nat ((~>) [a6989586621679970156] [a6989586621679970156]) Source #
Instances
SingI (DropSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (DropSym0 :: TyFun Nat ([a6989586621679970156] ~> [a6989586621679970156]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropSym0 :: TyFun Nat ([a6989586621679970156] ~> [a6989586621679970156]) -> Type) (a6989586621679974453 :: Nat) Source # | |
data DropSym1 (a6989586621679974453 :: Nat) :: forall a6989586621679970156. (~>) [a6989586621679970156] [a6989586621679970156] Source #
Instances
SingI d => SingI (DropSym1 d a :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (DropSym1 a6989586621679974453 a6989586621679970156 :: TyFun [a6989586621679970156] [a6989586621679970156] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropSym1 a6989586621679974453 a :: TyFun [a] [a] -> Type) (a6989586621679974454 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type DropSym2 (a6989586621679974453 :: Nat) (a6989586621679974454 :: [a6989586621679970156]) = Drop a6989586621679974453 a6989586621679974454 Source #
data SplitAtSym0 :: forall a6989586621679970155. (~>) Nat ((~>) [a6989586621679970155] ([a6989586621679970155], [a6989586621679970155])) Source #
Instances
SingI (SplitAtSym0 :: TyFun Nat ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing SplitAtSym0 Source # | |
SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat ([a6989586621679970155] ~> ([a6989586621679970155], [a6989586621679970155])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym0 :: TyFun Nat ([a6989586621679970155] ~> ([a6989586621679970155], [a6989586621679970155])) -> Type) (a6989586621679974447 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym0 :: TyFun Nat ([a6989586621679970155] ~> ([a6989586621679970155], [a6989586621679970155])) -> Type) (a6989586621679974447 :: Nat) = SplitAtSym1 a6989586621679974447 a6989586621679970155 :: TyFun [a6989586621679970155] ([a6989586621679970155], [a6989586621679970155]) -> Type |
data SplitAtSym1 (a6989586621679974447 :: Nat) :: forall a6989586621679970155. (~>) [a6989586621679970155] ([a6989586621679970155], [a6989586621679970155]) Source #
Instances
SingI d => SingI (SplitAtSym1 d a :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (SplitAtSym1 d a) Source # | |
SuppressUnusedWarnings (SplitAtSym1 a6989586621679974447 a6989586621679970155 :: TyFun [a6989586621679970155] ([a6989586621679970155], [a6989586621679970155]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym1 a6989586621679974447 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621679974448 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym1 a6989586621679974447 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621679974448 :: [a]) = SplitAt a6989586621679974447 a6989586621679974448 |
type SplitAtSym2 (a6989586621679974447 :: Nat) (a6989586621679974448 :: [a6989586621679970155]) = SplitAt a6989586621679974447 a6989586621679974448 Source #
data TakeWhileSym0 :: forall a6989586621679970162. (~>) ((~>) a6989586621679970162 Bool) ((~>) [a6989586621679970162] [a6989586621679970162]) Source #
Instances
SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing TakeWhileSym0 Source # | |
SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a6989586621679970162 ~> Bool) ([a6989586621679970162] ~> [a6989586621679970162]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym0 :: TyFun (a6989586621679970162 ~> Bool) ([a6989586621679970162] ~> [a6989586621679970162]) -> Type) (a6989586621679974611 :: a6989586621679970162 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym0 :: TyFun (a6989586621679970162 ~> Bool) ([a6989586621679970162] ~> [a6989586621679970162]) -> Type) (a6989586621679974611 :: a6989586621679970162 ~> Bool) = TakeWhileSym1 a6989586621679974611 |
data TakeWhileSym1 (a6989586621679974611 :: (~>) a6989586621679970162 Bool) :: (~>) [a6989586621679970162] [a6989586621679970162] Source #
Instances
SingI d => SingI (TakeWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (TakeWhileSym1 d) Source # | |
SuppressUnusedWarnings (TakeWhileSym1 a6989586621679974611 :: TyFun [a6989586621679970162] [a6989586621679970162] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym1 a6989586621679974611 :: TyFun [a] [a] -> Type) (a6989586621679974612 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym1 a6989586621679974611 :: TyFun [a] [a] -> Type) (a6989586621679974612 :: [a]) = TakeWhile a6989586621679974611 a6989586621679974612 |
type TakeWhileSym2 (a6989586621679974611 :: (~>) a6989586621679970162 Bool) (a6989586621679974612 :: [a6989586621679970162]) = TakeWhile a6989586621679974611 a6989586621679974612 Source #
data DropWhileSym0 :: forall a6989586621679970161. (~>) ((~>) a6989586621679970161 Bool) ((~>) [a6989586621679970161] [a6989586621679970161]) Source #
Instances
SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing DropWhileSym0 Source # | |
SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a6989586621679970161 ~> Bool) ([a6989586621679970161] ~> [a6989586621679970161]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym0 :: TyFun (a6989586621679970161 ~> Bool) ([a6989586621679970161] ~> [a6989586621679970161]) -> Type) (a6989586621679974593 :: a6989586621679970161 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym0 :: TyFun (a6989586621679970161 ~> Bool) ([a6989586621679970161] ~> [a6989586621679970161]) -> Type) (a6989586621679974593 :: a6989586621679970161 ~> Bool) = DropWhileSym1 a6989586621679974593 |
data DropWhileSym1 (a6989586621679974593 :: (~>) a6989586621679970161 Bool) :: (~>) [a6989586621679970161] [a6989586621679970161] Source #
Instances
SingI d => SingI (DropWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DropWhileSym1 d) Source # | |
SuppressUnusedWarnings (DropWhileSym1 a6989586621679974593 :: TyFun [a6989586621679970161] [a6989586621679970161] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym1 a6989586621679974593 :: TyFun [a] [a] -> Type) (a6989586621679974594 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym1 a6989586621679974593 :: TyFun [a] [a] -> Type) (a6989586621679974594 :: [a]) = DropWhile a6989586621679974593 a6989586621679974594 |
type DropWhileSym2 (a6989586621679974593 :: (~>) a6989586621679970161 Bool) (a6989586621679974594 :: [a6989586621679970161]) = DropWhile a6989586621679974593 a6989586621679974594 Source #
data DropWhileEndSym0 :: forall a6989586621679970160. (~>) ((~>) a6989586621679970160 Bool) ((~>) [a6989586621679970160] [a6989586621679970160]) Source #
Instances
SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a6989586621679970160 ~> Bool) ([a6989586621679970160] ~> [a6989586621679970160]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym0 :: TyFun (a6989586621679970160 ~> Bool) ([a6989586621679970160] ~> [a6989586621679970160]) -> Type) (a6989586621679974567 :: a6989586621679970160 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym0 :: TyFun (a6989586621679970160 ~> Bool) ([a6989586621679970160] ~> [a6989586621679970160]) -> Type) (a6989586621679974567 :: a6989586621679970160 ~> Bool) = DropWhileEndSym1 a6989586621679974567 |
data DropWhileEndSym1 (a6989586621679974567 :: (~>) a6989586621679970160 Bool) :: (~>) [a6989586621679970160] [a6989586621679970160] Source #
Instances
SingI d => SingI (DropWhileEndSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DropWhileEndSym1 d) Source # | |
SuppressUnusedWarnings (DropWhileEndSym1 a6989586621679974567 :: TyFun [a6989586621679970160] [a6989586621679970160] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym1 a6989586621679974567 :: TyFun [a] [a] -> Type) (a6989586621679974568 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym1 a6989586621679974567 :: TyFun [a] [a] -> Type) (a6989586621679974568 :: [a]) = DropWhileEnd a6989586621679974567 a6989586621679974568 |
type DropWhileEndSym2 (a6989586621679974567 :: (~>) a6989586621679970160 Bool) (a6989586621679974568 :: [a6989586621679970160]) = DropWhileEnd a6989586621679974567 a6989586621679974568 Source #
data SpanSym0 :: forall a6989586621679970159. (~>) ((~>) a6989586621679970159 Bool) ((~>) [a6989586621679970159] ([a6989586621679970159], [a6989586621679970159])) Source #
Instances
SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym0 :: TyFun (a6989586621679970159 ~> Bool) ([a6989586621679970159] ~> ([a6989586621679970159], [a6989586621679970159])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym0 :: TyFun (a6989586621679970159 ~> Bool) ([a6989586621679970159] ~> ([a6989586621679970159], [a6989586621679970159])) -> Type) (a6989586621679974524 :: a6989586621679970159 ~> Bool) Source # | |
data SpanSym1 (a6989586621679974524 :: (~>) a6989586621679970159 Bool) :: (~>) [a6989586621679970159] ([a6989586621679970159], [a6989586621679970159]) Source #
Instances
SingI d => SingI (SpanSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym1 a6989586621679974524 :: TyFun [a6989586621679970159] ([a6989586621679970159], [a6989586621679970159]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym1 a6989586621679974524 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679974525 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type SpanSym2 (a6989586621679974524 :: (~>) a6989586621679970159 Bool) (a6989586621679974525 :: [a6989586621679970159]) = Span a6989586621679974524 a6989586621679974525 Source #
data BreakSym0 :: forall a6989586621679970158. (~>) ((~>) a6989586621679970158 Bool) ((~>) [a6989586621679970158] ([a6989586621679970158], [a6989586621679970158])) Source #
Instances
SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym0 :: TyFun (a6989586621679970158 ~> Bool) ([a6989586621679970158] ~> ([a6989586621679970158], [a6989586621679970158])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym0 :: TyFun (a6989586621679970158 ~> Bool) ([a6989586621679970158] ~> ([a6989586621679970158], [a6989586621679970158])) -> Type) (a6989586621679974481 :: a6989586621679970158 ~> Bool) Source # | |
data BreakSym1 (a6989586621679974481 :: (~>) a6989586621679970158 Bool) :: (~>) [a6989586621679970158] ([a6989586621679970158], [a6989586621679970158]) Source #
Instances
SingI d => SingI (BreakSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym1 a6989586621679974481 :: TyFun [a6989586621679970158] ([a6989586621679970158], [a6989586621679970158]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym1 a6989586621679974481 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679974482 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type BreakSym2 (a6989586621679974481 :: (~>) a6989586621679970158 Bool) (a6989586621679974482 :: [a6989586621679970158]) = Break a6989586621679974481 a6989586621679974482 Source #
data StripPrefixSym0 :: forall a6989586621680092348. (~>) [a6989586621680092348] ((~>) [a6989586621680092348] (Maybe [a6989586621680092348])) Source #
Instances
SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a6989586621680092348] ([a6989586621680092348] ~> Maybe [a6989586621680092348]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (StripPrefixSym0 :: TyFun [a6989586621680092348] ([a6989586621680092348] ~> Maybe [a6989586621680092348]) -> Type) (a6989586621680094044 :: [a6989586621680092348]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym0 :: TyFun [a6989586621680092348] ([a6989586621680092348] ~> Maybe [a6989586621680092348]) -> Type) (a6989586621680094044 :: [a6989586621680092348]) = StripPrefixSym1 a6989586621680094044 |
data StripPrefixSym1 (a6989586621680094044 :: [a6989586621680092348]) :: (~>) [a6989586621680092348] (Maybe [a6989586621680092348]) Source #
Instances
SuppressUnusedWarnings (StripPrefixSym1 a6989586621680094044 :: TyFun [a6989586621680092348] (Maybe [a6989586621680092348]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (StripPrefixSym1 a6989586621680094044 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680094045 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym1 a6989586621680094044 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680094045 :: [a]) = StripPrefix a6989586621680094044 a6989586621680094045 |
type StripPrefixSym2 (a6989586621680094044 :: [a6989586621680092348]) (a6989586621680094045 :: [a6989586621680092348]) = StripPrefix a6989586621680094044 a6989586621680094045 Source #
data GroupSym0 :: forall a6989586621679970154. (~>) [a6989586621679970154] [[a6989586621679970154]] Source #
Instances
SEq a => SingI (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621679970154] [[a6989586621679970154]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679974444 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type GroupSym1 (a6989586621679974444 :: [a6989586621679970154]) = Group a6989586621679974444 Source #
data InitsSym0 :: forall a6989586621679970224. (~>) [a6989586621679970224] [[a6989586621679970224]] Source #
Instances
SingI (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621679970224] [[a6989586621679970224]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679975129 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type InitsSym1 (a6989586621679975129 :: [a6989586621679970224]) = Inits a6989586621679975129 Source #
data TailsSym0 :: forall a6989586621679970223. (~>) [a6989586621679970223] [[a6989586621679970223]] Source #
Instances
SingI (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621679970223] [[a6989586621679970223]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679975122 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type TailsSym1 (a6989586621679975122 :: [a6989586621679970223]) = Tails a6989586621679975122 Source #
data IsPrefixOfSym0 :: forall a6989586621679970222. (~>) [a6989586621679970222] ((~>) [a6989586621679970222] Bool) Source #
Instances
SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679970222] ([a6989586621679970222] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679970222] ([a6989586621679970222] ~> Bool) -> Type) (a6989586621679975114 :: [a6989586621679970222]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679970222] ([a6989586621679970222] ~> Bool) -> Type) (a6989586621679975114 :: [a6989586621679970222]) = IsPrefixOfSym1 a6989586621679975114 |
data IsPrefixOfSym1 (a6989586621679975114 :: [a6989586621679970222]) :: (~>) [a6989586621679970222] Bool Source #
Instances
(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IsPrefixOfSym1 d) Source # | |
SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679975114 :: TyFun [a6989586621679970222] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym1 a6989586621679975114 :: TyFun [a] Bool -> Type) (a6989586621679975115 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym1 a6989586621679975114 :: TyFun [a] Bool -> Type) (a6989586621679975115 :: [a]) = IsPrefixOf a6989586621679975114 a6989586621679975115 |
type IsPrefixOfSym2 (a6989586621679975114 :: [a6989586621679970222]) (a6989586621679975115 :: [a6989586621679970222]) = IsPrefixOf a6989586621679975114 a6989586621679975115 Source #
data IsSuffixOfSym0 :: forall a6989586621679970221. (~>) [a6989586621679970221] ((~>) [a6989586621679970221] Bool) Source #
Instances
SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679970221] ([a6989586621679970221] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679970221] ([a6989586621679970221] ~> Bool) -> Type) (a6989586621679975108 :: [a6989586621679970221]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679970221] ([a6989586621679970221] ~> Bool) -> Type) (a6989586621679975108 :: [a6989586621679970221]) = IsSuffixOfSym1 a6989586621679975108 |
data IsSuffixOfSym1 (a6989586621679975108 :: [a6989586621679970221]) :: (~>) [a6989586621679970221] Bool Source #
Instances
(SEq a, SingI d) => SingI (IsSuffixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IsSuffixOfSym1 d) Source # | |
SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679975108 :: TyFun [a6989586621679970221] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym1 a6989586621679975108 :: TyFun [a] Bool -> Type) (a6989586621679975109 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym1 a6989586621679975108 :: TyFun [a] Bool -> Type) (a6989586621679975109 :: [a]) = IsSuffixOf a6989586621679975108 a6989586621679975109 |
type IsSuffixOfSym2 (a6989586621679975108 :: [a6989586621679970221]) (a6989586621679975109 :: [a6989586621679970221]) = IsSuffixOf a6989586621679975108 a6989586621679975109 Source #
data IsInfixOfSym0 :: forall a6989586621679970220. (~>) [a6989586621679970220] ((~>) [a6989586621679970220] Bool) Source #
Instances
SEq a => SingI (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing IsInfixOfSym0 Source # | |
SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a6989586621679970220] ([a6989586621679970220] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym0 :: TyFun [a6989586621679970220] ([a6989586621679970220] ~> Bool) -> Type) (a6989586621679975102 :: [a6989586621679970220]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsInfixOfSym0 :: TyFun [a6989586621679970220] ([a6989586621679970220] ~> Bool) -> Type) (a6989586621679975102 :: [a6989586621679970220]) = IsInfixOfSym1 a6989586621679975102 |
data IsInfixOfSym1 (a6989586621679975102 :: [a6989586621679970220]) :: (~>) [a6989586621679970220] Bool Source #
Instances
(SEq a, SingI d) => SingI (IsInfixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IsInfixOfSym1 d) Source # | |
SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679975102 :: TyFun [a6989586621679970220] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym1 a6989586621679975102 :: TyFun [a] Bool -> Type) (a6989586621679975103 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsInfixOfSym1 a6989586621679975102 :: TyFun [a] Bool -> Type) (a6989586621679975103 :: [a]) = IsInfixOf a6989586621679975102 a6989586621679975103 |
type IsInfixOfSym2 (a6989586621679975102 :: [a6989586621679970220]) (a6989586621679975103 :: [a6989586621679970220]) = IsInfixOf a6989586621679975102 a6989586621679975103 Source #
data ElemSym0 :: forall a6989586621680486596 t6989586621680486579. (~>) a6989586621680486596 ((~>) (t6989586621680486579 a6989586621680486596) Bool) Source #
Instances
(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621680486596 (t6989586621680486579 a6989586621680486596 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym0 :: TyFun a6989586621680486596 (t6989586621680486579 a6989586621680486596 ~> Bool) -> Type) (arg6989586621680487242 :: a6989586621680486596) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data ElemSym1 (arg6989586621680487242 :: a6989586621680486596) :: forall t6989586621680486579. (~>) (t6989586621680486579 a6989586621680486596) Bool Source #
Instances
(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (ElemSym1 arg6989586621680487242 t6989586621680486579 :: TyFun (t6989586621680486579 a6989586621680486596) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym1 arg6989586621680487242 t :: TyFun (t a) Bool -> Type) (arg6989586621680487243 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type ElemSym2 (arg6989586621680487242 :: a6989586621680486596) (arg6989586621680487243 :: t6989586621680486579 a6989586621680486596) = Elem arg6989586621680487242 arg6989586621680487243 Source #
data NotElemSym0 :: forall a6989586621680486490 t6989586621680486489. (~>) a6989586621680486490 ((~>) (t6989586621680486489 a6989586621680486490) Bool) Source #
Instances
(SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing NotElemSym0 Source # | |
SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621680486490 (t6989586621680486489 a6989586621680486490 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym0 :: TyFun a6989586621680486490 (t6989586621680486489 a6989586621680486490 ~> Bool) -> Type) (a6989586621680486968 :: a6989586621680486490) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (NotElemSym0 :: TyFun a6989586621680486490 (t6989586621680486489 a6989586621680486490 ~> Bool) -> Type) (a6989586621680486968 :: a6989586621680486490) = NotElemSym1 a6989586621680486968 t6989586621680486489 :: TyFun (t6989586621680486489 a6989586621680486490) Bool -> Type |
data NotElemSym1 (a6989586621680486968 :: a6989586621680486490) :: forall t6989586621680486489. (~>) (t6989586621680486489 a6989586621680486490) Bool Source #
Instances
(SFoldable t, SEq a, SingI d) => SingI (NotElemSym1 d t :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (NotElemSym1 d t) Source # | |
SuppressUnusedWarnings (NotElemSym1 a6989586621680486968 t6989586621680486489 :: TyFun (t6989586621680486489 a6989586621680486490) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym1 a6989586621680486968 t :: TyFun (t a) Bool -> Type) (a6989586621680486969 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (NotElemSym1 a6989586621680486968 t :: TyFun (t a) Bool -> Type) (a6989586621680486969 :: t a) = NotElem a6989586621680486968 a6989586621680486969 |
type NotElemSym2 (a6989586621680486968 :: a6989586621680486490) (a6989586621680486969 :: t6989586621680486489 a6989586621680486490) = NotElem a6989586621680486968 a6989586621680486969 Source #
data LookupSym0 :: forall a6989586621679970147 b6989586621679970148. (~>) a6989586621679970147 ((~>) [(a6989586621679970147, b6989586621679970148)] (Maybe b6989586621679970148)) Source #
Instances
SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing LookupSym0 Source # | |
SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679970147 ([(a6989586621679970147, b6989586621679970148)] ~> Maybe b6989586621679970148) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym0 :: TyFun a6989586621679970147 ([(a6989586621679970147, b6989586621679970148)] ~> Maybe b6989586621679970148) -> Type) (a6989586621679974371 :: a6989586621679970147) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (LookupSym0 :: TyFun a6989586621679970147 ([(a6989586621679970147, b6989586621679970148)] ~> Maybe b6989586621679970148) -> Type) (a6989586621679974371 :: a6989586621679970147) = LookupSym1 a6989586621679974371 b6989586621679970148 :: TyFun [(a6989586621679970147, b6989586621679970148)] (Maybe b6989586621679970148) -> Type |
data LookupSym1 (a6989586621679974371 :: a6989586621679970147) :: forall b6989586621679970148. (~>) [(a6989586621679970147, b6989586621679970148)] (Maybe b6989586621679970148) Source #
Instances
(SEq a, SingI d) => SingI (LookupSym1 d b :: TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (LookupSym1 d b) Source # | |
SuppressUnusedWarnings (LookupSym1 a6989586621679974371 b6989586621679970148 :: TyFun [(a6989586621679970147, b6989586621679970148)] (Maybe b6989586621679970148) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym1 a6989586621679974371 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679974372 :: [(a, b)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (LookupSym1 a6989586621679974371 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679974372 :: [(a, b)]) = Lookup a6989586621679974371 a6989586621679974372 |
type LookupSym2 (a6989586621679974371 :: a6989586621679970147) (a6989586621679974372 :: [(a6989586621679970147, b6989586621679970148)]) = Lookup a6989586621679974371 a6989586621679974372 Source #
data FindSym0 :: forall a6989586621680486488 t6989586621680486487. (~>) ((~>) a6989586621680486488 Bool) ((~>) (t6989586621680486487 a6989586621680486488) (Maybe a6989586621680486488)) Source #
Instances
SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # | |
SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680486488 ~> Bool) (t6989586621680486487 a6989586621680486488 ~> Maybe a6989586621680486488) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindSym0 :: TyFun (a6989586621680486488 ~> Bool) (t6989586621680486487 a6989586621680486488 ~> Maybe a6989586621680486488) -> Type) (a6989586621680486941 :: a6989586621680486488 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FindSym0 :: TyFun (a6989586621680486488 ~> Bool) (t6989586621680486487 a6989586621680486488 ~> Maybe a6989586621680486488) -> Type) (a6989586621680486941 :: a6989586621680486488 ~> Bool) = FindSym1 a6989586621680486941 t6989586621680486487 :: TyFun (t6989586621680486487 a6989586621680486488) (Maybe a6989586621680486488) -> Type |
data FindSym1 (a6989586621680486941 :: (~>) a6989586621680486488 Bool) :: forall t6989586621680486487. (~>) (t6989586621680486487 a6989586621680486488) (Maybe a6989586621680486488) Source #
Instances
(SFoldable t, SingI d) => SingI (FindSym1 d t :: TyFun (t a) (Maybe a) -> Type) Source # | |
SuppressUnusedWarnings (FindSym1 a6989586621680486941 t6989586621680486487 :: TyFun (t6989586621680486487 a6989586621680486488) (Maybe a6989586621680486488) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindSym1 a6989586621680486941 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680486942 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type FindSym2 (a6989586621680486941 :: (~>) a6989586621680486488 Bool) (a6989586621680486942 :: t6989586621680486487 a6989586621680486488) = Find a6989586621680486941 a6989586621680486942 Source #
data FilterSym0 :: forall a6989586621679970170. (~>) ((~>) a6989586621679970170 Bool) ((~>) [a6989586621679970170] [a6989586621679970170]) Source #
Instances
SingI (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing FilterSym0 Source # | |
SuppressUnusedWarnings (FilterSym0 :: TyFun (a6989586621679970170 ~> Bool) ([a6989586621679970170] ~> [a6989586621679970170]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym0 :: TyFun (a6989586621679970170 ~> Bool) ([a6989586621679970170] ~> [a6989586621679970170]) -> Type) (a6989586621679974725 :: a6989586621679970170 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym0 :: TyFun (a6989586621679970170 ~> Bool) ([a6989586621679970170] ~> [a6989586621679970170]) -> Type) (a6989586621679974725 :: a6989586621679970170 ~> Bool) = FilterSym1 a6989586621679974725 |
data FilterSym1 (a6989586621679974725 :: (~>) a6989586621679970170 Bool) :: (~>) [a6989586621679970170] [a6989586621679970170] Source #
Instances
SingI d => SingI (FilterSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (FilterSym1 d) Source # | |
SuppressUnusedWarnings (FilterSym1 a6989586621679974725 :: TyFun [a6989586621679970170] [a6989586621679970170] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym1 a6989586621679974725 :: TyFun [a] [a] -> Type) (a6989586621679974726 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym1 a6989586621679974725 :: TyFun [a] [a] -> Type) (a6989586621679974726 :: [a]) = Filter a6989586621679974725 a6989586621679974726 |
type FilterSym2 (a6989586621679974725 :: (~>) a6989586621679970170 Bool) (a6989586621679974726 :: [a6989586621679970170]) = Filter a6989586621679974725 a6989586621679974726 Source #
data PartitionSym0 :: forall a6989586621679970146. (~>) ((~>) a6989586621679970146 Bool) ((~>) [a6989586621679970146] ([a6989586621679970146], [a6989586621679970146])) Source #
Instances
SingI (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing PartitionSym0 Source # | |
SuppressUnusedWarnings (PartitionSym0 :: TyFun (a6989586621679970146 ~> Bool) ([a6989586621679970146] ~> ([a6989586621679970146], [a6989586621679970146])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym0 :: TyFun (a6989586621679970146 ~> Bool) ([a6989586621679970146] ~> ([a6989586621679970146], [a6989586621679970146])) -> Type) (a6989586621679974365 :: a6989586621679970146 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym0 :: TyFun (a6989586621679970146 ~> Bool) ([a6989586621679970146] ~> ([a6989586621679970146], [a6989586621679970146])) -> Type) (a6989586621679974365 :: a6989586621679970146 ~> Bool) = PartitionSym1 a6989586621679974365 |
data PartitionSym1 (a6989586621679974365 :: (~>) a6989586621679970146 Bool) :: (~>) [a6989586621679970146] ([a6989586621679970146], [a6989586621679970146]) Source #
Instances
SingI d => SingI (PartitionSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (PartitionSym1 d) Source # | |
SuppressUnusedWarnings (PartitionSym1 a6989586621679974365 :: TyFun [a6989586621679970146] ([a6989586621679970146], [a6989586621679970146]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym1 a6989586621679974365 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679974366 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym1 a6989586621679974365 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679974366 :: [a]) = Partition a6989586621679974365 a6989586621679974366 |
type PartitionSym2 (a6989586621679974365 :: (~>) a6989586621679970146 Bool) (a6989586621679974366 :: [a6989586621679970146]) = Partition a6989586621679974365 a6989586621679974366 Source #
data (!!@#@$) :: forall a6989586621679970139. (~>) [a6989586621679970139] ((~>) Nat a6989586621679970139) infixl 9 Source #
Instances
SingI ((!!@#@$) :: TyFun [a] (Nat ~> a) -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$) :: TyFun [a6989586621679970139] (Nat ~> a6989586621679970139) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$) :: TyFun [a6989586621679970139] (Nat ~> a6989586621679970139) -> Type) (a6989586621679974286 :: [a6989586621679970139]) Source # | |
data (!!@#@$$) (a6989586621679974286 :: [a6989586621679970139]) :: (~>) Nat a6989586621679970139 infixl 9 Source #
Instances
SingI d => SingI ((!!@#@$$) d :: TyFun Nat a -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$$) a6989586621679974286 :: TyFun Nat a6989586621679970139 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$$) a6989586621679974286 :: TyFun Nat a -> Type) (a6989586621679974287 :: Nat) Source # | |
type (!!@#@$$$) (a6989586621679974286 :: [a6989586621679970139]) (a6989586621679974287 :: Nat) = (!!) a6989586621679974286 a6989586621679974287 Source #
data ElemIndexSym0 :: forall a6989586621679970168. (~>) a6989586621679970168 ((~>) [a6989586621679970168] (Maybe Nat)) Source #
Instances
SEq a => SingI (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing ElemIndexSym0 Source # | |
SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679970168 ([a6989586621679970168] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym0 :: TyFun a6989586621679970168 ([a6989586621679970168] ~> Maybe Nat) -> Type) (a6989586621679974709 :: a6989586621679970168) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndexSym0 :: TyFun a6989586621679970168 ([a6989586621679970168] ~> Maybe Nat) -> Type) (a6989586621679974709 :: a6989586621679970168) = ElemIndexSym1 a6989586621679974709 |
data ElemIndexSym1 (a6989586621679974709 :: a6989586621679970168) :: (~>) [a6989586621679970168] (Maybe Nat) Source #
Instances
(SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ElemIndexSym1 d) Source # | |
SuppressUnusedWarnings (ElemIndexSym1 a6989586621679974709 :: TyFun [a6989586621679970168] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym1 a6989586621679974709 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679974710 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndexSym1 a6989586621679974709 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679974710 :: [a]) = ElemIndex a6989586621679974709 a6989586621679974710 |
type ElemIndexSym2 (a6989586621679974709 :: a6989586621679970168) (a6989586621679974710 :: [a6989586621679970168]) = ElemIndex a6989586621679974709 a6989586621679974710 Source #
data ElemIndicesSym0 :: forall a6989586621679970167. (~>) a6989586621679970167 ((~>) [a6989586621679970167] [Nat]) Source #
Instances
SEq a => SingI (ElemIndicesSym0 :: TyFun a ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a6989586621679970167 ([a6989586621679970167] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym0 :: TyFun a6989586621679970167 ([a6989586621679970167] ~> [Nat]) -> Type) (a6989586621679974701 :: a6989586621679970167) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym0 :: TyFun a6989586621679970167 ([a6989586621679970167] ~> [Nat]) -> Type) (a6989586621679974701 :: a6989586621679970167) = ElemIndicesSym1 a6989586621679974701 |
data ElemIndicesSym1 (a6989586621679974701 :: a6989586621679970167) :: (~>) [a6989586621679970167] [Nat] Source #
Instances
(SEq a, SingI d) => SingI (ElemIndicesSym1 d :: TyFun [a] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ElemIndicesSym1 d) Source # | |
SuppressUnusedWarnings (ElemIndicesSym1 a6989586621679974701 :: TyFun [a6989586621679970167] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym1 a6989586621679974701 :: TyFun [a] [Nat] -> Type) (a6989586621679974702 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym1 a6989586621679974701 :: TyFun [a] [Nat] -> Type) (a6989586621679974702 :: [a]) = ElemIndices a6989586621679974701 a6989586621679974702 |
type ElemIndicesSym2 (a6989586621679974701 :: a6989586621679970167) (a6989586621679974702 :: [a6989586621679970167]) = ElemIndices a6989586621679974701 a6989586621679974702 Source #
data FindIndexSym0 :: forall a6989586621679970166. (~>) ((~>) a6989586621679970166 Bool) ((~>) [a6989586621679970166] (Maybe Nat)) Source #
Instances
SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing FindIndexSym0 Source # | |
SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a6989586621679970166 ~> Bool) ([a6989586621679970166] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym0 :: TyFun (a6989586621679970166 ~> Bool) ([a6989586621679970166] ~> Maybe Nat) -> Type) (a6989586621679974693 :: a6989586621679970166 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndexSym0 :: TyFun (a6989586621679970166 ~> Bool) ([a6989586621679970166] ~> Maybe Nat) -> Type) (a6989586621679974693 :: a6989586621679970166 ~> Bool) = FindIndexSym1 a6989586621679974693 |
data FindIndexSym1 (a6989586621679974693 :: (~>) a6989586621679970166 Bool) :: (~>) [a6989586621679970166] (Maybe Nat) Source #
Instances
SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (FindIndexSym1 d) Source # | |
SuppressUnusedWarnings (FindIndexSym1 a6989586621679974693 :: TyFun [a6989586621679970166] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym1 a6989586621679974693 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679974694 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndexSym1 a6989586621679974693 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679974694 :: [a]) = FindIndex a6989586621679974693 a6989586621679974694 |
type FindIndexSym2 (a6989586621679974693 :: (~>) a6989586621679970166 Bool) (a6989586621679974694 :: [a6989586621679970166]) = FindIndex a6989586621679974693 a6989586621679974694 Source #
data FindIndicesSym0 :: forall a6989586621679970165. (~>) ((~>) a6989586621679970165 Bool) ((~>) [a6989586621679970165] [Nat]) Source #
Instances
SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (a6989586621679970165 ~> Bool) ([a6989586621679970165] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym0 :: TyFun (a6989586621679970165 ~> Bool) ([a6989586621679970165] ~> [Nat]) -> Type) (a6989586621679974667 :: a6989586621679970165 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndicesSym0 :: TyFun (a6989586621679970165 ~> Bool) ([a6989586621679970165] ~> [Nat]) -> Type) (a6989586621679974667 :: a6989586621679970165 ~> Bool) = FindIndicesSym1 a6989586621679974667 |
data FindIndicesSym1 (a6989586621679974667 :: (~>) a6989586621679970165 Bool) :: (~>) [a6989586621679970165] [Nat] Source #
Instances
SingI d => SingI (FindIndicesSym1 d :: TyFun [a] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (FindIndicesSym1 d) Source # | |
SuppressUnusedWarnings (FindIndicesSym1 a6989586621679974667 :: TyFun [a6989586621679970165] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym1 a6989586621679974667 :: TyFun [a] [Nat] -> Type) (a6989586621679974668 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndicesSym1 a6989586621679974667 :: TyFun [a] [Nat] -> Type) (a6989586621679974668 :: [a]) = FindIndices a6989586621679974667 a6989586621679974668 |
type FindIndicesSym2 (a6989586621679974667 :: (~>) a6989586621679970165 Bool) (a6989586621679974668 :: [a6989586621679970165]) = FindIndices a6989586621679974667 a6989586621679974668 Source #
data ZipSym0 :: forall a6989586621679970216 b6989586621679970217. (~>) [a6989586621679970216] ((~>) [b6989586621679970217] [(a6989586621679970216, b6989586621679970217)]) Source #
Instances
SingI (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # | |
SuppressUnusedWarnings (ZipSym0 :: TyFun [a6989586621679970216] ([b6989586621679970217] ~> [(a6989586621679970216, b6989586621679970217)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym0 :: TyFun [a6989586621679970216] ([b6989586621679970217] ~> [(a6989586621679970216, b6989586621679970217)]) -> Type) (a6989586621679975080 :: [a6989586621679970216]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipSym0 :: TyFun [a6989586621679970216] ([b6989586621679970217] ~> [(a6989586621679970216, b6989586621679970217)]) -> Type) (a6989586621679975080 :: [a6989586621679970216]) = ZipSym1 a6989586621679975080 b6989586621679970217 :: TyFun [b6989586621679970217] [(a6989586621679970216, b6989586621679970217)] -> Type |
data ZipSym1 (a6989586621679975080 :: [a6989586621679970216]) :: forall b6989586621679970217. (~>) [b6989586621679970217] [(a6989586621679970216, b6989586621679970217)] Source #
Instances
SingI d => SingI (ZipSym1 d b :: TyFun [b] [(a, b)] -> Type) Source # | |
SuppressUnusedWarnings (ZipSym1 a6989586621679975080 b6989586621679970217 :: TyFun [b6989586621679970217] [(a6989586621679970216, b6989586621679970217)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym1 a6989586621679975080 b :: TyFun [b] [(a, b)] -> Type) (a6989586621679975081 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type ZipSym2 (a6989586621679975080 :: [a6989586621679970216]) (a6989586621679975081 :: [b6989586621679970217]) = Zip a6989586621679975080 a6989586621679975081 Source #
data Zip3Sym0 :: forall a6989586621679970213 b6989586621679970214 c6989586621679970215. (~>) [a6989586621679970213] ((~>) [b6989586621679970214] ((~>) [c6989586621679970215] [(a6989586621679970213, b6989586621679970214, c6989586621679970215)])) Source #
Instances
SingI (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a6989586621679970213] ([b6989586621679970214] ~> ([c6989586621679970215] ~> [(a6989586621679970213, b6989586621679970214, c6989586621679970215)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym0 :: TyFun [a6989586621679970213] ([b6989586621679970214] ~> ([c6989586621679970215] ~> [(a6989586621679970213, b6989586621679970214, c6989586621679970215)])) -> Type) (a6989586621679975068 :: [a6989586621679970213]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip3Sym0 :: TyFun [a6989586621679970213] ([b6989586621679970214] ~> ([c6989586621679970215] ~> [(a6989586621679970213, b6989586621679970214, c6989586621679970215)])) -> Type) (a6989586621679975068 :: [a6989586621679970213]) = Zip3Sym1 a6989586621679975068 b6989586621679970214 c6989586621679970215 :: TyFun [b6989586621679970214] ([c6989586621679970215] ~> [(a6989586621679970213, b6989586621679970214, c6989586621679970215)]) -> Type |
data Zip3Sym1 (a6989586621679975068 :: [a6989586621679970213]) :: forall b6989586621679970214 c6989586621679970215. (~>) [b6989586621679970214] ((~>) [c6989586621679970215] [(a6989586621679970213, b6989586621679970214, c6989586621679970215)]) Source #
Instances
SingI d => SingI (Zip3Sym1 d b c :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym1 a6989586621679975068 b6989586621679970214 c6989586621679970215 :: TyFun [b6989586621679970214] ([c6989586621679970215] ~> [(a6989586621679970213, b6989586621679970214, c6989586621679970215)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym1 a6989586621679975068 b6989586621679970214 c6989586621679970215 :: TyFun [b6989586621679970214] ([c6989586621679970215] ~> [(a6989586621679970213, b6989586621679970214, c6989586621679970215)]) -> Type) (a6989586621679975069 :: [b6989586621679970214]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip3Sym1 a6989586621679975068 b6989586621679970214 c6989586621679970215 :: TyFun [b6989586621679970214] ([c6989586621679970215] ~> [(a6989586621679970213, b6989586621679970214, c6989586621679970215)]) -> Type) (a6989586621679975069 :: [b6989586621679970214]) = Zip3Sym2 a6989586621679975068 a6989586621679975069 c6989586621679970215 :: TyFun [c6989586621679970215] [(a6989586621679970213, b6989586621679970214, c6989586621679970215)] -> Type |
data Zip3Sym2 (a6989586621679975068 :: [a6989586621679970213]) (a6989586621679975069 :: [b6989586621679970214]) :: forall c6989586621679970215. (~>) [c6989586621679970215] [(a6989586621679970213, b6989586621679970214, c6989586621679970215)] Source #
Instances
(SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 c :: TyFun [c] [(a, b, c)] -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym2 a6989586621679975069 a6989586621679975068 c6989586621679970215 :: TyFun [c6989586621679970215] [(a6989586621679970213, b6989586621679970214, c6989586621679970215)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym2 a6989586621679975069 a6989586621679975068 c :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679975070 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type Zip3Sym3 (a6989586621679975068 :: [a6989586621679970213]) (a6989586621679975069 :: [b6989586621679970214]) (a6989586621679975070 :: [c6989586621679970215]) = Zip3 a6989586621679975068 a6989586621679975069 a6989586621679975070 Source #
data Zip4Sym0 :: forall a6989586621680092344 b6989586621680092345 c6989586621680092346 d6989586621680092347. (~>) [a6989586621680092344] ((~>) [b6989586621680092345] ((~>) [c6989586621680092346] ((~>) [d6989586621680092347] [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)]))) Source #
Instances
SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a6989586621680092344] ([b6989586621680092345] ~> ([c6989586621680092346] ~> ([d6989586621680092347] ~> [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym0 :: TyFun [a6989586621680092344] ([b6989586621680092345] ~> ([c6989586621680092346] ~> ([d6989586621680092347] ~> [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)]))) -> Type) (a6989586621680094032 :: [a6989586621680092344]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym0 :: TyFun [a6989586621680092344] ([b6989586621680092345] ~> ([c6989586621680092346] ~> ([d6989586621680092347] ~> [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)]))) -> Type) (a6989586621680094032 :: [a6989586621680092344]) = Zip4Sym1 a6989586621680094032 b6989586621680092345 c6989586621680092346 d6989586621680092347 :: TyFun [b6989586621680092345] ([c6989586621680092346] ~> ([d6989586621680092347] ~> [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)])) -> Type |
data Zip4Sym1 (a6989586621680094032 :: [a6989586621680092344]) :: forall b6989586621680092345 c6989586621680092346 d6989586621680092347. (~>) [b6989586621680092345] ((~>) [c6989586621680092346] ((~>) [d6989586621680092347] [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)])) Source #
Instances
SuppressUnusedWarnings (Zip4Sym1 a6989586621680094032 b6989586621680092345 c6989586621680092346 d6989586621680092347 :: TyFun [b6989586621680092345] ([c6989586621680092346] ~> ([d6989586621680092347] ~> [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym1 a6989586621680094032 b6989586621680092345 c6989586621680092346 d6989586621680092347 :: TyFun [b6989586621680092345] ([c6989586621680092346] ~> ([d6989586621680092347] ~> [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)])) -> Type) (a6989586621680094033 :: [b6989586621680092345]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym1 a6989586621680094032 b6989586621680092345 c6989586621680092346 d6989586621680092347 :: TyFun [b6989586621680092345] ([c6989586621680092346] ~> ([d6989586621680092347] ~> [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)])) -> Type) (a6989586621680094033 :: [b6989586621680092345]) = Zip4Sym2 a6989586621680094032 a6989586621680094033 c6989586621680092346 d6989586621680092347 :: TyFun [c6989586621680092346] ([d6989586621680092347] ~> [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)]) -> Type |
data Zip4Sym2 (a6989586621680094032 :: [a6989586621680092344]) (a6989586621680094033 :: [b6989586621680092345]) :: forall c6989586621680092346 d6989586621680092347. (~>) [c6989586621680092346] ((~>) [d6989586621680092347] [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)]) Source #
Instances
SuppressUnusedWarnings (Zip4Sym2 a6989586621680094033 a6989586621680094032 c6989586621680092346 d6989586621680092347 :: TyFun [c6989586621680092346] ([d6989586621680092347] ~> [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym2 a6989586621680094033 a6989586621680094032 c6989586621680092346 d6989586621680092347 :: TyFun [c6989586621680092346] ([d6989586621680092347] ~> [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)]) -> Type) (a6989586621680094034 :: [c6989586621680092346]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym2 a6989586621680094033 a6989586621680094032 c6989586621680092346 d6989586621680092347 :: TyFun [c6989586621680092346] ([d6989586621680092347] ~> [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)]) -> Type) (a6989586621680094034 :: [c6989586621680092346]) = Zip4Sym3 a6989586621680094033 a6989586621680094032 a6989586621680094034 d6989586621680092347 :: TyFun [d6989586621680092347] [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)] -> Type |
data Zip4Sym3 (a6989586621680094032 :: [a6989586621680092344]) (a6989586621680094033 :: [b6989586621680092345]) (a6989586621680094034 :: [c6989586621680092346]) :: forall d6989586621680092347. (~>) [d6989586621680092347] [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)] Source #
Instances
SuppressUnusedWarnings (Zip4Sym3 a6989586621680094034 a6989586621680094033 a6989586621680094032 d6989586621680092347 :: TyFun [d6989586621680092347] [(a6989586621680092344, b6989586621680092345, c6989586621680092346, d6989586621680092347)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym3 a6989586621680094034 a6989586621680094033 a6989586621680094032 d :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621680094035 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type Zip4Sym4 (a6989586621680094032 :: [a6989586621680092344]) (a6989586621680094033 :: [b6989586621680092345]) (a6989586621680094034 :: [c6989586621680092346]) (a6989586621680094035 :: [d6989586621680092347]) = Zip4 a6989586621680094032 a6989586621680094033 a6989586621680094034 a6989586621680094035 Source #
data Zip5Sym0 :: forall a6989586621680092339 b6989586621680092340 c6989586621680092341 d6989586621680092342 e6989586621680092343. (~>) [a6989586621680092339] ((~>) [b6989586621680092340] ((~>) [c6989586621680092341] ((~>) [d6989586621680092342] ((~>) [e6989586621680092343] [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)])))) Source #
Instances
SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a6989586621680092339] ([b6989586621680092340] ~> ([c6989586621680092341] ~> ([d6989586621680092342] ~> ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym0 :: TyFun [a6989586621680092339] ([b6989586621680092340] ~> ([c6989586621680092341] ~> ([d6989586621680092342] ~> ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)])))) -> Type) (a6989586621680094009 :: [a6989586621680092339]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym0 :: TyFun [a6989586621680092339] ([b6989586621680092340] ~> ([c6989586621680092341] ~> ([d6989586621680092342] ~> ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)])))) -> Type) (a6989586621680094009 :: [a6989586621680092339]) = Zip5Sym1 a6989586621680094009 b6989586621680092340 c6989586621680092341 d6989586621680092342 e6989586621680092343 :: TyFun [b6989586621680092340] ([c6989586621680092341] ~> ([d6989586621680092342] ~> ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]))) -> Type |
data Zip5Sym1 (a6989586621680094009 :: [a6989586621680092339]) :: forall b6989586621680092340 c6989586621680092341 d6989586621680092342 e6989586621680092343. (~>) [b6989586621680092340] ((~>) [c6989586621680092341] ((~>) [d6989586621680092342] ((~>) [e6989586621680092343] [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]))) Source #
Instances
SuppressUnusedWarnings (Zip5Sym1 a6989586621680094009 b6989586621680092340 c6989586621680092341 d6989586621680092342 e6989586621680092343 :: TyFun [b6989586621680092340] ([c6989586621680092341] ~> ([d6989586621680092342] ~> ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym1 a6989586621680094009 b6989586621680092340 c6989586621680092341 d6989586621680092342 e6989586621680092343 :: TyFun [b6989586621680092340] ([c6989586621680092341] ~> ([d6989586621680092342] ~> ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]))) -> Type) (a6989586621680094010 :: [b6989586621680092340]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym1 a6989586621680094009 b6989586621680092340 c6989586621680092341 d6989586621680092342 e6989586621680092343 :: TyFun [b6989586621680092340] ([c6989586621680092341] ~> ([d6989586621680092342] ~> ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]))) -> Type) (a6989586621680094010 :: [b6989586621680092340]) = Zip5Sym2 a6989586621680094009 a6989586621680094010 c6989586621680092341 d6989586621680092342 e6989586621680092343 :: TyFun [c6989586621680092341] ([d6989586621680092342] ~> ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)])) -> Type |
data Zip5Sym2 (a6989586621680094009 :: [a6989586621680092339]) (a6989586621680094010 :: [b6989586621680092340]) :: forall c6989586621680092341 d6989586621680092342 e6989586621680092343. (~>) [c6989586621680092341] ((~>) [d6989586621680092342] ((~>) [e6989586621680092343] [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)])) Source #
Instances
SuppressUnusedWarnings (Zip5Sym2 a6989586621680094010 a6989586621680094009 c6989586621680092341 d6989586621680092342 e6989586621680092343 :: TyFun [c6989586621680092341] ([d6989586621680092342] ~> ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym2 a6989586621680094010 a6989586621680094009 c6989586621680092341 d6989586621680092342 e6989586621680092343 :: TyFun [c6989586621680092341] ([d6989586621680092342] ~> ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)])) -> Type) (a6989586621680094011 :: [c6989586621680092341]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym2 a6989586621680094010 a6989586621680094009 c6989586621680092341 d6989586621680092342 e6989586621680092343 :: TyFun [c6989586621680092341] ([d6989586621680092342] ~> ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)])) -> Type) (a6989586621680094011 :: [c6989586621680092341]) = Zip5Sym3 a6989586621680094010 a6989586621680094009 a6989586621680094011 d6989586621680092342 e6989586621680092343 :: TyFun [d6989586621680092342] ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]) -> Type |
data Zip5Sym3 (a6989586621680094009 :: [a6989586621680092339]) (a6989586621680094010 :: [b6989586621680092340]) (a6989586621680094011 :: [c6989586621680092341]) :: forall d6989586621680092342 e6989586621680092343. (~>) [d6989586621680092342] ((~>) [e6989586621680092343] [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]) Source #
Instances
SuppressUnusedWarnings (Zip5Sym3 a6989586621680094011 a6989586621680094010 a6989586621680094009 d6989586621680092342 e6989586621680092343 :: TyFun [d6989586621680092342] ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym3 a6989586621680094011 a6989586621680094010 a6989586621680094009 d6989586621680092342 e6989586621680092343 :: TyFun [d6989586621680092342] ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]) -> Type) (a6989586621680094012 :: [d6989586621680092342]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym3 a6989586621680094011 a6989586621680094010 a6989586621680094009 d6989586621680092342 e6989586621680092343 :: TyFun [d6989586621680092342] ([e6989586621680092343] ~> [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)]) -> Type) (a6989586621680094012 :: [d6989586621680092342]) = Zip5Sym4 a6989586621680094011 a6989586621680094010 a6989586621680094009 a6989586621680094012 e6989586621680092343 :: TyFun [e6989586621680092343] [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)] -> Type |
data Zip5Sym4 (a6989586621680094009 :: [a6989586621680092339]) (a6989586621680094010 :: [b6989586621680092340]) (a6989586621680094011 :: [c6989586621680092341]) (a6989586621680094012 :: [d6989586621680092342]) :: forall e6989586621680092343. (~>) [e6989586621680092343] [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)] Source #
Instances
SuppressUnusedWarnings (Zip5Sym4 a6989586621680094012 a6989586621680094011 a6989586621680094010 a6989586621680094009 e6989586621680092343 :: TyFun [e6989586621680092343] [(a6989586621680092339, b6989586621680092340, c6989586621680092341, d6989586621680092342, e6989586621680092343)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym4 a6989586621680094012 a6989586621680094011 a6989586621680094010 a6989586621680094009 e :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621680094013 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type Zip5Sym5 (a6989586621680094009 :: [a6989586621680092339]) (a6989586621680094010 :: [b6989586621680092340]) (a6989586621680094011 :: [c6989586621680092341]) (a6989586621680094012 :: [d6989586621680092342]) (a6989586621680094013 :: [e6989586621680092343]) = Zip5 a6989586621680094009 a6989586621680094010 a6989586621680094011 a6989586621680094012 a6989586621680094013 Source #
data Zip6Sym0 :: forall a6989586621680092333 b6989586621680092334 c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338. (~>) [a6989586621680092333] ((~>) [b6989586621680092334] ((~>) [c6989586621680092335] ((~>) [d6989586621680092336] ((~>) [e6989586621680092337] ((~>) [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]))))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a6989586621680092333] ([b6989586621680092334] ~> ([c6989586621680092335] ~> ([d6989586621680092336] ~> ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym0 :: TyFun [a6989586621680092333] ([b6989586621680092334] ~> ([c6989586621680092335] ~> ([d6989586621680092336] ~> ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]))))) -> Type) (a6989586621680093981 :: [a6989586621680092333]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym0 :: TyFun [a6989586621680092333] ([b6989586621680092334] ~> ([c6989586621680092335] ~> ([d6989586621680092336] ~> ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]))))) -> Type) (a6989586621680093981 :: [a6989586621680092333]) = Zip6Sym1 a6989586621680093981 b6989586621680092334 c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338 :: TyFun [b6989586621680092334] ([c6989586621680092335] ~> ([d6989586621680092336] ~> ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])))) -> Type |
data Zip6Sym1 (a6989586621680093981 :: [a6989586621680092333]) :: forall b6989586621680092334 c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338. (~>) [b6989586621680092334] ((~>) [c6989586621680092335] ((~>) [d6989586621680092336] ((~>) [e6989586621680092337] ((~>) [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym1 a6989586621680093981 b6989586621680092334 c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338 :: TyFun [b6989586621680092334] ([c6989586621680092335] ~> ([d6989586621680092336] ~> ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym1 a6989586621680093981 b6989586621680092334 c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338 :: TyFun [b6989586621680092334] ([c6989586621680092335] ~> ([d6989586621680092336] ~> ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])))) -> Type) (a6989586621680093982 :: [b6989586621680092334]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym1 a6989586621680093981 b6989586621680092334 c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338 :: TyFun [b6989586621680092334] ([c6989586621680092335] ~> ([d6989586621680092336] ~> ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])))) -> Type) (a6989586621680093982 :: [b6989586621680092334]) = Zip6Sym2 a6989586621680093981 a6989586621680093982 c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338 :: TyFun [c6989586621680092335] ([d6989586621680092336] ~> ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]))) -> Type |
data Zip6Sym2 (a6989586621680093981 :: [a6989586621680092333]) (a6989586621680093982 :: [b6989586621680092334]) :: forall c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338. (~>) [c6989586621680092335] ((~>) [d6989586621680092336] ((~>) [e6989586621680092337] ((~>) [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym2 a6989586621680093982 a6989586621680093981 c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338 :: TyFun [c6989586621680092335] ([d6989586621680092336] ~> ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym2 a6989586621680093982 a6989586621680093981 c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338 :: TyFun [c6989586621680092335] ([d6989586621680092336] ~> ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]))) -> Type) (a6989586621680093983 :: [c6989586621680092335]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym2 a6989586621680093982 a6989586621680093981 c6989586621680092335 d6989586621680092336 e6989586621680092337 f6989586621680092338 :: TyFun [c6989586621680092335] ([d6989586621680092336] ~> ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]))) -> Type) (a6989586621680093983 :: [c6989586621680092335]) = Zip6Sym3 a6989586621680093982 a6989586621680093981 a6989586621680093983 d6989586621680092336 e6989586621680092337 f6989586621680092338 :: TyFun [d6989586621680092336] ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])) -> Type |
data Zip6Sym3 (a6989586621680093981 :: [a6989586621680092333]) (a6989586621680093982 :: [b6989586621680092334]) (a6989586621680093983 :: [c6989586621680092335]) :: forall d6989586621680092336 e6989586621680092337 f6989586621680092338. (~>) [d6989586621680092336] ((~>) [e6989586621680092337] ((~>) [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])) Source #
Instances
SuppressUnusedWarnings (Zip6Sym3 a6989586621680093983 a6989586621680093982 a6989586621680093981 d6989586621680092336 e6989586621680092337 f6989586621680092338 :: TyFun [d6989586621680092336] ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym3 a6989586621680093983 a6989586621680093982 a6989586621680093981 d6989586621680092336 e6989586621680092337 f6989586621680092338 :: TyFun [d6989586621680092336] ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])) -> Type) (a6989586621680093984 :: [d6989586621680092336]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym3 a6989586621680093983 a6989586621680093982 a6989586621680093981 d6989586621680092336 e6989586621680092337 f6989586621680092338 :: TyFun [d6989586621680092336] ([e6989586621680092337] ~> ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)])) -> Type) (a6989586621680093984 :: [d6989586621680092336]) = Zip6Sym4 a6989586621680093983 a6989586621680093982 a6989586621680093981 a6989586621680093984 e6989586621680092337 f6989586621680092338 :: TyFun [e6989586621680092337] ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]) -> Type |
data Zip6Sym4 (a6989586621680093981 :: [a6989586621680092333]) (a6989586621680093982 :: [b6989586621680092334]) (a6989586621680093983 :: [c6989586621680092335]) (a6989586621680093984 :: [d6989586621680092336]) :: forall e6989586621680092337 f6989586621680092338. (~>) [e6989586621680092337] ((~>) [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]) Source #
Instances
SuppressUnusedWarnings (Zip6Sym4 a6989586621680093984 a6989586621680093983 a6989586621680093982 a6989586621680093981 e6989586621680092337 f6989586621680092338 :: TyFun [e6989586621680092337] ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym4 a6989586621680093984 a6989586621680093983 a6989586621680093982 a6989586621680093981 e6989586621680092337 f6989586621680092338 :: TyFun [e6989586621680092337] ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]) -> Type) (a6989586621680093985 :: [e6989586621680092337]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym4 a6989586621680093984 a6989586621680093983 a6989586621680093982 a6989586621680093981 e6989586621680092337 f6989586621680092338 :: TyFun [e6989586621680092337] ([f6989586621680092338] ~> [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)]) -> Type) (a6989586621680093985 :: [e6989586621680092337]) = Zip6Sym5 a6989586621680093984 a6989586621680093983 a6989586621680093982 a6989586621680093981 a6989586621680093985 f6989586621680092338 :: TyFun [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)] -> Type |
data Zip6Sym5 (a6989586621680093981 :: [a6989586621680092333]) (a6989586621680093982 :: [b6989586621680092334]) (a6989586621680093983 :: [c6989586621680092335]) (a6989586621680093984 :: [d6989586621680092336]) (a6989586621680093985 :: [e6989586621680092337]) :: forall f6989586621680092338. (~>) [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)] Source #
Instances
SuppressUnusedWarnings (Zip6Sym5 a6989586621680093985 a6989586621680093984 a6989586621680093983 a6989586621680093982 a6989586621680093981 f6989586621680092338 :: TyFun [f6989586621680092338] [(a6989586621680092333, b6989586621680092334, c6989586621680092335, d6989586621680092336, e6989586621680092337, f6989586621680092338)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym5 a6989586621680093985 a6989586621680093984 a6989586621680093983 a6989586621680093982 a6989586621680093981 f :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680093986 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym5 a6989586621680093985 a6989586621680093984 a6989586621680093983 a6989586621680093982 a6989586621680093981 f :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680093986 :: [f]) = Zip6 a6989586621680093985 a6989586621680093984 a6989586621680093983 a6989586621680093982 a6989586621680093981 a6989586621680093986 |
type Zip6Sym6 (a6989586621680093981 :: [a6989586621680092333]) (a6989586621680093982 :: [b6989586621680092334]) (a6989586621680093983 :: [c6989586621680092335]) (a6989586621680093984 :: [d6989586621680092336]) (a6989586621680093985 :: [e6989586621680092337]) (a6989586621680093986 :: [f6989586621680092338]) = Zip6 a6989586621680093981 a6989586621680093982 a6989586621680093983 a6989586621680093984 a6989586621680093985 a6989586621680093986 Source #
data Zip7Sym0 :: forall a6989586621680092326 b6989586621680092327 c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332. (~>) [a6989586621680092326] ((~>) [b6989586621680092327] ((~>) [c6989586621680092328] ((~>) [d6989586621680092329] ((~>) [e6989586621680092330] ((~>) [f6989586621680092331] ((~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])))))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a6989586621680092326] ([b6989586621680092327] ~> ([c6989586621680092328] ~> ([d6989586621680092329] ~> ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym0 :: TyFun [a6989586621680092326] ([b6989586621680092327] ~> ([c6989586621680092328] ~> ([d6989586621680092329] ~> ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])))))) -> Type) (a6989586621680093948 :: [a6989586621680092326]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym0 :: TyFun [a6989586621680092326] ([b6989586621680092327] ~> ([c6989586621680092328] ~> ([d6989586621680092329] ~> ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])))))) -> Type) (a6989586621680093948 :: [a6989586621680092326]) = Zip7Sym1 a6989586621680093948 b6989586621680092327 c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [b6989586621680092327] ([c6989586621680092328] ~> ([d6989586621680092329] ~> ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))))) -> Type |
data Zip7Sym1 (a6989586621680093948 :: [a6989586621680092326]) :: forall b6989586621680092327 c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332. (~>) [b6989586621680092327] ((~>) [c6989586621680092328] ((~>) [d6989586621680092329] ((~>) [e6989586621680092330] ((~>) [f6989586621680092331] ((~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym1 a6989586621680093948 b6989586621680092327 c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [b6989586621680092327] ([c6989586621680092328] ~> ([d6989586621680092329] ~> ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym1 a6989586621680093948 b6989586621680092327 c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [b6989586621680092327] ([c6989586621680092328] ~> ([d6989586621680092329] ~> ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))))) -> Type) (a6989586621680093949 :: [b6989586621680092327]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym1 a6989586621680093948 b6989586621680092327 c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [b6989586621680092327] ([c6989586621680092328] ~> ([d6989586621680092329] ~> ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))))) -> Type) (a6989586621680093949 :: [b6989586621680092327]) = Zip7Sym2 a6989586621680093948 a6989586621680093949 c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [c6989586621680092328] ([d6989586621680092329] ~> ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])))) -> Type |
data Zip7Sym2 (a6989586621680093948 :: [a6989586621680092326]) (a6989586621680093949 :: [b6989586621680092327]) :: forall c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332. (~>) [c6989586621680092328] ((~>) [d6989586621680092329] ((~>) [e6989586621680092330] ((~>) [f6989586621680092331] ((~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym2 a6989586621680093949 a6989586621680093948 c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [c6989586621680092328] ([d6989586621680092329] ~> ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym2 a6989586621680093949 a6989586621680093948 c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [c6989586621680092328] ([d6989586621680092329] ~> ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])))) -> Type) (a6989586621680093950 :: [c6989586621680092328]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym2 a6989586621680093949 a6989586621680093948 c6989586621680092328 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [c6989586621680092328] ([d6989586621680092329] ~> ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])))) -> Type) (a6989586621680093950 :: [c6989586621680092328]) = Zip7Sym3 a6989586621680093949 a6989586621680093948 a6989586621680093950 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [d6989586621680092329] ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))) -> Type |
data Zip7Sym3 (a6989586621680093948 :: [a6989586621680092326]) (a6989586621680093949 :: [b6989586621680092327]) (a6989586621680093950 :: [c6989586621680092328]) :: forall d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332. (~>) [d6989586621680092329] ((~>) [e6989586621680092330] ((~>) [f6989586621680092331] ((~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym3 a6989586621680093950 a6989586621680093949 a6989586621680093948 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [d6989586621680092329] ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym3 a6989586621680093950 a6989586621680093949 a6989586621680093948 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [d6989586621680092329] ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))) -> Type) (a6989586621680093951 :: [d6989586621680092329]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym3 a6989586621680093950 a6989586621680093949 a6989586621680093948 d6989586621680092329 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [d6989586621680092329] ([e6989586621680092330] ~> ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]))) -> Type) (a6989586621680093951 :: [d6989586621680092329]) = Zip7Sym4 a6989586621680093950 a6989586621680093949 a6989586621680093948 a6989586621680093951 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [e6989586621680092330] ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])) -> Type |
data Zip7Sym4 (a6989586621680093948 :: [a6989586621680092326]) (a6989586621680093949 :: [b6989586621680092327]) (a6989586621680093950 :: [c6989586621680092328]) (a6989586621680093951 :: [d6989586621680092329]) :: forall e6989586621680092330 f6989586621680092331 g6989586621680092332. (~>) [e6989586621680092330] ((~>) [f6989586621680092331] ((~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])) Source #
Instances
SuppressUnusedWarnings (Zip7Sym4 a6989586621680093951 a6989586621680093950 a6989586621680093949 a6989586621680093948 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [e6989586621680092330] ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym4 a6989586621680093951 a6989586621680093950 a6989586621680093949 a6989586621680093948 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [e6989586621680092330] ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])) -> Type) (a6989586621680093952 :: [e6989586621680092330]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym4 a6989586621680093951 a6989586621680093950 a6989586621680093949 a6989586621680093948 e6989586621680092330 f6989586621680092331 g6989586621680092332 :: TyFun [e6989586621680092330] ([f6989586621680092331] ~> ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)])) -> Type) (a6989586621680093952 :: [e6989586621680092330]) = Zip7Sym5 a6989586621680093951 a6989586621680093950 a6989586621680093949 a6989586621680093948 a6989586621680093952 f6989586621680092331 g6989586621680092332 :: TyFun [f6989586621680092331] ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]) -> Type |
data Zip7Sym5 (a6989586621680093948 :: [a6989586621680092326]) (a6989586621680093949 :: [b6989586621680092327]) (a6989586621680093950 :: [c6989586621680092328]) (a6989586621680093951 :: [d6989586621680092329]) (a6989586621680093952 :: [e6989586621680092330]) :: forall f6989586621680092331 g6989586621680092332. (~>) [f6989586621680092331] ((~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]) Source #
Instances
SuppressUnusedWarnings (Zip7Sym5 a6989586621680093952 a6989586621680093951 a6989586621680093950 a6989586621680093949 a6989586621680093948 f6989586621680092331 g6989586621680092332 :: TyFun [f6989586621680092331] ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym5 a6989586621680093952 a6989586621680093951 a6989586621680093950 a6989586621680093949 a6989586621680093948 f6989586621680092331 g6989586621680092332 :: TyFun [f6989586621680092331] ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]) -> Type) (a6989586621680093953 :: [f6989586621680092331]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym5 a6989586621680093952 a6989586621680093951 a6989586621680093950 a6989586621680093949 a6989586621680093948 f6989586621680092331 g6989586621680092332 :: TyFun [f6989586621680092331] ([g6989586621680092332] ~> [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)]) -> Type) (a6989586621680093953 :: [f6989586621680092331]) = Zip7Sym6 a6989586621680093952 a6989586621680093951 a6989586621680093950 a6989586621680093949 a6989586621680093948 a6989586621680093953 g6989586621680092332 :: TyFun [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)] -> Type |
data Zip7Sym6 (a6989586621680093948 :: [a6989586621680092326]) (a6989586621680093949 :: [b6989586621680092327]) (a6989586621680093950 :: [c6989586621680092328]) (a6989586621680093951 :: [d6989586621680092329]) (a6989586621680093952 :: [e6989586621680092330]) (a6989586621680093953 :: [f6989586621680092331]) :: forall g6989586621680092332. (~>) [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)] Source #
Instances
SuppressUnusedWarnings (Zip7Sym6 a6989586621680093953 a6989586621680093952 a6989586621680093951 a6989586621680093950 a6989586621680093949 a6989586621680093948 g6989586621680092332 :: TyFun [g6989586621680092332] [(a6989586621680092326, b6989586621680092327, c6989586621680092328, d6989586621680092329, e6989586621680092330, f6989586621680092331, g6989586621680092332)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym6 a6989586621680093953 a6989586621680093952 a6989586621680093951 a6989586621680093950 a6989586621680093949 a6989586621680093948 g :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680093954 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym6 a6989586621680093953 a6989586621680093952 a6989586621680093951 a6989586621680093950 a6989586621680093949 a6989586621680093948 g :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680093954 :: [g]) = Zip7 a6989586621680093953 a6989586621680093952 a6989586621680093951 a6989586621680093950 a6989586621680093949 a6989586621680093948 a6989586621680093954 |
type Zip7Sym7 (a6989586621680093948 :: [a6989586621680092326]) (a6989586621680093949 :: [b6989586621680092327]) (a6989586621680093950 :: [c6989586621680092328]) (a6989586621680093951 :: [d6989586621680092329]) (a6989586621680093952 :: [e6989586621680092330]) (a6989586621680093953 :: [f6989586621680092331]) (a6989586621680093954 :: [g6989586621680092332]) = Zip7 a6989586621680093948 a6989586621680093949 a6989586621680093950 a6989586621680093951 a6989586621680093952 a6989586621680093953 a6989586621680093954 Source #
data ZipWithSym0 :: forall a6989586621679970210 b6989586621679970211 c6989586621679970212. (~>) ((~>) a6989586621679970210 ((~>) b6989586621679970211 c6989586621679970212)) ((~>) [a6989586621679970210] ((~>) [b6989586621679970211] [c6989586621679970212])) Source #
Instances
SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing ZipWithSym0 Source # | |
SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a6989586621679970210 ~> (b6989586621679970211 ~> c6989586621679970212)) ([a6989586621679970210] ~> ([b6989586621679970211] ~> [c6989586621679970212])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym0 :: TyFun (a6989586621679970210 ~> (b6989586621679970211 ~> c6989586621679970212)) ([a6989586621679970210] ~> ([b6989586621679970211] ~> [c6989586621679970212])) -> Type) (a6989586621679975057 :: a6989586621679970210 ~> (b6989586621679970211 ~> c6989586621679970212)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym0 :: TyFun (a6989586621679970210 ~> (b6989586621679970211 ~> c6989586621679970212)) ([a6989586621679970210] ~> ([b6989586621679970211] ~> [c6989586621679970212])) -> Type) (a6989586621679975057 :: a6989586621679970210 ~> (b6989586621679970211 ~> c6989586621679970212)) = ZipWithSym1 a6989586621679975057 |
data ZipWithSym1 (a6989586621679975057 :: (~>) a6989586621679970210 ((~>) b6989586621679970211 c6989586621679970212)) :: (~>) [a6989586621679970210] ((~>) [b6989586621679970211] [c6989586621679970212]) Source #
Instances
SingI d => SingI (ZipWithSym1 d :: TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ZipWithSym1 d) Source # | |
SuppressUnusedWarnings (ZipWithSym1 a6989586621679975057 :: TyFun [a6989586621679970210] ([b6989586621679970211] ~> [c6989586621679970212]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym1 a6989586621679975057 :: TyFun [a6989586621679970210] ([b6989586621679970211] ~> [c6989586621679970212]) -> Type) (a6989586621679975058 :: [a6989586621679970210]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym1 a6989586621679975057 :: TyFun [a6989586621679970210] ([b6989586621679970211] ~> [c6989586621679970212]) -> Type) (a6989586621679975058 :: [a6989586621679970210]) = ZipWithSym2 a6989586621679975057 a6989586621679975058 |
data ZipWithSym2 (a6989586621679975057 :: (~>) a6989586621679970210 ((~>) b6989586621679970211 c6989586621679970212)) (a6989586621679975058 :: [a6989586621679970210]) :: (~>) [b6989586621679970211] [c6989586621679970212] Source #
Instances
(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun [b] [c] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ZipWithSym2 d1 d2) Source # | |
SuppressUnusedWarnings (ZipWithSym2 a6989586621679975058 a6989586621679975057 :: TyFun [b6989586621679970211] [c6989586621679970212] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym2 a6989586621679975058 a6989586621679975057 :: TyFun [b] [c] -> Type) (a6989586621679975059 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym2 a6989586621679975058 a6989586621679975057 :: TyFun [b] [c] -> Type) (a6989586621679975059 :: [b]) = ZipWith a6989586621679975058 a6989586621679975057 a6989586621679975059 |
type ZipWithSym3 (a6989586621679975057 :: (~>) a6989586621679970210 ((~>) b6989586621679970211 c6989586621679970212)) (a6989586621679975058 :: [a6989586621679970210]) (a6989586621679975059 :: [b6989586621679970211]) = ZipWith a6989586621679975057 a6989586621679975058 a6989586621679975059 Source #
data ZipWith3Sym0 :: forall a6989586621679970206 b6989586621679970207 c6989586621679970208 d6989586621679970209. (~>) ((~>) a6989586621679970206 ((~>) b6989586621679970207 ((~>) c6989586621679970208 d6989586621679970209))) ((~>) [a6989586621679970206] ((~>) [b6989586621679970207] ((~>) [c6989586621679970208] [d6989586621679970209]))) Source #
Instances
SingI (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing ZipWith3Sym0 Source # | |
SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (a6989586621679970206 ~> (b6989586621679970207 ~> (c6989586621679970208 ~> d6989586621679970209))) ([a6989586621679970206] ~> ([b6989586621679970207] ~> ([c6989586621679970208] ~> [d6989586621679970209]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym0 :: TyFun (a6989586621679970206 ~> (b6989586621679970207 ~> (c6989586621679970208 ~> d6989586621679970209))) ([a6989586621679970206] ~> ([b6989586621679970207] ~> ([c6989586621679970208] ~> [d6989586621679970209]))) -> Type) (a6989586621679975042 :: a6989586621679970206 ~> (b6989586621679970207 ~> (c6989586621679970208 ~> d6989586621679970209))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym0 :: TyFun (a6989586621679970206 ~> (b6989586621679970207 ~> (c6989586621679970208 ~> d6989586621679970209))) ([a6989586621679970206] ~> ([b6989586621679970207] ~> ([c6989586621679970208] ~> [d6989586621679970209]))) -> Type) (a6989586621679975042 :: a6989586621679970206 ~> (b6989586621679970207 ~> (c6989586621679970208 ~> d6989586621679970209))) = ZipWith3Sym1 a6989586621679975042 |
data ZipWith3Sym1 (a6989586621679975042 :: (~>) a6989586621679970206 ((~>) b6989586621679970207 ((~>) c6989586621679970208 d6989586621679970209))) :: (~>) [a6989586621679970206] ((~>) [b6989586621679970207] ((~>) [c6989586621679970208] [d6989586621679970209])) Source #
Instances
SingI d2 => SingI (ZipWith3Sym1 d2 :: TyFun [a] ([b] ~> ([c] ~> [d1])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ZipWith3Sym1 d2) Source # | |
SuppressUnusedWarnings (ZipWith3Sym1 a6989586621679975042 :: TyFun [a6989586621679970206] ([b6989586621679970207] ~> ([c6989586621679970208] ~> [d6989586621679970209])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym1 a6989586621679975042 :: TyFun [a6989586621679970206] ([b6989586621679970207] ~> ([c6989586621679970208] ~> [d6989586621679970209])) -> Type) (a6989586621679975043 :: [a6989586621679970206]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym1 a6989586621679975042 :: TyFun [a6989586621679970206] ([b6989586621679970207] ~> ([c6989586621679970208] ~> [d6989586621679970209])) -> Type) (a6989586621679975043 :: [a6989586621679970206]) = ZipWith3Sym2 a6989586621679975042 a6989586621679975043 |
data ZipWith3Sym2 (a6989586621679975042 :: (~>) a6989586621679970206 ((~>) b6989586621679970207 ((~>) c6989586621679970208 d6989586621679970209))) (a6989586621679975043 :: [a6989586621679970206]) :: (~>) [b6989586621679970207] ((~>) [c6989586621679970208] [d6989586621679970209]) Source #
Instances
(SingI d2, SingI d3) => SingI (ZipWith3Sym2 d2 d3 :: TyFun [b] ([c] ~> [d1]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ZipWith3Sym2 d2 d3) Source # | |
SuppressUnusedWarnings (ZipWith3Sym2 a6989586621679975043 a6989586621679975042 :: TyFun [b6989586621679970207] ([c6989586621679970208] ~> [d6989586621679970209]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym2 a6989586621679975043 a6989586621679975042 :: TyFun [b6989586621679970207] ([c6989586621679970208] ~> [d6989586621679970209]) -> Type) (a6989586621679975044 :: [b6989586621679970207]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym2 a6989586621679975043 a6989586621679975042 :: TyFun [b6989586621679970207] ([c6989586621679970208] ~> [d6989586621679970209]) -> Type) (a6989586621679975044 :: [b6989586621679970207]) = ZipWith3Sym3 a6989586621679975043 a6989586621679975042 a6989586621679975044 |
data ZipWith3Sym3 (a6989586621679975042 :: (~>) a6989586621679970206 ((~>) b6989586621679970207 ((~>) c6989586621679970208 d6989586621679970209))) (a6989586621679975043 :: [a6989586621679970206]) (a6989586621679975044 :: [b6989586621679970207]) :: (~>) [c6989586621679970208] [d6989586621679970209] Source #
Instances
(SingI d2, SingI d3, SingI d4) => SingI (ZipWith3Sym3 d2 d3 d4 :: TyFun [c] [d1] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ZipWith3Sym3 d2 d3 d4) Source # | |
SuppressUnusedWarnings (ZipWith3Sym3 a6989586621679975044 a6989586621679975043 a6989586621679975042 :: TyFun [c6989586621679970208] [d6989586621679970209] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym3 a6989586621679975044 a6989586621679975043 a6989586621679975042 :: TyFun [c] [d] -> Type) (a6989586621679975045 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym3 a6989586621679975044 a6989586621679975043 a6989586621679975042 :: TyFun [c] [d] -> Type) (a6989586621679975045 :: [c]) = ZipWith3 a6989586621679975044 a6989586621679975043 a6989586621679975042 a6989586621679975045 |
type ZipWith3Sym4 (a6989586621679975042 :: (~>) a6989586621679970206 ((~>) b6989586621679970207 ((~>) c6989586621679970208 d6989586621679970209))) (a6989586621679975043 :: [a6989586621679970206]) (a6989586621679975044 :: [b6989586621679970207]) (a6989586621679975045 :: [c6989586621679970208]) = ZipWith3 a6989586621679975042 a6989586621679975043 a6989586621679975044 a6989586621679975045 Source #
data ZipWith4Sym0 :: forall a6989586621680092321 b6989586621680092322 c6989586621680092323 d6989586621680092324 e6989586621680092325. (~>) ((~>) a6989586621680092321 ((~>) b6989586621680092322 ((~>) c6989586621680092323 ((~>) d6989586621680092324 e6989586621680092325)))) ((~>) [a6989586621680092321] ((~>) [b6989586621680092322] ((~>) [c6989586621680092323] ((~>) [d6989586621680092324] [e6989586621680092325])))) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (a6989586621680092321 ~> (b6989586621680092322 ~> (c6989586621680092323 ~> (d6989586621680092324 ~> e6989586621680092325)))) ([a6989586621680092321] ~> ([b6989586621680092322] ~> ([c6989586621680092323] ~> ([d6989586621680092324] ~> [e6989586621680092325])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym0 :: TyFun (a6989586621680092321 ~> (b6989586621680092322 ~> (c6989586621680092323 ~> (d6989586621680092324 ~> e6989586621680092325)))) ([a6989586621680092321] ~> ([b6989586621680092322] ~> ([c6989586621680092323] ~> ([d6989586621680092324] ~> [e6989586621680092325])))) -> Type) (a6989586621680093915 :: a6989586621680092321 ~> (b6989586621680092322 ~> (c6989586621680092323 ~> (d6989586621680092324 ~> e6989586621680092325)))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym0 :: TyFun (a6989586621680092321 ~> (b6989586621680092322 ~> (c6989586621680092323 ~> (d6989586621680092324 ~> e6989586621680092325)))) ([a6989586621680092321] ~> ([b6989586621680092322] ~> ([c6989586621680092323] ~> ([d6989586621680092324] ~> [e6989586621680092325])))) -> Type) (a6989586621680093915 :: a6989586621680092321 ~> (b6989586621680092322 ~> (c6989586621680092323 ~> (d6989586621680092324 ~> e6989586621680092325)))) = ZipWith4Sym1 a6989586621680093915 |
data ZipWith4Sym1 (a6989586621680093915 :: (~>) a6989586621680092321 ((~>) b6989586621680092322 ((~>) c6989586621680092323 ((~>) d6989586621680092324 e6989586621680092325)))) :: (~>) [a6989586621680092321] ((~>) [b6989586621680092322] ((~>) [c6989586621680092323] ((~>) [d6989586621680092324] [e6989586621680092325]))) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym1 a6989586621680093915 :: TyFun [a6989586621680092321] ([b6989586621680092322] ~> ([c6989586621680092323] ~> ([d6989586621680092324] ~> [e6989586621680092325]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym1 a6989586621680093915 :: TyFun [a6989586621680092321] ([b6989586621680092322] ~> ([c6989586621680092323] ~> ([d6989586621680092324] ~> [e6989586621680092325]))) -> Type) (a6989586621680093916 :: [a6989586621680092321]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym1 a6989586621680093915 :: TyFun [a6989586621680092321] ([b6989586621680092322] ~> ([c6989586621680092323] ~> ([d6989586621680092324] ~> [e6989586621680092325]))) -> Type) (a6989586621680093916 :: [a6989586621680092321]) = ZipWith4Sym2 a6989586621680093915 a6989586621680093916 |
data ZipWith4Sym2 (a6989586621680093915 :: (~>) a6989586621680092321 ((~>) b6989586621680092322 ((~>) c6989586621680092323 ((~>) d6989586621680092324 e6989586621680092325)))) (a6989586621680093916 :: [a6989586621680092321]) :: (~>) [b6989586621680092322] ((~>) [c6989586621680092323] ((~>) [d6989586621680092324] [e6989586621680092325])) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym2 a6989586621680093916 a6989586621680093915 :: TyFun [b6989586621680092322] ([c6989586621680092323] ~> ([d6989586621680092324] ~> [e6989586621680092325])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym2 a6989586621680093916 a6989586621680093915 :: TyFun [b6989586621680092322] ([c6989586621680092323] ~> ([d6989586621680092324] ~> [e6989586621680092325])) -> Type) (a6989586621680093917 :: [b6989586621680092322]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym2 a6989586621680093916 a6989586621680093915 :: TyFun [b6989586621680092322] ([c6989586621680092323] ~> ([d6989586621680092324] ~> [e6989586621680092325])) -> Type) (a6989586621680093917 :: [b6989586621680092322]) = ZipWith4Sym3 a6989586621680093916 a6989586621680093915 a6989586621680093917 |
data ZipWith4Sym3 (a6989586621680093915 :: (~>) a6989586621680092321 ((~>) b6989586621680092322 ((~>) c6989586621680092323 ((~>) d6989586621680092324 e6989586621680092325)))) (a6989586621680093916 :: [a6989586621680092321]) (a6989586621680093917 :: [b6989586621680092322]) :: (~>) [c6989586621680092323] ((~>) [d6989586621680092324] [e6989586621680092325]) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym3 a6989586621680093917 a6989586621680093916 a6989586621680093915 :: TyFun [c6989586621680092323] ([d6989586621680092324] ~> [e6989586621680092325]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym3 a6989586621680093917 a6989586621680093916 a6989586621680093915 :: TyFun [c6989586621680092323] ([d6989586621680092324] ~> [e6989586621680092325]) -> Type) (a6989586621680093918 :: [c6989586621680092323]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym3 a6989586621680093917 a6989586621680093916 a6989586621680093915 :: TyFun [c6989586621680092323] ([d6989586621680092324] ~> [e6989586621680092325]) -> Type) (a6989586621680093918 :: [c6989586621680092323]) = ZipWith4Sym4 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093918 |
data ZipWith4Sym4 (a6989586621680093915 :: (~>) a6989586621680092321 ((~>) b6989586621680092322 ((~>) c6989586621680092323 ((~>) d6989586621680092324 e6989586621680092325)))) (a6989586621680093916 :: [a6989586621680092321]) (a6989586621680093917 :: [b6989586621680092322]) (a6989586621680093918 :: [c6989586621680092323]) :: (~>) [d6989586621680092324] [e6989586621680092325] Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym4 a6989586621680093918 a6989586621680093917 a6989586621680093916 a6989586621680093915 :: TyFun [d6989586621680092324] [e6989586621680092325] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym4 a6989586621680093918 a6989586621680093917 a6989586621680093916 a6989586621680093915 :: TyFun [d] [e] -> Type) (a6989586621680093919 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym4 a6989586621680093918 a6989586621680093917 a6989586621680093916 a6989586621680093915 :: TyFun [d] [e] -> Type) (a6989586621680093919 :: [d]) = ZipWith4 a6989586621680093918 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093919 |
type ZipWith4Sym5 (a6989586621680093915 :: (~>) a6989586621680092321 ((~>) b6989586621680092322 ((~>) c6989586621680092323 ((~>) d6989586621680092324 e6989586621680092325)))) (a6989586621680093916 :: [a6989586621680092321]) (a6989586621680093917 :: [b6989586621680092322]) (a6989586621680093918 :: [c6989586621680092323]) (a6989586621680093919 :: [d6989586621680092324]) = ZipWith4 a6989586621680093915 a6989586621680093916 a6989586621680093917 a6989586621680093918 a6989586621680093919 Source #
data ZipWith5Sym0 :: forall a6989586621680092315 b6989586621680092316 c6989586621680092317 d6989586621680092318 e6989586621680092319 f6989586621680092320. (~>) ((~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) ((~>) [a6989586621680092315] ((~>) [b6989586621680092316] ((~>) [c6989586621680092317] ((~>) [d6989586621680092318] ((~>) [e6989586621680092319] [f6989586621680092320]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (a6989586621680092315 ~> (b6989586621680092316 ~> (c6989586621680092317 ~> (d6989586621680092318 ~> (e6989586621680092319 ~> f6989586621680092320))))) ([a6989586621680092315] ~> ([b6989586621680092316] ~> ([c6989586621680092317] ~> ([d6989586621680092318] ~> ([e6989586621680092319] ~> [f6989586621680092320]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym0 :: TyFun (a6989586621680092315 ~> (b6989586621680092316 ~> (c6989586621680092317 ~> (d6989586621680092318 ~> (e6989586621680092319 ~> f6989586621680092320))))) ([a6989586621680092315] ~> ([b6989586621680092316] ~> ([c6989586621680092317] ~> ([d6989586621680092318] ~> ([e6989586621680092319] ~> [f6989586621680092320]))))) -> Type) (a6989586621680093892 :: a6989586621680092315 ~> (b6989586621680092316 ~> (c6989586621680092317 ~> (d6989586621680092318 ~> (e6989586621680092319 ~> f6989586621680092320))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym0 :: TyFun (a6989586621680092315 ~> (b6989586621680092316 ~> (c6989586621680092317 ~> (d6989586621680092318 ~> (e6989586621680092319 ~> f6989586621680092320))))) ([a6989586621680092315] ~> ([b6989586621680092316] ~> ([c6989586621680092317] ~> ([d6989586621680092318] ~> ([e6989586621680092319] ~> [f6989586621680092320]))))) -> Type) (a6989586621680093892 :: a6989586621680092315 ~> (b6989586621680092316 ~> (c6989586621680092317 ~> (d6989586621680092318 ~> (e6989586621680092319 ~> f6989586621680092320))))) = ZipWith5Sym1 a6989586621680093892 |
data ZipWith5Sym1 (a6989586621680093892 :: (~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) :: (~>) [a6989586621680092315] ((~>) [b6989586621680092316] ((~>) [c6989586621680092317] ((~>) [d6989586621680092318] ((~>) [e6989586621680092319] [f6989586621680092320])))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym1 a6989586621680093892 :: TyFun [a6989586621680092315] ([b6989586621680092316] ~> ([c6989586621680092317] ~> ([d6989586621680092318] ~> ([e6989586621680092319] ~> [f6989586621680092320])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym1 a6989586621680093892 :: TyFun [a6989586621680092315] ([b6989586621680092316] ~> ([c6989586621680092317] ~> ([d6989586621680092318] ~> ([e6989586621680092319] ~> [f6989586621680092320])))) -> Type) (a6989586621680093893 :: [a6989586621680092315]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym1 a6989586621680093892 :: TyFun [a6989586621680092315] ([b6989586621680092316] ~> ([c6989586621680092317] ~> ([d6989586621680092318] ~> ([e6989586621680092319] ~> [f6989586621680092320])))) -> Type) (a6989586621680093893 :: [a6989586621680092315]) = ZipWith5Sym2 a6989586621680093892 a6989586621680093893 |
data ZipWith5Sym2 (a6989586621680093892 :: (~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) (a6989586621680093893 :: [a6989586621680092315]) :: (~>) [b6989586621680092316] ((~>) [c6989586621680092317] ((~>) [d6989586621680092318] ((~>) [e6989586621680092319] [f6989586621680092320]))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym2 a6989586621680093893 a6989586621680093892 :: TyFun [b6989586621680092316] ([c6989586621680092317] ~> ([d6989586621680092318] ~> ([e6989586621680092319] ~> [f6989586621680092320]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym2 a6989586621680093893 a6989586621680093892 :: TyFun [b6989586621680092316] ([c6989586621680092317] ~> ([d6989586621680092318] ~> ([e6989586621680092319] ~> [f6989586621680092320]))) -> Type) (a6989586621680093894 :: [b6989586621680092316]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym2 a6989586621680093893 a6989586621680093892 :: TyFun [b6989586621680092316] ([c6989586621680092317] ~> ([d6989586621680092318] ~> ([e6989586621680092319] ~> [f6989586621680092320]))) -> Type) (a6989586621680093894 :: [b6989586621680092316]) = ZipWith5Sym3 a6989586621680093893 a6989586621680093892 a6989586621680093894 |
data ZipWith5Sym3 (a6989586621680093892 :: (~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) (a6989586621680093893 :: [a6989586621680092315]) (a6989586621680093894 :: [b6989586621680092316]) :: (~>) [c6989586621680092317] ((~>) [d6989586621680092318] ((~>) [e6989586621680092319] [f6989586621680092320])) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym3 a6989586621680093894 a6989586621680093893 a6989586621680093892 :: TyFun [c6989586621680092317] ([d6989586621680092318] ~> ([e6989586621680092319] ~> [f6989586621680092320])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym3 a6989586621680093894 a6989586621680093893 a6989586621680093892 :: TyFun [c6989586621680092317] ([d6989586621680092318] ~> ([e6989586621680092319] ~> [f6989586621680092320])) -> Type) (a6989586621680093895 :: [c6989586621680092317]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym3 a6989586621680093894 a6989586621680093893 a6989586621680093892 :: TyFun [c6989586621680092317] ([d6989586621680092318] ~> ([e6989586621680092319] ~> [f6989586621680092320])) -> Type) (a6989586621680093895 :: [c6989586621680092317]) = ZipWith5Sym4 a6989586621680093894 a6989586621680093893 a6989586621680093892 a6989586621680093895 |
data ZipWith5Sym4 (a6989586621680093892 :: (~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) (a6989586621680093893 :: [a6989586621680092315]) (a6989586621680093894 :: [b6989586621680092316]) (a6989586621680093895 :: [c6989586621680092317]) :: (~>) [d6989586621680092318] ((~>) [e6989586621680092319] [f6989586621680092320]) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym4 a6989586621680093895 a6989586621680093894 a6989586621680093893 a6989586621680093892 :: TyFun [d6989586621680092318] ([e6989586621680092319] ~> [f6989586621680092320]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym4 a6989586621680093895 a6989586621680093894 a6989586621680093893 a6989586621680093892 :: TyFun [d6989586621680092318] ([e6989586621680092319] ~> [f6989586621680092320]) -> Type) (a6989586621680093896 :: [d6989586621680092318]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym4 a6989586621680093895 a6989586621680093894 a6989586621680093893 a6989586621680093892 :: TyFun [d6989586621680092318] ([e6989586621680092319] ~> [f6989586621680092320]) -> Type) (a6989586621680093896 :: [d6989586621680092318]) = ZipWith5Sym5 a6989586621680093895 a6989586621680093894 a6989586621680093893 a6989586621680093892 a6989586621680093896 |
data ZipWith5Sym5 (a6989586621680093892 :: (~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) (a6989586621680093893 :: [a6989586621680092315]) (a6989586621680093894 :: [b6989586621680092316]) (a6989586621680093895 :: [c6989586621680092317]) (a6989586621680093896 :: [d6989586621680092318]) :: (~>) [e6989586621680092319] [f6989586621680092320] Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym5 a6989586621680093896 a6989586621680093895 a6989586621680093894 a6989586621680093893 a6989586621680093892 :: TyFun [e6989586621680092319] [f6989586621680092320] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym5 a6989586621680093896 a6989586621680093895 a6989586621680093894 a6989586621680093893 a6989586621680093892 :: TyFun [e] [f] -> Type) (a6989586621680093897 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym5 a6989586621680093896 a6989586621680093895 a6989586621680093894 a6989586621680093893 a6989586621680093892 :: TyFun [e] [f] -> Type) (a6989586621680093897 :: [e]) = ZipWith5 a6989586621680093896 a6989586621680093895 a6989586621680093894 a6989586621680093893 a6989586621680093892 a6989586621680093897 |
type ZipWith5Sym6 (a6989586621680093892 :: (~>) a6989586621680092315 ((~>) b6989586621680092316 ((~>) c6989586621680092317 ((~>) d6989586621680092318 ((~>) e6989586621680092319 f6989586621680092320))))) (a6989586621680093893 :: [a6989586621680092315]) (a6989586621680093894 :: [b6989586621680092316]) (a6989586621680093895 :: [c6989586621680092317]) (a6989586621680093896 :: [d6989586621680092318]) (a6989586621680093897 :: [e6989586621680092319]) = ZipWith5 a6989586621680093892 a6989586621680093893 a6989586621680093894 a6989586621680093895 a6989586621680093896 a6989586621680093897 Source #
data ZipWith6Sym0 :: forall a6989586621680092308 b6989586621680092309 c6989586621680092310 d6989586621680092311 e6989586621680092312 f6989586621680092313 g6989586621680092314. (~>) ((~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) ((~>) [a6989586621680092308] ((~>) [b6989586621680092309] ((~>) [c6989586621680092310] ((~>) [d6989586621680092311] ((~>) [e6989586621680092312] ((~>) [f6989586621680092313] [g6989586621680092314])))))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (a6989586621680092308 ~> (b6989586621680092309 ~> (c6989586621680092310 ~> (d6989586621680092311 ~> (e6989586621680092312 ~> (f6989586621680092313 ~> g6989586621680092314)))))) ([a6989586621680092308] ~> ([b6989586621680092309] ~> ([c6989586621680092310] ~> ([d6989586621680092311] ~> ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym0 :: TyFun (a6989586621680092308 ~> (b6989586621680092309 ~> (c6989586621680092310 ~> (d6989586621680092311 ~> (e6989586621680092312 ~> (f6989586621680092313 ~> g6989586621680092314)))))) ([a6989586621680092308] ~> ([b6989586621680092309] ~> ([c6989586621680092310] ~> ([d6989586621680092311] ~> ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314])))))) -> Type) (a6989586621680093865 :: a6989586621680092308 ~> (b6989586621680092309 ~> (c6989586621680092310 ~> (d6989586621680092311 ~> (e6989586621680092312 ~> (f6989586621680092313 ~> g6989586621680092314)))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym0 :: TyFun (a6989586621680092308 ~> (b6989586621680092309 ~> (c6989586621680092310 ~> (d6989586621680092311 ~> (e6989586621680092312 ~> (f6989586621680092313 ~> g6989586621680092314)))))) ([a6989586621680092308] ~> ([b6989586621680092309] ~> ([c6989586621680092310] ~> ([d6989586621680092311] ~> ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314])))))) -> Type) (a6989586621680093865 :: a6989586621680092308 ~> (b6989586621680092309 ~> (c6989586621680092310 ~> (d6989586621680092311 ~> (e6989586621680092312 ~> (f6989586621680092313 ~> g6989586621680092314)))))) = ZipWith6Sym1 a6989586621680093865 |
data ZipWith6Sym1 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) :: (~>) [a6989586621680092308] ((~>) [b6989586621680092309] ((~>) [c6989586621680092310] ((~>) [d6989586621680092311] ((~>) [e6989586621680092312] ((~>) [f6989586621680092313] [g6989586621680092314]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym1 a6989586621680093865 :: TyFun [a6989586621680092308] ([b6989586621680092309] ~> ([c6989586621680092310] ~> ([d6989586621680092311] ~> ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym1 a6989586621680093865 :: TyFun [a6989586621680092308] ([b6989586621680092309] ~> ([c6989586621680092310] ~> ([d6989586621680092311] ~> ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314]))))) -> Type) (a6989586621680093866 :: [a6989586621680092308]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym1 a6989586621680093865 :: TyFun [a6989586621680092308] ([b6989586621680092309] ~> ([c6989586621680092310] ~> ([d6989586621680092311] ~> ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314]))))) -> Type) (a6989586621680093866 :: [a6989586621680092308]) = ZipWith6Sym2 a6989586621680093865 a6989586621680093866 |
data ZipWith6Sym2 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) (a6989586621680093866 :: [a6989586621680092308]) :: (~>) [b6989586621680092309] ((~>) [c6989586621680092310] ((~>) [d6989586621680092311] ((~>) [e6989586621680092312] ((~>) [f6989586621680092313] [g6989586621680092314])))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym2 a6989586621680093866 a6989586621680093865 :: TyFun [b6989586621680092309] ([c6989586621680092310] ~> ([d6989586621680092311] ~> ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym2 a6989586621680093866 a6989586621680093865 :: TyFun [b6989586621680092309] ([c6989586621680092310] ~> ([d6989586621680092311] ~> ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314])))) -> Type) (a6989586621680093867 :: [b6989586621680092309]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym2 a6989586621680093866 a6989586621680093865 :: TyFun [b6989586621680092309] ([c6989586621680092310] ~> ([d6989586621680092311] ~> ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314])))) -> Type) (a6989586621680093867 :: [b6989586621680092309]) = ZipWith6Sym3 a6989586621680093866 a6989586621680093865 a6989586621680093867 |
data ZipWith6Sym3 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) (a6989586621680093866 :: [a6989586621680092308]) (a6989586621680093867 :: [b6989586621680092309]) :: (~>) [c6989586621680092310] ((~>) [d6989586621680092311] ((~>) [e6989586621680092312] ((~>) [f6989586621680092313] [g6989586621680092314]))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym3 a6989586621680093867 a6989586621680093866 a6989586621680093865 :: TyFun [c6989586621680092310] ([d6989586621680092311] ~> ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym3 a6989586621680093867 a6989586621680093866 a6989586621680093865 :: TyFun [c6989586621680092310] ([d6989586621680092311] ~> ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314]))) -> Type) (a6989586621680093868 :: [c6989586621680092310]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym3 a6989586621680093867 a6989586621680093866 a6989586621680093865 :: TyFun [c6989586621680092310] ([d6989586621680092311] ~> ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314]))) -> Type) (a6989586621680093868 :: [c6989586621680092310]) = ZipWith6Sym4 a6989586621680093867 a6989586621680093866 a6989586621680093865 a6989586621680093868 |
data ZipWith6Sym4 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) (a6989586621680093866 :: [a6989586621680092308]) (a6989586621680093867 :: [b6989586621680092309]) (a6989586621680093868 :: [c6989586621680092310]) :: (~>) [d6989586621680092311] ((~>) [e6989586621680092312] ((~>) [f6989586621680092313] [g6989586621680092314])) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym4 a6989586621680093868 a6989586621680093867 a6989586621680093866 a6989586621680093865 :: TyFun [d6989586621680092311] ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym4 a6989586621680093868 a6989586621680093867 a6989586621680093866 a6989586621680093865 :: TyFun [d6989586621680092311] ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314])) -> Type) (a6989586621680093869 :: [d6989586621680092311]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym4 a6989586621680093868 a6989586621680093867 a6989586621680093866 a6989586621680093865 :: TyFun [d6989586621680092311] ([e6989586621680092312] ~> ([f6989586621680092313] ~> [g6989586621680092314])) -> Type) (a6989586621680093869 :: [d6989586621680092311]) = ZipWith6Sym5 a6989586621680093868 a6989586621680093867 a6989586621680093866 a6989586621680093865 a6989586621680093869 |
data ZipWith6Sym5 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) (a6989586621680093866 :: [a6989586621680092308]) (a6989586621680093867 :: [b6989586621680092309]) (a6989586621680093868 :: [c6989586621680092310]) (a6989586621680093869 :: [d6989586621680092311]) :: (~>) [e6989586621680092312] ((~>) [f6989586621680092313] [g6989586621680092314]) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym5 a6989586621680093869 a6989586621680093868 a6989586621680093867 a6989586621680093866 a6989586621680093865 :: TyFun [e6989586621680092312] ([f6989586621680092313] ~> [g6989586621680092314]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym5 a6989586621680093869 a6989586621680093868 a6989586621680093867 a6989586621680093866 a6989586621680093865 :: TyFun [e6989586621680092312] ([f6989586621680092313] ~> [g6989586621680092314]) -> Type) (a6989586621680093870 :: [e6989586621680092312]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym5 a6989586621680093869 a6989586621680093868 a6989586621680093867 a6989586621680093866 a6989586621680093865 :: TyFun [e6989586621680092312] ([f6989586621680092313] ~> [g6989586621680092314]) -> Type) (a6989586621680093870 :: [e6989586621680092312]) = ZipWith6Sym6 a6989586621680093869 a6989586621680093868 a6989586621680093867 a6989586621680093866 a6989586621680093865 a6989586621680093870 |
data ZipWith6Sym6 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) (a6989586621680093866 :: [a6989586621680092308]) (a6989586621680093867 :: [b6989586621680092309]) (a6989586621680093868 :: [c6989586621680092310]) (a6989586621680093869 :: [d6989586621680092311]) (a6989586621680093870 :: [e6989586621680092312]) :: (~>) [f6989586621680092313] [g6989586621680092314] Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym6 a6989586621680093870 a6989586621680093869 a6989586621680093868 a6989586621680093867 a6989586621680093866 a6989586621680093865 :: TyFun [f6989586621680092313] [g6989586621680092314] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym6 a6989586621680093870 a6989586621680093869 a6989586621680093868 a6989586621680093867 a6989586621680093866 a6989586621680093865 :: TyFun [f] [g] -> Type) (a6989586621680093871 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym6 a6989586621680093870 a6989586621680093869 a6989586621680093868 a6989586621680093867 a6989586621680093866 a6989586621680093865 :: TyFun [f] [g] -> Type) (a6989586621680093871 :: [f]) = ZipWith6 a6989586621680093870 a6989586621680093869 a6989586621680093868 a6989586621680093867 a6989586621680093866 a6989586621680093865 a6989586621680093871 |
type ZipWith6Sym7 (a6989586621680093865 :: (~>) a6989586621680092308 ((~>) b6989586621680092309 ((~>) c6989586621680092310 ((~>) d6989586621680092311 ((~>) e6989586621680092312 ((~>) f6989586621680092313 g6989586621680092314)))))) (a6989586621680093866 :: [a6989586621680092308]) (a6989586621680093867 :: [b6989586621680092309]) (a6989586621680093868 :: [c6989586621680092310]) (a6989586621680093869 :: [d6989586621680092311]) (a6989586621680093870 :: [e6989586621680092312]) (a6989586621680093871 :: [f6989586621680092313]) = ZipWith6 a6989586621680093865 a6989586621680093866 a6989586621680093867 a6989586621680093868 a6989586621680093869 a6989586621680093870 a6989586621680093871 Source #
data ZipWith7Sym0 :: forall a6989586621680092300 b6989586621680092301 c6989586621680092302 d6989586621680092303 e6989586621680092304 f6989586621680092305 g6989586621680092306 h6989586621680092307. (~>) ((~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) ((~>) [a6989586621680092300] ((~>) [b6989586621680092301] ((~>) [c6989586621680092302] ((~>) [d6989586621680092303] ((~>) [e6989586621680092304] ((~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307]))))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym0 :: TyFun (a6989586621680092300 ~> (b6989586621680092301 ~> (c6989586621680092302 ~> (d6989586621680092303 ~> (e6989586621680092304 ~> (f6989586621680092305 ~> (g6989586621680092306 ~> h6989586621680092307))))))) ([a6989586621680092300] ~> ([b6989586621680092301] ~> ([c6989586621680092302] ~> ([d6989586621680092303] ~> ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307]))))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym0 :: TyFun (a6989586621680092300 ~> (b6989586621680092301 ~> (c6989586621680092302 ~> (d6989586621680092303 ~> (e6989586621680092304 ~> (f6989586621680092305 ~> (g6989586621680092306 ~> h6989586621680092307))))))) ([a6989586621680092300] ~> ([b6989586621680092301] ~> ([c6989586621680092302] ~> ([d6989586621680092303] ~> ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307]))))))) -> Type) (a6989586621680093834 :: a6989586621680092300 ~> (b6989586621680092301 ~> (c6989586621680092302 ~> (d6989586621680092303 ~> (e6989586621680092304 ~> (f6989586621680092305 ~> (g6989586621680092306 ~> h6989586621680092307))))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym0 :: TyFun (a6989586621680092300 ~> (b6989586621680092301 ~> (c6989586621680092302 ~> (d6989586621680092303 ~> (e6989586621680092304 ~> (f6989586621680092305 ~> (g6989586621680092306 ~> h6989586621680092307))))))) ([a6989586621680092300] ~> ([b6989586621680092301] ~> ([c6989586621680092302] ~> ([d6989586621680092303] ~> ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307]))))))) -> Type) (a6989586621680093834 :: a6989586621680092300 ~> (b6989586621680092301 ~> (c6989586621680092302 ~> (d6989586621680092303 ~> (e6989586621680092304 ~> (f6989586621680092305 ~> (g6989586621680092306 ~> h6989586621680092307))))))) = ZipWith7Sym1 a6989586621680093834 |
data ZipWith7Sym1 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) :: (~>) [a6989586621680092300] ((~>) [b6989586621680092301] ((~>) [c6989586621680092302] ((~>) [d6989586621680092303] ((~>) [e6989586621680092304] ((~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307])))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym1 a6989586621680093834 :: TyFun [a6989586621680092300] ([b6989586621680092301] ~> ([c6989586621680092302] ~> ([d6989586621680092303] ~> ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym1 a6989586621680093834 :: TyFun [a6989586621680092300] ([b6989586621680092301] ~> ([c6989586621680092302] ~> ([d6989586621680092303] ~> ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307])))))) -> Type) (a6989586621680093835 :: [a6989586621680092300]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym1 a6989586621680093834 :: TyFun [a6989586621680092300] ([b6989586621680092301] ~> ([c6989586621680092302] ~> ([d6989586621680092303] ~> ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307])))))) -> Type) (a6989586621680093835 :: [a6989586621680092300]) = ZipWith7Sym2 a6989586621680093834 a6989586621680093835 |
data ZipWith7Sym2 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) :: (~>) [b6989586621680092301] ((~>) [c6989586621680092302] ((~>) [d6989586621680092303] ((~>) [e6989586621680092304] ((~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym2 a6989586621680093835 a6989586621680093834 :: TyFun [b6989586621680092301] ([c6989586621680092302] ~> ([d6989586621680092303] ~> ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym2 a6989586621680093835 a6989586621680093834 :: TyFun [b6989586621680092301] ([c6989586621680092302] ~> ([d6989586621680092303] ~> ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307]))))) -> Type) (a6989586621680093836 :: [b6989586621680092301]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym2 a6989586621680093835 a6989586621680093834 :: TyFun [b6989586621680092301] ([c6989586621680092302] ~> ([d6989586621680092303] ~> ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307]))))) -> Type) (a6989586621680093836 :: [b6989586621680092301]) = ZipWith7Sym3 a6989586621680093835 a6989586621680093834 a6989586621680093836 |
data ZipWith7Sym3 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) (a6989586621680093836 :: [b6989586621680092301]) :: (~>) [c6989586621680092302] ((~>) [d6989586621680092303] ((~>) [e6989586621680092304] ((~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307])))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym3 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [c6989586621680092302] ([d6989586621680092303] ~> ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym3 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [c6989586621680092302] ([d6989586621680092303] ~> ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307])))) -> Type) (a6989586621680093837 :: [c6989586621680092302]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym3 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [c6989586621680092302] ([d6989586621680092303] ~> ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307])))) -> Type) (a6989586621680093837 :: [c6989586621680092302]) = ZipWith7Sym4 a6989586621680093836 a6989586621680093835 a6989586621680093834 a6989586621680093837 |
data ZipWith7Sym4 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) (a6989586621680093836 :: [b6989586621680092301]) (a6989586621680093837 :: [c6989586621680092302]) :: (~>) [d6989586621680092303] ((~>) [e6989586621680092304] ((~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307]))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym4 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [d6989586621680092303] ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym4 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [d6989586621680092303] ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307]))) -> Type) (a6989586621680093838 :: [d6989586621680092303]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym4 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [d6989586621680092303] ([e6989586621680092304] ~> ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307]))) -> Type) (a6989586621680093838 :: [d6989586621680092303]) = ZipWith7Sym5 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 a6989586621680093838 |
data ZipWith7Sym5 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) (a6989586621680093836 :: [b6989586621680092301]) (a6989586621680093837 :: [c6989586621680092302]) (a6989586621680093838 :: [d6989586621680092303]) :: (~>) [e6989586621680092304] ((~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307])) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym5 a6989586621680093838 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [e6989586621680092304] ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym5 a6989586621680093838 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [e6989586621680092304] ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307])) -> Type) (a6989586621680093839 :: [e6989586621680092304]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym5 a6989586621680093838 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [e6989586621680092304] ([f6989586621680092305] ~> ([g6989586621680092306] ~> [h6989586621680092307])) -> Type) (a6989586621680093839 :: [e6989586621680092304]) = ZipWith7Sym6 a6989586621680093838 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 a6989586621680093839 |
data ZipWith7Sym6 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) (a6989586621680093836 :: [b6989586621680092301]) (a6989586621680093837 :: [c6989586621680092302]) (a6989586621680093838 :: [d6989586621680092303]) (a6989586621680093839 :: [e6989586621680092304]) :: (~>) [f6989586621680092305] ((~>) [g6989586621680092306] [h6989586621680092307]) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym6 a6989586621680093839 a6989586621680093838 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [f6989586621680092305] ([g6989586621680092306] ~> [h6989586621680092307]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym6 a6989586621680093839 a6989586621680093838 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [f6989586621680092305] ([g6989586621680092306] ~> [h6989586621680092307]) -> Type) (a6989586621680093840 :: [f6989586621680092305]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym6 a6989586621680093839 a6989586621680093838 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [f6989586621680092305] ([g6989586621680092306] ~> [h6989586621680092307]) -> Type) (a6989586621680093840 :: [f6989586621680092305]) = ZipWith7Sym7 a6989586621680093839 a6989586621680093838 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 a6989586621680093840 |
data ZipWith7Sym7 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) (a6989586621680093836 :: [b6989586621680092301]) (a6989586621680093837 :: [c6989586621680092302]) (a6989586621680093838 :: [d6989586621680092303]) (a6989586621680093839 :: [e6989586621680092304]) (a6989586621680093840 :: [f6989586621680092305]) :: (~>) [g6989586621680092306] [h6989586621680092307] Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym7 a6989586621680093840 a6989586621680093839 a6989586621680093838 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [g6989586621680092306] [h6989586621680092307] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym7 a6989586621680093840 a6989586621680093839 a6989586621680093838 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [g] [h] -> Type) (a6989586621680093841 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym7 a6989586621680093840 a6989586621680093839 a6989586621680093838 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 :: TyFun [g] [h] -> Type) (a6989586621680093841 :: [g]) = ZipWith7 a6989586621680093840 a6989586621680093839 a6989586621680093838 a6989586621680093837 a6989586621680093836 a6989586621680093835 a6989586621680093834 a6989586621680093841 |
type ZipWith7Sym8 (a6989586621680093834 :: (~>) a6989586621680092300 ((~>) b6989586621680092301 ((~>) c6989586621680092302 ((~>) d6989586621680092303 ((~>) e6989586621680092304 ((~>) f6989586621680092305 ((~>) g6989586621680092306 h6989586621680092307))))))) (a6989586621680093835 :: [a6989586621680092300]) (a6989586621680093836 :: [b6989586621680092301]) (a6989586621680093837 :: [c6989586621680092302]) (a6989586621680093838 :: [d6989586621680092303]) (a6989586621680093839 :: [e6989586621680092304]) (a6989586621680093840 :: [f6989586621680092305]) (a6989586621680093841 :: [g6989586621680092306]) = ZipWith7 a6989586621680093834 a6989586621680093835 a6989586621680093836 a6989586621680093837 a6989586621680093838 a6989586621680093839 a6989586621680093840 a6989586621680093841 Source #
data UnzipSym0 :: forall a6989586621679970204 b6989586621679970205. (~>) [(a6989586621679970204, b6989586621679970205)] ([a6989586621679970204], [b6989586621679970205]) Source #
Instances
SingI (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # | |
SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a6989586621679970204, b6989586621679970205)] ([a6989586621679970204], [b6989586621679970205]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679975023 :: [(a, b)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnzipSym1 (a6989586621679975023 :: [(a6989586621679970204, b6989586621679970205)]) = Unzip a6989586621679975023 Source #
data Unzip3Sym0 :: forall a6989586621679970201 b6989586621679970202 c6989586621679970203. (~>) [(a6989586621679970201, b6989586621679970202, c6989586621679970203)] ([a6989586621679970201], [b6989586621679970202], [c6989586621679970203]) Source #
Instances
SingI (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Unzip3Sym0 Source # | |
SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a6989586621679970201, b6989586621679970202, c6989586621679970203)] ([a6989586621679970201], [b6989586621679970202], [c6989586621679970203]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679975002 :: [(a, b, c)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679975002 :: [(a, b, c)]) = Unzip3 a6989586621679975002 |
type Unzip3Sym1 (a6989586621679975002 :: [(a6989586621679970201, b6989586621679970202, c6989586621679970203)]) = Unzip3 a6989586621679975002 Source #
data Unzip4Sym0 :: forall a6989586621679970197 b6989586621679970198 c6989586621679970199 d6989586621679970200. (~>) [(a6989586621679970197, b6989586621679970198, c6989586621679970199, d6989586621679970200)] ([a6989586621679970197], [b6989586621679970198], [c6989586621679970199], [d6989586621679970200]) Source #
Instances
SingI (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Unzip4Sym0 Source # | |
SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a6989586621679970197, b6989586621679970198, c6989586621679970199, d6989586621679970200)] ([a6989586621679970197], [b6989586621679970198], [c6989586621679970199], [d6989586621679970200]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679974979 :: [(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) (a6989586621679974979 :: [(a, b, c, d)]) = Unzip4 a6989586621679974979 |
type Unzip4Sym1 (a6989586621679974979 :: [(a6989586621679970197, b6989586621679970198, c6989586621679970199, d6989586621679970200)]) = Unzip4 a6989586621679974979 Source #
data Unzip5Sym0 :: forall a6989586621679970192 b6989586621679970193 c6989586621679970194 d6989586621679970195 e6989586621679970196. (~>) [(a6989586621679970192, b6989586621679970193, c6989586621679970194, d6989586621679970195, e6989586621679970196)] ([a6989586621679970192], [b6989586621679970193], [c6989586621679970194], [d6989586621679970195], [e6989586621679970196]) Source #
Instances
SingI (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Unzip5Sym0 Source # | |
SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a6989586621679970192, b6989586621679970193, c6989586621679970194, d6989586621679970195, e6989586621679970196)] ([a6989586621679970192], [b6989586621679970193], [c6989586621679970194], [d6989586621679970195], [e6989586621679970196]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679974954 :: [(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) (a6989586621679974954 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679974954 |
type Unzip5Sym1 (a6989586621679974954 :: [(a6989586621679970192, b6989586621679970193, c6989586621679970194, d6989586621679970195, e6989586621679970196)]) = Unzip5 a6989586621679974954 Source #
data Unzip6Sym0 :: forall a6989586621679970186 b6989586621679970187 c6989586621679970188 d6989586621679970189 e6989586621679970190 f6989586621679970191. (~>) [(a6989586621679970186, b6989586621679970187, c6989586621679970188, d6989586621679970189, e6989586621679970190, f6989586621679970191)] ([a6989586621679970186], [b6989586621679970187], [c6989586621679970188], [d6989586621679970189], [e6989586621679970190], [f6989586621679970191]) Source #
Instances
SingI (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Unzip6Sym0 Source # | |
SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a6989586621679970186, b6989586621679970187, c6989586621679970188, d6989586621679970189, e6989586621679970190, f6989586621679970191)] ([a6989586621679970186], [b6989586621679970187], [c6989586621679970188], [d6989586621679970189], [e6989586621679970190], [f6989586621679970191]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679974927 :: [(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) (a6989586621679974927 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679974927 |
type Unzip6Sym1 (a6989586621679974927 :: [(a6989586621679970186, b6989586621679970187, c6989586621679970188, d6989586621679970189, e6989586621679970190, f6989586621679970191)]) = Unzip6 a6989586621679974927 Source #
data Unzip7Sym0 :: forall a6989586621679970179 b6989586621679970180 c6989586621679970181 d6989586621679970182 e6989586621679970183 f6989586621679970184 g6989586621679970185. (~>) [(a6989586621679970179, b6989586621679970180, c6989586621679970181, d6989586621679970182, e6989586621679970183, f6989586621679970184, g6989586621679970185)] ([a6989586621679970179], [b6989586621679970180], [c6989586621679970181], [d6989586621679970182], [e6989586621679970183], [f6989586621679970184], [g6989586621679970185]) Source #
Instances
SingI (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing Unzip7Sym0 Source # | |
SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a6989586621679970179, b6989586621679970180, c6989586621679970181, d6989586621679970182, e6989586621679970183, f6989586621679970184, g6989586621679970185)] ([a6989586621679970179], [b6989586621679970180], [c6989586621679970181], [d6989586621679970182], [e6989586621679970183], [f6989586621679970184], [g6989586621679970185]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679974898 :: [(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) (a6989586621679974898 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679974898 |
type Unzip7Sym1 (a6989586621679974898 :: [(a6989586621679970179, b6989586621679970180, c6989586621679970181, d6989586621679970182, e6989586621679970183, f6989586621679970184, g6989586621679970185)]) = Unzip7 a6989586621679974898 Source #
data UnlinesSym0 :: (~>) [Symbol] Symbol Source #
Instances
SingI UnlinesSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing UnlinesSym0 Source # | |
SuppressUnusedWarnings UnlinesSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply UnlinesSym0 (a6989586621679974894 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnlinesSym1 (a6989586621679974894 :: [Symbol]) = Unlines a6989586621679974894 Source #
data UnwordsSym0 :: (~>) [Symbol] Symbol Source #
Instances
SingI UnwordsSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing UnwordsSym0 Source # | |
SuppressUnusedWarnings UnwordsSym0 Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply UnwordsSym0 (a6989586621679974883 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnwordsSym1 (a6989586621679974883 :: [Symbol]) = Unwords a6989586621679974883 Source #
data NubSym0 :: forall a6989586621679970138. (~>) [a6989586621679970138] [a6989586621679970138] Source #
Instances
SEq a => SingI (NubSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (NubSym0 :: TyFun [a6989586621679970138] [a6989586621679970138] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (NubSym0 :: TyFun [a] [a] -> Type) (a6989586621679974266 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data DeleteSym0 :: forall a6989586621679970178. (~>) a6989586621679970178 ((~>) [a6989586621679970178] [a6989586621679970178]) Source #
Instances
SEq a => SingI (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing DeleteSym0 Source # | |
SuppressUnusedWarnings (DeleteSym0 :: TyFun a6989586621679970178 ([a6989586621679970178] ~> [a6989586621679970178]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym0 :: TyFun a6989586621679970178 ([a6989586621679970178] ~> [a6989586621679970178]) -> Type) (a6989586621679974877 :: a6989586621679970178) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym0 :: TyFun a6989586621679970178 ([a6989586621679970178] ~> [a6989586621679970178]) -> Type) (a6989586621679974877 :: a6989586621679970178) = DeleteSym1 a6989586621679974877 |
data DeleteSym1 (a6989586621679974877 :: a6989586621679970178) :: (~>) [a6989586621679970178] [a6989586621679970178] Source #
Instances
(SEq a, SingI d) => SingI (DeleteSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DeleteSym1 d) Source # | |
SuppressUnusedWarnings (DeleteSym1 a6989586621679974877 :: TyFun [a6989586621679970178] [a6989586621679970178] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym1 a6989586621679974877 :: TyFun [a] [a] -> Type) (a6989586621679974878 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym1 a6989586621679974877 :: TyFun [a] [a] -> Type) (a6989586621679974878 :: [a]) = Delete a6989586621679974877 a6989586621679974878 |
type DeleteSym2 (a6989586621679974877 :: a6989586621679970178) (a6989586621679974878 :: [a6989586621679970178]) = Delete a6989586621679974877 a6989586621679974878 Source #
data (\\@#@$) :: forall a6989586621679970177. (~>) [a6989586621679970177] ((~>) [a6989586621679970177] [a6989586621679970177]) infix 5 Source #
Instances
SEq a => SingI ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((\\@#@$) :: TyFun [a6989586621679970177] ([a6989586621679970177] ~> [a6989586621679970177]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$) :: TyFun [a6989586621679970177] ([a6989586621679970177] ~> [a6989586621679970177]) -> Type) (a6989586621679974867 :: [a6989586621679970177]) Source # | |
data (\\@#@$$) (a6989586621679974867 :: [a6989586621679970177]) :: (~>) [a6989586621679970177] [a6989586621679970177] infix 5 Source #
Instances
(SEq a, SingI d) => SingI ((\\@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((\\@#@$$) a6989586621679974867 :: TyFun [a6989586621679970177] [a6989586621679970177] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$$) a6989586621679974867 :: TyFun [a] [a] -> Type) (a6989586621679974868 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type (\\@#@$$$) (a6989586621679974867 :: [a6989586621679970177]) (a6989586621679974868 :: [a6989586621679970177]) = (\\) a6989586621679974867 a6989586621679974868 Source #
data UnionSym0 :: forall a6989586621679970134. (~>) [a6989586621679970134] ((~>) [a6989586621679970134] [a6989586621679970134]) Source #
Instances
SEq a => SingI (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (UnionSym0 :: TyFun [a6989586621679970134] ([a6989586621679970134] ~> [a6989586621679970134]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym0 :: TyFun [a6989586621679970134] ([a6989586621679970134] ~> [a6989586621679970134]) -> Type) (a6989586621679974216 :: [a6989586621679970134]) Source # | |
data UnionSym1 (a6989586621679974216 :: [a6989586621679970134]) :: (~>) [a6989586621679970134] [a6989586621679970134] Source #
Instances
(SEq a, SingI d) => SingI (UnionSym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (UnionSym1 a6989586621679974216 :: TyFun [a6989586621679970134] [a6989586621679970134] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym1 a6989586621679974216 :: TyFun [a] [a] -> Type) (a6989586621679974217 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnionSym2 (a6989586621679974216 :: [a6989586621679970134]) (a6989586621679974217 :: [a6989586621679970134]) = Union a6989586621679974216 a6989586621679974217 Source #
data IntersectSym0 :: forall a6989586621679970164. (~>) [a6989586621679970164] ((~>) [a6989586621679970164] [a6989586621679970164]) Source #
Instances
SEq a => SingI (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing IntersectSym0 Source # | |
SuppressUnusedWarnings (IntersectSym0 :: TyFun [a6989586621679970164] ([a6989586621679970164] ~> [a6989586621679970164]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym0 :: TyFun [a6989586621679970164] ([a6989586621679970164] ~> [a6989586621679970164]) -> Type) (a6989586621679974661 :: [a6989586621679970164]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym0 :: TyFun [a6989586621679970164] ([a6989586621679970164] ~> [a6989586621679970164]) -> Type) (a6989586621679974661 :: [a6989586621679970164]) = IntersectSym1 a6989586621679974661 |
data IntersectSym1 (a6989586621679974661 :: [a6989586621679970164]) :: (~>) [a6989586621679970164] [a6989586621679970164] Source #
Instances
(SEq a, SingI d) => SingI (IntersectSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IntersectSym1 d) Source # | |
SuppressUnusedWarnings (IntersectSym1 a6989586621679974661 :: TyFun [a6989586621679970164] [a6989586621679970164] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym1 a6989586621679974661 :: TyFun [a] [a] -> Type) (a6989586621679974662 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym1 a6989586621679974661 :: TyFun [a] [a] -> Type) (a6989586621679974662 :: [a]) = Intersect a6989586621679974661 a6989586621679974662 |
type IntersectSym2 (a6989586621679974661 :: [a6989586621679970164]) (a6989586621679974662 :: [a6989586621679970164]) = Intersect a6989586621679974661 a6989586621679974662 Source #
data InsertSym0 :: forall a6989586621679970151. (~>) a6989586621679970151 ((~>) [a6989586621679970151] [a6989586621679970151]) Source #
Instances
SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing InsertSym0 Source # | |
SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621679970151 ([a6989586621679970151] ~> [a6989586621679970151]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym0 :: TyFun a6989586621679970151 ([a6989586621679970151] ~> [a6989586621679970151]) -> Type) (a6989586621679974424 :: a6989586621679970151) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym0 :: TyFun a6989586621679970151 ([a6989586621679970151] ~> [a6989586621679970151]) -> Type) (a6989586621679974424 :: a6989586621679970151) = InsertSym1 a6989586621679974424 |
data InsertSym1 (a6989586621679974424 :: a6989586621679970151) :: (~>) [a6989586621679970151] [a6989586621679970151] Source #
Instances
(SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (InsertSym1 d) Source # | |
SuppressUnusedWarnings (InsertSym1 a6989586621679974424 :: TyFun [a6989586621679970151] [a6989586621679970151] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym1 a6989586621679974424 :: TyFun [a] [a] -> Type) (a6989586621679974425 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym1 a6989586621679974424 :: TyFun [a] [a] -> Type) (a6989586621679974425 :: [a]) = Insert a6989586621679974424 a6989586621679974425 |
type InsertSym2 (a6989586621679974424 :: a6989586621679970151) (a6989586621679974425 :: [a6989586621679970151]) = Insert a6989586621679974424 a6989586621679974425 Source #
data SortSym0 :: forall a6989586621679970150. (~>) [a6989586621679970150] [a6989586621679970150] Source #
Instances
SOrd a => SingI (SortSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (SortSym0 :: TyFun [a6989586621679970150] [a6989586621679970150] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SortSym0 :: TyFun [a] [a] -> Type) (a6989586621679974421 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data NubBySym0 :: forall a6989586621679970137. (~>) ((~>) a6989586621679970137 ((~>) a6989586621679970137 Bool)) ((~>) [a6989586621679970137] [a6989586621679970137]) Source #
Instances
SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (NubBySym0 :: TyFun (a6989586621679970137 ~> (a6989586621679970137 ~> Bool)) ([a6989586621679970137] ~> [a6989586621679970137]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym0 :: TyFun (a6989586621679970137 ~> (a6989586621679970137 ~> Bool)) ([a6989586621679970137] ~> [a6989586621679970137]) -> Type) (a6989586621679974241 :: a6989586621679970137 ~> (a6989586621679970137 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data NubBySym1 (a6989586621679974241 :: (~>) a6989586621679970137 ((~>) a6989586621679970137 Bool)) :: (~>) [a6989586621679970137] [a6989586621679970137] Source #
Instances
SingI d => SingI (NubBySym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (NubBySym1 a6989586621679974241 :: TyFun [a6989586621679970137] [a6989586621679970137] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym1 a6989586621679974241 :: TyFun [a] [a] -> Type) (a6989586621679974242 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type NubBySym2 (a6989586621679974241 :: (~>) a6989586621679970137 ((~>) a6989586621679970137 Bool)) (a6989586621679974242 :: [a6989586621679970137]) = NubBy a6989586621679974241 a6989586621679974242 Source #
data DeleteBySym0 :: forall a6989586621679970176. (~>) ((~>) a6989586621679970176 ((~>) a6989586621679970176 Bool)) ((~>) a6989586621679970176 ((~>) [a6989586621679970176] [a6989586621679970176])) Source #
Instances
SingI (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing DeleteBySym0 Source # | |
SuppressUnusedWarnings (DeleteBySym0 :: TyFun (a6989586621679970176 ~> (a6989586621679970176 ~> Bool)) (a6989586621679970176 ~> ([a6989586621679970176] ~> [a6989586621679970176])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym0 :: TyFun (a6989586621679970176 ~> (a6989586621679970176 ~> Bool)) (a6989586621679970176 ~> ([a6989586621679970176] ~> [a6989586621679970176])) -> Type) (a6989586621679974845 :: a6989586621679970176 ~> (a6989586621679970176 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym0 :: TyFun (a6989586621679970176 ~> (a6989586621679970176 ~> Bool)) (a6989586621679970176 ~> ([a6989586621679970176] ~> [a6989586621679970176])) -> Type) (a6989586621679974845 :: a6989586621679970176 ~> (a6989586621679970176 ~> Bool)) = DeleteBySym1 a6989586621679974845 |
data DeleteBySym1 (a6989586621679974845 :: (~>) a6989586621679970176 ((~>) a6989586621679970176 Bool)) :: (~>) a6989586621679970176 ((~>) [a6989586621679970176] [a6989586621679970176]) Source #
Instances
SingI d => SingI (DeleteBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DeleteBySym1 d) Source # | |
SuppressUnusedWarnings (DeleteBySym1 a6989586621679974845 :: TyFun a6989586621679970176 ([a6989586621679970176] ~> [a6989586621679970176]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym1 a6989586621679974845 :: TyFun a6989586621679970176 ([a6989586621679970176] ~> [a6989586621679970176]) -> Type) (a6989586621679974846 :: a6989586621679970176) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym1 a6989586621679974845 :: TyFun a6989586621679970176 ([a6989586621679970176] ~> [a6989586621679970176]) -> Type) (a6989586621679974846 :: a6989586621679970176) = DeleteBySym2 a6989586621679974845 a6989586621679974846 |
data DeleteBySym2 (a6989586621679974845 :: (~>) a6989586621679970176 ((~>) a6989586621679970176 Bool)) (a6989586621679974846 :: a6989586621679970176) :: (~>) [a6989586621679970176] [a6989586621679970176] Source #
Instances
(SingI d1, SingI d2) => SingI (DeleteBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DeleteBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (DeleteBySym2 a6989586621679974846 a6989586621679974845 :: TyFun [a6989586621679970176] [a6989586621679970176] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym2 a6989586621679974846 a6989586621679974845 :: TyFun [a] [a] -> Type) (a6989586621679974847 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym2 a6989586621679974846 a6989586621679974845 :: TyFun [a] [a] -> Type) (a6989586621679974847 :: [a]) = DeleteBy a6989586621679974846 a6989586621679974845 a6989586621679974847 |
type DeleteBySym3 (a6989586621679974845 :: (~>) a6989586621679970176 ((~>) a6989586621679970176 Bool)) (a6989586621679974846 :: a6989586621679970176) (a6989586621679974847 :: [a6989586621679970176]) = DeleteBy a6989586621679974845 a6989586621679974846 a6989586621679974847 Source #
data DeleteFirstsBySym0 :: forall a6989586621679970175. (~>) ((~>) a6989586621679970175 ((~>) a6989586621679970175 Bool)) ((~>) [a6989586621679970175] ((~>) [a6989586621679970175] [a6989586621679970175])) Source #
Instances
SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (a6989586621679970175 ~> (a6989586621679970175 ~> Bool)) ([a6989586621679970175] ~> ([a6989586621679970175] ~> [a6989586621679970175])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679970175 ~> (a6989586621679970175 ~> Bool)) ([a6989586621679970175] ~> ([a6989586621679970175] ~> [a6989586621679970175])) -> Type) (a6989586621679974832 :: a6989586621679970175 ~> (a6989586621679970175 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679970175 ~> (a6989586621679970175 ~> Bool)) ([a6989586621679970175] ~> ([a6989586621679970175] ~> [a6989586621679970175])) -> Type) (a6989586621679974832 :: a6989586621679970175 ~> (a6989586621679970175 ~> Bool)) = DeleteFirstsBySym1 a6989586621679974832 |
data DeleteFirstsBySym1 (a6989586621679974832 :: (~>) a6989586621679970175 ((~>) a6989586621679970175 Bool)) :: (~>) [a6989586621679970175] ((~>) [a6989586621679970175] [a6989586621679970175]) Source #
Instances
SingI d => SingI (DeleteFirstsBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DeleteFirstsBySym1 d) Source # | |
SuppressUnusedWarnings (DeleteFirstsBySym1 a6989586621679974832 :: TyFun [a6989586621679970175] ([a6989586621679970175] ~> [a6989586621679970175]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym1 a6989586621679974832 :: TyFun [a6989586621679970175] ([a6989586621679970175] ~> [a6989586621679970175]) -> Type) (a6989586621679974833 :: [a6989586621679970175]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym1 a6989586621679974832 :: TyFun [a6989586621679970175] ([a6989586621679970175] ~> [a6989586621679970175]) -> Type) (a6989586621679974833 :: [a6989586621679970175]) = DeleteFirstsBySym2 a6989586621679974832 a6989586621679974833 |
data DeleteFirstsBySym2 (a6989586621679974832 :: (~>) a6989586621679970175 ((~>) a6989586621679970175 Bool)) (a6989586621679974833 :: [a6989586621679970175]) :: (~>) [a6989586621679970175] [a6989586621679970175] Source #
Instances
(SingI d1, SingI d2) => SingI (DeleteFirstsBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (DeleteFirstsBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (DeleteFirstsBySym2 a6989586621679974833 a6989586621679974832 :: TyFun [a6989586621679970175] [a6989586621679970175] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym2 a6989586621679974833 a6989586621679974832 :: TyFun [a] [a] -> Type) (a6989586621679974834 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym2 a6989586621679974833 a6989586621679974832 :: TyFun [a] [a] -> Type) (a6989586621679974834 :: [a]) = DeleteFirstsBy a6989586621679974833 a6989586621679974832 a6989586621679974834 |
type DeleteFirstsBySym3 (a6989586621679974832 :: (~>) a6989586621679970175 ((~>) a6989586621679970175 Bool)) (a6989586621679974833 :: [a6989586621679970175]) (a6989586621679974834 :: [a6989586621679970175]) = DeleteFirstsBy a6989586621679974832 a6989586621679974833 a6989586621679974834 Source #
data UnionBySym0 :: forall a6989586621679970135. (~>) ((~>) a6989586621679970135 ((~>) a6989586621679970135 Bool)) ((~>) [a6989586621679970135] ((~>) [a6989586621679970135] [a6989586621679970135])) Source #
Instances
SingI (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing UnionBySym0 Source # | |
SuppressUnusedWarnings (UnionBySym0 :: TyFun (a6989586621679970135 ~> (a6989586621679970135 ~> Bool)) ([a6989586621679970135] ~> ([a6989586621679970135] ~> [a6989586621679970135])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym0 :: TyFun (a6989586621679970135 ~> (a6989586621679970135 ~> Bool)) ([a6989586621679970135] ~> ([a6989586621679970135] ~> [a6989586621679970135])) -> Type) (a6989586621679974222 :: a6989586621679970135 ~> (a6989586621679970135 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym0 :: TyFun (a6989586621679970135 ~> (a6989586621679970135 ~> Bool)) ([a6989586621679970135] ~> ([a6989586621679970135] ~> [a6989586621679970135])) -> Type) (a6989586621679974222 :: a6989586621679970135 ~> (a6989586621679970135 ~> Bool)) = UnionBySym1 a6989586621679974222 |
data UnionBySym1 (a6989586621679974222 :: (~>) a6989586621679970135 ((~>) a6989586621679970135 Bool)) :: (~>) [a6989586621679970135] ((~>) [a6989586621679970135] [a6989586621679970135]) Source #
Instances
SingI d => SingI (UnionBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (UnionBySym1 d) Source # | |
SuppressUnusedWarnings (UnionBySym1 a6989586621679974222 :: TyFun [a6989586621679970135] ([a6989586621679970135] ~> [a6989586621679970135]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym1 a6989586621679974222 :: TyFun [a6989586621679970135] ([a6989586621679970135] ~> [a6989586621679970135]) -> Type) (a6989586621679974223 :: [a6989586621679970135]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym1 a6989586621679974222 :: TyFun [a6989586621679970135] ([a6989586621679970135] ~> [a6989586621679970135]) -> Type) (a6989586621679974223 :: [a6989586621679970135]) = UnionBySym2 a6989586621679974222 a6989586621679974223 |
data UnionBySym2 (a6989586621679974222 :: (~>) a6989586621679970135 ((~>) a6989586621679970135 Bool)) (a6989586621679974223 :: [a6989586621679970135]) :: (~>) [a6989586621679970135] [a6989586621679970135] Source #
Instances
(SingI d1, SingI d2) => SingI (UnionBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (UnionBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (UnionBySym2 a6989586621679974223 a6989586621679974222 :: TyFun [a6989586621679970135] [a6989586621679970135] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym2 a6989586621679974223 a6989586621679974222 :: TyFun [a] [a] -> Type) (a6989586621679974224 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym2 a6989586621679974223 a6989586621679974222 :: TyFun [a] [a] -> Type) (a6989586621679974224 :: [a]) = UnionBy a6989586621679974223 a6989586621679974222 a6989586621679974224 |
type UnionBySym3 (a6989586621679974222 :: (~>) a6989586621679970135 ((~>) a6989586621679970135 Bool)) (a6989586621679974223 :: [a6989586621679970135]) (a6989586621679974224 :: [a6989586621679970135]) = UnionBy a6989586621679974222 a6989586621679974223 a6989586621679974224 Source #
data IntersectBySym0 :: forall a6989586621679970163. (~>) ((~>) a6989586621679970163 ((~>) a6989586621679970163 Bool)) ((~>) [a6989586621679970163] ((~>) [a6989586621679970163] [a6989586621679970163])) Source #
Instances
SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IntersectBySym0 :: TyFun (a6989586621679970163 ~> (a6989586621679970163 ~> Bool)) ([a6989586621679970163] ~> ([a6989586621679970163] ~> [a6989586621679970163])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym0 :: TyFun (a6989586621679970163 ~> (a6989586621679970163 ~> Bool)) ([a6989586621679970163] ~> ([a6989586621679970163] ~> [a6989586621679970163])) -> Type) (a6989586621679974625 :: a6989586621679970163 ~> (a6989586621679970163 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym0 :: TyFun (a6989586621679970163 ~> (a6989586621679970163 ~> Bool)) ([a6989586621679970163] ~> ([a6989586621679970163] ~> [a6989586621679970163])) -> Type) (a6989586621679974625 :: a6989586621679970163 ~> (a6989586621679970163 ~> Bool)) = IntersectBySym1 a6989586621679974625 |
data IntersectBySym1 (a6989586621679974625 :: (~>) a6989586621679970163 ((~>) a6989586621679970163 Bool)) :: (~>) [a6989586621679970163] ((~>) [a6989586621679970163] [a6989586621679970163]) Source #
Instances
SingI d => SingI (IntersectBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IntersectBySym1 d) Source # | |
SuppressUnusedWarnings (IntersectBySym1 a6989586621679974625 :: TyFun [a6989586621679970163] ([a6989586621679970163] ~> [a6989586621679970163]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym1 a6989586621679974625 :: TyFun [a6989586621679970163] ([a6989586621679970163] ~> [a6989586621679970163]) -> Type) (a6989586621679974626 :: [a6989586621679970163]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym1 a6989586621679974625 :: TyFun [a6989586621679970163] ([a6989586621679970163] ~> [a6989586621679970163]) -> Type) (a6989586621679974626 :: [a6989586621679970163]) = IntersectBySym2 a6989586621679974625 a6989586621679974626 |
data IntersectBySym2 (a6989586621679974625 :: (~>) a6989586621679970163 ((~>) a6989586621679970163 Bool)) (a6989586621679974626 :: [a6989586621679970163]) :: (~>) [a6989586621679970163] [a6989586621679970163] Source #
Instances
(SingI d1, SingI d2) => SingI (IntersectBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IntersectBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (IntersectBySym2 a6989586621679974626 a6989586621679974625 :: TyFun [a6989586621679970163] [a6989586621679970163] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym2 a6989586621679974626 a6989586621679974625 :: TyFun [a] [a] -> Type) (a6989586621679974627 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym2 a6989586621679974626 a6989586621679974625 :: TyFun [a] [a] -> Type) (a6989586621679974627 :: [a]) = IntersectBy a6989586621679974626 a6989586621679974625 a6989586621679974627 |
type IntersectBySym3 (a6989586621679974625 :: (~>) a6989586621679970163 ((~>) a6989586621679970163 Bool)) (a6989586621679974626 :: [a6989586621679970163]) (a6989586621679974627 :: [a6989586621679970163]) = IntersectBy a6989586621679974625 a6989586621679974626 a6989586621679974627 Source #
data GroupBySym0 :: forall a6989586621679970149. (~>) ((~>) a6989586621679970149 ((~>) a6989586621679970149 Bool)) ((~>) [a6989586621679970149] [[a6989586621679970149]]) Source #
Instances
SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing GroupBySym0 Source # | |
SuppressUnusedWarnings (GroupBySym0 :: TyFun (a6989586621679970149 ~> (a6989586621679970149 ~> Bool)) ([a6989586621679970149] ~> [[a6989586621679970149]]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym0 :: TyFun (a6989586621679970149 ~> (a6989586621679970149 ~> Bool)) ([a6989586621679970149] ~> [[a6989586621679970149]]) -> Type) (a6989586621679974388 :: a6989586621679970149 ~> (a6989586621679970149 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GroupBySym0 :: TyFun (a6989586621679970149 ~> (a6989586621679970149 ~> Bool)) ([a6989586621679970149] ~> [[a6989586621679970149]]) -> Type) (a6989586621679974388 :: a6989586621679970149 ~> (a6989586621679970149 ~> Bool)) = GroupBySym1 a6989586621679974388 |
data GroupBySym1 (a6989586621679974388 :: (~>) a6989586621679970149 ((~>) a6989586621679970149 Bool)) :: (~>) [a6989586621679970149] [[a6989586621679970149]] Source #
Instances
SingI d => SingI (GroupBySym1 d :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (GroupBySym1 d) Source # | |
SuppressUnusedWarnings (GroupBySym1 a6989586621679974388 :: TyFun [a6989586621679970149] [[a6989586621679970149]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym1 a6989586621679974388 :: TyFun [a] [[a]] -> Type) (a6989586621679974389 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GroupBySym1 a6989586621679974388 :: TyFun [a] [[a]] -> Type) (a6989586621679974389 :: [a]) = GroupBy a6989586621679974388 a6989586621679974389 |
type GroupBySym2 (a6989586621679974388 :: (~>) a6989586621679970149 ((~>) a6989586621679970149 Bool)) (a6989586621679974389 :: [a6989586621679970149]) = GroupBy a6989586621679974388 a6989586621679974389 Source #
data SortBySym0 :: forall a6989586621679970174. (~>) ((~>) a6989586621679970174 ((~>) a6989586621679970174 Ordering)) ((~>) [a6989586621679970174] [a6989586621679970174]) Source #
Instances
SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing SortBySym0 Source # | |
SuppressUnusedWarnings (SortBySym0 :: TyFun (a6989586621679970174 ~> (a6989586621679970174 ~> Ordering)) ([a6989586621679970174] ~> [a6989586621679970174]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym0 :: TyFun (a6989586621679970174 ~> (a6989586621679970174 ~> Ordering)) ([a6989586621679970174] ~> [a6989586621679970174]) -> Type) (a6989586621679974824 :: a6989586621679970174 ~> (a6989586621679970174 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SortBySym0 :: TyFun (a6989586621679970174 ~> (a6989586621679970174 ~> Ordering)) ([a6989586621679970174] ~> [a6989586621679970174]) -> Type) (a6989586621679974824 :: a6989586621679970174 ~> (a6989586621679970174 ~> Ordering)) = SortBySym1 a6989586621679974824 |
data SortBySym1 (a6989586621679974824 :: (~>) a6989586621679970174 ((~>) a6989586621679970174 Ordering)) :: (~>) [a6989586621679970174] [a6989586621679970174] Source #
Instances
SingI d => SingI (SortBySym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (SortBySym1 d) Source # | |
SuppressUnusedWarnings (SortBySym1 a6989586621679974824 :: TyFun [a6989586621679970174] [a6989586621679970174] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym1 a6989586621679974824 :: TyFun [a] [a] -> Type) (a6989586621679974825 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SortBySym1 a6989586621679974824 :: TyFun [a] [a] -> Type) (a6989586621679974825 :: [a]) = SortBy a6989586621679974824 a6989586621679974825 |
type SortBySym2 (a6989586621679974824 :: (~>) a6989586621679970174 ((~>) a6989586621679970174 Ordering)) (a6989586621679974825 :: [a6989586621679970174]) = SortBy a6989586621679974824 a6989586621679974825 Source #
data InsertBySym0 :: forall a6989586621679970173. (~>) ((~>) a6989586621679970173 ((~>) a6989586621679970173 Ordering)) ((~>) a6989586621679970173 ((~>) [a6989586621679970173] [a6989586621679970173])) Source #
Instances
SingI (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing InsertBySym0 Source # | |
SuppressUnusedWarnings (InsertBySym0 :: TyFun (a6989586621679970173 ~> (a6989586621679970173 ~> Ordering)) (a6989586621679970173 ~> ([a6989586621679970173] ~> [a6989586621679970173])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym0 :: TyFun (a6989586621679970173 ~> (a6989586621679970173 ~> Ordering)) (a6989586621679970173 ~> ([a6989586621679970173] ~> [a6989586621679970173])) -> Type) (a6989586621679974800 :: a6989586621679970173 ~> (a6989586621679970173 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym0 :: TyFun (a6989586621679970173 ~> (a6989586621679970173 ~> Ordering)) (a6989586621679970173 ~> ([a6989586621679970173] ~> [a6989586621679970173])) -> Type) (a6989586621679974800 :: a6989586621679970173 ~> (a6989586621679970173 ~> Ordering)) = InsertBySym1 a6989586621679974800 |
data InsertBySym1 (a6989586621679974800 :: (~>) a6989586621679970173 ((~>) a6989586621679970173 Ordering)) :: (~>) a6989586621679970173 ((~>) [a6989586621679970173] [a6989586621679970173]) Source #
Instances
SingI d => SingI (InsertBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (InsertBySym1 d) Source # | |
SuppressUnusedWarnings (InsertBySym1 a6989586621679974800 :: TyFun a6989586621679970173 ([a6989586621679970173] ~> [a6989586621679970173]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym1 a6989586621679974800 :: TyFun a6989586621679970173 ([a6989586621679970173] ~> [a6989586621679970173]) -> Type) (a6989586621679974801 :: a6989586621679970173) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym1 a6989586621679974800 :: TyFun a6989586621679970173 ([a6989586621679970173] ~> [a6989586621679970173]) -> Type) (a6989586621679974801 :: a6989586621679970173) = InsertBySym2 a6989586621679974800 a6989586621679974801 |
data InsertBySym2 (a6989586621679974800 :: (~>) a6989586621679970173 ((~>) a6989586621679970173 Ordering)) (a6989586621679974801 :: a6989586621679970173) :: (~>) [a6989586621679970173] [a6989586621679970173] Source #
Instances
(SingI d1, SingI d2) => SingI (InsertBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (InsertBySym2 d1 d2) Source # | |
SuppressUnusedWarnings (InsertBySym2 a6989586621679974801 a6989586621679974800 :: TyFun [a6989586621679970173] [a6989586621679970173] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym2 a6989586621679974801 a6989586621679974800 :: TyFun [a] [a] -> Type) (a6989586621679974802 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym2 a6989586621679974801 a6989586621679974800 :: TyFun [a] [a] -> Type) (a6989586621679974802 :: [a]) = InsertBy a6989586621679974801 a6989586621679974800 a6989586621679974802 |
type InsertBySym3 (a6989586621679974800 :: (~>) a6989586621679970173 ((~>) a6989586621679970173 Ordering)) (a6989586621679974801 :: a6989586621679970173) (a6989586621679974802 :: [a6989586621679970173]) = InsertBy a6989586621679974800 a6989586621679974801 a6989586621679974802 Source #
data MaximumBySym0 :: forall a6989586621680486494 t6989586621680486493. (~>) ((~>) a6989586621680486494 ((~>) a6989586621680486494 Ordering)) ((~>) (t6989586621680486493 a6989586621680486494) a6989586621680486494) Source #
Instances
SFoldable t => SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing MaximumBySym0 Source # | |
SuppressUnusedWarnings (MaximumBySym0 :: TyFun (a6989586621680486494 ~> (a6989586621680486494 ~> Ordering)) (t6989586621680486493 a6989586621680486494 ~> a6989586621680486494) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym0 :: TyFun (a6989586621680486494 ~> (a6989586621680486494 ~> Ordering)) (t6989586621680486493 a6989586621680486494 ~> a6989586621680486494) -> Type) (a6989586621680487001 :: a6989586621680486494 ~> (a6989586621680486494 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym0 :: TyFun (a6989586621680486494 ~> (a6989586621680486494 ~> Ordering)) (t6989586621680486493 a6989586621680486494 ~> a6989586621680486494) -> Type) (a6989586621680487001 :: a6989586621680486494 ~> (a6989586621680486494 ~> Ordering)) = MaximumBySym1 a6989586621680487001 t6989586621680486493 :: TyFun (t6989586621680486493 a6989586621680486494) a6989586621680486494 -> Type |
data MaximumBySym1 (a6989586621680487001 :: (~>) a6989586621680486494 ((~>) a6989586621680486494 Ordering)) :: forall t6989586621680486493. (~>) (t6989586621680486493 a6989586621680486494) a6989586621680486494 Source #
Instances
(SFoldable t, SingI d) => SingI (MaximumBySym1 d t :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (MaximumBySym1 d t) Source # | |
SuppressUnusedWarnings (MaximumBySym1 a6989586621680487001 t6989586621680486493 :: TyFun (t6989586621680486493 a6989586621680486494) a6989586621680486494 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym1 a6989586621680487001 t :: TyFun (t a) a -> Type) (a6989586621680487002 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym1 a6989586621680487001 t :: TyFun (t a) a -> Type) (a6989586621680487002 :: t a) = MaximumBy a6989586621680487001 a6989586621680487002 |
type MaximumBySym2 (a6989586621680487001 :: (~>) a6989586621680486494 ((~>) a6989586621680486494 Ordering)) (a6989586621680487002 :: t6989586621680486493 a6989586621680486494) = MaximumBy a6989586621680487001 a6989586621680487002 Source #
data MinimumBySym0 :: forall a6989586621680486492 t6989586621680486491. (~>) ((~>) a6989586621680486492 ((~>) a6989586621680486492 Ordering)) ((~>) (t6989586621680486491 a6989586621680486492) a6989586621680486492) Source #
Instances
SFoldable t => SingI (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing MinimumBySym0 Source # | |
SuppressUnusedWarnings (MinimumBySym0 :: TyFun (a6989586621680486492 ~> (a6989586621680486492 ~> Ordering)) (t6989586621680486491 a6989586621680486492 ~> a6989586621680486492) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym0 :: TyFun (a6989586621680486492 ~> (a6989586621680486492 ~> Ordering)) (t6989586621680486491 a6989586621680486492 ~> a6989586621680486492) -> Type) (a6989586621680486976 :: a6989586621680486492 ~> (a6989586621680486492 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym0 :: TyFun (a6989586621680486492 ~> (a6989586621680486492 ~> Ordering)) (t6989586621680486491 a6989586621680486492 ~> a6989586621680486492) -> Type) (a6989586621680486976 :: a6989586621680486492 ~> (a6989586621680486492 ~> Ordering)) = MinimumBySym1 a6989586621680486976 t6989586621680486491 :: TyFun (t6989586621680486491 a6989586621680486492) a6989586621680486492 -> Type |
data MinimumBySym1 (a6989586621680486976 :: (~>) a6989586621680486492 ((~>) a6989586621680486492 Ordering)) :: forall t6989586621680486491. (~>) (t6989586621680486491 a6989586621680486492) a6989586621680486492 Source #
Instances
(SFoldable t, SingI d) => SingI (MinimumBySym1 d t :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (MinimumBySym1 d t) Source # | |
SuppressUnusedWarnings (MinimumBySym1 a6989586621680486976 t6989586621680486491 :: TyFun (t6989586621680486491 a6989586621680486492) a6989586621680486492 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym1 a6989586621680486976 t :: TyFun (t a) a -> Type) (a6989586621680486977 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym1 a6989586621680486976 t :: TyFun (t a) a -> Type) (a6989586621680486977 :: t a) = MinimumBy a6989586621680486976 a6989586621680486977 |
type MinimumBySym2 (a6989586621680486976 :: (~>) a6989586621680486492 ((~>) a6989586621680486492 Ordering)) (a6989586621680486977 :: t6989586621680486491 a6989586621680486492) = MinimumBy a6989586621680486976 a6989586621680486977 Source #
data GenericLengthSym0 :: forall a6989586621679970133 i6989586621679970132. (~>) [a6989586621679970133] i6989586621679970132 Source #
Instances
SNum i => SingI (GenericLengthSym0 :: TyFun [a] i -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a6989586621679970133] i6989586621679970132 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679974209 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679974209 :: [a]) = GenericLength a6989586621679974209 :: k2 |
type GenericLengthSym1 (a6989586621679974209 :: [a6989586621679970133]) = GenericLength a6989586621679974209 Source #
data GenericTakeSym0 :: forall i6989586621680092298 a6989586621680092299. (~>) i6989586621680092298 ((~>) [a6989586621680092299] [a6989586621680092299]) Source #
Instances
SuppressUnusedWarnings (GenericTakeSym0 :: TyFun i6989586621680092298 ([a6989586621680092299] ~> [a6989586621680092299]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericTakeSym0 :: TyFun i6989586621680092298 ([a6989586621680092299] ~> [a6989586621680092299]) -> Type) (a6989586621680093828 :: i6989586621680092298) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericTakeSym0 :: TyFun i6989586621680092298 ([a6989586621680092299] ~> [a6989586621680092299]) -> Type) (a6989586621680093828 :: i6989586621680092298) = GenericTakeSym1 a6989586621680093828 a6989586621680092299 :: TyFun [a6989586621680092299] [a6989586621680092299] -> Type |
data GenericTakeSym1 (a6989586621680093828 :: i6989586621680092298) :: forall a6989586621680092299. (~>) [a6989586621680092299] [a6989586621680092299] Source #
Instances
SuppressUnusedWarnings (GenericTakeSym1 a6989586621680093828 a6989586621680092299 :: TyFun [a6989586621680092299] [a6989586621680092299] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericTakeSym1 a6989586621680093828 a :: TyFun [a] [a] -> Type) (a6989586621680093829 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericTakeSym1 a6989586621680093828 a :: TyFun [a] [a] -> Type) (a6989586621680093829 :: [a]) = GenericTake a6989586621680093828 a6989586621680093829 |
type GenericTakeSym2 (a6989586621680093828 :: i6989586621680092298) (a6989586621680093829 :: [a6989586621680092299]) = GenericTake a6989586621680093828 a6989586621680093829 Source #
data GenericDropSym0 :: forall i6989586621680092296 a6989586621680092297. (~>) i6989586621680092296 ((~>) [a6989586621680092297] [a6989586621680092297]) Source #
Instances
SuppressUnusedWarnings (GenericDropSym0 :: TyFun i6989586621680092296 ([a6989586621680092297] ~> [a6989586621680092297]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericDropSym0 :: TyFun i6989586621680092296 ([a6989586621680092297] ~> [a6989586621680092297]) -> Type) (a6989586621680093818 :: i6989586621680092296) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericDropSym0 :: TyFun i6989586621680092296 ([a6989586621680092297] ~> [a6989586621680092297]) -> Type) (a6989586621680093818 :: i6989586621680092296) = GenericDropSym1 a6989586621680093818 a6989586621680092297 :: TyFun [a6989586621680092297] [a6989586621680092297] -> Type |
data GenericDropSym1 (a6989586621680093818 :: i6989586621680092296) :: forall a6989586621680092297. (~>) [a6989586621680092297] [a6989586621680092297] Source #
Instances
SuppressUnusedWarnings (GenericDropSym1 a6989586621680093818 a6989586621680092297 :: TyFun [a6989586621680092297] [a6989586621680092297] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericDropSym1 a6989586621680093818 a :: TyFun [a] [a] -> Type) (a6989586621680093819 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericDropSym1 a6989586621680093818 a :: TyFun [a] [a] -> Type) (a6989586621680093819 :: [a]) = GenericDrop a6989586621680093818 a6989586621680093819 |
type GenericDropSym2 (a6989586621680093818 :: i6989586621680092296) (a6989586621680093819 :: [a6989586621680092297]) = GenericDrop a6989586621680093818 a6989586621680093819 Source #
data GenericSplitAtSym0 :: forall i6989586621680092294 a6989586621680092295. (~>) i6989586621680092294 ((~>) [a6989586621680092295] ([a6989586621680092295], [a6989586621680092295])) Source #
Instances
SuppressUnusedWarnings (GenericSplitAtSym0 :: TyFun i6989586621680092294 ([a6989586621680092295] ~> ([a6989586621680092295], [a6989586621680092295])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericSplitAtSym0 :: TyFun i6989586621680092294 ([a6989586621680092295] ~> ([a6989586621680092295], [a6989586621680092295])) -> Type) (a6989586621680093808 :: i6989586621680092294) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericSplitAtSym0 :: TyFun i6989586621680092294 ([a6989586621680092295] ~> ([a6989586621680092295], [a6989586621680092295])) -> Type) (a6989586621680093808 :: i6989586621680092294) = GenericSplitAtSym1 a6989586621680093808 a6989586621680092295 :: TyFun [a6989586621680092295] ([a6989586621680092295], [a6989586621680092295]) -> Type |
data GenericSplitAtSym1 (a6989586621680093808 :: i6989586621680092294) :: forall a6989586621680092295. (~>) [a6989586621680092295] ([a6989586621680092295], [a6989586621680092295]) Source #
Instances
SuppressUnusedWarnings (GenericSplitAtSym1 a6989586621680093808 a6989586621680092295 :: TyFun [a6989586621680092295] ([a6989586621680092295], [a6989586621680092295]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericSplitAtSym1 a6989586621680093808 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621680093809 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericSplitAtSym1 a6989586621680093808 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621680093809 :: [a]) = GenericSplitAt a6989586621680093808 a6989586621680093809 |
type GenericSplitAtSym2 (a6989586621680093808 :: i6989586621680092294) (a6989586621680093809 :: [a6989586621680092295]) = GenericSplitAt a6989586621680093808 a6989586621680093809 Source #
data GenericIndexSym0 :: forall a6989586621680092293 i6989586621680092292. (~>) [a6989586621680092293] ((~>) i6989586621680092292 a6989586621680092293) Source #
Instances
SuppressUnusedWarnings (GenericIndexSym0 :: TyFun [a6989586621680092293] (i6989586621680092292 ~> a6989586621680092293) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericIndexSym0 :: TyFun [a6989586621680092293] (i6989586621680092292 ~> a6989586621680092293) -> Type) (a6989586621680093798 :: [a6989586621680092293]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericIndexSym0 :: TyFun [a6989586621680092293] (i6989586621680092292 ~> a6989586621680092293) -> Type) (a6989586621680093798 :: [a6989586621680092293]) = GenericIndexSym1 a6989586621680093798 i6989586621680092292 :: TyFun i6989586621680092292 a6989586621680092293 -> Type |
data GenericIndexSym1 (a6989586621680093798 :: [a6989586621680092293]) :: forall i6989586621680092292. (~>) i6989586621680092292 a6989586621680092293 Source #
Instances
SuppressUnusedWarnings (GenericIndexSym1 a6989586621680093798 i6989586621680092292 :: TyFun i6989586621680092292 a6989586621680092293 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericIndexSym1 a6989586621680093798 i :: TyFun i a -> Type) (a6989586621680093799 :: i) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericIndexSym1 a6989586621680093798 i :: TyFun i a -> Type) (a6989586621680093799 :: i) = GenericIndex a6989586621680093798 a6989586621680093799 |
type GenericIndexSym2 (a6989586621680093798 :: [a6989586621680092293]) (a6989586621680093799 :: i6989586621680092292) = GenericIndex a6989586621680093798 a6989586621680093799 Source #
data GenericReplicateSym0 :: forall i6989586621680092290 a6989586621680092291. (~>) i6989586621680092290 ((~>) a6989586621680092291 [a6989586621680092291]) Source #
Instances
SuppressUnusedWarnings (GenericReplicateSym0 :: TyFun i6989586621680092290 (a6989586621680092291 ~> [a6989586621680092291]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericReplicateSym0 :: TyFun i6989586621680092290 (a6989586621680092291 ~> [a6989586621680092291]) -> Type) (a6989586621680093788 :: i6989586621680092290) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericReplicateSym0 :: TyFun i6989586621680092290 (a6989586621680092291 ~> [a6989586621680092291]) -> Type) (a6989586621680093788 :: i6989586621680092290) = GenericReplicateSym1 a6989586621680093788 a6989586621680092291 :: TyFun a6989586621680092291 [a6989586621680092291] -> Type |
data GenericReplicateSym1 (a6989586621680093788 :: i6989586621680092290) :: forall a6989586621680092291. (~>) a6989586621680092291 [a6989586621680092291] Source #
Instances
SuppressUnusedWarnings (GenericReplicateSym1 a6989586621680093788 a6989586621680092291 :: TyFun a6989586621680092291 [a6989586621680092291] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericReplicateSym1 a6989586621680093788 a :: TyFun a [a] -> Type) (a6989586621680093789 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericReplicateSym1 a6989586621680093788 a :: TyFun a [a] -> Type) (a6989586621680093789 :: a) = GenericReplicate a6989586621680093788 a6989586621680093789 |
type GenericReplicateSym2 (a6989586621680093788 :: i6989586621680092290) (a6989586621680093789 :: a6989586621680092291) = GenericReplicate a6989586621680093788 a6989586621680093789 Source #