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 (:@#@$$) (t6989586621679310927 :: a3530822107858468865 :: Type) :: (~>) [a3530822107858468865] [a3530822107858468865 :: Type]
- type (:@#@$$$) (t6989586621679310927 :: a3530822107858468865) (t6989586621679310928 :: [a3530822107858468865]) = '(:) t6989586621679310927 t6989586621679310928
- type (++@#@$$$) (a6989586621679541756 :: [a6989586621679541559]) (a6989586621679541757 :: [a6989586621679541559]) = (++) a6989586621679541756 a6989586621679541757
- data (++@#@$$) (a6989586621679541756 :: [a6989586621679541559]) :: (~>) [a6989586621679541559] [a6989586621679541559]
- data (++@#@$) :: forall a6989586621679541559. (~>) [a6989586621679541559] ((~>) [a6989586621679541559] [a6989586621679541559])
- data HeadSym0 :: forall a6989586621679970309. (~>) [a6989586621679970309] a6989586621679970309
- type HeadSym1 (a6989586621679975656 :: [a6989586621679970309]) = Head a6989586621679975656
- data LastSym0 :: forall a6989586621679970308. (~>) [a6989586621679970308] a6989586621679970308
- type LastSym1 (a6989586621679975651 :: [a6989586621679970308]) = Last a6989586621679975651
- data TailSym0 :: forall a6989586621679970307. (~>) [a6989586621679970307] [a6989586621679970307]
- type TailSym1 (a6989586621679975648 :: [a6989586621679970307]) = Tail a6989586621679975648
- data InitSym0 :: forall a6989586621679970306. (~>) [a6989586621679970306] [a6989586621679970306]
- type InitSym1 (a6989586621679975634 :: [a6989586621679970306]) = Init a6989586621679975634
- data NullSym0 :: forall t6989586621680486628 a6989586621680486643. (~>) (t6989586621680486628 a6989586621680486643) Bool
- type NullSym1 (arg6989586621680487287 :: t6989586621680486628 a6989586621680486643) = Null arg6989586621680487287
- data LengthSym0 :: forall t6989586621680486628 a6989586621680486644. (~>) (t6989586621680486628 a6989586621680486644) Nat
- type LengthSym1 (arg6989586621680487289 :: t6989586621680486628 a6989586621680486644) = Length arg6989586621680487289
- data MapSym0 :: forall a6989586621679541560 b6989586621679541561. (~>) ((~>) a6989586621679541560 b6989586621679541561) ((~>) [a6989586621679541560] [b6989586621679541561])
- data MapSym1 (a6989586621679541764 :: (~>) a6989586621679541560 b6989586621679541561) :: (~>) [a6989586621679541560] [b6989586621679541561]
- type MapSym2 (a6989586621679541764 :: (~>) a6989586621679541560 b6989586621679541561) (a6989586621679541765 :: [a6989586621679541560]) = Map a6989586621679541764 a6989586621679541765
- data ReverseSym0 :: forall a6989586621679970304. (~>) [a6989586621679970304] [a6989586621679970304]
- type ReverseSym1 (a6989586621679975619 :: [a6989586621679970304]) = Reverse a6989586621679975619
- data IntersperseSym0 :: forall a6989586621679970303. (~>) a6989586621679970303 ((~>) [a6989586621679970303] [a6989586621679970303])
- data IntersperseSym1 (a6989586621679975612 :: a6989586621679970303) :: (~>) [a6989586621679970303] [a6989586621679970303]
- type IntersperseSym2 (a6989586621679975612 :: a6989586621679970303) (a6989586621679975613 :: [a6989586621679970303]) = Intersperse a6989586621679975612 a6989586621679975613
- data IntercalateSym0 :: forall a6989586621679970302. (~>) [a6989586621679970302] ((~>) [[a6989586621679970302]] [a6989586621679970302])
- data IntercalateSym1 (a6989586621679975606 :: [a6989586621679970302]) :: (~>) [[a6989586621679970302]] [a6989586621679970302]
- type IntercalateSym2 (a6989586621679975606 :: [a6989586621679970302]) (a6989586621679975607 :: [[a6989586621679970302]]) = Intercalate a6989586621679975606 a6989586621679975607
- data TransposeSym0 :: forall a6989586621679970189. (~>) [[a6989586621679970189]] [[a6989586621679970189]]
- type TransposeSym1 (a6989586621679974349 :: [[a6989586621679970189]]) = Transpose a6989586621679974349
- data SubsequencesSym0 :: forall a6989586621679970301. (~>) [a6989586621679970301] [[a6989586621679970301]]
- type SubsequencesSym1 (a6989586621679975603 :: [a6989586621679970301]) = Subsequences a6989586621679975603
- data PermutationsSym0 :: forall a6989586621679970298. (~>) [a6989586621679970298] [[a6989586621679970298]]
- type PermutationsSym1 (a6989586621679975485 :: [a6989586621679970298]) = Permutations a6989586621679975485
- data FoldlSym0 :: forall b6989586621680486636 a6989586621680486637 t6989586621680486628. (~>) ((~>) b6989586621680486636 ((~>) a6989586621680486637 b6989586621680486636)) ((~>) b6989586621680486636 ((~>) (t6989586621680486628 a6989586621680486637) b6989586621680486636))
- data FoldlSym1 (arg6989586621680487265 :: (~>) b6989586621680486636 ((~>) a6989586621680486637 b6989586621680486636)) :: forall t6989586621680486628. (~>) b6989586621680486636 ((~>) (t6989586621680486628 a6989586621680486637) b6989586621680486636)
- data FoldlSym2 (arg6989586621680487265 :: (~>) b6989586621680486636 ((~>) a6989586621680486637 b6989586621680486636)) (arg6989586621680487266 :: b6989586621680486636) :: forall t6989586621680486628. (~>) (t6989586621680486628 a6989586621680486637) b6989586621680486636
- type FoldlSym3 (arg6989586621680487265 :: (~>) b6989586621680486636 ((~>) a6989586621680486637 b6989586621680486636)) (arg6989586621680487266 :: b6989586621680486636) (arg6989586621680487267 :: t6989586621680486628 a6989586621680486637) = Foldl arg6989586621680487265 arg6989586621680487266 arg6989586621680487267
- data Foldl'Sym0 :: forall b6989586621680486638 a6989586621680486639 t6989586621680486628. (~>) ((~>) b6989586621680486638 ((~>) a6989586621680486639 b6989586621680486638)) ((~>) b6989586621680486638 ((~>) (t6989586621680486628 a6989586621680486639) b6989586621680486638))
- data Foldl'Sym1 (arg6989586621680487271 :: (~>) b6989586621680486638 ((~>) a6989586621680486639 b6989586621680486638)) :: forall t6989586621680486628. (~>) b6989586621680486638 ((~>) (t6989586621680486628 a6989586621680486639) b6989586621680486638)
- data Foldl'Sym2 (arg6989586621680487271 :: (~>) b6989586621680486638 ((~>) a6989586621680486639 b6989586621680486638)) (arg6989586621680487272 :: b6989586621680486638) :: forall t6989586621680486628. (~>) (t6989586621680486628 a6989586621680486639) b6989586621680486638
- type Foldl'Sym3 (arg6989586621680487271 :: (~>) b6989586621680486638 ((~>) a6989586621680486639 b6989586621680486638)) (arg6989586621680487272 :: b6989586621680486638) (arg6989586621680487273 :: t6989586621680486628 a6989586621680486639) = Foldl' arg6989586621680487271 arg6989586621680487272 arg6989586621680487273
- data Foldl1Sym0 :: forall a6989586621680486641 t6989586621680486628. (~>) ((~>) a6989586621680486641 ((~>) a6989586621680486641 a6989586621680486641)) ((~>) (t6989586621680486628 a6989586621680486641) a6989586621680486641)
- data Foldl1Sym1 (arg6989586621680487281 :: (~>) a6989586621680486641 ((~>) a6989586621680486641 a6989586621680486641)) :: forall t6989586621680486628. (~>) (t6989586621680486628 a6989586621680486641) a6989586621680486641
- type Foldl1Sym2 (arg6989586621680487281 :: (~>) a6989586621680486641 ((~>) a6989586621680486641 a6989586621680486641)) (arg6989586621680487282 :: t6989586621680486628 a6989586621680486641) = Foldl1 arg6989586621680487281 arg6989586621680487282
- data Foldl1'Sym0 :: forall a6989586621679970294. (~>) ((~>) a6989586621679970294 ((~>) a6989586621679970294 a6989586621679970294)) ((~>) [a6989586621679970294] a6989586621679970294)
- data Foldl1'Sym1 (a6989586621679975443 :: (~>) a6989586621679970294 ((~>) a6989586621679970294 a6989586621679970294)) :: (~>) [a6989586621679970294] a6989586621679970294
- type Foldl1'Sym2 (a6989586621679975443 :: (~>) a6989586621679970294 ((~>) a6989586621679970294 a6989586621679970294)) (a6989586621679975444 :: [a6989586621679970294]) = Foldl1' a6989586621679975443 a6989586621679975444
- data FoldrSym0 :: forall a6989586621680486632 b6989586621680486633 t6989586621680486628. (~>) ((~>) a6989586621680486632 ((~>) b6989586621680486633 b6989586621680486633)) ((~>) b6989586621680486633 ((~>) (t6989586621680486628 a6989586621680486632) b6989586621680486633))
- data FoldrSym1 (arg6989586621680487253 :: (~>) a6989586621680486632 ((~>) b6989586621680486633 b6989586621680486633)) :: forall t6989586621680486628. (~>) b6989586621680486633 ((~>) (t6989586621680486628 a6989586621680486632) b6989586621680486633)
- data FoldrSym2 (arg6989586621680487253 :: (~>) a6989586621680486632 ((~>) b6989586621680486633 b6989586621680486633)) (arg6989586621680487254 :: b6989586621680486633) :: forall t6989586621680486628. (~>) (t6989586621680486628 a6989586621680486632) b6989586621680486633
- type FoldrSym3 (arg6989586621680487253 :: (~>) a6989586621680486632 ((~>) b6989586621680486633 b6989586621680486633)) (arg6989586621680487254 :: b6989586621680486633) (arg6989586621680487255 :: t6989586621680486628 a6989586621680486632) = Foldr arg6989586621680487253 arg6989586621680487254 arg6989586621680487255
- data Foldr1Sym0 :: forall a6989586621680486640 t6989586621680486628. (~>) ((~>) a6989586621680486640 ((~>) a6989586621680486640 a6989586621680486640)) ((~>) (t6989586621680486628 a6989586621680486640) a6989586621680486640)
- data Foldr1Sym1 (arg6989586621680487277 :: (~>) a6989586621680486640 ((~>) a6989586621680486640 a6989586621680486640)) :: forall t6989586621680486628. (~>) (t6989586621680486628 a6989586621680486640) a6989586621680486640
- type Foldr1Sym2 (arg6989586621680487277 :: (~>) a6989586621680486640 ((~>) a6989586621680486640 a6989586621680486640)) (arg6989586621680487278 :: t6989586621680486628 a6989586621680486640) = Foldr1 arg6989586621680487277 arg6989586621680487278
- data ConcatSym0 :: forall t6989586621680486553 a6989586621680486554. (~>) (t6989586621680486553 [a6989586621680486554]) [a6989586621680486554]
- type ConcatSym1 (a6989586621680487135 :: t6989586621680486553 [a6989586621680486554]) = Concat a6989586621680487135
- data ConcatMapSym0 :: forall a6989586621680486551 b6989586621680486552 t6989586621680486550. (~>) ((~>) a6989586621680486551 [b6989586621680486552]) ((~>) (t6989586621680486550 a6989586621680486551) [b6989586621680486552])
- data ConcatMapSym1 (a6989586621680487119 :: (~>) a6989586621680486551 [b6989586621680486552]) :: forall t6989586621680486550. (~>) (t6989586621680486550 a6989586621680486551) [b6989586621680486552]
- type ConcatMapSym2 (a6989586621680487119 :: (~>) a6989586621680486551 [b6989586621680486552]) (a6989586621680487120 :: t6989586621680486550 a6989586621680486551) = ConcatMap a6989586621680487119 a6989586621680487120
- data AndSym0 :: forall t6989586621680486549. (~>) (t6989586621680486549 Bool) Bool
- type AndSym1 (a6989586621680487110 :: t6989586621680486549 Bool) = And a6989586621680487110
- data OrSym0 :: forall t6989586621680486548. (~>) (t6989586621680486548 Bool) Bool
- type OrSym1 (a6989586621680487101 :: t6989586621680486548 Bool) = Or a6989586621680487101
- data AnySym0 :: forall a6989586621680486547 t6989586621680486546. (~>) ((~>) a6989586621680486547 Bool) ((~>) (t6989586621680486546 a6989586621680486547) Bool)
- data AnySym1 (a6989586621680487088 :: (~>) a6989586621680486547 Bool) :: forall t6989586621680486546. (~>) (t6989586621680486546 a6989586621680486547) Bool
- type AnySym2 (a6989586621680487088 :: (~>) a6989586621680486547 Bool) (a6989586621680487089 :: t6989586621680486546 a6989586621680486547) = Any a6989586621680487088 a6989586621680487089
- data AllSym0 :: forall a6989586621680486545 t6989586621680486544. (~>) ((~>) a6989586621680486545 Bool) ((~>) (t6989586621680486544 a6989586621680486545) Bool)
- data AllSym1 (a6989586621680487075 :: (~>) a6989586621680486545 Bool) :: forall t6989586621680486544. (~>) (t6989586621680486544 a6989586621680486545) Bool
- type AllSym2 (a6989586621680487075 :: (~>) a6989586621680486545 Bool) (a6989586621680487076 :: t6989586621680486544 a6989586621680486545) = All a6989586621680487075 a6989586621680487076
- data SumSym0 :: forall t6989586621680486628 a6989586621680486648. (~>) (t6989586621680486628 a6989586621680486648) a6989586621680486648
- type SumSym1 (arg6989586621680487299 :: t6989586621680486628 a6989586621680486648) = Sum arg6989586621680487299
- data ProductSym0 :: forall t6989586621680486628 a6989586621680486649. (~>) (t6989586621680486628 a6989586621680486649) a6989586621680486649
- type ProductSym1 (arg6989586621680487301 :: t6989586621680486628 a6989586621680486649) = Product arg6989586621680487301
- data MaximumSym0 :: forall t6989586621680486628 a6989586621680486646. (~>) (t6989586621680486628 a6989586621680486646) a6989586621680486646
- type MaximumSym1 (arg6989586621680487295 :: t6989586621680486628 a6989586621680486646) = Maximum arg6989586621680487295
- data MinimumSym0 :: forall t6989586621680486628 a6989586621680486647. (~>) (t6989586621680486628 a6989586621680486647) a6989586621680486647
- type MinimumSym1 (arg6989586621680487297 :: t6989586621680486628 a6989586621680486647) = Minimum arg6989586621680487297
- data ScanlSym0 :: forall b6989586621679970286 a6989586621679970287. (~>) ((~>) b6989586621679970286 ((~>) a6989586621679970287 b6989586621679970286)) ((~>) b6989586621679970286 ((~>) [a6989586621679970287] [b6989586621679970286]))
- data ScanlSym1 (a6989586621679975380 :: (~>) b6989586621679970286 ((~>) a6989586621679970287 b6989586621679970286)) :: (~>) b6989586621679970286 ((~>) [a6989586621679970287] [b6989586621679970286])
- data ScanlSym2 (a6989586621679975380 :: (~>) b6989586621679970286 ((~>) a6989586621679970287 b6989586621679970286)) (a6989586621679975381 :: b6989586621679970286) :: (~>) [a6989586621679970287] [b6989586621679970286]
- type ScanlSym3 (a6989586621679975380 :: (~>) b6989586621679970286 ((~>) a6989586621679970287 b6989586621679970286)) (a6989586621679975381 :: b6989586621679970286) (a6989586621679975382 :: [a6989586621679970287]) = Scanl a6989586621679975380 a6989586621679975381 a6989586621679975382
- data Scanl1Sym0 :: forall a6989586621679970285. (~>) ((~>) a6989586621679970285 ((~>) a6989586621679970285 a6989586621679970285)) ((~>) [a6989586621679970285] [a6989586621679970285])
- data Scanl1Sym1 (a6989586621679975373 :: (~>) a6989586621679970285 ((~>) a6989586621679970285 a6989586621679970285)) :: (~>) [a6989586621679970285] [a6989586621679970285]
- type Scanl1Sym2 (a6989586621679975373 :: (~>) a6989586621679970285 ((~>) a6989586621679970285 a6989586621679970285)) (a6989586621679975374 :: [a6989586621679970285]) = Scanl1 a6989586621679975373 a6989586621679975374
- data ScanrSym0 :: forall a6989586621679970283 b6989586621679970284. (~>) ((~>) a6989586621679970283 ((~>) b6989586621679970284 b6989586621679970284)) ((~>) b6989586621679970284 ((~>) [a6989586621679970283] [b6989586621679970284]))
- data ScanrSym1 (a6989586621679975352 :: (~>) a6989586621679970283 ((~>) b6989586621679970284 b6989586621679970284)) :: (~>) b6989586621679970284 ((~>) [a6989586621679970283] [b6989586621679970284])
- data ScanrSym2 (a6989586621679975352 :: (~>) a6989586621679970283 ((~>) b6989586621679970284 b6989586621679970284)) (a6989586621679975353 :: b6989586621679970284) :: (~>) [a6989586621679970283] [b6989586621679970284]
- type ScanrSym3 (a6989586621679975352 :: (~>) a6989586621679970283 ((~>) b6989586621679970284 b6989586621679970284)) (a6989586621679975353 :: b6989586621679970284) (a6989586621679975354 :: [a6989586621679970283]) = Scanr a6989586621679975352 a6989586621679975353 a6989586621679975354
- data Scanr1Sym0 :: forall a6989586621679970282. (~>) ((~>) a6989586621679970282 ((~>) a6989586621679970282 a6989586621679970282)) ((~>) [a6989586621679970282] [a6989586621679970282])
- data Scanr1Sym1 (a6989586621679975328 :: (~>) a6989586621679970282 ((~>) a6989586621679970282 a6989586621679970282)) :: (~>) [a6989586621679970282] [a6989586621679970282]
- type Scanr1Sym2 (a6989586621679975328 :: (~>) a6989586621679970282 ((~>) a6989586621679970282 a6989586621679970282)) (a6989586621679975329 :: [a6989586621679970282]) = Scanr1 a6989586621679975328 a6989586621679975329
- data MapAccumLSym0 :: forall a6989586621680800353 b6989586621680800354 c6989586621680800355 t6989586621680800352. (~>) ((~>) a6989586621680800353 ((~>) b6989586621680800354 (a6989586621680800353, c6989586621680800355))) ((~>) a6989586621680800353 ((~>) (t6989586621680800352 b6989586621680800354) (a6989586621680800353, t6989586621680800352 c6989586621680800355)))
- data MapAccumLSym1 (a6989586621680800856 :: (~>) a6989586621680800353 ((~>) b6989586621680800354 (a6989586621680800353, c6989586621680800355))) :: forall t6989586621680800352. (~>) a6989586621680800353 ((~>) (t6989586621680800352 b6989586621680800354) (a6989586621680800353, t6989586621680800352 c6989586621680800355))
- data MapAccumLSym2 (a6989586621680800856 :: (~>) a6989586621680800353 ((~>) b6989586621680800354 (a6989586621680800353, c6989586621680800355))) (a6989586621680800857 :: a6989586621680800353) :: forall t6989586621680800352. (~>) (t6989586621680800352 b6989586621680800354) (a6989586621680800353, t6989586621680800352 c6989586621680800355)
- type MapAccumLSym3 (a6989586621680800856 :: (~>) a6989586621680800353 ((~>) b6989586621680800354 (a6989586621680800353, c6989586621680800355))) (a6989586621680800857 :: a6989586621680800353) (a6989586621680800858 :: t6989586621680800352 b6989586621680800354) = MapAccumL a6989586621680800856 a6989586621680800857 a6989586621680800858
- data MapAccumRSym0 :: forall a6989586621680800349 b6989586621680800350 c6989586621680800351 t6989586621680800348. (~>) ((~>) a6989586621680800349 ((~>) b6989586621680800350 (a6989586621680800349, c6989586621680800351))) ((~>) a6989586621680800349 ((~>) (t6989586621680800348 b6989586621680800350) (a6989586621680800349, t6989586621680800348 c6989586621680800351)))
- data MapAccumRSym1 (a6989586621680800839 :: (~>) a6989586621680800349 ((~>) b6989586621680800350 (a6989586621680800349, c6989586621680800351))) :: forall t6989586621680800348. (~>) a6989586621680800349 ((~>) (t6989586621680800348 b6989586621680800350) (a6989586621680800349, t6989586621680800348 c6989586621680800351))
- data MapAccumRSym2 (a6989586621680800839 :: (~>) a6989586621680800349 ((~>) b6989586621680800350 (a6989586621680800349, c6989586621680800351))) (a6989586621680800840 :: a6989586621680800349) :: forall t6989586621680800348. (~>) (t6989586621680800348 b6989586621680800350) (a6989586621680800349, t6989586621680800348 c6989586621680800351)
- type MapAccumRSym3 (a6989586621680800839 :: (~>) a6989586621680800349 ((~>) b6989586621680800350 (a6989586621680800349, c6989586621680800351))) (a6989586621680800840 :: a6989586621680800349) (a6989586621680800841 :: t6989586621680800348 b6989586621680800350) = MapAccumR a6989586621680800839 a6989586621680800840 a6989586621680800841
- data ReplicateSym0 :: forall a6989586621679970190. (~>) Nat ((~>) a6989586621679970190 [a6989586621679970190])
- data ReplicateSym1 (a6989586621679974355 :: Nat) :: forall a6989586621679970190. (~>) a6989586621679970190 [a6989586621679970190]
- type ReplicateSym2 (a6989586621679974355 :: Nat) (a6989586621679974356 :: a6989586621679970190) = Replicate a6989586621679974355 a6989586621679974356
- data UnfoldrSym0 :: forall b6989586621679970274 a6989586621679970275. (~>) ((~>) b6989586621679970274 (Maybe (a6989586621679970275, b6989586621679970274))) ((~>) b6989586621679970274 [a6989586621679970275])
- data UnfoldrSym1 (a6989586621679975186 :: (~>) b6989586621679970274 (Maybe (a6989586621679970275, b6989586621679970274))) :: (~>) b6989586621679970274 [a6989586621679970275]
- type UnfoldrSym2 (a6989586621679975186 :: (~>) b6989586621679970274 (Maybe (a6989586621679970275, b6989586621679970274))) (a6989586621679975187 :: b6989586621679970274) = Unfoldr a6989586621679975186 a6989586621679975187
- data TakeSym0 :: forall a6989586621679970206. (~>) Nat ((~>) [a6989586621679970206] [a6989586621679970206])
- data TakeSym1 (a6989586621679974516 :: Nat) :: forall a6989586621679970206. (~>) [a6989586621679970206] [a6989586621679970206]
- type TakeSym2 (a6989586621679974516 :: Nat) (a6989586621679974517 :: [a6989586621679970206]) = Take a6989586621679974516 a6989586621679974517
- data DropSym0 :: forall a6989586621679970205. (~>) Nat ((~>) [a6989586621679970205] [a6989586621679970205])
- data DropSym1 (a6989586621679974502 :: Nat) :: forall a6989586621679970205. (~>) [a6989586621679970205] [a6989586621679970205]
- type DropSym2 (a6989586621679974502 :: Nat) (a6989586621679974503 :: [a6989586621679970205]) = Drop a6989586621679974502 a6989586621679974503
- data SplitAtSym0 :: forall a6989586621679970204. (~>) Nat ((~>) [a6989586621679970204] ([a6989586621679970204], [a6989586621679970204]))
- data SplitAtSym1 (a6989586621679974496 :: Nat) :: forall a6989586621679970204. (~>) [a6989586621679970204] ([a6989586621679970204], [a6989586621679970204])
- type SplitAtSym2 (a6989586621679974496 :: Nat) (a6989586621679974497 :: [a6989586621679970204]) = SplitAt a6989586621679974496 a6989586621679974497
- data TakeWhileSym0 :: forall a6989586621679970211. (~>) ((~>) a6989586621679970211 Bool) ((~>) [a6989586621679970211] [a6989586621679970211])
- data TakeWhileSym1 (a6989586621679974660 :: (~>) a6989586621679970211 Bool) :: (~>) [a6989586621679970211] [a6989586621679970211]
- type TakeWhileSym2 (a6989586621679974660 :: (~>) a6989586621679970211 Bool) (a6989586621679974661 :: [a6989586621679970211]) = TakeWhile a6989586621679974660 a6989586621679974661
- data DropWhileSym0 :: forall a6989586621679970210. (~>) ((~>) a6989586621679970210 Bool) ((~>) [a6989586621679970210] [a6989586621679970210])
- data DropWhileSym1 (a6989586621679974642 :: (~>) a6989586621679970210 Bool) :: (~>) [a6989586621679970210] [a6989586621679970210]
- type DropWhileSym2 (a6989586621679974642 :: (~>) a6989586621679970210 Bool) (a6989586621679974643 :: [a6989586621679970210]) = DropWhile a6989586621679974642 a6989586621679974643
- data DropWhileEndSym0 :: forall a6989586621679970209. (~>) ((~>) a6989586621679970209 Bool) ((~>) [a6989586621679970209] [a6989586621679970209])
- data DropWhileEndSym1 (a6989586621679974616 :: (~>) a6989586621679970209 Bool) :: (~>) [a6989586621679970209] [a6989586621679970209]
- type DropWhileEndSym2 (a6989586621679974616 :: (~>) a6989586621679970209 Bool) (a6989586621679974617 :: [a6989586621679970209]) = DropWhileEnd a6989586621679974616 a6989586621679974617
- data SpanSym0 :: forall a6989586621679970208. (~>) ((~>) a6989586621679970208 Bool) ((~>) [a6989586621679970208] ([a6989586621679970208], [a6989586621679970208]))
- data SpanSym1 (a6989586621679974573 :: (~>) a6989586621679970208 Bool) :: (~>) [a6989586621679970208] ([a6989586621679970208], [a6989586621679970208])
- type SpanSym2 (a6989586621679974573 :: (~>) a6989586621679970208 Bool) (a6989586621679974574 :: [a6989586621679970208]) = Span a6989586621679974573 a6989586621679974574
- data BreakSym0 :: forall a6989586621679970207. (~>) ((~>) a6989586621679970207 Bool) ((~>) [a6989586621679970207] ([a6989586621679970207], [a6989586621679970207]))
- data BreakSym1 (a6989586621679974530 :: (~>) a6989586621679970207 Bool) :: (~>) [a6989586621679970207] ([a6989586621679970207], [a6989586621679970207])
- type BreakSym2 (a6989586621679974530 :: (~>) a6989586621679970207 Bool) (a6989586621679974531 :: [a6989586621679970207]) = Break a6989586621679974530 a6989586621679974531
- data StripPrefixSym0 :: forall a6989586621680092397. (~>) [a6989586621680092397] ((~>) [a6989586621680092397] (Maybe [a6989586621680092397]))
- data StripPrefixSym1 (a6989586621680094093 :: [a6989586621680092397]) :: (~>) [a6989586621680092397] (Maybe [a6989586621680092397])
- type StripPrefixSym2 (a6989586621680094093 :: [a6989586621680092397]) (a6989586621680094094 :: [a6989586621680092397]) = StripPrefix a6989586621680094093 a6989586621680094094
- data GroupSym0 :: forall a6989586621679970203. (~>) [a6989586621679970203] [[a6989586621679970203]]
- type GroupSym1 (a6989586621679974493 :: [a6989586621679970203]) = Group a6989586621679974493
- data InitsSym0 :: forall a6989586621679970273. (~>) [a6989586621679970273] [[a6989586621679970273]]
- type InitsSym1 (a6989586621679975178 :: [a6989586621679970273]) = Inits a6989586621679975178
- data TailsSym0 :: forall a6989586621679970272. (~>) [a6989586621679970272] [[a6989586621679970272]]
- type TailsSym1 (a6989586621679975171 :: [a6989586621679970272]) = Tails a6989586621679975171
- data IsPrefixOfSym0 :: forall a6989586621679970271. (~>) [a6989586621679970271] ((~>) [a6989586621679970271] Bool)
- data IsPrefixOfSym1 (a6989586621679975163 :: [a6989586621679970271]) :: (~>) [a6989586621679970271] Bool
- type IsPrefixOfSym2 (a6989586621679975163 :: [a6989586621679970271]) (a6989586621679975164 :: [a6989586621679970271]) = IsPrefixOf a6989586621679975163 a6989586621679975164
- data IsSuffixOfSym0 :: forall a6989586621679970270. (~>) [a6989586621679970270] ((~>) [a6989586621679970270] Bool)
- data IsSuffixOfSym1 (a6989586621679975157 :: [a6989586621679970270]) :: (~>) [a6989586621679970270] Bool
- type IsSuffixOfSym2 (a6989586621679975157 :: [a6989586621679970270]) (a6989586621679975158 :: [a6989586621679970270]) = IsSuffixOf a6989586621679975157 a6989586621679975158
- data IsInfixOfSym0 :: forall a6989586621679970269. (~>) [a6989586621679970269] ((~>) [a6989586621679970269] Bool)
- data IsInfixOfSym1 (a6989586621679975151 :: [a6989586621679970269]) :: (~>) [a6989586621679970269] Bool
- type IsInfixOfSym2 (a6989586621679975151 :: [a6989586621679970269]) (a6989586621679975152 :: [a6989586621679970269]) = IsInfixOf a6989586621679975151 a6989586621679975152
- data ElemSym0 :: forall a6989586621680486645 t6989586621680486628. (~>) a6989586621680486645 ((~>) (t6989586621680486628 a6989586621680486645) Bool)
- data ElemSym1 (arg6989586621680487291 :: a6989586621680486645) :: forall t6989586621680486628. (~>) (t6989586621680486628 a6989586621680486645) Bool
- type ElemSym2 (arg6989586621680487291 :: a6989586621680486645) (arg6989586621680487292 :: t6989586621680486628 a6989586621680486645) = Elem arg6989586621680487291 arg6989586621680487292
- data NotElemSym0 :: forall a6989586621680486539 t6989586621680486538. (~>) a6989586621680486539 ((~>) (t6989586621680486538 a6989586621680486539) Bool)
- data NotElemSym1 (a6989586621680487017 :: a6989586621680486539) :: forall t6989586621680486538. (~>) (t6989586621680486538 a6989586621680486539) Bool
- type NotElemSym2 (a6989586621680487017 :: a6989586621680486539) (a6989586621680487018 :: t6989586621680486538 a6989586621680486539) = NotElem a6989586621680487017 a6989586621680487018
- data LookupSym0 :: forall a6989586621679970196 b6989586621679970197. (~>) a6989586621679970196 ((~>) [(a6989586621679970196, b6989586621679970197)] (Maybe b6989586621679970197))
- data LookupSym1 (a6989586621679974420 :: a6989586621679970196) :: forall b6989586621679970197. (~>) [(a6989586621679970196, b6989586621679970197)] (Maybe b6989586621679970197)
- type LookupSym2 (a6989586621679974420 :: a6989586621679970196) (a6989586621679974421 :: [(a6989586621679970196, b6989586621679970197)]) = Lookup a6989586621679974420 a6989586621679974421
- data FindSym0 :: forall a6989586621680486537 t6989586621680486536. (~>) ((~>) a6989586621680486537 Bool) ((~>) (t6989586621680486536 a6989586621680486537) (Maybe a6989586621680486537))
- data FindSym1 (a6989586621680486990 :: (~>) a6989586621680486537 Bool) :: forall t6989586621680486536. (~>) (t6989586621680486536 a6989586621680486537) (Maybe a6989586621680486537)
- type FindSym2 (a6989586621680486990 :: (~>) a6989586621680486537 Bool) (a6989586621680486991 :: t6989586621680486536 a6989586621680486537) = Find a6989586621680486990 a6989586621680486991
- data FilterSym0 :: forall a6989586621679970219. (~>) ((~>) a6989586621679970219 Bool) ((~>) [a6989586621679970219] [a6989586621679970219])
- data FilterSym1 (a6989586621679974774 :: (~>) a6989586621679970219 Bool) :: (~>) [a6989586621679970219] [a6989586621679970219]
- type FilterSym2 (a6989586621679974774 :: (~>) a6989586621679970219 Bool) (a6989586621679974775 :: [a6989586621679970219]) = Filter a6989586621679974774 a6989586621679974775
- data PartitionSym0 :: forall a6989586621679970195. (~>) ((~>) a6989586621679970195 Bool) ((~>) [a6989586621679970195] ([a6989586621679970195], [a6989586621679970195]))
- data PartitionSym1 (a6989586621679974414 :: (~>) a6989586621679970195 Bool) :: (~>) [a6989586621679970195] ([a6989586621679970195], [a6989586621679970195])
- type PartitionSym2 (a6989586621679974414 :: (~>) a6989586621679970195 Bool) (a6989586621679974415 :: [a6989586621679970195]) = Partition a6989586621679974414 a6989586621679974415
- data (!!@#@$) :: forall a6989586621679970188. (~>) [a6989586621679970188] ((~>) Nat a6989586621679970188)
- data (!!@#@$$) (a6989586621679974335 :: [a6989586621679970188]) :: (~>) Nat a6989586621679970188
- type (!!@#@$$$) (a6989586621679974335 :: [a6989586621679970188]) (a6989586621679974336 :: Nat) = (!!) a6989586621679974335 a6989586621679974336
- data ElemIndexSym0 :: forall a6989586621679970217. (~>) a6989586621679970217 ((~>) [a6989586621679970217] (Maybe Nat))
- data ElemIndexSym1 (a6989586621679974758 :: a6989586621679970217) :: (~>) [a6989586621679970217] (Maybe Nat)
- type ElemIndexSym2 (a6989586621679974758 :: a6989586621679970217) (a6989586621679974759 :: [a6989586621679970217]) = ElemIndex a6989586621679974758 a6989586621679974759
- data ElemIndicesSym0 :: forall a6989586621679970216. (~>) a6989586621679970216 ((~>) [a6989586621679970216] [Nat])
- data ElemIndicesSym1 (a6989586621679974750 :: a6989586621679970216) :: (~>) [a6989586621679970216] [Nat]
- type ElemIndicesSym2 (a6989586621679974750 :: a6989586621679970216) (a6989586621679974751 :: [a6989586621679970216]) = ElemIndices a6989586621679974750 a6989586621679974751
- data FindIndexSym0 :: forall a6989586621679970215. (~>) ((~>) a6989586621679970215 Bool) ((~>) [a6989586621679970215] (Maybe Nat))
- data FindIndexSym1 (a6989586621679974742 :: (~>) a6989586621679970215 Bool) :: (~>) [a6989586621679970215] (Maybe Nat)
- type FindIndexSym2 (a6989586621679974742 :: (~>) a6989586621679970215 Bool) (a6989586621679974743 :: [a6989586621679970215]) = FindIndex a6989586621679974742 a6989586621679974743
- data FindIndicesSym0 :: forall a6989586621679970214. (~>) ((~>) a6989586621679970214 Bool) ((~>) [a6989586621679970214] [Nat])
- data FindIndicesSym1 (a6989586621679974716 :: (~>) a6989586621679970214 Bool) :: (~>) [a6989586621679970214] [Nat]
- type FindIndicesSym2 (a6989586621679974716 :: (~>) a6989586621679970214 Bool) (a6989586621679974717 :: [a6989586621679970214]) = FindIndices a6989586621679974716 a6989586621679974717
- data ZipSym0 :: forall a6989586621679970265 b6989586621679970266. (~>) [a6989586621679970265] ((~>) [b6989586621679970266] [(a6989586621679970265, b6989586621679970266)])
- data ZipSym1 (a6989586621679975129 :: [a6989586621679970265]) :: forall b6989586621679970266. (~>) [b6989586621679970266] [(a6989586621679970265, b6989586621679970266)]
- type ZipSym2 (a6989586621679975129 :: [a6989586621679970265]) (a6989586621679975130 :: [b6989586621679970266]) = Zip a6989586621679975129 a6989586621679975130
- data Zip3Sym0 :: forall a6989586621679970262 b6989586621679970263 c6989586621679970264. (~>) [a6989586621679970262] ((~>) [b6989586621679970263] ((~>) [c6989586621679970264] [(a6989586621679970262, b6989586621679970263, c6989586621679970264)]))
- data Zip3Sym1 (a6989586621679975117 :: [a6989586621679970262]) :: forall b6989586621679970263 c6989586621679970264. (~>) [b6989586621679970263] ((~>) [c6989586621679970264] [(a6989586621679970262, b6989586621679970263, c6989586621679970264)])
- data Zip3Sym2 (a6989586621679975117 :: [a6989586621679970262]) (a6989586621679975118 :: [b6989586621679970263]) :: forall c6989586621679970264. (~>) [c6989586621679970264] [(a6989586621679970262, b6989586621679970263, c6989586621679970264)]
- type Zip3Sym3 (a6989586621679975117 :: [a6989586621679970262]) (a6989586621679975118 :: [b6989586621679970263]) (a6989586621679975119 :: [c6989586621679970264]) = Zip3 a6989586621679975117 a6989586621679975118 a6989586621679975119
- data Zip4Sym0 :: forall a6989586621680092393 b6989586621680092394 c6989586621680092395 d6989586621680092396. (~>) [a6989586621680092393] ((~>) [b6989586621680092394] ((~>) [c6989586621680092395] ((~>) [d6989586621680092396] [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)])))
- data Zip4Sym1 (a6989586621680094081 :: [a6989586621680092393]) :: forall b6989586621680092394 c6989586621680092395 d6989586621680092396. (~>) [b6989586621680092394] ((~>) [c6989586621680092395] ((~>) [d6989586621680092396] [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)]))
- data Zip4Sym2 (a6989586621680094081 :: [a6989586621680092393]) (a6989586621680094082 :: [b6989586621680092394]) :: forall c6989586621680092395 d6989586621680092396. (~>) [c6989586621680092395] ((~>) [d6989586621680092396] [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)])
- data Zip4Sym3 (a6989586621680094081 :: [a6989586621680092393]) (a6989586621680094082 :: [b6989586621680092394]) (a6989586621680094083 :: [c6989586621680092395]) :: forall d6989586621680092396. (~>) [d6989586621680092396] [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)]
- type Zip4Sym4 (a6989586621680094081 :: [a6989586621680092393]) (a6989586621680094082 :: [b6989586621680092394]) (a6989586621680094083 :: [c6989586621680092395]) (a6989586621680094084 :: [d6989586621680092396]) = Zip4 a6989586621680094081 a6989586621680094082 a6989586621680094083 a6989586621680094084
- data Zip5Sym0 :: forall a6989586621680092388 b6989586621680092389 c6989586621680092390 d6989586621680092391 e6989586621680092392. (~>) [a6989586621680092388] ((~>) [b6989586621680092389] ((~>) [c6989586621680092390] ((~>) [d6989586621680092391] ((~>) [e6989586621680092392] [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]))))
- data Zip5Sym1 (a6989586621680094058 :: [a6989586621680092388]) :: forall b6989586621680092389 c6989586621680092390 d6989586621680092391 e6989586621680092392. (~>) [b6989586621680092389] ((~>) [c6989586621680092390] ((~>) [d6989586621680092391] ((~>) [e6989586621680092392] [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)])))
- data Zip5Sym2 (a6989586621680094058 :: [a6989586621680092388]) (a6989586621680094059 :: [b6989586621680092389]) :: forall c6989586621680092390 d6989586621680092391 e6989586621680092392. (~>) [c6989586621680092390] ((~>) [d6989586621680092391] ((~>) [e6989586621680092392] [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]))
- data Zip5Sym3 (a6989586621680094058 :: [a6989586621680092388]) (a6989586621680094059 :: [b6989586621680092389]) (a6989586621680094060 :: [c6989586621680092390]) :: forall d6989586621680092391 e6989586621680092392. (~>) [d6989586621680092391] ((~>) [e6989586621680092392] [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)])
- data Zip5Sym4 (a6989586621680094058 :: [a6989586621680092388]) (a6989586621680094059 :: [b6989586621680092389]) (a6989586621680094060 :: [c6989586621680092390]) (a6989586621680094061 :: [d6989586621680092391]) :: forall e6989586621680092392. (~>) [e6989586621680092392] [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]
- type Zip5Sym5 (a6989586621680094058 :: [a6989586621680092388]) (a6989586621680094059 :: [b6989586621680092389]) (a6989586621680094060 :: [c6989586621680092390]) (a6989586621680094061 :: [d6989586621680092391]) (a6989586621680094062 :: [e6989586621680092392]) = Zip5 a6989586621680094058 a6989586621680094059 a6989586621680094060 a6989586621680094061 a6989586621680094062
- data Zip6Sym0 :: forall a6989586621680092382 b6989586621680092383 c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387. (~>) [a6989586621680092382] ((~>) [b6989586621680092383] ((~>) [c6989586621680092384] ((~>) [d6989586621680092385] ((~>) [e6989586621680092386] ((~>) [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])))))
- data Zip6Sym1 (a6989586621680094030 :: [a6989586621680092382]) :: forall b6989586621680092383 c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387. (~>) [b6989586621680092383] ((~>) [c6989586621680092384] ((~>) [d6989586621680092385] ((~>) [e6989586621680092386] ((~>) [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]))))
- data Zip6Sym2 (a6989586621680094030 :: [a6989586621680092382]) (a6989586621680094031 :: [b6989586621680092383]) :: forall c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387. (~>) [c6989586621680092384] ((~>) [d6989586621680092385] ((~>) [e6989586621680092386] ((~>) [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])))
- data Zip6Sym3 (a6989586621680094030 :: [a6989586621680092382]) (a6989586621680094031 :: [b6989586621680092383]) (a6989586621680094032 :: [c6989586621680092384]) :: forall d6989586621680092385 e6989586621680092386 f6989586621680092387. (~>) [d6989586621680092385] ((~>) [e6989586621680092386] ((~>) [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]))
- data Zip6Sym4 (a6989586621680094030 :: [a6989586621680092382]) (a6989586621680094031 :: [b6989586621680092383]) (a6989586621680094032 :: [c6989586621680092384]) (a6989586621680094033 :: [d6989586621680092385]) :: forall e6989586621680092386 f6989586621680092387. (~>) [e6989586621680092386] ((~>) [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])
- data Zip6Sym5 (a6989586621680094030 :: [a6989586621680092382]) (a6989586621680094031 :: [b6989586621680092383]) (a6989586621680094032 :: [c6989586621680092384]) (a6989586621680094033 :: [d6989586621680092385]) (a6989586621680094034 :: [e6989586621680092386]) :: forall f6989586621680092387. (~>) [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]
- type Zip6Sym6 (a6989586621680094030 :: [a6989586621680092382]) (a6989586621680094031 :: [b6989586621680092383]) (a6989586621680094032 :: [c6989586621680092384]) (a6989586621680094033 :: [d6989586621680092385]) (a6989586621680094034 :: [e6989586621680092386]) (a6989586621680094035 :: [f6989586621680092387]) = Zip6 a6989586621680094030 a6989586621680094031 a6989586621680094032 a6989586621680094033 a6989586621680094034 a6989586621680094035
- data Zip7Sym0 :: forall a6989586621680092375 b6989586621680092376 c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381. (~>) [a6989586621680092375] ((~>) [b6989586621680092376] ((~>) [c6989586621680092377] ((~>) [d6989586621680092378] ((~>) [e6989586621680092379] ((~>) [f6989586621680092380] ((~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))))))
- data Zip7Sym1 (a6989586621680093997 :: [a6989586621680092375]) :: forall b6989586621680092376 c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381. (~>) [b6989586621680092376] ((~>) [c6989586621680092377] ((~>) [d6989586621680092378] ((~>) [e6989586621680092379] ((~>) [f6989586621680092380] ((~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])))))
- data Zip7Sym2 (a6989586621680093997 :: [a6989586621680092375]) (a6989586621680093998 :: [b6989586621680092376]) :: forall c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381. (~>) [c6989586621680092377] ((~>) [d6989586621680092378] ((~>) [e6989586621680092379] ((~>) [f6989586621680092380] ((~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))))
- data Zip7Sym3 (a6989586621680093997 :: [a6989586621680092375]) (a6989586621680093998 :: [b6989586621680092376]) (a6989586621680093999 :: [c6989586621680092377]) :: forall d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381. (~>) [d6989586621680092378] ((~>) [e6989586621680092379] ((~>) [f6989586621680092380] ((~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])))
- data Zip7Sym4 (a6989586621680093997 :: [a6989586621680092375]) (a6989586621680093998 :: [b6989586621680092376]) (a6989586621680093999 :: [c6989586621680092377]) (a6989586621680094000 :: [d6989586621680092378]) :: forall e6989586621680092379 f6989586621680092380 g6989586621680092381. (~>) [e6989586621680092379] ((~>) [f6989586621680092380] ((~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))
- data Zip7Sym5 (a6989586621680093997 :: [a6989586621680092375]) (a6989586621680093998 :: [b6989586621680092376]) (a6989586621680093999 :: [c6989586621680092377]) (a6989586621680094000 :: [d6989586621680092378]) (a6989586621680094001 :: [e6989586621680092379]) :: forall f6989586621680092380 g6989586621680092381. (~>) [f6989586621680092380] ((~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])
- data Zip7Sym6 (a6989586621680093997 :: [a6989586621680092375]) (a6989586621680093998 :: [b6989586621680092376]) (a6989586621680093999 :: [c6989586621680092377]) (a6989586621680094000 :: [d6989586621680092378]) (a6989586621680094001 :: [e6989586621680092379]) (a6989586621680094002 :: [f6989586621680092380]) :: forall g6989586621680092381. (~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]
- type Zip7Sym7 (a6989586621680093997 :: [a6989586621680092375]) (a6989586621680093998 :: [b6989586621680092376]) (a6989586621680093999 :: [c6989586621680092377]) (a6989586621680094000 :: [d6989586621680092378]) (a6989586621680094001 :: [e6989586621680092379]) (a6989586621680094002 :: [f6989586621680092380]) (a6989586621680094003 :: [g6989586621680092381]) = Zip7 a6989586621680093997 a6989586621680093998 a6989586621680093999 a6989586621680094000 a6989586621680094001 a6989586621680094002 a6989586621680094003
- data ZipWithSym0 :: forall a6989586621679970259 b6989586621679970260 c6989586621679970261. (~>) ((~>) a6989586621679970259 ((~>) b6989586621679970260 c6989586621679970261)) ((~>) [a6989586621679970259] ((~>) [b6989586621679970260] [c6989586621679970261]))
- data ZipWithSym1 (a6989586621679975106 :: (~>) a6989586621679970259 ((~>) b6989586621679970260 c6989586621679970261)) :: (~>) [a6989586621679970259] ((~>) [b6989586621679970260] [c6989586621679970261])
- data ZipWithSym2 (a6989586621679975106 :: (~>) a6989586621679970259 ((~>) b6989586621679970260 c6989586621679970261)) (a6989586621679975107 :: [a6989586621679970259]) :: (~>) [b6989586621679970260] [c6989586621679970261]
- type ZipWithSym3 (a6989586621679975106 :: (~>) a6989586621679970259 ((~>) b6989586621679970260 c6989586621679970261)) (a6989586621679975107 :: [a6989586621679970259]) (a6989586621679975108 :: [b6989586621679970260]) = ZipWith a6989586621679975106 a6989586621679975107 a6989586621679975108
- data ZipWith3Sym0 :: forall a6989586621679970255 b6989586621679970256 c6989586621679970257 d6989586621679970258. (~>) ((~>) a6989586621679970255 ((~>) b6989586621679970256 ((~>) c6989586621679970257 d6989586621679970258))) ((~>) [a6989586621679970255] ((~>) [b6989586621679970256] ((~>) [c6989586621679970257] [d6989586621679970258])))
- data ZipWith3Sym1 (a6989586621679975091 :: (~>) a6989586621679970255 ((~>) b6989586621679970256 ((~>) c6989586621679970257 d6989586621679970258))) :: (~>) [a6989586621679970255] ((~>) [b6989586621679970256] ((~>) [c6989586621679970257] [d6989586621679970258]))
- data ZipWith3Sym2 (a6989586621679975091 :: (~>) a6989586621679970255 ((~>) b6989586621679970256 ((~>) c6989586621679970257 d6989586621679970258))) (a6989586621679975092 :: [a6989586621679970255]) :: (~>) [b6989586621679970256] ((~>) [c6989586621679970257] [d6989586621679970258])
- data ZipWith3Sym3 (a6989586621679975091 :: (~>) a6989586621679970255 ((~>) b6989586621679970256 ((~>) c6989586621679970257 d6989586621679970258))) (a6989586621679975092 :: [a6989586621679970255]) (a6989586621679975093 :: [b6989586621679970256]) :: (~>) [c6989586621679970257] [d6989586621679970258]
- type ZipWith3Sym4 (a6989586621679975091 :: (~>) a6989586621679970255 ((~>) b6989586621679970256 ((~>) c6989586621679970257 d6989586621679970258))) (a6989586621679975092 :: [a6989586621679970255]) (a6989586621679975093 :: [b6989586621679970256]) (a6989586621679975094 :: [c6989586621679970257]) = ZipWith3 a6989586621679975091 a6989586621679975092 a6989586621679975093 a6989586621679975094
- data ZipWith4Sym0 :: forall a6989586621680092370 b6989586621680092371 c6989586621680092372 d6989586621680092373 e6989586621680092374. (~>) ((~>) a6989586621680092370 ((~>) b6989586621680092371 ((~>) c6989586621680092372 ((~>) d6989586621680092373 e6989586621680092374)))) ((~>) [a6989586621680092370] ((~>) [b6989586621680092371] ((~>) [c6989586621680092372] ((~>) [d6989586621680092373] [e6989586621680092374]))))
- data ZipWith4Sym1 (a6989586621680093964 :: (~>) a6989586621680092370 ((~>) b6989586621680092371 ((~>) c6989586621680092372 ((~>) d6989586621680092373 e6989586621680092374)))) :: (~>) [a6989586621680092370] ((~>) [b6989586621680092371] ((~>) [c6989586621680092372] ((~>) [d6989586621680092373] [e6989586621680092374])))
- data ZipWith4Sym2 (a6989586621680093964 :: (~>) a6989586621680092370 ((~>) b6989586621680092371 ((~>) c6989586621680092372 ((~>) d6989586621680092373 e6989586621680092374)))) (a6989586621680093965 :: [a6989586621680092370]) :: (~>) [b6989586621680092371] ((~>) [c6989586621680092372] ((~>) [d6989586621680092373] [e6989586621680092374]))
- data ZipWith4Sym3 (a6989586621680093964 :: (~>) a6989586621680092370 ((~>) b6989586621680092371 ((~>) c6989586621680092372 ((~>) d6989586621680092373 e6989586621680092374)))) (a6989586621680093965 :: [a6989586621680092370]) (a6989586621680093966 :: [b6989586621680092371]) :: (~>) [c6989586621680092372] ((~>) [d6989586621680092373] [e6989586621680092374])
- data ZipWith4Sym4 (a6989586621680093964 :: (~>) a6989586621680092370 ((~>) b6989586621680092371 ((~>) c6989586621680092372 ((~>) d6989586621680092373 e6989586621680092374)))) (a6989586621680093965 :: [a6989586621680092370]) (a6989586621680093966 :: [b6989586621680092371]) (a6989586621680093967 :: [c6989586621680092372]) :: (~>) [d6989586621680092373] [e6989586621680092374]
- type ZipWith4Sym5 (a6989586621680093964 :: (~>) a6989586621680092370 ((~>) b6989586621680092371 ((~>) c6989586621680092372 ((~>) d6989586621680092373 e6989586621680092374)))) (a6989586621680093965 :: [a6989586621680092370]) (a6989586621680093966 :: [b6989586621680092371]) (a6989586621680093967 :: [c6989586621680092372]) (a6989586621680093968 :: [d6989586621680092373]) = ZipWith4 a6989586621680093964 a6989586621680093965 a6989586621680093966 a6989586621680093967 a6989586621680093968
- data ZipWith5Sym0 :: forall a6989586621680092364 b6989586621680092365 c6989586621680092366 d6989586621680092367 e6989586621680092368 f6989586621680092369. (~>) ((~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) ((~>) [a6989586621680092364] ((~>) [b6989586621680092365] ((~>) [c6989586621680092366] ((~>) [d6989586621680092367] ((~>) [e6989586621680092368] [f6989586621680092369])))))
- data ZipWith5Sym1 (a6989586621680093941 :: (~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) :: (~>) [a6989586621680092364] ((~>) [b6989586621680092365] ((~>) [c6989586621680092366] ((~>) [d6989586621680092367] ((~>) [e6989586621680092368] [f6989586621680092369]))))
- data ZipWith5Sym2 (a6989586621680093941 :: (~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) (a6989586621680093942 :: [a6989586621680092364]) :: (~>) [b6989586621680092365] ((~>) [c6989586621680092366] ((~>) [d6989586621680092367] ((~>) [e6989586621680092368] [f6989586621680092369])))
- data ZipWith5Sym3 (a6989586621680093941 :: (~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) (a6989586621680093942 :: [a6989586621680092364]) (a6989586621680093943 :: [b6989586621680092365]) :: (~>) [c6989586621680092366] ((~>) [d6989586621680092367] ((~>) [e6989586621680092368] [f6989586621680092369]))
- data ZipWith5Sym4 (a6989586621680093941 :: (~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) (a6989586621680093942 :: [a6989586621680092364]) (a6989586621680093943 :: [b6989586621680092365]) (a6989586621680093944 :: [c6989586621680092366]) :: (~>) [d6989586621680092367] ((~>) [e6989586621680092368] [f6989586621680092369])
- data ZipWith5Sym5 (a6989586621680093941 :: (~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) (a6989586621680093942 :: [a6989586621680092364]) (a6989586621680093943 :: [b6989586621680092365]) (a6989586621680093944 :: [c6989586621680092366]) (a6989586621680093945 :: [d6989586621680092367]) :: (~>) [e6989586621680092368] [f6989586621680092369]
- type ZipWith5Sym6 (a6989586621680093941 :: (~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) (a6989586621680093942 :: [a6989586621680092364]) (a6989586621680093943 :: [b6989586621680092365]) (a6989586621680093944 :: [c6989586621680092366]) (a6989586621680093945 :: [d6989586621680092367]) (a6989586621680093946 :: [e6989586621680092368]) = ZipWith5 a6989586621680093941 a6989586621680093942 a6989586621680093943 a6989586621680093944 a6989586621680093945 a6989586621680093946
- data ZipWith6Sym0 :: forall a6989586621680092357 b6989586621680092358 c6989586621680092359 d6989586621680092360 e6989586621680092361 f6989586621680092362 g6989586621680092363. (~>) ((~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) ((~>) [a6989586621680092357] ((~>) [b6989586621680092358] ((~>) [c6989586621680092359] ((~>) [d6989586621680092360] ((~>) [e6989586621680092361] ((~>) [f6989586621680092362] [g6989586621680092363]))))))
- data ZipWith6Sym1 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) :: (~>) [a6989586621680092357] ((~>) [b6989586621680092358] ((~>) [c6989586621680092359] ((~>) [d6989586621680092360] ((~>) [e6989586621680092361] ((~>) [f6989586621680092362] [g6989586621680092363])))))
- data ZipWith6Sym2 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) (a6989586621680093915 :: [a6989586621680092357]) :: (~>) [b6989586621680092358] ((~>) [c6989586621680092359] ((~>) [d6989586621680092360] ((~>) [e6989586621680092361] ((~>) [f6989586621680092362] [g6989586621680092363]))))
- data ZipWith6Sym3 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) (a6989586621680093915 :: [a6989586621680092357]) (a6989586621680093916 :: [b6989586621680092358]) :: (~>) [c6989586621680092359] ((~>) [d6989586621680092360] ((~>) [e6989586621680092361] ((~>) [f6989586621680092362] [g6989586621680092363])))
- data ZipWith6Sym4 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) (a6989586621680093915 :: [a6989586621680092357]) (a6989586621680093916 :: [b6989586621680092358]) (a6989586621680093917 :: [c6989586621680092359]) :: (~>) [d6989586621680092360] ((~>) [e6989586621680092361] ((~>) [f6989586621680092362] [g6989586621680092363]))
- data ZipWith6Sym5 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) (a6989586621680093915 :: [a6989586621680092357]) (a6989586621680093916 :: [b6989586621680092358]) (a6989586621680093917 :: [c6989586621680092359]) (a6989586621680093918 :: [d6989586621680092360]) :: (~>) [e6989586621680092361] ((~>) [f6989586621680092362] [g6989586621680092363])
- data ZipWith6Sym6 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) (a6989586621680093915 :: [a6989586621680092357]) (a6989586621680093916 :: [b6989586621680092358]) (a6989586621680093917 :: [c6989586621680092359]) (a6989586621680093918 :: [d6989586621680092360]) (a6989586621680093919 :: [e6989586621680092361]) :: (~>) [f6989586621680092362] [g6989586621680092363]
- type ZipWith6Sym7 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) (a6989586621680093915 :: [a6989586621680092357]) (a6989586621680093916 :: [b6989586621680092358]) (a6989586621680093917 :: [c6989586621680092359]) (a6989586621680093918 :: [d6989586621680092360]) (a6989586621680093919 :: [e6989586621680092361]) (a6989586621680093920 :: [f6989586621680092362]) = ZipWith6 a6989586621680093914 a6989586621680093915 a6989586621680093916 a6989586621680093917 a6989586621680093918 a6989586621680093919 a6989586621680093920
- data ZipWith7Sym0 :: forall a6989586621680092349 b6989586621680092350 c6989586621680092351 d6989586621680092352 e6989586621680092353 f6989586621680092354 g6989586621680092355 h6989586621680092356. (~>) ((~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) ((~>) [a6989586621680092349] ((~>) [b6989586621680092350] ((~>) [c6989586621680092351] ((~>) [d6989586621680092352] ((~>) [e6989586621680092353] ((~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356])))))))
- data ZipWith7Sym1 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) :: (~>) [a6989586621680092349] ((~>) [b6989586621680092350] ((~>) [c6989586621680092351] ((~>) [d6989586621680092352] ((~>) [e6989586621680092353] ((~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356]))))))
- data ZipWith7Sym2 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) :: (~>) [b6989586621680092350] ((~>) [c6989586621680092351] ((~>) [d6989586621680092352] ((~>) [e6989586621680092353] ((~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356])))))
- data ZipWith7Sym3 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) (a6989586621680093885 :: [b6989586621680092350]) :: (~>) [c6989586621680092351] ((~>) [d6989586621680092352] ((~>) [e6989586621680092353] ((~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356]))))
- data ZipWith7Sym4 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) (a6989586621680093885 :: [b6989586621680092350]) (a6989586621680093886 :: [c6989586621680092351]) :: (~>) [d6989586621680092352] ((~>) [e6989586621680092353] ((~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356])))
- data ZipWith7Sym5 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) (a6989586621680093885 :: [b6989586621680092350]) (a6989586621680093886 :: [c6989586621680092351]) (a6989586621680093887 :: [d6989586621680092352]) :: (~>) [e6989586621680092353] ((~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356]))
- data ZipWith7Sym6 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) (a6989586621680093885 :: [b6989586621680092350]) (a6989586621680093886 :: [c6989586621680092351]) (a6989586621680093887 :: [d6989586621680092352]) (a6989586621680093888 :: [e6989586621680092353]) :: (~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356])
- data ZipWith7Sym7 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) (a6989586621680093885 :: [b6989586621680092350]) (a6989586621680093886 :: [c6989586621680092351]) (a6989586621680093887 :: [d6989586621680092352]) (a6989586621680093888 :: [e6989586621680092353]) (a6989586621680093889 :: [f6989586621680092354]) :: (~>) [g6989586621680092355] [h6989586621680092356]
- type ZipWith7Sym8 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) (a6989586621680093885 :: [b6989586621680092350]) (a6989586621680093886 :: [c6989586621680092351]) (a6989586621680093887 :: [d6989586621680092352]) (a6989586621680093888 :: [e6989586621680092353]) (a6989586621680093889 :: [f6989586621680092354]) (a6989586621680093890 :: [g6989586621680092355]) = ZipWith7 a6989586621680093883 a6989586621680093884 a6989586621680093885 a6989586621680093886 a6989586621680093887 a6989586621680093888 a6989586621680093889 a6989586621680093890
- data UnzipSym0 :: forall a6989586621679970253 b6989586621679970254. (~>) [(a6989586621679970253, b6989586621679970254)] ([a6989586621679970253], [b6989586621679970254])
- type UnzipSym1 (a6989586621679975072 :: [(a6989586621679970253, b6989586621679970254)]) = Unzip a6989586621679975072
- data Unzip3Sym0 :: forall a6989586621679970250 b6989586621679970251 c6989586621679970252. (~>) [(a6989586621679970250, b6989586621679970251, c6989586621679970252)] ([a6989586621679970250], [b6989586621679970251], [c6989586621679970252])
- type Unzip3Sym1 (a6989586621679975051 :: [(a6989586621679970250, b6989586621679970251, c6989586621679970252)]) = Unzip3 a6989586621679975051
- data Unzip4Sym0 :: forall a6989586621679970246 b6989586621679970247 c6989586621679970248 d6989586621679970249. (~>) [(a6989586621679970246, b6989586621679970247, c6989586621679970248, d6989586621679970249)] ([a6989586621679970246], [b6989586621679970247], [c6989586621679970248], [d6989586621679970249])
- type Unzip4Sym1 (a6989586621679975028 :: [(a6989586621679970246, b6989586621679970247, c6989586621679970248, d6989586621679970249)]) = Unzip4 a6989586621679975028
- data Unzip5Sym0 :: forall a6989586621679970241 b6989586621679970242 c6989586621679970243 d6989586621679970244 e6989586621679970245. (~>) [(a6989586621679970241, b6989586621679970242, c6989586621679970243, d6989586621679970244, e6989586621679970245)] ([a6989586621679970241], [b6989586621679970242], [c6989586621679970243], [d6989586621679970244], [e6989586621679970245])
- type Unzip5Sym1 (a6989586621679975003 :: [(a6989586621679970241, b6989586621679970242, c6989586621679970243, d6989586621679970244, e6989586621679970245)]) = Unzip5 a6989586621679975003
- data Unzip6Sym0 :: forall a6989586621679970235 b6989586621679970236 c6989586621679970237 d6989586621679970238 e6989586621679970239 f6989586621679970240. (~>) [(a6989586621679970235, b6989586621679970236, c6989586621679970237, d6989586621679970238, e6989586621679970239, f6989586621679970240)] ([a6989586621679970235], [b6989586621679970236], [c6989586621679970237], [d6989586621679970238], [e6989586621679970239], [f6989586621679970240])
- type Unzip6Sym1 (a6989586621679974976 :: [(a6989586621679970235, b6989586621679970236, c6989586621679970237, d6989586621679970238, e6989586621679970239, f6989586621679970240)]) = Unzip6 a6989586621679974976
- data Unzip7Sym0 :: forall a6989586621679970228 b6989586621679970229 c6989586621679970230 d6989586621679970231 e6989586621679970232 f6989586621679970233 g6989586621679970234. (~>) [(a6989586621679970228, b6989586621679970229, c6989586621679970230, d6989586621679970231, e6989586621679970232, f6989586621679970233, g6989586621679970234)] ([a6989586621679970228], [b6989586621679970229], [c6989586621679970230], [d6989586621679970231], [e6989586621679970232], [f6989586621679970233], [g6989586621679970234])
- type Unzip7Sym1 (a6989586621679974947 :: [(a6989586621679970228, b6989586621679970229, c6989586621679970230, d6989586621679970231, e6989586621679970232, f6989586621679970233, g6989586621679970234)]) = Unzip7 a6989586621679974947
- data UnlinesSym0 :: (~>) [Symbol] Symbol
- type UnlinesSym1 (a6989586621679974943 :: [Symbol]) = Unlines a6989586621679974943
- data UnwordsSym0 :: (~>) [Symbol] Symbol
- type UnwordsSym1 (a6989586621679974932 :: [Symbol]) = Unwords a6989586621679974932
- data NubSym0 :: forall a6989586621679970187. (~>) [a6989586621679970187] [a6989586621679970187]
- type NubSym1 (a6989586621679974315 :: [a6989586621679970187]) = Nub a6989586621679974315
- data DeleteSym0 :: forall a6989586621679970227. (~>) a6989586621679970227 ((~>) [a6989586621679970227] [a6989586621679970227])
- data DeleteSym1 (a6989586621679974926 :: a6989586621679970227) :: (~>) [a6989586621679970227] [a6989586621679970227]
- type DeleteSym2 (a6989586621679974926 :: a6989586621679970227) (a6989586621679974927 :: [a6989586621679970227]) = Delete a6989586621679974926 a6989586621679974927
- data (\\@#@$) :: forall a6989586621679970226. (~>) [a6989586621679970226] ((~>) [a6989586621679970226] [a6989586621679970226])
- data (\\@#@$$) (a6989586621679974916 :: [a6989586621679970226]) :: (~>) [a6989586621679970226] [a6989586621679970226]
- type (\\@#@$$$) (a6989586621679974916 :: [a6989586621679970226]) (a6989586621679974917 :: [a6989586621679970226]) = (\\) a6989586621679974916 a6989586621679974917
- data UnionSym0 :: forall a6989586621679970183. (~>) [a6989586621679970183] ((~>) [a6989586621679970183] [a6989586621679970183])
- data UnionSym1 (a6989586621679974265 :: [a6989586621679970183]) :: (~>) [a6989586621679970183] [a6989586621679970183]
- type UnionSym2 (a6989586621679974265 :: [a6989586621679970183]) (a6989586621679974266 :: [a6989586621679970183]) = Union a6989586621679974265 a6989586621679974266
- data IntersectSym0 :: forall a6989586621679970213. (~>) [a6989586621679970213] ((~>) [a6989586621679970213] [a6989586621679970213])
- data IntersectSym1 (a6989586621679974710 :: [a6989586621679970213]) :: (~>) [a6989586621679970213] [a6989586621679970213]
- type IntersectSym2 (a6989586621679974710 :: [a6989586621679970213]) (a6989586621679974711 :: [a6989586621679970213]) = Intersect a6989586621679974710 a6989586621679974711
- data InsertSym0 :: forall a6989586621679970200. (~>) a6989586621679970200 ((~>) [a6989586621679970200] [a6989586621679970200])
- data InsertSym1 (a6989586621679974473 :: a6989586621679970200) :: (~>) [a6989586621679970200] [a6989586621679970200]
- type InsertSym2 (a6989586621679974473 :: a6989586621679970200) (a6989586621679974474 :: [a6989586621679970200]) = Insert a6989586621679974473 a6989586621679974474
- data SortSym0 :: forall a6989586621679970199. (~>) [a6989586621679970199] [a6989586621679970199]
- type SortSym1 (a6989586621679974470 :: [a6989586621679970199]) = Sort a6989586621679974470
- data NubBySym0 :: forall a6989586621679970186. (~>) ((~>) a6989586621679970186 ((~>) a6989586621679970186 Bool)) ((~>) [a6989586621679970186] [a6989586621679970186])
- data NubBySym1 (a6989586621679974290 :: (~>) a6989586621679970186 ((~>) a6989586621679970186 Bool)) :: (~>) [a6989586621679970186] [a6989586621679970186]
- type NubBySym2 (a6989586621679974290 :: (~>) a6989586621679970186 ((~>) a6989586621679970186 Bool)) (a6989586621679974291 :: [a6989586621679970186]) = NubBy a6989586621679974290 a6989586621679974291
- data DeleteBySym0 :: forall a6989586621679970225. (~>) ((~>) a6989586621679970225 ((~>) a6989586621679970225 Bool)) ((~>) a6989586621679970225 ((~>) [a6989586621679970225] [a6989586621679970225]))
- data DeleteBySym1 (a6989586621679974894 :: (~>) a6989586621679970225 ((~>) a6989586621679970225 Bool)) :: (~>) a6989586621679970225 ((~>) [a6989586621679970225] [a6989586621679970225])
- data DeleteBySym2 (a6989586621679974894 :: (~>) a6989586621679970225 ((~>) a6989586621679970225 Bool)) (a6989586621679974895 :: a6989586621679970225) :: (~>) [a6989586621679970225] [a6989586621679970225]
- type DeleteBySym3 (a6989586621679974894 :: (~>) a6989586621679970225 ((~>) a6989586621679970225 Bool)) (a6989586621679974895 :: a6989586621679970225) (a6989586621679974896 :: [a6989586621679970225]) = DeleteBy a6989586621679974894 a6989586621679974895 a6989586621679974896
- data DeleteFirstsBySym0 :: forall a6989586621679970224. (~>) ((~>) a6989586621679970224 ((~>) a6989586621679970224 Bool)) ((~>) [a6989586621679970224] ((~>) [a6989586621679970224] [a6989586621679970224]))
- data DeleteFirstsBySym1 (a6989586621679974881 :: (~>) a6989586621679970224 ((~>) a6989586621679970224 Bool)) :: (~>) [a6989586621679970224] ((~>) [a6989586621679970224] [a6989586621679970224])
- data DeleteFirstsBySym2 (a6989586621679974881 :: (~>) a6989586621679970224 ((~>) a6989586621679970224 Bool)) (a6989586621679974882 :: [a6989586621679970224]) :: (~>) [a6989586621679970224] [a6989586621679970224]
- type DeleteFirstsBySym3 (a6989586621679974881 :: (~>) a6989586621679970224 ((~>) a6989586621679970224 Bool)) (a6989586621679974882 :: [a6989586621679970224]) (a6989586621679974883 :: [a6989586621679970224]) = DeleteFirstsBy a6989586621679974881 a6989586621679974882 a6989586621679974883
- data UnionBySym0 :: forall a6989586621679970184. (~>) ((~>) a6989586621679970184 ((~>) a6989586621679970184 Bool)) ((~>) [a6989586621679970184] ((~>) [a6989586621679970184] [a6989586621679970184]))
- data UnionBySym1 (a6989586621679974271 :: (~>) a6989586621679970184 ((~>) a6989586621679970184 Bool)) :: (~>) [a6989586621679970184] ((~>) [a6989586621679970184] [a6989586621679970184])
- data UnionBySym2 (a6989586621679974271 :: (~>) a6989586621679970184 ((~>) a6989586621679970184 Bool)) (a6989586621679974272 :: [a6989586621679970184]) :: (~>) [a6989586621679970184] [a6989586621679970184]
- type UnionBySym3 (a6989586621679974271 :: (~>) a6989586621679970184 ((~>) a6989586621679970184 Bool)) (a6989586621679974272 :: [a6989586621679970184]) (a6989586621679974273 :: [a6989586621679970184]) = UnionBy a6989586621679974271 a6989586621679974272 a6989586621679974273
- data IntersectBySym0 :: forall a6989586621679970212. (~>) ((~>) a6989586621679970212 ((~>) a6989586621679970212 Bool)) ((~>) [a6989586621679970212] ((~>) [a6989586621679970212] [a6989586621679970212]))
- data IntersectBySym1 (a6989586621679974674 :: (~>) a6989586621679970212 ((~>) a6989586621679970212 Bool)) :: (~>) [a6989586621679970212] ((~>) [a6989586621679970212] [a6989586621679970212])
- data IntersectBySym2 (a6989586621679974674 :: (~>) a6989586621679970212 ((~>) a6989586621679970212 Bool)) (a6989586621679974675 :: [a6989586621679970212]) :: (~>) [a6989586621679970212] [a6989586621679970212]
- type IntersectBySym3 (a6989586621679974674 :: (~>) a6989586621679970212 ((~>) a6989586621679970212 Bool)) (a6989586621679974675 :: [a6989586621679970212]) (a6989586621679974676 :: [a6989586621679970212]) = IntersectBy a6989586621679974674 a6989586621679974675 a6989586621679974676
- data GroupBySym0 :: forall a6989586621679970198. (~>) ((~>) a6989586621679970198 ((~>) a6989586621679970198 Bool)) ((~>) [a6989586621679970198] [[a6989586621679970198]])
- data GroupBySym1 (a6989586621679974437 :: (~>) a6989586621679970198 ((~>) a6989586621679970198 Bool)) :: (~>) [a6989586621679970198] [[a6989586621679970198]]
- type GroupBySym2 (a6989586621679974437 :: (~>) a6989586621679970198 ((~>) a6989586621679970198 Bool)) (a6989586621679974438 :: [a6989586621679970198]) = GroupBy a6989586621679974437 a6989586621679974438
- data SortBySym0 :: forall a6989586621679970223. (~>) ((~>) a6989586621679970223 ((~>) a6989586621679970223 Ordering)) ((~>) [a6989586621679970223] [a6989586621679970223])
- data SortBySym1 (a6989586621679974873 :: (~>) a6989586621679970223 ((~>) a6989586621679970223 Ordering)) :: (~>) [a6989586621679970223] [a6989586621679970223]
- type SortBySym2 (a6989586621679974873 :: (~>) a6989586621679970223 ((~>) a6989586621679970223 Ordering)) (a6989586621679974874 :: [a6989586621679970223]) = SortBy a6989586621679974873 a6989586621679974874
- data InsertBySym0 :: forall a6989586621679970222. (~>) ((~>) a6989586621679970222 ((~>) a6989586621679970222 Ordering)) ((~>) a6989586621679970222 ((~>) [a6989586621679970222] [a6989586621679970222]))
- data InsertBySym1 (a6989586621679974849 :: (~>) a6989586621679970222 ((~>) a6989586621679970222 Ordering)) :: (~>) a6989586621679970222 ((~>) [a6989586621679970222] [a6989586621679970222])
- data InsertBySym2 (a6989586621679974849 :: (~>) a6989586621679970222 ((~>) a6989586621679970222 Ordering)) (a6989586621679974850 :: a6989586621679970222) :: (~>) [a6989586621679970222] [a6989586621679970222]
- type InsertBySym3 (a6989586621679974849 :: (~>) a6989586621679970222 ((~>) a6989586621679970222 Ordering)) (a6989586621679974850 :: a6989586621679970222) (a6989586621679974851 :: [a6989586621679970222]) = InsertBy a6989586621679974849 a6989586621679974850 a6989586621679974851
- data MaximumBySym0 :: forall a6989586621680486543 t6989586621680486542. (~>) ((~>) a6989586621680486543 ((~>) a6989586621680486543 Ordering)) ((~>) (t6989586621680486542 a6989586621680486543) a6989586621680486543)
- data MaximumBySym1 (a6989586621680487050 :: (~>) a6989586621680486543 ((~>) a6989586621680486543 Ordering)) :: forall t6989586621680486542. (~>) (t6989586621680486542 a6989586621680486543) a6989586621680486543
- type MaximumBySym2 (a6989586621680487050 :: (~>) a6989586621680486543 ((~>) a6989586621680486543 Ordering)) (a6989586621680487051 :: t6989586621680486542 a6989586621680486543) = MaximumBy a6989586621680487050 a6989586621680487051
- data MinimumBySym0 :: forall a6989586621680486541 t6989586621680486540. (~>) ((~>) a6989586621680486541 ((~>) a6989586621680486541 Ordering)) ((~>) (t6989586621680486540 a6989586621680486541) a6989586621680486541)
- data MinimumBySym1 (a6989586621680487025 :: (~>) a6989586621680486541 ((~>) a6989586621680486541 Ordering)) :: forall t6989586621680486540. (~>) (t6989586621680486540 a6989586621680486541) a6989586621680486541
- type MinimumBySym2 (a6989586621680487025 :: (~>) a6989586621680486541 ((~>) a6989586621680486541 Ordering)) (a6989586621680487026 :: t6989586621680486540 a6989586621680486541) = MinimumBy a6989586621680487025 a6989586621680487026
- data GenericLengthSym0 :: forall a6989586621679970182 i6989586621679970181. (~>) [a6989586621679970182] i6989586621679970181
- type GenericLengthSym1 (a6989586621679974258 :: [a6989586621679970182]) = GenericLength a6989586621679974258
- data GenericTakeSym0 :: forall i6989586621680092347 a6989586621680092348. (~>) i6989586621680092347 ((~>) [a6989586621680092348] [a6989586621680092348])
- data GenericTakeSym1 (a6989586621680093877 :: i6989586621680092347) :: forall a6989586621680092348. (~>) [a6989586621680092348] [a6989586621680092348]
- type GenericTakeSym2 (a6989586621680093877 :: i6989586621680092347) (a6989586621680093878 :: [a6989586621680092348]) = GenericTake a6989586621680093877 a6989586621680093878
- data GenericDropSym0 :: forall i6989586621680092345 a6989586621680092346. (~>) i6989586621680092345 ((~>) [a6989586621680092346] [a6989586621680092346])
- data GenericDropSym1 (a6989586621680093867 :: i6989586621680092345) :: forall a6989586621680092346. (~>) [a6989586621680092346] [a6989586621680092346]
- type GenericDropSym2 (a6989586621680093867 :: i6989586621680092345) (a6989586621680093868 :: [a6989586621680092346]) = GenericDrop a6989586621680093867 a6989586621680093868
- data GenericSplitAtSym0 :: forall i6989586621680092343 a6989586621680092344. (~>) i6989586621680092343 ((~>) [a6989586621680092344] ([a6989586621680092344], [a6989586621680092344]))
- data GenericSplitAtSym1 (a6989586621680093857 :: i6989586621680092343) :: forall a6989586621680092344. (~>) [a6989586621680092344] ([a6989586621680092344], [a6989586621680092344])
- type GenericSplitAtSym2 (a6989586621680093857 :: i6989586621680092343) (a6989586621680093858 :: [a6989586621680092344]) = GenericSplitAt a6989586621680093857 a6989586621680093858
- data GenericIndexSym0 :: forall a6989586621680092342 i6989586621680092341. (~>) [a6989586621680092342] ((~>) i6989586621680092341 a6989586621680092342)
- data GenericIndexSym1 (a6989586621680093847 :: [a6989586621680092342]) :: forall i6989586621680092341. (~>) i6989586621680092341 a6989586621680092342
- type GenericIndexSym2 (a6989586621680093847 :: [a6989586621680092342]) (a6989586621680093848 :: i6989586621680092341) = GenericIndex a6989586621680093847 a6989586621680093848
- data GenericReplicateSym0 :: forall i6989586621680092339 a6989586621680092340. (~>) i6989586621680092339 ((~>) a6989586621680092340 [a6989586621680092340])
- data GenericReplicateSym1 (a6989586621680093837 :: i6989586621680092339) :: forall a6989586621680092340. (~>) a6989586621680092340 [a6989586621680092340]
- type GenericReplicateSym2 (a6989586621680093837 :: i6989586621680092339) (a6989586621680093838 :: a6989586621680092340) = GenericReplicate a6989586621680093837 a6989586621680093838
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 :: [a6989586621680486643]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (a :: [a6989586621680486643]) | |
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 a6989586621680486643) Source # | |
Defined in Data.Singletons.Prelude.Identity type Null (a :: Identity a6989586621680486643) | |
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 a6989586621680486643) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (a :: Dual a6989586621680486643) | |
type Null (a :: Product a6989586621680486643) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (a :: Product a6989586621680486643) | |
type Null (a :: Sum a6989586621680486643) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (a :: Sum a6989586621680486643) | |
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 a6989586621680486643) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Null (a2 :: Either a1 a6989586621680486643) | |
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 :: [a6989586621680486644]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (a :: [a6989586621680486644]) | |
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 a6989586621680486644) Source # | |
Defined in Data.Singletons.Prelude.Identity type Length (a :: Identity a6989586621680486644) | |
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 a6989586621680486644) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (a :: Dual a6989586621680486644) | |
type Length (a :: Product a6989586621680486644) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (a :: Product a6989586621680486644) | |
type Length (a :: Sum a6989586621680486644) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (a :: Sum a6989586621680486644) | |
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 a6989586621680486644) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Length (a2 :: Either a1 a6989586621680486644) | |
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 ~> (a6989586621680486637 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680486637) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680486637 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680486637]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680486637 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680486637) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680486637 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680486637) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680486637 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680486637) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a1 :: k2 ~> (a6989586621680486637 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680486637) 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 ~> (a6989586621680486637 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680486637) 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 ~> (a6989586621680486639 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680486639]) 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 ~> (a6989586621680486639 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680486639) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680486639 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680486639) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (a1 :: k2 ~> (a6989586621680486639 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680486639) 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 ~> (a6989586621680486639 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680486639) 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 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680486632]) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Identity | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Min a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Max a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680486632) 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 :: a6989586621680486632 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Either a1 a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a6989586621680486632 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: (a1, a6989586621680486632)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a6989586621680486632 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Arg a1 a6989586621680486632) Source # | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Foldr (a1 :: a6989586621680486632 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Const m a6989586621680486632) 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_6989586621680487115 x (Let6989586621680487113Scrutinee_6989586621680486875Sym1 x) |
type family Or (a :: t Bool) :: Bool where ... Source #
Equations
Or x = Case_6989586621680487106 x (Let6989586621680487104Scrutinee_6989586621680486877Sym1 x) |
type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #
Equations
Any p x = Case_6989586621680487097 p x (Let6989586621680487094Scrutinee_6989586621680486879Sym2 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_6989586621680487084 p x (Let6989586621680487081Scrutinee_6989586621680486881Sym2 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_6989586621679970789 wild_6989586621679970791)) = Case_6989586621679975347 f x wild_6989586621679970789 wild_6989586621679970791 (Let6989586621679975342Scrutinee_6989586621679970783Sym4 f x wild_6989586621679970789 wild_6989586621679970791) |
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_6989586621680800869 f s t (Let6989586621680800865Scrutinee_6989586621680800436Sym3 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_6989586621680800852 f s t (Let6989586621680800848Scrutinee_6989586621680800440Sym3 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_6989586621679974364 n x (Let6989586621679974361Scrutinee_6989586621679970885Sym2 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_6989586621679975195 f b (Let6989586621679975192Scrutinee_6989586621679970793Sym2 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 Let6989586621679974577XsSym0) Let6989586621679974577XsSym0 | |
Span p ('(:) x xs') = Case_6989586621679974589 p x xs' (Let6989586621679974585Scrutinee_6989586621679970865Sym3 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 Let6989586621679974534XsSym0) Let6989586621679974534XsSym0 | |
Break p ('(:) x xs') = Case_6989586621679974546 p x xs' (Let6989586621679974542Scrutinee_6989586621679970867Sym3 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_6989586621680092465 arg_6989586621680092467 = Case_6989586621680094100 arg_6989586621680092465 arg_6989586621680092467 (Apply (Apply Tuple2Sym0 arg_6989586621680092465) arg_6989586621680092467) |
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_6989586621679974434 key x y xys (Let6989586621679974429Scrutinee_6989586621679970881Sym4 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_6989586621680487013 p y (Let6989586621680486996Scrutinee_6989586621680486887Sym2 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_6989586621679974754 = Apply (Apply FindIndicesSym0 (Apply (==@#@$) x)) a_6989586621679974754 |
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_6989586621679974746 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679974746 |
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_6989586621680094073 a_6989586621680094075 a_6989586621680094077 a_6989586621680094079 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621680094073) a_6989586621680094075) a_6989586621680094077) a_6989586621680094079 |
type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ... Source #
Equations
Zip5 a_6989586621680094048 a_6989586621680094050 a_6989586621680094052 a_6989586621680094054 a_6989586621680094056 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621680094048) a_6989586621680094050) a_6989586621680094052) a_6989586621680094054) a_6989586621680094056 |
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_6989586621680094018 a_6989586621680094020 a_6989586621680094022 a_6989586621680094024 a_6989586621680094026 a_6989586621680094028 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621680094018) a_6989586621680094020) a_6989586621680094022) a_6989586621680094024) a_6989586621680094026) a_6989586621680094028 |
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_6989586621680093983 a_6989586621680093985 a_6989586621680093987 a_6989586621680093989 a_6989586621680093991 a_6989586621680093993 a_6989586621680093995 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621680093983) a_6989586621680093985) a_6989586621680093987) a_6989586621680093989) a_6989586621680093991) a_6989586621680093993) a_6989586621680093995 |
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_6989586621679974468 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679974468 |
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_6989586621679974887 a_6989586621679974889 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679974887) a_6989586621679974889 |
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_6989586621679970851 wild_6989586621679970853) ('(:) wild_6989586621679970855 wild_6989586621679970857) = Apply (Apply (>>=@#@$) (Let6989586621679974685XsSym5 eq wild_6989586621679970851 wild_6989586621679970853 wild_6989586621679970855 wild_6989586621679970857)) (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679974696Sym0 eq) wild_6989586621679970851) wild_6989586621679970853) wild_6989586621679970855) wild_6989586621679970857) |
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_6989586621680487054 = Apply (Apply Foldl1Sym0 (Let6989586621680487058Max'Sym2 cmp a_6989586621680487054)) a_6989586621680487054 |
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_6989586621680487029 = Apply (Apply Foldl1Sym0 (Let6989586621680487033Min'Sym2 cmp a_6989586621680487029)) a_6989586621680487029 |
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_6989586621680093873 a_6989586621680093875 = Apply (Apply TakeSym0 a_6989586621680093873) a_6989586621680093875 |
type family GenericDrop (a :: i) (a :: [a]) :: [a] where ... Source #
Equations
GenericDrop a_6989586621680093863 a_6989586621680093865 = Apply (Apply DropSym0 a_6989586621680093863) a_6989586621680093865 |
type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ... Source #
Equations
GenericSplitAt a_6989586621680093853 a_6989586621680093855 = Apply (Apply SplitAtSym0 a_6989586621680093853) a_6989586621680093855 |
type family GenericIndex (a :: [a]) (a :: i) :: a where ... Source #
Equations
GenericIndex a_6989586621680093843 a_6989586621680093845 = Apply (Apply (!!@#@$) a_6989586621680093843) a_6989586621680093845 |
type family GenericReplicate (a :: i) (a :: a) :: [a] where ... Source #
Equations
GenericReplicate a_6989586621680093833 a_6989586621680093835 = Apply (Apply ReplicateSym0 a_6989586621680093833) a_6989586621680093835 |
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) (t6989586621679310927 :: a3530822107858468865) Source # | |
data (:@#@$$) (t6989586621679310927 :: a3530822107858468865 :: Type) :: (~>) [a3530822107858468865] [a3530822107858468865 :: Type] infixr 5 Source #
Instances
SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((:@#@$$) t6989586621679310927 :: TyFun [a3530822107858468865] [a3530822107858468865] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances Methods suppressUnusedWarnings :: () Source # | |
type Apply ((:@#@$$) t6989586621679310927 :: TyFun [a] [a] -> Type) (t6989586621679310928 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Instances |
type (:@#@$$$) (t6989586621679310927 :: a3530822107858468865) (t6989586621679310928 :: [a3530822107858468865]) = '(:) t6989586621679310927 t6989586621679310928 Source #
type (++@#@$$$) (a6989586621679541756 :: [a6989586621679541559]) (a6989586621679541757 :: [a6989586621679541559]) = (++) a6989586621679541756 a6989586621679541757 Source #
data (++@#@$$) (a6989586621679541756 :: [a6989586621679541559]) :: (~>) [a6989586621679541559] [a6989586621679541559] infixr 5 Source #
Instances
SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((++@#@$$) a6989586621679541756 :: TyFun [a6989586621679541559] [a6989586621679541559] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$$) a6989586621679541756 :: TyFun [a] [a] -> Type) (a6989586621679541757 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Base |
data (++@#@$) :: forall a6989586621679541559. (~>) [a6989586621679541559] ((~>) [a6989586621679541559] [a6989586621679541559]) infixr 5 Source #
Instances
SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679541559] ([a6989586621679541559] ~> [a6989586621679541559]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () Source # | |
type Apply ((++@#@$) :: TyFun [a6989586621679541559] ([a6989586621679541559] ~> [a6989586621679541559]) -> Type) (a6989586621679541756 :: [a6989586621679541559]) Source # | |
data HeadSym0 :: forall a6989586621679970309. (~>) [a6989586621679970309] a6989586621679970309 Source #
Instances
SingI (HeadSym0 :: TyFun [a] a -> Type) Source # | |
SuppressUnusedWarnings (HeadSym0 :: TyFun [a6989586621679970309] a6989586621679970309 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679975656 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data LastSym0 :: forall a6989586621679970308. (~>) [a6989586621679970308] a6989586621679970308 Source #
Instances
SingI (LastSym0 :: TyFun [a] a -> Type) Source # | |
SuppressUnusedWarnings (LastSym0 :: TyFun [a6989586621679970308] a6989586621679970308 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679975651 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data TailSym0 :: forall a6989586621679970307. (~>) [a6989586621679970307] [a6989586621679970307] Source #
Instances
SingI (TailSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (TailSym0 :: TyFun [a6989586621679970307] [a6989586621679970307] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679975648 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data InitSym0 :: forall a6989586621679970306. (~>) [a6989586621679970306] [a6989586621679970306] Source #
Instances
SingI (InitSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (InitSym0 :: TyFun [a6989586621679970306] [a6989586621679970306] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679975634 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data NullSym0 :: forall t6989586621680486628 a6989586621680486643. (~>) (t6989586621680486628 a6989586621680486643) Bool Source #
Instances
SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680486628 a6989586621680486643) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680487287 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type NullSym1 (arg6989586621680487287 :: t6989586621680486628 a6989586621680486643) = Null arg6989586621680487287 Source #
data LengthSym0 :: forall t6989586621680486628 a6989586621680486644. (~>) (t6989586621680486628 a6989586621680486644) 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 (t6989586621680486628 a6989586621680486644) Nat -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (arg6989586621680487289 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (arg6989586621680487289 :: t a) = Length arg6989586621680487289 |
type LengthSym1 (arg6989586621680487289 :: t6989586621680486628 a6989586621680486644) = Length arg6989586621680487289 Source #
data MapSym0 :: forall a6989586621679541560 b6989586621679541561. (~>) ((~>) a6989586621679541560 b6989586621679541561) ((~>) [a6989586621679541560] [b6989586621679541561]) Source #
Instances
SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (MapSym0 :: TyFun (a6989586621679541560 ~> b6989586621679541561) ([a6989586621679541560] ~> [b6989586621679541561]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapSym0 :: TyFun (a6989586621679541560 ~> b6989586621679541561) ([a6989586621679541560] ~> [b6989586621679541561]) -> Type) (a6989586621679541764 :: a6989586621679541560 ~> b6989586621679541561) Source # | |
data MapSym1 (a6989586621679541764 :: (~>) a6989586621679541560 b6989586621679541561) :: (~>) [a6989586621679541560] [b6989586621679541561] Source #
Instances
SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (MapSym1 a6989586621679541764 :: TyFun [a6989586621679541560] [b6989586621679541561] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapSym1 a6989586621679541764 :: TyFun [a] [b] -> Type) (a6989586621679541765 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Base |
type MapSym2 (a6989586621679541764 :: (~>) a6989586621679541560 b6989586621679541561) (a6989586621679541765 :: [a6989586621679541560]) = Map a6989586621679541764 a6989586621679541765 Source #
data ReverseSym0 :: forall a6989586621679970304. (~>) [a6989586621679970304] [a6989586621679970304] Source #
Instances
SingI (ReverseSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing ReverseSym0 Source # | |
SuppressUnusedWarnings (ReverseSym0 :: TyFun [a6989586621679970304] [a6989586621679970304] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679975619 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679975619 :: [a]) = Reverse a6989586621679975619 |
type ReverseSym1 (a6989586621679975619 :: [a6989586621679970304]) = Reverse a6989586621679975619 Source #
data IntersperseSym0 :: forall a6989586621679970303. (~>) a6989586621679970303 ((~>) [a6989586621679970303] [a6989586621679970303]) Source #
Instances
SingI (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679970303 ([a6989586621679970303] ~> [a6989586621679970303]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym0 :: TyFun a6989586621679970303 ([a6989586621679970303] ~> [a6989586621679970303]) -> Type) (a6989586621679975612 :: a6989586621679970303) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym0 :: TyFun a6989586621679970303 ([a6989586621679970303] ~> [a6989586621679970303]) -> Type) (a6989586621679975612 :: a6989586621679970303) = IntersperseSym1 a6989586621679975612 |
data IntersperseSym1 (a6989586621679975612 :: a6989586621679970303) :: (~>) [a6989586621679970303] [a6989586621679970303] 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 a6989586621679975612 :: TyFun [a6989586621679970303] [a6989586621679970303] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersperseSym1 a6989586621679975612 :: TyFun [a] [a] -> Type) (a6989586621679975613 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym1 a6989586621679975612 :: TyFun [a] [a] -> Type) (a6989586621679975613 :: [a]) = Intersperse a6989586621679975612 a6989586621679975613 |
type IntersperseSym2 (a6989586621679975612 :: a6989586621679970303) (a6989586621679975613 :: [a6989586621679970303]) = Intersperse a6989586621679975612 a6989586621679975613 Source #
data IntercalateSym0 :: forall a6989586621679970302. (~>) [a6989586621679970302] ((~>) [[a6989586621679970302]] [a6989586621679970302]) Source #
Instances
SingI (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a6989586621679970302] ([[a6989586621679970302]] ~> [a6989586621679970302]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym0 :: TyFun [a6989586621679970302] ([[a6989586621679970302]] ~> [a6989586621679970302]) -> Type) (a6989586621679975606 :: [a6989586621679970302]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym0 :: TyFun [a6989586621679970302] ([[a6989586621679970302]] ~> [a6989586621679970302]) -> Type) (a6989586621679975606 :: [a6989586621679970302]) = IntercalateSym1 a6989586621679975606 |
data IntercalateSym1 (a6989586621679975606 :: [a6989586621679970302]) :: (~>) [[a6989586621679970302]] [a6989586621679970302] 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 a6989586621679975606 :: TyFun [[a6989586621679970302]] [a6989586621679970302] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntercalateSym1 a6989586621679975606 :: TyFun [[a]] [a] -> Type) (a6989586621679975607 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym1 a6989586621679975606 :: TyFun [[a]] [a] -> Type) (a6989586621679975607 :: [[a]]) = Intercalate a6989586621679975606 a6989586621679975607 |
type IntercalateSym2 (a6989586621679975606 :: [a6989586621679970302]) (a6989586621679975607 :: [[a6989586621679970302]]) = Intercalate a6989586621679975606 a6989586621679975607 Source #
data TransposeSym0 :: forall a6989586621679970189. (~>) [[a6989586621679970189]] [[a6989586621679970189]] Source #
Instances
SingI (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing TransposeSym0 Source # | |
SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a6989586621679970189]] [[a6989586621679970189]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679974349 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679974349 :: [[a]]) = Transpose a6989586621679974349 |
type TransposeSym1 (a6989586621679974349 :: [[a6989586621679970189]]) = Transpose a6989586621679974349 Source #
data SubsequencesSym0 :: forall a6989586621679970301. (~>) [a6989586621679970301] [[a6989586621679970301]] Source #
Instances
SingI (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a6989586621679970301] [[a6989586621679970301]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679975603 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679975603 :: [a]) = Subsequences a6989586621679975603 |
type SubsequencesSym1 (a6989586621679975603 :: [a6989586621679970301]) = Subsequences a6989586621679975603 Source #
data PermutationsSym0 :: forall a6989586621679970298. (~>) [a6989586621679970298] [[a6989586621679970298]] Source #
Instances
SingI (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a6989586621679970298] [[a6989586621679970298]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679975485 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679975485 :: [a]) = Permutations a6989586621679975485 |
type PermutationsSym1 (a6989586621679975485 :: [a6989586621679970298]) = Permutations a6989586621679975485 Source #
data FoldlSym0 :: forall b6989586621680486636 a6989586621680486637 t6989586621680486628. (~>) ((~>) b6989586621680486636 ((~>) a6989586621680486637 b6989586621680486636)) ((~>) b6989586621680486636 ((~>) (t6989586621680486628 a6989586621680486637) b6989586621680486636)) Source #
Instances
SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym0 :: TyFun (b6989586621680486636 ~> (a6989586621680486637 ~> b6989586621680486636)) (b6989586621680486636 ~> (t6989586621680486628 a6989586621680486637 ~> b6989586621680486636)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym0 :: TyFun (b6989586621680486636 ~> (a6989586621680486637 ~> b6989586621680486636)) (b6989586621680486636 ~> (t6989586621680486628 a6989586621680486637 ~> b6989586621680486636)) -> Type) (arg6989586621680487265 :: b6989586621680486636 ~> (a6989586621680486637 ~> b6989586621680486636)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldlSym0 :: TyFun (b6989586621680486636 ~> (a6989586621680486637 ~> b6989586621680486636)) (b6989586621680486636 ~> (t6989586621680486628 a6989586621680486637 ~> b6989586621680486636)) -> Type) (arg6989586621680487265 :: b6989586621680486636 ~> (a6989586621680486637 ~> b6989586621680486636)) = FoldlSym1 arg6989586621680487265 t6989586621680486628 :: TyFun b6989586621680486636 (t6989586621680486628 a6989586621680486637 ~> b6989586621680486636) -> Type |
data FoldlSym1 (arg6989586621680487265 :: (~>) b6989586621680486636 ((~>) a6989586621680486637 b6989586621680486636)) :: forall t6989586621680486628. (~>) b6989586621680486636 ((~>) (t6989586621680486628 a6989586621680486637) b6989586621680486636) Source #
Instances
(SFoldable t, SingI d) => SingI (FoldlSym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym1 arg6989586621680487265 t6989586621680486628 :: TyFun b6989586621680486636 (t6989586621680486628 a6989586621680486637 ~> b6989586621680486636) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym1 arg6989586621680487265 t6989586621680486628 :: TyFun b6989586621680486636 (t6989586621680486628 a6989586621680486637 ~> b6989586621680486636) -> Type) (arg6989586621680487266 :: b6989586621680486636) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldlSym1 arg6989586621680487265 t6989586621680486628 :: TyFun b6989586621680486636 (t6989586621680486628 a6989586621680486637 ~> b6989586621680486636) -> Type) (arg6989586621680487266 :: b6989586621680486636) = FoldlSym2 arg6989586621680487265 arg6989586621680487266 t6989586621680486628 :: TyFun (t6989586621680486628 a6989586621680486637) b6989586621680486636 -> Type |
data FoldlSym2 (arg6989586621680487265 :: (~>) b6989586621680486636 ((~>) a6989586621680486637 b6989586621680486636)) (arg6989586621680487266 :: b6989586621680486636) :: forall t6989586621680486628. (~>) (t6989586621680486628 a6989586621680486637) b6989586621680486636 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # | |
SuppressUnusedWarnings (FoldlSym2 arg6989586621680487266 arg6989586621680487265 t6989586621680486628 :: TyFun (t6989586621680486628 a6989586621680486637) b6989586621680486636 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldlSym2 arg6989586621680487266 arg6989586621680487265 t :: TyFun (t a) b -> Type) (arg6989586621680487267 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type FoldlSym3 (arg6989586621680487265 :: (~>) b6989586621680486636 ((~>) a6989586621680486637 b6989586621680486636)) (arg6989586621680487266 :: b6989586621680486636) (arg6989586621680487267 :: t6989586621680486628 a6989586621680486637) = Foldl arg6989586621680487265 arg6989586621680487266 arg6989586621680487267 Source #
data Foldl'Sym0 :: forall b6989586621680486638 a6989586621680486639 t6989586621680486628. (~>) ((~>) b6989586621680486638 ((~>) a6989586621680486639 b6989586621680486638)) ((~>) b6989586621680486638 ((~>) (t6989586621680486628 a6989586621680486639) b6989586621680486638)) 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 (b6989586621680486638 ~> (a6989586621680486639 ~> b6989586621680486638)) (b6989586621680486638 ~> (t6989586621680486628 a6989586621680486639 ~> b6989586621680486638)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym0 :: TyFun (b6989586621680486638 ~> (a6989586621680486639 ~> b6989586621680486638)) (b6989586621680486638 ~> (t6989586621680486628 a6989586621680486639 ~> b6989586621680486638)) -> Type) (arg6989586621680487271 :: b6989586621680486638 ~> (a6989586621680486639 ~> b6989586621680486638)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym0 :: TyFun (b6989586621680486638 ~> (a6989586621680486639 ~> b6989586621680486638)) (b6989586621680486638 ~> (t6989586621680486628 a6989586621680486639 ~> b6989586621680486638)) -> Type) (arg6989586621680487271 :: b6989586621680486638 ~> (a6989586621680486639 ~> b6989586621680486638)) = Foldl'Sym1 arg6989586621680487271 t6989586621680486628 :: TyFun b6989586621680486638 (t6989586621680486628 a6989586621680486639 ~> b6989586621680486638) -> Type |
data Foldl'Sym1 (arg6989586621680487271 :: (~>) b6989586621680486638 ((~>) a6989586621680486639 b6989586621680486638)) :: forall t6989586621680486628. (~>) b6989586621680486638 ((~>) (t6989586621680486628 a6989586621680486639) b6989586621680486638) 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 arg6989586621680487271 t6989586621680486628 :: TyFun b6989586621680486638 (t6989586621680486628 a6989586621680486639 ~> b6989586621680486638) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym1 arg6989586621680487271 t6989586621680486628 :: TyFun b6989586621680486638 (t6989586621680486628 a6989586621680486639 ~> b6989586621680486638) -> Type) (arg6989586621680487272 :: b6989586621680486638) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym1 arg6989586621680487271 t6989586621680486628 :: TyFun b6989586621680486638 (t6989586621680486628 a6989586621680486639 ~> b6989586621680486638) -> Type) (arg6989586621680487272 :: b6989586621680486638) = Foldl'Sym2 arg6989586621680487271 arg6989586621680487272 t6989586621680486628 :: TyFun (t6989586621680486628 a6989586621680486639) b6989586621680486638 -> Type |
data Foldl'Sym2 (arg6989586621680487271 :: (~>) b6989586621680486638 ((~>) a6989586621680486639 b6989586621680486638)) (arg6989586621680487272 :: b6989586621680486638) :: forall t6989586621680486628. (~>) (t6989586621680486628 a6989586621680486639) b6989586621680486638 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 arg6989586621680487272 arg6989586621680487271 t6989586621680486628 :: TyFun (t6989586621680486628 a6989586621680486639) b6989586621680486638 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl'Sym2 arg6989586621680487272 arg6989586621680487271 t :: TyFun (t a) b -> Type) (arg6989586621680487273 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym2 arg6989586621680487272 arg6989586621680487271 t :: TyFun (t a) b -> Type) (arg6989586621680487273 :: t a) = Foldl' arg6989586621680487272 arg6989586621680487271 arg6989586621680487273 |
type Foldl'Sym3 (arg6989586621680487271 :: (~>) b6989586621680486638 ((~>) a6989586621680486639 b6989586621680486638)) (arg6989586621680487272 :: b6989586621680486638) (arg6989586621680487273 :: t6989586621680486628 a6989586621680486639) = Foldl' arg6989586621680487271 arg6989586621680487272 arg6989586621680487273 Source #
data Foldl1Sym0 :: forall a6989586621680486641 t6989586621680486628. (~>) ((~>) a6989586621680486641 ((~>) a6989586621680486641 a6989586621680486641)) ((~>) (t6989586621680486628 a6989586621680486641) a6989586621680486641) 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 (a6989586621680486641 ~> (a6989586621680486641 ~> a6989586621680486641)) (t6989586621680486628 a6989586621680486641 ~> a6989586621680486641) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym0 :: TyFun (a6989586621680486641 ~> (a6989586621680486641 ~> a6989586621680486641)) (t6989586621680486628 a6989586621680486641 ~> a6989586621680486641) -> Type) (arg6989586621680487281 :: a6989586621680486641 ~> (a6989586621680486641 ~> a6989586621680486641)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl1Sym0 :: TyFun (a6989586621680486641 ~> (a6989586621680486641 ~> a6989586621680486641)) (t6989586621680486628 a6989586621680486641 ~> a6989586621680486641) -> Type) (arg6989586621680487281 :: a6989586621680486641 ~> (a6989586621680486641 ~> a6989586621680486641)) = Foldl1Sym1 arg6989586621680487281 t6989586621680486628 :: TyFun (t6989586621680486628 a6989586621680486641) a6989586621680486641 -> Type |
data Foldl1Sym1 (arg6989586621680487281 :: (~>) a6989586621680486641 ((~>) a6989586621680486641 a6989586621680486641)) :: forall t6989586621680486628. (~>) (t6989586621680486628 a6989586621680486641) a6989586621680486641 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 arg6989586621680487281 t6989586621680486628 :: TyFun (t6989586621680486628 a6989586621680486641) a6989586621680486641 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1Sym1 arg6989586621680487281 t :: TyFun (t a) a -> Type) (arg6989586621680487282 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl1Sym1 arg6989586621680487281 t :: TyFun (t a) a -> Type) (arg6989586621680487282 :: t a) = Foldl1 arg6989586621680487281 arg6989586621680487282 |
type Foldl1Sym2 (arg6989586621680487281 :: (~>) a6989586621680486641 ((~>) a6989586621680486641 a6989586621680486641)) (arg6989586621680487282 :: t6989586621680486628 a6989586621680486641) = Foldl1 arg6989586621680487281 arg6989586621680487282 Source #
data Foldl1'Sym0 :: forall a6989586621679970294. (~>) ((~>) a6989586621679970294 ((~>) a6989586621679970294 a6989586621679970294)) ((~>) [a6989586621679970294] a6989586621679970294) 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 (a6989586621679970294 ~> (a6989586621679970294 ~> a6989586621679970294)) ([a6989586621679970294] ~> a6989586621679970294) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym0 :: TyFun (a6989586621679970294 ~> (a6989586621679970294 ~> a6989586621679970294)) ([a6989586621679970294] ~> a6989586621679970294) -> Type) (a6989586621679975443 :: a6989586621679970294 ~> (a6989586621679970294 ~> a6989586621679970294)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym0 :: TyFun (a6989586621679970294 ~> (a6989586621679970294 ~> a6989586621679970294)) ([a6989586621679970294] ~> a6989586621679970294) -> Type) (a6989586621679975443 :: a6989586621679970294 ~> (a6989586621679970294 ~> a6989586621679970294)) = Foldl1'Sym1 a6989586621679975443 |
data Foldl1'Sym1 (a6989586621679975443 :: (~>) a6989586621679970294 ((~>) a6989586621679970294 a6989586621679970294)) :: (~>) [a6989586621679970294] a6989586621679970294 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 a6989586621679975443 :: TyFun [a6989586621679970294] a6989586621679970294 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldl1'Sym1 a6989586621679975443 :: TyFun [a] a -> Type) (a6989586621679975444 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym1 a6989586621679975443 :: TyFun [a] a -> Type) (a6989586621679975444 :: [a]) = Foldl1' a6989586621679975443 a6989586621679975444 |
type Foldl1'Sym2 (a6989586621679975443 :: (~>) a6989586621679970294 ((~>) a6989586621679970294 a6989586621679970294)) (a6989586621679975444 :: [a6989586621679970294]) = Foldl1' a6989586621679975443 a6989586621679975444 Source #
data FoldrSym0 :: forall a6989586621680486632 b6989586621680486633 t6989586621680486628. (~>) ((~>) a6989586621680486632 ((~>) b6989586621680486633 b6989586621680486633)) ((~>) b6989586621680486633 ((~>) (t6989586621680486628 a6989586621680486632) b6989586621680486633)) Source #
Instances
SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym0 :: TyFun (a6989586621680486632 ~> (b6989586621680486633 ~> b6989586621680486633)) (b6989586621680486633 ~> (t6989586621680486628 a6989586621680486632 ~> b6989586621680486633)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym0 :: TyFun (a6989586621680486632 ~> (b6989586621680486633 ~> b6989586621680486633)) (b6989586621680486633 ~> (t6989586621680486628 a6989586621680486632 ~> b6989586621680486633)) -> Type) (arg6989586621680487253 :: a6989586621680486632 ~> (b6989586621680486633 ~> b6989586621680486633)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldrSym0 :: TyFun (a6989586621680486632 ~> (b6989586621680486633 ~> b6989586621680486633)) (b6989586621680486633 ~> (t6989586621680486628 a6989586621680486632 ~> b6989586621680486633)) -> Type) (arg6989586621680487253 :: a6989586621680486632 ~> (b6989586621680486633 ~> b6989586621680486633)) = FoldrSym1 arg6989586621680487253 t6989586621680486628 :: TyFun b6989586621680486633 (t6989586621680486628 a6989586621680486632 ~> b6989586621680486633) -> Type |
data FoldrSym1 (arg6989586621680487253 :: (~>) a6989586621680486632 ((~>) b6989586621680486633 b6989586621680486633)) :: forall t6989586621680486628. (~>) b6989586621680486633 ((~>) (t6989586621680486628 a6989586621680486632) b6989586621680486633) Source #
Instances
(SFoldable t, SingI d) => SingI (FoldrSym1 d t :: TyFun b (t a ~> b) -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym1 arg6989586621680487253 t6989586621680486628 :: TyFun b6989586621680486633 (t6989586621680486628 a6989586621680486632 ~> b6989586621680486633) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym1 arg6989586621680487253 t6989586621680486628 :: TyFun b6989586621680486633 (t6989586621680486628 a6989586621680486632 ~> b6989586621680486633) -> Type) (arg6989586621680487254 :: b6989586621680486633) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldrSym1 arg6989586621680487253 t6989586621680486628 :: TyFun b6989586621680486633 (t6989586621680486628 a6989586621680486632 ~> b6989586621680486633) -> Type) (arg6989586621680487254 :: b6989586621680486633) = FoldrSym2 arg6989586621680487253 arg6989586621680487254 t6989586621680486628 :: TyFun (t6989586621680486628 a6989586621680486632) b6989586621680486633 -> Type |
data FoldrSym2 (arg6989586621680487253 :: (~>) a6989586621680486632 ((~>) b6989586621680486633 b6989586621680486633)) (arg6989586621680487254 :: b6989586621680486633) :: forall t6989586621680486628. (~>) (t6989586621680486628 a6989586621680486632) b6989586621680486633 Source #
Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # | |
SuppressUnusedWarnings (FoldrSym2 arg6989586621680487254 arg6989586621680487253 t6989586621680486628 :: TyFun (t6989586621680486628 a6989586621680486632) b6989586621680486633 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FoldrSym2 arg6989586621680487254 arg6989586621680487253 t :: TyFun (t a) b -> Type) (arg6989586621680487255 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type FoldrSym3 (arg6989586621680487253 :: (~>) a6989586621680486632 ((~>) b6989586621680486633 b6989586621680486633)) (arg6989586621680487254 :: b6989586621680486633) (arg6989586621680487255 :: t6989586621680486628 a6989586621680486632) = Foldr arg6989586621680487253 arg6989586621680487254 arg6989586621680487255 Source #
data Foldr1Sym0 :: forall a6989586621680486640 t6989586621680486628. (~>) ((~>) a6989586621680486640 ((~>) a6989586621680486640 a6989586621680486640)) ((~>) (t6989586621680486628 a6989586621680486640) a6989586621680486640) 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 (a6989586621680486640 ~> (a6989586621680486640 ~> a6989586621680486640)) (t6989586621680486628 a6989586621680486640 ~> a6989586621680486640) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym0 :: TyFun (a6989586621680486640 ~> (a6989586621680486640 ~> a6989586621680486640)) (t6989586621680486628 a6989586621680486640 ~> a6989586621680486640) -> Type) (arg6989586621680487277 :: a6989586621680486640 ~> (a6989586621680486640 ~> a6989586621680486640)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr1Sym0 :: TyFun (a6989586621680486640 ~> (a6989586621680486640 ~> a6989586621680486640)) (t6989586621680486628 a6989586621680486640 ~> a6989586621680486640) -> Type) (arg6989586621680487277 :: a6989586621680486640 ~> (a6989586621680486640 ~> a6989586621680486640)) = Foldr1Sym1 arg6989586621680487277 t6989586621680486628 :: TyFun (t6989586621680486628 a6989586621680486640) a6989586621680486640 -> Type |
data Foldr1Sym1 (arg6989586621680487277 :: (~>) a6989586621680486640 ((~>) a6989586621680486640 a6989586621680486640)) :: forall t6989586621680486628. (~>) (t6989586621680486628 a6989586621680486640) a6989586621680486640 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 arg6989586621680487277 t6989586621680486628 :: TyFun (t6989586621680486628 a6989586621680486640) a6989586621680486640 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (Foldr1Sym1 arg6989586621680487277 t :: TyFun (t a) a -> Type) (arg6989586621680487278 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr1Sym1 arg6989586621680487277 t :: TyFun (t a) a -> Type) (arg6989586621680487278 :: t a) = Foldr1 arg6989586621680487277 arg6989586621680487278 |
type Foldr1Sym2 (arg6989586621680487277 :: (~>) a6989586621680486640 ((~>) a6989586621680486640 a6989586621680486640)) (arg6989586621680487278 :: t6989586621680486628 a6989586621680486640) = Foldr1 arg6989586621680487277 arg6989586621680487278 Source #
data ConcatSym0 :: forall t6989586621680486553 a6989586621680486554. (~>) (t6989586621680486553 [a6989586621680486554]) [a6989586621680486554] 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 (t6989586621680486553 [a6989586621680486554]) [a6989586621680486554] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680487135 :: t [a]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680487135 :: t [a]) = Concat a6989586621680487135 |
type ConcatSym1 (a6989586621680487135 :: t6989586621680486553 [a6989586621680486554]) = Concat a6989586621680487135 Source #
data ConcatMapSym0 :: forall a6989586621680486551 b6989586621680486552 t6989586621680486550. (~>) ((~>) a6989586621680486551 [b6989586621680486552]) ((~>) (t6989586621680486550 a6989586621680486551) [b6989586621680486552]) 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 (a6989586621680486551 ~> [b6989586621680486552]) (t6989586621680486550 a6989586621680486551 ~> [b6989586621680486552]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym0 :: TyFun (a6989586621680486551 ~> [b6989586621680486552]) (t6989586621680486550 a6989586621680486551 ~> [b6989586621680486552]) -> Type) (a6989586621680487119 :: a6989586621680486551 ~> [b6989586621680486552]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym0 :: TyFun (a6989586621680486551 ~> [b6989586621680486552]) (t6989586621680486550 a6989586621680486551 ~> [b6989586621680486552]) -> Type) (a6989586621680487119 :: a6989586621680486551 ~> [b6989586621680486552]) = ConcatMapSym1 a6989586621680487119 t6989586621680486550 :: TyFun (t6989586621680486550 a6989586621680486551) [b6989586621680486552] -> Type |
data ConcatMapSym1 (a6989586621680487119 :: (~>) a6989586621680486551 [b6989586621680486552]) :: forall t6989586621680486550. (~>) (t6989586621680486550 a6989586621680486551) [b6989586621680486552] 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 a6989586621680487119 t6989586621680486550 :: TyFun (t6989586621680486550 a6989586621680486551) [b6989586621680486552] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ConcatMapSym1 a6989586621680487119 t :: TyFun (t a) [b] -> Type) (a6989586621680487120 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym1 a6989586621680487119 t :: TyFun (t a) [b] -> Type) (a6989586621680487120 :: t a) = ConcatMap a6989586621680487119 a6989586621680487120 |
type ConcatMapSym2 (a6989586621680487119 :: (~>) a6989586621680486551 [b6989586621680486552]) (a6989586621680487120 :: t6989586621680486550 a6989586621680486551) = ConcatMap a6989586621680487119 a6989586621680487120 Source #
data AndSym0 :: forall t6989586621680486549. (~>) (t6989586621680486549 Bool) Bool Source #
Instances
SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
SuppressUnusedWarnings (AndSym0 :: TyFun (t6989586621680486549 Bool) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680487110 :: t Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type AndSym1 (a6989586621680487110 :: t6989586621680486549 Bool) = And a6989586621680487110 Source #
data OrSym0 :: forall t6989586621680486548. (~>) (t6989586621680486548 Bool) Bool Source #
Instances
SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
SuppressUnusedWarnings (OrSym0 :: TyFun (t6989586621680486548 Bool) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680487101 :: t Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data AnySym0 :: forall a6989586621680486547 t6989586621680486546. (~>) ((~>) a6989586621680486547 Bool) ((~>) (t6989586621680486546 a6989586621680486547) Bool) Source #
Instances
SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (AnySym0 :: TyFun (a6989586621680486547 ~> Bool) (t6989586621680486546 a6989586621680486547 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AnySym0 :: TyFun (a6989586621680486547 ~> Bool) (t6989586621680486546 a6989586621680486547 ~> Bool) -> Type) (a6989586621680487088 :: a6989586621680486547 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data AnySym1 (a6989586621680487088 :: (~>) a6989586621680486547 Bool) :: forall t6989586621680486546. (~>) (t6989586621680486546 a6989586621680486547) Bool Source #
Instances
(SFoldable t, SingI d) => SingI (AnySym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (AnySym1 a6989586621680487088 t6989586621680486546 :: TyFun (t6989586621680486546 a6989586621680486547) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AnySym1 a6989586621680487088 t :: TyFun (t a) Bool -> Type) (a6989586621680487089 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type AnySym2 (a6989586621680487088 :: (~>) a6989586621680486547 Bool) (a6989586621680487089 :: t6989586621680486546 a6989586621680486547) = Any a6989586621680487088 a6989586621680487089 Source #
data AllSym0 :: forall a6989586621680486545 t6989586621680486544. (~>) ((~>) a6989586621680486545 Bool) ((~>) (t6989586621680486544 a6989586621680486545) Bool) Source #
Instances
SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (AllSym0 :: TyFun (a6989586621680486545 ~> Bool) (t6989586621680486544 a6989586621680486545 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AllSym0 :: TyFun (a6989586621680486545 ~> Bool) (t6989586621680486544 a6989586621680486545 ~> Bool) -> Type) (a6989586621680487075 :: a6989586621680486545 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data AllSym1 (a6989586621680487075 :: (~>) a6989586621680486545 Bool) :: forall t6989586621680486544. (~>) (t6989586621680486544 a6989586621680486545) Bool Source #
Instances
(SFoldable t, SingI d) => SingI (AllSym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (AllSym1 a6989586621680487075 t6989586621680486544 :: TyFun (t6989586621680486544 a6989586621680486545) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (AllSym1 a6989586621680487075 t :: TyFun (t a) Bool -> Type) (a6989586621680487076 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type AllSym2 (a6989586621680487075 :: (~>) a6989586621680486545 Bool) (a6989586621680487076 :: t6989586621680486544 a6989586621680486545) = All a6989586621680487075 a6989586621680487076 Source #
data SumSym0 :: forall t6989586621680486628 a6989586621680486648. (~>) (t6989586621680486628 a6989586621680486648) a6989586621680486648 Source #
Instances
(SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # | |
SuppressUnusedWarnings (SumSym0 :: TyFun (t6989586621680486628 a6989586621680486648) a6989586621680486648 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (SumSym0 :: TyFun (t a) a -> Type) (arg6989586621680487299 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type SumSym1 (arg6989586621680487299 :: t6989586621680486628 a6989586621680486648) = Sum arg6989586621680487299 Source #
data ProductSym0 :: forall t6989586621680486628 a6989586621680486649. (~>) (t6989586621680486628 a6989586621680486649) a6989586621680486649 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 (t6989586621680486628 a6989586621680486649) a6989586621680486649 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680487301 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680487301 :: t a) = Product arg6989586621680487301 |
type ProductSym1 (arg6989586621680487301 :: t6989586621680486628 a6989586621680486649) = Product arg6989586621680487301 Source #
data MaximumSym0 :: forall t6989586621680486628 a6989586621680486646. (~>) (t6989586621680486628 a6989586621680486646) a6989586621680486646 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 (t6989586621680486628 a6989586621680486646) a6989586621680486646 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680487295 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680487295 :: t a) = Maximum arg6989586621680487295 |
type MaximumSym1 (arg6989586621680487295 :: t6989586621680486628 a6989586621680486646) = Maximum arg6989586621680487295 Source #
data MinimumSym0 :: forall t6989586621680486628 a6989586621680486647. (~>) (t6989586621680486628 a6989586621680486647) a6989586621680486647 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 (t6989586621680486628 a6989586621680486647) a6989586621680486647 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680487297 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680487297 :: t a) = Minimum arg6989586621680487297 |
type MinimumSym1 (arg6989586621680487297 :: t6989586621680486628 a6989586621680486647) = Minimum arg6989586621680487297 Source #
data ScanlSym0 :: forall b6989586621679970286 a6989586621679970287. (~>) ((~>) b6989586621679970286 ((~>) a6989586621679970287 b6989586621679970286)) ((~>) b6989586621679970286 ((~>) [a6989586621679970287] [b6989586621679970286])) Source #
Instances
SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym0 :: TyFun (b6989586621679970286 ~> (a6989586621679970287 ~> b6989586621679970286)) (b6989586621679970286 ~> ([a6989586621679970287] ~> [b6989586621679970286])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym0 :: TyFun (b6989586621679970286 ~> (a6989586621679970287 ~> b6989586621679970286)) (b6989586621679970286 ~> ([a6989586621679970287] ~> [b6989586621679970286])) -> Type) (a6989586621679975380 :: b6989586621679970286 ~> (a6989586621679970287 ~> b6989586621679970286)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ScanlSym0 :: TyFun (b6989586621679970286 ~> (a6989586621679970287 ~> b6989586621679970286)) (b6989586621679970286 ~> ([a6989586621679970287] ~> [b6989586621679970286])) -> Type) (a6989586621679975380 :: b6989586621679970286 ~> (a6989586621679970287 ~> b6989586621679970286)) = ScanlSym1 a6989586621679975380 |
data ScanlSym1 (a6989586621679975380 :: (~>) b6989586621679970286 ((~>) a6989586621679970287 b6989586621679970286)) :: (~>) b6989586621679970286 ((~>) [a6989586621679970287] [b6989586621679970286]) Source #
Instances
SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym1 a6989586621679975380 :: TyFun b6989586621679970286 ([a6989586621679970287] ~> [b6989586621679970286]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym1 a6989586621679975380 :: TyFun b6989586621679970286 ([a6989586621679970287] ~> [b6989586621679970286]) -> Type) (a6989586621679975381 :: b6989586621679970286) Source # | |
data ScanlSym2 (a6989586621679975380 :: (~>) b6989586621679970286 ((~>) a6989586621679970287 b6989586621679970286)) (a6989586621679975381 :: b6989586621679970286) :: (~>) [a6989586621679970287] [b6989586621679970286] Source #
Instances
(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym2 a6989586621679975381 a6989586621679975380 :: TyFun [a6989586621679970287] [b6989586621679970286] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanlSym2 a6989586621679975381 a6989586621679975380 :: TyFun [a] [b] -> Type) (a6989586621679975382 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type ScanlSym3 (a6989586621679975380 :: (~>) b6989586621679970286 ((~>) a6989586621679970287 b6989586621679970286)) (a6989586621679975381 :: b6989586621679970286) (a6989586621679975382 :: [a6989586621679970287]) = Scanl a6989586621679975380 a6989586621679975381 a6989586621679975382 Source #
data Scanl1Sym0 :: forall a6989586621679970285. (~>) ((~>) a6989586621679970285 ((~>) a6989586621679970285 a6989586621679970285)) ((~>) [a6989586621679970285] [a6989586621679970285]) 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 (a6989586621679970285 ~> (a6989586621679970285 ~> a6989586621679970285)) ([a6989586621679970285] ~> [a6989586621679970285]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym0 :: TyFun (a6989586621679970285 ~> (a6989586621679970285 ~> a6989586621679970285)) ([a6989586621679970285] ~> [a6989586621679970285]) -> Type) (a6989586621679975373 :: a6989586621679970285 ~> (a6989586621679970285 ~> a6989586621679970285)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym0 :: TyFun (a6989586621679970285 ~> (a6989586621679970285 ~> a6989586621679970285)) ([a6989586621679970285] ~> [a6989586621679970285]) -> Type) (a6989586621679975373 :: a6989586621679970285 ~> (a6989586621679970285 ~> a6989586621679970285)) = Scanl1Sym1 a6989586621679975373 |
data Scanl1Sym1 (a6989586621679975373 :: (~>) a6989586621679970285 ((~>) a6989586621679970285 a6989586621679970285)) :: (~>) [a6989586621679970285] [a6989586621679970285] 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 a6989586621679975373 :: TyFun [a6989586621679970285] [a6989586621679970285] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Scanl1Sym1 a6989586621679975373 :: TyFun [a] [a] -> Type) (a6989586621679975374 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym1 a6989586621679975373 :: TyFun [a] [a] -> Type) (a6989586621679975374 :: [a]) = Scanl1 a6989586621679975373 a6989586621679975374 |
type Scanl1Sym2 (a6989586621679975373 :: (~>) a6989586621679970285 ((~>) a6989586621679970285 a6989586621679970285)) (a6989586621679975374 :: [a6989586621679970285]) = Scanl1 a6989586621679975373 a6989586621679975374 Source #
data ScanrSym0 :: forall a6989586621679970283 b6989586621679970284. (~>) ((~>) a6989586621679970283 ((~>) b6989586621679970284 b6989586621679970284)) ((~>) b6989586621679970284 ((~>) [a6989586621679970283] [b6989586621679970284])) Source #
Instances
SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym0 :: TyFun (a6989586621679970283 ~> (b6989586621679970284 ~> b6989586621679970284)) (b6989586621679970284 ~> ([a6989586621679970283] ~> [b6989586621679970284])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym0 :: TyFun (a6989586621679970283 ~> (b6989586621679970284 ~> b6989586621679970284)) (b6989586621679970284 ~> ([a6989586621679970283] ~> [b6989586621679970284])) -> Type) (a6989586621679975352 :: a6989586621679970283 ~> (b6989586621679970284 ~> b6989586621679970284)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ScanrSym0 :: TyFun (a6989586621679970283 ~> (b6989586621679970284 ~> b6989586621679970284)) (b6989586621679970284 ~> ([a6989586621679970283] ~> [b6989586621679970284])) -> Type) (a6989586621679975352 :: a6989586621679970283 ~> (b6989586621679970284 ~> b6989586621679970284)) = ScanrSym1 a6989586621679975352 |
data ScanrSym1 (a6989586621679975352 :: (~>) a6989586621679970283 ((~>) b6989586621679970284 b6989586621679970284)) :: (~>) b6989586621679970284 ((~>) [a6989586621679970283] [b6989586621679970284]) Source #
Instances
SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym1 a6989586621679975352 :: TyFun b6989586621679970284 ([a6989586621679970283] ~> [b6989586621679970284]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym1 a6989586621679975352 :: TyFun b6989586621679970284 ([a6989586621679970283] ~> [b6989586621679970284]) -> Type) (a6989586621679975353 :: b6989586621679970284) Source # | |
data ScanrSym2 (a6989586621679975352 :: (~>) a6989586621679970283 ((~>) b6989586621679970284 b6989586621679970284)) (a6989586621679975353 :: b6989586621679970284) :: (~>) [a6989586621679970283] [b6989586621679970284] Source #
Instances
(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym2 a6989586621679975353 a6989586621679975352 :: TyFun [a6989586621679970283] [b6989586621679970284] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ScanrSym2 a6989586621679975353 a6989586621679975352 :: TyFun [a] [b] -> Type) (a6989586621679975354 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type ScanrSym3 (a6989586621679975352 :: (~>) a6989586621679970283 ((~>) b6989586621679970284 b6989586621679970284)) (a6989586621679975353 :: b6989586621679970284) (a6989586621679975354 :: [a6989586621679970283]) = Scanr a6989586621679975352 a6989586621679975353 a6989586621679975354 Source #
data Scanr1Sym0 :: forall a6989586621679970282. (~>) ((~>) a6989586621679970282 ((~>) a6989586621679970282 a6989586621679970282)) ((~>) [a6989586621679970282] [a6989586621679970282]) 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 (a6989586621679970282 ~> (a6989586621679970282 ~> a6989586621679970282)) ([a6989586621679970282] ~> [a6989586621679970282]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym0 :: TyFun (a6989586621679970282 ~> (a6989586621679970282 ~> a6989586621679970282)) ([a6989586621679970282] ~> [a6989586621679970282]) -> Type) (a6989586621679975328 :: a6989586621679970282 ~> (a6989586621679970282 ~> a6989586621679970282)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym0 :: TyFun (a6989586621679970282 ~> (a6989586621679970282 ~> a6989586621679970282)) ([a6989586621679970282] ~> [a6989586621679970282]) -> Type) (a6989586621679975328 :: a6989586621679970282 ~> (a6989586621679970282 ~> a6989586621679970282)) = Scanr1Sym1 a6989586621679975328 |
data Scanr1Sym1 (a6989586621679975328 :: (~>) a6989586621679970282 ((~>) a6989586621679970282 a6989586621679970282)) :: (~>) [a6989586621679970282] [a6989586621679970282] 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 a6989586621679975328 :: TyFun [a6989586621679970282] [a6989586621679970282] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Scanr1Sym1 a6989586621679975328 :: TyFun [a] [a] -> Type) (a6989586621679975329 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym1 a6989586621679975328 :: TyFun [a] [a] -> Type) (a6989586621679975329 :: [a]) = Scanr1 a6989586621679975328 a6989586621679975329 |
type Scanr1Sym2 (a6989586621679975328 :: (~>) a6989586621679970282 ((~>) a6989586621679970282 a6989586621679970282)) (a6989586621679975329 :: [a6989586621679970282]) = Scanr1 a6989586621679975328 a6989586621679975329 Source #
data MapAccumLSym0 :: forall a6989586621680800353 b6989586621680800354 c6989586621680800355 t6989586621680800352. (~>) ((~>) a6989586621680800353 ((~>) b6989586621680800354 (a6989586621680800353, c6989586621680800355))) ((~>) a6989586621680800353 ((~>) (t6989586621680800352 b6989586621680800354) (a6989586621680800353, t6989586621680800352 c6989586621680800355))) 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 (a6989586621680800353 ~> (b6989586621680800354 ~> (a6989586621680800353, c6989586621680800355))) (a6989586621680800353 ~> (t6989586621680800352 b6989586621680800354 ~> (a6989586621680800353, t6989586621680800352 c6989586621680800355))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym0 :: TyFun (a6989586621680800353 ~> (b6989586621680800354 ~> (a6989586621680800353, c6989586621680800355))) (a6989586621680800353 ~> (t6989586621680800352 b6989586621680800354 ~> (a6989586621680800353, t6989586621680800352 c6989586621680800355))) -> Type) (a6989586621680800856 :: a6989586621680800353 ~> (b6989586621680800354 ~> (a6989586621680800353, c6989586621680800355))) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym0 :: TyFun (a6989586621680800353 ~> (b6989586621680800354 ~> (a6989586621680800353, c6989586621680800355))) (a6989586621680800353 ~> (t6989586621680800352 b6989586621680800354 ~> (a6989586621680800353, t6989586621680800352 c6989586621680800355))) -> Type) (a6989586621680800856 :: a6989586621680800353 ~> (b6989586621680800354 ~> (a6989586621680800353, c6989586621680800355))) = MapAccumLSym1 a6989586621680800856 t6989586621680800352 :: TyFun a6989586621680800353 (t6989586621680800352 b6989586621680800354 ~> (a6989586621680800353, t6989586621680800352 c6989586621680800355)) -> Type |
data MapAccumLSym1 (a6989586621680800856 :: (~>) a6989586621680800353 ((~>) b6989586621680800354 (a6989586621680800353, c6989586621680800355))) :: forall t6989586621680800352. (~>) a6989586621680800353 ((~>) (t6989586621680800352 b6989586621680800354) (a6989586621680800353, t6989586621680800352 c6989586621680800355)) 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 a6989586621680800856 t6989586621680800352 :: TyFun a6989586621680800353 (t6989586621680800352 b6989586621680800354 ~> (a6989586621680800353, t6989586621680800352 c6989586621680800355)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym1 a6989586621680800856 t6989586621680800352 :: TyFun a6989586621680800353 (t6989586621680800352 b6989586621680800354 ~> (a6989586621680800353, t6989586621680800352 c6989586621680800355)) -> Type) (a6989586621680800857 :: a6989586621680800353) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym1 a6989586621680800856 t6989586621680800352 :: TyFun a6989586621680800353 (t6989586621680800352 b6989586621680800354 ~> (a6989586621680800353, t6989586621680800352 c6989586621680800355)) -> Type) (a6989586621680800857 :: a6989586621680800353) = MapAccumLSym2 a6989586621680800856 a6989586621680800857 t6989586621680800352 :: TyFun (t6989586621680800352 b6989586621680800354) (a6989586621680800353, t6989586621680800352 c6989586621680800355) -> Type |
data MapAccumLSym2 (a6989586621680800856 :: (~>) a6989586621680800353 ((~>) b6989586621680800354 (a6989586621680800353, c6989586621680800355))) (a6989586621680800857 :: a6989586621680800353) :: forall t6989586621680800352. (~>) (t6989586621680800352 b6989586621680800354) (a6989586621680800353, t6989586621680800352 c6989586621680800355) 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 a6989586621680800857 a6989586621680800856 t6989586621680800352 :: TyFun (t6989586621680800352 b6989586621680800354) (a6989586621680800353, t6989586621680800352 c6989586621680800355) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumLSym2 a6989586621680800857 a6989586621680800856 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680800858 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym2 a6989586621680800857 a6989586621680800856 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680800858 :: t b) = MapAccumL a6989586621680800857 a6989586621680800856 a6989586621680800858 |
type MapAccumLSym3 (a6989586621680800856 :: (~>) a6989586621680800353 ((~>) b6989586621680800354 (a6989586621680800353, c6989586621680800355))) (a6989586621680800857 :: a6989586621680800353) (a6989586621680800858 :: t6989586621680800352 b6989586621680800354) = MapAccumL a6989586621680800856 a6989586621680800857 a6989586621680800858 Source #
data MapAccumRSym0 :: forall a6989586621680800349 b6989586621680800350 c6989586621680800351 t6989586621680800348. (~>) ((~>) a6989586621680800349 ((~>) b6989586621680800350 (a6989586621680800349, c6989586621680800351))) ((~>) a6989586621680800349 ((~>) (t6989586621680800348 b6989586621680800350) (a6989586621680800349, t6989586621680800348 c6989586621680800351))) 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 (a6989586621680800349 ~> (b6989586621680800350 ~> (a6989586621680800349, c6989586621680800351))) (a6989586621680800349 ~> (t6989586621680800348 b6989586621680800350 ~> (a6989586621680800349, t6989586621680800348 c6989586621680800351))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym0 :: TyFun (a6989586621680800349 ~> (b6989586621680800350 ~> (a6989586621680800349, c6989586621680800351))) (a6989586621680800349 ~> (t6989586621680800348 b6989586621680800350 ~> (a6989586621680800349, t6989586621680800348 c6989586621680800351))) -> Type) (a6989586621680800839 :: a6989586621680800349 ~> (b6989586621680800350 ~> (a6989586621680800349, c6989586621680800351))) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym0 :: TyFun (a6989586621680800349 ~> (b6989586621680800350 ~> (a6989586621680800349, c6989586621680800351))) (a6989586621680800349 ~> (t6989586621680800348 b6989586621680800350 ~> (a6989586621680800349, t6989586621680800348 c6989586621680800351))) -> Type) (a6989586621680800839 :: a6989586621680800349 ~> (b6989586621680800350 ~> (a6989586621680800349, c6989586621680800351))) = MapAccumRSym1 a6989586621680800839 t6989586621680800348 :: TyFun a6989586621680800349 (t6989586621680800348 b6989586621680800350 ~> (a6989586621680800349, t6989586621680800348 c6989586621680800351)) -> Type |
data MapAccumRSym1 (a6989586621680800839 :: (~>) a6989586621680800349 ((~>) b6989586621680800350 (a6989586621680800349, c6989586621680800351))) :: forall t6989586621680800348. (~>) a6989586621680800349 ((~>) (t6989586621680800348 b6989586621680800350) (a6989586621680800349, t6989586621680800348 c6989586621680800351)) 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 a6989586621680800839 t6989586621680800348 :: TyFun a6989586621680800349 (t6989586621680800348 b6989586621680800350 ~> (a6989586621680800349, t6989586621680800348 c6989586621680800351)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym1 a6989586621680800839 t6989586621680800348 :: TyFun a6989586621680800349 (t6989586621680800348 b6989586621680800350 ~> (a6989586621680800349, t6989586621680800348 c6989586621680800351)) -> Type) (a6989586621680800840 :: a6989586621680800349) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym1 a6989586621680800839 t6989586621680800348 :: TyFun a6989586621680800349 (t6989586621680800348 b6989586621680800350 ~> (a6989586621680800349, t6989586621680800348 c6989586621680800351)) -> Type) (a6989586621680800840 :: a6989586621680800349) = MapAccumRSym2 a6989586621680800839 a6989586621680800840 t6989586621680800348 :: TyFun (t6989586621680800348 b6989586621680800350) (a6989586621680800349, t6989586621680800348 c6989586621680800351) -> Type |
data MapAccumRSym2 (a6989586621680800839 :: (~>) a6989586621680800349 ((~>) b6989586621680800350 (a6989586621680800349, c6989586621680800351))) (a6989586621680800840 :: a6989586621680800349) :: forall t6989586621680800348. (~>) (t6989586621680800348 b6989586621680800350) (a6989586621680800349, t6989586621680800348 c6989586621680800351) 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 a6989586621680800840 a6989586621680800839 t6989586621680800348 :: TyFun (t6989586621680800348 b6989586621680800350) (a6989586621680800349, t6989586621680800348 c6989586621680800351) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MapAccumRSym2 a6989586621680800840 a6989586621680800839 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680800841 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym2 a6989586621680800840 a6989586621680800839 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680800841 :: t b) = MapAccumR a6989586621680800840 a6989586621680800839 a6989586621680800841 |
type MapAccumRSym3 (a6989586621680800839 :: (~>) a6989586621680800349 ((~>) b6989586621680800350 (a6989586621680800349, c6989586621680800351))) (a6989586621680800840 :: a6989586621680800349) (a6989586621680800841 :: t6989586621680800348 b6989586621680800350) = MapAccumR a6989586621680800839 a6989586621680800840 a6989586621680800841 Source #
data ReplicateSym0 :: forall a6989586621679970190. (~>) Nat ((~>) a6989586621679970190 [a6989586621679970190]) 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 (a6989586621679970190 ~> [a6989586621679970190]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym0 :: TyFun Nat (a6989586621679970190 ~> [a6989586621679970190]) -> Type) (a6989586621679974355 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym0 :: TyFun Nat (a6989586621679970190 ~> [a6989586621679970190]) -> Type) (a6989586621679974355 :: Nat) = ReplicateSym1 a6989586621679974355 a6989586621679970190 :: TyFun a6989586621679970190 [a6989586621679970190] -> Type |
data ReplicateSym1 (a6989586621679974355 :: Nat) :: forall a6989586621679970190. (~>) a6989586621679970190 [a6989586621679970190] 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 a6989586621679974355 a6989586621679970190 :: TyFun a6989586621679970190 [a6989586621679970190] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ReplicateSym1 a6989586621679974355 a :: TyFun a [a] -> Type) (a6989586621679974356 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym1 a6989586621679974355 a :: TyFun a [a] -> Type) (a6989586621679974356 :: a) = Replicate a6989586621679974355 a6989586621679974356 |
type ReplicateSym2 (a6989586621679974355 :: Nat) (a6989586621679974356 :: a6989586621679970190) = Replicate a6989586621679974355 a6989586621679974356 Source #
data UnfoldrSym0 :: forall b6989586621679970274 a6989586621679970275. (~>) ((~>) b6989586621679970274 (Maybe (a6989586621679970275, b6989586621679970274))) ((~>) b6989586621679970274 [a6989586621679970275]) 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 (b6989586621679970274 ~> Maybe (a6989586621679970275, b6989586621679970274)) (b6989586621679970274 ~> [a6989586621679970275]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym0 :: TyFun (b6989586621679970274 ~> Maybe (a6989586621679970275, b6989586621679970274)) (b6989586621679970274 ~> [a6989586621679970275]) -> Type) (a6989586621679975186 :: b6989586621679970274 ~> Maybe (a6989586621679970275, b6989586621679970274)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym0 :: TyFun (b6989586621679970274 ~> Maybe (a6989586621679970275, b6989586621679970274)) (b6989586621679970274 ~> [a6989586621679970275]) -> Type) (a6989586621679975186 :: b6989586621679970274 ~> Maybe (a6989586621679970275, b6989586621679970274)) = UnfoldrSym1 a6989586621679975186 |
data UnfoldrSym1 (a6989586621679975186 :: (~>) b6989586621679970274 (Maybe (a6989586621679970275, b6989586621679970274))) :: (~>) b6989586621679970274 [a6989586621679970275] 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 a6989586621679975186 :: TyFun b6989586621679970274 [a6989586621679970275] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnfoldrSym1 a6989586621679975186 :: TyFun b [a] -> Type) (a6989586621679975187 :: b) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym1 a6989586621679975186 :: TyFun b [a] -> Type) (a6989586621679975187 :: b) = Unfoldr a6989586621679975186 a6989586621679975187 |
type UnfoldrSym2 (a6989586621679975186 :: (~>) b6989586621679970274 (Maybe (a6989586621679970275, b6989586621679970274))) (a6989586621679975187 :: b6989586621679970274) = Unfoldr a6989586621679975186 a6989586621679975187 Source #
data TakeSym0 :: forall a6989586621679970206. (~>) Nat ((~>) [a6989586621679970206] [a6989586621679970206]) Source #
Instances
SingI (TakeSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (TakeSym0 :: TyFun Nat ([a6989586621679970206] ~> [a6989586621679970206]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym0 :: TyFun Nat ([a6989586621679970206] ~> [a6989586621679970206]) -> Type) (a6989586621679974516 :: Nat) Source # | |
data TakeSym1 (a6989586621679974516 :: Nat) :: forall a6989586621679970206. (~>) [a6989586621679970206] [a6989586621679970206] Source #
Instances
SingI d => SingI (TakeSym1 d a :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (TakeSym1 a6989586621679974516 a6989586621679970206 :: TyFun [a6989586621679970206] [a6989586621679970206] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TakeSym1 a6989586621679974516 a :: TyFun [a] [a] -> Type) (a6989586621679974517 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type TakeSym2 (a6989586621679974516 :: Nat) (a6989586621679974517 :: [a6989586621679970206]) = Take a6989586621679974516 a6989586621679974517 Source #
data DropSym0 :: forall a6989586621679970205. (~>) Nat ((~>) [a6989586621679970205] [a6989586621679970205]) Source #
Instances
SingI (DropSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (DropSym0 :: TyFun Nat ([a6989586621679970205] ~> [a6989586621679970205]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropSym0 :: TyFun Nat ([a6989586621679970205] ~> [a6989586621679970205]) -> Type) (a6989586621679974502 :: Nat) Source # | |
data DropSym1 (a6989586621679974502 :: Nat) :: forall a6989586621679970205. (~>) [a6989586621679970205] [a6989586621679970205] Source #
Instances
SingI d => SingI (DropSym1 d a :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (DropSym1 a6989586621679974502 a6989586621679970205 :: TyFun [a6989586621679970205] [a6989586621679970205] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropSym1 a6989586621679974502 a :: TyFun [a] [a] -> Type) (a6989586621679974503 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type DropSym2 (a6989586621679974502 :: Nat) (a6989586621679974503 :: [a6989586621679970205]) = Drop a6989586621679974502 a6989586621679974503 Source #
data SplitAtSym0 :: forall a6989586621679970204. (~>) Nat ((~>) [a6989586621679970204] ([a6989586621679970204], [a6989586621679970204])) 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 ([a6989586621679970204] ~> ([a6989586621679970204], [a6989586621679970204])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym0 :: TyFun Nat ([a6989586621679970204] ~> ([a6989586621679970204], [a6989586621679970204])) -> Type) (a6989586621679974496 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym0 :: TyFun Nat ([a6989586621679970204] ~> ([a6989586621679970204], [a6989586621679970204])) -> Type) (a6989586621679974496 :: Nat) = SplitAtSym1 a6989586621679974496 a6989586621679970204 :: TyFun [a6989586621679970204] ([a6989586621679970204], [a6989586621679970204]) -> Type |
data SplitAtSym1 (a6989586621679974496 :: Nat) :: forall a6989586621679970204. (~>) [a6989586621679970204] ([a6989586621679970204], [a6989586621679970204]) 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 a6989586621679974496 a6989586621679970204 :: TyFun [a6989586621679970204] ([a6989586621679970204], [a6989586621679970204]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SplitAtSym1 a6989586621679974496 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621679974497 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym1 a6989586621679974496 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621679974497 :: [a]) = SplitAt a6989586621679974496 a6989586621679974497 |
type SplitAtSym2 (a6989586621679974496 :: Nat) (a6989586621679974497 :: [a6989586621679970204]) = SplitAt a6989586621679974496 a6989586621679974497 Source #
data TakeWhileSym0 :: forall a6989586621679970211. (~>) ((~>) a6989586621679970211 Bool) ((~>) [a6989586621679970211] [a6989586621679970211]) 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 (a6989586621679970211 ~> Bool) ([a6989586621679970211] ~> [a6989586621679970211]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym0 :: TyFun (a6989586621679970211 ~> Bool) ([a6989586621679970211] ~> [a6989586621679970211]) -> Type) (a6989586621679974660 :: a6989586621679970211 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym0 :: TyFun (a6989586621679970211 ~> Bool) ([a6989586621679970211] ~> [a6989586621679970211]) -> Type) (a6989586621679974660 :: a6989586621679970211 ~> Bool) = TakeWhileSym1 a6989586621679974660 |
data TakeWhileSym1 (a6989586621679974660 :: (~>) a6989586621679970211 Bool) :: (~>) [a6989586621679970211] [a6989586621679970211] 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 a6989586621679974660 :: TyFun [a6989586621679970211] [a6989586621679970211] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TakeWhileSym1 a6989586621679974660 :: TyFun [a] [a] -> Type) (a6989586621679974661 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym1 a6989586621679974660 :: TyFun [a] [a] -> Type) (a6989586621679974661 :: [a]) = TakeWhile a6989586621679974660 a6989586621679974661 |
type TakeWhileSym2 (a6989586621679974660 :: (~>) a6989586621679970211 Bool) (a6989586621679974661 :: [a6989586621679970211]) = TakeWhile a6989586621679974660 a6989586621679974661 Source #
data DropWhileSym0 :: forall a6989586621679970210. (~>) ((~>) a6989586621679970210 Bool) ((~>) [a6989586621679970210] [a6989586621679970210]) 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 (a6989586621679970210 ~> Bool) ([a6989586621679970210] ~> [a6989586621679970210]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym0 :: TyFun (a6989586621679970210 ~> Bool) ([a6989586621679970210] ~> [a6989586621679970210]) -> Type) (a6989586621679974642 :: a6989586621679970210 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym0 :: TyFun (a6989586621679970210 ~> Bool) ([a6989586621679970210] ~> [a6989586621679970210]) -> Type) (a6989586621679974642 :: a6989586621679970210 ~> Bool) = DropWhileSym1 a6989586621679974642 |
data DropWhileSym1 (a6989586621679974642 :: (~>) a6989586621679970210 Bool) :: (~>) [a6989586621679970210] [a6989586621679970210] 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 a6989586621679974642 :: TyFun [a6989586621679970210] [a6989586621679970210] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileSym1 a6989586621679974642 :: TyFun [a] [a] -> Type) (a6989586621679974643 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym1 a6989586621679974642 :: TyFun [a] [a] -> Type) (a6989586621679974643 :: [a]) = DropWhile a6989586621679974642 a6989586621679974643 |
type DropWhileSym2 (a6989586621679974642 :: (~>) a6989586621679970210 Bool) (a6989586621679974643 :: [a6989586621679970210]) = DropWhile a6989586621679974642 a6989586621679974643 Source #
data DropWhileEndSym0 :: forall a6989586621679970209. (~>) ((~>) a6989586621679970209 Bool) ((~>) [a6989586621679970209] [a6989586621679970209]) Source #
Instances
SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a6989586621679970209 ~> Bool) ([a6989586621679970209] ~> [a6989586621679970209]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym0 :: TyFun (a6989586621679970209 ~> Bool) ([a6989586621679970209] ~> [a6989586621679970209]) -> Type) (a6989586621679974616 :: a6989586621679970209 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym0 :: TyFun (a6989586621679970209 ~> Bool) ([a6989586621679970209] ~> [a6989586621679970209]) -> Type) (a6989586621679974616 :: a6989586621679970209 ~> Bool) = DropWhileEndSym1 a6989586621679974616 |
data DropWhileEndSym1 (a6989586621679974616 :: (~>) a6989586621679970209 Bool) :: (~>) [a6989586621679970209] [a6989586621679970209] 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 a6989586621679974616 :: TyFun [a6989586621679970209] [a6989586621679970209] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DropWhileEndSym1 a6989586621679974616 :: TyFun [a] [a] -> Type) (a6989586621679974617 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym1 a6989586621679974616 :: TyFun [a] [a] -> Type) (a6989586621679974617 :: [a]) = DropWhileEnd a6989586621679974616 a6989586621679974617 |
type DropWhileEndSym2 (a6989586621679974616 :: (~>) a6989586621679970209 Bool) (a6989586621679974617 :: [a6989586621679970209]) = DropWhileEnd a6989586621679974616 a6989586621679974617 Source #
data SpanSym0 :: forall a6989586621679970208. (~>) ((~>) a6989586621679970208 Bool) ((~>) [a6989586621679970208] ([a6989586621679970208], [a6989586621679970208])) Source #
Instances
SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym0 :: TyFun (a6989586621679970208 ~> Bool) ([a6989586621679970208] ~> ([a6989586621679970208], [a6989586621679970208])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym0 :: TyFun (a6989586621679970208 ~> Bool) ([a6989586621679970208] ~> ([a6989586621679970208], [a6989586621679970208])) -> Type) (a6989586621679974573 :: a6989586621679970208 ~> Bool) Source # | |
data SpanSym1 (a6989586621679974573 :: (~>) a6989586621679970208 Bool) :: (~>) [a6989586621679970208] ([a6989586621679970208], [a6989586621679970208]) Source #
Instances
SingI d => SingI (SpanSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym1 a6989586621679974573 :: TyFun [a6989586621679970208] ([a6989586621679970208], [a6989586621679970208]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SpanSym1 a6989586621679974573 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679974574 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type SpanSym2 (a6989586621679974573 :: (~>) a6989586621679970208 Bool) (a6989586621679974574 :: [a6989586621679970208]) = Span a6989586621679974573 a6989586621679974574 Source #
data BreakSym0 :: forall a6989586621679970207. (~>) ((~>) a6989586621679970207 Bool) ((~>) [a6989586621679970207] ([a6989586621679970207], [a6989586621679970207])) Source #
Instances
SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym0 :: TyFun (a6989586621679970207 ~> Bool) ([a6989586621679970207] ~> ([a6989586621679970207], [a6989586621679970207])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym0 :: TyFun (a6989586621679970207 ~> Bool) ([a6989586621679970207] ~> ([a6989586621679970207], [a6989586621679970207])) -> Type) (a6989586621679974530 :: a6989586621679970207 ~> Bool) Source # | |
data BreakSym1 (a6989586621679974530 :: (~>) a6989586621679970207 Bool) :: (~>) [a6989586621679970207] ([a6989586621679970207], [a6989586621679970207]) Source #
Instances
SingI d => SingI (BreakSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym1 a6989586621679974530 :: TyFun [a6989586621679970207] ([a6989586621679970207], [a6989586621679970207]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (BreakSym1 a6989586621679974530 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679974531 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type BreakSym2 (a6989586621679974530 :: (~>) a6989586621679970207 Bool) (a6989586621679974531 :: [a6989586621679970207]) = Break a6989586621679974530 a6989586621679974531 Source #
data StripPrefixSym0 :: forall a6989586621680092397. (~>) [a6989586621680092397] ((~>) [a6989586621680092397] (Maybe [a6989586621680092397])) Source #
Instances
SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a6989586621680092397] ([a6989586621680092397] ~> Maybe [a6989586621680092397]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (StripPrefixSym0 :: TyFun [a6989586621680092397] ([a6989586621680092397] ~> Maybe [a6989586621680092397]) -> Type) (a6989586621680094093 :: [a6989586621680092397]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym0 :: TyFun [a6989586621680092397] ([a6989586621680092397] ~> Maybe [a6989586621680092397]) -> Type) (a6989586621680094093 :: [a6989586621680092397]) = StripPrefixSym1 a6989586621680094093 |
data StripPrefixSym1 (a6989586621680094093 :: [a6989586621680092397]) :: (~>) [a6989586621680092397] (Maybe [a6989586621680092397]) Source #
Instances
SuppressUnusedWarnings (StripPrefixSym1 a6989586621680094093 :: TyFun [a6989586621680092397] (Maybe [a6989586621680092397]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (StripPrefixSym1 a6989586621680094093 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680094094 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym1 a6989586621680094093 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680094094 :: [a]) = StripPrefix a6989586621680094093 a6989586621680094094 |
type StripPrefixSym2 (a6989586621680094093 :: [a6989586621680092397]) (a6989586621680094094 :: [a6989586621680092397]) = StripPrefix a6989586621680094093 a6989586621680094094 Source #
data GroupSym0 :: forall a6989586621679970203. (~>) [a6989586621679970203] [[a6989586621679970203]] Source #
Instances
SEq a => SingI (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621679970203] [[a6989586621679970203]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679974493 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type GroupSym1 (a6989586621679974493 :: [a6989586621679970203]) = Group a6989586621679974493 Source #
data InitsSym0 :: forall a6989586621679970273. (~>) [a6989586621679970273] [[a6989586621679970273]] Source #
Instances
SingI (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621679970273] [[a6989586621679970273]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679975178 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type InitsSym1 (a6989586621679975178 :: [a6989586621679970273]) = Inits a6989586621679975178 Source #
data TailsSym0 :: forall a6989586621679970272. (~>) [a6989586621679970272] [[a6989586621679970272]] Source #
Instances
SingI (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621679970272] [[a6989586621679970272]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679975171 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type TailsSym1 (a6989586621679975171 :: [a6989586621679970272]) = Tails a6989586621679975171 Source #
data IsPrefixOfSym0 :: forall a6989586621679970271. (~>) [a6989586621679970271] ((~>) [a6989586621679970271] Bool) Source #
Instances
SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679970271] ([a6989586621679970271] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679970271] ([a6989586621679970271] ~> Bool) -> Type) (a6989586621679975163 :: [a6989586621679970271]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679970271] ([a6989586621679970271] ~> Bool) -> Type) (a6989586621679975163 :: [a6989586621679970271]) = IsPrefixOfSym1 a6989586621679975163 |
data IsPrefixOfSym1 (a6989586621679975163 :: [a6989586621679970271]) :: (~>) [a6989586621679970271] 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 a6989586621679975163 :: TyFun [a6989586621679970271] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsPrefixOfSym1 a6989586621679975163 :: TyFun [a] Bool -> Type) (a6989586621679975164 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym1 a6989586621679975163 :: TyFun [a] Bool -> Type) (a6989586621679975164 :: [a]) = IsPrefixOf a6989586621679975163 a6989586621679975164 |
type IsPrefixOfSym2 (a6989586621679975163 :: [a6989586621679970271]) (a6989586621679975164 :: [a6989586621679970271]) = IsPrefixOf a6989586621679975163 a6989586621679975164 Source #
data IsSuffixOfSym0 :: forall a6989586621679970270. (~>) [a6989586621679970270] ((~>) [a6989586621679970270] Bool) Source #
Instances
SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679970270] ([a6989586621679970270] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679970270] ([a6989586621679970270] ~> Bool) -> Type) (a6989586621679975157 :: [a6989586621679970270]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679970270] ([a6989586621679970270] ~> Bool) -> Type) (a6989586621679975157 :: [a6989586621679970270]) = IsSuffixOfSym1 a6989586621679975157 |
data IsSuffixOfSym1 (a6989586621679975157 :: [a6989586621679970270]) :: (~>) [a6989586621679970270] 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 a6989586621679975157 :: TyFun [a6989586621679970270] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsSuffixOfSym1 a6989586621679975157 :: TyFun [a] Bool -> Type) (a6989586621679975158 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym1 a6989586621679975157 :: TyFun [a] Bool -> Type) (a6989586621679975158 :: [a]) = IsSuffixOf a6989586621679975157 a6989586621679975158 |
type IsSuffixOfSym2 (a6989586621679975157 :: [a6989586621679970270]) (a6989586621679975158 :: [a6989586621679970270]) = IsSuffixOf a6989586621679975157 a6989586621679975158 Source #
data IsInfixOfSym0 :: forall a6989586621679970269. (~>) [a6989586621679970269] ((~>) [a6989586621679970269] 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 [a6989586621679970269] ([a6989586621679970269] ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym0 :: TyFun [a6989586621679970269] ([a6989586621679970269] ~> Bool) -> Type) (a6989586621679975151 :: [a6989586621679970269]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsInfixOfSym0 :: TyFun [a6989586621679970269] ([a6989586621679970269] ~> Bool) -> Type) (a6989586621679975151 :: [a6989586621679970269]) = IsInfixOfSym1 a6989586621679975151 |
data IsInfixOfSym1 (a6989586621679975151 :: [a6989586621679970269]) :: (~>) [a6989586621679970269] 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 a6989586621679975151 :: TyFun [a6989586621679970269] Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IsInfixOfSym1 a6989586621679975151 :: TyFun [a] Bool -> Type) (a6989586621679975152 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsInfixOfSym1 a6989586621679975151 :: TyFun [a] Bool -> Type) (a6989586621679975152 :: [a]) = IsInfixOf a6989586621679975151 a6989586621679975152 |
type IsInfixOfSym2 (a6989586621679975151 :: [a6989586621679970269]) (a6989586621679975152 :: [a6989586621679970269]) = IsInfixOf a6989586621679975151 a6989586621679975152 Source #
data ElemSym0 :: forall a6989586621680486645 t6989586621680486628. (~>) a6989586621680486645 ((~>) (t6989586621680486628 a6989586621680486645) Bool) Source #
Instances
(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621680486645 (t6989586621680486628 a6989586621680486645 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym0 :: TyFun a6989586621680486645 (t6989586621680486628 a6989586621680486645 ~> Bool) -> Type) (arg6989586621680487291 :: a6989586621680486645) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
data ElemSym1 (arg6989586621680487291 :: a6989586621680486645) :: forall t6989586621680486628. (~>) (t6989586621680486628 a6989586621680486645) Bool Source #
Instances
(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d t :: TyFun (t a) Bool -> Type) Source # | |
SuppressUnusedWarnings (ElemSym1 arg6989586621680487291 t6989586621680486628 :: TyFun (t6989586621680486628 a6989586621680486645) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemSym1 arg6989586621680487291 t :: TyFun (t a) Bool -> Type) (arg6989586621680487292 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type ElemSym2 (arg6989586621680487291 :: a6989586621680486645) (arg6989586621680487292 :: t6989586621680486628 a6989586621680486645) = Elem arg6989586621680487291 arg6989586621680487292 Source #
data NotElemSym0 :: forall a6989586621680486539 t6989586621680486538. (~>) a6989586621680486539 ((~>) (t6989586621680486538 a6989586621680486539) 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 a6989586621680486539 (t6989586621680486538 a6989586621680486539 ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym0 :: TyFun a6989586621680486539 (t6989586621680486538 a6989586621680486539 ~> Bool) -> Type) (a6989586621680487017 :: a6989586621680486539) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (NotElemSym0 :: TyFun a6989586621680486539 (t6989586621680486538 a6989586621680486539 ~> Bool) -> Type) (a6989586621680487017 :: a6989586621680486539) = NotElemSym1 a6989586621680487017 t6989586621680486538 :: TyFun (t6989586621680486538 a6989586621680486539) Bool -> Type |
data NotElemSym1 (a6989586621680487017 :: a6989586621680486539) :: forall t6989586621680486538. (~>) (t6989586621680486538 a6989586621680486539) 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 a6989586621680487017 t6989586621680486538 :: TyFun (t6989586621680486538 a6989586621680486539) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (NotElemSym1 a6989586621680487017 t :: TyFun (t a) Bool -> Type) (a6989586621680487018 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (NotElemSym1 a6989586621680487017 t :: TyFun (t a) Bool -> Type) (a6989586621680487018 :: t a) = NotElem a6989586621680487017 a6989586621680487018 |
type NotElemSym2 (a6989586621680487017 :: a6989586621680486539) (a6989586621680487018 :: t6989586621680486538 a6989586621680486539) = NotElem a6989586621680487017 a6989586621680487018 Source #
data LookupSym0 :: forall a6989586621679970196 b6989586621679970197. (~>) a6989586621679970196 ((~>) [(a6989586621679970196, b6989586621679970197)] (Maybe b6989586621679970197)) 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 a6989586621679970196 ([(a6989586621679970196, b6989586621679970197)] ~> Maybe b6989586621679970197) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym0 :: TyFun a6989586621679970196 ([(a6989586621679970196, b6989586621679970197)] ~> Maybe b6989586621679970197) -> Type) (a6989586621679974420 :: a6989586621679970196) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (LookupSym0 :: TyFun a6989586621679970196 ([(a6989586621679970196, b6989586621679970197)] ~> Maybe b6989586621679970197) -> Type) (a6989586621679974420 :: a6989586621679970196) = LookupSym1 a6989586621679974420 b6989586621679970197 :: TyFun [(a6989586621679970196, b6989586621679970197)] (Maybe b6989586621679970197) -> Type |
data LookupSym1 (a6989586621679974420 :: a6989586621679970196) :: forall b6989586621679970197. (~>) [(a6989586621679970196, b6989586621679970197)] (Maybe b6989586621679970197) 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 a6989586621679974420 b6989586621679970197 :: TyFun [(a6989586621679970196, b6989586621679970197)] (Maybe b6989586621679970197) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (LookupSym1 a6989586621679974420 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679974421 :: [(a, b)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (LookupSym1 a6989586621679974420 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679974421 :: [(a, b)]) = Lookup a6989586621679974420 a6989586621679974421 |
type LookupSym2 (a6989586621679974420 :: a6989586621679970196) (a6989586621679974421 :: [(a6989586621679970196, b6989586621679970197)]) = Lookup a6989586621679974420 a6989586621679974421 Source #
data FindSym0 :: forall a6989586621680486537 t6989586621680486536. (~>) ((~>) a6989586621680486537 Bool) ((~>) (t6989586621680486536 a6989586621680486537) (Maybe a6989586621680486537)) Source #
Instances
SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # | |
SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680486537 ~> Bool) (t6989586621680486536 a6989586621680486537 ~> Maybe a6989586621680486537) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindSym0 :: TyFun (a6989586621680486537 ~> Bool) (t6989586621680486536 a6989586621680486537 ~> Maybe a6989586621680486537) -> Type) (a6989586621680486990 :: a6989586621680486537 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FindSym0 :: TyFun (a6989586621680486537 ~> Bool) (t6989586621680486536 a6989586621680486537 ~> Maybe a6989586621680486537) -> Type) (a6989586621680486990 :: a6989586621680486537 ~> Bool) = FindSym1 a6989586621680486990 t6989586621680486536 :: TyFun (t6989586621680486536 a6989586621680486537) (Maybe a6989586621680486537) -> Type |
data FindSym1 (a6989586621680486990 :: (~>) a6989586621680486537 Bool) :: forall t6989586621680486536. (~>) (t6989586621680486536 a6989586621680486537) (Maybe a6989586621680486537) Source #
Instances
(SFoldable t, SingI d) => SingI (FindSym1 d t :: TyFun (t a) (Maybe a) -> Type) Source # | |
SuppressUnusedWarnings (FindSym1 a6989586621680486990 t6989586621680486536 :: TyFun (t6989586621680486536 a6989586621680486537) (Maybe a6989586621680486537) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindSym1 a6989586621680486990 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680486991 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable |
type FindSym2 (a6989586621680486990 :: (~>) a6989586621680486537 Bool) (a6989586621680486991 :: t6989586621680486536 a6989586621680486537) = Find a6989586621680486990 a6989586621680486991 Source #
data FilterSym0 :: forall a6989586621679970219. (~>) ((~>) a6989586621679970219 Bool) ((~>) [a6989586621679970219] [a6989586621679970219]) 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 (a6989586621679970219 ~> Bool) ([a6989586621679970219] ~> [a6989586621679970219]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym0 :: TyFun (a6989586621679970219 ~> Bool) ([a6989586621679970219] ~> [a6989586621679970219]) -> Type) (a6989586621679974774 :: a6989586621679970219 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym0 :: TyFun (a6989586621679970219 ~> Bool) ([a6989586621679970219] ~> [a6989586621679970219]) -> Type) (a6989586621679974774 :: a6989586621679970219 ~> Bool) = FilterSym1 a6989586621679974774 |
data FilterSym1 (a6989586621679974774 :: (~>) a6989586621679970219 Bool) :: (~>) [a6989586621679970219] [a6989586621679970219] 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 a6989586621679974774 :: TyFun [a6989586621679970219] [a6989586621679970219] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FilterSym1 a6989586621679974774 :: TyFun [a] [a] -> Type) (a6989586621679974775 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym1 a6989586621679974774 :: TyFun [a] [a] -> Type) (a6989586621679974775 :: [a]) = Filter a6989586621679974774 a6989586621679974775 |
type FilterSym2 (a6989586621679974774 :: (~>) a6989586621679970219 Bool) (a6989586621679974775 :: [a6989586621679970219]) = Filter a6989586621679974774 a6989586621679974775 Source #
data PartitionSym0 :: forall a6989586621679970195. (~>) ((~>) a6989586621679970195 Bool) ((~>) [a6989586621679970195] ([a6989586621679970195], [a6989586621679970195])) 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 (a6989586621679970195 ~> Bool) ([a6989586621679970195] ~> ([a6989586621679970195], [a6989586621679970195])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym0 :: TyFun (a6989586621679970195 ~> Bool) ([a6989586621679970195] ~> ([a6989586621679970195], [a6989586621679970195])) -> Type) (a6989586621679974414 :: a6989586621679970195 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym0 :: TyFun (a6989586621679970195 ~> Bool) ([a6989586621679970195] ~> ([a6989586621679970195], [a6989586621679970195])) -> Type) (a6989586621679974414 :: a6989586621679970195 ~> Bool) = PartitionSym1 a6989586621679974414 |
data PartitionSym1 (a6989586621679974414 :: (~>) a6989586621679970195 Bool) :: (~>) [a6989586621679970195] ([a6989586621679970195], [a6989586621679970195]) 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 a6989586621679974414 :: TyFun [a6989586621679970195] ([a6989586621679970195], [a6989586621679970195]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (PartitionSym1 a6989586621679974414 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679974415 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym1 a6989586621679974414 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679974415 :: [a]) = Partition a6989586621679974414 a6989586621679974415 |
type PartitionSym2 (a6989586621679974414 :: (~>) a6989586621679970195 Bool) (a6989586621679974415 :: [a6989586621679970195]) = Partition a6989586621679974414 a6989586621679974415 Source #
data (!!@#@$) :: forall a6989586621679970188. (~>) [a6989586621679970188] ((~>) Nat a6989586621679970188) infixl 9 Source #
Instances
SingI ((!!@#@$) :: TyFun [a] (Nat ~> a) -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$) :: TyFun [a6989586621679970188] (Nat ~> a6989586621679970188) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$) :: TyFun [a6989586621679970188] (Nat ~> a6989586621679970188) -> Type) (a6989586621679974335 :: [a6989586621679970188]) Source # | |
data (!!@#@$$) (a6989586621679974335 :: [a6989586621679970188]) :: (~>) Nat a6989586621679970188 infixl 9 Source #
Instances
SingI d => SingI ((!!@#@$$) d :: TyFun Nat a -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$$) a6989586621679974335 :: TyFun Nat a6989586621679970188 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply ((!!@#@$$) a6989586621679974335 :: TyFun Nat a -> Type) (a6989586621679974336 :: Nat) Source # | |
type (!!@#@$$$) (a6989586621679974335 :: [a6989586621679970188]) (a6989586621679974336 :: Nat) = (!!) a6989586621679974335 a6989586621679974336 Source #
data ElemIndexSym0 :: forall a6989586621679970217. (~>) a6989586621679970217 ((~>) [a6989586621679970217] (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 a6989586621679970217 ([a6989586621679970217] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym0 :: TyFun a6989586621679970217 ([a6989586621679970217] ~> Maybe Nat) -> Type) (a6989586621679974758 :: a6989586621679970217) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndexSym0 :: TyFun a6989586621679970217 ([a6989586621679970217] ~> Maybe Nat) -> Type) (a6989586621679974758 :: a6989586621679970217) = ElemIndexSym1 a6989586621679974758 |
data ElemIndexSym1 (a6989586621679974758 :: a6989586621679970217) :: (~>) [a6989586621679970217] (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 a6989586621679974758 :: TyFun [a6989586621679970217] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndexSym1 a6989586621679974758 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679974759 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndexSym1 a6989586621679974758 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679974759 :: [a]) = ElemIndex a6989586621679974758 a6989586621679974759 |
type ElemIndexSym2 (a6989586621679974758 :: a6989586621679970217) (a6989586621679974759 :: [a6989586621679970217]) = ElemIndex a6989586621679974758 a6989586621679974759 Source #
data ElemIndicesSym0 :: forall a6989586621679970216. (~>) a6989586621679970216 ((~>) [a6989586621679970216] [Nat]) Source #
Instances
SEq a => SingI (ElemIndicesSym0 :: TyFun a ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a6989586621679970216 ([a6989586621679970216] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym0 :: TyFun a6989586621679970216 ([a6989586621679970216] ~> [Nat]) -> Type) (a6989586621679974750 :: a6989586621679970216) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym0 :: TyFun a6989586621679970216 ([a6989586621679970216] ~> [Nat]) -> Type) (a6989586621679974750 :: a6989586621679970216) = ElemIndicesSym1 a6989586621679974750 |
data ElemIndicesSym1 (a6989586621679974750 :: a6989586621679970216) :: (~>) [a6989586621679970216] [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 a6989586621679974750 :: TyFun [a6989586621679970216] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ElemIndicesSym1 a6989586621679974750 :: TyFun [a] [Nat] -> Type) (a6989586621679974751 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym1 a6989586621679974750 :: TyFun [a] [Nat] -> Type) (a6989586621679974751 :: [a]) = ElemIndices a6989586621679974750 a6989586621679974751 |
type ElemIndicesSym2 (a6989586621679974750 :: a6989586621679970216) (a6989586621679974751 :: [a6989586621679970216]) = ElemIndices a6989586621679974750 a6989586621679974751 Source #
data FindIndexSym0 :: forall a6989586621679970215. (~>) ((~>) a6989586621679970215 Bool) ((~>) [a6989586621679970215] (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 (a6989586621679970215 ~> Bool) ([a6989586621679970215] ~> Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym0 :: TyFun (a6989586621679970215 ~> Bool) ([a6989586621679970215] ~> Maybe Nat) -> Type) (a6989586621679974742 :: a6989586621679970215 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndexSym0 :: TyFun (a6989586621679970215 ~> Bool) ([a6989586621679970215] ~> Maybe Nat) -> Type) (a6989586621679974742 :: a6989586621679970215 ~> Bool) = FindIndexSym1 a6989586621679974742 |
data FindIndexSym1 (a6989586621679974742 :: (~>) a6989586621679970215 Bool) :: (~>) [a6989586621679970215] (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 a6989586621679974742 :: TyFun [a6989586621679970215] (Maybe Nat) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindIndexSym1 a6989586621679974742 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679974743 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndexSym1 a6989586621679974742 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679974743 :: [a]) = FindIndex a6989586621679974742 a6989586621679974743 |
type FindIndexSym2 (a6989586621679974742 :: (~>) a6989586621679970215 Bool) (a6989586621679974743 :: [a6989586621679970215]) = FindIndex a6989586621679974742 a6989586621679974743 Source #
data FindIndicesSym0 :: forall a6989586621679970214. (~>) ((~>) a6989586621679970214 Bool) ((~>) [a6989586621679970214] [Nat]) Source #
Instances
SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (a6989586621679970214 ~> Bool) ([a6989586621679970214] ~> [Nat]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym0 :: TyFun (a6989586621679970214 ~> Bool) ([a6989586621679970214] ~> [Nat]) -> Type) (a6989586621679974716 :: a6989586621679970214 ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndicesSym0 :: TyFun (a6989586621679970214 ~> Bool) ([a6989586621679970214] ~> [Nat]) -> Type) (a6989586621679974716 :: a6989586621679970214 ~> Bool) = FindIndicesSym1 a6989586621679974716 |
data FindIndicesSym1 (a6989586621679974716 :: (~>) a6989586621679970214 Bool) :: (~>) [a6989586621679970214] [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 a6989586621679974716 :: TyFun [a6989586621679970214] [Nat] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (FindIndicesSym1 a6989586621679974716 :: TyFun [a] [Nat] -> Type) (a6989586621679974717 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndicesSym1 a6989586621679974716 :: TyFun [a] [Nat] -> Type) (a6989586621679974717 :: [a]) = FindIndices a6989586621679974716 a6989586621679974717 |
type FindIndicesSym2 (a6989586621679974716 :: (~>) a6989586621679970214 Bool) (a6989586621679974717 :: [a6989586621679970214]) = FindIndices a6989586621679974716 a6989586621679974717 Source #
data ZipSym0 :: forall a6989586621679970265 b6989586621679970266. (~>) [a6989586621679970265] ((~>) [b6989586621679970266] [(a6989586621679970265, b6989586621679970266)]) Source #
Instances
SingI (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # | |
SuppressUnusedWarnings (ZipSym0 :: TyFun [a6989586621679970265] ([b6989586621679970266] ~> [(a6989586621679970265, b6989586621679970266)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym0 :: TyFun [a6989586621679970265] ([b6989586621679970266] ~> [(a6989586621679970265, b6989586621679970266)]) -> Type) (a6989586621679975129 :: [a6989586621679970265]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipSym0 :: TyFun [a6989586621679970265] ([b6989586621679970266] ~> [(a6989586621679970265, b6989586621679970266)]) -> Type) (a6989586621679975129 :: [a6989586621679970265]) = ZipSym1 a6989586621679975129 b6989586621679970266 :: TyFun [b6989586621679970266] [(a6989586621679970265, b6989586621679970266)] -> Type |
data ZipSym1 (a6989586621679975129 :: [a6989586621679970265]) :: forall b6989586621679970266. (~>) [b6989586621679970266] [(a6989586621679970265, b6989586621679970266)] Source #
Instances
SingI d => SingI (ZipSym1 d b :: TyFun [b] [(a, b)] -> Type) Source # | |
SuppressUnusedWarnings (ZipSym1 a6989586621679975129 b6989586621679970266 :: TyFun [b6989586621679970266] [(a6989586621679970265, b6989586621679970266)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipSym1 a6989586621679975129 b :: TyFun [b] [(a, b)] -> Type) (a6989586621679975130 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type ZipSym2 (a6989586621679975129 :: [a6989586621679970265]) (a6989586621679975130 :: [b6989586621679970266]) = Zip a6989586621679975129 a6989586621679975130 Source #
data Zip3Sym0 :: forall a6989586621679970262 b6989586621679970263 c6989586621679970264. (~>) [a6989586621679970262] ((~>) [b6989586621679970263] ((~>) [c6989586621679970264] [(a6989586621679970262, b6989586621679970263, c6989586621679970264)])) Source #
Instances
SingI (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a6989586621679970262] ([b6989586621679970263] ~> ([c6989586621679970264] ~> [(a6989586621679970262, b6989586621679970263, c6989586621679970264)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym0 :: TyFun [a6989586621679970262] ([b6989586621679970263] ~> ([c6989586621679970264] ~> [(a6989586621679970262, b6989586621679970263, c6989586621679970264)])) -> Type) (a6989586621679975117 :: [a6989586621679970262]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip3Sym0 :: TyFun [a6989586621679970262] ([b6989586621679970263] ~> ([c6989586621679970264] ~> [(a6989586621679970262, b6989586621679970263, c6989586621679970264)])) -> Type) (a6989586621679975117 :: [a6989586621679970262]) = Zip3Sym1 a6989586621679975117 b6989586621679970263 c6989586621679970264 :: TyFun [b6989586621679970263] ([c6989586621679970264] ~> [(a6989586621679970262, b6989586621679970263, c6989586621679970264)]) -> Type |
data Zip3Sym1 (a6989586621679975117 :: [a6989586621679970262]) :: forall b6989586621679970263 c6989586621679970264. (~>) [b6989586621679970263] ((~>) [c6989586621679970264] [(a6989586621679970262, b6989586621679970263, c6989586621679970264)]) Source #
Instances
SingI d => SingI (Zip3Sym1 d b c :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym1 a6989586621679975117 b6989586621679970263 c6989586621679970264 :: TyFun [b6989586621679970263] ([c6989586621679970264] ~> [(a6989586621679970262, b6989586621679970263, c6989586621679970264)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym1 a6989586621679975117 b6989586621679970263 c6989586621679970264 :: TyFun [b6989586621679970263] ([c6989586621679970264] ~> [(a6989586621679970262, b6989586621679970263, c6989586621679970264)]) -> Type) (a6989586621679975118 :: [b6989586621679970263]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip3Sym1 a6989586621679975117 b6989586621679970263 c6989586621679970264 :: TyFun [b6989586621679970263] ([c6989586621679970264] ~> [(a6989586621679970262, b6989586621679970263, c6989586621679970264)]) -> Type) (a6989586621679975118 :: [b6989586621679970263]) = Zip3Sym2 a6989586621679975117 a6989586621679975118 c6989586621679970264 :: TyFun [c6989586621679970264] [(a6989586621679970262, b6989586621679970263, c6989586621679970264)] -> Type |
data Zip3Sym2 (a6989586621679975117 :: [a6989586621679970262]) (a6989586621679975118 :: [b6989586621679970263]) :: forall c6989586621679970264. (~>) [c6989586621679970264] [(a6989586621679970262, b6989586621679970263, c6989586621679970264)] Source #
Instances
(SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 c :: TyFun [c] [(a, b, c)] -> Type) Source # | |
SuppressUnusedWarnings (Zip3Sym2 a6989586621679975118 a6989586621679975117 c6989586621679970264 :: TyFun [c6989586621679970264] [(a6989586621679970262, b6989586621679970263, c6989586621679970264)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip3Sym2 a6989586621679975118 a6989586621679975117 c :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679975119 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type Zip3Sym3 (a6989586621679975117 :: [a6989586621679970262]) (a6989586621679975118 :: [b6989586621679970263]) (a6989586621679975119 :: [c6989586621679970264]) = Zip3 a6989586621679975117 a6989586621679975118 a6989586621679975119 Source #
data Zip4Sym0 :: forall a6989586621680092393 b6989586621680092394 c6989586621680092395 d6989586621680092396. (~>) [a6989586621680092393] ((~>) [b6989586621680092394] ((~>) [c6989586621680092395] ((~>) [d6989586621680092396] [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)]))) Source #
Instances
SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a6989586621680092393] ([b6989586621680092394] ~> ([c6989586621680092395] ~> ([d6989586621680092396] ~> [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym0 :: TyFun [a6989586621680092393] ([b6989586621680092394] ~> ([c6989586621680092395] ~> ([d6989586621680092396] ~> [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)]))) -> Type) (a6989586621680094081 :: [a6989586621680092393]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym0 :: TyFun [a6989586621680092393] ([b6989586621680092394] ~> ([c6989586621680092395] ~> ([d6989586621680092396] ~> [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)]))) -> Type) (a6989586621680094081 :: [a6989586621680092393]) = Zip4Sym1 a6989586621680094081 b6989586621680092394 c6989586621680092395 d6989586621680092396 :: TyFun [b6989586621680092394] ([c6989586621680092395] ~> ([d6989586621680092396] ~> [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)])) -> Type |
data Zip4Sym1 (a6989586621680094081 :: [a6989586621680092393]) :: forall b6989586621680092394 c6989586621680092395 d6989586621680092396. (~>) [b6989586621680092394] ((~>) [c6989586621680092395] ((~>) [d6989586621680092396] [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)])) Source #
Instances
SuppressUnusedWarnings (Zip4Sym1 a6989586621680094081 b6989586621680092394 c6989586621680092395 d6989586621680092396 :: TyFun [b6989586621680092394] ([c6989586621680092395] ~> ([d6989586621680092396] ~> [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym1 a6989586621680094081 b6989586621680092394 c6989586621680092395 d6989586621680092396 :: TyFun [b6989586621680092394] ([c6989586621680092395] ~> ([d6989586621680092396] ~> [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)])) -> Type) (a6989586621680094082 :: [b6989586621680092394]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym1 a6989586621680094081 b6989586621680092394 c6989586621680092395 d6989586621680092396 :: TyFun [b6989586621680092394] ([c6989586621680092395] ~> ([d6989586621680092396] ~> [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)])) -> Type) (a6989586621680094082 :: [b6989586621680092394]) = Zip4Sym2 a6989586621680094081 a6989586621680094082 c6989586621680092395 d6989586621680092396 :: TyFun [c6989586621680092395] ([d6989586621680092396] ~> [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)]) -> Type |
data Zip4Sym2 (a6989586621680094081 :: [a6989586621680092393]) (a6989586621680094082 :: [b6989586621680092394]) :: forall c6989586621680092395 d6989586621680092396. (~>) [c6989586621680092395] ((~>) [d6989586621680092396] [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)]) Source #
Instances
SuppressUnusedWarnings (Zip4Sym2 a6989586621680094082 a6989586621680094081 c6989586621680092395 d6989586621680092396 :: TyFun [c6989586621680092395] ([d6989586621680092396] ~> [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym2 a6989586621680094082 a6989586621680094081 c6989586621680092395 d6989586621680092396 :: TyFun [c6989586621680092395] ([d6989586621680092396] ~> [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)]) -> Type) (a6989586621680094083 :: [c6989586621680092395]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip4Sym2 a6989586621680094082 a6989586621680094081 c6989586621680092395 d6989586621680092396 :: TyFun [c6989586621680092395] ([d6989586621680092396] ~> [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)]) -> Type) (a6989586621680094083 :: [c6989586621680092395]) = Zip4Sym3 a6989586621680094082 a6989586621680094081 a6989586621680094083 d6989586621680092396 :: TyFun [d6989586621680092396] [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)] -> Type |
data Zip4Sym3 (a6989586621680094081 :: [a6989586621680092393]) (a6989586621680094082 :: [b6989586621680092394]) (a6989586621680094083 :: [c6989586621680092395]) :: forall d6989586621680092396. (~>) [d6989586621680092396] [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)] Source #
Instances
SuppressUnusedWarnings (Zip4Sym3 a6989586621680094083 a6989586621680094082 a6989586621680094081 d6989586621680092396 :: TyFun [d6989586621680092396] [(a6989586621680092393, b6989586621680092394, c6989586621680092395, d6989586621680092396)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip4Sym3 a6989586621680094083 a6989586621680094082 a6989586621680094081 d :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621680094084 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type Zip4Sym4 (a6989586621680094081 :: [a6989586621680092393]) (a6989586621680094082 :: [b6989586621680092394]) (a6989586621680094083 :: [c6989586621680092395]) (a6989586621680094084 :: [d6989586621680092396]) = Zip4 a6989586621680094081 a6989586621680094082 a6989586621680094083 a6989586621680094084 Source #
data Zip5Sym0 :: forall a6989586621680092388 b6989586621680092389 c6989586621680092390 d6989586621680092391 e6989586621680092392. (~>) [a6989586621680092388] ((~>) [b6989586621680092389] ((~>) [c6989586621680092390] ((~>) [d6989586621680092391] ((~>) [e6989586621680092392] [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)])))) Source #
Instances
SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a6989586621680092388] ([b6989586621680092389] ~> ([c6989586621680092390] ~> ([d6989586621680092391] ~> ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym0 :: TyFun [a6989586621680092388] ([b6989586621680092389] ~> ([c6989586621680092390] ~> ([d6989586621680092391] ~> ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)])))) -> Type) (a6989586621680094058 :: [a6989586621680092388]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym0 :: TyFun [a6989586621680092388] ([b6989586621680092389] ~> ([c6989586621680092390] ~> ([d6989586621680092391] ~> ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)])))) -> Type) (a6989586621680094058 :: [a6989586621680092388]) = Zip5Sym1 a6989586621680094058 b6989586621680092389 c6989586621680092390 d6989586621680092391 e6989586621680092392 :: TyFun [b6989586621680092389] ([c6989586621680092390] ~> ([d6989586621680092391] ~> ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]))) -> Type |
data Zip5Sym1 (a6989586621680094058 :: [a6989586621680092388]) :: forall b6989586621680092389 c6989586621680092390 d6989586621680092391 e6989586621680092392. (~>) [b6989586621680092389] ((~>) [c6989586621680092390] ((~>) [d6989586621680092391] ((~>) [e6989586621680092392] [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]))) Source #
Instances
SuppressUnusedWarnings (Zip5Sym1 a6989586621680094058 b6989586621680092389 c6989586621680092390 d6989586621680092391 e6989586621680092392 :: TyFun [b6989586621680092389] ([c6989586621680092390] ~> ([d6989586621680092391] ~> ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym1 a6989586621680094058 b6989586621680092389 c6989586621680092390 d6989586621680092391 e6989586621680092392 :: TyFun [b6989586621680092389] ([c6989586621680092390] ~> ([d6989586621680092391] ~> ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]))) -> Type) (a6989586621680094059 :: [b6989586621680092389]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym1 a6989586621680094058 b6989586621680092389 c6989586621680092390 d6989586621680092391 e6989586621680092392 :: TyFun [b6989586621680092389] ([c6989586621680092390] ~> ([d6989586621680092391] ~> ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]))) -> Type) (a6989586621680094059 :: [b6989586621680092389]) = Zip5Sym2 a6989586621680094058 a6989586621680094059 c6989586621680092390 d6989586621680092391 e6989586621680092392 :: TyFun [c6989586621680092390] ([d6989586621680092391] ~> ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)])) -> Type |
data Zip5Sym2 (a6989586621680094058 :: [a6989586621680092388]) (a6989586621680094059 :: [b6989586621680092389]) :: forall c6989586621680092390 d6989586621680092391 e6989586621680092392. (~>) [c6989586621680092390] ((~>) [d6989586621680092391] ((~>) [e6989586621680092392] [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)])) Source #
Instances
SuppressUnusedWarnings (Zip5Sym2 a6989586621680094059 a6989586621680094058 c6989586621680092390 d6989586621680092391 e6989586621680092392 :: TyFun [c6989586621680092390] ([d6989586621680092391] ~> ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym2 a6989586621680094059 a6989586621680094058 c6989586621680092390 d6989586621680092391 e6989586621680092392 :: TyFun [c6989586621680092390] ([d6989586621680092391] ~> ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)])) -> Type) (a6989586621680094060 :: [c6989586621680092390]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym2 a6989586621680094059 a6989586621680094058 c6989586621680092390 d6989586621680092391 e6989586621680092392 :: TyFun [c6989586621680092390] ([d6989586621680092391] ~> ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)])) -> Type) (a6989586621680094060 :: [c6989586621680092390]) = Zip5Sym3 a6989586621680094059 a6989586621680094058 a6989586621680094060 d6989586621680092391 e6989586621680092392 :: TyFun [d6989586621680092391] ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]) -> Type |
data Zip5Sym3 (a6989586621680094058 :: [a6989586621680092388]) (a6989586621680094059 :: [b6989586621680092389]) (a6989586621680094060 :: [c6989586621680092390]) :: forall d6989586621680092391 e6989586621680092392. (~>) [d6989586621680092391] ((~>) [e6989586621680092392] [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]) Source #
Instances
SuppressUnusedWarnings (Zip5Sym3 a6989586621680094060 a6989586621680094059 a6989586621680094058 d6989586621680092391 e6989586621680092392 :: TyFun [d6989586621680092391] ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym3 a6989586621680094060 a6989586621680094059 a6989586621680094058 d6989586621680092391 e6989586621680092392 :: TyFun [d6989586621680092391] ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]) -> Type) (a6989586621680094061 :: [d6989586621680092391]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip5Sym3 a6989586621680094060 a6989586621680094059 a6989586621680094058 d6989586621680092391 e6989586621680092392 :: TyFun [d6989586621680092391] ([e6989586621680092392] ~> [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)]) -> Type) (a6989586621680094061 :: [d6989586621680092391]) = Zip5Sym4 a6989586621680094060 a6989586621680094059 a6989586621680094058 a6989586621680094061 e6989586621680092392 :: TyFun [e6989586621680092392] [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)] -> Type |
data Zip5Sym4 (a6989586621680094058 :: [a6989586621680092388]) (a6989586621680094059 :: [b6989586621680092389]) (a6989586621680094060 :: [c6989586621680092390]) (a6989586621680094061 :: [d6989586621680092391]) :: forall e6989586621680092392. (~>) [e6989586621680092392] [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)] Source #
Instances
SuppressUnusedWarnings (Zip5Sym4 a6989586621680094061 a6989586621680094060 a6989586621680094059 a6989586621680094058 e6989586621680092392 :: TyFun [e6989586621680092392] [(a6989586621680092388, b6989586621680092389, c6989586621680092390, d6989586621680092391, e6989586621680092392)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip5Sym4 a6989586621680094061 a6989586621680094060 a6989586621680094059 a6989586621680094058 e :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621680094062 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type Zip5Sym5 (a6989586621680094058 :: [a6989586621680092388]) (a6989586621680094059 :: [b6989586621680092389]) (a6989586621680094060 :: [c6989586621680092390]) (a6989586621680094061 :: [d6989586621680092391]) (a6989586621680094062 :: [e6989586621680092392]) = Zip5 a6989586621680094058 a6989586621680094059 a6989586621680094060 a6989586621680094061 a6989586621680094062 Source #
data Zip6Sym0 :: forall a6989586621680092382 b6989586621680092383 c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387. (~>) [a6989586621680092382] ((~>) [b6989586621680092383] ((~>) [c6989586621680092384] ((~>) [d6989586621680092385] ((~>) [e6989586621680092386] ((~>) [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]))))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a6989586621680092382] ([b6989586621680092383] ~> ([c6989586621680092384] ~> ([d6989586621680092385] ~> ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym0 :: TyFun [a6989586621680092382] ([b6989586621680092383] ~> ([c6989586621680092384] ~> ([d6989586621680092385] ~> ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]))))) -> Type) (a6989586621680094030 :: [a6989586621680092382]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym0 :: TyFun [a6989586621680092382] ([b6989586621680092383] ~> ([c6989586621680092384] ~> ([d6989586621680092385] ~> ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]))))) -> Type) (a6989586621680094030 :: [a6989586621680092382]) = Zip6Sym1 a6989586621680094030 b6989586621680092383 c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387 :: TyFun [b6989586621680092383] ([c6989586621680092384] ~> ([d6989586621680092385] ~> ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])))) -> Type |
data Zip6Sym1 (a6989586621680094030 :: [a6989586621680092382]) :: forall b6989586621680092383 c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387. (~>) [b6989586621680092383] ((~>) [c6989586621680092384] ((~>) [d6989586621680092385] ((~>) [e6989586621680092386] ((~>) [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym1 a6989586621680094030 b6989586621680092383 c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387 :: TyFun [b6989586621680092383] ([c6989586621680092384] ~> ([d6989586621680092385] ~> ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym1 a6989586621680094030 b6989586621680092383 c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387 :: TyFun [b6989586621680092383] ([c6989586621680092384] ~> ([d6989586621680092385] ~> ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])))) -> Type) (a6989586621680094031 :: [b6989586621680092383]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym1 a6989586621680094030 b6989586621680092383 c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387 :: TyFun [b6989586621680092383] ([c6989586621680092384] ~> ([d6989586621680092385] ~> ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])))) -> Type) (a6989586621680094031 :: [b6989586621680092383]) = Zip6Sym2 a6989586621680094030 a6989586621680094031 c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387 :: TyFun [c6989586621680092384] ([d6989586621680092385] ~> ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]))) -> Type |
data Zip6Sym2 (a6989586621680094030 :: [a6989586621680092382]) (a6989586621680094031 :: [b6989586621680092383]) :: forall c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387. (~>) [c6989586621680092384] ((~>) [d6989586621680092385] ((~>) [e6989586621680092386] ((~>) [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym2 a6989586621680094031 a6989586621680094030 c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387 :: TyFun [c6989586621680092384] ([d6989586621680092385] ~> ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym2 a6989586621680094031 a6989586621680094030 c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387 :: TyFun [c6989586621680092384] ([d6989586621680092385] ~> ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]))) -> Type) (a6989586621680094032 :: [c6989586621680092384]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym2 a6989586621680094031 a6989586621680094030 c6989586621680092384 d6989586621680092385 e6989586621680092386 f6989586621680092387 :: TyFun [c6989586621680092384] ([d6989586621680092385] ~> ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]))) -> Type) (a6989586621680094032 :: [c6989586621680092384]) = Zip6Sym3 a6989586621680094031 a6989586621680094030 a6989586621680094032 d6989586621680092385 e6989586621680092386 f6989586621680092387 :: TyFun [d6989586621680092385] ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])) -> Type |
data Zip6Sym3 (a6989586621680094030 :: [a6989586621680092382]) (a6989586621680094031 :: [b6989586621680092383]) (a6989586621680094032 :: [c6989586621680092384]) :: forall d6989586621680092385 e6989586621680092386 f6989586621680092387. (~>) [d6989586621680092385] ((~>) [e6989586621680092386] ((~>) [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])) Source #
Instances
SuppressUnusedWarnings (Zip6Sym3 a6989586621680094032 a6989586621680094031 a6989586621680094030 d6989586621680092385 e6989586621680092386 f6989586621680092387 :: TyFun [d6989586621680092385] ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym3 a6989586621680094032 a6989586621680094031 a6989586621680094030 d6989586621680092385 e6989586621680092386 f6989586621680092387 :: TyFun [d6989586621680092385] ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])) -> Type) (a6989586621680094033 :: [d6989586621680092385]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym3 a6989586621680094032 a6989586621680094031 a6989586621680094030 d6989586621680092385 e6989586621680092386 f6989586621680092387 :: TyFun [d6989586621680092385] ([e6989586621680092386] ~> ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)])) -> Type) (a6989586621680094033 :: [d6989586621680092385]) = Zip6Sym4 a6989586621680094032 a6989586621680094031 a6989586621680094030 a6989586621680094033 e6989586621680092386 f6989586621680092387 :: TyFun [e6989586621680092386] ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]) -> Type |
data Zip6Sym4 (a6989586621680094030 :: [a6989586621680092382]) (a6989586621680094031 :: [b6989586621680092383]) (a6989586621680094032 :: [c6989586621680092384]) (a6989586621680094033 :: [d6989586621680092385]) :: forall e6989586621680092386 f6989586621680092387. (~>) [e6989586621680092386] ((~>) [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]) Source #
Instances
SuppressUnusedWarnings (Zip6Sym4 a6989586621680094033 a6989586621680094032 a6989586621680094031 a6989586621680094030 e6989586621680092386 f6989586621680092387 :: TyFun [e6989586621680092386] ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym4 a6989586621680094033 a6989586621680094032 a6989586621680094031 a6989586621680094030 e6989586621680092386 f6989586621680092387 :: TyFun [e6989586621680092386] ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]) -> Type) (a6989586621680094034 :: [e6989586621680092386]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym4 a6989586621680094033 a6989586621680094032 a6989586621680094031 a6989586621680094030 e6989586621680092386 f6989586621680092387 :: TyFun [e6989586621680092386] ([f6989586621680092387] ~> [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)]) -> Type) (a6989586621680094034 :: [e6989586621680092386]) = Zip6Sym5 a6989586621680094033 a6989586621680094032 a6989586621680094031 a6989586621680094030 a6989586621680094034 f6989586621680092387 :: TyFun [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)] -> Type |
data Zip6Sym5 (a6989586621680094030 :: [a6989586621680092382]) (a6989586621680094031 :: [b6989586621680092383]) (a6989586621680094032 :: [c6989586621680092384]) (a6989586621680094033 :: [d6989586621680092385]) (a6989586621680094034 :: [e6989586621680092386]) :: forall f6989586621680092387. (~>) [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)] Source #
Instances
SuppressUnusedWarnings (Zip6Sym5 a6989586621680094034 a6989586621680094033 a6989586621680094032 a6989586621680094031 a6989586621680094030 f6989586621680092387 :: TyFun [f6989586621680092387] [(a6989586621680092382, b6989586621680092383, c6989586621680092384, d6989586621680092385, e6989586621680092386, f6989586621680092387)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip6Sym5 a6989586621680094034 a6989586621680094033 a6989586621680094032 a6989586621680094031 a6989586621680094030 f :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680094035 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym5 a6989586621680094034 a6989586621680094033 a6989586621680094032 a6989586621680094031 a6989586621680094030 f :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680094035 :: [f]) = Zip6 a6989586621680094034 a6989586621680094033 a6989586621680094032 a6989586621680094031 a6989586621680094030 a6989586621680094035 |
type Zip6Sym6 (a6989586621680094030 :: [a6989586621680092382]) (a6989586621680094031 :: [b6989586621680092383]) (a6989586621680094032 :: [c6989586621680092384]) (a6989586621680094033 :: [d6989586621680092385]) (a6989586621680094034 :: [e6989586621680092386]) (a6989586621680094035 :: [f6989586621680092387]) = Zip6 a6989586621680094030 a6989586621680094031 a6989586621680094032 a6989586621680094033 a6989586621680094034 a6989586621680094035 Source #
data Zip7Sym0 :: forall a6989586621680092375 b6989586621680092376 c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381. (~>) [a6989586621680092375] ((~>) [b6989586621680092376] ((~>) [c6989586621680092377] ((~>) [d6989586621680092378] ((~>) [e6989586621680092379] ((~>) [f6989586621680092380] ((~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])))))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a6989586621680092375] ([b6989586621680092376] ~> ([c6989586621680092377] ~> ([d6989586621680092378] ~> ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym0 :: TyFun [a6989586621680092375] ([b6989586621680092376] ~> ([c6989586621680092377] ~> ([d6989586621680092378] ~> ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])))))) -> Type) (a6989586621680093997 :: [a6989586621680092375]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym0 :: TyFun [a6989586621680092375] ([b6989586621680092376] ~> ([c6989586621680092377] ~> ([d6989586621680092378] ~> ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])))))) -> Type) (a6989586621680093997 :: [a6989586621680092375]) = Zip7Sym1 a6989586621680093997 b6989586621680092376 c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [b6989586621680092376] ([c6989586621680092377] ~> ([d6989586621680092378] ~> ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))))) -> Type |
data Zip7Sym1 (a6989586621680093997 :: [a6989586621680092375]) :: forall b6989586621680092376 c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381. (~>) [b6989586621680092376] ((~>) [c6989586621680092377] ((~>) [d6989586621680092378] ((~>) [e6989586621680092379] ((~>) [f6989586621680092380] ((~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym1 a6989586621680093997 b6989586621680092376 c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [b6989586621680092376] ([c6989586621680092377] ~> ([d6989586621680092378] ~> ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym1 a6989586621680093997 b6989586621680092376 c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [b6989586621680092376] ([c6989586621680092377] ~> ([d6989586621680092378] ~> ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))))) -> Type) (a6989586621680093998 :: [b6989586621680092376]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym1 a6989586621680093997 b6989586621680092376 c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [b6989586621680092376] ([c6989586621680092377] ~> ([d6989586621680092378] ~> ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))))) -> Type) (a6989586621680093998 :: [b6989586621680092376]) = Zip7Sym2 a6989586621680093997 a6989586621680093998 c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [c6989586621680092377] ([d6989586621680092378] ~> ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])))) -> Type |
data Zip7Sym2 (a6989586621680093997 :: [a6989586621680092375]) (a6989586621680093998 :: [b6989586621680092376]) :: forall c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381. (~>) [c6989586621680092377] ((~>) [d6989586621680092378] ((~>) [e6989586621680092379] ((~>) [f6989586621680092380] ((~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym2 a6989586621680093998 a6989586621680093997 c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [c6989586621680092377] ([d6989586621680092378] ~> ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym2 a6989586621680093998 a6989586621680093997 c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [c6989586621680092377] ([d6989586621680092378] ~> ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])))) -> Type) (a6989586621680093999 :: [c6989586621680092377]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym2 a6989586621680093998 a6989586621680093997 c6989586621680092377 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [c6989586621680092377] ([d6989586621680092378] ~> ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])))) -> Type) (a6989586621680093999 :: [c6989586621680092377]) = Zip7Sym3 a6989586621680093998 a6989586621680093997 a6989586621680093999 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [d6989586621680092378] ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))) -> Type |
data Zip7Sym3 (a6989586621680093997 :: [a6989586621680092375]) (a6989586621680093998 :: [b6989586621680092376]) (a6989586621680093999 :: [c6989586621680092377]) :: forall d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381. (~>) [d6989586621680092378] ((~>) [e6989586621680092379] ((~>) [f6989586621680092380] ((~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym3 a6989586621680093999 a6989586621680093998 a6989586621680093997 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [d6989586621680092378] ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym3 a6989586621680093999 a6989586621680093998 a6989586621680093997 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [d6989586621680092378] ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))) -> Type) (a6989586621680094000 :: [d6989586621680092378]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym3 a6989586621680093999 a6989586621680093998 a6989586621680093997 d6989586621680092378 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [d6989586621680092378] ([e6989586621680092379] ~> ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]))) -> Type) (a6989586621680094000 :: [d6989586621680092378]) = Zip7Sym4 a6989586621680093999 a6989586621680093998 a6989586621680093997 a6989586621680094000 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [e6989586621680092379] ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])) -> Type |
data Zip7Sym4 (a6989586621680093997 :: [a6989586621680092375]) (a6989586621680093998 :: [b6989586621680092376]) (a6989586621680093999 :: [c6989586621680092377]) (a6989586621680094000 :: [d6989586621680092378]) :: forall e6989586621680092379 f6989586621680092380 g6989586621680092381. (~>) [e6989586621680092379] ((~>) [f6989586621680092380] ((~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])) Source #
Instances
SuppressUnusedWarnings (Zip7Sym4 a6989586621680094000 a6989586621680093999 a6989586621680093998 a6989586621680093997 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [e6989586621680092379] ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym4 a6989586621680094000 a6989586621680093999 a6989586621680093998 a6989586621680093997 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [e6989586621680092379] ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])) -> Type) (a6989586621680094001 :: [e6989586621680092379]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym4 a6989586621680094000 a6989586621680093999 a6989586621680093998 a6989586621680093997 e6989586621680092379 f6989586621680092380 g6989586621680092381 :: TyFun [e6989586621680092379] ([f6989586621680092380] ~> ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)])) -> Type) (a6989586621680094001 :: [e6989586621680092379]) = Zip7Sym5 a6989586621680094000 a6989586621680093999 a6989586621680093998 a6989586621680093997 a6989586621680094001 f6989586621680092380 g6989586621680092381 :: TyFun [f6989586621680092380] ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]) -> Type |
data Zip7Sym5 (a6989586621680093997 :: [a6989586621680092375]) (a6989586621680093998 :: [b6989586621680092376]) (a6989586621680093999 :: [c6989586621680092377]) (a6989586621680094000 :: [d6989586621680092378]) (a6989586621680094001 :: [e6989586621680092379]) :: forall f6989586621680092380 g6989586621680092381. (~>) [f6989586621680092380] ((~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]) Source #
Instances
SuppressUnusedWarnings (Zip7Sym5 a6989586621680094001 a6989586621680094000 a6989586621680093999 a6989586621680093998 a6989586621680093997 f6989586621680092380 g6989586621680092381 :: TyFun [f6989586621680092380] ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym5 a6989586621680094001 a6989586621680094000 a6989586621680093999 a6989586621680093998 a6989586621680093997 f6989586621680092380 g6989586621680092381 :: TyFun [f6989586621680092380] ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]) -> Type) (a6989586621680094002 :: [f6989586621680092380]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym5 a6989586621680094001 a6989586621680094000 a6989586621680093999 a6989586621680093998 a6989586621680093997 f6989586621680092380 g6989586621680092381 :: TyFun [f6989586621680092380] ([g6989586621680092381] ~> [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)]) -> Type) (a6989586621680094002 :: [f6989586621680092380]) = Zip7Sym6 a6989586621680094001 a6989586621680094000 a6989586621680093999 a6989586621680093998 a6989586621680093997 a6989586621680094002 g6989586621680092381 :: TyFun [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)] -> Type |
data Zip7Sym6 (a6989586621680093997 :: [a6989586621680092375]) (a6989586621680093998 :: [b6989586621680092376]) (a6989586621680093999 :: [c6989586621680092377]) (a6989586621680094000 :: [d6989586621680092378]) (a6989586621680094001 :: [e6989586621680092379]) (a6989586621680094002 :: [f6989586621680092380]) :: forall g6989586621680092381. (~>) [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)] Source #
Instances
SuppressUnusedWarnings (Zip7Sym6 a6989586621680094002 a6989586621680094001 a6989586621680094000 a6989586621680093999 a6989586621680093998 a6989586621680093997 g6989586621680092381 :: TyFun [g6989586621680092381] [(a6989586621680092375, b6989586621680092376, c6989586621680092377, d6989586621680092378, e6989586621680092379, f6989586621680092380, g6989586621680092381)] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Zip7Sym6 a6989586621680094002 a6989586621680094001 a6989586621680094000 a6989586621680093999 a6989586621680093998 a6989586621680093997 g :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680094003 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym6 a6989586621680094002 a6989586621680094001 a6989586621680094000 a6989586621680093999 a6989586621680093998 a6989586621680093997 g :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680094003 :: [g]) = Zip7 a6989586621680094002 a6989586621680094001 a6989586621680094000 a6989586621680093999 a6989586621680093998 a6989586621680093997 a6989586621680094003 |
type Zip7Sym7 (a6989586621680093997 :: [a6989586621680092375]) (a6989586621680093998 :: [b6989586621680092376]) (a6989586621680093999 :: [c6989586621680092377]) (a6989586621680094000 :: [d6989586621680092378]) (a6989586621680094001 :: [e6989586621680092379]) (a6989586621680094002 :: [f6989586621680092380]) (a6989586621680094003 :: [g6989586621680092381]) = Zip7 a6989586621680093997 a6989586621680093998 a6989586621680093999 a6989586621680094000 a6989586621680094001 a6989586621680094002 a6989586621680094003 Source #
data ZipWithSym0 :: forall a6989586621679970259 b6989586621679970260 c6989586621679970261. (~>) ((~>) a6989586621679970259 ((~>) b6989586621679970260 c6989586621679970261)) ((~>) [a6989586621679970259] ((~>) [b6989586621679970260] [c6989586621679970261])) 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 (a6989586621679970259 ~> (b6989586621679970260 ~> c6989586621679970261)) ([a6989586621679970259] ~> ([b6989586621679970260] ~> [c6989586621679970261])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym0 :: TyFun (a6989586621679970259 ~> (b6989586621679970260 ~> c6989586621679970261)) ([a6989586621679970259] ~> ([b6989586621679970260] ~> [c6989586621679970261])) -> Type) (a6989586621679975106 :: a6989586621679970259 ~> (b6989586621679970260 ~> c6989586621679970261)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym0 :: TyFun (a6989586621679970259 ~> (b6989586621679970260 ~> c6989586621679970261)) ([a6989586621679970259] ~> ([b6989586621679970260] ~> [c6989586621679970261])) -> Type) (a6989586621679975106 :: a6989586621679970259 ~> (b6989586621679970260 ~> c6989586621679970261)) = ZipWithSym1 a6989586621679975106 |
data ZipWithSym1 (a6989586621679975106 :: (~>) a6989586621679970259 ((~>) b6989586621679970260 c6989586621679970261)) :: (~>) [a6989586621679970259] ((~>) [b6989586621679970260] [c6989586621679970261]) 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 a6989586621679975106 :: TyFun [a6989586621679970259] ([b6989586621679970260] ~> [c6989586621679970261]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym1 a6989586621679975106 :: TyFun [a6989586621679970259] ([b6989586621679970260] ~> [c6989586621679970261]) -> Type) (a6989586621679975107 :: [a6989586621679970259]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym1 a6989586621679975106 :: TyFun [a6989586621679970259] ([b6989586621679970260] ~> [c6989586621679970261]) -> Type) (a6989586621679975107 :: [a6989586621679970259]) = ZipWithSym2 a6989586621679975106 a6989586621679975107 |
data ZipWithSym2 (a6989586621679975106 :: (~>) a6989586621679970259 ((~>) b6989586621679970260 c6989586621679970261)) (a6989586621679975107 :: [a6989586621679970259]) :: (~>) [b6989586621679970260] [c6989586621679970261] 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 a6989586621679975107 a6989586621679975106 :: TyFun [b6989586621679970260] [c6989586621679970261] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWithSym2 a6989586621679975107 a6989586621679975106 :: TyFun [b] [c] -> Type) (a6989586621679975108 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym2 a6989586621679975107 a6989586621679975106 :: TyFun [b] [c] -> Type) (a6989586621679975108 :: [b]) = ZipWith a6989586621679975107 a6989586621679975106 a6989586621679975108 |
type ZipWithSym3 (a6989586621679975106 :: (~>) a6989586621679970259 ((~>) b6989586621679970260 c6989586621679970261)) (a6989586621679975107 :: [a6989586621679970259]) (a6989586621679975108 :: [b6989586621679970260]) = ZipWith a6989586621679975106 a6989586621679975107 a6989586621679975108 Source #
data ZipWith3Sym0 :: forall a6989586621679970255 b6989586621679970256 c6989586621679970257 d6989586621679970258. (~>) ((~>) a6989586621679970255 ((~>) b6989586621679970256 ((~>) c6989586621679970257 d6989586621679970258))) ((~>) [a6989586621679970255] ((~>) [b6989586621679970256] ((~>) [c6989586621679970257] [d6989586621679970258]))) 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 (a6989586621679970255 ~> (b6989586621679970256 ~> (c6989586621679970257 ~> d6989586621679970258))) ([a6989586621679970255] ~> ([b6989586621679970256] ~> ([c6989586621679970257] ~> [d6989586621679970258]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym0 :: TyFun (a6989586621679970255 ~> (b6989586621679970256 ~> (c6989586621679970257 ~> d6989586621679970258))) ([a6989586621679970255] ~> ([b6989586621679970256] ~> ([c6989586621679970257] ~> [d6989586621679970258]))) -> Type) (a6989586621679975091 :: a6989586621679970255 ~> (b6989586621679970256 ~> (c6989586621679970257 ~> d6989586621679970258))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym0 :: TyFun (a6989586621679970255 ~> (b6989586621679970256 ~> (c6989586621679970257 ~> d6989586621679970258))) ([a6989586621679970255] ~> ([b6989586621679970256] ~> ([c6989586621679970257] ~> [d6989586621679970258]))) -> Type) (a6989586621679975091 :: a6989586621679970255 ~> (b6989586621679970256 ~> (c6989586621679970257 ~> d6989586621679970258))) = ZipWith3Sym1 a6989586621679975091 |
data ZipWith3Sym1 (a6989586621679975091 :: (~>) a6989586621679970255 ((~>) b6989586621679970256 ((~>) c6989586621679970257 d6989586621679970258))) :: (~>) [a6989586621679970255] ((~>) [b6989586621679970256] ((~>) [c6989586621679970257] [d6989586621679970258])) 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 a6989586621679975091 :: TyFun [a6989586621679970255] ([b6989586621679970256] ~> ([c6989586621679970257] ~> [d6989586621679970258])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym1 a6989586621679975091 :: TyFun [a6989586621679970255] ([b6989586621679970256] ~> ([c6989586621679970257] ~> [d6989586621679970258])) -> Type) (a6989586621679975092 :: [a6989586621679970255]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym1 a6989586621679975091 :: TyFun [a6989586621679970255] ([b6989586621679970256] ~> ([c6989586621679970257] ~> [d6989586621679970258])) -> Type) (a6989586621679975092 :: [a6989586621679970255]) = ZipWith3Sym2 a6989586621679975091 a6989586621679975092 |
data ZipWith3Sym2 (a6989586621679975091 :: (~>) a6989586621679970255 ((~>) b6989586621679970256 ((~>) c6989586621679970257 d6989586621679970258))) (a6989586621679975092 :: [a6989586621679970255]) :: (~>) [b6989586621679970256] ((~>) [c6989586621679970257] [d6989586621679970258]) 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 a6989586621679975092 a6989586621679975091 :: TyFun [b6989586621679970256] ([c6989586621679970257] ~> [d6989586621679970258]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym2 a6989586621679975092 a6989586621679975091 :: TyFun [b6989586621679970256] ([c6989586621679970257] ~> [d6989586621679970258]) -> Type) (a6989586621679975093 :: [b6989586621679970256]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym2 a6989586621679975092 a6989586621679975091 :: TyFun [b6989586621679970256] ([c6989586621679970257] ~> [d6989586621679970258]) -> Type) (a6989586621679975093 :: [b6989586621679970256]) = ZipWith3Sym3 a6989586621679975092 a6989586621679975091 a6989586621679975093 |
data ZipWith3Sym3 (a6989586621679975091 :: (~>) a6989586621679970255 ((~>) b6989586621679970256 ((~>) c6989586621679970257 d6989586621679970258))) (a6989586621679975092 :: [a6989586621679970255]) (a6989586621679975093 :: [b6989586621679970256]) :: (~>) [c6989586621679970257] [d6989586621679970258] 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 a6989586621679975093 a6989586621679975092 a6989586621679975091 :: TyFun [c6989586621679970257] [d6989586621679970258] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith3Sym3 a6989586621679975093 a6989586621679975092 a6989586621679975091 :: TyFun [c] [d] -> Type) (a6989586621679975094 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym3 a6989586621679975093 a6989586621679975092 a6989586621679975091 :: TyFun [c] [d] -> Type) (a6989586621679975094 :: [c]) = ZipWith3 a6989586621679975093 a6989586621679975092 a6989586621679975091 a6989586621679975094 |
type ZipWith3Sym4 (a6989586621679975091 :: (~>) a6989586621679970255 ((~>) b6989586621679970256 ((~>) c6989586621679970257 d6989586621679970258))) (a6989586621679975092 :: [a6989586621679970255]) (a6989586621679975093 :: [b6989586621679970256]) (a6989586621679975094 :: [c6989586621679970257]) = ZipWith3 a6989586621679975091 a6989586621679975092 a6989586621679975093 a6989586621679975094 Source #
data ZipWith4Sym0 :: forall a6989586621680092370 b6989586621680092371 c6989586621680092372 d6989586621680092373 e6989586621680092374. (~>) ((~>) a6989586621680092370 ((~>) b6989586621680092371 ((~>) c6989586621680092372 ((~>) d6989586621680092373 e6989586621680092374)))) ((~>) [a6989586621680092370] ((~>) [b6989586621680092371] ((~>) [c6989586621680092372] ((~>) [d6989586621680092373] [e6989586621680092374])))) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (a6989586621680092370 ~> (b6989586621680092371 ~> (c6989586621680092372 ~> (d6989586621680092373 ~> e6989586621680092374)))) ([a6989586621680092370] ~> ([b6989586621680092371] ~> ([c6989586621680092372] ~> ([d6989586621680092373] ~> [e6989586621680092374])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym0 :: TyFun (a6989586621680092370 ~> (b6989586621680092371 ~> (c6989586621680092372 ~> (d6989586621680092373 ~> e6989586621680092374)))) ([a6989586621680092370] ~> ([b6989586621680092371] ~> ([c6989586621680092372] ~> ([d6989586621680092373] ~> [e6989586621680092374])))) -> Type) (a6989586621680093964 :: a6989586621680092370 ~> (b6989586621680092371 ~> (c6989586621680092372 ~> (d6989586621680092373 ~> e6989586621680092374)))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym0 :: TyFun (a6989586621680092370 ~> (b6989586621680092371 ~> (c6989586621680092372 ~> (d6989586621680092373 ~> e6989586621680092374)))) ([a6989586621680092370] ~> ([b6989586621680092371] ~> ([c6989586621680092372] ~> ([d6989586621680092373] ~> [e6989586621680092374])))) -> Type) (a6989586621680093964 :: a6989586621680092370 ~> (b6989586621680092371 ~> (c6989586621680092372 ~> (d6989586621680092373 ~> e6989586621680092374)))) = ZipWith4Sym1 a6989586621680093964 |
data ZipWith4Sym1 (a6989586621680093964 :: (~>) a6989586621680092370 ((~>) b6989586621680092371 ((~>) c6989586621680092372 ((~>) d6989586621680092373 e6989586621680092374)))) :: (~>) [a6989586621680092370] ((~>) [b6989586621680092371] ((~>) [c6989586621680092372] ((~>) [d6989586621680092373] [e6989586621680092374]))) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym1 a6989586621680093964 :: TyFun [a6989586621680092370] ([b6989586621680092371] ~> ([c6989586621680092372] ~> ([d6989586621680092373] ~> [e6989586621680092374]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym1 a6989586621680093964 :: TyFun [a6989586621680092370] ([b6989586621680092371] ~> ([c6989586621680092372] ~> ([d6989586621680092373] ~> [e6989586621680092374]))) -> Type) (a6989586621680093965 :: [a6989586621680092370]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym1 a6989586621680093964 :: TyFun [a6989586621680092370] ([b6989586621680092371] ~> ([c6989586621680092372] ~> ([d6989586621680092373] ~> [e6989586621680092374]))) -> Type) (a6989586621680093965 :: [a6989586621680092370]) = ZipWith4Sym2 a6989586621680093964 a6989586621680093965 |
data ZipWith4Sym2 (a6989586621680093964 :: (~>) a6989586621680092370 ((~>) b6989586621680092371 ((~>) c6989586621680092372 ((~>) d6989586621680092373 e6989586621680092374)))) (a6989586621680093965 :: [a6989586621680092370]) :: (~>) [b6989586621680092371] ((~>) [c6989586621680092372] ((~>) [d6989586621680092373] [e6989586621680092374])) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym2 a6989586621680093965 a6989586621680093964 :: TyFun [b6989586621680092371] ([c6989586621680092372] ~> ([d6989586621680092373] ~> [e6989586621680092374])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym2 a6989586621680093965 a6989586621680093964 :: TyFun [b6989586621680092371] ([c6989586621680092372] ~> ([d6989586621680092373] ~> [e6989586621680092374])) -> Type) (a6989586621680093966 :: [b6989586621680092371]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym2 a6989586621680093965 a6989586621680093964 :: TyFun [b6989586621680092371] ([c6989586621680092372] ~> ([d6989586621680092373] ~> [e6989586621680092374])) -> Type) (a6989586621680093966 :: [b6989586621680092371]) = ZipWith4Sym3 a6989586621680093965 a6989586621680093964 a6989586621680093966 |
data ZipWith4Sym3 (a6989586621680093964 :: (~>) a6989586621680092370 ((~>) b6989586621680092371 ((~>) c6989586621680092372 ((~>) d6989586621680092373 e6989586621680092374)))) (a6989586621680093965 :: [a6989586621680092370]) (a6989586621680093966 :: [b6989586621680092371]) :: (~>) [c6989586621680092372] ((~>) [d6989586621680092373] [e6989586621680092374]) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym3 a6989586621680093966 a6989586621680093965 a6989586621680093964 :: TyFun [c6989586621680092372] ([d6989586621680092373] ~> [e6989586621680092374]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym3 a6989586621680093966 a6989586621680093965 a6989586621680093964 :: TyFun [c6989586621680092372] ([d6989586621680092373] ~> [e6989586621680092374]) -> Type) (a6989586621680093967 :: [c6989586621680092372]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym3 a6989586621680093966 a6989586621680093965 a6989586621680093964 :: TyFun [c6989586621680092372] ([d6989586621680092373] ~> [e6989586621680092374]) -> Type) (a6989586621680093967 :: [c6989586621680092372]) = ZipWith4Sym4 a6989586621680093966 a6989586621680093965 a6989586621680093964 a6989586621680093967 |
data ZipWith4Sym4 (a6989586621680093964 :: (~>) a6989586621680092370 ((~>) b6989586621680092371 ((~>) c6989586621680092372 ((~>) d6989586621680092373 e6989586621680092374)))) (a6989586621680093965 :: [a6989586621680092370]) (a6989586621680093966 :: [b6989586621680092371]) (a6989586621680093967 :: [c6989586621680092372]) :: (~>) [d6989586621680092373] [e6989586621680092374] Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym4 a6989586621680093967 a6989586621680093966 a6989586621680093965 a6989586621680093964 :: TyFun [d6989586621680092373] [e6989586621680092374] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith4Sym4 a6989586621680093967 a6989586621680093966 a6989586621680093965 a6989586621680093964 :: TyFun [d] [e] -> Type) (a6989586621680093968 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym4 a6989586621680093967 a6989586621680093966 a6989586621680093965 a6989586621680093964 :: TyFun [d] [e] -> Type) (a6989586621680093968 :: [d]) = ZipWith4 a6989586621680093967 a6989586621680093966 a6989586621680093965 a6989586621680093964 a6989586621680093968 |
type ZipWith4Sym5 (a6989586621680093964 :: (~>) a6989586621680092370 ((~>) b6989586621680092371 ((~>) c6989586621680092372 ((~>) d6989586621680092373 e6989586621680092374)))) (a6989586621680093965 :: [a6989586621680092370]) (a6989586621680093966 :: [b6989586621680092371]) (a6989586621680093967 :: [c6989586621680092372]) (a6989586621680093968 :: [d6989586621680092373]) = ZipWith4 a6989586621680093964 a6989586621680093965 a6989586621680093966 a6989586621680093967 a6989586621680093968 Source #
data ZipWith5Sym0 :: forall a6989586621680092364 b6989586621680092365 c6989586621680092366 d6989586621680092367 e6989586621680092368 f6989586621680092369. (~>) ((~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) ((~>) [a6989586621680092364] ((~>) [b6989586621680092365] ((~>) [c6989586621680092366] ((~>) [d6989586621680092367] ((~>) [e6989586621680092368] [f6989586621680092369]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (a6989586621680092364 ~> (b6989586621680092365 ~> (c6989586621680092366 ~> (d6989586621680092367 ~> (e6989586621680092368 ~> f6989586621680092369))))) ([a6989586621680092364] ~> ([b6989586621680092365] ~> ([c6989586621680092366] ~> ([d6989586621680092367] ~> ([e6989586621680092368] ~> [f6989586621680092369]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym0 :: TyFun (a6989586621680092364 ~> (b6989586621680092365 ~> (c6989586621680092366 ~> (d6989586621680092367 ~> (e6989586621680092368 ~> f6989586621680092369))))) ([a6989586621680092364] ~> ([b6989586621680092365] ~> ([c6989586621680092366] ~> ([d6989586621680092367] ~> ([e6989586621680092368] ~> [f6989586621680092369]))))) -> Type) (a6989586621680093941 :: a6989586621680092364 ~> (b6989586621680092365 ~> (c6989586621680092366 ~> (d6989586621680092367 ~> (e6989586621680092368 ~> f6989586621680092369))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym0 :: TyFun (a6989586621680092364 ~> (b6989586621680092365 ~> (c6989586621680092366 ~> (d6989586621680092367 ~> (e6989586621680092368 ~> f6989586621680092369))))) ([a6989586621680092364] ~> ([b6989586621680092365] ~> ([c6989586621680092366] ~> ([d6989586621680092367] ~> ([e6989586621680092368] ~> [f6989586621680092369]))))) -> Type) (a6989586621680093941 :: a6989586621680092364 ~> (b6989586621680092365 ~> (c6989586621680092366 ~> (d6989586621680092367 ~> (e6989586621680092368 ~> f6989586621680092369))))) = ZipWith5Sym1 a6989586621680093941 |
data ZipWith5Sym1 (a6989586621680093941 :: (~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) :: (~>) [a6989586621680092364] ((~>) [b6989586621680092365] ((~>) [c6989586621680092366] ((~>) [d6989586621680092367] ((~>) [e6989586621680092368] [f6989586621680092369])))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym1 a6989586621680093941 :: TyFun [a6989586621680092364] ([b6989586621680092365] ~> ([c6989586621680092366] ~> ([d6989586621680092367] ~> ([e6989586621680092368] ~> [f6989586621680092369])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym1 a6989586621680093941 :: TyFun [a6989586621680092364] ([b6989586621680092365] ~> ([c6989586621680092366] ~> ([d6989586621680092367] ~> ([e6989586621680092368] ~> [f6989586621680092369])))) -> Type) (a6989586621680093942 :: [a6989586621680092364]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym1 a6989586621680093941 :: TyFun [a6989586621680092364] ([b6989586621680092365] ~> ([c6989586621680092366] ~> ([d6989586621680092367] ~> ([e6989586621680092368] ~> [f6989586621680092369])))) -> Type) (a6989586621680093942 :: [a6989586621680092364]) = ZipWith5Sym2 a6989586621680093941 a6989586621680093942 |
data ZipWith5Sym2 (a6989586621680093941 :: (~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) (a6989586621680093942 :: [a6989586621680092364]) :: (~>) [b6989586621680092365] ((~>) [c6989586621680092366] ((~>) [d6989586621680092367] ((~>) [e6989586621680092368] [f6989586621680092369]))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym2 a6989586621680093942 a6989586621680093941 :: TyFun [b6989586621680092365] ([c6989586621680092366] ~> ([d6989586621680092367] ~> ([e6989586621680092368] ~> [f6989586621680092369]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym2 a6989586621680093942 a6989586621680093941 :: TyFun [b6989586621680092365] ([c6989586621680092366] ~> ([d6989586621680092367] ~> ([e6989586621680092368] ~> [f6989586621680092369]))) -> Type) (a6989586621680093943 :: [b6989586621680092365]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym2 a6989586621680093942 a6989586621680093941 :: TyFun [b6989586621680092365] ([c6989586621680092366] ~> ([d6989586621680092367] ~> ([e6989586621680092368] ~> [f6989586621680092369]))) -> Type) (a6989586621680093943 :: [b6989586621680092365]) = ZipWith5Sym3 a6989586621680093942 a6989586621680093941 a6989586621680093943 |
data ZipWith5Sym3 (a6989586621680093941 :: (~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) (a6989586621680093942 :: [a6989586621680092364]) (a6989586621680093943 :: [b6989586621680092365]) :: (~>) [c6989586621680092366] ((~>) [d6989586621680092367] ((~>) [e6989586621680092368] [f6989586621680092369])) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym3 a6989586621680093943 a6989586621680093942 a6989586621680093941 :: TyFun [c6989586621680092366] ([d6989586621680092367] ~> ([e6989586621680092368] ~> [f6989586621680092369])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym3 a6989586621680093943 a6989586621680093942 a6989586621680093941 :: TyFun [c6989586621680092366] ([d6989586621680092367] ~> ([e6989586621680092368] ~> [f6989586621680092369])) -> Type) (a6989586621680093944 :: [c6989586621680092366]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym3 a6989586621680093943 a6989586621680093942 a6989586621680093941 :: TyFun [c6989586621680092366] ([d6989586621680092367] ~> ([e6989586621680092368] ~> [f6989586621680092369])) -> Type) (a6989586621680093944 :: [c6989586621680092366]) = ZipWith5Sym4 a6989586621680093943 a6989586621680093942 a6989586621680093941 a6989586621680093944 |
data ZipWith5Sym4 (a6989586621680093941 :: (~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) (a6989586621680093942 :: [a6989586621680092364]) (a6989586621680093943 :: [b6989586621680092365]) (a6989586621680093944 :: [c6989586621680092366]) :: (~>) [d6989586621680092367] ((~>) [e6989586621680092368] [f6989586621680092369]) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym4 a6989586621680093944 a6989586621680093943 a6989586621680093942 a6989586621680093941 :: TyFun [d6989586621680092367] ([e6989586621680092368] ~> [f6989586621680092369]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym4 a6989586621680093944 a6989586621680093943 a6989586621680093942 a6989586621680093941 :: TyFun [d6989586621680092367] ([e6989586621680092368] ~> [f6989586621680092369]) -> Type) (a6989586621680093945 :: [d6989586621680092367]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym4 a6989586621680093944 a6989586621680093943 a6989586621680093942 a6989586621680093941 :: TyFun [d6989586621680092367] ([e6989586621680092368] ~> [f6989586621680092369]) -> Type) (a6989586621680093945 :: [d6989586621680092367]) = ZipWith5Sym5 a6989586621680093944 a6989586621680093943 a6989586621680093942 a6989586621680093941 a6989586621680093945 |
data ZipWith5Sym5 (a6989586621680093941 :: (~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) (a6989586621680093942 :: [a6989586621680092364]) (a6989586621680093943 :: [b6989586621680092365]) (a6989586621680093944 :: [c6989586621680092366]) (a6989586621680093945 :: [d6989586621680092367]) :: (~>) [e6989586621680092368] [f6989586621680092369] Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym5 a6989586621680093945 a6989586621680093944 a6989586621680093943 a6989586621680093942 a6989586621680093941 :: TyFun [e6989586621680092368] [f6989586621680092369] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith5Sym5 a6989586621680093945 a6989586621680093944 a6989586621680093943 a6989586621680093942 a6989586621680093941 :: TyFun [e] [f] -> Type) (a6989586621680093946 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym5 a6989586621680093945 a6989586621680093944 a6989586621680093943 a6989586621680093942 a6989586621680093941 :: TyFun [e] [f] -> Type) (a6989586621680093946 :: [e]) = ZipWith5 a6989586621680093945 a6989586621680093944 a6989586621680093943 a6989586621680093942 a6989586621680093941 a6989586621680093946 |
type ZipWith5Sym6 (a6989586621680093941 :: (~>) a6989586621680092364 ((~>) b6989586621680092365 ((~>) c6989586621680092366 ((~>) d6989586621680092367 ((~>) e6989586621680092368 f6989586621680092369))))) (a6989586621680093942 :: [a6989586621680092364]) (a6989586621680093943 :: [b6989586621680092365]) (a6989586621680093944 :: [c6989586621680092366]) (a6989586621680093945 :: [d6989586621680092367]) (a6989586621680093946 :: [e6989586621680092368]) = ZipWith5 a6989586621680093941 a6989586621680093942 a6989586621680093943 a6989586621680093944 a6989586621680093945 a6989586621680093946 Source #
data ZipWith6Sym0 :: forall a6989586621680092357 b6989586621680092358 c6989586621680092359 d6989586621680092360 e6989586621680092361 f6989586621680092362 g6989586621680092363. (~>) ((~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) ((~>) [a6989586621680092357] ((~>) [b6989586621680092358] ((~>) [c6989586621680092359] ((~>) [d6989586621680092360] ((~>) [e6989586621680092361] ((~>) [f6989586621680092362] [g6989586621680092363])))))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (a6989586621680092357 ~> (b6989586621680092358 ~> (c6989586621680092359 ~> (d6989586621680092360 ~> (e6989586621680092361 ~> (f6989586621680092362 ~> g6989586621680092363)))))) ([a6989586621680092357] ~> ([b6989586621680092358] ~> ([c6989586621680092359] ~> ([d6989586621680092360] ~> ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym0 :: TyFun (a6989586621680092357 ~> (b6989586621680092358 ~> (c6989586621680092359 ~> (d6989586621680092360 ~> (e6989586621680092361 ~> (f6989586621680092362 ~> g6989586621680092363)))))) ([a6989586621680092357] ~> ([b6989586621680092358] ~> ([c6989586621680092359] ~> ([d6989586621680092360] ~> ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363])))))) -> Type) (a6989586621680093914 :: a6989586621680092357 ~> (b6989586621680092358 ~> (c6989586621680092359 ~> (d6989586621680092360 ~> (e6989586621680092361 ~> (f6989586621680092362 ~> g6989586621680092363)))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym0 :: TyFun (a6989586621680092357 ~> (b6989586621680092358 ~> (c6989586621680092359 ~> (d6989586621680092360 ~> (e6989586621680092361 ~> (f6989586621680092362 ~> g6989586621680092363)))))) ([a6989586621680092357] ~> ([b6989586621680092358] ~> ([c6989586621680092359] ~> ([d6989586621680092360] ~> ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363])))))) -> Type) (a6989586621680093914 :: a6989586621680092357 ~> (b6989586621680092358 ~> (c6989586621680092359 ~> (d6989586621680092360 ~> (e6989586621680092361 ~> (f6989586621680092362 ~> g6989586621680092363)))))) = ZipWith6Sym1 a6989586621680093914 |
data ZipWith6Sym1 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) :: (~>) [a6989586621680092357] ((~>) [b6989586621680092358] ((~>) [c6989586621680092359] ((~>) [d6989586621680092360] ((~>) [e6989586621680092361] ((~>) [f6989586621680092362] [g6989586621680092363]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym1 a6989586621680093914 :: TyFun [a6989586621680092357] ([b6989586621680092358] ~> ([c6989586621680092359] ~> ([d6989586621680092360] ~> ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym1 a6989586621680093914 :: TyFun [a6989586621680092357] ([b6989586621680092358] ~> ([c6989586621680092359] ~> ([d6989586621680092360] ~> ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363]))))) -> Type) (a6989586621680093915 :: [a6989586621680092357]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym1 a6989586621680093914 :: TyFun [a6989586621680092357] ([b6989586621680092358] ~> ([c6989586621680092359] ~> ([d6989586621680092360] ~> ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363]))))) -> Type) (a6989586621680093915 :: [a6989586621680092357]) = ZipWith6Sym2 a6989586621680093914 a6989586621680093915 |
data ZipWith6Sym2 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) (a6989586621680093915 :: [a6989586621680092357]) :: (~>) [b6989586621680092358] ((~>) [c6989586621680092359] ((~>) [d6989586621680092360] ((~>) [e6989586621680092361] ((~>) [f6989586621680092362] [g6989586621680092363])))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym2 a6989586621680093915 a6989586621680093914 :: TyFun [b6989586621680092358] ([c6989586621680092359] ~> ([d6989586621680092360] ~> ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym2 a6989586621680093915 a6989586621680093914 :: TyFun [b6989586621680092358] ([c6989586621680092359] ~> ([d6989586621680092360] ~> ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363])))) -> Type) (a6989586621680093916 :: [b6989586621680092358]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym2 a6989586621680093915 a6989586621680093914 :: TyFun [b6989586621680092358] ([c6989586621680092359] ~> ([d6989586621680092360] ~> ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363])))) -> Type) (a6989586621680093916 :: [b6989586621680092358]) = ZipWith6Sym3 a6989586621680093915 a6989586621680093914 a6989586621680093916 |
data ZipWith6Sym3 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) (a6989586621680093915 :: [a6989586621680092357]) (a6989586621680093916 :: [b6989586621680092358]) :: (~>) [c6989586621680092359] ((~>) [d6989586621680092360] ((~>) [e6989586621680092361] ((~>) [f6989586621680092362] [g6989586621680092363]))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym3 a6989586621680093916 a6989586621680093915 a6989586621680093914 :: TyFun [c6989586621680092359] ([d6989586621680092360] ~> ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym3 a6989586621680093916 a6989586621680093915 a6989586621680093914 :: TyFun [c6989586621680092359] ([d6989586621680092360] ~> ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363]))) -> Type) (a6989586621680093917 :: [c6989586621680092359]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym3 a6989586621680093916 a6989586621680093915 a6989586621680093914 :: TyFun [c6989586621680092359] ([d6989586621680092360] ~> ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363]))) -> Type) (a6989586621680093917 :: [c6989586621680092359]) = ZipWith6Sym4 a6989586621680093916 a6989586621680093915 a6989586621680093914 a6989586621680093917 |
data ZipWith6Sym4 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) (a6989586621680093915 :: [a6989586621680092357]) (a6989586621680093916 :: [b6989586621680092358]) (a6989586621680093917 :: [c6989586621680092359]) :: (~>) [d6989586621680092360] ((~>) [e6989586621680092361] ((~>) [f6989586621680092362] [g6989586621680092363])) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym4 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093914 :: TyFun [d6989586621680092360] ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym4 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093914 :: TyFun [d6989586621680092360] ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363])) -> Type) (a6989586621680093918 :: [d6989586621680092360]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym4 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093914 :: TyFun [d6989586621680092360] ([e6989586621680092361] ~> ([f6989586621680092362] ~> [g6989586621680092363])) -> Type) (a6989586621680093918 :: [d6989586621680092360]) = ZipWith6Sym5 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093914 a6989586621680093918 |
data ZipWith6Sym5 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) (a6989586621680093915 :: [a6989586621680092357]) (a6989586621680093916 :: [b6989586621680092358]) (a6989586621680093917 :: [c6989586621680092359]) (a6989586621680093918 :: [d6989586621680092360]) :: (~>) [e6989586621680092361] ((~>) [f6989586621680092362] [g6989586621680092363]) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym5 a6989586621680093918 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093914 :: TyFun [e6989586621680092361] ([f6989586621680092362] ~> [g6989586621680092363]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym5 a6989586621680093918 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093914 :: TyFun [e6989586621680092361] ([f6989586621680092362] ~> [g6989586621680092363]) -> Type) (a6989586621680093919 :: [e6989586621680092361]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym5 a6989586621680093918 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093914 :: TyFun [e6989586621680092361] ([f6989586621680092362] ~> [g6989586621680092363]) -> Type) (a6989586621680093919 :: [e6989586621680092361]) = ZipWith6Sym6 a6989586621680093918 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093914 a6989586621680093919 |
data ZipWith6Sym6 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) (a6989586621680093915 :: [a6989586621680092357]) (a6989586621680093916 :: [b6989586621680092358]) (a6989586621680093917 :: [c6989586621680092359]) (a6989586621680093918 :: [d6989586621680092360]) (a6989586621680093919 :: [e6989586621680092361]) :: (~>) [f6989586621680092362] [g6989586621680092363] Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym6 a6989586621680093919 a6989586621680093918 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093914 :: TyFun [f6989586621680092362] [g6989586621680092363] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith6Sym6 a6989586621680093919 a6989586621680093918 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093914 :: TyFun [f] [g] -> Type) (a6989586621680093920 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym6 a6989586621680093919 a6989586621680093918 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093914 :: TyFun [f] [g] -> Type) (a6989586621680093920 :: [f]) = ZipWith6 a6989586621680093919 a6989586621680093918 a6989586621680093917 a6989586621680093916 a6989586621680093915 a6989586621680093914 a6989586621680093920 |
type ZipWith6Sym7 (a6989586621680093914 :: (~>) a6989586621680092357 ((~>) b6989586621680092358 ((~>) c6989586621680092359 ((~>) d6989586621680092360 ((~>) e6989586621680092361 ((~>) f6989586621680092362 g6989586621680092363)))))) (a6989586621680093915 :: [a6989586621680092357]) (a6989586621680093916 :: [b6989586621680092358]) (a6989586621680093917 :: [c6989586621680092359]) (a6989586621680093918 :: [d6989586621680092360]) (a6989586621680093919 :: [e6989586621680092361]) (a6989586621680093920 :: [f6989586621680092362]) = ZipWith6 a6989586621680093914 a6989586621680093915 a6989586621680093916 a6989586621680093917 a6989586621680093918 a6989586621680093919 a6989586621680093920 Source #
data ZipWith7Sym0 :: forall a6989586621680092349 b6989586621680092350 c6989586621680092351 d6989586621680092352 e6989586621680092353 f6989586621680092354 g6989586621680092355 h6989586621680092356. (~>) ((~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) ((~>) [a6989586621680092349] ((~>) [b6989586621680092350] ((~>) [c6989586621680092351] ((~>) [d6989586621680092352] ((~>) [e6989586621680092353] ((~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356]))))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym0 :: TyFun (a6989586621680092349 ~> (b6989586621680092350 ~> (c6989586621680092351 ~> (d6989586621680092352 ~> (e6989586621680092353 ~> (f6989586621680092354 ~> (g6989586621680092355 ~> h6989586621680092356))))))) ([a6989586621680092349] ~> ([b6989586621680092350] ~> ([c6989586621680092351] ~> ([d6989586621680092352] ~> ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356]))))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym0 :: TyFun (a6989586621680092349 ~> (b6989586621680092350 ~> (c6989586621680092351 ~> (d6989586621680092352 ~> (e6989586621680092353 ~> (f6989586621680092354 ~> (g6989586621680092355 ~> h6989586621680092356))))))) ([a6989586621680092349] ~> ([b6989586621680092350] ~> ([c6989586621680092351] ~> ([d6989586621680092352] ~> ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356]))))))) -> Type) (a6989586621680093883 :: a6989586621680092349 ~> (b6989586621680092350 ~> (c6989586621680092351 ~> (d6989586621680092352 ~> (e6989586621680092353 ~> (f6989586621680092354 ~> (g6989586621680092355 ~> h6989586621680092356))))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym0 :: TyFun (a6989586621680092349 ~> (b6989586621680092350 ~> (c6989586621680092351 ~> (d6989586621680092352 ~> (e6989586621680092353 ~> (f6989586621680092354 ~> (g6989586621680092355 ~> h6989586621680092356))))))) ([a6989586621680092349] ~> ([b6989586621680092350] ~> ([c6989586621680092351] ~> ([d6989586621680092352] ~> ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356]))))))) -> Type) (a6989586621680093883 :: a6989586621680092349 ~> (b6989586621680092350 ~> (c6989586621680092351 ~> (d6989586621680092352 ~> (e6989586621680092353 ~> (f6989586621680092354 ~> (g6989586621680092355 ~> h6989586621680092356))))))) = ZipWith7Sym1 a6989586621680093883 |
data ZipWith7Sym1 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) :: (~>) [a6989586621680092349] ((~>) [b6989586621680092350] ((~>) [c6989586621680092351] ((~>) [d6989586621680092352] ((~>) [e6989586621680092353] ((~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356])))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym1 a6989586621680093883 :: TyFun [a6989586621680092349] ([b6989586621680092350] ~> ([c6989586621680092351] ~> ([d6989586621680092352] ~> ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356])))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym1 a6989586621680093883 :: TyFun [a6989586621680092349] ([b6989586621680092350] ~> ([c6989586621680092351] ~> ([d6989586621680092352] ~> ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356])))))) -> Type) (a6989586621680093884 :: [a6989586621680092349]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym1 a6989586621680093883 :: TyFun [a6989586621680092349] ([b6989586621680092350] ~> ([c6989586621680092351] ~> ([d6989586621680092352] ~> ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356])))))) -> Type) (a6989586621680093884 :: [a6989586621680092349]) = ZipWith7Sym2 a6989586621680093883 a6989586621680093884 |
data ZipWith7Sym2 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) :: (~>) [b6989586621680092350] ((~>) [c6989586621680092351] ((~>) [d6989586621680092352] ((~>) [e6989586621680092353] ((~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym2 a6989586621680093884 a6989586621680093883 :: TyFun [b6989586621680092350] ([c6989586621680092351] ~> ([d6989586621680092352] ~> ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356]))))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym2 a6989586621680093884 a6989586621680093883 :: TyFun [b6989586621680092350] ([c6989586621680092351] ~> ([d6989586621680092352] ~> ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356]))))) -> Type) (a6989586621680093885 :: [b6989586621680092350]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym2 a6989586621680093884 a6989586621680093883 :: TyFun [b6989586621680092350] ([c6989586621680092351] ~> ([d6989586621680092352] ~> ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356]))))) -> Type) (a6989586621680093885 :: [b6989586621680092350]) = ZipWith7Sym3 a6989586621680093884 a6989586621680093883 a6989586621680093885 |
data ZipWith7Sym3 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) (a6989586621680093885 :: [b6989586621680092350]) :: (~>) [c6989586621680092351] ((~>) [d6989586621680092352] ((~>) [e6989586621680092353] ((~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356])))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym3 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [c6989586621680092351] ([d6989586621680092352] ~> ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356])))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym3 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [c6989586621680092351] ([d6989586621680092352] ~> ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356])))) -> Type) (a6989586621680093886 :: [c6989586621680092351]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym3 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [c6989586621680092351] ([d6989586621680092352] ~> ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356])))) -> Type) (a6989586621680093886 :: [c6989586621680092351]) = ZipWith7Sym4 a6989586621680093885 a6989586621680093884 a6989586621680093883 a6989586621680093886 |
data ZipWith7Sym4 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) (a6989586621680093885 :: [b6989586621680092350]) (a6989586621680093886 :: [c6989586621680092351]) :: (~>) [d6989586621680092352] ((~>) [e6989586621680092353] ((~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356]))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym4 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [d6989586621680092352] ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356]))) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym4 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [d6989586621680092352] ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356]))) -> Type) (a6989586621680093887 :: [d6989586621680092352]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym4 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [d6989586621680092352] ([e6989586621680092353] ~> ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356]))) -> Type) (a6989586621680093887 :: [d6989586621680092352]) = ZipWith7Sym5 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 a6989586621680093887 |
data ZipWith7Sym5 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) (a6989586621680093885 :: [b6989586621680092350]) (a6989586621680093886 :: [c6989586621680092351]) (a6989586621680093887 :: [d6989586621680092352]) :: (~>) [e6989586621680092353] ((~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356])) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym5 a6989586621680093887 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [e6989586621680092353] ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym5 a6989586621680093887 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [e6989586621680092353] ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356])) -> Type) (a6989586621680093888 :: [e6989586621680092353]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym5 a6989586621680093887 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [e6989586621680092353] ([f6989586621680092354] ~> ([g6989586621680092355] ~> [h6989586621680092356])) -> Type) (a6989586621680093888 :: [e6989586621680092353]) = ZipWith7Sym6 a6989586621680093887 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 a6989586621680093888 |
data ZipWith7Sym6 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) (a6989586621680093885 :: [b6989586621680092350]) (a6989586621680093886 :: [c6989586621680092351]) (a6989586621680093887 :: [d6989586621680092352]) (a6989586621680093888 :: [e6989586621680092353]) :: (~>) [f6989586621680092354] ((~>) [g6989586621680092355] [h6989586621680092356]) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym6 a6989586621680093888 a6989586621680093887 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [f6989586621680092354] ([g6989586621680092355] ~> [h6989586621680092356]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym6 a6989586621680093888 a6989586621680093887 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [f6989586621680092354] ([g6989586621680092355] ~> [h6989586621680092356]) -> Type) (a6989586621680093889 :: [f6989586621680092354]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym6 a6989586621680093888 a6989586621680093887 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [f6989586621680092354] ([g6989586621680092355] ~> [h6989586621680092356]) -> Type) (a6989586621680093889 :: [f6989586621680092354]) = ZipWith7Sym7 a6989586621680093888 a6989586621680093887 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 a6989586621680093889 |
data ZipWith7Sym7 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) (a6989586621680093885 :: [b6989586621680092350]) (a6989586621680093886 :: [c6989586621680092351]) (a6989586621680093887 :: [d6989586621680092352]) (a6989586621680093888 :: [e6989586621680092353]) (a6989586621680093889 :: [f6989586621680092354]) :: (~>) [g6989586621680092355] [h6989586621680092356] Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym7 a6989586621680093889 a6989586621680093888 a6989586621680093887 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [g6989586621680092355] [h6989586621680092356] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (ZipWith7Sym7 a6989586621680093889 a6989586621680093888 a6989586621680093887 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [g] [h] -> Type) (a6989586621680093890 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym7 a6989586621680093889 a6989586621680093888 a6989586621680093887 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 :: TyFun [g] [h] -> Type) (a6989586621680093890 :: [g]) = ZipWith7 a6989586621680093889 a6989586621680093888 a6989586621680093887 a6989586621680093886 a6989586621680093885 a6989586621680093884 a6989586621680093883 a6989586621680093890 |
type ZipWith7Sym8 (a6989586621680093883 :: (~>) a6989586621680092349 ((~>) b6989586621680092350 ((~>) c6989586621680092351 ((~>) d6989586621680092352 ((~>) e6989586621680092353 ((~>) f6989586621680092354 ((~>) g6989586621680092355 h6989586621680092356))))))) (a6989586621680093884 :: [a6989586621680092349]) (a6989586621680093885 :: [b6989586621680092350]) (a6989586621680093886 :: [c6989586621680092351]) (a6989586621680093887 :: [d6989586621680092352]) (a6989586621680093888 :: [e6989586621680092353]) (a6989586621680093889 :: [f6989586621680092354]) (a6989586621680093890 :: [g6989586621680092355]) = ZipWith7 a6989586621680093883 a6989586621680093884 a6989586621680093885 a6989586621680093886 a6989586621680093887 a6989586621680093888 a6989586621680093889 a6989586621680093890 Source #
data UnzipSym0 :: forall a6989586621679970253 b6989586621679970254. (~>) [(a6989586621679970253, b6989586621679970254)] ([a6989586621679970253], [b6989586621679970254]) Source #
Instances
SingI (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # | |
SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a6989586621679970253, b6989586621679970254)] ([a6989586621679970253], [b6989586621679970254]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679975072 :: [(a, b)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnzipSym1 (a6989586621679975072 :: [(a6989586621679970253, b6989586621679970254)]) = Unzip a6989586621679975072 Source #
data Unzip3Sym0 :: forall a6989586621679970250 b6989586621679970251 c6989586621679970252. (~>) [(a6989586621679970250, b6989586621679970251, c6989586621679970252)] ([a6989586621679970250], [b6989586621679970251], [c6989586621679970252]) 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 [(a6989586621679970250, b6989586621679970251, c6989586621679970252)] ([a6989586621679970250], [b6989586621679970251], [c6989586621679970252]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679975051 :: [(a, b, c)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679975051 :: [(a, b, c)]) = Unzip3 a6989586621679975051 |
type Unzip3Sym1 (a6989586621679975051 :: [(a6989586621679970250, b6989586621679970251, c6989586621679970252)]) = Unzip3 a6989586621679975051 Source #
data Unzip4Sym0 :: forall a6989586621679970246 b6989586621679970247 c6989586621679970248 d6989586621679970249. (~>) [(a6989586621679970246, b6989586621679970247, c6989586621679970248, d6989586621679970249)] ([a6989586621679970246], [b6989586621679970247], [c6989586621679970248], [d6989586621679970249]) 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 [(a6989586621679970246, b6989586621679970247, c6989586621679970248, d6989586621679970249)] ([a6989586621679970246], [b6989586621679970247], [c6989586621679970248], [d6989586621679970249]) -> 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) (a6989586621679975028 :: [(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) (a6989586621679975028 :: [(a, b, c, d)]) = Unzip4 a6989586621679975028 |
type Unzip4Sym1 (a6989586621679975028 :: [(a6989586621679970246, b6989586621679970247, c6989586621679970248, d6989586621679970249)]) = Unzip4 a6989586621679975028 Source #
data Unzip5Sym0 :: forall a6989586621679970241 b6989586621679970242 c6989586621679970243 d6989586621679970244 e6989586621679970245. (~>) [(a6989586621679970241, b6989586621679970242, c6989586621679970243, d6989586621679970244, e6989586621679970245)] ([a6989586621679970241], [b6989586621679970242], [c6989586621679970243], [d6989586621679970244], [e6989586621679970245]) 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 [(a6989586621679970241, b6989586621679970242, c6989586621679970243, d6989586621679970244, e6989586621679970245)] ([a6989586621679970241], [b6989586621679970242], [c6989586621679970243], [d6989586621679970244], [e6989586621679970245]) -> 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) (a6989586621679975003 :: [(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) (a6989586621679975003 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679975003 |
type Unzip5Sym1 (a6989586621679975003 :: [(a6989586621679970241, b6989586621679970242, c6989586621679970243, d6989586621679970244, e6989586621679970245)]) = Unzip5 a6989586621679975003 Source #
data Unzip6Sym0 :: forall a6989586621679970235 b6989586621679970236 c6989586621679970237 d6989586621679970238 e6989586621679970239 f6989586621679970240. (~>) [(a6989586621679970235, b6989586621679970236, c6989586621679970237, d6989586621679970238, e6989586621679970239, f6989586621679970240)] ([a6989586621679970235], [b6989586621679970236], [c6989586621679970237], [d6989586621679970238], [e6989586621679970239], [f6989586621679970240]) 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 [(a6989586621679970235, b6989586621679970236, c6989586621679970237, d6989586621679970238, e6989586621679970239, f6989586621679970240)] ([a6989586621679970235], [b6989586621679970236], [c6989586621679970237], [d6989586621679970238], [e6989586621679970239], [f6989586621679970240]) -> 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) (a6989586621679974976 :: [(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) (a6989586621679974976 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679974976 |
type Unzip6Sym1 (a6989586621679974976 :: [(a6989586621679970235, b6989586621679970236, c6989586621679970237, d6989586621679970238, e6989586621679970239, f6989586621679970240)]) = Unzip6 a6989586621679974976 Source #
data Unzip7Sym0 :: forall a6989586621679970228 b6989586621679970229 c6989586621679970230 d6989586621679970231 e6989586621679970232 f6989586621679970233 g6989586621679970234. (~>) [(a6989586621679970228, b6989586621679970229, c6989586621679970230, d6989586621679970231, e6989586621679970232, f6989586621679970233, g6989586621679970234)] ([a6989586621679970228], [b6989586621679970229], [c6989586621679970230], [d6989586621679970231], [e6989586621679970232], [f6989586621679970233], [g6989586621679970234]) 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 [(a6989586621679970228, b6989586621679970229, c6989586621679970230, d6989586621679970231, e6989586621679970232, f6989586621679970233, g6989586621679970234)] ([a6989586621679970228], [b6989586621679970229], [c6989586621679970230], [d6989586621679970231], [e6989586621679970232], [f6989586621679970233], [g6989586621679970234]) -> 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) (a6989586621679974947 :: [(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) (a6989586621679974947 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679974947 |
type Unzip7Sym1 (a6989586621679974947 :: [(a6989586621679970228, b6989586621679970229, c6989586621679970230, d6989586621679970231, e6989586621679970232, f6989586621679970233, g6989586621679970234)]) = Unzip7 a6989586621679974947 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 (a6989586621679974943 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnlinesSym1 (a6989586621679974943 :: [Symbol]) = Unlines a6989586621679974943 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 (a6989586621679974932 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnwordsSym1 (a6989586621679974932 :: [Symbol]) = Unwords a6989586621679974932 Source #
data NubSym0 :: forall a6989586621679970187. (~>) [a6989586621679970187] [a6989586621679970187] Source #
Instances
SEq a => SingI (NubSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (NubSym0 :: TyFun [a6989586621679970187] [a6989586621679970187] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (NubSym0 :: TyFun [a] [a] -> Type) (a6989586621679974315 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data DeleteSym0 :: forall a6989586621679970227. (~>) a6989586621679970227 ((~>) [a6989586621679970227] [a6989586621679970227]) 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 a6989586621679970227 ([a6989586621679970227] ~> [a6989586621679970227]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym0 :: TyFun a6989586621679970227 ([a6989586621679970227] ~> [a6989586621679970227]) -> Type) (a6989586621679974926 :: a6989586621679970227) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym0 :: TyFun a6989586621679970227 ([a6989586621679970227] ~> [a6989586621679970227]) -> Type) (a6989586621679974926 :: a6989586621679970227) = DeleteSym1 a6989586621679974926 |
data DeleteSym1 (a6989586621679974926 :: a6989586621679970227) :: (~>) [a6989586621679970227] [a6989586621679970227] 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 a6989586621679974926 :: TyFun [a6989586621679970227] [a6989586621679970227] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteSym1 a6989586621679974926 :: TyFun [a] [a] -> Type) (a6989586621679974927 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym1 a6989586621679974926 :: TyFun [a] [a] -> Type) (a6989586621679974927 :: [a]) = Delete a6989586621679974926 a6989586621679974927 |
type DeleteSym2 (a6989586621679974926 :: a6989586621679970227) (a6989586621679974927 :: [a6989586621679970227]) = Delete a6989586621679974926 a6989586621679974927 Source #
data (\\@#@$) :: forall a6989586621679970226. (~>) [a6989586621679970226] ((~>) [a6989586621679970226] [a6989586621679970226]) infix 5 Source #
Instances
SEq a => SingI ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings ((\\@#@$) :: TyFun [a6989586621679970226] ([a6989586621679970226] ~> [a6989586621679970226]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$) :: TyFun [a6989586621679970226] ([a6989586621679970226] ~> [a6989586621679970226]) -> Type) (a6989586621679974916 :: [a6989586621679970226]) Source # | |
data (\\@#@$$) (a6989586621679974916 :: [a6989586621679970226]) :: (~>) [a6989586621679970226] [a6989586621679970226] infix 5 Source #
Instances
(SEq a, SingI d) => SingI ((\\@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings ((\\@#@$$) a6989586621679974916 :: TyFun [a6989586621679970226] [a6989586621679970226] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply ((\\@#@$$) a6989586621679974916 :: TyFun [a] [a] -> Type) (a6989586621679974917 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type (\\@#@$$$) (a6989586621679974916 :: [a6989586621679970226]) (a6989586621679974917 :: [a6989586621679970226]) = (\\) a6989586621679974916 a6989586621679974917 Source #
data UnionSym0 :: forall a6989586621679970183. (~>) [a6989586621679970183] ((~>) [a6989586621679970183] [a6989586621679970183]) Source #
Instances
SEq a => SingI (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (UnionSym0 :: TyFun [a6989586621679970183] ([a6989586621679970183] ~> [a6989586621679970183]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym0 :: TyFun [a6989586621679970183] ([a6989586621679970183] ~> [a6989586621679970183]) -> Type) (a6989586621679974265 :: [a6989586621679970183]) Source # | |
data UnionSym1 (a6989586621679974265 :: [a6989586621679970183]) :: (~>) [a6989586621679970183] [a6989586621679970183] Source #
Instances
(SEq a, SingI d) => SingI (UnionSym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (UnionSym1 a6989586621679974265 :: TyFun [a6989586621679970183] [a6989586621679970183] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionSym1 a6989586621679974265 :: TyFun [a] [a] -> Type) (a6989586621679974266 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type UnionSym2 (a6989586621679974265 :: [a6989586621679970183]) (a6989586621679974266 :: [a6989586621679970183]) = Union a6989586621679974265 a6989586621679974266 Source #
data IntersectSym0 :: forall a6989586621679970213. (~>) [a6989586621679970213] ((~>) [a6989586621679970213] [a6989586621679970213]) 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 [a6989586621679970213] ([a6989586621679970213] ~> [a6989586621679970213]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym0 :: TyFun [a6989586621679970213] ([a6989586621679970213] ~> [a6989586621679970213]) -> Type) (a6989586621679974710 :: [a6989586621679970213]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym0 :: TyFun [a6989586621679970213] ([a6989586621679970213] ~> [a6989586621679970213]) -> Type) (a6989586621679974710 :: [a6989586621679970213]) = IntersectSym1 a6989586621679974710 |
data IntersectSym1 (a6989586621679974710 :: [a6989586621679970213]) :: (~>) [a6989586621679970213] [a6989586621679970213] 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 a6989586621679974710 :: TyFun [a6989586621679970213] [a6989586621679970213] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectSym1 a6989586621679974710 :: TyFun [a] [a] -> Type) (a6989586621679974711 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym1 a6989586621679974710 :: TyFun [a] [a] -> Type) (a6989586621679974711 :: [a]) = Intersect a6989586621679974710 a6989586621679974711 |
type IntersectSym2 (a6989586621679974710 :: [a6989586621679970213]) (a6989586621679974711 :: [a6989586621679970213]) = Intersect a6989586621679974710 a6989586621679974711 Source #
data InsertSym0 :: forall a6989586621679970200. (~>) a6989586621679970200 ((~>) [a6989586621679970200] [a6989586621679970200]) 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 a6989586621679970200 ([a6989586621679970200] ~> [a6989586621679970200]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym0 :: TyFun a6989586621679970200 ([a6989586621679970200] ~> [a6989586621679970200]) -> Type) (a6989586621679974473 :: a6989586621679970200) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym0 :: TyFun a6989586621679970200 ([a6989586621679970200] ~> [a6989586621679970200]) -> Type) (a6989586621679974473 :: a6989586621679970200) = InsertSym1 a6989586621679974473 |
data InsertSym1 (a6989586621679974473 :: a6989586621679970200) :: (~>) [a6989586621679970200] [a6989586621679970200] 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 a6989586621679974473 :: TyFun [a6989586621679970200] [a6989586621679970200] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertSym1 a6989586621679974473 :: TyFun [a] [a] -> Type) (a6989586621679974474 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym1 a6989586621679974473 :: TyFun [a] [a] -> Type) (a6989586621679974474 :: [a]) = Insert a6989586621679974473 a6989586621679974474 |
type InsertSym2 (a6989586621679974473 :: a6989586621679970200) (a6989586621679974474 :: [a6989586621679970200]) = Insert a6989586621679974473 a6989586621679974474 Source #
data SortSym0 :: forall a6989586621679970199. (~>) [a6989586621679970199] [a6989586621679970199] Source #
Instances
SOrd a => SingI (SortSym0 :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (SortSym0 :: TyFun [a6989586621679970199] [a6989586621679970199] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SortSym0 :: TyFun [a] [a] -> Type) (a6989586621679974470 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data NubBySym0 :: forall a6989586621679970186. (~>) ((~>) a6989586621679970186 ((~>) a6989586621679970186 Bool)) ((~>) [a6989586621679970186] [a6989586621679970186]) Source #
Instances
SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (NubBySym0 :: TyFun (a6989586621679970186 ~> (a6989586621679970186 ~> Bool)) ([a6989586621679970186] ~> [a6989586621679970186]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym0 :: TyFun (a6989586621679970186 ~> (a6989586621679970186 ~> Bool)) ([a6989586621679970186] ~> [a6989586621679970186]) -> Type) (a6989586621679974290 :: a6989586621679970186 ~> (a6989586621679970186 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
data NubBySym1 (a6989586621679974290 :: (~>) a6989586621679970186 ((~>) a6989586621679970186 Bool)) :: (~>) [a6989586621679970186] [a6989586621679970186] Source #
Instances
SingI d => SingI (NubBySym1 d :: TyFun [a] [a] -> Type) Source # | |
SuppressUnusedWarnings (NubBySym1 a6989586621679974290 :: TyFun [a6989586621679970186] [a6989586621679970186] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (NubBySym1 a6989586621679974290 :: TyFun [a] [a] -> Type) (a6989586621679974291 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal |
type NubBySym2 (a6989586621679974290 :: (~>) a6989586621679970186 ((~>) a6989586621679970186 Bool)) (a6989586621679974291 :: [a6989586621679970186]) = NubBy a6989586621679974290 a6989586621679974291 Source #
data DeleteBySym0 :: forall a6989586621679970225. (~>) ((~>) a6989586621679970225 ((~>) a6989586621679970225 Bool)) ((~>) a6989586621679970225 ((~>) [a6989586621679970225] [a6989586621679970225])) 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 (a6989586621679970225 ~> (a6989586621679970225 ~> Bool)) (a6989586621679970225 ~> ([a6989586621679970225] ~> [a6989586621679970225])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym0 :: TyFun (a6989586621679970225 ~> (a6989586621679970225 ~> Bool)) (a6989586621679970225 ~> ([a6989586621679970225] ~> [a6989586621679970225])) -> Type) (a6989586621679974894 :: a6989586621679970225 ~> (a6989586621679970225 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym0 :: TyFun (a6989586621679970225 ~> (a6989586621679970225 ~> Bool)) (a6989586621679970225 ~> ([a6989586621679970225] ~> [a6989586621679970225])) -> Type) (a6989586621679974894 :: a6989586621679970225 ~> (a6989586621679970225 ~> Bool)) = DeleteBySym1 a6989586621679974894 |
data DeleteBySym1 (a6989586621679974894 :: (~>) a6989586621679970225 ((~>) a6989586621679970225 Bool)) :: (~>) a6989586621679970225 ((~>) [a6989586621679970225] [a6989586621679970225]) 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 a6989586621679974894 :: TyFun a6989586621679970225 ([a6989586621679970225] ~> [a6989586621679970225]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym1 a6989586621679974894 :: TyFun a6989586621679970225 ([a6989586621679970225] ~> [a6989586621679970225]) -> Type) (a6989586621679974895 :: a6989586621679970225) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym1 a6989586621679974894 :: TyFun a6989586621679970225 ([a6989586621679970225] ~> [a6989586621679970225]) -> Type) (a6989586621679974895 :: a6989586621679970225) = DeleteBySym2 a6989586621679974894 a6989586621679974895 |
data DeleteBySym2 (a6989586621679974894 :: (~>) a6989586621679970225 ((~>) a6989586621679970225 Bool)) (a6989586621679974895 :: a6989586621679970225) :: (~>) [a6989586621679970225] [a6989586621679970225] 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 a6989586621679974895 a6989586621679974894 :: TyFun [a6989586621679970225] [a6989586621679970225] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteBySym2 a6989586621679974895 a6989586621679974894 :: TyFun [a] [a] -> Type) (a6989586621679974896 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym2 a6989586621679974895 a6989586621679974894 :: TyFun [a] [a] -> Type) (a6989586621679974896 :: [a]) = DeleteBy a6989586621679974895 a6989586621679974894 a6989586621679974896 |
type DeleteBySym3 (a6989586621679974894 :: (~>) a6989586621679970225 ((~>) a6989586621679970225 Bool)) (a6989586621679974895 :: a6989586621679970225) (a6989586621679974896 :: [a6989586621679970225]) = DeleteBy a6989586621679974894 a6989586621679974895 a6989586621679974896 Source #
data DeleteFirstsBySym0 :: forall a6989586621679970224. (~>) ((~>) a6989586621679970224 ((~>) a6989586621679970224 Bool)) ((~>) [a6989586621679970224] ((~>) [a6989586621679970224] [a6989586621679970224])) Source #
Instances
SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (a6989586621679970224 ~> (a6989586621679970224 ~> Bool)) ([a6989586621679970224] ~> ([a6989586621679970224] ~> [a6989586621679970224])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679970224 ~> (a6989586621679970224 ~> Bool)) ([a6989586621679970224] ~> ([a6989586621679970224] ~> [a6989586621679970224])) -> Type) (a6989586621679974881 :: a6989586621679970224 ~> (a6989586621679970224 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679970224 ~> (a6989586621679970224 ~> Bool)) ([a6989586621679970224] ~> ([a6989586621679970224] ~> [a6989586621679970224])) -> Type) (a6989586621679974881 :: a6989586621679970224 ~> (a6989586621679970224 ~> Bool)) = DeleteFirstsBySym1 a6989586621679974881 |
data DeleteFirstsBySym1 (a6989586621679974881 :: (~>) a6989586621679970224 ((~>) a6989586621679970224 Bool)) :: (~>) [a6989586621679970224] ((~>) [a6989586621679970224] [a6989586621679970224]) 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 a6989586621679974881 :: TyFun [a6989586621679970224] ([a6989586621679970224] ~> [a6989586621679970224]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym1 a6989586621679974881 :: TyFun [a6989586621679970224] ([a6989586621679970224] ~> [a6989586621679970224]) -> Type) (a6989586621679974882 :: [a6989586621679970224]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym1 a6989586621679974881 :: TyFun [a6989586621679970224] ([a6989586621679970224] ~> [a6989586621679970224]) -> Type) (a6989586621679974882 :: [a6989586621679970224]) = DeleteFirstsBySym2 a6989586621679974881 a6989586621679974882 |
data DeleteFirstsBySym2 (a6989586621679974881 :: (~>) a6989586621679970224 ((~>) a6989586621679970224 Bool)) (a6989586621679974882 :: [a6989586621679970224]) :: (~>) [a6989586621679970224] [a6989586621679970224] 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 a6989586621679974882 a6989586621679974881 :: TyFun [a6989586621679970224] [a6989586621679970224] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (DeleteFirstsBySym2 a6989586621679974882 a6989586621679974881 :: TyFun [a] [a] -> Type) (a6989586621679974883 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym2 a6989586621679974882 a6989586621679974881 :: TyFun [a] [a] -> Type) (a6989586621679974883 :: [a]) = DeleteFirstsBy a6989586621679974882 a6989586621679974881 a6989586621679974883 |
type DeleteFirstsBySym3 (a6989586621679974881 :: (~>) a6989586621679970224 ((~>) a6989586621679970224 Bool)) (a6989586621679974882 :: [a6989586621679970224]) (a6989586621679974883 :: [a6989586621679970224]) = DeleteFirstsBy a6989586621679974881 a6989586621679974882 a6989586621679974883 Source #
data UnionBySym0 :: forall a6989586621679970184. (~>) ((~>) a6989586621679970184 ((~>) a6989586621679970184 Bool)) ((~>) [a6989586621679970184] ((~>) [a6989586621679970184] [a6989586621679970184])) 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 (a6989586621679970184 ~> (a6989586621679970184 ~> Bool)) ([a6989586621679970184] ~> ([a6989586621679970184] ~> [a6989586621679970184])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym0 :: TyFun (a6989586621679970184 ~> (a6989586621679970184 ~> Bool)) ([a6989586621679970184] ~> ([a6989586621679970184] ~> [a6989586621679970184])) -> Type) (a6989586621679974271 :: a6989586621679970184 ~> (a6989586621679970184 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym0 :: TyFun (a6989586621679970184 ~> (a6989586621679970184 ~> Bool)) ([a6989586621679970184] ~> ([a6989586621679970184] ~> [a6989586621679970184])) -> Type) (a6989586621679974271 :: a6989586621679970184 ~> (a6989586621679970184 ~> Bool)) = UnionBySym1 a6989586621679974271 |
data UnionBySym1 (a6989586621679974271 :: (~>) a6989586621679970184 ((~>) a6989586621679970184 Bool)) :: (~>) [a6989586621679970184] ((~>) [a6989586621679970184] [a6989586621679970184]) 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 a6989586621679974271 :: TyFun [a6989586621679970184] ([a6989586621679970184] ~> [a6989586621679970184]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym1 a6989586621679974271 :: TyFun [a6989586621679970184] ([a6989586621679970184] ~> [a6989586621679970184]) -> Type) (a6989586621679974272 :: [a6989586621679970184]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym1 a6989586621679974271 :: TyFun [a6989586621679970184] ([a6989586621679970184] ~> [a6989586621679970184]) -> Type) (a6989586621679974272 :: [a6989586621679970184]) = UnionBySym2 a6989586621679974271 a6989586621679974272 |
data UnionBySym2 (a6989586621679974271 :: (~>) a6989586621679970184 ((~>) a6989586621679970184 Bool)) (a6989586621679974272 :: [a6989586621679970184]) :: (~>) [a6989586621679970184] [a6989586621679970184] 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 a6989586621679974272 a6989586621679974271 :: TyFun [a6989586621679970184] [a6989586621679970184] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (UnionBySym2 a6989586621679974272 a6989586621679974271 :: TyFun [a] [a] -> Type) (a6989586621679974273 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym2 a6989586621679974272 a6989586621679974271 :: TyFun [a] [a] -> Type) (a6989586621679974273 :: [a]) = UnionBy a6989586621679974272 a6989586621679974271 a6989586621679974273 |
type UnionBySym3 (a6989586621679974271 :: (~>) a6989586621679970184 ((~>) a6989586621679970184 Bool)) (a6989586621679974272 :: [a6989586621679970184]) (a6989586621679974273 :: [a6989586621679970184]) = UnionBy a6989586621679974271 a6989586621679974272 a6989586621679974273 Source #
data IntersectBySym0 :: forall a6989586621679970212. (~>) ((~>) a6989586621679970212 ((~>) a6989586621679970212 Bool)) ((~>) [a6989586621679970212] ((~>) [a6989586621679970212] [a6989586621679970212])) Source #
Instances
SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (IntersectBySym0 :: TyFun (a6989586621679970212 ~> (a6989586621679970212 ~> Bool)) ([a6989586621679970212] ~> ([a6989586621679970212] ~> [a6989586621679970212])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym0 :: TyFun (a6989586621679970212 ~> (a6989586621679970212 ~> Bool)) ([a6989586621679970212] ~> ([a6989586621679970212] ~> [a6989586621679970212])) -> Type) (a6989586621679974674 :: a6989586621679970212 ~> (a6989586621679970212 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym0 :: TyFun (a6989586621679970212 ~> (a6989586621679970212 ~> Bool)) ([a6989586621679970212] ~> ([a6989586621679970212] ~> [a6989586621679970212])) -> Type) (a6989586621679974674 :: a6989586621679970212 ~> (a6989586621679970212 ~> Bool)) = IntersectBySym1 a6989586621679974674 |
data IntersectBySym1 (a6989586621679974674 :: (~>) a6989586621679970212 ((~>) a6989586621679970212 Bool)) :: (~>) [a6989586621679970212] ((~>) [a6989586621679970212] [a6989586621679970212]) 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 a6989586621679974674 :: TyFun [a6989586621679970212] ([a6989586621679970212] ~> [a6989586621679970212]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym1 a6989586621679974674 :: TyFun [a6989586621679970212] ([a6989586621679970212] ~> [a6989586621679970212]) -> Type) (a6989586621679974675 :: [a6989586621679970212]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym1 a6989586621679974674 :: TyFun [a6989586621679970212] ([a6989586621679970212] ~> [a6989586621679970212]) -> Type) (a6989586621679974675 :: [a6989586621679970212]) = IntersectBySym2 a6989586621679974674 a6989586621679974675 |
data IntersectBySym2 (a6989586621679974674 :: (~>) a6989586621679970212 ((~>) a6989586621679970212 Bool)) (a6989586621679974675 :: [a6989586621679970212]) :: (~>) [a6989586621679970212] [a6989586621679970212] 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 a6989586621679974675 a6989586621679974674 :: TyFun [a6989586621679970212] [a6989586621679970212] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (IntersectBySym2 a6989586621679974675 a6989586621679974674 :: TyFun [a] [a] -> Type) (a6989586621679974676 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym2 a6989586621679974675 a6989586621679974674 :: TyFun [a] [a] -> Type) (a6989586621679974676 :: [a]) = IntersectBy a6989586621679974675 a6989586621679974674 a6989586621679974676 |
type IntersectBySym3 (a6989586621679974674 :: (~>) a6989586621679970212 ((~>) a6989586621679970212 Bool)) (a6989586621679974675 :: [a6989586621679970212]) (a6989586621679974676 :: [a6989586621679970212]) = IntersectBy a6989586621679974674 a6989586621679974675 a6989586621679974676 Source #
data GroupBySym0 :: forall a6989586621679970198. (~>) ((~>) a6989586621679970198 ((~>) a6989586621679970198 Bool)) ((~>) [a6989586621679970198] [[a6989586621679970198]]) 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 (a6989586621679970198 ~> (a6989586621679970198 ~> Bool)) ([a6989586621679970198] ~> [[a6989586621679970198]]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym0 :: TyFun (a6989586621679970198 ~> (a6989586621679970198 ~> Bool)) ([a6989586621679970198] ~> [[a6989586621679970198]]) -> Type) (a6989586621679974437 :: a6989586621679970198 ~> (a6989586621679970198 ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GroupBySym0 :: TyFun (a6989586621679970198 ~> (a6989586621679970198 ~> Bool)) ([a6989586621679970198] ~> [[a6989586621679970198]]) -> Type) (a6989586621679974437 :: a6989586621679970198 ~> (a6989586621679970198 ~> Bool)) = GroupBySym1 a6989586621679974437 |
data GroupBySym1 (a6989586621679974437 :: (~>) a6989586621679970198 ((~>) a6989586621679970198 Bool)) :: (~>) [a6989586621679970198] [[a6989586621679970198]] 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 a6989586621679974437 :: TyFun [a6989586621679970198] [[a6989586621679970198]] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GroupBySym1 a6989586621679974437 :: TyFun [a] [[a]] -> Type) (a6989586621679974438 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GroupBySym1 a6989586621679974437 :: TyFun [a] [[a]] -> Type) (a6989586621679974438 :: [a]) = GroupBy a6989586621679974437 a6989586621679974438 |
type GroupBySym2 (a6989586621679974437 :: (~>) a6989586621679970198 ((~>) a6989586621679970198 Bool)) (a6989586621679974438 :: [a6989586621679970198]) = GroupBy a6989586621679974437 a6989586621679974438 Source #
data SortBySym0 :: forall a6989586621679970223. (~>) ((~>) a6989586621679970223 ((~>) a6989586621679970223 Ordering)) ((~>) [a6989586621679970223] [a6989586621679970223]) 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 (a6989586621679970223 ~> (a6989586621679970223 ~> Ordering)) ([a6989586621679970223] ~> [a6989586621679970223]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym0 :: TyFun (a6989586621679970223 ~> (a6989586621679970223 ~> Ordering)) ([a6989586621679970223] ~> [a6989586621679970223]) -> Type) (a6989586621679974873 :: a6989586621679970223 ~> (a6989586621679970223 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SortBySym0 :: TyFun (a6989586621679970223 ~> (a6989586621679970223 ~> Ordering)) ([a6989586621679970223] ~> [a6989586621679970223]) -> Type) (a6989586621679974873 :: a6989586621679970223 ~> (a6989586621679970223 ~> Ordering)) = SortBySym1 a6989586621679974873 |
data SortBySym1 (a6989586621679974873 :: (~>) a6989586621679970223 ((~>) a6989586621679970223 Ordering)) :: (~>) [a6989586621679970223] [a6989586621679970223] 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 a6989586621679974873 :: TyFun [a6989586621679970223] [a6989586621679970223] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (SortBySym1 a6989586621679974873 :: TyFun [a] [a] -> Type) (a6989586621679974874 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SortBySym1 a6989586621679974873 :: TyFun [a] [a] -> Type) (a6989586621679974874 :: [a]) = SortBy a6989586621679974873 a6989586621679974874 |
type SortBySym2 (a6989586621679974873 :: (~>) a6989586621679970223 ((~>) a6989586621679970223 Ordering)) (a6989586621679974874 :: [a6989586621679970223]) = SortBy a6989586621679974873 a6989586621679974874 Source #
data InsertBySym0 :: forall a6989586621679970222. (~>) ((~>) a6989586621679970222 ((~>) a6989586621679970222 Ordering)) ((~>) a6989586621679970222 ((~>) [a6989586621679970222] [a6989586621679970222])) 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 (a6989586621679970222 ~> (a6989586621679970222 ~> Ordering)) (a6989586621679970222 ~> ([a6989586621679970222] ~> [a6989586621679970222])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym0 :: TyFun (a6989586621679970222 ~> (a6989586621679970222 ~> Ordering)) (a6989586621679970222 ~> ([a6989586621679970222] ~> [a6989586621679970222])) -> Type) (a6989586621679974849 :: a6989586621679970222 ~> (a6989586621679970222 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym0 :: TyFun (a6989586621679970222 ~> (a6989586621679970222 ~> Ordering)) (a6989586621679970222 ~> ([a6989586621679970222] ~> [a6989586621679970222])) -> Type) (a6989586621679974849 :: a6989586621679970222 ~> (a6989586621679970222 ~> Ordering)) = InsertBySym1 a6989586621679974849 |
data InsertBySym1 (a6989586621679974849 :: (~>) a6989586621679970222 ((~>) a6989586621679970222 Ordering)) :: (~>) a6989586621679970222 ((~>) [a6989586621679970222] [a6989586621679970222]) 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 a6989586621679974849 :: TyFun a6989586621679970222 ([a6989586621679970222] ~> [a6989586621679970222]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym1 a6989586621679974849 :: TyFun a6989586621679970222 ([a6989586621679970222] ~> [a6989586621679970222]) -> Type) (a6989586621679974850 :: a6989586621679970222) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym1 a6989586621679974849 :: TyFun a6989586621679970222 ([a6989586621679970222] ~> [a6989586621679970222]) -> Type) (a6989586621679974850 :: a6989586621679970222) = InsertBySym2 a6989586621679974849 a6989586621679974850 |
data InsertBySym2 (a6989586621679974849 :: (~>) a6989586621679970222 ((~>) a6989586621679970222 Ordering)) (a6989586621679974850 :: a6989586621679970222) :: (~>) [a6989586621679970222] [a6989586621679970222] 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 a6989586621679974850 a6989586621679974849 :: TyFun [a6989586621679970222] [a6989586621679970222] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (InsertBySym2 a6989586621679974850 a6989586621679974849 :: TyFun [a] [a] -> Type) (a6989586621679974851 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym2 a6989586621679974850 a6989586621679974849 :: TyFun [a] [a] -> Type) (a6989586621679974851 :: [a]) = InsertBy a6989586621679974850 a6989586621679974849 a6989586621679974851 |
type InsertBySym3 (a6989586621679974849 :: (~>) a6989586621679970222 ((~>) a6989586621679970222 Ordering)) (a6989586621679974850 :: a6989586621679970222) (a6989586621679974851 :: [a6989586621679970222]) = InsertBy a6989586621679974849 a6989586621679974850 a6989586621679974851 Source #
data MaximumBySym0 :: forall a6989586621680486543 t6989586621680486542. (~>) ((~>) a6989586621680486543 ((~>) a6989586621680486543 Ordering)) ((~>) (t6989586621680486542 a6989586621680486543) a6989586621680486543) 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 (a6989586621680486543 ~> (a6989586621680486543 ~> Ordering)) (t6989586621680486542 a6989586621680486543 ~> a6989586621680486543) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym0 :: TyFun (a6989586621680486543 ~> (a6989586621680486543 ~> Ordering)) (t6989586621680486542 a6989586621680486543 ~> a6989586621680486543) -> Type) (a6989586621680487050 :: a6989586621680486543 ~> (a6989586621680486543 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym0 :: TyFun (a6989586621680486543 ~> (a6989586621680486543 ~> Ordering)) (t6989586621680486542 a6989586621680486543 ~> a6989586621680486543) -> Type) (a6989586621680487050 :: a6989586621680486543 ~> (a6989586621680486543 ~> Ordering)) = MaximumBySym1 a6989586621680487050 t6989586621680486542 :: TyFun (t6989586621680486542 a6989586621680486543) a6989586621680486543 -> Type |
data MaximumBySym1 (a6989586621680487050 :: (~>) a6989586621680486543 ((~>) a6989586621680486543 Ordering)) :: forall t6989586621680486542. (~>) (t6989586621680486542 a6989586621680486543) a6989586621680486543 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 a6989586621680487050 t6989586621680486542 :: TyFun (t6989586621680486542 a6989586621680486543) a6989586621680486543 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MaximumBySym1 a6989586621680487050 t :: TyFun (t a) a -> Type) (a6989586621680487051 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym1 a6989586621680487050 t :: TyFun (t a) a -> Type) (a6989586621680487051 :: t a) = MaximumBy a6989586621680487050 a6989586621680487051 |
type MaximumBySym2 (a6989586621680487050 :: (~>) a6989586621680486543 ((~>) a6989586621680486543 Ordering)) (a6989586621680487051 :: t6989586621680486542 a6989586621680486543) = MaximumBy a6989586621680487050 a6989586621680487051 Source #
data MinimumBySym0 :: forall a6989586621680486541 t6989586621680486540. (~>) ((~>) a6989586621680486541 ((~>) a6989586621680486541 Ordering)) ((~>) (t6989586621680486540 a6989586621680486541) a6989586621680486541) 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 (a6989586621680486541 ~> (a6989586621680486541 ~> Ordering)) (t6989586621680486540 a6989586621680486541 ~> a6989586621680486541) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym0 :: TyFun (a6989586621680486541 ~> (a6989586621680486541 ~> Ordering)) (t6989586621680486540 a6989586621680486541 ~> a6989586621680486541) -> Type) (a6989586621680487025 :: a6989586621680486541 ~> (a6989586621680486541 ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym0 :: TyFun (a6989586621680486541 ~> (a6989586621680486541 ~> Ordering)) (t6989586621680486540 a6989586621680486541 ~> a6989586621680486541) -> Type) (a6989586621680487025 :: a6989586621680486541 ~> (a6989586621680486541 ~> Ordering)) = MinimumBySym1 a6989586621680487025 t6989586621680486540 :: TyFun (t6989586621680486540 a6989586621680486541) a6989586621680486541 -> Type |
data MinimumBySym1 (a6989586621680487025 :: (~>) a6989586621680486541 ((~>) a6989586621680486541 Ordering)) :: forall t6989586621680486540. (~>) (t6989586621680486540 a6989586621680486541) a6989586621680486541 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 a6989586621680487025 t6989586621680486540 :: TyFun (t6989586621680486540 a6989586621680486541) a6989586621680486541 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () Source # | |
type Apply (MinimumBySym1 a6989586621680487025 t :: TyFun (t a) a -> Type) (a6989586621680487026 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym1 a6989586621680487025 t :: TyFun (t a) a -> Type) (a6989586621680487026 :: t a) = MinimumBy a6989586621680487025 a6989586621680487026 |
type MinimumBySym2 (a6989586621680487025 :: (~>) a6989586621680486541 ((~>) a6989586621680486541 Ordering)) (a6989586621680487026 :: t6989586621680486540 a6989586621680486541) = MinimumBy a6989586621680487025 a6989586621680487026 Source #
data GenericLengthSym0 :: forall a6989586621679970182 i6989586621679970181. (~>) [a6989586621679970182] i6989586621679970181 Source #
Instances
SNum i => SingI (GenericLengthSym0 :: TyFun [a] i -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a6989586621679970182] i6989586621679970181 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679974258 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679974258 :: [a]) = GenericLength a6989586621679974258 :: k2 |
type GenericLengthSym1 (a6989586621679974258 :: [a6989586621679970182]) = GenericLength a6989586621679974258 Source #
data GenericTakeSym0 :: forall i6989586621680092347 a6989586621680092348. (~>) i6989586621680092347 ((~>) [a6989586621680092348] [a6989586621680092348]) Source #
Instances
SuppressUnusedWarnings (GenericTakeSym0 :: TyFun i6989586621680092347 ([a6989586621680092348] ~> [a6989586621680092348]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericTakeSym0 :: TyFun i6989586621680092347 ([a6989586621680092348] ~> [a6989586621680092348]) -> Type) (a6989586621680093877 :: i6989586621680092347) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericTakeSym0 :: TyFun i6989586621680092347 ([a6989586621680092348] ~> [a6989586621680092348]) -> Type) (a6989586621680093877 :: i6989586621680092347) = GenericTakeSym1 a6989586621680093877 a6989586621680092348 :: TyFun [a6989586621680092348] [a6989586621680092348] -> Type |
data GenericTakeSym1 (a6989586621680093877 :: i6989586621680092347) :: forall a6989586621680092348. (~>) [a6989586621680092348] [a6989586621680092348] Source #
Instances
SuppressUnusedWarnings (GenericTakeSym1 a6989586621680093877 a6989586621680092348 :: TyFun [a6989586621680092348] [a6989586621680092348] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericTakeSym1 a6989586621680093877 a :: TyFun [a] [a] -> Type) (a6989586621680093878 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericTakeSym1 a6989586621680093877 a :: TyFun [a] [a] -> Type) (a6989586621680093878 :: [a]) = GenericTake a6989586621680093877 a6989586621680093878 |
type GenericTakeSym2 (a6989586621680093877 :: i6989586621680092347) (a6989586621680093878 :: [a6989586621680092348]) = GenericTake a6989586621680093877 a6989586621680093878 Source #
data GenericDropSym0 :: forall i6989586621680092345 a6989586621680092346. (~>) i6989586621680092345 ((~>) [a6989586621680092346] [a6989586621680092346]) Source #
Instances
SuppressUnusedWarnings (GenericDropSym0 :: TyFun i6989586621680092345 ([a6989586621680092346] ~> [a6989586621680092346]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericDropSym0 :: TyFun i6989586621680092345 ([a6989586621680092346] ~> [a6989586621680092346]) -> Type) (a6989586621680093867 :: i6989586621680092345) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericDropSym0 :: TyFun i6989586621680092345 ([a6989586621680092346] ~> [a6989586621680092346]) -> Type) (a6989586621680093867 :: i6989586621680092345) = GenericDropSym1 a6989586621680093867 a6989586621680092346 :: TyFun [a6989586621680092346] [a6989586621680092346] -> Type |
data GenericDropSym1 (a6989586621680093867 :: i6989586621680092345) :: forall a6989586621680092346. (~>) [a6989586621680092346] [a6989586621680092346] Source #
Instances
SuppressUnusedWarnings (GenericDropSym1 a6989586621680093867 a6989586621680092346 :: TyFun [a6989586621680092346] [a6989586621680092346] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericDropSym1 a6989586621680093867 a :: TyFun [a] [a] -> Type) (a6989586621680093868 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericDropSym1 a6989586621680093867 a :: TyFun [a] [a] -> Type) (a6989586621680093868 :: [a]) = GenericDrop a6989586621680093867 a6989586621680093868 |
type GenericDropSym2 (a6989586621680093867 :: i6989586621680092345) (a6989586621680093868 :: [a6989586621680092346]) = GenericDrop a6989586621680093867 a6989586621680093868 Source #
data GenericSplitAtSym0 :: forall i6989586621680092343 a6989586621680092344. (~>) i6989586621680092343 ((~>) [a6989586621680092344] ([a6989586621680092344], [a6989586621680092344])) Source #
Instances
SuppressUnusedWarnings (GenericSplitAtSym0 :: TyFun i6989586621680092343 ([a6989586621680092344] ~> ([a6989586621680092344], [a6989586621680092344])) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericSplitAtSym0 :: TyFun i6989586621680092343 ([a6989586621680092344] ~> ([a6989586621680092344], [a6989586621680092344])) -> Type) (a6989586621680093857 :: i6989586621680092343) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericSplitAtSym0 :: TyFun i6989586621680092343 ([a6989586621680092344] ~> ([a6989586621680092344], [a6989586621680092344])) -> Type) (a6989586621680093857 :: i6989586621680092343) = GenericSplitAtSym1 a6989586621680093857 a6989586621680092344 :: TyFun [a6989586621680092344] ([a6989586621680092344], [a6989586621680092344]) -> Type |
data GenericSplitAtSym1 (a6989586621680093857 :: i6989586621680092343) :: forall a6989586621680092344. (~>) [a6989586621680092344] ([a6989586621680092344], [a6989586621680092344]) Source #
Instances
SuppressUnusedWarnings (GenericSplitAtSym1 a6989586621680093857 a6989586621680092344 :: TyFun [a6989586621680092344] ([a6989586621680092344], [a6989586621680092344]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericSplitAtSym1 a6989586621680093857 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621680093858 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericSplitAtSym1 a6989586621680093857 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621680093858 :: [a]) = GenericSplitAt a6989586621680093857 a6989586621680093858 |
type GenericSplitAtSym2 (a6989586621680093857 :: i6989586621680092343) (a6989586621680093858 :: [a6989586621680092344]) = GenericSplitAt a6989586621680093857 a6989586621680093858 Source #
data GenericIndexSym0 :: forall a6989586621680092342 i6989586621680092341. (~>) [a6989586621680092342] ((~>) i6989586621680092341 a6989586621680092342) Source #
Instances
SuppressUnusedWarnings (GenericIndexSym0 :: TyFun [a6989586621680092342] (i6989586621680092341 ~> a6989586621680092342) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericIndexSym0 :: TyFun [a6989586621680092342] (i6989586621680092341 ~> a6989586621680092342) -> Type) (a6989586621680093847 :: [a6989586621680092342]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericIndexSym0 :: TyFun [a6989586621680092342] (i6989586621680092341 ~> a6989586621680092342) -> Type) (a6989586621680093847 :: [a6989586621680092342]) = GenericIndexSym1 a6989586621680093847 i6989586621680092341 :: TyFun i6989586621680092341 a6989586621680092342 -> Type |
data GenericIndexSym1 (a6989586621680093847 :: [a6989586621680092342]) :: forall i6989586621680092341. (~>) i6989586621680092341 a6989586621680092342 Source #
Instances
SuppressUnusedWarnings (GenericIndexSym1 a6989586621680093847 i6989586621680092341 :: TyFun i6989586621680092341 a6989586621680092342 -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericIndexSym1 a6989586621680093847 i :: TyFun i a -> Type) (a6989586621680093848 :: i) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericIndexSym1 a6989586621680093847 i :: TyFun i a -> Type) (a6989586621680093848 :: i) = GenericIndex a6989586621680093847 a6989586621680093848 |
type GenericIndexSym2 (a6989586621680093847 :: [a6989586621680092342]) (a6989586621680093848 :: i6989586621680092341) = GenericIndex a6989586621680093847 a6989586621680093848 Source #
data GenericReplicateSym0 :: forall i6989586621680092339 a6989586621680092340. (~>) i6989586621680092339 ((~>) a6989586621680092340 [a6989586621680092340]) Source #
Instances
SuppressUnusedWarnings (GenericReplicateSym0 :: TyFun i6989586621680092339 (a6989586621680092340 ~> [a6989586621680092340]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericReplicateSym0 :: TyFun i6989586621680092339 (a6989586621680092340 ~> [a6989586621680092340]) -> Type) (a6989586621680093837 :: i6989586621680092339) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericReplicateSym0 :: TyFun i6989586621680092339 (a6989586621680092340 ~> [a6989586621680092340]) -> Type) (a6989586621680093837 :: i6989586621680092339) = GenericReplicateSym1 a6989586621680093837 a6989586621680092340 :: TyFun a6989586621680092340 [a6989586621680092340] -> Type |
data GenericReplicateSym1 (a6989586621680093837 :: i6989586621680092339) :: forall a6989586621680092340. (~>) a6989586621680092340 [a6989586621680092340] Source #
Instances
SuppressUnusedWarnings (GenericReplicateSym1 a6989586621680093837 a6989586621680092340 :: TyFun a6989586621680092340 [a6989586621680092340] -> Type) Source # | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () Source # | |
type Apply (GenericReplicateSym1 a6989586621680093837 a :: TyFun a [a] -> Type) (a6989586621680093838 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericReplicateSym1 a6989586621680093837 a :: TyFun a [a] -> Type) (a6989586621680093838 :: a) = GenericReplicate a6989586621680093837 a6989586621680093838 |
type GenericReplicateSym2 (a6989586621680093837 :: i6989586621680092339) (a6989586621680093838 :: a6989586621680092340) = GenericReplicate a6989586621680093837 a6989586621680093838 Source #