singletons-2.5: A framework for generating singleton types

Copyright(C) 2013-2014 Richard Eisenberg Jan Stolarek
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Prelude.List

Contents

Description

Defines functions and datatypes relating to the singleton for '[]', including a singletons version of a few of the definitions in Data.List.

Because many of these definitions are produced by Template Haskell, it is not possible to create proper Haddock documentation. Please look up the corresponding operation in Data.List. Also, please excuse the apparent repeated variable names. This is due to an interaction between Template Haskell and Haddock.

Synopsis
  • data family Sing :: k -> Type
  • type SList = (Sing :: [a] -> Type)
  • type family (a :: [a]) ++ (a :: [a]) :: [a] where ...
  • (%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a])
  • type family Head (a :: [a]) :: a where ...
  • sHead :: forall a (t :: [a]). Sing t -> Sing (Apply HeadSym0 t :: a)
  • type family Last (a :: [a]) :: a where ...
  • sLast :: forall a (t :: [a]). Sing t -> Sing (Apply LastSym0 t :: a)
  • type family Tail (a :: [a]) :: [a] where ...
  • sTail :: forall a (t :: [a]). Sing t -> Sing (Apply TailSym0 t :: [a])
  • type family Init (a :: [a]) :: [a] where ...
  • sInit :: forall a (t :: [a]). Sing t -> Sing (Apply InitSym0 t :: [a])
  • type family Null (arg :: t a) :: Bool
  • sNull :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply NullSym0 t :: Bool)
  • type family Length (arg :: t a) :: Nat
  • sLength :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply LengthSym0 t :: Nat)
  • type family Map (a :: (~>) a b) (a :: [a]) :: [b] where ...
  • sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b])
  • type family Reverse (a :: [a]) :: [a] where ...
  • sReverse :: forall a (t :: [a]). Sing t -> Sing (Apply ReverseSym0 t :: [a])
  • type family Intersperse (a :: a) (a :: [a]) :: [a] where ...
  • sIntersperse :: forall a (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a])
  • type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ...
  • sIntercalate :: forall a (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a])
  • type family Transpose (a :: [[a]]) :: [[a]] where ...
  • sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]])
  • type family Subsequences (a :: [a]) :: [[a]] where ...
  • sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]])
  • type family Permutations (a :: [a]) :: [[a]] where ...
  • sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]])
  • type family Foldl (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
  • sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b)
  • type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
  • sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b)
  • type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
  • sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a)
  • type family Foldl1' (a :: (~>) a ((~>) a a)) (a :: [a]) :: a where ...
  • sFoldl1' :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a)
  • type family Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b
  • sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b)
  • type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
  • sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a)
  • type family Concat (a :: t [a]) :: [a] where ...
  • sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a])
  • type family ConcatMap (a :: (~>) a [b]) (a :: t a) :: [b] where ...
  • sConcatMap :: forall t a b (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b])
  • type family And (a :: t Bool) :: Bool where ...
  • sAnd :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool)
  • type family Or (a :: t Bool) :: Bool where ...
  • sOr :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool)
  • type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ...
  • sAny :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool)
  • type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ...
  • sAll :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool)
  • type family Sum (arg :: t a) :: a
  • sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a)
  • type family Product (arg :: t a) :: a
  • sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a)
  • type family Maximum (arg :: t a) :: a
  • sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a)
  • type family Minimum (arg :: t a) :: a
  • sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a)
  • type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: [b] where ...
  • sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b])
  • type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
  • sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a])
  • type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: [b] where ...
  • sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b])
  • type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
  • sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a])
  • type family MapAccumL (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
  • sMapAccumL :: forall t a b c (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (a, t c))
  • type family MapAccumR (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
  • sMapAccumR :: forall t a b c (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c))
  • type family Replicate (a :: Nat) (a :: a) :: [a] where ...
  • sReplicate :: forall a (t :: Nat) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a])
  • type family Unfoldr (a :: (~>) b (Maybe (a, b))) (a :: b) :: [a] where ...
  • sUnfoldr :: forall b a (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a])
  • type family Take (a :: Nat) (a :: [a]) :: [a] where ...
  • sTake :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a])
  • type family Drop (a :: Nat) (a :: [a]) :: [a] where ...
  • sDrop :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a])
  • type family SplitAt (a :: Nat) (a :: [a]) :: ([a], [a]) where ...
  • sSplitAt :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a]))
  • type family TakeWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
  • sTakeWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a])
  • type family DropWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
  • sDropWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a])
  • type family DropWhileEnd (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
  • sDropWhileEnd :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a])
  • type family Span (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
  • sSpan :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a]))
  • type family Break (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
  • sBreak :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a]))
  • type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ...
  • type family Group (a :: [a]) :: [[a]] where ...
  • sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [[a]])
  • type family Inits (a :: [a]) :: [[a]] where ...
  • sInits :: forall a (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: [[a]])
  • type family Tails (a :: [a]) :: [[a]] where ...
  • sTails :: forall a (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: [[a]])
  • type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ...
  • sIsPrefixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool)
  • type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ...
  • sIsSuffixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool)
  • type family IsInfixOf (a :: [a]) (a :: [a]) :: Bool where ...
  • sIsInfixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool)
  • type family Elem (arg :: a) (arg :: t a) :: Bool
  • sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool)
  • type family NotElem (a :: a) (a :: t a) :: Bool where ...
  • sNotElem :: forall t a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool)
  • type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ...
  • sLookup :: forall a b (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b)
  • type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ...
  • sFind :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a)
  • type family Filter (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
  • sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
  • type family Partition (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
  • sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
  • type family (a :: [a]) !! (a :: Nat) :: a where ...
  • (%!!) :: forall a (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a)
  • type family ElemIndex (a :: a) (a :: [a]) :: Maybe Nat where ...
  • sElemIndex :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat)
  • type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ...
  • sElemIndices :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat])
  • type family FindIndex (a :: (~>) a Bool) (a :: [a]) :: Maybe Nat where ...
  • sFindIndex :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat)
  • type family FindIndices (a :: (~>) a Bool) (a :: [a]) :: [Nat] where ...
  • sFindIndices :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat])
  • type family Zip (a :: [a]) (a :: [b]) :: [(a, b)] where ...
  • sZip :: forall a b (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)])
  • type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ...
  • sZip3 :: forall a b c (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)])
  • type family Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ...
  • type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ...
  • type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ...
  • type family Zip7 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [(a, b, c, d, e, f, g)] where ...
  • type family ZipWith (a :: (~>) a ((~>) b c)) (a :: [a]) (a :: [b]) :: [c] where ...
  • sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c])
  • type family ZipWith3 (a :: (~>) a ((~>) b ((~>) c d))) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ...
  • sZipWith3 :: forall a b c d (t :: (~>) a ((~>) b ((~>) c d))) (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d])
  • type family ZipWith4 (a :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ...
  • type family ZipWith5 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ...
  • type family ZipWith6 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ...
  • type family ZipWith7 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ...
  • type family Unzip (a :: [(a, b)]) :: ([a], [b]) where ...
  • sUnzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b]))
  • type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ...
  • sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c]))
  • type family Unzip4 (a :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
  • sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d]))
  • type family Unzip5 (a :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ...
  • sUnzip5 :: forall a b c d e (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e]))
  • type family Unzip6 (a :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ...
  • sUnzip6 :: forall a b c d e f (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f]))
  • type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
  • sUnzip7 :: forall a b c d e f g (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g]))
  • type family Unlines (a :: [Symbol]) :: Symbol where ...
  • sUnlines :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnlinesSym0 t :: Symbol)
  • type family Unwords (a :: [Symbol]) :: Symbol where ...
  • sUnwords :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnwordsSym0 t :: Symbol)
  • type family Nub (a :: [a]) :: [a] where ...
  • sNub :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply NubSym0 t :: [a])
  • type family Delete (a :: a) (a :: [a]) :: [a] where ...
  • sDelete :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a])
  • type family (a :: [a]) \\ (a :: [a]) :: [a] where ...
  • (%\\) :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (\\@#@$) t) t :: [a])
  • type family Union (a :: [a]) (a :: [a]) :: [a] where ...
  • sUnion :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a])
  • type family Intersect (a :: [a]) (a :: [a]) :: [a] where ...
  • sIntersect :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a])
  • type family Insert (a :: a) (a :: [a]) :: [a] where ...
  • sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a])
  • type family Sort (a :: [a]) :: [a] where ...
  • sSort :: forall a (t :: [a]). SOrd a => Sing t -> Sing (Apply SortSym0 t :: [a])
  • type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [a] where ...
  • sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a])
  • type family DeleteBy (a :: (~>) a ((~>) a Bool)) (a :: a) (a :: [a]) :: [a] where ...
  • sDeleteBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a])
  • type family DeleteFirstsBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
  • sDeleteFirstsBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a])
  • type family UnionBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
  • sUnionBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a])
  • type family IntersectBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
  • sIntersectBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a])
  • type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [[a]] where ...
  • sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]])
  • type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: [a]) :: [a] where ...
  • sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a])
  • type family InsertBy (a :: (~>) a ((~>) a Ordering)) (a :: a) (a :: [a]) :: [a] where ...
  • sInsertBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a])
  • type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
  • sMaximumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a)
  • type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
  • sMinimumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a)
  • type family GenericLength (a :: [a]) :: i where ...
  • sGenericLength :: forall i a (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i)
  • type family GenericTake (a :: i) (a :: [a]) :: [a] where ...
  • type family GenericDrop (a :: i) (a :: [a]) :: [a] where ...
  • type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ...
  • type family GenericIndex (a :: [a]) (a :: i) :: a where ...
  • type family GenericReplicate (a :: i) (a :: a) :: [a] where ...
  • type NilSym0 = '[]
  • data (:@#@$) :: forall (a3530822107858468865 :: Type). (~>) a3530822107858468865 ((~>) [a3530822107858468865] [(a3530822107858468865 :: Type)])
  • data (:@#@$$) (t6989586621679298917 :: (a3530822107858468865 :: Type)) :: (~>) [a3530822107858468865] [(a3530822107858468865 :: Type)]
  • type (:@#@$$$) (t6989586621679298917 :: a3530822107858468865) (t6989586621679298918 :: [a3530822107858468865]) = (:) t6989586621679298917 t6989586621679298918
  • type (++@#@$$$) (a6989586621679521123 :: [a6989586621679520926]) (a6989586621679521124 :: [a6989586621679520926]) = (++) a6989586621679521123 a6989586621679521124
  • data (++@#@$$) (a6989586621679521123 :: [a6989586621679520926]) :: (~>) [a6989586621679520926] [a6989586621679520926]
  • data (++@#@$) :: forall a6989586621679520926. (~>) [a6989586621679520926] ((~>) [a6989586621679520926] [a6989586621679520926])
  • data HeadSym0 :: forall a6989586621679940142. (~>) [a6989586621679940142] a6989586621679940142
  • type HeadSym1 (a6989586621679950665 :: [a6989586621679940142]) = Head a6989586621679950665
  • data LastSym0 :: forall a6989586621679940141. (~>) [a6989586621679940141] a6989586621679940141
  • type LastSym1 (a6989586621679950660 :: [a6989586621679940141]) = Last a6989586621679950660
  • data TailSym0 :: forall a6989586621679940140. (~>) [a6989586621679940140] [a6989586621679940140]
  • type TailSym1 (a6989586621679950657 :: [a6989586621679940140]) = Tail a6989586621679950657
  • data InitSym0 :: forall a6989586621679940139. (~>) [a6989586621679940139] [a6989586621679940139]
  • type InitSym1 (a6989586621679950643 :: [a6989586621679940139]) = Init a6989586621679950643
  • data NullSym0 :: forall a6989586621680452738 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452738) Bool
  • type NullSym1 (arg6989586621680453386 :: t6989586621680452723 a6989586621680452738) = Null arg6989586621680453386
  • data LengthSym0 :: forall a6989586621680452739 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452739) Nat
  • type LengthSym1 (arg6989586621680453388 :: t6989586621680452723 a6989586621680452739) = Length arg6989586621680453388
  • data MapSym0 :: forall a6989586621679520927 b6989586621679520928. (~>) ((~>) a6989586621679520927 b6989586621679520928) ((~>) [a6989586621679520927] [b6989586621679520928])
  • data MapSym1 (a6989586621679521131 :: (~>) a6989586621679520927 b6989586621679520928) :: (~>) [a6989586621679520927] [b6989586621679520928]
  • type MapSym2 (a6989586621679521131 :: (~>) a6989586621679520927 b6989586621679520928) (a6989586621679521132 :: [a6989586621679520927]) = Map a6989586621679521131 a6989586621679521132
  • data ReverseSym0 :: forall a6989586621679940137. (~>) [a6989586621679940137] [a6989586621679940137]
  • type ReverseSym1 (a6989586621679950596 :: [a6989586621679940137]) = Reverse a6989586621679950596
  • data IntersperseSym0 :: forall a6989586621679940136. (~>) a6989586621679940136 ((~>) [a6989586621679940136] [a6989586621679940136])
  • data IntersperseSym1 (a6989586621679950583 :: a6989586621679940136) :: (~>) [a6989586621679940136] [a6989586621679940136]
  • type IntersperseSym2 (a6989586621679950583 :: a6989586621679940136) (a6989586621679950584 :: [a6989586621679940136]) = Intersperse a6989586621679950583 a6989586621679950584
  • data IntercalateSym0 :: forall a6989586621679940135. (~>) [a6989586621679940135] ((~>) [[a6989586621679940135]] [a6989586621679940135])
  • data IntercalateSym1 (a6989586621679950590 :: [a6989586621679940135]) :: (~>) [[a6989586621679940135]] [a6989586621679940135]
  • type IntercalateSym2 (a6989586621679950590 :: [a6989586621679940135]) (a6989586621679950591 :: [[a6989586621679940135]]) = Intercalate a6989586621679950590 a6989586621679950591
  • data TransposeSym0 :: forall a6989586621679940022. (~>) [[a6989586621679940022]] [[a6989586621679940022]]
  • type TransposeSym1 (a6989586621679950668 :: [[a6989586621679940022]]) = Transpose a6989586621679950668
  • data SubsequencesSym0 :: forall a6989586621679940134. (~>) [a6989586621679940134] [[a6989586621679940134]]
  • type SubsequencesSym1 (a6989586621679950580 :: [a6989586621679940134]) = Subsequences a6989586621679950580
  • data PermutationsSym0 :: forall a6989586621679940131. (~>) [a6989586621679940131] [[a6989586621679940131]]
  • type PermutationsSym1 (a6989586621679950462 :: [a6989586621679940131]) = Permutations a6989586621679950462
  • data FoldlSym0 :: forall a6989586621680452732 b6989586621680452731 t6989586621680452723. (~>) ((~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) ((~>) b6989586621680452731 ((~>) (t6989586621680452723 a6989586621680452732) b6989586621680452731))
  • data FoldlSym1 (arg6989586621680453364 :: (~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) :: forall t6989586621680452723. (~>) b6989586621680452731 ((~>) (t6989586621680452723 a6989586621680452732) b6989586621680452731)
  • data FoldlSym2 (arg6989586621680453364 :: (~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) (arg6989586621680453365 :: b6989586621680452731) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452732) b6989586621680452731
  • type FoldlSym3 (arg6989586621680453364 :: (~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) (arg6989586621680453365 :: b6989586621680452731) (arg6989586621680453366 :: t6989586621680452723 a6989586621680452732) = Foldl arg6989586621680453364 arg6989586621680453365 arg6989586621680453366
  • data Foldl'Sym0 :: forall a6989586621680452734 b6989586621680452733 t6989586621680452723. (~>) ((~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) ((~>) b6989586621680452733 ((~>) (t6989586621680452723 a6989586621680452734) b6989586621680452733))
  • data Foldl'Sym1 (arg6989586621680453370 :: (~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) :: forall t6989586621680452723. (~>) b6989586621680452733 ((~>) (t6989586621680452723 a6989586621680452734) b6989586621680452733)
  • data Foldl'Sym2 (arg6989586621680453370 :: (~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) (arg6989586621680453371 :: b6989586621680452733) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452734) b6989586621680452733
  • type Foldl'Sym3 (arg6989586621680453370 :: (~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) (arg6989586621680453371 :: b6989586621680452733) (arg6989586621680453372 :: t6989586621680452723 a6989586621680452734) = Foldl' arg6989586621680453370 arg6989586621680453371 arg6989586621680453372
  • data Foldl1Sym0 :: forall a6989586621680452736 t6989586621680452723. (~>) ((~>) a6989586621680452736 ((~>) a6989586621680452736 a6989586621680452736)) ((~>) (t6989586621680452723 a6989586621680452736) a6989586621680452736)
  • data Foldl1Sym1 (arg6989586621680453380 :: (~>) a6989586621680452736 ((~>) a6989586621680452736 a6989586621680452736)) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452736) a6989586621680452736
  • type Foldl1Sym2 (arg6989586621680453380 :: (~>) a6989586621680452736 ((~>) a6989586621680452736 a6989586621680452736)) (arg6989586621680453381 :: t6989586621680452723 a6989586621680452736) = Foldl1 arg6989586621680453380 arg6989586621680453381
  • data Foldl1'Sym0 :: forall a6989586621679940127. (~>) ((~>) a6989586621679940127 ((~>) a6989586621679940127 a6989586621679940127)) ((~>) [a6989586621679940127] a6989586621679940127)
  • data Foldl1'Sym1 (a6989586621679950455 :: (~>) a6989586621679940127 ((~>) a6989586621679940127 a6989586621679940127)) :: (~>) [a6989586621679940127] a6989586621679940127
  • type Foldl1'Sym2 (a6989586621679950455 :: (~>) a6989586621679940127 ((~>) a6989586621679940127 a6989586621679940127)) (a6989586621679950456 :: [a6989586621679940127]) = Foldl1' a6989586621679950455 a6989586621679950456
  • data FoldrSym0 :: forall a6989586621680452727 b6989586621680452728 t6989586621680452723. (~>) ((~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) ((~>) b6989586621680452728 ((~>) (t6989586621680452723 a6989586621680452727) b6989586621680452728))
  • data FoldrSym1 (arg6989586621680453352 :: (~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) :: forall t6989586621680452723. (~>) b6989586621680452728 ((~>) (t6989586621680452723 a6989586621680452727) b6989586621680452728)
  • data FoldrSym2 (arg6989586621680453352 :: (~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) (arg6989586621680453353 :: b6989586621680452728) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452727) b6989586621680452728
  • type FoldrSym3 (arg6989586621680453352 :: (~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) (arg6989586621680453353 :: b6989586621680452728) (arg6989586621680453354 :: t6989586621680452723 a6989586621680452727) = Foldr arg6989586621680453352 arg6989586621680453353 arg6989586621680453354
  • data Foldr1Sym0 :: forall a6989586621680452735 t6989586621680452723. (~>) ((~>) a6989586621680452735 ((~>) a6989586621680452735 a6989586621680452735)) ((~>) (t6989586621680452723 a6989586621680452735) a6989586621680452735)
  • data Foldr1Sym1 (arg6989586621680453376 :: (~>) a6989586621680452735 ((~>) a6989586621680452735 a6989586621680452735)) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452735) a6989586621680452735
  • type Foldr1Sym2 (arg6989586621680453376 :: (~>) a6989586621680452735 ((~>) a6989586621680452735 a6989586621680452735)) (arg6989586621680453377 :: t6989586621680452723 a6989586621680452735) = Foldr1 arg6989586621680453376 arg6989586621680453377
  • data ConcatSym0 :: forall a6989586621680452649 t6989586621680452648. (~>) (t6989586621680452648 [a6989586621680452649]) [a6989586621680452649]
  • type ConcatSym1 (a6989586621680453234 :: t6989586621680452648 [a6989586621680452649]) = Concat a6989586621680453234
  • data ConcatMapSym0 :: forall a6989586621680452646 b6989586621680452647 t6989586621680452645. (~>) ((~>) a6989586621680452646 [b6989586621680452647]) ((~>) (t6989586621680452645 a6989586621680452646) [b6989586621680452647])
  • data ConcatMapSym1 (a6989586621680453218 :: (~>) a6989586621680452646 [b6989586621680452647]) :: forall t6989586621680452645. (~>) (t6989586621680452645 a6989586621680452646) [b6989586621680452647]
  • type ConcatMapSym2 (a6989586621680453218 :: (~>) a6989586621680452646 [b6989586621680452647]) (a6989586621680453219 :: t6989586621680452645 a6989586621680452646) = ConcatMap a6989586621680453218 a6989586621680453219
  • data AndSym0 :: forall t6989586621680452644. (~>) (t6989586621680452644 Bool) Bool
  • type AndSym1 (a6989586621680453209 :: t6989586621680452644 Bool) = And a6989586621680453209
  • data OrSym0 :: forall t6989586621680452643. (~>) (t6989586621680452643 Bool) Bool
  • type OrSym1 (a6989586621680453200 :: t6989586621680452643 Bool) = Or a6989586621680453200
  • data AnySym0 :: forall a6989586621680452642 t6989586621680452641. (~>) ((~>) a6989586621680452642 Bool) ((~>) (t6989586621680452641 a6989586621680452642) Bool)
  • data AnySym1 (a6989586621680453187 :: (~>) a6989586621680452642 Bool) :: forall t6989586621680452641. (~>) (t6989586621680452641 a6989586621680452642) Bool
  • type AnySym2 (a6989586621680453187 :: (~>) a6989586621680452642 Bool) (a6989586621680453188 :: t6989586621680452641 a6989586621680452642) = Any a6989586621680453187 a6989586621680453188
  • data AllSym0 :: forall a6989586621680452640 t6989586621680452639. (~>) ((~>) a6989586621680452640 Bool) ((~>) (t6989586621680452639 a6989586621680452640) Bool)
  • data AllSym1 (a6989586621680453174 :: (~>) a6989586621680452640 Bool) :: forall t6989586621680452639. (~>) (t6989586621680452639 a6989586621680452640) Bool
  • type AllSym2 (a6989586621680453174 :: (~>) a6989586621680452640 Bool) (a6989586621680453175 :: t6989586621680452639 a6989586621680452640) = All a6989586621680453174 a6989586621680453175
  • data SumSym0 :: forall a6989586621680452743 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452743) a6989586621680452743
  • type SumSym1 (arg6989586621680453398 :: t6989586621680452723 a6989586621680452743) = Sum arg6989586621680453398
  • data ProductSym0 :: forall a6989586621680452744 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452744) a6989586621680452744
  • type ProductSym1 (arg6989586621680453400 :: t6989586621680452723 a6989586621680452744) = Product arg6989586621680453400
  • data MaximumSym0 :: forall a6989586621680452741 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452741) a6989586621680452741
  • type MaximumSym1 (arg6989586621680453394 :: t6989586621680452723 a6989586621680452741) = Maximum arg6989586621680453394
  • data MinimumSym0 :: forall a6989586621680452742 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452742) a6989586621680452742
  • type MinimumSym1 (arg6989586621680453396 :: t6989586621680452723 a6989586621680452742) = Minimum arg6989586621680453396
  • data ScanlSym0 :: forall a6989586621679940120 b6989586621679940119. (~>) ((~>) b6989586621679940119 ((~>) a6989586621679940120 b6989586621679940119)) ((~>) b6989586621679940119 ((~>) [a6989586621679940120] [b6989586621679940119]))
  • data ScanlSym1 (a6989586621679950228 :: (~>) b6989586621679940119 ((~>) a6989586621679940120 b6989586621679940119)) :: (~>) b6989586621679940119 ((~>) [a6989586621679940120] [b6989586621679940119])
  • data ScanlSym2 (a6989586621679950228 :: (~>) b6989586621679940119 ((~>) a6989586621679940120 b6989586621679940119)) (a6989586621679950229 :: b6989586621679940119) :: (~>) [a6989586621679940120] [b6989586621679940119]
  • type ScanlSym3 (a6989586621679950228 :: (~>) b6989586621679940119 ((~>) a6989586621679940120 b6989586621679940119)) (a6989586621679950229 :: b6989586621679940119) (a6989586621679950230 :: [a6989586621679940120]) = Scanl a6989586621679950228 a6989586621679950229 a6989586621679950230
  • data Scanl1Sym0 :: forall a6989586621679940118. (~>) ((~>) a6989586621679940118 ((~>) a6989586621679940118 a6989586621679940118)) ((~>) [a6989586621679940118] [a6989586621679940118])
  • data Scanl1Sym1 (a6989586621679950242 :: (~>) a6989586621679940118 ((~>) a6989586621679940118 a6989586621679940118)) :: (~>) [a6989586621679940118] [a6989586621679940118]
  • type Scanl1Sym2 (a6989586621679950242 :: (~>) a6989586621679940118 ((~>) a6989586621679940118 a6989586621679940118)) (a6989586621679950243 :: [a6989586621679940118]) = Scanl1 a6989586621679950242 a6989586621679950243
  • data ScanrSym0 :: forall a6989586621679940116 b6989586621679940117. (~>) ((~>) a6989586621679940116 ((~>) b6989586621679940117 b6989586621679940117)) ((~>) b6989586621679940117 ((~>) [a6989586621679940116] [b6989586621679940117]))
  • data ScanrSym1 (a6989586621679950207 :: (~>) a6989586621679940116 ((~>) b6989586621679940117 b6989586621679940117)) :: (~>) b6989586621679940117 ((~>) [a6989586621679940116] [b6989586621679940117])
  • data ScanrSym2 (a6989586621679950207 :: (~>) a6989586621679940116 ((~>) b6989586621679940117 b6989586621679940117)) (a6989586621679950208 :: b6989586621679940117) :: (~>) [a6989586621679940116] [b6989586621679940117]
  • type ScanrSym3 (a6989586621679950207 :: (~>) a6989586621679940116 ((~>) b6989586621679940117 b6989586621679940117)) (a6989586621679950208 :: b6989586621679940117) (a6989586621679950209 :: [a6989586621679940116]) = Scanr a6989586621679950207 a6989586621679950208 a6989586621679950209
  • data Scanr1Sym0 :: forall a6989586621679940115. (~>) ((~>) a6989586621679940115 ((~>) a6989586621679940115 a6989586621679940115)) ((~>) [a6989586621679940115] [a6989586621679940115])
  • data Scanr1Sym1 (a6989586621679950183 :: (~>) a6989586621679940115 ((~>) a6989586621679940115 a6989586621679940115)) :: (~>) [a6989586621679940115] [a6989586621679940115]
  • type Scanr1Sym2 (a6989586621679950183 :: (~>) a6989586621679940115 ((~>) a6989586621679940115 a6989586621679940115)) (a6989586621679950184 :: [a6989586621679940115]) = Scanr1 a6989586621679950183 a6989586621679950184
  • data MapAccumLSym0 :: forall a6989586621680756572 b6989586621680756573 c6989586621680756574 t6989586621680756571. (~>) ((~>) a6989586621680756572 ((~>) b6989586621680756573 (a6989586621680756572, c6989586621680756574))) ((~>) a6989586621680756572 ((~>) (t6989586621680756571 b6989586621680756573) (a6989586621680756572, t6989586621680756571 c6989586621680756574)))
  • data MapAccumLSym1 (a6989586621680757111 :: (~>) a6989586621680756572 ((~>) b6989586621680756573 (a6989586621680756572, c6989586621680756574))) :: forall t6989586621680756571. (~>) a6989586621680756572 ((~>) (t6989586621680756571 b6989586621680756573) (a6989586621680756572, t6989586621680756571 c6989586621680756574))
  • data MapAccumLSym2 (a6989586621680757111 :: (~>) a6989586621680756572 ((~>) b6989586621680756573 (a6989586621680756572, c6989586621680756574))) (a6989586621680757112 :: a6989586621680756572) :: forall t6989586621680756571. (~>) (t6989586621680756571 b6989586621680756573) (a6989586621680756572, t6989586621680756571 c6989586621680756574)
  • type MapAccumLSym3 (a6989586621680757111 :: (~>) a6989586621680756572 ((~>) b6989586621680756573 (a6989586621680756572, c6989586621680756574))) (a6989586621680757112 :: a6989586621680756572) (a6989586621680757113 :: t6989586621680756571 b6989586621680756573) = MapAccumL a6989586621680757111 a6989586621680757112 a6989586621680757113
  • data MapAccumRSym0 :: forall a6989586621680756568 b6989586621680756569 c6989586621680756570 t6989586621680756567. (~>) ((~>) a6989586621680756568 ((~>) b6989586621680756569 (a6989586621680756568, c6989586621680756570))) ((~>) a6989586621680756568 ((~>) (t6989586621680756567 b6989586621680756569) (a6989586621680756568, t6989586621680756567 c6989586621680756570)))
  • data MapAccumRSym1 (a6989586621680757094 :: (~>) a6989586621680756568 ((~>) b6989586621680756569 (a6989586621680756568, c6989586621680756570))) :: forall t6989586621680756567. (~>) a6989586621680756568 ((~>) (t6989586621680756567 b6989586621680756569) (a6989586621680756568, t6989586621680756567 c6989586621680756570))
  • data MapAccumRSym2 (a6989586621680757094 :: (~>) a6989586621680756568 ((~>) b6989586621680756569 (a6989586621680756568, c6989586621680756570))) (a6989586621680757095 :: a6989586621680756568) :: forall t6989586621680756567. (~>) (t6989586621680756567 b6989586621680756569) (a6989586621680756568, t6989586621680756567 c6989586621680756570)
  • type MapAccumRSym3 (a6989586621680757094 :: (~>) a6989586621680756568 ((~>) b6989586621680756569 (a6989586621680756568, c6989586621680756570))) (a6989586621680757095 :: a6989586621680756568) (a6989586621680757096 :: t6989586621680756567 b6989586621680756569) = MapAccumR a6989586621680757094 a6989586621680757095 a6989586621680757096
  • data ReplicateSym0 :: forall a6989586621679940023. (~>) Nat ((~>) a6989586621679940023 [a6989586621679940023])
  • data ReplicateSym1 (a6989586621679949325 :: Nat) :: forall a6989586621679940023. (~>) a6989586621679940023 [a6989586621679940023]
  • type ReplicateSym2 (a6989586621679949325 :: Nat) (a6989586621679949326 :: a6989586621679940023) = Replicate a6989586621679949325 a6989586621679949326
  • data UnfoldrSym0 :: forall a6989586621679940108 b6989586621679940107. (~>) ((~>) b6989586621679940107 (Maybe (a6989586621679940108, b6989586621679940107))) ((~>) b6989586621679940107 [a6989586621679940108])
  • data UnfoldrSym1 (a6989586621679950041 :: (~>) b6989586621679940107 (Maybe (a6989586621679940108, b6989586621679940107))) :: (~>) b6989586621679940107 [a6989586621679940108]
  • type UnfoldrSym2 (a6989586621679950041 :: (~>) b6989586621679940107 (Maybe (a6989586621679940108, b6989586621679940107))) (a6989586621679950042 :: b6989586621679940107) = Unfoldr a6989586621679950041 a6989586621679950042
  • data TakeSym0 :: forall a6989586621679940039. (~>) Nat ((~>) [a6989586621679940039] [a6989586621679940039])
  • data TakeSym1 (a6989586621679949421 :: Nat) :: forall a6989586621679940039. (~>) [a6989586621679940039] [a6989586621679940039]
  • type TakeSym2 (a6989586621679949421 :: Nat) (a6989586621679949422 :: [a6989586621679940039]) = Take a6989586621679949421 a6989586621679949422
  • data DropSym0 :: forall a6989586621679940038. (~>) Nat ((~>) [a6989586621679940038] [a6989586621679940038])
  • data DropSym1 (a6989586621679949407 :: Nat) :: forall a6989586621679940038. (~>) [a6989586621679940038] [a6989586621679940038]
  • type DropSym2 (a6989586621679949407 :: Nat) (a6989586621679949408 :: [a6989586621679940038]) = Drop a6989586621679949407 a6989586621679949408
  • data SplitAtSym0 :: forall a6989586621679940037. (~>) Nat ((~>) [a6989586621679940037] ([a6989586621679940037], [a6989586621679940037]))
  • data SplitAtSym1 (a6989586621679949435 :: Nat) :: forall a6989586621679940037. (~>) [a6989586621679940037] ([a6989586621679940037], [a6989586621679940037])
  • type SplitAtSym2 (a6989586621679949435 :: Nat) (a6989586621679949436 :: [a6989586621679940037]) = SplitAt a6989586621679949435 a6989586621679949436
  • data TakeWhileSym0 :: forall a6989586621679940044. (~>) ((~>) a6989586621679940044 Bool) ((~>) [a6989586621679940044] [a6989586621679940044])
  • data TakeWhileSym1 (a6989586621679949579 :: (~>) a6989586621679940044 Bool) :: (~>) [a6989586621679940044] [a6989586621679940044]
  • type TakeWhileSym2 (a6989586621679949579 :: (~>) a6989586621679940044 Bool) (a6989586621679949580 :: [a6989586621679940044]) = TakeWhile a6989586621679949579 a6989586621679949580
  • data DropWhileSym0 :: forall a6989586621679940043. (~>) ((~>) a6989586621679940043 Bool) ((~>) [a6989586621679940043] [a6989586621679940043])
  • data DropWhileSym1 (a6989586621679949561 :: (~>) a6989586621679940043 Bool) :: (~>) [a6989586621679940043] [a6989586621679940043]
  • type DropWhileSym2 (a6989586621679949561 :: (~>) a6989586621679940043 Bool) (a6989586621679949562 :: [a6989586621679940043]) = DropWhile a6989586621679949561 a6989586621679949562
  • data DropWhileEndSym0 :: forall a6989586621679940042. (~>) ((~>) a6989586621679940042 Bool) ((~>) [a6989586621679940042] [a6989586621679940042])
  • data DropWhileEndSym1 (a6989586621679950617 :: (~>) a6989586621679940042 Bool) :: (~>) [a6989586621679940042] [a6989586621679940042]
  • type DropWhileEndSym2 (a6989586621679950617 :: (~>) a6989586621679940042 Bool) (a6989586621679950618 :: [a6989586621679940042]) = DropWhileEnd a6989586621679950617 a6989586621679950618
  • data SpanSym0 :: forall a6989586621679940041. (~>) ((~>) a6989586621679940041 Bool) ((~>) [a6989586621679940041] ([a6989586621679940041], [a6989586621679940041]))
  • data SpanSym1 (a6989586621679949484 :: (~>) a6989586621679940041 Bool) :: (~>) [a6989586621679940041] ([a6989586621679940041], [a6989586621679940041])
  • type SpanSym2 (a6989586621679949484 :: (~>) a6989586621679940041 Bool) (a6989586621679949485 :: [a6989586621679940041]) = Span a6989586621679949484 a6989586621679949485
  • data BreakSym0 :: forall a6989586621679940040. (~>) ((~>) a6989586621679940040 Bool) ((~>) [a6989586621679940040] ([a6989586621679940040], [a6989586621679940040]))
  • data BreakSym1 (a6989586621679949441 :: (~>) a6989586621679940040 Bool) :: (~>) [a6989586621679940040] ([a6989586621679940040], [a6989586621679940040])
  • type BreakSym2 (a6989586621679949441 :: (~>) a6989586621679940040 Bool) (a6989586621679949442 :: [a6989586621679940040]) = Break a6989586621679949441 a6989586621679949442
  • data StripPrefixSym0 :: forall a6989586621680066266. (~>) [a6989586621680066266] ((~>) [a6989586621680066266] (Maybe [a6989586621680066266]))
  • data StripPrefixSym1 (a6989586621680078976 :: [a6989586621680066266]) :: (~>) [a6989586621680066266] (Maybe [a6989586621680066266])
  • type StripPrefixSym2 (a6989586621680078976 :: [a6989586621680066266]) (a6989586621680078977 :: [a6989586621680066266]) = StripPrefix a6989586621680078976 a6989586621680078977
  • data GroupSym0 :: forall a6989586621679940036. (~>) [a6989586621679940036] [[a6989586621679940036]]
  • type GroupSym1 (a6989586621679949558 :: [a6989586621679940036]) = Group a6989586621679949558
  • data InitsSym0 :: forall a6989586621679940106. (~>) [a6989586621679940106] [[a6989586621679940106]]
  • type InitsSym1 (a6989586621679950033 :: [a6989586621679940106]) = Inits a6989586621679950033
  • data TailsSym0 :: forall a6989586621679940105. (~>) [a6989586621679940105] [[a6989586621679940105]]
  • type TailsSym1 (a6989586621679950026 :: [a6989586621679940105]) = Tails a6989586621679950026
  • data IsPrefixOfSym0 :: forall a6989586621679940104. (~>) [a6989586621679940104] ((~>) [a6989586621679940104] Bool)
  • data IsPrefixOfSym1 (a6989586621679950018 :: [a6989586621679940104]) :: (~>) [a6989586621679940104] Bool
  • type IsPrefixOfSym2 (a6989586621679950018 :: [a6989586621679940104]) (a6989586621679950019 :: [a6989586621679940104]) = IsPrefixOf a6989586621679950018 a6989586621679950019
  • data IsSuffixOfSym0 :: forall a6989586621679940103. (~>) [a6989586621679940103] ((~>) [a6989586621679940103] Bool)
  • data IsSuffixOfSym1 (a6989586621679950609 :: [a6989586621679940103]) :: (~>) [a6989586621679940103] Bool
  • type IsSuffixOfSym2 (a6989586621679950609 :: [a6989586621679940103]) (a6989586621679950610 :: [a6989586621679940103]) = IsSuffixOf a6989586621679950609 a6989586621679950610
  • data IsInfixOfSym0 :: forall a6989586621679940102. (~>) [a6989586621679940102] ((~>) [a6989586621679940102] Bool)
  • data IsInfixOfSym1 (a6989586621679950256 :: [a6989586621679940102]) :: (~>) [a6989586621679940102] Bool
  • type IsInfixOfSym2 (a6989586621679950256 :: [a6989586621679940102]) (a6989586621679950257 :: [a6989586621679940102]) = IsInfixOf a6989586621679950256 a6989586621679950257
  • data ElemSym0 :: forall a6989586621680452740 t6989586621680452723. (~>) a6989586621680452740 ((~>) (t6989586621680452723 a6989586621680452740) Bool)
  • data ElemSym1 (arg6989586621680453390 :: a6989586621680452740) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452740) Bool
  • type ElemSym2 (arg6989586621680453390 :: a6989586621680452740) (arg6989586621680453391 :: t6989586621680452723 a6989586621680452740) = Elem arg6989586621680453390 arg6989586621680453391
  • data NotElemSym0 :: forall a6989586621680452634 t6989586621680452633. (~>) a6989586621680452634 ((~>) (t6989586621680452633 a6989586621680452634) Bool)
  • data NotElemSym1 (a6989586621680453116 :: a6989586621680452634) :: forall t6989586621680452633. (~>) (t6989586621680452633 a6989586621680452634) Bool
  • type NotElemSym2 (a6989586621680453116 :: a6989586621680452634) (a6989586621680453117 :: t6989586621680452633 a6989586621680452634) = NotElem a6989586621680453116 a6989586621680453117
  • data LookupSym0 :: forall a6989586621679940029 b6989586621679940030. (~>) a6989586621679940029 ((~>) [(a6989586621679940029, b6989586621679940030)] (Maybe b6989586621679940030))
  • data LookupSym1 (a6989586621679949390 :: a6989586621679940029) :: forall b6989586621679940030. (~>) [(a6989586621679940029, b6989586621679940030)] (Maybe b6989586621679940030)
  • type LookupSym2 (a6989586621679949390 :: a6989586621679940029) (a6989586621679949391 :: [(a6989586621679940029, b6989586621679940030)]) = Lookup a6989586621679949390 a6989586621679949391
  • data FindSym0 :: forall a6989586621680452632 t6989586621680452631. (~>) ((~>) a6989586621680452632 Bool) ((~>) (t6989586621680452631 a6989586621680452632) (Maybe a6989586621680452632))
  • data FindSym1 (a6989586621680453089 :: (~>) a6989586621680452632 Bool) :: forall t6989586621680452631. (~>) (t6989586621680452631 a6989586621680452632) (Maybe a6989586621680452632)
  • type FindSym2 (a6989586621680453089 :: (~>) a6989586621680452632 Bool) (a6989586621680453090 :: t6989586621680452631 a6989586621680452632) = Find a6989586621680453089 a6989586621680453090
  • data FilterSym0 :: forall a6989586621679940052. (~>) ((~>) a6989586621679940052 Bool) ((~>) [a6989586621679940052] [a6989586621679940052])
  • data FilterSym1 (a6989586621679949593 :: (~>) a6989586621679940052 Bool) :: (~>) [a6989586621679940052] [a6989586621679940052]
  • type FilterSym2 (a6989586621679949593 :: (~>) a6989586621679940052 Bool) (a6989586621679949594 :: [a6989586621679940052]) = Filter a6989586621679949593 a6989586621679949594
  • data PartitionSym0 :: forall a6989586621679940028. (~>) ((~>) a6989586621679940028 Bool) ((~>) [a6989586621679940028] ([a6989586621679940028], [a6989586621679940028]))
  • data PartitionSym1 (a6989586621679949384 :: (~>) a6989586621679940028 Bool) :: (~>) [a6989586621679940028] ([a6989586621679940028], [a6989586621679940028])
  • type PartitionSym2 (a6989586621679949384 :: (~>) a6989586621679940028 Bool) (a6989586621679949385 :: [a6989586621679940028]) = Partition a6989586621679949384 a6989586621679949385
  • data (!!@#@$) :: forall a6989586621679940021. (~>) [a6989586621679940021] ((~>) Nat a6989586621679940021)
  • data (!!@#@$$) (a6989586621679949311 :: [a6989586621679940021]) :: (~>) Nat a6989586621679940021
  • type (!!@#@$$$) (a6989586621679949311 :: [a6989586621679940021]) (a6989586621679949312 :: Nat) = (!!) a6989586621679949311 a6989586621679949312
  • data ElemIndexSym0 :: forall a6989586621679940050. (~>) a6989586621679940050 ((~>) [a6989586621679940050] (Maybe Nat))
  • data ElemIndexSym1 (a6989586621679949976 :: a6989586621679940050) :: (~>) [a6989586621679940050] (Maybe Nat)
  • type ElemIndexSym2 (a6989586621679949976 :: a6989586621679940050) (a6989586621679949977 :: [a6989586621679940050]) = ElemIndex a6989586621679949976 a6989586621679949977
  • data ElemIndicesSym0 :: forall a6989586621679940049. (~>) a6989586621679940049 ((~>) [a6989586621679940049] [Nat])
  • data ElemIndicesSym1 (a6989586621679949960 :: a6989586621679940049) :: (~>) [a6989586621679940049] [Nat]
  • type ElemIndicesSym2 (a6989586621679949960 :: a6989586621679940049) (a6989586621679949961 :: [a6989586621679940049]) = ElemIndices a6989586621679949960 a6989586621679949961
  • data FindIndexSym0 :: forall a6989586621679940048. (~>) ((~>) a6989586621679940048 Bool) ((~>) [a6989586621679940048] (Maybe Nat))
  • data FindIndexSym1 (a6989586621679949968 :: (~>) a6989586621679940048 Bool) :: (~>) [a6989586621679940048] (Maybe Nat)
  • type FindIndexSym2 (a6989586621679949968 :: (~>) a6989586621679940048 Bool) (a6989586621679949969 :: [a6989586621679940048]) = FindIndex a6989586621679949968 a6989586621679949969
  • data FindIndicesSym0 :: forall a6989586621679940047. (~>) ((~>) a6989586621679940047 Bool) ((~>) [a6989586621679940047] [Nat])
  • data FindIndicesSym1 (a6989586621679949934 :: (~>) a6989586621679940047 Bool) :: (~>) [a6989586621679940047] [Nat]
  • type FindIndicesSym2 (a6989586621679949934 :: (~>) a6989586621679940047 Bool) (a6989586621679949935 :: [a6989586621679940047]) = FindIndices a6989586621679949934 a6989586621679949935
  • data ZipSym0 :: forall a6989586621679940098 b6989586621679940099. (~>) [a6989586621679940098] ((~>) [b6989586621679940099] [(a6989586621679940098, b6989586621679940099)])
  • data ZipSym1 (a6989586621679949926 :: [a6989586621679940098]) :: forall b6989586621679940099. (~>) [b6989586621679940099] [(a6989586621679940098, b6989586621679940099)]
  • type ZipSym2 (a6989586621679949926 :: [a6989586621679940098]) (a6989586621679949927 :: [b6989586621679940099]) = Zip a6989586621679949926 a6989586621679949927
  • data Zip3Sym0 :: forall a6989586621679940095 b6989586621679940096 c6989586621679940097. (~>) [a6989586621679940095] ((~>) [b6989586621679940096] ((~>) [c6989586621679940097] [(a6989586621679940095, b6989586621679940096, c6989586621679940097)]))
  • data Zip3Sym1 (a6989586621679949914 :: [a6989586621679940095]) :: forall b6989586621679940096 c6989586621679940097. (~>) [b6989586621679940096] ((~>) [c6989586621679940097] [(a6989586621679940095, b6989586621679940096, c6989586621679940097)])
  • data Zip3Sym2 (a6989586621679949914 :: [a6989586621679940095]) (a6989586621679949915 :: [b6989586621679940096]) :: forall c6989586621679940097. (~>) [c6989586621679940097] [(a6989586621679940095, b6989586621679940096, c6989586621679940097)]
  • type Zip3Sym3 (a6989586621679949914 :: [a6989586621679940095]) (a6989586621679949915 :: [b6989586621679940096]) (a6989586621679949916 :: [c6989586621679940097]) = Zip3 a6989586621679949914 a6989586621679949915 a6989586621679949916
  • data Zip4Sym0 :: forall a6989586621680066262 b6989586621680066263 c6989586621680066264 d6989586621680066265. (~>) [a6989586621680066262] ((~>) [b6989586621680066263] ((~>) [c6989586621680066264] ((~>) [d6989586621680066265] [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)])))
  • data Zip4Sym1 (a6989586621680078964 :: [a6989586621680066262]) :: forall b6989586621680066263 c6989586621680066264 d6989586621680066265. (~>) [b6989586621680066263] ((~>) [c6989586621680066264] ((~>) [d6989586621680066265] [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)]))
  • data Zip4Sym2 (a6989586621680078964 :: [a6989586621680066262]) (a6989586621680078965 :: [b6989586621680066263]) :: forall c6989586621680066264 d6989586621680066265. (~>) [c6989586621680066264] ((~>) [d6989586621680066265] [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)])
  • data Zip4Sym3 (a6989586621680078964 :: [a6989586621680066262]) (a6989586621680078965 :: [b6989586621680066263]) (a6989586621680078966 :: [c6989586621680066264]) :: forall d6989586621680066265. (~>) [d6989586621680066265] [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)]
  • type Zip4Sym4 (a6989586621680078964 :: [a6989586621680066262]) (a6989586621680078965 :: [b6989586621680066263]) (a6989586621680078966 :: [c6989586621680066264]) (a6989586621680078967 :: [d6989586621680066265]) = Zip4 a6989586621680078964 a6989586621680078965 a6989586621680078966 a6989586621680078967
  • data Zip5Sym0 :: forall a6989586621680066257 b6989586621680066258 c6989586621680066259 d6989586621680066260 e6989586621680066261. (~>) [a6989586621680066257] ((~>) [b6989586621680066258] ((~>) [c6989586621680066259] ((~>) [d6989586621680066260] ((~>) [e6989586621680066261] [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]))))
  • data Zip5Sym1 (a6989586621680078941 :: [a6989586621680066257]) :: forall b6989586621680066258 c6989586621680066259 d6989586621680066260 e6989586621680066261. (~>) [b6989586621680066258] ((~>) [c6989586621680066259] ((~>) [d6989586621680066260] ((~>) [e6989586621680066261] [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)])))
  • data Zip5Sym2 (a6989586621680078941 :: [a6989586621680066257]) (a6989586621680078942 :: [b6989586621680066258]) :: forall c6989586621680066259 d6989586621680066260 e6989586621680066261. (~>) [c6989586621680066259] ((~>) [d6989586621680066260] ((~>) [e6989586621680066261] [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]))
  • data Zip5Sym3 (a6989586621680078941 :: [a6989586621680066257]) (a6989586621680078942 :: [b6989586621680066258]) (a6989586621680078943 :: [c6989586621680066259]) :: forall d6989586621680066260 e6989586621680066261. (~>) [d6989586621680066260] ((~>) [e6989586621680066261] [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)])
  • data Zip5Sym4 (a6989586621680078941 :: [a6989586621680066257]) (a6989586621680078942 :: [b6989586621680066258]) (a6989586621680078943 :: [c6989586621680066259]) (a6989586621680078944 :: [d6989586621680066260]) :: forall e6989586621680066261. (~>) [e6989586621680066261] [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]
  • type Zip5Sym5 (a6989586621680078941 :: [a6989586621680066257]) (a6989586621680078942 :: [b6989586621680066258]) (a6989586621680078943 :: [c6989586621680066259]) (a6989586621680078944 :: [d6989586621680066260]) (a6989586621680078945 :: [e6989586621680066261]) = Zip5 a6989586621680078941 a6989586621680078942 a6989586621680078943 a6989586621680078944 a6989586621680078945
  • data Zip6Sym0 :: forall a6989586621680066251 b6989586621680066252 c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256. (~>) [a6989586621680066251] ((~>) [b6989586621680066252] ((~>) [c6989586621680066253] ((~>) [d6989586621680066254] ((~>) [e6989586621680066255] ((~>) [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])))))
  • data Zip6Sym1 (a6989586621680078913 :: [a6989586621680066251]) :: forall b6989586621680066252 c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256. (~>) [b6989586621680066252] ((~>) [c6989586621680066253] ((~>) [d6989586621680066254] ((~>) [e6989586621680066255] ((~>) [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]))))
  • data Zip6Sym2 (a6989586621680078913 :: [a6989586621680066251]) (a6989586621680078914 :: [b6989586621680066252]) :: forall c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256. (~>) [c6989586621680066253] ((~>) [d6989586621680066254] ((~>) [e6989586621680066255] ((~>) [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])))
  • data Zip6Sym3 (a6989586621680078913 :: [a6989586621680066251]) (a6989586621680078914 :: [b6989586621680066252]) (a6989586621680078915 :: [c6989586621680066253]) :: forall d6989586621680066254 e6989586621680066255 f6989586621680066256. (~>) [d6989586621680066254] ((~>) [e6989586621680066255] ((~>) [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]))
  • data Zip6Sym4 (a6989586621680078913 :: [a6989586621680066251]) (a6989586621680078914 :: [b6989586621680066252]) (a6989586621680078915 :: [c6989586621680066253]) (a6989586621680078916 :: [d6989586621680066254]) :: forall e6989586621680066255 f6989586621680066256. (~>) [e6989586621680066255] ((~>) [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])
  • data Zip6Sym5 (a6989586621680078913 :: [a6989586621680066251]) (a6989586621680078914 :: [b6989586621680066252]) (a6989586621680078915 :: [c6989586621680066253]) (a6989586621680078916 :: [d6989586621680066254]) (a6989586621680078917 :: [e6989586621680066255]) :: forall f6989586621680066256. (~>) [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]
  • type Zip6Sym6 (a6989586621680078913 :: [a6989586621680066251]) (a6989586621680078914 :: [b6989586621680066252]) (a6989586621680078915 :: [c6989586621680066253]) (a6989586621680078916 :: [d6989586621680066254]) (a6989586621680078917 :: [e6989586621680066255]) (a6989586621680078918 :: [f6989586621680066256]) = Zip6 a6989586621680078913 a6989586621680078914 a6989586621680078915 a6989586621680078916 a6989586621680078917 a6989586621680078918
  • data Zip7Sym0 :: forall a6989586621680066244 b6989586621680066245 c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250. (~>) [a6989586621680066244] ((~>) [b6989586621680066245] ((~>) [c6989586621680066246] ((~>) [d6989586621680066247] ((~>) [e6989586621680066248] ((~>) [f6989586621680066249] ((~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))))))
  • data Zip7Sym1 (a6989586621680078880 :: [a6989586621680066244]) :: forall b6989586621680066245 c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250. (~>) [b6989586621680066245] ((~>) [c6989586621680066246] ((~>) [d6989586621680066247] ((~>) [e6989586621680066248] ((~>) [f6989586621680066249] ((~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])))))
  • data Zip7Sym2 (a6989586621680078880 :: [a6989586621680066244]) (a6989586621680078881 :: [b6989586621680066245]) :: forall c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250. (~>) [c6989586621680066246] ((~>) [d6989586621680066247] ((~>) [e6989586621680066248] ((~>) [f6989586621680066249] ((~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))))
  • data Zip7Sym3 (a6989586621680078880 :: [a6989586621680066244]) (a6989586621680078881 :: [b6989586621680066245]) (a6989586621680078882 :: [c6989586621680066246]) :: forall d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250. (~>) [d6989586621680066247] ((~>) [e6989586621680066248] ((~>) [f6989586621680066249] ((~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])))
  • data Zip7Sym4 (a6989586621680078880 :: [a6989586621680066244]) (a6989586621680078881 :: [b6989586621680066245]) (a6989586621680078882 :: [c6989586621680066246]) (a6989586621680078883 :: [d6989586621680066247]) :: forall e6989586621680066248 f6989586621680066249 g6989586621680066250. (~>) [e6989586621680066248] ((~>) [f6989586621680066249] ((~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))
  • data Zip7Sym5 (a6989586621680078880 :: [a6989586621680066244]) (a6989586621680078881 :: [b6989586621680066245]) (a6989586621680078882 :: [c6989586621680066246]) (a6989586621680078883 :: [d6989586621680066247]) (a6989586621680078884 :: [e6989586621680066248]) :: forall f6989586621680066249 g6989586621680066250. (~>) [f6989586621680066249] ((~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])
  • data Zip7Sym6 (a6989586621680078880 :: [a6989586621680066244]) (a6989586621680078881 :: [b6989586621680066245]) (a6989586621680078882 :: [c6989586621680066246]) (a6989586621680078883 :: [d6989586621680066247]) (a6989586621680078884 :: [e6989586621680066248]) (a6989586621680078885 :: [f6989586621680066249]) :: forall g6989586621680066250. (~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]
  • type Zip7Sym7 (a6989586621680078880 :: [a6989586621680066244]) (a6989586621680078881 :: [b6989586621680066245]) (a6989586621680078882 :: [c6989586621680066246]) (a6989586621680078883 :: [d6989586621680066247]) (a6989586621680078884 :: [e6989586621680066248]) (a6989586621680078885 :: [f6989586621680066249]) (a6989586621680078886 :: [g6989586621680066250]) = Zip7 a6989586621680078880 a6989586621680078881 a6989586621680078882 a6989586621680078883 a6989586621680078884 a6989586621680078885 a6989586621680078886
  • data ZipWithSym0 :: forall a6989586621679940092 b6989586621679940093 c6989586621679940094. (~>) ((~>) a6989586621679940092 ((~>) b6989586621679940093 c6989586621679940094)) ((~>) [a6989586621679940092] ((~>) [b6989586621679940093] [c6989586621679940094]))
  • data ZipWithSym1 (a6989586621679949903 :: (~>) a6989586621679940092 ((~>) b6989586621679940093 c6989586621679940094)) :: (~>) [a6989586621679940092] ((~>) [b6989586621679940093] [c6989586621679940094])
  • data ZipWithSym2 (a6989586621679949903 :: (~>) a6989586621679940092 ((~>) b6989586621679940093 c6989586621679940094)) (a6989586621679949904 :: [a6989586621679940092]) :: (~>) [b6989586621679940093] [c6989586621679940094]
  • type ZipWithSym3 (a6989586621679949903 :: (~>) a6989586621679940092 ((~>) b6989586621679940093 c6989586621679940094)) (a6989586621679949904 :: [a6989586621679940092]) (a6989586621679949905 :: [b6989586621679940093]) = ZipWith a6989586621679949903 a6989586621679949904 a6989586621679949905
  • data ZipWith3Sym0 :: forall a6989586621679940088 b6989586621679940089 c6989586621679940090 d6989586621679940091. (~>) ((~>) a6989586621679940088 ((~>) b6989586621679940089 ((~>) c6989586621679940090 d6989586621679940091))) ((~>) [a6989586621679940088] ((~>) [b6989586621679940089] ((~>) [c6989586621679940090] [d6989586621679940091])))
  • data ZipWith3Sym1 (a6989586621679949888 :: (~>) a6989586621679940088 ((~>) b6989586621679940089 ((~>) c6989586621679940090 d6989586621679940091))) :: (~>) [a6989586621679940088] ((~>) [b6989586621679940089] ((~>) [c6989586621679940090] [d6989586621679940091]))
  • data ZipWith3Sym2 (a6989586621679949888 :: (~>) a6989586621679940088 ((~>) b6989586621679940089 ((~>) c6989586621679940090 d6989586621679940091))) (a6989586621679949889 :: [a6989586621679940088]) :: (~>) [b6989586621679940089] ((~>) [c6989586621679940090] [d6989586621679940091])
  • data ZipWith3Sym3 (a6989586621679949888 :: (~>) a6989586621679940088 ((~>) b6989586621679940089 ((~>) c6989586621679940090 d6989586621679940091))) (a6989586621679949889 :: [a6989586621679940088]) (a6989586621679949890 :: [b6989586621679940089]) :: (~>) [c6989586621679940090] [d6989586621679940091]
  • type ZipWith3Sym4 (a6989586621679949888 :: (~>) a6989586621679940088 ((~>) b6989586621679940089 ((~>) c6989586621679940090 d6989586621679940091))) (a6989586621679949889 :: [a6989586621679940088]) (a6989586621679949890 :: [b6989586621679940089]) (a6989586621679949891 :: [c6989586621679940090]) = ZipWith3 a6989586621679949888 a6989586621679949889 a6989586621679949890 a6989586621679949891
  • data ZipWith4Sym0 :: forall a6989586621680066239 b6989586621680066240 c6989586621680066241 d6989586621680066242 e6989586621680066243. (~>) ((~>) a6989586621680066239 ((~>) b6989586621680066240 ((~>) c6989586621680066241 ((~>) d6989586621680066242 e6989586621680066243)))) ((~>) [a6989586621680066239] ((~>) [b6989586621680066240] ((~>) [c6989586621680066241] ((~>) [d6989586621680066242] [e6989586621680066243]))))
  • data ZipWith4Sym1 (a6989586621680078847 :: (~>) a6989586621680066239 ((~>) b6989586621680066240 ((~>) c6989586621680066241 ((~>) d6989586621680066242 e6989586621680066243)))) :: (~>) [a6989586621680066239] ((~>) [b6989586621680066240] ((~>) [c6989586621680066241] ((~>) [d6989586621680066242] [e6989586621680066243])))
  • data ZipWith4Sym2 (a6989586621680078847 :: (~>) a6989586621680066239 ((~>) b6989586621680066240 ((~>) c6989586621680066241 ((~>) d6989586621680066242 e6989586621680066243)))) (a6989586621680078848 :: [a6989586621680066239]) :: (~>) [b6989586621680066240] ((~>) [c6989586621680066241] ((~>) [d6989586621680066242] [e6989586621680066243]))
  • data ZipWith4Sym3 (a6989586621680078847 :: (~>) a6989586621680066239 ((~>) b6989586621680066240 ((~>) c6989586621680066241 ((~>) d6989586621680066242 e6989586621680066243)))) (a6989586621680078848 :: [a6989586621680066239]) (a6989586621680078849 :: [b6989586621680066240]) :: (~>) [c6989586621680066241] ((~>) [d6989586621680066242] [e6989586621680066243])
  • data ZipWith4Sym4 (a6989586621680078847 :: (~>) a6989586621680066239 ((~>) b6989586621680066240 ((~>) c6989586621680066241 ((~>) d6989586621680066242 e6989586621680066243)))) (a6989586621680078848 :: [a6989586621680066239]) (a6989586621680078849 :: [b6989586621680066240]) (a6989586621680078850 :: [c6989586621680066241]) :: (~>) [d6989586621680066242] [e6989586621680066243]
  • type ZipWith4Sym5 (a6989586621680078847 :: (~>) a6989586621680066239 ((~>) b6989586621680066240 ((~>) c6989586621680066241 ((~>) d6989586621680066242 e6989586621680066243)))) (a6989586621680078848 :: [a6989586621680066239]) (a6989586621680078849 :: [b6989586621680066240]) (a6989586621680078850 :: [c6989586621680066241]) (a6989586621680078851 :: [d6989586621680066242]) = ZipWith4 a6989586621680078847 a6989586621680078848 a6989586621680078849 a6989586621680078850 a6989586621680078851
  • data ZipWith5Sym0 :: forall a6989586621680066233 b6989586621680066234 c6989586621680066235 d6989586621680066236 e6989586621680066237 f6989586621680066238. (~>) ((~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) ((~>) [a6989586621680066233] ((~>) [b6989586621680066234] ((~>) [c6989586621680066235] ((~>) [d6989586621680066236] ((~>) [e6989586621680066237] [f6989586621680066238])))))
  • data ZipWith5Sym1 (a6989586621680078824 :: (~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) :: (~>) [a6989586621680066233] ((~>) [b6989586621680066234] ((~>) [c6989586621680066235] ((~>) [d6989586621680066236] ((~>) [e6989586621680066237] [f6989586621680066238]))))
  • data ZipWith5Sym2 (a6989586621680078824 :: (~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) (a6989586621680078825 :: [a6989586621680066233]) :: (~>) [b6989586621680066234] ((~>) [c6989586621680066235] ((~>) [d6989586621680066236] ((~>) [e6989586621680066237] [f6989586621680066238])))
  • data ZipWith5Sym3 (a6989586621680078824 :: (~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) (a6989586621680078825 :: [a6989586621680066233]) (a6989586621680078826 :: [b6989586621680066234]) :: (~>) [c6989586621680066235] ((~>) [d6989586621680066236] ((~>) [e6989586621680066237] [f6989586621680066238]))
  • data ZipWith5Sym4 (a6989586621680078824 :: (~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) (a6989586621680078825 :: [a6989586621680066233]) (a6989586621680078826 :: [b6989586621680066234]) (a6989586621680078827 :: [c6989586621680066235]) :: (~>) [d6989586621680066236] ((~>) [e6989586621680066237] [f6989586621680066238])
  • data ZipWith5Sym5 (a6989586621680078824 :: (~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) (a6989586621680078825 :: [a6989586621680066233]) (a6989586621680078826 :: [b6989586621680066234]) (a6989586621680078827 :: [c6989586621680066235]) (a6989586621680078828 :: [d6989586621680066236]) :: (~>) [e6989586621680066237] [f6989586621680066238]
  • type ZipWith5Sym6 (a6989586621680078824 :: (~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) (a6989586621680078825 :: [a6989586621680066233]) (a6989586621680078826 :: [b6989586621680066234]) (a6989586621680078827 :: [c6989586621680066235]) (a6989586621680078828 :: [d6989586621680066236]) (a6989586621680078829 :: [e6989586621680066237]) = ZipWith5 a6989586621680078824 a6989586621680078825 a6989586621680078826 a6989586621680078827 a6989586621680078828 a6989586621680078829
  • data ZipWith6Sym0 :: forall a6989586621680066226 b6989586621680066227 c6989586621680066228 d6989586621680066229 e6989586621680066230 f6989586621680066231 g6989586621680066232. (~>) ((~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) ((~>) [a6989586621680066226] ((~>) [b6989586621680066227] ((~>) [c6989586621680066228] ((~>) [d6989586621680066229] ((~>) [e6989586621680066230] ((~>) [f6989586621680066231] [g6989586621680066232]))))))
  • data ZipWith6Sym1 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) :: (~>) [a6989586621680066226] ((~>) [b6989586621680066227] ((~>) [c6989586621680066228] ((~>) [d6989586621680066229] ((~>) [e6989586621680066230] ((~>) [f6989586621680066231] [g6989586621680066232])))))
  • data ZipWith6Sym2 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) (a6989586621680078798 :: [a6989586621680066226]) :: (~>) [b6989586621680066227] ((~>) [c6989586621680066228] ((~>) [d6989586621680066229] ((~>) [e6989586621680066230] ((~>) [f6989586621680066231] [g6989586621680066232]))))
  • data ZipWith6Sym3 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) (a6989586621680078798 :: [a6989586621680066226]) (a6989586621680078799 :: [b6989586621680066227]) :: (~>) [c6989586621680066228] ((~>) [d6989586621680066229] ((~>) [e6989586621680066230] ((~>) [f6989586621680066231] [g6989586621680066232])))
  • data ZipWith6Sym4 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) (a6989586621680078798 :: [a6989586621680066226]) (a6989586621680078799 :: [b6989586621680066227]) (a6989586621680078800 :: [c6989586621680066228]) :: (~>) [d6989586621680066229] ((~>) [e6989586621680066230] ((~>) [f6989586621680066231] [g6989586621680066232]))
  • data ZipWith6Sym5 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) (a6989586621680078798 :: [a6989586621680066226]) (a6989586621680078799 :: [b6989586621680066227]) (a6989586621680078800 :: [c6989586621680066228]) (a6989586621680078801 :: [d6989586621680066229]) :: (~>) [e6989586621680066230] ((~>) [f6989586621680066231] [g6989586621680066232])
  • data ZipWith6Sym6 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) (a6989586621680078798 :: [a6989586621680066226]) (a6989586621680078799 :: [b6989586621680066227]) (a6989586621680078800 :: [c6989586621680066228]) (a6989586621680078801 :: [d6989586621680066229]) (a6989586621680078802 :: [e6989586621680066230]) :: (~>) [f6989586621680066231] [g6989586621680066232]
  • type ZipWith6Sym7 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) (a6989586621680078798 :: [a6989586621680066226]) (a6989586621680078799 :: [b6989586621680066227]) (a6989586621680078800 :: [c6989586621680066228]) (a6989586621680078801 :: [d6989586621680066229]) (a6989586621680078802 :: [e6989586621680066230]) (a6989586621680078803 :: [f6989586621680066231]) = ZipWith6 a6989586621680078797 a6989586621680078798 a6989586621680078799 a6989586621680078800 a6989586621680078801 a6989586621680078802 a6989586621680078803
  • data ZipWith7Sym0 :: forall a6989586621680066218 b6989586621680066219 c6989586621680066220 d6989586621680066221 e6989586621680066222 f6989586621680066223 g6989586621680066224 h6989586621680066225. (~>) ((~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) ((~>) [a6989586621680066218] ((~>) [b6989586621680066219] ((~>) [c6989586621680066220] ((~>) [d6989586621680066221] ((~>) [e6989586621680066222] ((~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225])))))))
  • data ZipWith7Sym1 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) :: (~>) [a6989586621680066218] ((~>) [b6989586621680066219] ((~>) [c6989586621680066220] ((~>) [d6989586621680066221] ((~>) [e6989586621680066222] ((~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225]))))))
  • data ZipWith7Sym2 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) :: (~>) [b6989586621680066219] ((~>) [c6989586621680066220] ((~>) [d6989586621680066221] ((~>) [e6989586621680066222] ((~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225])))))
  • data ZipWith7Sym3 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) (a6989586621680078768 :: [b6989586621680066219]) :: (~>) [c6989586621680066220] ((~>) [d6989586621680066221] ((~>) [e6989586621680066222] ((~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225]))))
  • data ZipWith7Sym4 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) (a6989586621680078768 :: [b6989586621680066219]) (a6989586621680078769 :: [c6989586621680066220]) :: (~>) [d6989586621680066221] ((~>) [e6989586621680066222] ((~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225])))
  • data ZipWith7Sym5 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) (a6989586621680078768 :: [b6989586621680066219]) (a6989586621680078769 :: [c6989586621680066220]) (a6989586621680078770 :: [d6989586621680066221]) :: (~>) [e6989586621680066222] ((~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225]))
  • data ZipWith7Sym6 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) (a6989586621680078768 :: [b6989586621680066219]) (a6989586621680078769 :: [c6989586621680066220]) (a6989586621680078770 :: [d6989586621680066221]) (a6989586621680078771 :: [e6989586621680066222]) :: (~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225])
  • data ZipWith7Sym7 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) (a6989586621680078768 :: [b6989586621680066219]) (a6989586621680078769 :: [c6989586621680066220]) (a6989586621680078770 :: [d6989586621680066221]) (a6989586621680078771 :: [e6989586621680066222]) (a6989586621680078772 :: [f6989586621680066223]) :: (~>) [g6989586621680066224] [h6989586621680066225]
  • type ZipWith7Sym8 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) (a6989586621680078768 :: [b6989586621680066219]) (a6989586621680078769 :: [c6989586621680066220]) (a6989586621680078770 :: [d6989586621680066221]) (a6989586621680078771 :: [e6989586621680066222]) (a6989586621680078772 :: [f6989586621680066223]) (a6989586621680078773 :: [g6989586621680066224]) = ZipWith7 a6989586621680078766 a6989586621680078767 a6989586621680078768 a6989586621680078769 a6989586621680078770 a6989586621680078771 a6989586621680078772 a6989586621680078773
  • data UnzipSym0 :: forall a6989586621679940086 b6989586621679940087. (~>) [(a6989586621679940086, b6989586621679940087)] ([a6989586621679940086], [b6989586621679940087])
  • type UnzipSym1 (a6989586621679949869 :: [(a6989586621679940086, b6989586621679940087)]) = Unzip a6989586621679949869
  • data Unzip3Sym0 :: forall a6989586621679940083 b6989586621679940084 c6989586621679940085. (~>) [(a6989586621679940083, b6989586621679940084, c6989586621679940085)] ([a6989586621679940083], [b6989586621679940084], [c6989586621679940085])
  • type Unzip3Sym1 (a6989586621679949848 :: [(a6989586621679940083, b6989586621679940084, c6989586621679940085)]) = Unzip3 a6989586621679949848
  • data Unzip4Sym0 :: forall a6989586621679940079 b6989586621679940080 c6989586621679940081 d6989586621679940082. (~>) [(a6989586621679940079, b6989586621679940080, c6989586621679940081, d6989586621679940082)] ([a6989586621679940079], [b6989586621679940080], [c6989586621679940081], [d6989586621679940082])
  • type Unzip4Sym1 (a6989586621679949825 :: [(a6989586621679940079, b6989586621679940080, c6989586621679940081, d6989586621679940082)]) = Unzip4 a6989586621679949825
  • data Unzip5Sym0 :: forall a6989586621679940074 b6989586621679940075 c6989586621679940076 d6989586621679940077 e6989586621679940078. (~>) [(a6989586621679940074, b6989586621679940075, c6989586621679940076, d6989586621679940077, e6989586621679940078)] ([a6989586621679940074], [b6989586621679940075], [c6989586621679940076], [d6989586621679940077], [e6989586621679940078])
  • type Unzip5Sym1 (a6989586621679949800 :: [(a6989586621679940074, b6989586621679940075, c6989586621679940076, d6989586621679940077, e6989586621679940078)]) = Unzip5 a6989586621679949800
  • data Unzip6Sym0 :: forall a6989586621679940068 b6989586621679940069 c6989586621679940070 d6989586621679940071 e6989586621679940072 f6989586621679940073. (~>) [(a6989586621679940068, b6989586621679940069, c6989586621679940070, d6989586621679940071, e6989586621679940072, f6989586621679940073)] ([a6989586621679940068], [b6989586621679940069], [c6989586621679940070], [d6989586621679940071], [e6989586621679940072], [f6989586621679940073])
  • type Unzip6Sym1 (a6989586621679949773 :: [(a6989586621679940068, b6989586621679940069, c6989586621679940070, d6989586621679940071, e6989586621679940072, f6989586621679940073)]) = Unzip6 a6989586621679949773
  • data Unzip7Sym0 :: forall a6989586621679940061 b6989586621679940062 c6989586621679940063 d6989586621679940064 e6989586621679940065 f6989586621679940066 g6989586621679940067. (~>) [(a6989586621679940061, b6989586621679940062, c6989586621679940063, d6989586621679940064, e6989586621679940065, f6989586621679940066, g6989586621679940067)] ([a6989586621679940061], [b6989586621679940062], [c6989586621679940063], [d6989586621679940064], [e6989586621679940065], [f6989586621679940066], [g6989586621679940067])
  • type Unzip7Sym1 (a6989586621679949744 :: [(a6989586621679940061, b6989586621679940062, c6989586621679940063, d6989586621679940064, e6989586621679940065, f6989586621679940066, g6989586621679940067)]) = Unzip7 a6989586621679949744
  • data UnlinesSym0 :: (~>) [Symbol] Symbol
  • type UnlinesSym1 (a6989586621679949740 :: [Symbol]) = Unlines a6989586621679949740
  • data UnwordsSym0 :: (~>) [Symbol] Symbol
  • type UnwordsSym1 (a6989586621679949729 :: [Symbol]) = Unwords a6989586621679949729
  • data NubSym0 :: forall a6989586621679940020. (~>) [a6989586621679940020] [a6989586621679940020]
  • type NubSym1 (a6989586621679949998 :: [a6989586621679940020]) = Nub a6989586621679949998
  • data DeleteSym0 :: forall a6989586621679940060. (~>) a6989586621679940060 ((~>) [a6989586621679940060] [a6989586621679940060])
  • data DeleteSym1 (a6989586621679949713 :: a6989586621679940060) :: (~>) [a6989586621679940060] [a6989586621679940060]
  • type DeleteSym2 (a6989586621679949713 :: a6989586621679940060) (a6989586621679949714 :: [a6989586621679940060]) = Delete a6989586621679949713 a6989586621679949714
  • data (\\@#@$) :: forall a6989586621679940059. (~>) [a6989586621679940059] ((~>) [a6989586621679940059] [a6989586621679940059])
  • data (\\@#@$$) (a6989586621679949723 :: [a6989586621679940059]) :: (~>) [a6989586621679940059] [a6989586621679940059]
  • type (\\@#@$$$) (a6989586621679949723 :: [a6989586621679940059]) (a6989586621679949724 :: [a6989586621679940059]) = (\\) a6989586621679949723 a6989586621679949724
  • data UnionSym0 :: forall a6989586621679940016. (~>) [a6989586621679940016] ((~>) [a6989586621679940016] [a6989586621679940016])
  • data UnionSym1 (a6989586621679949703 :: [a6989586621679940016]) :: (~>) [a6989586621679940016] [a6989586621679940016]
  • type UnionSym2 (a6989586621679949703 :: [a6989586621679940016]) (a6989586621679949704 :: [a6989586621679940016]) = Union a6989586621679949703 a6989586621679949704
  • data IntersectSym0 :: forall a6989586621679940046. (~>) [a6989586621679940046] ((~>) [a6989586621679940046] [a6989586621679940046])
  • data IntersectSym1 (a6989586621679950298 :: [a6989586621679940046]) :: (~>) [a6989586621679940046] [a6989586621679940046]
  • type IntersectSym2 (a6989586621679950298 :: [a6989586621679940046]) (a6989586621679950299 :: [a6989586621679940046]) = Intersect a6989586621679950298 a6989586621679950299
  • data InsertSym0 :: forall a6989586621679940033. (~>) a6989586621679940033 ((~>) [a6989586621679940033] [a6989586621679940033])
  • data InsertSym1 (a6989586621679949640 :: a6989586621679940033) :: (~>) [a6989586621679940033] [a6989586621679940033]
  • type InsertSym2 (a6989586621679949640 :: a6989586621679940033) (a6989586621679949641 :: [a6989586621679940033]) = Insert a6989586621679949640 a6989586621679949641
  • data SortSym0 :: forall a6989586621679940032. (~>) [a6989586621679940032] [a6989586621679940032]
  • type SortSym1 (a6989586621679949656 :: [a6989586621679940032]) = Sort a6989586621679949656
  • data NubBySym0 :: forall a6989586621679940019. (~>) ((~>) a6989586621679940019 ((~>) a6989586621679940019 Bool)) ((~>) [a6989586621679940019] [a6989586621679940019])
  • data NubBySym1 (a6989586621679949286 :: (~>) a6989586621679940019 ((~>) a6989586621679940019 Bool)) :: (~>) [a6989586621679940019] [a6989586621679940019]
  • type NubBySym2 (a6989586621679949286 :: (~>) a6989586621679940019 ((~>) a6989586621679940019 Bool)) (a6989586621679949287 :: [a6989586621679940019]) = NubBy a6989586621679949286 a6989586621679949287
  • data DeleteBySym0 :: forall a6989586621679940058. (~>) ((~>) a6989586621679940058 ((~>) a6989586621679940058 Bool)) ((~>) a6989586621679940058 ((~>) [a6989586621679940058] [a6989586621679940058]))
  • data DeleteBySym1 (a6989586621679949659 :: (~>) a6989586621679940058 ((~>) a6989586621679940058 Bool)) :: (~>) a6989586621679940058 ((~>) [a6989586621679940058] [a6989586621679940058])
  • data DeleteBySym2 (a6989586621679949659 :: (~>) a6989586621679940058 ((~>) a6989586621679940058 Bool)) (a6989586621679949660 :: a6989586621679940058) :: (~>) [a6989586621679940058] [a6989586621679940058]
  • type DeleteBySym3 (a6989586621679949659 :: (~>) a6989586621679940058 ((~>) a6989586621679940058 Bool)) (a6989586621679949660 :: a6989586621679940058) (a6989586621679949661 :: [a6989586621679940058]) = DeleteBy a6989586621679949659 a6989586621679949660 a6989586621679949661
  • data DeleteFirstsBySym0 :: forall a6989586621679940057. (~>) ((~>) a6989586621679940057 ((~>) a6989586621679940057 Bool)) ((~>) [a6989586621679940057] ((~>) [a6989586621679940057] [a6989586621679940057]))
  • data DeleteFirstsBySym1 (a6989586621679949677 :: (~>) a6989586621679940057 ((~>) a6989586621679940057 Bool)) :: (~>) [a6989586621679940057] ((~>) [a6989586621679940057] [a6989586621679940057])
  • data DeleteFirstsBySym2 (a6989586621679949677 :: (~>) a6989586621679940057 ((~>) a6989586621679940057 Bool)) (a6989586621679949678 :: [a6989586621679940057]) :: (~>) [a6989586621679940057] [a6989586621679940057]
  • type DeleteFirstsBySym3 (a6989586621679949677 :: (~>) a6989586621679940057 ((~>) a6989586621679940057 Bool)) (a6989586621679949678 :: [a6989586621679940057]) (a6989586621679949679 :: [a6989586621679940057]) = DeleteFirstsBy a6989586621679949677 a6989586621679949678 a6989586621679949679
  • data UnionBySym0 :: forall a6989586621679940017. (~>) ((~>) a6989586621679940017 ((~>) a6989586621679940017 Bool)) ((~>) [a6989586621679940017] ((~>) [a6989586621679940017] [a6989586621679940017]))
  • data UnionBySym1 (a6989586621679949690 :: (~>) a6989586621679940017 ((~>) a6989586621679940017 Bool)) :: (~>) [a6989586621679940017] ((~>) [a6989586621679940017] [a6989586621679940017])
  • data UnionBySym2 (a6989586621679949690 :: (~>) a6989586621679940017 ((~>) a6989586621679940017 Bool)) (a6989586621679949691 :: [a6989586621679940017]) :: (~>) [a6989586621679940017] [a6989586621679940017]
  • type UnionBySym3 (a6989586621679949690 :: (~>) a6989586621679940017 ((~>) a6989586621679940017 Bool)) (a6989586621679949691 :: [a6989586621679940017]) (a6989586621679949692 :: [a6989586621679940017]) = UnionBy a6989586621679949690 a6989586621679949691 a6989586621679949692
  • data IntersectBySym0 :: forall a6989586621679940045. (~>) ((~>) a6989586621679940045 ((~>) a6989586621679940045 Bool)) ((~>) [a6989586621679940045] ((~>) [a6989586621679940045] [a6989586621679940045]))
  • data IntersectBySym1 (a6989586621679950262 :: (~>) a6989586621679940045 ((~>) a6989586621679940045 Bool)) :: (~>) [a6989586621679940045] ((~>) [a6989586621679940045] [a6989586621679940045])
  • data IntersectBySym2 (a6989586621679950262 :: (~>) a6989586621679940045 ((~>) a6989586621679940045 Bool)) (a6989586621679950263 :: [a6989586621679940045]) :: (~>) [a6989586621679940045] [a6989586621679940045]
  • type IntersectBySym3 (a6989586621679950262 :: (~>) a6989586621679940045 ((~>) a6989586621679940045 Bool)) (a6989586621679950263 :: [a6989586621679940045]) (a6989586621679950264 :: [a6989586621679940045]) = IntersectBy a6989586621679950262 a6989586621679950263 a6989586621679950264
  • data GroupBySym0 :: forall a6989586621679940031. (~>) ((~>) a6989586621679940031 ((~>) a6989586621679940031 Bool)) ((~>) [a6989586621679940031] [[a6989586621679940031]])
  • data GroupBySym1 (a6989586621679949527 :: (~>) a6989586621679940031 ((~>) a6989586621679940031 Bool)) :: (~>) [a6989586621679940031] [[a6989586621679940031]]
  • type GroupBySym2 (a6989586621679949527 :: (~>) a6989586621679940031 ((~>) a6989586621679940031 Bool)) (a6989586621679949528 :: [a6989586621679940031]) = GroupBy a6989586621679949527 a6989586621679949528
  • data SortBySym0 :: forall a6989586621679940056. (~>) ((~>) a6989586621679940056 ((~>) a6989586621679940056 Ordering)) ((~>) [a6989586621679940056] [a6989586621679940056])
  • data SortBySym1 (a6989586621679949646 :: (~>) a6989586621679940056 ((~>) a6989586621679940056 Ordering)) :: (~>) [a6989586621679940056] [a6989586621679940056]
  • type SortBySym2 (a6989586621679949646 :: (~>) a6989586621679940056 ((~>) a6989586621679940056 Ordering)) (a6989586621679949647 :: [a6989586621679940056]) = SortBy a6989586621679949646 a6989586621679949647
  • data InsertBySym0 :: forall a6989586621679940055. (~>) ((~>) a6989586621679940055 ((~>) a6989586621679940055 Ordering)) ((~>) a6989586621679940055 ((~>) [a6989586621679940055] [a6989586621679940055]))
  • data InsertBySym1 (a6989586621679949616 :: (~>) a6989586621679940055 ((~>) a6989586621679940055 Ordering)) :: (~>) a6989586621679940055 ((~>) [a6989586621679940055] [a6989586621679940055])
  • data InsertBySym2 (a6989586621679949616 :: (~>) a6989586621679940055 ((~>) a6989586621679940055 Ordering)) (a6989586621679949617 :: a6989586621679940055) :: (~>) [a6989586621679940055] [a6989586621679940055]
  • type InsertBySym3 (a6989586621679949616 :: (~>) a6989586621679940055 ((~>) a6989586621679940055 Ordering)) (a6989586621679949617 :: a6989586621679940055) (a6989586621679949618 :: [a6989586621679940055]) = InsertBy a6989586621679949616 a6989586621679949617 a6989586621679949618
  • data MaximumBySym0 :: forall a6989586621680452638 t6989586621680452637. (~>) ((~>) a6989586621680452638 ((~>) a6989586621680452638 Ordering)) ((~>) (t6989586621680452637 a6989586621680452638) a6989586621680452638)
  • data MaximumBySym1 (a6989586621680453149 :: (~>) a6989586621680452638 ((~>) a6989586621680452638 Ordering)) :: forall t6989586621680452637. (~>) (t6989586621680452637 a6989586621680452638) a6989586621680452638
  • type MaximumBySym2 (a6989586621680453149 :: (~>) a6989586621680452638 ((~>) a6989586621680452638 Ordering)) (a6989586621680453150 :: t6989586621680452637 a6989586621680452638) = MaximumBy a6989586621680453149 a6989586621680453150
  • data MinimumBySym0 :: forall a6989586621680452636 t6989586621680452635. (~>) ((~>) a6989586621680452636 ((~>) a6989586621680452636 Ordering)) ((~>) (t6989586621680452635 a6989586621680452636) a6989586621680452636)
  • data MinimumBySym1 (a6989586621680453124 :: (~>) a6989586621680452636 ((~>) a6989586621680452636 Ordering)) :: forall t6989586621680452635. (~>) (t6989586621680452635 a6989586621680452636) a6989586621680452636
  • type MinimumBySym2 (a6989586621680453124 :: (~>) a6989586621680452636 ((~>) a6989586621680452636 Ordering)) (a6989586621680453125 :: t6989586621680452635 a6989586621680452636) = MinimumBy a6989586621680453124 a6989586621680453125
  • data GenericLengthSym0 :: forall a6989586621679940015 i6989586621679940014. (~>) [a6989586621679940015] i6989586621679940014
  • type GenericLengthSym1 (a6989586621679949273 :: [a6989586621679940015]) = GenericLength a6989586621679949273
  • data GenericTakeSym0 :: forall a6989586621680066217 i6989586621680066216. (~>) i6989586621680066216 ((~>) [a6989586621680066217] [a6989586621680066217])
  • data GenericTakeSym1 (a6989586621680078760 :: i6989586621680066216) :: forall a6989586621680066217. (~>) [a6989586621680066217] [a6989586621680066217]
  • type GenericTakeSym2 (a6989586621680078760 :: i6989586621680066216) (a6989586621680078761 :: [a6989586621680066217]) = GenericTake a6989586621680078760 a6989586621680078761
  • data GenericDropSym0 :: forall a6989586621680066215 i6989586621680066214. (~>) i6989586621680066214 ((~>) [a6989586621680066215] [a6989586621680066215])
  • data GenericDropSym1 (a6989586621680078750 :: i6989586621680066214) :: forall a6989586621680066215. (~>) [a6989586621680066215] [a6989586621680066215]
  • type GenericDropSym2 (a6989586621680078750 :: i6989586621680066214) (a6989586621680078751 :: [a6989586621680066215]) = GenericDrop a6989586621680078750 a6989586621680078751
  • data GenericSplitAtSym0 :: forall a6989586621680066213 i6989586621680066212. (~>) i6989586621680066212 ((~>) [a6989586621680066213] ([a6989586621680066213], [a6989586621680066213]))
  • data GenericSplitAtSym1 (a6989586621680078740 :: i6989586621680066212) :: forall a6989586621680066213. (~>) [a6989586621680066213] ([a6989586621680066213], [a6989586621680066213])
  • type GenericSplitAtSym2 (a6989586621680078740 :: i6989586621680066212) (a6989586621680078741 :: [a6989586621680066213]) = GenericSplitAt a6989586621680078740 a6989586621680078741
  • data GenericIndexSym0 :: forall a6989586621680066211 i6989586621680066210. (~>) [a6989586621680066211] ((~>) i6989586621680066210 a6989586621680066211)
  • data GenericIndexSym1 (a6989586621680078730 :: [a6989586621680066211]) :: forall i6989586621680066210. (~>) i6989586621680066210 a6989586621680066211
  • type GenericIndexSym2 (a6989586621680078730 :: [a6989586621680066211]) (a6989586621680078731 :: i6989586621680066210) = GenericIndex a6989586621680078730 a6989586621680078731
  • data GenericReplicateSym0 :: forall a6989586621680066209 i6989586621680066208. (~>) i6989586621680066208 ((~>) a6989586621680066209 [a6989586621680066209])
  • data GenericReplicateSym1 (a6989586621680078720 :: i6989586621680066208) :: forall a6989586621680066209. (~>) a6989586621680066209 [a6989586621680066209]
  • type GenericReplicateSym2 (a6989586621680078720 :: i6989586621680066208) (a6989586621680078721 :: a6989586621680066209) = GenericReplicate a6989586621680078720 a6989586621680078721

The singleton for lists

data family Sing :: k -> Type infixr 5 Source #

The singleton kind-indexed data family.

Instances
SDecide k => TestCoercion (Sing :: k -> Type) Source # 
Instance details

Defined in Data.Singletons.Decide

Methods

testCoercion :: Sing a -> Sing b -> Maybe (Coercion a b) #

SDecide k => TestEquality (Sing :: k -> Type) Source # 
Instance details

Defined in Data.Singletons.Decide

Methods

testEquality :: Sing a -> Sing b -> Maybe (a :~: b) #

Show (SSymbol s) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> SSymbol s -> ShowS #

show :: SSymbol s -> String #

showList :: [SSymbol s] -> ShowS #

Show (SNat n) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> SNat n -> ShowS #

show :: SNat n -> String #

showList :: [SNat n] -> ShowS #

Eq (Sing a) Source # 
Instance details

Defined in Data.Singletons.TypeRepTYPE

Methods

(==) :: Sing a -> Sing a -> Bool #

(/=) :: Sing a -> Sing a -> Bool #

Ord (Sing a) Source # 
Instance details

Defined in Data.Singletons.TypeRepTYPE

Methods

compare :: Sing a -> Sing a -> Ordering #

(<) :: Sing a -> Sing a -> Bool #

(<=) :: Sing a -> Sing a -> Bool #

(>) :: Sing a -> Sing a -> Bool #

(>=) :: Sing a -> Sing a -> Bool #

max :: Sing a -> Sing a -> Sing a #

min :: Sing a -> Sing a -> Sing a #

Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing [a]) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing a => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing a) Source # 
Instance details

Defined in Data.Singletons.TypeRepTYPE

Methods

showsPrec :: Int -> Sing a -> ShowS #

show :: Sing a -> String #

showList :: [Sing a] -> ShowS #

Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f, ShowSing g) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing a => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing a => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing a => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing a => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing m => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing (Maybe a) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing a => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing (Maybe a) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing (Maybe a) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing a => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing Bool => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing Bool => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing a => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

ShowSing a => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing [a]) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

data Sing (a :: Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (a :: Bool) where
data Sing (a :: Ordering) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (a :: Ordering) where
data Sing (n :: Nat) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

data Sing (n :: Nat) where
data Sing (n :: Symbol) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

data Sing (n :: Symbol) where
data Sing (a :: ()) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (a :: ()) where
data Sing (a :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (a :: Void)
data Sing (a :: All) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (a :: All) where
data Sing (a :: Any) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (a :: Any) where
data Sing (a :: PErrorMessage) Source # 
Instance details

Defined in Data.Singletons.TypeError

data Sing (a :: PErrorMessage) where
data Sing (b :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: [a]) where
  • SNil :: forall k (b :: [k]). Sing ([] :: [k])
  • SCons :: forall a (b :: [a]) (n :: a) (n :: [a]). Sing n -> Sing n -> Sing (n ': n)
data Sing (b :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: Maybe a) where
data Sing (a :: TYPE rep) Source #

A choice of singleton for the kind TYPE rep (for some RuntimeRep rep), an instantiation of which is the famous kind Type.

Conceivably, one could generalize this instance to `Sing :: k -> Type` for any kind k, and remove all other Sing instances. We don't adopt this design, however, since it is far more convenient in practice to work with explicit singleton values than TypeReps (for instance, TypeReps are more difficult to pattern match on, and require extra runtime checks).

We cannot produce explicit singleton values for everything in TYPE rep, however, since it is an open kind, so we reach for TypeRep in this one particular case.

Instance details

Defined in Data.Singletons.TypeRepTYPE

data Sing (a :: TYPE rep) = STypeRep (TypeRep a)
data Sing (b :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Min a) where
data Sing (b :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Max a) where
data Sing (b :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: First a) where
data Sing (b :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Last a) where
data Sing (a :: WrappedMonoid m) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (a :: WrappedMonoid m) where
data Sing (b :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Option a) where
data Sing (b :: Identity a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: Identity a) where
data Sing (b :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

data Sing (b :: First a) where
data Sing (b :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

data Sing (b :: Last a) where
data Sing (b :: Dual a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Dual a) where
data Sing (b :: Sum a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Sum a) where
data Sing (b :: Product a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Product a) where
data Sing (b :: Down a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

data Sing (b :: Down a) where
data Sing (b :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: NonEmpty a) where
data Sing (c :: Either a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (c :: Either a b) where
data Sing (c :: (a, b)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (c :: (a, b)) where
data Sing (c :: Arg a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

data Sing (c :: Arg a b) where
data Sing (f :: k1 ~> k2) Source # 
Instance details

Defined in Data.Singletons.Internal

data Sing (f :: k1 ~> k2) = SLambda {}
data Sing (d :: (a, b, c)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (d :: (a, b, c)) where
data Sing (c :: Const a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

data Sing (c :: Const a b) where
data Sing (e :: (a, b, c, d)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (e :: (a, b, c, d)) where
data Sing (f :: (a, b, c, d, e)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (f :: (a, b, c, d, e)) where
data Sing (g :: (a, b, c, d, e, f)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (g :: (a, b, c, d, e, f)) where
data Sing (h :: (a, b, c, d, e, f, g)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (h :: (a, b, c, d, e, f, g)) where

Though Haddock doesn't show it, the Sing instance above declares constructors

SNil  :: Sing '[]
SCons :: Sing (h :: k) -> Sing (t :: [k]) -> Sing (h ': t)

type SList = (Sing :: [a] -> Type) Source #

SList is a kind-restricted synonym for Sing: type SList (a :: [k]) = Sing a

Basic functions

type family (a :: [a]) ++ (a :: [a]) :: [a] where ... infixr 5 Source #

Equations

'[] ++ ys = ys 
((:) x xs) ++ ys = Apply (Apply (:@#@$) x) (Apply (Apply (++@#@$) xs) ys) 

(%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a]) infixr 5 Source #

type family Head (a :: [a]) :: a where ... Source #

Equations

Head ((:) a _) = a 
Head '[] = Apply ErrorSym0 "Data.Singletons.List.head: empty list" 

sHead :: forall a (t :: [a]). Sing t -> Sing (Apply HeadSym0 t :: a) Source #

type family Last (a :: [a]) :: a where ... Source #

Equations

Last '[] = Apply ErrorSym0 "Data.Singletons.List.last: empty list" 
Last '[x] = x 
Last ((:) _ ((:) x xs)) = Apply LastSym0 (Apply (Apply (:@#@$) x) xs) 

sLast :: forall a (t :: [a]). Sing t -> Sing (Apply LastSym0 t :: a) Source #

type family Tail (a :: [a]) :: [a] where ... Source #

Equations

Tail ((:) _ t) = t 
Tail '[] = Apply ErrorSym0 "Data.Singletons.List.tail: empty list" 

sTail :: forall a (t :: [a]). Sing t -> Sing (Apply TailSym0 t :: [a]) Source #

type family Init (a :: [a]) :: [a] where ... Source #

Equations

Init '[] = Apply ErrorSym0 "Data.Singletons.List.init: empty list" 
Init ((:) x xs) = Apply (Apply (Let6989586621679950647Init'Sym2 x xs) x) xs 

sInit :: forall a (t :: [a]). Sing t -> Sing (Apply InitSym0 t :: [a]) Source #

type family Null (arg :: t a) :: Bool Source #

Instances
type Null (a :: [a6989586621680452738]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (a :: [a6989586621680452738])
type Null (arg :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (arg :: Maybe a)
type Null (arg :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Null (arg :: Min a)
type Null (arg :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Null (arg :: Max a)
type Null (arg :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Null (arg :: First a)
type Null (arg :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Null (arg :: Last a)
type Null (arg :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Null (arg :: Option a)
type Null (a :: Identity a6989586621680452738) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Null (a :: Identity a6989586621680452738)
type Null (arg :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (arg :: First a)
type Null (arg :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (arg :: Last a)
type Null (a :: Dual a6989586621680452738) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (a :: Dual a6989586621680452738)
type Null (a :: Sum a6989586621680452738) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (a :: Sum a6989586621680452738)
type Null (a :: Product a6989586621680452738) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (a :: Product a6989586621680452738)
type Null (arg :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (arg :: NonEmpty a)
type Null (a2 :: Either a1 a6989586621680452738) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (a2 :: Either a1 a6989586621680452738)
type Null (arg :: (a1, a2)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (arg :: (a1, a2))
type Null (arg :: Arg a1 a2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Null (arg :: Arg a1 a2)
type Null (arg :: Const m a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Null (arg :: Const m a)

sNull :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply NullSym0 t :: Bool) Source #

type family Length (arg :: t a) :: Nat Source #

Instances
type Length (a :: [a6989586621680452739]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (a :: [a6989586621680452739])
type Length (arg :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (arg :: Maybe a)
type Length (arg :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Length (arg :: Min a)
type Length (arg :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Length (arg :: Max a)
type Length (arg :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Length (arg :: First a)
type Length (arg :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Length (arg :: Last a)
type Length (arg :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Length (arg :: Option a)
type Length (a :: Identity a6989586621680452739) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Length (a :: Identity a6989586621680452739)
type Length (arg :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (arg :: First a)
type Length (arg :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (arg :: Last a)
type Length (a :: Dual a6989586621680452739) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (a :: Dual a6989586621680452739)
type Length (a :: Sum a6989586621680452739) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (a :: Sum a6989586621680452739)
type Length (a :: Product a6989586621680452739) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (a :: Product a6989586621680452739)
type Length (arg :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (arg :: NonEmpty a)
type Length (a2 :: Either a1 a6989586621680452739) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (a2 :: Either a1 a6989586621680452739)
type Length (arg :: (a1, a2)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (arg :: (a1, a2))
type Length (arg :: Arg a1 a2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Length (arg :: Arg a1 a2)
type Length (arg :: Const m a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Length (arg :: Const m a)

sLength :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply LengthSym0 t :: Nat) Source #

List transformations

type family Map (a :: (~>) a b) (a :: [a]) :: [b] where ... Source #

Equations

Map _ '[] = '[] 
Map f ((:) x xs) = Apply (Apply (:@#@$) (Apply f x)) (Apply (Apply MapSym0 f) xs) 

sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b]) Source #

type family Reverse (a :: [a]) :: [a] where ... Source #

Equations

Reverse l = Apply (Apply (Let6989586621679950599RevSym1 l) l) '[] 

sReverse :: forall a (t :: [a]). Sing t -> Sing (Apply ReverseSym0 t :: [a]) 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 #

type family Transpose (a :: [[a]]) :: [[a]] where ... Source #

Equations

Transpose '[] = '[] 
Transpose ((:) '[] xss) = Apply TransposeSym0 xss 
Transpose ((:) ((:) x xs) xss) = Apply (Apply (:@#@$) (Apply (Apply (:@#@$) x) (Apply (Apply MapSym0 HeadSym0) xss))) (Apply TransposeSym0 (Apply (Apply (:@#@$) xs) (Apply (Apply MapSym0 TailSym0) xss))) 

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 #

Equations

Permutations xs0 = Apply (Apply (:@#@$) xs0) (Apply (Apply (Let6989586621679950465PermsSym1 xs0) xs0) '[]) 

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 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680452732]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680452732])
type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680452732) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680452732)
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Min a)
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Max a)
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a)
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a)
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Option a)
type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680452732) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680452732)
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a)
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a)
type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680452732) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680452732)
type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680452732) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680452732)
type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680452732) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680452732)
type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680452732) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (a1 :: k2 ~> (a6989586621680452732 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680452732)
type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1)
type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1))
type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Arg a2 a1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Arg a2 a1)
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Const m a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Const m a)

sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source #

type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #

Instances
type Foldl' (a1 :: k2 ~> (a6989586621680452734 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680452734]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (a1 :: k2 ~> (a6989586621680452734 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680452734])
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Min a)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Max a)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Option a)
type Foldl' (a1 :: k2 ~> (a6989586621680452734 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680452734) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Foldl' (a1 :: k2 ~> (a6989586621680452734 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680452734)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a)
type Foldl' (a1 :: k2 ~> (a6989586621680452734 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680452734) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (a1 :: k2 ~> (a6989586621680452734 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680452734)
type Foldl' (a1 :: k2 ~> (a6989586621680452734 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680452734) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (a1 :: k2 ~> (a6989586621680452734 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680452734)
type Foldl' (a1 :: k2 ~> (a6989586621680452734 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680452734) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (a1 :: k2 ~> (a6989586621680452734 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680452734)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: NonEmpty a)
type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1)
type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1))
type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Arg a2 a1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Arg a2 a1)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Const m a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Const m a)

sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) Source #

type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #

Instances
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2])
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a)
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Min a)
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Max a)
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a)
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a)
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Option a)
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2)
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a)
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a)
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2)
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2)
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2)
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2)
type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1)
type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1))
type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Arg a2 a1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Arg a2 a1)
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Const m a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Const m a)

sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) Source #

type family Foldl1' (a :: (~>) a ((~>) a a)) (a :: [a]) :: a where ... Source #

Equations

Foldl1' f ((:) x xs) = Apply (Apply (Apply Foldl'Sym0 f) x) xs 
Foldl1' _ '[] = Apply ErrorSym0 "Data.Singletons.List.foldl1': empty list" 

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 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680452727]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680452727])
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680452727)
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Min a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Min a6989586621680452727)
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Max a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Max a6989586621680452727)
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680452727)
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680452727)
type Foldr (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Option a)
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680452727)
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: First a6989586621680452727)
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680452727)
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680452727)
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Sum a6989586621680452727)
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680452727)
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: NonEmpty a6989586621680452727)
type Foldr (a2 :: a6989586621680452727 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Either a1 a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a2 :: a6989586621680452727 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Either a1 a6989586621680452727)
type Foldr (a2 :: a6989586621680452727 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: (a1, a6989586621680452727)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a2 :: a6989586621680452727 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: (a1, a6989586621680452727))
type Foldr (a2 :: a6989586621680452727 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Arg a1 a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr (a2 :: a6989586621680452727 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Arg a1 a6989586621680452727)
type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Const m a6989586621680452727) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Foldr (a1 :: a6989586621680452727 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Const m a6989586621680452727)

sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source #

type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #

Instances
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2])
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a)
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Min a)
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Max a)
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a)
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a)
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Option a)
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2)
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a)
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a)
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2)
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2)
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2)
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2)
type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1)
type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1))
type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Arg a2 a1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Arg a2 a1)
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Const m a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Const m a)

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

type family Concat (a :: t [a]) :: [a] where ... Source #

Equations

Concat xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621680453237Sym0 xs)) '[]) xs 

sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a]) Source #

type family ConcatMap (a :: (~>) a [b]) (a :: t a) :: [b] where ... Source #

Equations

ConcatMap f xs = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_6989586621680453224Sym0 f) xs)) '[]) xs 

sConcatMap :: forall t a b (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) Source #

type family And (a :: t Bool) :: Bool where ... Source #

Equations

And x = Case_6989586621680453214 x (Let6989586621680453212Scrutinee_6989586621680452970Sym1 x) 

sAnd :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool) Source #

type family Or (a :: t Bool) :: Bool where ... Source #

Equations

Or x = Case_6989586621680453205 x (Let6989586621680453203Scrutinee_6989586621680452972Sym1 x) 

sOr :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool) Source #

type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #

Equations

Any p x = Case_6989586621680453196 p x (Let6989586621680453193Scrutinee_6989586621680452974Sym2 p x) 

sAny :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool) Source #

type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #

Equations

All p x = Case_6989586621680453183 p x (Let6989586621680453180Scrutinee_6989586621680452976Sym2 p x) 

sAll :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) Source #

type family Sum (arg :: t a) :: a Source #

Instances
type Sum (a :: [k2]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (a :: [k2])
type Sum (arg :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg :: Maybe a)
type Sum (arg :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sum (arg :: Min a)
type Sum (arg :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sum (arg :: Max a)
type Sum (arg :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sum (arg :: First a)
type Sum (arg :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sum (arg :: Last a)
type Sum (arg :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sum (arg :: Option a)
type Sum (a :: Identity k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Sum (a :: Identity k2)
type Sum (arg :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg :: First a)
type Sum (arg :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg :: Last a)
type Sum (a :: Dual k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (a :: Dual k2)
type Sum (a :: Sum k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (a :: Sum k2)
type Sum (a :: Product k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (a :: Product k2)
type Sum (arg :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg :: NonEmpty a)
type Sum (arg :: Either a1 a2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg :: Either a1 a2)
type Sum (arg :: (a1, a2)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg :: (a1, a2))
type Sum (arg :: Arg a1 a2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sum (arg :: Arg a1 a2)
type Sum (arg :: Const m a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Sum (arg :: Const m a)

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 # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (a :: [k2])
type Product (arg :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg :: Maybe a)
type Product (arg :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Product (arg :: Min a)
type Product (arg :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Product (arg :: Max a)
type Product (arg :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Product (arg :: First a)
type Product (arg :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Product (arg :: Last a)
type Product (arg :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Product (arg :: Option a)
type Product (a :: Identity k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Product (a :: Identity k2)
type Product (arg :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg :: First a)
type Product (arg :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg :: Last a)
type Product (a :: Dual k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (a :: Dual k2)
type Product (a :: Sum k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (a :: Sum k2)
type Product (a :: Product k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (a :: Product k2)
type Product (arg :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg :: NonEmpty a)
type Product (arg :: Either a1 a2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg :: Either a1 a2)
type Product (arg :: (a1, a2)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg :: (a1, a2))
type Product (arg :: Arg a1 a2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Product (arg :: Arg a1 a2)
type Product (arg :: Const m a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Product (arg :: Const m a)

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 # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (a :: [k2])
type Maximum (arg :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg :: Maybe a)
type Maximum (arg :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Maximum (arg :: Min a)
type Maximum (arg :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Maximum (arg :: Max a)
type Maximum (arg :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Maximum (arg :: First a)
type Maximum (arg :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Maximum (arg :: Last a)
type Maximum (arg :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Maximum (arg :: Option a)
type Maximum (a :: Identity k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Maximum (a :: Identity k2)
type Maximum (arg :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg :: First a)
type Maximum (arg :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg :: Last a)
type Maximum (a :: Dual k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (a :: Dual k2)
type Maximum (a :: Sum k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (a :: Sum k2)
type Maximum (a :: Product k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (a :: Product k2)
type Maximum (arg :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg :: NonEmpty a)
type Maximum (arg :: Either a1 a2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg :: Either a1 a2)
type Maximum (arg :: (a1, a2)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg :: (a1, a2))
type Maximum (arg :: Arg a1 a2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Maximum (arg :: Arg a1 a2)
type Maximum (arg :: Const m a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Maximum (arg :: Const m a)

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 # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (a :: [k2])
type Minimum (arg :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg :: Maybe a)
type Minimum (arg :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Minimum (arg :: Min a)
type Minimum (arg :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Minimum (arg :: Max a)
type Minimum (arg :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Minimum (arg :: First a)
type Minimum (arg :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Minimum (arg :: Last a)
type Minimum (arg :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Minimum (arg :: Option a)
type Minimum (a :: Identity k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Minimum (a :: Identity k2)
type Minimum (arg :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg :: First a)
type Minimum (arg :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg :: Last a)
type Minimum (a :: Dual k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (a :: Dual k2)
type Minimum (a :: Sum k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (a :: Sum k2)
type Minimum (a :: Product k2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (a :: Product k2)
type Minimum (arg :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg :: NonEmpty a)
type Minimum (arg :: Either a1 a2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg :: Either a1 a2)
type Minimum (arg :: (a1, a2)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg :: (a1, a2))
type Minimum (arg :: Arg a1 a2) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Minimum (arg :: Arg a1 a2)
type Minimum (arg :: Const m a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Minimum (arg :: Const m a)

sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a) Source #

Building lists

Scans

type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: [b] where ... Source #

Equations

Scanl f q ls = Apply (Apply (:@#@$) q) (Case_6989586621679950237 f q ls ls) 

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 #

type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ... Source #

Equations

Scanl1 f ((:) x xs) = Apply (Apply (Apply ScanlSym0 f) x) xs 
Scanl1 _ '[] = '[] 

sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a]) Source #

type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: [b] where ... Source #

Equations

Scanr _ q0 '[] = Apply (Apply (:@#@$) q0) '[] 
Scanr f q0 ((:) x xs) = Case_6989586621679950223 f q0 x xs (Let6989586621679950218Scrutinee_6989586621679940611Sym4 f q0 x xs) 

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_6989586621679940623 wild_6989586621679940625)) = Case_6989586621679950202 f x wild_6989586621679940623 wild_6989586621679940625 (Let6989586621679950197Scrutinee_6989586621679940617Sym4 f x wild_6989586621679940623 wild_6989586621679940625) 

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_6989586621680757124 f s t (Let6989586621680757120Scrutinee_6989586621680756655Sym3 f s t) 

sMapAccumL :: forall t a b c (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (a, t c)) Source #

type family MapAccumR (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ... Source #

Equations

MapAccumR f s t = Case_6989586621680757107 f s t (Let6989586621680757103Scrutinee_6989586621680756659Sym3 f s t) 

sMapAccumR :: forall t a b c (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c)) Source #

Cyclical lists

type family Replicate (a :: Nat) (a :: a) :: [a] where ... Source #

Equations

Replicate n x = Case_6989586621679949334 n x (Let6989586621679949331Scrutinee_6989586621679940719Sym2 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_6989586621679950050 f b (Let6989586621679950047Scrutinee_6989586621679940627Sym2 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

type family Take (a :: Nat) (a :: [a]) :: [a] where ... Source #

Equations

Take _ '[] = '[] 
Take n ((:) x xs) = Case_6989586621679949432 n x xs (Let6989586621679949428Scrutinee_6989586621679940703Sym3 n x xs) 

sTake :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) Source #

type family Drop (a :: Nat) (a :: [a]) :: [a] where ... Source #

Equations

Drop _ '[] = '[] 
Drop n ((:) x xs) = Case_6989586621679949418 n x xs (Let6989586621679949414Scrutinee_6989586621679940705Sym3 n x xs) 

sDrop :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) Source #

type family SplitAt (a :: Nat) (a :: [a]) :: ([a], [a]) where ... Source #

Equations

SplitAt n xs = Apply (Apply Tuple2Sym0 (Apply (Apply TakeSym0 n) xs)) (Apply (Apply DropSym0 n) xs) 

sSplitAt :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) Source #

type family TakeWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ... Source #

Equations

TakeWhile _ '[] = '[] 
TakeWhile p ((:) x xs) = Case_6989586621679949590 p x xs (Let6989586621679949586Scrutinee_6989586621679940693Sym3 p x xs) 

sTakeWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) Source #

type family DropWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ... Source #

Equations

DropWhile _ '[] = '[] 
DropWhile p ((:) x xs') = Case_6989586621679949576 p x xs' (Let6989586621679949572Scrutinee_6989586621679940695Sym3 p x xs') 

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 #

Equations

DropWhileEnd p a_6989586621679950621 = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_6989586621679950625Sym0 p) a_6989586621679950621)) '[]) a_6989586621679950621 

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 Let6989586621679949488XsSym0) Let6989586621679949488XsSym0 
Span p ((:) x xs') = Case_6989586621679949500 p x xs' (Let6989586621679949496Scrutinee_6989586621679940699Sym3 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 Let6989586621679949445XsSym0) Let6989586621679949445XsSym0 
Break p ((:) x xs') = Case_6989586621679949457 p x xs' (Let6989586621679949453Scrutinee_6989586621679940701Sym3 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_6989586621680066334 arg_6989586621680066336 = Case_6989586621680078983 arg_6989586621680066334 arg_6989586621680066336 (Apply (Apply Tuple2Sym0 arg_6989586621680066334) arg_6989586621680066336) 

type family Group (a :: [a]) :: [[a]] where ... Source #

Equations

Group xs = Apply (Apply GroupBySym0 (==@#@$)) xs 

sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [[a]]) Source #

type family Inits (a :: [a]) :: [[a]] where ... Source #

Equations

Inits xs = Apply (Apply (:@#@$) '[]) (Case_6989586621679950036 xs xs) 

sInits :: forall a (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: [[a]]) Source #

type family Tails (a :: [a]) :: [[a]] where ... Source #

Equations

Tails xs = Apply (Apply (:@#@$) xs) (Case_6989586621679950029 xs xs) 

sTails :: forall a (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: [[a]]) Source #

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 #

sIsSuffixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) Source #

type family IsInfixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #

Equations

IsInfixOf needle haystack = Apply (Apply AnySym0 (Apply IsPrefixOfSym0 needle)) (Apply TailsSym0 haystack) 

sIsInfixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool) Source #

Searching lists

Searching by equality

type family Elem (arg :: a) (arg :: t a) :: Bool Source #

Instances
type Elem (a1 :: k1) (a2 :: [k1]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (a1 :: k1) (a2 :: [k1])
type Elem (arg1 :: a) (arg2 :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (arg1 :: a) (arg2 :: Maybe a)
type Elem (arg1 :: a) (arg2 :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Elem (arg1 :: a) (arg2 :: Min a)
type Elem (arg1 :: a) (arg2 :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Elem (arg1 :: a) (arg2 :: Max a)
type Elem (arg1 :: a) (arg2 :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Elem (arg1 :: a) (arg2 :: First a)
type Elem (arg1 :: a) (arg2 :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Elem (arg1 :: a) (arg2 :: Last a)
type Elem (arg1 :: a) (arg2 :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Elem (arg1 :: a) (arg2 :: Option a)
type Elem (a1 :: k1) (a2 :: Identity k1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Elem (a1 :: k1) (a2 :: Identity k1)
type Elem (arg1 :: a) (arg2 :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (arg1 :: a) (arg2 :: First a)
type Elem (arg1 :: a) (arg2 :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (arg1 :: a) (arg2 :: Last a)
type Elem (a1 :: k1) (a2 :: Dual k1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (a1 :: k1) (a2 :: Dual k1)
type Elem (a1 :: k1) (a2 :: Sum k1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (a1 :: k1) (a2 :: Sum k1)
type Elem (a1 :: k1) (a2 :: Product k1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (a1 :: k1) (a2 :: Product k1)
type Elem (arg1 :: a) (arg2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (arg1 :: a) (arg2 :: NonEmpty a)
type Elem (arg1 :: a1) (arg2 :: Either a2 a1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (arg1 :: a1) (arg2 :: Either a2 a1)
type Elem (arg1 :: a1) (arg2 :: (a2, a1)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (arg1 :: a1) (arg2 :: (a2, a1))
type Elem (arg1 :: a1) (arg2 :: Arg a2 a1) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Elem (arg1 :: a1) (arg2 :: Arg a2 a1)
type Elem (arg1 :: a) (arg2 :: Const m a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Elem (arg1 :: a) (arg2 :: Const m a)

sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) Source #

type family NotElem (a :: a) (a :: t a) :: Bool where ... Source #

Equations

NotElem x a_6989586621680453120 = Apply (Apply (Apply (.@#@$) NotSym0) (Apply ElemSym0 x)) a_6989586621680453120 

sNotElem :: forall t a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) Source #

type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... Source #

Equations

Lookup _key '[] = NothingSym0 
Lookup key ((:) '(x, y) xys) = Case_6989586621679949404 key x y xys (Let6989586621679949399Scrutinee_6989586621679940715Sym4 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_6989586621680453112 p y (Let6989586621680453095Scrutinee_6989586621680452982Sym2 p y) 

sFind :: forall t a (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a) Source #

type family Filter (a :: (~>) a Bool) (a :: [a]) :: [a] where ... Source #

Equations

Filter _p '[] = '[] 
Filter p ((:) x xs) = Case_6989586621679949605 p x xs (Let6989586621679949601Scrutinee_6989586621679940681Sym3 p x xs) 

sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) Source #

type family Partition (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ... Source #

Equations

Partition p xs = Apply (Apply (Apply FoldrSym0 (Apply SelectSym0 p)) (Apply (Apply Tuple2Sym0 '[]) '[])) xs 

sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) Source #

Indexing lists

type family (a :: [a]) !! (a :: Nat) :: a where ... infixl 9 Source #

Equations

'[] !! _ = Apply ErrorSym0 "Data.Singletons.List.!!: index too large" 
((:) x xs) !! n = Case_6989586621679949322 x xs n (Let6989586621679949318Scrutinee_6989586621679940721Sym3 x xs n) 

(%!!) :: forall a (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) infixl 9 Source #

type family ElemIndex (a :: a) (a :: [a]) :: Maybe Nat where ... Source #

Equations

ElemIndex x a_6989586621679949980 = Apply (Apply FindIndexSym0 (Apply (==@#@$) x)) a_6989586621679949980 

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_6989586621679949964 = Apply (Apply FindIndicesSym0 (Apply (==@#@$) x)) a_6989586621679949964 

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_6989586621679949972 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679949972 

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 #

Equations

FindIndices p xs = Apply (Apply MapSym0 SndSym0) (Apply (Apply FilterSym0 (Apply (Apply Lambda_6989586621679949949Sym0 p) xs)) (Apply (Apply ZipSym0 xs) (Apply (Apply (Let6989586621679949940BuildListSym2 p xs) (FromInteger 0)) xs))) 

sFindIndices :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat]) Source #

Zipping and unzipping lists

type family Zip (a :: [a]) (a :: [b]) :: [(a, b)] where ... Source #

Equations

Zip ((:) x xs) ((:) y ys) = Apply (Apply (:@#@$) (Apply (Apply Tuple2Sym0 x) y)) (Apply (Apply ZipSym0 xs) ys) 
Zip '[] '[] = '[] 
Zip ((:) _ _) '[] = '[] 
Zip '[] ((:) _ _) = '[] 

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_6989586621680078956 a_6989586621680078958 a_6989586621680078960 a_6989586621680078962 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621680078956) a_6989586621680078958) a_6989586621680078960) a_6989586621680078962 

type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ... Source #

Equations

Zip5 a_6989586621680078931 a_6989586621680078933 a_6989586621680078935 a_6989586621680078937 a_6989586621680078939 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621680078931) a_6989586621680078933) a_6989586621680078935) a_6989586621680078937) a_6989586621680078939 

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_6989586621680078901 a_6989586621680078903 a_6989586621680078905 a_6989586621680078907 a_6989586621680078909 a_6989586621680078911 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621680078901) a_6989586621680078903) a_6989586621680078905) a_6989586621680078907) a_6989586621680078909) a_6989586621680078911 

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_6989586621680078866 a_6989586621680078868 a_6989586621680078870 a_6989586621680078872 a_6989586621680078874 a_6989586621680078876 a_6989586621680078878 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621680078866) a_6989586621680078868) a_6989586621680078870) a_6989586621680078872) a_6989586621680078874) a_6989586621680078876) a_6989586621680078878 

type family ZipWith (a :: (~>) a ((~>) b c)) (a :: [a]) (a :: [b]) :: [c] where ... Source #

Equations

ZipWith f ((:) x xs) ((:) y ys) = Apply (Apply (:@#@$) (Apply (Apply f x) y)) (Apply (Apply (Apply ZipWithSym0 f) xs) ys) 
ZipWith _ '[] '[] = '[] 
ZipWith _ ((:) _ _) '[] = '[] 
ZipWith _ '[] ((:) _ _) = '[] 

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 #

Equations

ZipWith4 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) = Apply (Apply (:@#@$) (Apply (Apply (Apply (Apply z a) b) c) d)) (Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 z) as) bs) cs) ds) 
ZipWith4 _ _ _ _ _ = '[] 

type family ZipWith5 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ... Source #

Equations

ZipWith5 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) ((:) e es) = Apply (Apply (:@#@$) (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e)) (Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 z) as) bs) cs) ds) es) 
ZipWith5 _ _ _ _ _ _ = '[] 

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 #

Equations

ZipWith6 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) ((:) e es) ((:) f fs) = Apply (Apply (:@#@$) (Apply (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e) f)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 z) as) bs) cs) ds) es) fs) 
ZipWith6 _ _ _ _ _ _ _ = '[] 

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 _ _ _ _ _ _ _ _ = '[] 

type family Unzip (a :: [(a, b)]) :: ([a], [b]) where ... Source #

Equations

Unzip xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679949872Sym0 xs)) (Apply (Apply Tuple2Sym0 '[]) '[])) xs 

sUnzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b])) Source #

type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ... Source #

Equations

Unzip3 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679949851Sym0 xs)) (Apply (Apply (Apply Tuple3Sym0 '[]) '[]) '[])) xs 

sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c])) Source #

type family Unzip4 (a :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ... Source #

Equations

Unzip4 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679949828Sym0 xs)) (Apply (Apply (Apply (Apply Tuple4Sym0 '[]) '[]) '[]) '[])) xs 

sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d])) Source #

type family Unzip5 (a :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ... Source #

Equations

Unzip5 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679949803Sym0 xs)) (Apply (Apply (Apply (Apply (Apply Tuple5Sym0 '[]) '[]) '[]) '[]) '[])) xs 

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 #

type family Unzip6 (a :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ... Source #

Equations

Unzip6 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679949776Sym0 xs)) (Apply (Apply (Apply (Apply (Apply (Apply Tuple6Sym0 '[]) '[]) '[]) '[]) '[]) '[])) xs 

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 #

Equations

Unzip7 xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621679949747Sym0 xs)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply Tuple7Sym0 '[]) '[]) '[]) '[]) '[]) '[]) '[])) xs 

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 Symbols

type family Unlines (a :: [Symbol]) :: Symbol where ... Source #

Equations

Unlines '[] = "" 
Unlines ((:) l ls) = Apply (Apply (<>@#@$) l) (Apply (Apply (<>@#@$) "\n") (Apply UnlinesSym0 ls)) 

sUnlines :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnlinesSym0 t :: Symbol) Source #

type family Unwords (a :: [Symbol]) :: Symbol where ... Source #

Equations

Unwords '[] = "" 
Unwords ((:) w ws) = Apply (Apply (<>@#@$) w) (Apply (Let6989586621679949733GoSym2 w ws) ws) 

sUnwords :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnwordsSym0 t :: Symbol) Source #

"Set" operations

type family Nub (a :: [a]) :: [a] where ... Source #

Equations

Nub l = Apply (Apply (Let6989586621679950001Nub'Sym1 l) l) '[] 

sNub :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply NubSym0 t :: [a]) Source #

type family Delete (a :: a) (a :: [a]) :: [a] where ... Source #

Equations

Delete a_6989586621679949709 a_6989586621679949711 = Apply (Apply (Apply DeleteBySym0 (==@#@$)) a_6989586621679949709) a_6989586621679949711 

sDelete :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a]) Source #

type family (a :: [a]) \\ (a :: [a]) :: [a] where ... infix 5 Source #

Equations

a_6989586621679949719 \\ a_6989586621679949721 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 DeleteSym0)) a_6989586621679949719) a_6989586621679949721 

(%\\) :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (\\@#@$) t) t :: [a]) infix 5 Source #

type family Union (a :: [a]) (a :: [a]) :: [a] where ... Source #

Equations

Union a_6989586621679949699 a_6989586621679949701 = Apply (Apply (Apply UnionBySym0 (==@#@$)) a_6989586621679949699) a_6989586621679949701 

sUnion :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a]) Source #

type family Intersect (a :: [a]) (a :: [a]) :: [a] where ... Source #

Equations

Intersect a_6989586621679950294 a_6989586621679950296 = Apply (Apply (Apply IntersectBySym0 (==@#@$)) a_6989586621679950294) a_6989586621679950296 

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_6989586621679949654 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679949654 

sSort :: forall a (t :: [a]). SOrd a => Sing t -> Sing (Apply SortSym0 t :: [a]) Source #

Generalized functions

The "By" operations

User-supplied equality (replacing an Eq context)

The predicate is assumed to define an equivalence.

type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [a] where ... Source #

Equations

NubBy eq l = Apply (Apply (Let6989586621679949292NubBy'Sym2 eq l) l) '[] 

sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a]) Source #

type family DeleteBy (a :: (~>) a ((~>) a Bool)) (a :: a) (a :: [a]) :: [a] where ... Source #

Equations

DeleteBy _ _ '[] = '[] 
DeleteBy eq x ((:) y ys) = Case_6989586621679949674 eq x y ys (Let6989586621679949669Scrutinee_6989586621679940665Sym4 eq x y ys) 

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_6989586621679949683 a_6989586621679949685 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679949683) a_6989586621679949685 

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 #

type family UnionBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ... Source #

Equations

UnionBy eq xs ys = Apply (Apply (++@#@$) xs) (Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) (Apply (Apply NubBySym0 eq) ys)) xs) 

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_6989586621679940685 wild_6989586621679940687) ((:) wild_6989586621679940689 wild_6989586621679940691) = Apply (Apply (>>=@#@$) (Let6989586621679950273XsSym5 eq wild_6989586621679940685 wild_6989586621679940687 wild_6989586621679940689 wild_6989586621679940691)) (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679950284Sym0 eq) wild_6989586621679940685) wild_6989586621679940687) wild_6989586621679940689) wild_6989586621679940691) 

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 #

type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [[a]] where ... Source #

Equations

GroupBy _ '[] = '[] 
GroupBy eq ((:) x xs) = Apply (Apply (:@#@$) (Apply (Apply (:@#@$) x) (Let6989586621679949534YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621679949534ZsSym3 eq x xs)) 

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.

type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: [a]) :: [a] where ... Source #

Equations

SortBy cmp a_6989586621679949650 = Apply (Apply (Apply FoldrSym0 (Apply InsertBySym0 cmp)) '[]) a_6989586621679949650 

sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a]) Source #

type family InsertBy (a :: (~>) a ((~>) a Ordering)) (a :: a) (a :: [a]) :: [a] where ... Source #

Equations

InsertBy _ x '[] = Apply (Apply (:@#@$) x) '[] 
InsertBy cmp x ((:) y ys') = Case_6989586621679949637 cmp x y ys' (Let6989586621679949632Scrutinee_6989586621679940667Sym4 cmp x y ys') 

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_6989586621680453153 = Apply (Apply Foldl1Sym0 (Let6989586621680453157Max'Sym2 cmp a_6989586621680453153)) a_6989586621680453153 

sMaximumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) Source #

type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #

Equations

MinimumBy cmp a_6989586621680453128 = Apply (Apply Foldl1Sym0 (Let6989586621680453132Min'Sym2 cmp a_6989586621680453128)) a_6989586621680453128 

sMinimumBy :: forall t a (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) Source #

The "generic" operations

The prefix `generic' indicates an overloaded function that is a generalized version of a Prelude function.

type family GenericLength (a :: [a]) :: i where ... Source #

sGenericLength :: forall i a (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i) Source #

type family GenericTake (a :: i) (a :: [a]) :: [a] where ... Source #

Equations

GenericTake a_6989586621680078756 a_6989586621680078758 = Apply (Apply TakeSym0 a_6989586621680078756) a_6989586621680078758 

type family GenericDrop (a :: i) (a :: [a]) :: [a] where ... Source #

Equations

GenericDrop a_6989586621680078746 a_6989586621680078748 = Apply (Apply DropSym0 a_6989586621680078746) a_6989586621680078748 

type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ... Source #

Equations

GenericSplitAt a_6989586621680078736 a_6989586621680078738 = Apply (Apply SplitAtSym0 a_6989586621680078736) a_6989586621680078738 

type family GenericIndex (a :: [a]) (a :: i) :: a where ... Source #

Equations

GenericIndex a_6989586621680078726 a_6989586621680078728 = Apply (Apply (!!@#@$) a_6989586621680078726) a_6989586621680078728 

type family GenericReplicate (a :: i) (a :: a) :: [a] where ... Source #

Equations

GenericReplicate a_6989586621680078716 a_6989586621680078718 = Apply (Apply ReplicateSym0 a_6989586621680078716) a_6989586621680078718 

Defunctionalization symbols

type NilSym0 = '[] Source #

data (:@#@$) :: forall (a3530822107858468865 :: Type). (~>) a3530822107858468865 ((~>) [a3530822107858468865] [(a3530822107858468865 :: Type)]) infixr 5 Source #

Instances
SingI ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings ((:@#@$) :: TyFun a3530822107858468865 ([a3530822107858468865] ~> [a3530822107858468865]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:@#@$) :: TyFun a3530822107858468865 ([a3530822107858468865] ~> [a3530822107858468865]) -> Type) (t6989586621679298917 :: a3530822107858468865) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:@#@$) :: TyFun a3530822107858468865 ([a3530822107858468865] ~> [a3530822107858468865]) -> Type) (t6989586621679298917 :: a3530822107858468865) = (:@#@$$) t6989586621679298917

data (:@#@$$) (t6989586621679298917 :: (a3530822107858468865 :: Type)) :: (~>) [a3530822107858468865] [(a3530822107858468865 :: Type)] infixr 5 Source #

Instances
SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

sing :: Sing ((:@#@$$) d) Source #

SuppressUnusedWarnings ((:@#@$$) t6989586621679298917 :: TyFun [a3530822107858468865] [a3530822107858468865] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:@#@$$) t6989586621679298917 :: TyFun [a] [a] -> Type) (t6989586621679298918 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:@#@$$) t6989586621679298917 :: TyFun [a] [a] -> Type) (t6989586621679298918 :: [a]) = t6989586621679298917 ': t6989586621679298918

type (:@#@$$$) (t6989586621679298917 :: a3530822107858468865) (t6989586621679298918 :: [a3530822107858468865]) = (:) t6989586621679298917 t6989586621679298918 Source #

type (++@#@$$$) (a6989586621679521123 :: [a6989586621679520926]) (a6989586621679521124 :: [a6989586621679520926]) = (++) a6989586621679521123 a6989586621679521124 Source #

data (++@#@$$) (a6989586621679521123 :: [a6989586621679520926]) :: (~>) [a6989586621679520926] [a6989586621679520926] infixr 5 Source #

Instances
SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing ((++@#@$$) d) Source #

SuppressUnusedWarnings ((++@#@$$) a6989586621679521123 :: TyFun [a6989586621679520926] [a6989586621679520926] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((++@#@$$) a6989586621679521123 :: TyFun [a] [a] -> Type) (a6989586621679521124 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((++@#@$$) a6989586621679521123 :: TyFun [a] [a] -> Type) (a6989586621679521124 :: [a]) = a6989586621679521123 ++ a6989586621679521124

data (++@#@$) :: forall a6989586621679520926. (~>) [a6989586621679520926] ((~>) [a6989586621679520926] [a6989586621679520926]) infixr 5 Source #

Instances
SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679520926] ([a6989586621679520926] ~> [a6989586621679520926]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((++@#@$) :: TyFun [a6989586621679520926] ([a6989586621679520926] ~> [a6989586621679520926]) -> Type) (a6989586621679521123 :: [a6989586621679520926]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((++@#@$) :: TyFun [a6989586621679520926] ([a6989586621679520926] ~> [a6989586621679520926]) -> Type) (a6989586621679521123 :: [a6989586621679520926]) = (++@#@$$) a6989586621679521123

data HeadSym0 :: forall a6989586621679940142. (~>) [a6989586621679940142] a6989586621679940142 Source #

Instances
SingI (HeadSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (HeadSym0 :: TyFun [a6989586621679940142] a6989586621679940142 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679950665 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679950665 :: [a]) = Head a6989586621679950665

type HeadSym1 (a6989586621679950665 :: [a6989586621679940142]) = Head a6989586621679950665 Source #

data LastSym0 :: forall a6989586621679940141. (~>) [a6989586621679940141] a6989586621679940141 Source #

Instances
SingI (LastSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (LastSym0 :: TyFun [a6989586621679940141] a6989586621679940141 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679950660 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679950660 :: [a]) = Last a6989586621679950660

type LastSym1 (a6989586621679950660 :: [a6989586621679940141]) = Last a6989586621679950660 Source #

data TailSym0 :: forall a6989586621679940140. (~>) [a6989586621679940140] [a6989586621679940140] Source #

Instances
SingI (TailSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TailSym0 :: TyFun [a6989586621679940140] [a6989586621679940140] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679950657 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679950657 :: [a]) = Tail a6989586621679950657

type TailSym1 (a6989586621679950657 :: [a6989586621679940140]) = Tail a6989586621679950657 Source #

data InitSym0 :: forall a6989586621679940139. (~>) [a6989586621679940139] [a6989586621679940139] Source #

Instances
SingI (InitSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (InitSym0 :: TyFun [a6989586621679940139] [a6989586621679940139] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679950643 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679950643 :: [a]) = Init a6989586621679950643

type InitSym1 (a6989586621679950643 :: [a6989586621679940139]) = Init a6989586621679950643 Source #

data NullSym0 :: forall a6989586621680452738 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452738) Bool Source #

Instances
SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680452723 a6989586621680452738) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680453386 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680453386 :: t a) = Null arg6989586621680453386

type NullSym1 (arg6989586621680453386 :: t6989586621680452723 a6989586621680452738) = Null arg6989586621680453386 Source #

data LengthSym0 :: forall a6989586621680452739 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452739) Nat Source #

Instances
SFoldable t => SingI (LengthSym0 :: TyFun (t a) Nat -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (LengthSym0 :: TyFun (t6989586621680452723 a6989586621680452739) Nat -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (arg6989586621680453388 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (arg6989586621680453388 :: t a) = Length arg6989586621680453388

type LengthSym1 (arg6989586621680453388 :: t6989586621680452723 a6989586621680452739) = Length arg6989586621680453388 Source #

data MapSym0 :: forall a6989586621679520927 b6989586621679520928. (~>) ((~>) a6989586621679520927 b6989586621679520928) ((~>) [a6989586621679520927] [b6989586621679520928]) Source #

Instances
SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (MapSym0 :: TyFun (a6989586621679520927 ~> b6989586621679520928) ([a6989586621679520927] ~> [b6989586621679520928]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym0 :: TyFun (a6989586621679520927 ~> b6989586621679520928) ([a6989586621679520927] ~> [b6989586621679520928]) -> Type) (a6989586621679521131 :: a6989586621679520927 ~> b6989586621679520928) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym0 :: TyFun (a6989586621679520927 ~> b6989586621679520928) ([a6989586621679520927] ~> [b6989586621679520928]) -> Type) (a6989586621679521131 :: a6989586621679520927 ~> b6989586621679520928) = MapSym1 a6989586621679521131

data MapSym1 (a6989586621679521131 :: (~>) a6989586621679520927 b6989586621679520928) :: (~>) [a6989586621679520927] [b6989586621679520928] Source #

Instances
SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (MapSym1 d) Source #

SuppressUnusedWarnings (MapSym1 a6989586621679521131 :: TyFun [a6989586621679520927] [b6989586621679520928] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym1 a6989586621679521131 :: TyFun [a] [b] -> Type) (a6989586621679521132 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym1 a6989586621679521131 :: TyFun [a] [b] -> Type) (a6989586621679521132 :: [a]) = Map a6989586621679521131 a6989586621679521132

type MapSym2 (a6989586621679521131 :: (~>) a6989586621679520927 b6989586621679520928) (a6989586621679521132 :: [a6989586621679520927]) = Map a6989586621679521131 a6989586621679521132 Source #

data ReverseSym0 :: forall a6989586621679940137. (~>) [a6989586621679940137] [a6989586621679940137] Source #

Instances
SingI (ReverseSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ReverseSym0 :: TyFun [a6989586621679940137] [a6989586621679940137] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679950596 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679950596 :: [a]) = Reverse a6989586621679950596

type ReverseSym1 (a6989586621679950596 :: [a6989586621679940137]) = Reverse a6989586621679950596 Source #

data IntersperseSym0 :: forall a6989586621679940136. (~>) a6989586621679940136 ((~>) [a6989586621679940136] [a6989586621679940136]) Source #

Instances
SingI (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679940136 ([a6989586621679940136] ~> [a6989586621679940136]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersperseSym0 :: TyFun a6989586621679940136 ([a6989586621679940136] ~> [a6989586621679940136]) -> Type) (a6989586621679950583 :: a6989586621679940136) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersperseSym0 :: TyFun a6989586621679940136 ([a6989586621679940136] ~> [a6989586621679940136]) -> Type) (a6989586621679950583 :: a6989586621679940136) = IntersperseSym1 a6989586621679950583

data IntersperseSym1 (a6989586621679950583 :: a6989586621679940136) :: (~>) [a6989586621679940136] [a6989586621679940136] Source #

Instances
SingI d => SingI (IntersperseSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntersperseSym1 a6989586621679950583 :: TyFun [a6989586621679940136] [a6989586621679940136] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersperseSym1 a6989586621679950583 :: TyFun [a] [a] -> Type) (a6989586621679950584 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersperseSym1 a6989586621679950583 :: TyFun [a] [a] -> Type) (a6989586621679950584 :: [a]) = Intersperse a6989586621679950583 a6989586621679950584

type IntersperseSym2 (a6989586621679950583 :: a6989586621679940136) (a6989586621679950584 :: [a6989586621679940136]) = Intersperse a6989586621679950583 a6989586621679950584 Source #

data IntercalateSym0 :: forall a6989586621679940135. (~>) [a6989586621679940135] ((~>) [[a6989586621679940135]] [a6989586621679940135]) Source #

Instances
SingI (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a6989586621679940135] ([[a6989586621679940135]] ~> [a6989586621679940135]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntercalateSym0 :: TyFun [a6989586621679940135] ([[a6989586621679940135]] ~> [a6989586621679940135]) -> Type) (a6989586621679950590 :: [a6989586621679940135]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntercalateSym0 :: TyFun [a6989586621679940135] ([[a6989586621679940135]] ~> [a6989586621679940135]) -> Type) (a6989586621679950590 :: [a6989586621679940135]) = IntercalateSym1 a6989586621679950590

data IntercalateSym1 (a6989586621679950590 :: [a6989586621679940135]) :: (~>) [[a6989586621679940135]] [a6989586621679940135] Source #

Instances
SingI d => SingI (IntercalateSym1 d :: TyFun [[a]] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntercalateSym1 a6989586621679950590 :: TyFun [[a6989586621679940135]] [a6989586621679940135] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntercalateSym1 a6989586621679950590 :: TyFun [[a]] [a] -> Type) (a6989586621679950591 :: [[a]]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntercalateSym1 a6989586621679950590 :: TyFun [[a]] [a] -> Type) (a6989586621679950591 :: [[a]]) = Intercalate a6989586621679950590 a6989586621679950591

type IntercalateSym2 (a6989586621679950590 :: [a6989586621679940135]) (a6989586621679950591 :: [[a6989586621679940135]]) = Intercalate a6989586621679950590 a6989586621679950591 Source #

data TransposeSym0 :: forall a6989586621679940022. (~>) [[a6989586621679940022]] [[a6989586621679940022]] Source #

Instances
SingI (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a6989586621679940022]] [[a6989586621679940022]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679950668 :: [[a]]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679950668 :: [[a]]) = Transpose a6989586621679950668

type TransposeSym1 (a6989586621679950668 :: [[a6989586621679940022]]) = Transpose a6989586621679950668 Source #

data SubsequencesSym0 :: forall a6989586621679940134. (~>) [a6989586621679940134] [[a6989586621679940134]] Source #

Instances
SingI (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a6989586621679940134] [[a6989586621679940134]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679950580 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679950580 :: [a]) = Subsequences a6989586621679950580

type SubsequencesSym1 (a6989586621679950580 :: [a6989586621679940134]) = Subsequences a6989586621679950580 Source #

data PermutationsSym0 :: forall a6989586621679940131. (~>) [a6989586621679940131] [[a6989586621679940131]] Source #

Instances
SingI (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a6989586621679940131] [[a6989586621679940131]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679950462 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679950462 :: [a]) = Permutations a6989586621679950462

type PermutationsSym1 (a6989586621679950462 :: [a6989586621679940131]) = Permutations a6989586621679950462 Source #

data FoldlSym0 :: forall a6989586621680452732 b6989586621680452731 t6989586621680452723. (~>) ((~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) ((~>) b6989586621680452731 ((~>) (t6989586621680452723 a6989586621680452732) b6989586621680452731)) Source #

Instances
SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FoldlSym0 :: TyFun (b6989586621680452731 ~> (a6989586621680452732 ~> b6989586621680452731)) (b6989586621680452731 ~> (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym0 :: TyFun (b6989586621680452731 ~> (a6989586621680452732 ~> b6989586621680452731)) (b6989586621680452731 ~> (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731)) -> Type) (arg6989586621680453364 :: b6989586621680452731 ~> (a6989586621680452732 ~> b6989586621680452731)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym0 :: TyFun (b6989586621680452731 ~> (a6989586621680452732 ~> b6989586621680452731)) (b6989586621680452731 ~> (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731)) -> Type) (arg6989586621680453364 :: b6989586621680452731 ~> (a6989586621680452732 ~> b6989586621680452731)) = (FoldlSym1 arg6989586621680453364 t6989586621680452723 :: TyFun b6989586621680452731 (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731) -> Type)

data FoldlSym1 (arg6989586621680453364 :: (~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) :: forall t6989586621680452723. (~>) b6989586621680452731 ((~>) (t6989586621680452723 a6989586621680452732) b6989586621680452731) Source #

Instances
(SFoldable t, SingI d) => SingI (FoldlSym1 d t :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldlSym1 d t) Source #

SuppressUnusedWarnings (FoldlSym1 arg6989586621680453364 t6989586621680452723 :: TyFun b6989586621680452731 (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym1 arg6989586621680453364 t6989586621680452723 :: TyFun b6989586621680452731 (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731) -> Type) (arg6989586621680453365 :: b6989586621680452731) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym1 arg6989586621680453364 t6989586621680452723 :: TyFun b6989586621680452731 (t6989586621680452723 a6989586621680452732 ~> b6989586621680452731) -> Type) (arg6989586621680453365 :: b6989586621680452731) = (FoldlSym2 arg6989586621680453364 arg6989586621680453365 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452732) b6989586621680452731 -> Type)

data FoldlSym2 (arg6989586621680453364 :: (~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) (arg6989586621680453365 :: b6989586621680452731) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452732) b6989586621680452731 Source #

Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldlSym2 d1 d2 t) Source #

SuppressUnusedWarnings (FoldlSym2 arg6989586621680453365 arg6989586621680453364 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452732) b6989586621680452731 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym2 arg6989586621680453365 arg6989586621680453364 t :: TyFun (t a) b -> Type) (arg6989586621680453366 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym2 arg6989586621680453365 arg6989586621680453364 t :: TyFun (t a) b -> Type) (arg6989586621680453366 :: t a) = Foldl arg6989586621680453365 arg6989586621680453364 arg6989586621680453366

type FoldlSym3 (arg6989586621680453364 :: (~>) b6989586621680452731 ((~>) a6989586621680452732 b6989586621680452731)) (arg6989586621680453365 :: b6989586621680452731) (arg6989586621680453366 :: t6989586621680452723 a6989586621680452732) = Foldl arg6989586621680453364 arg6989586621680453365 arg6989586621680453366 Source #

data Foldl'Sym0 :: forall a6989586621680452734 b6989586621680452733 t6989586621680452723. (~>) ((~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) ((~>) b6989586621680452733 ((~>) (t6989586621680452723 a6989586621680452734) b6989586621680452733)) Source #

Instances
SFoldable t => SingI (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (b6989586621680452733 ~> (a6989586621680452734 ~> b6989586621680452733)) (b6989586621680452733 ~> (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym0 :: TyFun (b6989586621680452733 ~> (a6989586621680452734 ~> b6989586621680452733)) (b6989586621680452733 ~> (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733)) -> Type) (arg6989586621680453370 :: b6989586621680452733 ~> (a6989586621680452734 ~> b6989586621680452733)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym0 :: TyFun (b6989586621680452733 ~> (a6989586621680452734 ~> b6989586621680452733)) (b6989586621680452733 ~> (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733)) -> Type) (arg6989586621680453370 :: b6989586621680452733 ~> (a6989586621680452734 ~> b6989586621680452733)) = (Foldl'Sym1 arg6989586621680453370 t6989586621680452723 :: TyFun b6989586621680452733 (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733) -> Type)

data Foldl'Sym1 (arg6989586621680453370 :: (~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) :: forall t6989586621680452723. (~>) b6989586621680452733 ((~>) (t6989586621680452723 a6989586621680452734) b6989586621680452733) Source #

Instances
(SFoldable t, SingI d) => SingI (Foldl'Sym1 d t :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (Foldl'Sym1 d t) Source #

SuppressUnusedWarnings (Foldl'Sym1 arg6989586621680453370 t6989586621680452723 :: TyFun b6989586621680452733 (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym1 arg6989586621680453370 t6989586621680452723 :: TyFun b6989586621680452733 (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733) -> Type) (arg6989586621680453371 :: b6989586621680452733) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym1 arg6989586621680453370 t6989586621680452723 :: TyFun b6989586621680452733 (t6989586621680452723 a6989586621680452734 ~> b6989586621680452733) -> Type) (arg6989586621680453371 :: b6989586621680452733) = (Foldl'Sym2 arg6989586621680453370 arg6989586621680453371 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452734) b6989586621680452733 -> Type)

data Foldl'Sym2 (arg6989586621680453370 :: (~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) (arg6989586621680453371 :: b6989586621680452733) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452734) b6989586621680452733 Source #

Instances
(SFoldable t, SingI d1, SingI d2) => SingI (Foldl'Sym2 d1 d2 t :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (Foldl'Sym2 d1 d2 t) Source #

SuppressUnusedWarnings (Foldl'Sym2 arg6989586621680453371 arg6989586621680453370 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452734) b6989586621680452733 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym2 arg6989586621680453371 arg6989586621680453370 t :: TyFun (t a) b -> Type) (arg6989586621680453372 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym2 arg6989586621680453371 arg6989586621680453370 t :: TyFun (t a) b -> Type) (arg6989586621680453372 :: t a) = Foldl' arg6989586621680453371 arg6989586621680453370 arg6989586621680453372

type Foldl'Sym3 (arg6989586621680453370 :: (~>) b6989586621680452733 ((~>) a6989586621680452734 b6989586621680452733)) (arg6989586621680453371 :: b6989586621680452733) (arg6989586621680453372 :: t6989586621680452723 a6989586621680452734) = Foldl' arg6989586621680453370 arg6989586621680453371 arg6989586621680453372 Source #

data Foldl1Sym0 :: forall a6989586621680452736 t6989586621680452723. (~>) ((~>) a6989586621680452736 ((~>) a6989586621680452736 a6989586621680452736)) ((~>) (t6989586621680452723 a6989586621680452736) a6989586621680452736) Source #

Instances
SFoldable t => SingI (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (a6989586621680452736 ~> (a6989586621680452736 ~> a6989586621680452736)) (t6989586621680452723 a6989586621680452736 ~> a6989586621680452736) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym0 :: TyFun (a6989586621680452736 ~> (a6989586621680452736 ~> a6989586621680452736)) (t6989586621680452723 a6989586621680452736 ~> a6989586621680452736) -> Type) (arg6989586621680453380 :: a6989586621680452736 ~> (a6989586621680452736 ~> a6989586621680452736)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym0 :: TyFun (a6989586621680452736 ~> (a6989586621680452736 ~> a6989586621680452736)) (t6989586621680452723 a6989586621680452736 ~> a6989586621680452736) -> Type) (arg6989586621680453380 :: a6989586621680452736 ~> (a6989586621680452736 ~> a6989586621680452736)) = (Foldl1Sym1 arg6989586621680453380 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452736) a6989586621680452736 -> Type)

data Foldl1Sym1 (arg6989586621680453380 :: (~>) a6989586621680452736 ((~>) a6989586621680452736 a6989586621680452736)) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452736) a6989586621680452736 Source #

Instances
(SFoldable t, SingI d) => SingI (Foldl1Sym1 d t :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (Foldl1Sym1 d t) Source #

SuppressUnusedWarnings (Foldl1Sym1 arg6989586621680453380 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452736) a6989586621680452736 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym1 arg6989586621680453380 t :: TyFun (t a) a -> Type) (arg6989586621680453381 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym1 arg6989586621680453380 t :: TyFun (t a) a -> Type) (arg6989586621680453381 :: t a) = Foldl1 arg6989586621680453380 arg6989586621680453381

type Foldl1Sym2 (arg6989586621680453380 :: (~>) a6989586621680452736 ((~>) a6989586621680452736 a6989586621680452736)) (arg6989586621680453381 :: t6989586621680452723 a6989586621680452736) = Foldl1 arg6989586621680453380 arg6989586621680453381 Source #

data Foldl1'Sym0 :: forall a6989586621679940127. (~>) ((~>) a6989586621679940127 ((~>) a6989586621679940127 a6989586621679940127)) ((~>) [a6989586621679940127] a6989586621679940127) Source #

Instances
SingI (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (a6989586621679940127 ~> (a6989586621679940127 ~> a6989586621679940127)) ([a6989586621679940127] ~> a6989586621679940127) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Foldl1'Sym0 :: TyFun (a6989586621679940127 ~> (a6989586621679940127 ~> a6989586621679940127)) ([a6989586621679940127] ~> a6989586621679940127) -> Type) (a6989586621679950455 :: a6989586621679940127 ~> (a6989586621679940127 ~> a6989586621679940127)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Foldl1'Sym0 :: TyFun (a6989586621679940127 ~> (a6989586621679940127 ~> a6989586621679940127)) ([a6989586621679940127] ~> a6989586621679940127) -> Type) (a6989586621679950455 :: a6989586621679940127 ~> (a6989586621679940127 ~> a6989586621679940127)) = Foldl1'Sym1 a6989586621679950455

data Foldl1'Sym1 (a6989586621679950455 :: (~>) a6989586621679940127 ((~>) a6989586621679940127 a6989586621679940127)) :: (~>) [a6989586621679940127] a6989586621679940127 Source #

Instances
SingI d => SingI (Foldl1'Sym1 d :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (Foldl1'Sym1 d) Source #

SuppressUnusedWarnings (Foldl1'Sym1 a6989586621679950455 :: TyFun [a6989586621679940127] a6989586621679940127 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Foldl1'Sym1 a6989586621679950455 :: TyFun [a] a -> Type) (a6989586621679950456 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Foldl1'Sym1 a6989586621679950455 :: TyFun [a] a -> Type) (a6989586621679950456 :: [a]) = Foldl1' a6989586621679950455 a6989586621679950456

type Foldl1'Sym2 (a6989586621679950455 :: (~>) a6989586621679940127 ((~>) a6989586621679940127 a6989586621679940127)) (a6989586621679950456 :: [a6989586621679940127]) = Foldl1' a6989586621679950455 a6989586621679950456 Source #

data FoldrSym0 :: forall a6989586621680452727 b6989586621680452728 t6989586621680452723. (~>) ((~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) ((~>) b6989586621680452728 ((~>) (t6989586621680452723 a6989586621680452727) b6989586621680452728)) Source #

Instances
SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FoldrSym0 :: TyFun (a6989586621680452727 ~> (b6989586621680452728 ~> b6989586621680452728)) (b6989586621680452728 ~> (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym0 :: TyFun (a6989586621680452727 ~> (b6989586621680452728 ~> b6989586621680452728)) (b6989586621680452728 ~> (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728)) -> Type) (arg6989586621680453352 :: a6989586621680452727 ~> (b6989586621680452728 ~> b6989586621680452728)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym0 :: TyFun (a6989586621680452727 ~> (b6989586621680452728 ~> b6989586621680452728)) (b6989586621680452728 ~> (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728)) -> Type) (arg6989586621680453352 :: a6989586621680452727 ~> (b6989586621680452728 ~> b6989586621680452728)) = (FoldrSym1 arg6989586621680453352 t6989586621680452723 :: TyFun b6989586621680452728 (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728) -> Type)

data FoldrSym1 (arg6989586621680453352 :: (~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) :: forall t6989586621680452723. (~>) b6989586621680452728 ((~>) (t6989586621680452723 a6989586621680452727) b6989586621680452728) Source #

Instances
(SFoldable t, SingI d) => SingI (FoldrSym1 d t :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldrSym1 d t) Source #

SuppressUnusedWarnings (FoldrSym1 arg6989586621680453352 t6989586621680452723 :: TyFun b6989586621680452728 (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym1 arg6989586621680453352 t6989586621680452723 :: TyFun b6989586621680452728 (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728) -> Type) (arg6989586621680453353 :: b6989586621680452728) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym1 arg6989586621680453352 t6989586621680452723 :: TyFun b6989586621680452728 (t6989586621680452723 a6989586621680452727 ~> b6989586621680452728) -> Type) (arg6989586621680453353 :: b6989586621680452728) = (FoldrSym2 arg6989586621680453352 arg6989586621680453353 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452727) b6989586621680452728 -> Type)

data FoldrSym2 (arg6989586621680453352 :: (~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) (arg6989586621680453353 :: b6989586621680452728) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452727) b6989586621680452728 Source #

Instances
(SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 t :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FoldrSym2 d1 d2 t) Source #

SuppressUnusedWarnings (FoldrSym2 arg6989586621680453353 arg6989586621680453352 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452727) b6989586621680452728 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym2 arg6989586621680453353 arg6989586621680453352 t :: TyFun (t a) b -> Type) (arg6989586621680453354 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldrSym2 arg6989586621680453353 arg6989586621680453352 t :: TyFun (t a) b -> Type) (arg6989586621680453354 :: t a) = Foldr arg6989586621680453353 arg6989586621680453352 arg6989586621680453354

type FoldrSym3 (arg6989586621680453352 :: (~>) a6989586621680452727 ((~>) b6989586621680452728 b6989586621680452728)) (arg6989586621680453353 :: b6989586621680452728) (arg6989586621680453354 :: t6989586621680452723 a6989586621680452727) = Foldr arg6989586621680453352 arg6989586621680453353 arg6989586621680453354 Source #

data Foldr1Sym0 :: forall a6989586621680452735 t6989586621680452723. (~>) ((~>) a6989586621680452735 ((~>) a6989586621680452735 a6989586621680452735)) ((~>) (t6989586621680452723 a6989586621680452735) a6989586621680452735) Source #

Instances
SFoldable t => SingI (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (a6989586621680452735 ~> (a6989586621680452735 ~> a6989586621680452735)) (t6989586621680452723 a6989586621680452735 ~> a6989586621680452735) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr1Sym0 :: TyFun (a6989586621680452735 ~> (a6989586621680452735 ~> a6989586621680452735)) (t6989586621680452723 a6989586621680452735 ~> a6989586621680452735) -> Type) (arg6989586621680453376 :: a6989586621680452735 ~> (a6989586621680452735 ~> a6989586621680452735)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr1Sym0 :: TyFun (a6989586621680452735 ~> (a6989586621680452735 ~> a6989586621680452735)) (t6989586621680452723 a6989586621680452735 ~> a6989586621680452735) -> Type) (arg6989586621680453376 :: a6989586621680452735 ~> (a6989586621680452735 ~> a6989586621680452735)) = (Foldr1Sym1 arg6989586621680453376 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452735) a6989586621680452735 -> Type)

data Foldr1Sym1 (arg6989586621680453376 :: (~>) a6989586621680452735 ((~>) a6989586621680452735 a6989586621680452735)) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452735) a6989586621680452735 Source #

Instances
(SFoldable t, SingI d) => SingI (Foldr1Sym1 d t :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (Foldr1Sym1 d t) Source #

SuppressUnusedWarnings (Foldr1Sym1 arg6989586621680453376 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452735) a6989586621680452735 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr1Sym1 arg6989586621680453376 t :: TyFun (t a) a -> Type) (arg6989586621680453377 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr1Sym1 arg6989586621680453376 t :: TyFun (t a) a -> Type) (arg6989586621680453377 :: t a) = Foldr1 arg6989586621680453376 arg6989586621680453377

type Foldr1Sym2 (arg6989586621680453376 :: (~>) a6989586621680452735 ((~>) a6989586621680452735 a6989586621680452735)) (arg6989586621680453377 :: t6989586621680452723 a6989586621680452735) = Foldr1 arg6989586621680453376 arg6989586621680453377 Source #

data ConcatSym0 :: forall a6989586621680452649 t6989586621680452648. (~>) (t6989586621680452648 [a6989586621680452649]) [a6989586621680452649] Source #

Instances
SFoldable t => SingI (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ConcatSym0 :: TyFun (t6989586621680452648 [a6989586621680452649]) [a6989586621680452649] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680453234 :: t [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680453234 :: t [a]) = Concat a6989586621680453234

type ConcatSym1 (a6989586621680453234 :: t6989586621680452648 [a6989586621680452649]) = Concat a6989586621680453234 Source #

data ConcatMapSym0 :: forall a6989586621680452646 b6989586621680452647 t6989586621680452645. (~>) ((~>) a6989586621680452646 [b6989586621680452647]) ((~>) (t6989586621680452645 a6989586621680452646) [b6989586621680452647]) Source #

Instances
SFoldable t => SingI (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (a6989586621680452646 ~> [b6989586621680452647]) (t6989586621680452645 a6989586621680452646 ~> [b6989586621680452647]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatMapSym0 :: TyFun (a6989586621680452646 ~> [b6989586621680452647]) (t6989586621680452645 a6989586621680452646 ~> [b6989586621680452647]) -> Type) (a6989586621680453218 :: a6989586621680452646 ~> [b6989586621680452647]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatMapSym0 :: TyFun (a6989586621680452646 ~> [b6989586621680452647]) (t6989586621680452645 a6989586621680452646 ~> [b6989586621680452647]) -> Type) (a6989586621680453218 :: a6989586621680452646 ~> [b6989586621680452647]) = (ConcatMapSym1 a6989586621680453218 t6989586621680452645 :: TyFun (t6989586621680452645 a6989586621680452646) [b6989586621680452647] -> Type)

data ConcatMapSym1 (a6989586621680453218 :: (~>) a6989586621680452646 [b6989586621680452647]) :: forall t6989586621680452645. (~>) (t6989586621680452645 a6989586621680452646) [b6989586621680452647] Source #

Instances
(SFoldable t, SingI d) => SingI (ConcatMapSym1 d t :: TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (ConcatMapSym1 d t) Source #

SuppressUnusedWarnings (ConcatMapSym1 a6989586621680453218 t6989586621680452645 :: TyFun (t6989586621680452645 a6989586621680452646) [b6989586621680452647] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatMapSym1 a6989586621680453218 t :: TyFun (t a) [b] -> Type) (a6989586621680453219 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ConcatMapSym1 a6989586621680453218 t :: TyFun (t a) [b] -> Type) (a6989586621680453219 :: t a) = ConcatMap a6989586621680453218 a6989586621680453219

type ConcatMapSym2 (a6989586621680453218 :: (~>) a6989586621680452646 [b6989586621680452647]) (a6989586621680453219 :: t6989586621680452645 a6989586621680452646) = ConcatMap a6989586621680453218 a6989586621680453219 Source #

data AndSym0 :: forall t6989586621680452644. (~>) (t6989586621680452644 Bool) Bool Source #

Instances
SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AndSym0 :: TyFun (t6989586621680452644 Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680453209 :: t Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680453209 :: t Bool) = And a6989586621680453209

type AndSym1 (a6989586621680453209 :: t6989586621680452644 Bool) = And a6989586621680453209 Source #

data OrSym0 :: forall t6989586621680452643. (~>) (t6989586621680452643 Bool) Bool Source #

Instances
SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing OrSym0 Source #

SuppressUnusedWarnings (OrSym0 :: TyFun (t6989586621680452643 Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680453200 :: t Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680453200 :: t Bool) = Or a6989586621680453200

type OrSym1 (a6989586621680453200 :: t6989586621680452643 Bool) = Or a6989586621680453200 Source #

data AnySym0 :: forall a6989586621680452642 t6989586621680452641. (~>) ((~>) a6989586621680452642 Bool) ((~>) (t6989586621680452641 a6989586621680452642) Bool) Source #

Instances
SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AnySym0 :: TyFun (a6989586621680452642 ~> Bool) (t6989586621680452641 a6989586621680452642 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym0 :: TyFun (a6989586621680452642 ~> Bool) (t6989586621680452641 a6989586621680452642 ~> Bool) -> Type) (a6989586621680453187 :: a6989586621680452642 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym0 :: TyFun (a6989586621680452642 ~> Bool) (t6989586621680452641 a6989586621680452642 ~> Bool) -> Type) (a6989586621680453187 :: a6989586621680452642 ~> Bool) = (AnySym1 a6989586621680453187 t6989586621680452641 :: TyFun (t6989586621680452641 a6989586621680452642) Bool -> Type)

data AnySym1 (a6989586621680453187 :: (~>) a6989586621680452642 Bool) :: forall t6989586621680452641. (~>) (t6989586621680452641 a6989586621680452642) Bool Source #

Instances
(SFoldable t, SingI d) => SingI (AnySym1 d t :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (AnySym1 d t) Source #

SuppressUnusedWarnings (AnySym1 a6989586621680453187 t6989586621680452641 :: TyFun (t6989586621680452641 a6989586621680452642) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym1 a6989586621680453187 t :: TyFun (t a) Bool -> Type) (a6989586621680453188 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym1 a6989586621680453187 t :: TyFun (t a) Bool -> Type) (a6989586621680453188 :: t a) = Any a6989586621680453187 a6989586621680453188

type AnySym2 (a6989586621680453187 :: (~>) a6989586621680452642 Bool) (a6989586621680453188 :: t6989586621680452641 a6989586621680452642) = Any a6989586621680453187 a6989586621680453188 Source #

data AllSym0 :: forall a6989586621680452640 t6989586621680452639. (~>) ((~>) a6989586621680452640 Bool) ((~>) (t6989586621680452639 a6989586621680452640) Bool) Source #

Instances
SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AllSym0 :: TyFun (a6989586621680452640 ~> Bool) (t6989586621680452639 a6989586621680452640 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym0 :: TyFun (a6989586621680452640 ~> Bool) (t6989586621680452639 a6989586621680452640 ~> Bool) -> Type) (a6989586621680453174 :: a6989586621680452640 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym0 :: TyFun (a6989586621680452640 ~> Bool) (t6989586621680452639 a6989586621680452640 ~> Bool) -> Type) (a6989586621680453174 :: a6989586621680452640 ~> Bool) = (AllSym1 a6989586621680453174 t6989586621680452639 :: TyFun (t6989586621680452639 a6989586621680452640) Bool -> Type)

data AllSym1 (a6989586621680453174 :: (~>) a6989586621680452640 Bool) :: forall t6989586621680452639. (~>) (t6989586621680452639 a6989586621680452640) Bool Source #

Instances
(SFoldable t, SingI d) => SingI (AllSym1 d t :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (AllSym1 d t) Source #

SuppressUnusedWarnings (AllSym1 a6989586621680453174 t6989586621680452639 :: TyFun (t6989586621680452639 a6989586621680452640) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym1 a6989586621680453174 t :: TyFun (t a) Bool -> Type) (a6989586621680453175 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym1 a6989586621680453174 t :: TyFun (t a) Bool -> Type) (a6989586621680453175 :: t a) = All a6989586621680453174 a6989586621680453175

type AllSym2 (a6989586621680453174 :: (~>) a6989586621680452640 Bool) (a6989586621680453175 :: t6989586621680452639 a6989586621680452640) = All a6989586621680453174 a6989586621680453175 Source #

data SumSym0 :: forall a6989586621680452743 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452743) a6989586621680452743 Source #

Instances
(SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (SumSym0 :: TyFun (t6989586621680452723 a6989586621680452743) a6989586621680452743 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (SumSym0 :: TyFun (t a) a -> Type) (arg6989586621680453398 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (SumSym0 :: TyFun (t a) a -> Type) (arg6989586621680453398 :: t a) = Sum arg6989586621680453398

type SumSym1 (arg6989586621680453398 :: t6989586621680452723 a6989586621680452743) = Sum arg6989586621680453398 Source #

data ProductSym0 :: forall a6989586621680452744 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452744) a6989586621680452744 Source #

Instances
(SFoldable t, SNum a) => SingI (ProductSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ProductSym0 :: TyFun (t6989586621680452723 a6989586621680452744) a6989586621680452744 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680453400 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ProductSym0 :: TyFun (t a) a -> Type) (arg6989586621680453400 :: t a) = Product arg6989586621680453400

type ProductSym1 (arg6989586621680453400 :: t6989586621680452723 a6989586621680452744) = Product arg6989586621680453400 Source #

data MaximumSym0 :: forall a6989586621680452741 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452741) a6989586621680452741 Source #

Instances
(SFoldable t, SOrd a) => SingI (MaximumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MaximumSym0 :: TyFun (t6989586621680452723 a6989586621680452741) a6989586621680452741 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680453394 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (arg6989586621680453394 :: t a) = Maximum arg6989586621680453394

type MaximumSym1 (arg6989586621680453394 :: t6989586621680452723 a6989586621680452741) = Maximum arg6989586621680453394 Source #

data MinimumSym0 :: forall a6989586621680452742 t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452742) a6989586621680452742 Source #

Instances
(SFoldable t, SOrd a) => SingI (MinimumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MinimumSym0 :: TyFun (t6989586621680452723 a6989586621680452742) a6989586621680452742 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680453396 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (arg6989586621680453396 :: t a) = Minimum arg6989586621680453396

type MinimumSym1 (arg6989586621680453396 :: t6989586621680452723 a6989586621680452742) = Minimum arg6989586621680453396 Source #

data ScanlSym0 :: forall a6989586621679940120 b6989586621679940119. (~>) ((~>) b6989586621679940119 ((~>) a6989586621679940120 b6989586621679940119)) ((~>) b6989586621679940119 ((~>) [a6989586621679940120] [b6989586621679940119])) Source #

Instances
SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ScanlSym0 :: TyFun (b6989586621679940119 ~> (a6989586621679940120 ~> b6989586621679940119)) (b6989586621679940119 ~> ([a6989586621679940120] ~> [b6989586621679940119])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ScanlSym0 :: TyFun (b6989586621679940119 ~> (a6989586621679940120 ~> b6989586621679940119)) (b6989586621679940119 ~> ([a6989586621679940120] ~> [b6989586621679940119])) -> Type) (a6989586621679950228 :: b6989586621679940119 ~> (a6989586621679940120 ~> b6989586621679940119)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ScanlSym0 :: TyFun (b6989586621679940119 ~> (a6989586621679940120 ~> b6989586621679940119)) (b6989586621679940119 ~> ([a6989586621679940120] ~> [b6989586621679940119])) -> Type) (a6989586621679950228 :: b6989586621679940119 ~> (a6989586621679940120 ~> b6989586621679940119)) = ScanlSym1 a6989586621679950228

data ScanlSym1 (a6989586621679950228 :: (~>) b6989586621679940119 ((~>) a6989586621679940120 b6989586621679940119)) :: (~>) b6989586621679940119 ((~>) [a6989586621679940120] [b6989586621679940119]) Source #

Instances
SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ScanlSym1 d) Source #

SuppressUnusedWarnings (ScanlSym1 a6989586621679950228 :: TyFun b6989586621679940119 ([a6989586621679940120] ~> [b6989586621679940119]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ScanlSym1 a6989586621679950228 :: TyFun b6989586621679940119 ([a6989586621679940120] ~> [b6989586621679940119]) -> Type) (a6989586621679950229 :: b6989586621679940119) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ScanlSym1 a6989586621679950228 :: TyFun b6989586621679940119 ([a6989586621679940120] ~> [b6989586621679940119]) -> Type) (a6989586621679950229 :: b6989586621679940119) = ScanlSym2 a6989586621679950228 a6989586621679950229

data ScanlSym2 (a6989586621679950228 :: (~>) b6989586621679940119 ((~>) a6989586621679940120 b6989586621679940119)) (a6989586621679950229 :: b6989586621679940119) :: (~>) [a6989586621679940120] [b6989586621679940119] Source #

Instances
(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ScanlSym2 d1 d2) Source #

SuppressUnusedWarnings (ScanlSym2 a6989586621679950229 a6989586621679950228 :: TyFun [a6989586621679940120] [b6989586621679940119] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ScanlSym2 a6989586621679950229 a6989586621679950228 :: TyFun [a] [b] -> Type) (a6989586621679950230 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ScanlSym2 a6989586621679950229 a6989586621679950228 :: TyFun [a] [b] -> Type) (a6989586621679950230 :: [a]) = Scanl a6989586621679950229 a6989586621679950228 a6989586621679950230

type ScanlSym3 (a6989586621679950228 :: (~>) b6989586621679940119 ((~>) a6989586621679940120 b6989586621679940119)) (a6989586621679950229 :: b6989586621679940119) (a6989586621679950230 :: [a6989586621679940120]) = Scanl a6989586621679950228 a6989586621679950229 a6989586621679950230 Source #

data Scanl1Sym0 :: forall a6989586621679940118. (~>) ((~>) a6989586621679940118 ((~>) a6989586621679940118 a6989586621679940118)) ((~>) [a6989586621679940118] [a6989586621679940118]) Source #

Instances
SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a6989586621679940118 ~> (a6989586621679940118 ~> a6989586621679940118)) ([a6989586621679940118] ~> [a6989586621679940118]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Scanl1Sym0 :: TyFun (a6989586621679940118 ~> (a6989586621679940118 ~> a6989586621679940118)) ([a6989586621679940118] ~> [a6989586621679940118]) -> Type) (a6989586621679950242 :: a6989586621679940118 ~> (a6989586621679940118 ~> a6989586621679940118)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Scanl1Sym0 :: TyFun (a6989586621679940118 ~> (a6989586621679940118 ~> a6989586621679940118)) ([a6989586621679940118] ~> [a6989586621679940118]) -> Type) (a6989586621679950242 :: a6989586621679940118 ~> (a6989586621679940118 ~> a6989586621679940118)) = Scanl1Sym1 a6989586621679950242

data Scanl1Sym1 (a6989586621679950242 :: (~>) a6989586621679940118 ((~>) a6989586621679940118 a6989586621679940118)) :: (~>) [a6989586621679940118] [a6989586621679940118] Source #

Instances
SingI d => SingI (Scanl1Sym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (Scanl1Sym1 d) Source #

SuppressUnusedWarnings (Scanl1Sym1 a6989586621679950242 :: TyFun [a6989586621679940118] [a6989586621679940118] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Scanl1Sym1 a6989586621679950242 :: TyFun [a] [a] -> Type) (a6989586621679950243 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Scanl1Sym1 a6989586621679950242 :: TyFun [a] [a] -> Type) (a6989586621679950243 :: [a]) = Scanl1 a6989586621679950242 a6989586621679950243

type Scanl1Sym2 (a6989586621679950242 :: (~>) a6989586621679940118 ((~>) a6989586621679940118 a6989586621679940118)) (a6989586621679950243 :: [a6989586621679940118]) = Scanl1 a6989586621679950242 a6989586621679950243 Source #

data ScanrSym0 :: forall a6989586621679940116 b6989586621679940117. (~>) ((~>) a6989586621679940116 ((~>) b6989586621679940117 b6989586621679940117)) ((~>) b6989586621679940117 ((~>) [a6989586621679940116] [b6989586621679940117])) Source #

Instances
SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ScanrSym0 :: TyFun (a6989586621679940116 ~> (b6989586621679940117 ~> b6989586621679940117)) (b6989586621679940117 ~> ([a6989586621679940116] ~> [b6989586621679940117])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ScanrSym0 :: TyFun (a6989586621679940116 ~> (b6989586621679940117 ~> b6989586621679940117)) (b6989586621679940117 ~> ([a6989586621679940116] ~> [b6989586621679940117])) -> Type) (a6989586621679950207 :: a6989586621679940116 ~> (b6989586621679940117 ~> b6989586621679940117)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ScanrSym0 :: TyFun (a6989586621679940116 ~> (b6989586621679940117 ~> b6989586621679940117)) (b6989586621679940117 ~> ([a6989586621679940116] ~> [b6989586621679940117])) -> Type) (a6989586621679950207 :: a6989586621679940116 ~> (b6989586621679940117 ~> b6989586621679940117)) = ScanrSym1 a6989586621679950207

data ScanrSym1 (a6989586621679950207 :: (~>) a6989586621679940116 ((~>) b6989586621679940117 b6989586621679940117)) :: (~>) b6989586621679940117 ((~>) [a6989586621679940116] [b6989586621679940117]) Source #

Instances
SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ScanrSym1 d) Source #

SuppressUnusedWarnings (ScanrSym1 a6989586621679950207 :: TyFun b6989586621679940117 ([a6989586621679940116] ~> [b6989586621679940117]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ScanrSym1 a6989586621679950207 :: TyFun b6989586621679940117 ([a6989586621679940116] ~> [b6989586621679940117]) -> Type) (a6989586621679950208 :: b6989586621679940117) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ScanrSym1 a6989586621679950207 :: TyFun b6989586621679940117 ([a6989586621679940116] ~> [b6989586621679940117]) -> Type) (a6989586621679950208 :: b6989586621679940117) = ScanrSym2 a6989586621679950207 a6989586621679950208

data ScanrSym2 (a6989586621679950207 :: (~>) a6989586621679940116 ((~>) b6989586621679940117 b6989586621679940117)) (a6989586621679950208 :: b6989586621679940117) :: (~>) [a6989586621679940116] [b6989586621679940117] Source #

Instances
(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ScanrSym2 d1 d2) Source #

SuppressUnusedWarnings (ScanrSym2 a6989586621679950208 a6989586621679950207 :: TyFun [a6989586621679940116] [b6989586621679940117] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ScanrSym2 a6989586621679950208 a6989586621679950207 :: TyFun [a] [b] -> Type) (a6989586621679950209 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ScanrSym2 a6989586621679950208 a6989586621679950207 :: TyFun [a] [b] -> Type) (a6989586621679950209 :: [a]) = Scanr a6989586621679950208 a6989586621679950207 a6989586621679950209

type ScanrSym3 (a6989586621679950207 :: (~>) a6989586621679940116 ((~>) b6989586621679940117 b6989586621679940117)) (a6989586621679950208 :: b6989586621679940117) (a6989586621679950209 :: [a6989586621679940116]) = Scanr a6989586621679950207 a6989586621679950208 a6989586621679950209 Source #

data Scanr1Sym0 :: forall a6989586621679940115. (~>) ((~>) a6989586621679940115 ((~>) a6989586621679940115 a6989586621679940115)) ((~>) [a6989586621679940115] [a6989586621679940115]) Source #

Instances
SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a6989586621679940115 ~> (a6989586621679940115 ~> a6989586621679940115)) ([a6989586621679940115] ~> [a6989586621679940115]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Scanr1Sym0 :: TyFun (a6989586621679940115 ~> (a6989586621679940115 ~> a6989586621679940115)) ([a6989586621679940115] ~> [a6989586621679940115]) -> Type) (a6989586621679950183 :: a6989586621679940115 ~> (a6989586621679940115 ~> a6989586621679940115)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Scanr1Sym0 :: TyFun (a6989586621679940115 ~> (a6989586621679940115 ~> a6989586621679940115)) ([a6989586621679940115] ~> [a6989586621679940115]) -> Type) (a6989586621679950183 :: a6989586621679940115 ~> (a6989586621679940115 ~> a6989586621679940115)) = Scanr1Sym1 a6989586621679950183

data Scanr1Sym1 (a6989586621679950183 :: (~>) a6989586621679940115 ((~>) a6989586621679940115 a6989586621679940115)) :: (~>) [a6989586621679940115] [a6989586621679940115] Source #

Instances
SingI d => SingI (Scanr1Sym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (Scanr1Sym1 d) Source #

SuppressUnusedWarnings (Scanr1Sym1 a6989586621679950183 :: TyFun [a6989586621679940115] [a6989586621679940115] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Scanr1Sym1 a6989586621679950183 :: TyFun [a] [a] -> Type) (a6989586621679950184 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Scanr1Sym1 a6989586621679950183 :: TyFun [a] [a] -> Type) (a6989586621679950184 :: [a]) = Scanr1 a6989586621679950183 a6989586621679950184

type Scanr1Sym2 (a6989586621679950183 :: (~>) a6989586621679940115 ((~>) a6989586621679940115 a6989586621679940115)) (a6989586621679950184 :: [a6989586621679940115]) = Scanr1 a6989586621679950183 a6989586621679950184 Source #

data MapAccumLSym0 :: forall a6989586621680756572 b6989586621680756573 c6989586621680756574 t6989586621680756571. (~>) ((~>) a6989586621680756572 ((~>) b6989586621680756573 (a6989586621680756572, c6989586621680756574))) ((~>) a6989586621680756572 ((~>) (t6989586621680756571 b6989586621680756573) (a6989586621680756572, t6989586621680756571 c6989586621680756574))) Source #

Instances
STraversable t => SingI (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (a6989586621680756572 ~> (b6989586621680756573 ~> (a6989586621680756572, c6989586621680756574))) (a6989586621680756572 ~> (t6989586621680756571 b6989586621680756573 ~> (a6989586621680756572, t6989586621680756571 c6989586621680756574))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (MapAccumLSym0 :: TyFun (a6989586621680756572 ~> (b6989586621680756573 ~> (a6989586621680756572, c6989586621680756574))) (a6989586621680756572 ~> (t6989586621680756571 b6989586621680756573 ~> (a6989586621680756572, t6989586621680756571 c6989586621680756574))) -> Type) (a6989586621680757111 :: a6989586621680756572 ~> (b6989586621680756573 ~> (a6989586621680756572, c6989586621680756574))) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (MapAccumLSym0 :: TyFun (a6989586621680756572 ~> (b6989586621680756573 ~> (a6989586621680756572, c6989586621680756574))) (a6989586621680756572 ~> (t6989586621680756571 b6989586621680756573 ~> (a6989586621680756572, t6989586621680756571 c6989586621680756574))) -> Type) (a6989586621680757111 :: a6989586621680756572 ~> (b6989586621680756573 ~> (a6989586621680756572, c6989586621680756574))) = (MapAccumLSym1 a6989586621680757111 t6989586621680756571 :: TyFun a6989586621680756572 (t6989586621680756571 b6989586621680756573 ~> (a6989586621680756572, t6989586621680756571 c6989586621680756574)) -> Type)

data MapAccumLSym1 (a6989586621680757111 :: (~>) a6989586621680756572 ((~>) b6989586621680756573 (a6989586621680756572, c6989586621680756574))) :: forall t6989586621680756571. (~>) a6989586621680756572 ((~>) (t6989586621680756571 b6989586621680756573) (a6989586621680756572, t6989586621680756571 c6989586621680756574)) Source #

Instances
(STraversable t, SingI d) => SingI (MapAccumLSym1 d t :: TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

Methods

sing :: Sing (MapAccumLSym1 d t) Source #

SuppressUnusedWarnings (MapAccumLSym1 a6989586621680757111 t6989586621680756571 :: TyFun a6989586621680756572 (t6989586621680756571 b6989586621680756573 ~> (a6989586621680756572, t6989586621680756571 c6989586621680756574)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (MapAccumLSym1 a6989586621680757111 t6989586621680756571 :: TyFun a6989586621680756572 (t6989586621680756571 b6989586621680756573 ~> (a6989586621680756572, t6989586621680756571 c6989586621680756574)) -> Type) (a6989586621680757112 :: a6989586621680756572) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (MapAccumLSym1 a6989586621680757111 t6989586621680756571 :: TyFun a6989586621680756572 (t6989586621680756571 b6989586621680756573 ~> (a6989586621680756572, t6989586621680756571 c6989586621680756574)) -> Type) (a6989586621680757112 :: a6989586621680756572) = (MapAccumLSym2 a6989586621680757111 a6989586621680757112 t6989586621680756571 :: TyFun (t6989586621680756571 b6989586621680756573) (a6989586621680756572, t6989586621680756571 c6989586621680756574) -> Type)

data MapAccumLSym2 (a6989586621680757111 :: (~>) a6989586621680756572 ((~>) b6989586621680756573 (a6989586621680756572, c6989586621680756574))) (a6989586621680757112 :: a6989586621680756572) :: forall t6989586621680756571. (~>) (t6989586621680756571 b6989586621680756573) (a6989586621680756572, t6989586621680756571 c6989586621680756574) Source #

Instances
(STraversable t, SingI d1, SingI d2) => SingI (MapAccumLSym2 d1 d2 t :: TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

Methods

sing :: Sing (MapAccumLSym2 d1 d2 t) Source #

SuppressUnusedWarnings (MapAccumLSym2 a6989586621680757112 a6989586621680757111 t6989586621680756571 :: TyFun (t6989586621680756571 b6989586621680756573) (a6989586621680756572, t6989586621680756571 c6989586621680756574) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (MapAccumLSym2 a6989586621680757112 a6989586621680757111 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680757113 :: t b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (MapAccumLSym2 a6989586621680757112 a6989586621680757111 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680757113 :: t b) = MapAccumL a6989586621680757112 a6989586621680757111 a6989586621680757113

type MapAccumLSym3 (a6989586621680757111 :: (~>) a6989586621680756572 ((~>) b6989586621680756573 (a6989586621680756572, c6989586621680756574))) (a6989586621680757112 :: a6989586621680756572) (a6989586621680757113 :: t6989586621680756571 b6989586621680756573) = MapAccumL a6989586621680757111 a6989586621680757112 a6989586621680757113 Source #

data MapAccumRSym0 :: forall a6989586621680756568 b6989586621680756569 c6989586621680756570 t6989586621680756567. (~>) ((~>) a6989586621680756568 ((~>) b6989586621680756569 (a6989586621680756568, c6989586621680756570))) ((~>) a6989586621680756568 ((~>) (t6989586621680756567 b6989586621680756569) (a6989586621680756568, t6989586621680756567 c6989586621680756570))) Source #

Instances
STraversable t => SingI (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (a6989586621680756568 ~> (b6989586621680756569 ~> (a6989586621680756568, c6989586621680756570))) (a6989586621680756568 ~> (t6989586621680756567 b6989586621680756569 ~> (a6989586621680756568, t6989586621680756567 c6989586621680756570))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (MapAccumRSym0 :: TyFun (a6989586621680756568 ~> (b6989586621680756569 ~> (a6989586621680756568, c6989586621680756570))) (a6989586621680756568 ~> (t6989586621680756567 b6989586621680756569 ~> (a6989586621680756568, t6989586621680756567 c6989586621680756570))) -> Type) (a6989586621680757094 :: a6989586621680756568 ~> (b6989586621680756569 ~> (a6989586621680756568, c6989586621680756570))) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (MapAccumRSym0 :: TyFun (a6989586621680756568 ~> (b6989586621680756569 ~> (a6989586621680756568, c6989586621680756570))) (a6989586621680756568 ~> (t6989586621680756567 b6989586621680756569 ~> (a6989586621680756568, t6989586621680756567 c6989586621680756570))) -> Type) (a6989586621680757094 :: a6989586621680756568 ~> (b6989586621680756569 ~> (a6989586621680756568, c6989586621680756570))) = (MapAccumRSym1 a6989586621680757094 t6989586621680756567 :: TyFun a6989586621680756568 (t6989586621680756567 b6989586621680756569 ~> (a6989586621680756568, t6989586621680756567 c6989586621680756570)) -> Type)

data MapAccumRSym1 (a6989586621680757094 :: (~>) a6989586621680756568 ((~>) b6989586621680756569 (a6989586621680756568, c6989586621680756570))) :: forall t6989586621680756567. (~>) a6989586621680756568 ((~>) (t6989586621680756567 b6989586621680756569) (a6989586621680756568, t6989586621680756567 c6989586621680756570)) Source #

Instances
(STraversable t, SingI d) => SingI (MapAccumRSym1 d t :: TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

Methods

sing :: Sing (MapAccumRSym1 d t) Source #

SuppressUnusedWarnings (MapAccumRSym1 a6989586621680757094 t6989586621680756567 :: TyFun a6989586621680756568 (t6989586621680756567 b6989586621680756569 ~> (a6989586621680756568, t6989586621680756567 c6989586621680756570)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (MapAccumRSym1 a6989586621680757094 t6989586621680756567 :: TyFun a6989586621680756568 (t6989586621680756567 b6989586621680756569 ~> (a6989586621680756568, t6989586621680756567 c6989586621680756570)) -> Type) (a6989586621680757095 :: a6989586621680756568) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (MapAccumRSym1 a6989586621680757094 t6989586621680756567 :: TyFun a6989586621680756568 (t6989586621680756567 b6989586621680756569 ~> (a6989586621680756568, t6989586621680756567 c6989586621680756570)) -> Type) (a6989586621680757095 :: a6989586621680756568) = (MapAccumRSym2 a6989586621680757094 a6989586621680757095 t6989586621680756567 :: TyFun (t6989586621680756567 b6989586621680756569) (a6989586621680756568, t6989586621680756567 c6989586621680756570) -> Type)

data MapAccumRSym2 (a6989586621680757094 :: (~>) a6989586621680756568 ((~>) b6989586621680756569 (a6989586621680756568, c6989586621680756570))) (a6989586621680757095 :: a6989586621680756568) :: forall t6989586621680756567. (~>) (t6989586621680756567 b6989586621680756569) (a6989586621680756568, t6989586621680756567 c6989586621680756570) Source #

Instances
(STraversable t, SingI d1, SingI d2) => SingI (MapAccumRSym2 d1 d2 t :: TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

Methods

sing :: Sing (MapAccumRSym2 d1 d2 t) Source #

SuppressUnusedWarnings (MapAccumRSym2 a6989586621680757095 a6989586621680757094 t6989586621680756567 :: TyFun (t6989586621680756567 b6989586621680756569) (a6989586621680756568, t6989586621680756567 c6989586621680756570) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (MapAccumRSym2 a6989586621680757095 a6989586621680757094 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680757096 :: t b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (MapAccumRSym2 a6989586621680757095 a6989586621680757094 t :: TyFun (t b) (a, t c) -> Type) (a6989586621680757096 :: t b) = MapAccumR a6989586621680757095 a6989586621680757094 a6989586621680757096

type MapAccumRSym3 (a6989586621680757094 :: (~>) a6989586621680756568 ((~>) b6989586621680756569 (a6989586621680756568, c6989586621680756570))) (a6989586621680757095 :: a6989586621680756568) (a6989586621680757096 :: t6989586621680756567 b6989586621680756569) = MapAccumR a6989586621680757094 a6989586621680757095 a6989586621680757096 Source #

data ReplicateSym0 :: forall a6989586621679940023. (~>) Nat ((~>) a6989586621679940023 [a6989586621679940023]) Source #

Instances
SingI (ReplicateSym0 :: TyFun Nat (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ReplicateSym0 :: TyFun Nat (a6989586621679940023 ~> [a6989586621679940023]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ReplicateSym0 :: TyFun Nat (a6989586621679940023 ~> [a6989586621679940023]) -> Type) (a6989586621679949325 :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ReplicateSym0 :: TyFun Nat (a6989586621679940023 ~> [a6989586621679940023]) -> Type) (a6989586621679949325 :: Nat) = (ReplicateSym1 a6989586621679949325 a6989586621679940023 :: TyFun a6989586621679940023 [a6989586621679940023] -> Type)

data ReplicateSym1 (a6989586621679949325 :: Nat) :: forall a6989586621679940023. (~>) a6989586621679940023 [a6989586621679940023] Source #

Instances
SingI d => SingI (ReplicateSym1 d a :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ReplicateSym1 d a) Source #

SuppressUnusedWarnings (ReplicateSym1 a6989586621679949325 a6989586621679940023 :: TyFun a6989586621679940023 [a6989586621679940023] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ReplicateSym1 a6989586621679949325 a :: TyFun a [a] -> Type) (a6989586621679949326 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ReplicateSym1 a6989586621679949325 a :: TyFun a [a] -> Type) (a6989586621679949326 :: a) = Replicate a6989586621679949325 a6989586621679949326

type ReplicateSym2 (a6989586621679949325 :: Nat) (a6989586621679949326 :: a6989586621679940023) = Replicate a6989586621679949325 a6989586621679949326 Source #

data UnfoldrSym0 :: forall a6989586621679940108 b6989586621679940107. (~>) ((~>) b6989586621679940107 (Maybe (a6989586621679940108, b6989586621679940107))) ((~>) b6989586621679940107 [a6989586621679940108]) Source #

Instances
SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (b6989586621679940107 ~> Maybe (a6989586621679940108, b6989586621679940107)) (b6989586621679940107 ~> [a6989586621679940108]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnfoldrSym0 :: TyFun (b6989586621679940107 ~> Maybe (a6989586621679940108, b6989586621679940107)) (b6989586621679940107 ~> [a6989586621679940108]) -> Type) (a6989586621679950041 :: b6989586621679940107 ~> Maybe (a6989586621679940108, b6989586621679940107)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnfoldrSym0 :: TyFun (b6989586621679940107 ~> Maybe (a6989586621679940108, b6989586621679940107)) (b6989586621679940107 ~> [a6989586621679940108]) -> Type) (a6989586621679950041 :: b6989586621679940107 ~> Maybe (a6989586621679940108, b6989586621679940107)) = UnfoldrSym1 a6989586621679950041

data UnfoldrSym1 (a6989586621679950041 :: (~>) b6989586621679940107 (Maybe (a6989586621679940108, b6989586621679940107))) :: (~>) b6989586621679940107 [a6989586621679940108] Source #

Instances
SingI d => SingI (UnfoldrSym1 d :: TyFun b [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (UnfoldrSym1 d) Source #

SuppressUnusedWarnings (UnfoldrSym1 a6989586621679950041 :: TyFun b6989586621679940107 [a6989586621679940108] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnfoldrSym1 a6989586621679950041 :: TyFun b [a] -> Type) (a6989586621679950042 :: b) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnfoldrSym1 a6989586621679950041 :: TyFun b [a] -> Type) (a6989586621679950042 :: b) = Unfoldr a6989586621679950041 a6989586621679950042

type UnfoldrSym2 (a6989586621679950041 :: (~>) b6989586621679940107 (Maybe (a6989586621679940108, b6989586621679940107))) (a6989586621679950042 :: b6989586621679940107) = Unfoldr a6989586621679950041 a6989586621679950042 Source #

data TakeSym0 :: forall a6989586621679940039. (~>) Nat ((~>) [a6989586621679940039] [a6989586621679940039]) Source #

Instances
SingI (TakeSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TakeSym0 :: TyFun Nat ([a6989586621679940039] ~> [a6989586621679940039]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TakeSym0 :: TyFun Nat ([a6989586621679940039] ~> [a6989586621679940039]) -> Type) (a6989586621679949421 :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TakeSym0 :: TyFun Nat ([a6989586621679940039] ~> [a6989586621679940039]) -> Type) (a6989586621679949421 :: Nat) = (TakeSym1 a6989586621679949421 a6989586621679940039 :: TyFun [a6989586621679940039] [a6989586621679940039] -> Type)

data TakeSym1 (a6989586621679949421 :: Nat) :: forall a6989586621679940039. (~>) [a6989586621679940039] [a6989586621679940039] Source #

Instances
SingI d => SingI (TakeSym1 d a :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (TakeSym1 d a) Source #

SuppressUnusedWarnings (TakeSym1 a6989586621679949421 a6989586621679940039 :: TyFun [a6989586621679940039] [a6989586621679940039] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TakeSym1 a6989586621679949421 a :: TyFun [a] [a] -> Type) (a6989586621679949422 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TakeSym1 a6989586621679949421 a :: TyFun [a] [a] -> Type) (a6989586621679949422 :: [a]) = Take a6989586621679949421 a6989586621679949422

type TakeSym2 (a6989586621679949421 :: Nat) (a6989586621679949422 :: [a6989586621679940039]) = Take a6989586621679949421 a6989586621679949422 Source #

data DropSym0 :: forall a6989586621679940038. (~>) Nat ((~>) [a6989586621679940038] [a6989586621679940038]) Source #

Instances
SingI (DropSym0 :: TyFun Nat ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DropSym0 :: TyFun Nat ([a6989586621679940038] ~> [a6989586621679940038]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropSym0 :: TyFun Nat ([a6989586621679940038] ~> [a6989586621679940038]) -> Type) (a6989586621679949407 :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropSym0 :: TyFun Nat ([a6989586621679940038] ~> [a6989586621679940038]) -> Type) (a6989586621679949407 :: Nat) = (DropSym1 a6989586621679949407 a6989586621679940038 :: TyFun [a6989586621679940038] [a6989586621679940038] -> Type)

data DropSym1 (a6989586621679949407 :: Nat) :: forall a6989586621679940038. (~>) [a6989586621679940038] [a6989586621679940038] Source #

Instances
SingI d => SingI (DropSym1 d a :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (DropSym1 d a) Source #

SuppressUnusedWarnings (DropSym1 a6989586621679949407 a6989586621679940038 :: TyFun [a6989586621679940038] [a6989586621679940038] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropSym1 a6989586621679949407 a :: TyFun [a] [a] -> Type) (a6989586621679949408 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropSym1 a6989586621679949407 a :: TyFun [a] [a] -> Type) (a6989586621679949408 :: [a]) = Drop a6989586621679949407 a6989586621679949408

type DropSym2 (a6989586621679949407 :: Nat) (a6989586621679949408 :: [a6989586621679940038]) = Drop a6989586621679949407 a6989586621679949408 Source #

data SplitAtSym0 :: forall a6989586621679940037. (~>) Nat ((~>) [a6989586621679940037] ([a6989586621679940037], [a6989586621679940037])) Source #

Instances
SingI (SplitAtSym0 :: TyFun Nat ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat ([a6989586621679940037] ~> ([a6989586621679940037], [a6989586621679940037])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SplitAtSym0 :: TyFun Nat ([a6989586621679940037] ~> ([a6989586621679940037], [a6989586621679940037])) -> Type) (a6989586621679949435 :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SplitAtSym0 :: TyFun Nat ([a6989586621679940037] ~> ([a6989586621679940037], [a6989586621679940037])) -> Type) (a6989586621679949435 :: Nat) = (SplitAtSym1 a6989586621679949435 a6989586621679940037 :: TyFun [a6989586621679940037] ([a6989586621679940037], [a6989586621679940037]) -> Type)

data SplitAtSym1 (a6989586621679949435 :: Nat) :: forall a6989586621679940037. (~>) [a6989586621679940037] ([a6989586621679940037], [a6989586621679940037]) Source #

Instances
SingI d => SingI (SplitAtSym1 d a :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (SplitAtSym1 d a) Source #

SuppressUnusedWarnings (SplitAtSym1 a6989586621679949435 a6989586621679940037 :: TyFun [a6989586621679940037] ([a6989586621679940037], [a6989586621679940037]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SplitAtSym1 a6989586621679949435 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621679949436 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SplitAtSym1 a6989586621679949435 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621679949436 :: [a]) = SplitAt a6989586621679949435 a6989586621679949436

type SplitAtSym2 (a6989586621679949435 :: Nat) (a6989586621679949436 :: [a6989586621679940037]) = SplitAt a6989586621679949435 a6989586621679949436 Source #

data TakeWhileSym0 :: forall a6989586621679940044. (~>) ((~>) a6989586621679940044 Bool) ((~>) [a6989586621679940044] [a6989586621679940044]) Source #

Instances
SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a6989586621679940044 ~> Bool) ([a6989586621679940044] ~> [a6989586621679940044]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TakeWhileSym0 :: TyFun (a6989586621679940044 ~> Bool) ([a6989586621679940044] ~> [a6989586621679940044]) -> Type) (a6989586621679949579 :: a6989586621679940044 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TakeWhileSym0 :: TyFun (a6989586621679940044 ~> Bool) ([a6989586621679940044] ~> [a6989586621679940044]) -> Type) (a6989586621679949579 :: a6989586621679940044 ~> Bool) = TakeWhileSym1 a6989586621679949579

data TakeWhileSym1 (a6989586621679949579 :: (~>) a6989586621679940044 Bool) :: (~>) [a6989586621679940044] [a6989586621679940044] Source #

Instances
SingI d => SingI (TakeWhileSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TakeWhileSym1 a6989586621679949579 :: TyFun [a6989586621679940044] [a6989586621679940044] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TakeWhileSym1 a6989586621679949579 :: TyFun [a] [a] -> Type) (a6989586621679949580 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TakeWhileSym1 a6989586621679949579 :: TyFun [a] [a] -> Type) (a6989586621679949580 :: [a]) = TakeWhile a6989586621679949579 a6989586621679949580

type TakeWhileSym2 (a6989586621679949579 :: (~>) a6989586621679940044 Bool) (a6989586621679949580 :: [a6989586621679940044]) = TakeWhile a6989586621679949579 a6989586621679949580 Source #

data DropWhileSym0 :: forall a6989586621679940043. (~>) ((~>) a6989586621679940043 Bool) ((~>) [a6989586621679940043] [a6989586621679940043]) Source #

Instances
SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a6989586621679940043 ~> Bool) ([a6989586621679940043] ~> [a6989586621679940043]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileSym0 :: TyFun (a6989586621679940043 ~> Bool) ([a6989586621679940043] ~> [a6989586621679940043]) -> Type) (a6989586621679949561 :: a6989586621679940043 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileSym0 :: TyFun (a6989586621679940043 ~> Bool) ([a6989586621679940043] ~> [a6989586621679940043]) -> Type) (a6989586621679949561 :: a6989586621679940043 ~> Bool) = DropWhileSym1 a6989586621679949561

data DropWhileSym1 (a6989586621679949561 :: (~>) a6989586621679940043 Bool) :: (~>) [a6989586621679940043] [a6989586621679940043] Source #

Instances
SingI d => SingI (DropWhileSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DropWhileSym1 a6989586621679949561 :: TyFun [a6989586621679940043] [a6989586621679940043] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileSym1 a6989586621679949561 :: TyFun [a] [a] -> Type) (a6989586621679949562 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileSym1 a6989586621679949561 :: TyFun [a] [a] -> Type) (a6989586621679949562 :: [a]) = DropWhile a6989586621679949561 a6989586621679949562

type DropWhileSym2 (a6989586621679949561 :: (~>) a6989586621679940043 Bool) (a6989586621679949562 :: [a6989586621679940043]) = DropWhile a6989586621679949561 a6989586621679949562 Source #

data DropWhileEndSym0 :: forall a6989586621679940042. (~>) ((~>) a6989586621679940042 Bool) ((~>) [a6989586621679940042] [a6989586621679940042]) Source #

Instances
SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a6989586621679940042 ~> Bool) ([a6989586621679940042] ~> [a6989586621679940042]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileEndSym0 :: TyFun (a6989586621679940042 ~> Bool) ([a6989586621679940042] ~> [a6989586621679940042]) -> Type) (a6989586621679950617 :: a6989586621679940042 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileEndSym0 :: TyFun (a6989586621679940042 ~> Bool) ([a6989586621679940042] ~> [a6989586621679940042]) -> Type) (a6989586621679950617 :: a6989586621679940042 ~> Bool) = DropWhileEndSym1 a6989586621679950617

data DropWhileEndSym1 (a6989586621679950617 :: (~>) a6989586621679940042 Bool) :: (~>) [a6989586621679940042] [a6989586621679940042] Source #

Instances
SingI d => SingI (DropWhileEndSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DropWhileEndSym1 a6989586621679950617 :: TyFun [a6989586621679940042] [a6989586621679940042] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileEndSym1 a6989586621679950617 :: TyFun [a] [a] -> Type) (a6989586621679950618 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileEndSym1 a6989586621679950617 :: TyFun [a] [a] -> Type) (a6989586621679950618 :: [a]) = DropWhileEnd a6989586621679950617 a6989586621679950618

type DropWhileEndSym2 (a6989586621679950617 :: (~>) a6989586621679940042 Bool) (a6989586621679950618 :: [a6989586621679940042]) = DropWhileEnd a6989586621679950617 a6989586621679950618 Source #

data SpanSym0 :: forall a6989586621679940041. (~>) ((~>) a6989586621679940041 Bool) ((~>) [a6989586621679940041] ([a6989586621679940041], [a6989586621679940041])) Source #

Instances
SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (SpanSym0 :: TyFun (a6989586621679940041 ~> Bool) ([a6989586621679940041] ~> ([a6989586621679940041], [a6989586621679940041])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SpanSym0 :: TyFun (a6989586621679940041 ~> Bool) ([a6989586621679940041] ~> ([a6989586621679940041], [a6989586621679940041])) -> Type) (a6989586621679949484 :: a6989586621679940041 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SpanSym0 :: TyFun (a6989586621679940041 ~> Bool) ([a6989586621679940041] ~> ([a6989586621679940041], [a6989586621679940041])) -> Type) (a6989586621679949484 :: a6989586621679940041 ~> Bool) = SpanSym1 a6989586621679949484

data SpanSym1 (a6989586621679949484 :: (~>) a6989586621679940041 Bool) :: (~>) [a6989586621679940041] ([a6989586621679940041], [a6989586621679940041]) Source #

Instances
SingI d => SingI (SpanSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (SpanSym1 d) Source #

SuppressUnusedWarnings (SpanSym1 a6989586621679949484 :: TyFun [a6989586621679940041] ([a6989586621679940041], [a6989586621679940041]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SpanSym1 a6989586621679949484 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679949485 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SpanSym1 a6989586621679949484 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679949485 :: [a]) = Span a6989586621679949484 a6989586621679949485

type SpanSym2 (a6989586621679949484 :: (~>) a6989586621679940041 Bool) (a6989586621679949485 :: [a6989586621679940041]) = Span a6989586621679949484 a6989586621679949485 Source #

data BreakSym0 :: forall a6989586621679940040. (~>) ((~>) a6989586621679940040 Bool) ((~>) [a6989586621679940040] ([a6989586621679940040], [a6989586621679940040])) Source #

Instances
SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (BreakSym0 :: TyFun (a6989586621679940040 ~> Bool) ([a6989586621679940040] ~> ([a6989586621679940040], [a6989586621679940040])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (BreakSym0 :: TyFun (a6989586621679940040 ~> Bool) ([a6989586621679940040] ~> ([a6989586621679940040], [a6989586621679940040])) -> Type) (a6989586621679949441 :: a6989586621679940040 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (BreakSym0 :: TyFun (a6989586621679940040 ~> Bool) ([a6989586621679940040] ~> ([a6989586621679940040], [a6989586621679940040])) -> Type) (a6989586621679949441 :: a6989586621679940040 ~> Bool) = BreakSym1 a6989586621679949441

data BreakSym1 (a6989586621679949441 :: (~>) a6989586621679940040 Bool) :: (~>) [a6989586621679940040] ([a6989586621679940040], [a6989586621679940040]) Source #

Instances
SingI d => SingI (BreakSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (BreakSym1 d) Source #

SuppressUnusedWarnings (BreakSym1 a6989586621679949441 :: TyFun [a6989586621679940040] ([a6989586621679940040], [a6989586621679940040]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (BreakSym1 a6989586621679949441 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679949442 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (BreakSym1 a6989586621679949441 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679949442 :: [a]) = Break a6989586621679949441 a6989586621679949442

type BreakSym2 (a6989586621679949441 :: (~>) a6989586621679940040 Bool) (a6989586621679949442 :: [a6989586621679940040]) = Break a6989586621679949441 a6989586621679949442 Source #

data StripPrefixSym0 :: forall a6989586621680066266. (~>) [a6989586621680066266] ((~>) [a6989586621680066266] (Maybe [a6989586621680066266])) Source #

Instances
SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a6989586621680066266] ([a6989586621680066266] ~> Maybe [a6989586621680066266]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (StripPrefixSym0 :: TyFun [a6989586621680066266] ([a6989586621680066266] ~> Maybe [a6989586621680066266]) -> Type) (a6989586621680078976 :: [a6989586621680066266]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (StripPrefixSym0 :: TyFun [a6989586621680066266] ([a6989586621680066266] ~> Maybe [a6989586621680066266]) -> Type) (a6989586621680078976 :: [a6989586621680066266]) = StripPrefixSym1 a6989586621680078976

data StripPrefixSym1 (a6989586621680078976 :: [a6989586621680066266]) :: (~>) [a6989586621680066266] (Maybe [a6989586621680066266]) Source #

Instances
SuppressUnusedWarnings (StripPrefixSym1 a6989586621680078976 :: TyFun [a6989586621680066266] (Maybe [a6989586621680066266]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (StripPrefixSym1 a6989586621680078976 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680078977 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (StripPrefixSym1 a6989586621680078976 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680078977 :: [a]) = StripPrefix a6989586621680078976 a6989586621680078977

type StripPrefixSym2 (a6989586621680078976 :: [a6989586621680066266]) (a6989586621680078977 :: [a6989586621680066266]) = StripPrefix a6989586621680078976 a6989586621680078977 Source #

data GroupSym0 :: forall a6989586621679940036. (~>) [a6989586621679940036] [[a6989586621679940036]] Source #

Instances
SEq a => SingI (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621679940036] [[a6989586621679940036]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679949558 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679949558 :: [a]) = Group a6989586621679949558

type GroupSym1 (a6989586621679949558 :: [a6989586621679940036]) = Group a6989586621679949558 Source #

data InitsSym0 :: forall a6989586621679940106. (~>) [a6989586621679940106] [[a6989586621679940106]] Source #

Instances
SingI (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621679940106] [[a6989586621679940106]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679950033 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679950033 :: [a]) = Inits a6989586621679950033

type InitsSym1 (a6989586621679950033 :: [a6989586621679940106]) = Inits a6989586621679950033 Source #

data TailsSym0 :: forall a6989586621679940105. (~>) [a6989586621679940105] [[a6989586621679940105]] Source #

Instances
SingI (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621679940105] [[a6989586621679940105]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679950026 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679950026 :: [a]) = Tails a6989586621679950026

type TailsSym1 (a6989586621679950026 :: [a6989586621679940105]) = Tails a6989586621679950026 Source #

data IsPrefixOfSym0 :: forall a6989586621679940104. (~>) [a6989586621679940104] ((~>) [a6989586621679940104] Bool) Source #

Instances
SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679940104] ([a6989586621679940104] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679940104] ([a6989586621679940104] ~> Bool) -> Type) (a6989586621679950018 :: [a6989586621679940104]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679940104] ([a6989586621679940104] ~> Bool) -> Type) (a6989586621679950018 :: [a6989586621679940104]) = IsPrefixOfSym1 a6989586621679950018

data IsPrefixOfSym1 (a6989586621679950018 :: [a6989586621679940104]) :: (~>) [a6989586621679940104] Bool Source #

Instances
(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679950018 :: TyFun [a6989586621679940104] Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsPrefixOfSym1 a6989586621679950018 :: TyFun [a] Bool -> Type) (a6989586621679950019 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsPrefixOfSym1 a6989586621679950018 :: TyFun [a] Bool -> Type) (a6989586621679950019 :: [a]) = IsPrefixOf a6989586621679950018 a6989586621679950019

type IsPrefixOfSym2 (a6989586621679950018 :: [a6989586621679940104]) (a6989586621679950019 :: [a6989586621679940104]) = IsPrefixOf a6989586621679950018 a6989586621679950019 Source #

data IsSuffixOfSym0 :: forall a6989586621679940103. (~>) [a6989586621679940103] ((~>) [a6989586621679940103] Bool) Source #

Instances
SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679940103] ([a6989586621679940103] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679940103] ([a6989586621679940103] ~> Bool) -> Type) (a6989586621679950609 :: [a6989586621679940103]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679940103] ([a6989586621679940103] ~> Bool) -> Type) (a6989586621679950609 :: [a6989586621679940103]) = IsSuffixOfSym1 a6989586621679950609

data IsSuffixOfSym1 (a6989586621679950609 :: [a6989586621679940103]) :: (~>) [a6989586621679940103] Bool Source #

Instances
(SEq a, SingI d) => SingI (IsSuffixOfSym1 d :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679950609 :: TyFun [a6989586621679940103] Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsSuffixOfSym1 a6989586621679950609 :: TyFun [a] Bool -> Type) (a6989586621679950610 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsSuffixOfSym1 a6989586621679950609 :: TyFun [a] Bool -> Type) (a6989586621679950610 :: [a]) = IsSuffixOf a6989586621679950609 a6989586621679950610

type IsSuffixOfSym2 (a6989586621679950609 :: [a6989586621679940103]) (a6989586621679950610 :: [a6989586621679940103]) = IsSuffixOf a6989586621679950609 a6989586621679950610 Source #

data IsInfixOfSym0 :: forall a6989586621679940102. (~>) [a6989586621679940102] ((~>) [a6989586621679940102] Bool) Source #

Instances
SEq a => SingI (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a6989586621679940102] ([a6989586621679940102] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsInfixOfSym0 :: TyFun [a6989586621679940102] ([a6989586621679940102] ~> Bool) -> Type) (a6989586621679950256 :: [a6989586621679940102]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsInfixOfSym0 :: TyFun [a6989586621679940102] ([a6989586621679940102] ~> Bool) -> Type) (a6989586621679950256 :: [a6989586621679940102]) = IsInfixOfSym1 a6989586621679950256

data IsInfixOfSym1 (a6989586621679950256 :: [a6989586621679940102]) :: (~>) [a6989586621679940102] Bool Source #

Instances
(SEq a, SingI d) => SingI (IsInfixOfSym1 d :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679950256 :: TyFun [a6989586621679940102] Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsInfixOfSym1 a6989586621679950256 :: TyFun [a] Bool -> Type) (a6989586621679950257 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsInfixOfSym1 a6989586621679950256 :: TyFun [a] Bool -> Type) (a6989586621679950257 :: [a]) = IsInfixOf a6989586621679950256 a6989586621679950257

type IsInfixOfSym2 (a6989586621679950256 :: [a6989586621679940102]) (a6989586621679950257 :: [a6989586621679940102]) = IsInfixOf a6989586621679950256 a6989586621679950257 Source #

data ElemSym0 :: forall a6989586621680452740 t6989586621680452723. (~>) a6989586621680452740 ((~>) (t6989586621680452723 a6989586621680452740) Bool) Source #

Instances
(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621680452740 (t6989586621680452723 a6989586621680452740 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym0 :: TyFun a6989586621680452740 (t6989586621680452723 a6989586621680452740 ~> Bool) -> Type) (arg6989586621680453390 :: a6989586621680452740) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym0 :: TyFun a6989586621680452740 (t6989586621680452723 a6989586621680452740 ~> Bool) -> Type) (arg6989586621680453390 :: a6989586621680452740) = (ElemSym1 arg6989586621680453390 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452740) Bool -> Type)

data ElemSym1 (arg6989586621680453390 :: a6989586621680452740) :: forall t6989586621680452723. (~>) (t6989586621680452723 a6989586621680452740) Bool Source #

Instances
(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d t :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (ElemSym1 d t) Source #

SuppressUnusedWarnings (ElemSym1 arg6989586621680453390 t6989586621680452723 :: TyFun (t6989586621680452723 a6989586621680452740) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym1 arg6989586621680453390 t :: TyFun (t a) Bool -> Type) (arg6989586621680453391 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym1 arg6989586621680453390 t :: TyFun (t a) Bool -> Type) (arg6989586621680453391 :: t a) = Elem arg6989586621680453390 arg6989586621680453391

type ElemSym2 (arg6989586621680453390 :: a6989586621680452740) (arg6989586621680453391 :: t6989586621680452723 a6989586621680452740) = Elem arg6989586621680453390 arg6989586621680453391 Source #

data NotElemSym0 :: forall a6989586621680452634 t6989586621680452633. (~>) a6989586621680452634 ((~>) (t6989586621680452633 a6989586621680452634) Bool) Source #

Instances
(SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621680452634 (t6989586621680452633 a6989586621680452634 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym0 :: TyFun a6989586621680452634 (t6989586621680452633 a6989586621680452634 ~> Bool) -> Type) (a6989586621680453116 :: a6989586621680452634) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym0 :: TyFun a6989586621680452634 (t6989586621680452633 a6989586621680452634 ~> Bool) -> Type) (a6989586621680453116 :: a6989586621680452634) = (NotElemSym1 a6989586621680453116 t6989586621680452633 :: TyFun (t6989586621680452633 a6989586621680452634) Bool -> Type)

data NotElemSym1 (a6989586621680453116 :: a6989586621680452634) :: forall t6989586621680452633. (~>) (t6989586621680452633 a6989586621680452634) Bool Source #

Instances
(SFoldable t, SEq a, SingI d) => SingI (NotElemSym1 d t :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (NotElemSym1 d t) Source #

SuppressUnusedWarnings (NotElemSym1 a6989586621680453116 t6989586621680452633 :: TyFun (t6989586621680452633 a6989586621680452634) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym1 a6989586621680453116 t :: TyFun (t a) Bool -> Type) (a6989586621680453117 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym1 a6989586621680453116 t :: TyFun (t a) Bool -> Type) (a6989586621680453117 :: t a) = NotElem a6989586621680453116 a6989586621680453117

type NotElemSym2 (a6989586621680453116 :: a6989586621680452634) (a6989586621680453117 :: t6989586621680452633 a6989586621680452634) = NotElem a6989586621680453116 a6989586621680453117 Source #

data LookupSym0 :: forall a6989586621679940029 b6989586621679940030. (~>) a6989586621679940029 ((~>) [(a6989586621679940029, b6989586621679940030)] (Maybe b6989586621679940030)) Source #

Instances
SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679940029 ([(a6989586621679940029, b6989586621679940030)] ~> Maybe b6989586621679940030) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LookupSym0 :: TyFun a6989586621679940029 ([(a6989586621679940029, b6989586621679940030)] ~> Maybe b6989586621679940030) -> Type) (a6989586621679949390 :: a6989586621679940029) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LookupSym0 :: TyFun a6989586621679940029 ([(a6989586621679940029, b6989586621679940030)] ~> Maybe b6989586621679940030) -> Type) (a6989586621679949390 :: a6989586621679940029) = (LookupSym1 a6989586621679949390 b6989586621679940030 :: TyFun [(a6989586621679940029, b6989586621679940030)] (Maybe b6989586621679940030) -> Type)

data LookupSym1 (a6989586621679949390 :: a6989586621679940029) :: forall b6989586621679940030. (~>) [(a6989586621679940029, b6989586621679940030)] (Maybe b6989586621679940030) Source #

Instances
(SEq a, SingI d) => SingI (LookupSym1 d b :: TyFun [(a, b)] (Maybe b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (LookupSym1 d b) Source #

SuppressUnusedWarnings (LookupSym1 a6989586621679949390 b6989586621679940030 :: TyFun [(a6989586621679940029, b6989586621679940030)] (Maybe b6989586621679940030) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LookupSym1 a6989586621679949390 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679949391 :: [(a, b)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LookupSym1 a6989586621679949390 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679949391 :: [(a, b)]) = Lookup a6989586621679949390 a6989586621679949391

type LookupSym2 (a6989586621679949390 :: a6989586621679940029) (a6989586621679949391 :: [(a6989586621679940029, b6989586621679940030)]) = Lookup a6989586621679949390 a6989586621679949391 Source #

data FindSym0 :: forall a6989586621680452632 t6989586621680452631. (~>) ((~>) a6989586621680452632 Bool) ((~>) (t6989586621680452631 a6989586621680452632) (Maybe a6989586621680452632)) Source #

Instances
SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680452632 ~> Bool) (t6989586621680452631 a6989586621680452632 ~> Maybe a6989586621680452632) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a6989586621680452632 ~> Bool) (t6989586621680452631 a6989586621680452632 ~> Maybe a6989586621680452632) -> Type) (a6989586621680453089 :: a6989586621680452632 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a6989586621680452632 ~> Bool) (t6989586621680452631 a6989586621680452632 ~> Maybe a6989586621680452632) -> Type) (a6989586621680453089 :: a6989586621680452632 ~> Bool) = (FindSym1 a6989586621680453089 t6989586621680452631 :: TyFun (t6989586621680452631 a6989586621680452632) (Maybe a6989586621680452632) -> Type)

data FindSym1 (a6989586621680453089 :: (~>) a6989586621680452632 Bool) :: forall t6989586621680452631. (~>) (t6989586621680452631 a6989586621680452632) (Maybe a6989586621680452632) Source #

Instances
(SFoldable t, SingI d) => SingI (FindSym1 d t :: TyFun (t a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FindSym1 d t) Source #

SuppressUnusedWarnings (FindSym1 a6989586621680453089 t6989586621680452631 :: TyFun (t6989586621680452631 a6989586621680452632) (Maybe a6989586621680452632) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym1 a6989586621680453089 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680453090 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym1 a6989586621680453089 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680453090 :: t a) = Find a6989586621680453089 a6989586621680453090

type FindSym2 (a6989586621680453089 :: (~>) a6989586621680452632 Bool) (a6989586621680453090 :: t6989586621680452631 a6989586621680452632) = Find a6989586621680453089 a6989586621680453090 Source #

data FilterSym0 :: forall a6989586621679940052. (~>) ((~>) a6989586621679940052 Bool) ((~>) [a6989586621679940052] [a6989586621679940052]) Source #

Instances
SingI (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FilterSym0 :: TyFun (a6989586621679940052 ~> Bool) ([a6989586621679940052] ~> [a6989586621679940052]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FilterSym0 :: TyFun (a6989586621679940052 ~> Bool) ([a6989586621679940052] ~> [a6989586621679940052]) -> Type) (a6989586621679949593 :: a6989586621679940052 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FilterSym0 :: TyFun (a6989586621679940052 ~> Bool) ([a6989586621679940052] ~> [a6989586621679940052]) -> Type) (a6989586621679949593 :: a6989586621679940052 ~> Bool) = FilterSym1 a6989586621679949593

data FilterSym1 (a6989586621679949593 :: (~>) a6989586621679940052 Bool) :: (~>) [a6989586621679940052] [a6989586621679940052] Source #

Instances
SingI d => SingI (FilterSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (FilterSym1 d) Source #

SuppressUnusedWarnings (FilterSym1 a6989586621679949593 :: TyFun [a6989586621679940052] [a6989586621679940052] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FilterSym1 a6989586621679949593 :: TyFun [a] [a] -> Type) (a6989586621679949594 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FilterSym1 a6989586621679949593 :: TyFun [a] [a] -> Type) (a6989586621679949594 :: [a]) = Filter a6989586621679949593 a6989586621679949594

type FilterSym2 (a6989586621679949593 :: (~>) a6989586621679940052 Bool) (a6989586621679949594 :: [a6989586621679940052]) = Filter a6989586621679949593 a6989586621679949594 Source #

data PartitionSym0 :: forall a6989586621679940028. (~>) ((~>) a6989586621679940028 Bool) ((~>) [a6989586621679940028] ([a6989586621679940028], [a6989586621679940028])) Source #

Instances
SingI (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (PartitionSym0 :: TyFun (a6989586621679940028 ~> Bool) ([a6989586621679940028] ~> ([a6989586621679940028], [a6989586621679940028])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (PartitionSym0 :: TyFun (a6989586621679940028 ~> Bool) ([a6989586621679940028] ~> ([a6989586621679940028], [a6989586621679940028])) -> Type) (a6989586621679949384 :: a6989586621679940028 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (PartitionSym0 :: TyFun (a6989586621679940028 ~> Bool) ([a6989586621679940028] ~> ([a6989586621679940028], [a6989586621679940028])) -> Type) (a6989586621679949384 :: a6989586621679940028 ~> Bool) = PartitionSym1 a6989586621679949384

data PartitionSym1 (a6989586621679949384 :: (~>) a6989586621679940028 Bool) :: (~>) [a6989586621679940028] ([a6989586621679940028], [a6989586621679940028]) Source #

Instances
SingI d => SingI (PartitionSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (PartitionSym1 a6989586621679949384 :: TyFun [a6989586621679940028] ([a6989586621679940028], [a6989586621679940028]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (PartitionSym1 a6989586621679949384 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679949385 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (PartitionSym1 a6989586621679949384 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679949385 :: [a]) = Partition a6989586621679949384 a6989586621679949385

type PartitionSym2 (a6989586621679949384 :: (~>) a6989586621679940028 Bool) (a6989586621679949385 :: [a6989586621679940028]) = Partition a6989586621679949384 a6989586621679949385 Source #

data (!!@#@$) :: forall a6989586621679940021. (~>) [a6989586621679940021] ((~>) Nat a6989586621679940021) infixl 9 Source #

Instances
SingI ((!!@#@$) :: TyFun [a] (Nat ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings ((!!@#@$) :: TyFun [a6989586621679940021] (Nat ~> a6989586621679940021) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply ((!!@#@$) :: TyFun [a6989586621679940021] (Nat ~> a6989586621679940021) -> Type) (a6989586621679949311 :: [a6989586621679940021]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply ((!!@#@$) :: TyFun [a6989586621679940021] (Nat ~> a6989586621679940021) -> Type) (a6989586621679949311 :: [a6989586621679940021]) = (!!@#@$$) a6989586621679949311

data (!!@#@$$) (a6989586621679949311 :: [a6989586621679940021]) :: (~>) Nat a6989586621679940021 infixl 9 Source #

Instances
SingI d => SingI ((!!@#@$$) d :: TyFun Nat a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing ((!!@#@$$) d) Source #

SuppressUnusedWarnings ((!!@#@$$) a6989586621679949311 :: TyFun Nat a6989586621679940021 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply ((!!@#@$$) a6989586621679949311 :: TyFun Nat a -> Type) (a6989586621679949312 :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply ((!!@#@$$) a6989586621679949311 :: TyFun Nat a -> Type) (a6989586621679949312 :: Nat) = a6989586621679949311 !! a6989586621679949312

type (!!@#@$$$) (a6989586621679949311 :: [a6989586621679940021]) (a6989586621679949312 :: Nat) = (!!) a6989586621679949311 a6989586621679949312 Source #

data ElemIndexSym0 :: forall a6989586621679940050. (~>) a6989586621679940050 ((~>) [a6989586621679940050] (Maybe Nat)) Source #

Instances
SEq a => SingI (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679940050 ([a6989586621679940050] ~> Maybe Nat) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndexSym0 :: TyFun a6989586621679940050 ([a6989586621679940050] ~> Maybe Nat) -> Type) (a6989586621679949976 :: a6989586621679940050) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndexSym0 :: TyFun a6989586621679940050 ([a6989586621679940050] ~> Maybe Nat) -> Type) (a6989586621679949976 :: a6989586621679940050) = ElemIndexSym1 a6989586621679949976

data ElemIndexSym1 (a6989586621679949976 :: a6989586621679940050) :: (~>) [a6989586621679940050] (Maybe Nat) Source #

Instances
(SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemIndexSym1 a6989586621679949976 :: TyFun [a6989586621679940050] (Maybe Nat) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndexSym1 a6989586621679949976 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949977 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndexSym1 a6989586621679949976 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949977 :: [a]) = ElemIndex a6989586621679949976 a6989586621679949977

type ElemIndexSym2 (a6989586621679949976 :: a6989586621679940050) (a6989586621679949977 :: [a6989586621679940050]) = ElemIndex a6989586621679949976 a6989586621679949977 Source #

data ElemIndicesSym0 :: forall a6989586621679940049. (~>) a6989586621679940049 ((~>) [a6989586621679940049] [Nat]) Source #

Instances
SEq a => SingI (ElemIndicesSym0 :: TyFun a ([a] ~> [Nat]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a6989586621679940049 ([a6989586621679940049] ~> [Nat]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndicesSym0 :: TyFun a6989586621679940049 ([a6989586621679940049] ~> [Nat]) -> Type) (a6989586621679949960 :: a6989586621679940049) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndicesSym0 :: TyFun a6989586621679940049 ([a6989586621679940049] ~> [Nat]) -> Type) (a6989586621679949960 :: a6989586621679940049) = ElemIndicesSym1 a6989586621679949960

data ElemIndicesSym1 (a6989586621679949960 :: a6989586621679940049) :: (~>) [a6989586621679940049] [Nat] Source #

Instances
(SEq a, SingI d) => SingI (ElemIndicesSym1 d :: TyFun [a] [Nat] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemIndicesSym1 a6989586621679949960 :: TyFun [a6989586621679940049] [Nat] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndicesSym1 a6989586621679949960 :: TyFun [a] [Nat] -> Type) (a6989586621679949961 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndicesSym1 a6989586621679949960 :: TyFun [a] [Nat] -> Type) (a6989586621679949961 :: [a]) = ElemIndices a6989586621679949960 a6989586621679949961

type ElemIndicesSym2 (a6989586621679949960 :: a6989586621679940049) (a6989586621679949961 :: [a6989586621679940049]) = ElemIndices a6989586621679949960 a6989586621679949961 Source #

data FindIndexSym0 :: forall a6989586621679940048. (~>) ((~>) a6989586621679940048 Bool) ((~>) [a6989586621679940048] (Maybe Nat)) Source #

Instances
SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a6989586621679940048 ~> Bool) ([a6989586621679940048] ~> Maybe Nat) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym0 :: TyFun (a6989586621679940048 ~> Bool) ([a6989586621679940048] ~> Maybe Nat) -> Type) (a6989586621679949968 :: a6989586621679940048 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym0 :: TyFun (a6989586621679940048 ~> Bool) ([a6989586621679940048] ~> Maybe Nat) -> Type) (a6989586621679949968 :: a6989586621679940048 ~> Bool) = FindIndexSym1 a6989586621679949968

data FindIndexSym1 (a6989586621679949968 :: (~>) a6989586621679940048 Bool) :: (~>) [a6989586621679940048] (Maybe Nat) Source #

Instances
SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindIndexSym1 a6989586621679949968 :: TyFun [a6989586621679940048] (Maybe Nat) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym1 a6989586621679949968 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949969 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym1 a6989586621679949968 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949969 :: [a]) = FindIndex a6989586621679949968 a6989586621679949969

type FindIndexSym2 (a6989586621679949968 :: (~>) a6989586621679940048 Bool) (a6989586621679949969 :: [a6989586621679940048]) = FindIndex a6989586621679949968 a6989586621679949969 Source #

data FindIndicesSym0 :: forall a6989586621679940047. (~>) ((~>) a6989586621679940047 Bool) ((~>) [a6989586621679940047] [Nat]) Source #

Instances
SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (a6989586621679940047 ~> Bool) ([a6989586621679940047] ~> [Nat]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndicesSym0 :: TyFun (a6989586621679940047 ~> Bool) ([a6989586621679940047] ~> [Nat]) -> Type) (a6989586621679949934 :: a6989586621679940047 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndicesSym0 :: TyFun (a6989586621679940047 ~> Bool) ([a6989586621679940047] ~> [Nat]) -> Type) (a6989586621679949934 :: a6989586621679940047 ~> Bool) = FindIndicesSym1 a6989586621679949934

data FindIndicesSym1 (a6989586621679949934 :: (~>) a6989586621679940047 Bool) :: (~>) [a6989586621679940047] [Nat] Source #

Instances
SingI d => SingI (FindIndicesSym1 d :: TyFun [a] [Nat] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindIndicesSym1 a6989586621679949934 :: TyFun [a6989586621679940047] [Nat] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndicesSym1 a6989586621679949934 :: TyFun [a] [Nat] -> Type) (a6989586621679949935 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndicesSym1 a6989586621679949934 :: TyFun [a] [Nat] -> Type) (a6989586621679949935 :: [a]) = FindIndices a6989586621679949934 a6989586621679949935

type FindIndicesSym2 (a6989586621679949934 :: (~>) a6989586621679940047 Bool) (a6989586621679949935 :: [a6989586621679940047]) = FindIndices a6989586621679949934 a6989586621679949935 Source #

data ZipSym0 :: forall a6989586621679940098 b6989586621679940099. (~>) [a6989586621679940098] ((~>) [b6989586621679940099] [(a6989586621679940098, b6989586621679940099)]) Source #

Instances
SingI (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ZipSym0 :: TyFun [a6989586621679940098] ([b6989586621679940099] ~> [(a6989586621679940098, b6989586621679940099)]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipSym0 :: TyFun [a6989586621679940098] ([b6989586621679940099] ~> [(a6989586621679940098, b6989586621679940099)]) -> Type) (a6989586621679949926 :: [a6989586621679940098]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipSym0 :: TyFun [a6989586621679940098] ([b6989586621679940099] ~> [(a6989586621679940098, b6989586621679940099)]) -> Type) (a6989586621679949926 :: [a6989586621679940098]) = (ZipSym1 a6989586621679949926 b6989586621679940099 :: TyFun [b6989586621679940099] [(a6989586621679940098, b6989586621679940099)] -> Type)

data ZipSym1 (a6989586621679949926 :: [a6989586621679940098]) :: forall b6989586621679940099. (~>) [b6989586621679940099] [(a6989586621679940098, b6989586621679940099)] Source #

Instances
SingI d => SingI (ZipSym1 d b :: TyFun [b] [(a, b)] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ZipSym1 d b) Source #

SuppressUnusedWarnings (ZipSym1 a6989586621679949926 b6989586621679940099 :: TyFun [b6989586621679940099] [(a6989586621679940098, b6989586621679940099)] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipSym1 a6989586621679949926 b :: TyFun [b] [(a, b)] -> Type) (a6989586621679949927 :: [b]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipSym1 a6989586621679949926 b :: TyFun [b] [(a, b)] -> Type) (a6989586621679949927 :: [b]) = Zip a6989586621679949926 a6989586621679949927

type ZipSym2 (a6989586621679949926 :: [a6989586621679940098]) (a6989586621679949927 :: [b6989586621679940099]) = Zip a6989586621679949926 a6989586621679949927 Source #

data Zip3Sym0 :: forall a6989586621679940095 b6989586621679940096 c6989586621679940097. (~>) [a6989586621679940095] ((~>) [b6989586621679940096] ((~>) [c6989586621679940097] [(a6989586621679940095, b6989586621679940096, c6989586621679940097)])) Source #

Instances
SingI (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a6989586621679940095] ([b6989586621679940096] ~> ([c6989586621679940097] ~> [(a6989586621679940095, b6989586621679940096, c6989586621679940097)])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip3Sym0 :: TyFun [a6989586621679940095] ([b6989586621679940096] ~> ([c6989586621679940097] ~> [(a6989586621679940095, b6989586621679940096, c6989586621679940097)])) -> Type) (a6989586621679949914 :: [a6989586621679940095]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip3Sym0 :: TyFun [a6989586621679940095] ([b6989586621679940096] ~> ([c6989586621679940097] ~> [(a6989586621679940095, b6989586621679940096, c6989586621679940097)])) -> Type) (a6989586621679949914 :: [a6989586621679940095]) = (Zip3Sym1 a6989586621679949914 b6989586621679940096 c6989586621679940097 :: TyFun [b6989586621679940096] ([c6989586621679940097] ~> [(a6989586621679940095, b6989586621679940096, c6989586621679940097)]) -> Type)

data Zip3Sym1 (a6989586621679949914 :: [a6989586621679940095]) :: forall b6989586621679940096 c6989586621679940097. (~>) [b6989586621679940096] ((~>) [c6989586621679940097] [(a6989586621679940095, b6989586621679940096, c6989586621679940097)]) Source #

Instances
SingI d => SingI (Zip3Sym1 d b c :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (Zip3Sym1 d b c) Source #

SuppressUnusedWarnings (Zip3Sym1 a6989586621679949914 b6989586621679940096 c6989586621679940097 :: TyFun [b6989586621679940096] ([c6989586621679940097] ~> [(a6989586621679940095, b6989586621679940096, c6989586621679940097)]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip3Sym1 a6989586621679949914 b6989586621679940096 c6989586621679940097 :: TyFun [b6989586621679940096] ([c6989586621679940097] ~> [(a6989586621679940095, b6989586621679940096, c6989586621679940097)]) -> Type) (a6989586621679949915 :: [b6989586621679940096]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip3Sym1 a6989586621679949914 b6989586621679940096 c6989586621679940097 :: TyFun [b6989586621679940096] ([c6989586621679940097] ~> [(a6989586621679940095, b6989586621679940096, c6989586621679940097)]) -> Type) (a6989586621679949915 :: [b6989586621679940096]) = (Zip3Sym2 a6989586621679949914 a6989586621679949915 c6989586621679940097 :: TyFun [c6989586621679940097] [(a6989586621679940095, b6989586621679940096, c6989586621679940097)] -> Type)

data Zip3Sym2 (a6989586621679949914 :: [a6989586621679940095]) (a6989586621679949915 :: [b6989586621679940096]) :: forall c6989586621679940097. (~>) [c6989586621679940097] [(a6989586621679940095, b6989586621679940096, c6989586621679940097)] Source #

Instances
(SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 c :: TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (Zip3Sym2 d1 d2 c) Source #

SuppressUnusedWarnings (Zip3Sym2 a6989586621679949915 a6989586621679949914 c6989586621679940097 :: TyFun [c6989586621679940097] [(a6989586621679940095, b6989586621679940096, c6989586621679940097)] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip3Sym2 a6989586621679949915 a6989586621679949914 c :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679949916 :: [c]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip3Sym2 a6989586621679949915 a6989586621679949914 c :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679949916 :: [c]) = Zip3 a6989586621679949915 a6989586621679949914 a6989586621679949916

type Zip3Sym3 (a6989586621679949914 :: [a6989586621679940095]) (a6989586621679949915 :: [b6989586621679940096]) (a6989586621679949916 :: [c6989586621679940097]) = Zip3 a6989586621679949914 a6989586621679949915 a6989586621679949916 Source #

data Zip4Sym0 :: forall a6989586621680066262 b6989586621680066263 c6989586621680066264 d6989586621680066265. (~>) [a6989586621680066262] ((~>) [b6989586621680066263] ((~>) [c6989586621680066264] ((~>) [d6989586621680066265] [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)]))) Source #

Instances
SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a6989586621680066262] ([b6989586621680066263] ~> ([c6989586621680066264] ~> ([d6989586621680066265] ~> [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)]))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip4Sym0 :: TyFun [a6989586621680066262] ([b6989586621680066263] ~> ([c6989586621680066264] ~> ([d6989586621680066265] ~> [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)]))) -> Type) (a6989586621680078964 :: [a6989586621680066262]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip4Sym0 :: TyFun [a6989586621680066262] ([b6989586621680066263] ~> ([c6989586621680066264] ~> ([d6989586621680066265] ~> [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)]))) -> Type) (a6989586621680078964 :: [a6989586621680066262]) = (Zip4Sym1 a6989586621680078964 b6989586621680066263 c6989586621680066264 d6989586621680066265 :: TyFun [b6989586621680066263] ([c6989586621680066264] ~> ([d6989586621680066265] ~> [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)])) -> Type)

data Zip4Sym1 (a6989586621680078964 :: [a6989586621680066262]) :: forall b6989586621680066263 c6989586621680066264 d6989586621680066265. (~>) [b6989586621680066263] ((~>) [c6989586621680066264] ((~>) [d6989586621680066265] [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)])) Source #

Instances
SuppressUnusedWarnings (Zip4Sym1 a6989586621680078964 b6989586621680066263 c6989586621680066264 d6989586621680066265 :: TyFun [b6989586621680066263] ([c6989586621680066264] ~> ([d6989586621680066265] ~> [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip4Sym1 a6989586621680078964 b6989586621680066263 c6989586621680066264 d6989586621680066265 :: TyFun [b6989586621680066263] ([c6989586621680066264] ~> ([d6989586621680066265] ~> [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)])) -> Type) (a6989586621680078965 :: [b6989586621680066263]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip4Sym1 a6989586621680078964 b6989586621680066263 c6989586621680066264 d6989586621680066265 :: TyFun [b6989586621680066263] ([c6989586621680066264] ~> ([d6989586621680066265] ~> [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)])) -> Type) (a6989586621680078965 :: [b6989586621680066263]) = (Zip4Sym2 a6989586621680078964 a6989586621680078965 c6989586621680066264 d6989586621680066265 :: TyFun [c6989586621680066264] ([d6989586621680066265] ~> [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)]) -> Type)

data Zip4Sym2 (a6989586621680078964 :: [a6989586621680066262]) (a6989586621680078965 :: [b6989586621680066263]) :: forall c6989586621680066264 d6989586621680066265. (~>) [c6989586621680066264] ((~>) [d6989586621680066265] [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)]) Source #

Instances
SuppressUnusedWarnings (Zip4Sym2 a6989586621680078965 a6989586621680078964 c6989586621680066264 d6989586621680066265 :: TyFun [c6989586621680066264] ([d6989586621680066265] ~> [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip4Sym2 a6989586621680078965 a6989586621680078964 c6989586621680066264 d6989586621680066265 :: TyFun [c6989586621680066264] ([d6989586621680066265] ~> [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)]) -> Type) (a6989586621680078966 :: [c6989586621680066264]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip4Sym2 a6989586621680078965 a6989586621680078964 c6989586621680066264 d6989586621680066265 :: TyFun [c6989586621680066264] ([d6989586621680066265] ~> [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)]) -> Type) (a6989586621680078966 :: [c6989586621680066264]) = (Zip4Sym3 a6989586621680078965 a6989586621680078964 a6989586621680078966 d6989586621680066265 :: TyFun [d6989586621680066265] [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)] -> Type)

data Zip4Sym3 (a6989586621680078964 :: [a6989586621680066262]) (a6989586621680078965 :: [b6989586621680066263]) (a6989586621680078966 :: [c6989586621680066264]) :: forall d6989586621680066265. (~>) [d6989586621680066265] [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)] Source #

Instances
SuppressUnusedWarnings (Zip4Sym3 a6989586621680078966 a6989586621680078965 a6989586621680078964 d6989586621680066265 :: TyFun [d6989586621680066265] [(a6989586621680066262, b6989586621680066263, c6989586621680066264, d6989586621680066265)] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip4Sym3 a6989586621680078966 a6989586621680078965 a6989586621680078964 d :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621680078967 :: [d]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip4Sym3 a6989586621680078966 a6989586621680078965 a6989586621680078964 d :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621680078967 :: [d]) = Zip4 a6989586621680078966 a6989586621680078965 a6989586621680078964 a6989586621680078967

type Zip4Sym4 (a6989586621680078964 :: [a6989586621680066262]) (a6989586621680078965 :: [b6989586621680066263]) (a6989586621680078966 :: [c6989586621680066264]) (a6989586621680078967 :: [d6989586621680066265]) = Zip4 a6989586621680078964 a6989586621680078965 a6989586621680078966 a6989586621680078967 Source #

data Zip5Sym0 :: forall a6989586621680066257 b6989586621680066258 c6989586621680066259 d6989586621680066260 e6989586621680066261. (~>) [a6989586621680066257] ((~>) [b6989586621680066258] ((~>) [c6989586621680066259] ((~>) [d6989586621680066260] ((~>) [e6989586621680066261] [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)])))) Source #

Instances
SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a6989586621680066257] ([b6989586621680066258] ~> ([c6989586621680066259] ~> ([d6989586621680066260] ~> ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)])))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip5Sym0 :: TyFun [a6989586621680066257] ([b6989586621680066258] ~> ([c6989586621680066259] ~> ([d6989586621680066260] ~> ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)])))) -> Type) (a6989586621680078941 :: [a6989586621680066257]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip5Sym0 :: TyFun [a6989586621680066257] ([b6989586621680066258] ~> ([c6989586621680066259] ~> ([d6989586621680066260] ~> ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)])))) -> Type) (a6989586621680078941 :: [a6989586621680066257]) = (Zip5Sym1 a6989586621680078941 b6989586621680066258 c6989586621680066259 d6989586621680066260 e6989586621680066261 :: TyFun [b6989586621680066258] ([c6989586621680066259] ~> ([d6989586621680066260] ~> ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]))) -> Type)

data Zip5Sym1 (a6989586621680078941 :: [a6989586621680066257]) :: forall b6989586621680066258 c6989586621680066259 d6989586621680066260 e6989586621680066261. (~>) [b6989586621680066258] ((~>) [c6989586621680066259] ((~>) [d6989586621680066260] ((~>) [e6989586621680066261] [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]))) Source #

Instances
SuppressUnusedWarnings (Zip5Sym1 a6989586621680078941 b6989586621680066258 c6989586621680066259 d6989586621680066260 e6989586621680066261 :: TyFun [b6989586621680066258] ([c6989586621680066259] ~> ([d6989586621680066260] ~> ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip5Sym1 a6989586621680078941 b6989586621680066258 c6989586621680066259 d6989586621680066260 e6989586621680066261 :: TyFun [b6989586621680066258] ([c6989586621680066259] ~> ([d6989586621680066260] ~> ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]))) -> Type) (a6989586621680078942 :: [b6989586621680066258]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip5Sym1 a6989586621680078941 b6989586621680066258 c6989586621680066259 d6989586621680066260 e6989586621680066261 :: TyFun [b6989586621680066258] ([c6989586621680066259] ~> ([d6989586621680066260] ~> ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]))) -> Type) (a6989586621680078942 :: [b6989586621680066258]) = (Zip5Sym2 a6989586621680078941 a6989586621680078942 c6989586621680066259 d6989586621680066260 e6989586621680066261 :: TyFun [c6989586621680066259] ([d6989586621680066260] ~> ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)])) -> Type)

data Zip5Sym2 (a6989586621680078941 :: [a6989586621680066257]) (a6989586621680078942 :: [b6989586621680066258]) :: forall c6989586621680066259 d6989586621680066260 e6989586621680066261. (~>) [c6989586621680066259] ((~>) [d6989586621680066260] ((~>) [e6989586621680066261] [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)])) Source #

Instances
SuppressUnusedWarnings (Zip5Sym2 a6989586621680078942 a6989586621680078941 c6989586621680066259 d6989586621680066260 e6989586621680066261 :: TyFun [c6989586621680066259] ([d6989586621680066260] ~> ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip5Sym2 a6989586621680078942 a6989586621680078941 c6989586621680066259 d6989586621680066260 e6989586621680066261 :: TyFun [c6989586621680066259] ([d6989586621680066260] ~> ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)])) -> Type) (a6989586621680078943 :: [c6989586621680066259]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip5Sym2 a6989586621680078942 a6989586621680078941 c6989586621680066259 d6989586621680066260 e6989586621680066261 :: TyFun [c6989586621680066259] ([d6989586621680066260] ~> ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)])) -> Type) (a6989586621680078943 :: [c6989586621680066259]) = (Zip5Sym3 a6989586621680078942 a6989586621680078941 a6989586621680078943 d6989586621680066260 e6989586621680066261 :: TyFun [d6989586621680066260] ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]) -> Type)

data Zip5Sym3 (a6989586621680078941 :: [a6989586621680066257]) (a6989586621680078942 :: [b6989586621680066258]) (a6989586621680078943 :: [c6989586621680066259]) :: forall d6989586621680066260 e6989586621680066261. (~>) [d6989586621680066260] ((~>) [e6989586621680066261] [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]) Source #

Instances
SuppressUnusedWarnings (Zip5Sym3 a6989586621680078943 a6989586621680078942 a6989586621680078941 d6989586621680066260 e6989586621680066261 :: TyFun [d6989586621680066260] ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip5Sym3 a6989586621680078943 a6989586621680078942 a6989586621680078941 d6989586621680066260 e6989586621680066261 :: TyFun [d6989586621680066260] ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]) -> Type) (a6989586621680078944 :: [d6989586621680066260]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip5Sym3 a6989586621680078943 a6989586621680078942 a6989586621680078941 d6989586621680066260 e6989586621680066261 :: TyFun [d6989586621680066260] ([e6989586621680066261] ~> [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)]) -> Type) (a6989586621680078944 :: [d6989586621680066260]) = (Zip5Sym4 a6989586621680078943 a6989586621680078942 a6989586621680078941 a6989586621680078944 e6989586621680066261 :: TyFun [e6989586621680066261] [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)] -> Type)

data Zip5Sym4 (a6989586621680078941 :: [a6989586621680066257]) (a6989586621680078942 :: [b6989586621680066258]) (a6989586621680078943 :: [c6989586621680066259]) (a6989586621680078944 :: [d6989586621680066260]) :: forall e6989586621680066261. (~>) [e6989586621680066261] [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)] Source #

Instances
SuppressUnusedWarnings (Zip5Sym4 a6989586621680078944 a6989586621680078943 a6989586621680078942 a6989586621680078941 e6989586621680066261 :: TyFun [e6989586621680066261] [(a6989586621680066257, b6989586621680066258, c6989586621680066259, d6989586621680066260, e6989586621680066261)] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip5Sym4 a6989586621680078944 a6989586621680078943 a6989586621680078942 a6989586621680078941 e :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621680078945 :: [e]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip5Sym4 a6989586621680078944 a6989586621680078943 a6989586621680078942 a6989586621680078941 e :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621680078945 :: [e]) = Zip5 a6989586621680078944 a6989586621680078943 a6989586621680078942 a6989586621680078941 a6989586621680078945

type Zip5Sym5 (a6989586621680078941 :: [a6989586621680066257]) (a6989586621680078942 :: [b6989586621680066258]) (a6989586621680078943 :: [c6989586621680066259]) (a6989586621680078944 :: [d6989586621680066260]) (a6989586621680078945 :: [e6989586621680066261]) = Zip5 a6989586621680078941 a6989586621680078942 a6989586621680078943 a6989586621680078944 a6989586621680078945 Source #

data Zip6Sym0 :: forall a6989586621680066251 b6989586621680066252 c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256. (~>) [a6989586621680066251] ((~>) [b6989586621680066252] ((~>) [c6989586621680066253] ((~>) [d6989586621680066254] ((~>) [e6989586621680066255] ((~>) [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]))))) Source #

Instances
SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a6989586621680066251] ([b6989586621680066252] ~> ([c6989586621680066253] ~> ([d6989586621680066254] ~> ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip6Sym0 :: TyFun [a6989586621680066251] ([b6989586621680066252] ~> ([c6989586621680066253] ~> ([d6989586621680066254] ~> ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]))))) -> Type) (a6989586621680078913 :: [a6989586621680066251]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip6Sym0 :: TyFun [a6989586621680066251] ([b6989586621680066252] ~> ([c6989586621680066253] ~> ([d6989586621680066254] ~> ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]))))) -> Type) (a6989586621680078913 :: [a6989586621680066251]) = (Zip6Sym1 a6989586621680078913 b6989586621680066252 c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256 :: TyFun [b6989586621680066252] ([c6989586621680066253] ~> ([d6989586621680066254] ~> ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])))) -> Type)

data Zip6Sym1 (a6989586621680078913 :: [a6989586621680066251]) :: forall b6989586621680066252 c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256. (~>) [b6989586621680066252] ((~>) [c6989586621680066253] ((~>) [d6989586621680066254] ((~>) [e6989586621680066255] ((~>) [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])))) Source #

Instances
SuppressUnusedWarnings (Zip6Sym1 a6989586621680078913 b6989586621680066252 c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256 :: TyFun [b6989586621680066252] ([c6989586621680066253] ~> ([d6989586621680066254] ~> ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip6Sym1 a6989586621680078913 b6989586621680066252 c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256 :: TyFun [b6989586621680066252] ([c6989586621680066253] ~> ([d6989586621680066254] ~> ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])))) -> Type) (a6989586621680078914 :: [b6989586621680066252]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip6Sym1 a6989586621680078913 b6989586621680066252 c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256 :: TyFun [b6989586621680066252] ([c6989586621680066253] ~> ([d6989586621680066254] ~> ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])))) -> Type) (a6989586621680078914 :: [b6989586621680066252]) = (Zip6Sym2 a6989586621680078913 a6989586621680078914 c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256 :: TyFun [c6989586621680066253] ([d6989586621680066254] ~> ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]))) -> Type)

data Zip6Sym2 (a6989586621680078913 :: [a6989586621680066251]) (a6989586621680078914 :: [b6989586621680066252]) :: forall c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256. (~>) [c6989586621680066253] ((~>) [d6989586621680066254] ((~>) [e6989586621680066255] ((~>) [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]))) Source #

Instances
SuppressUnusedWarnings (Zip6Sym2 a6989586621680078914 a6989586621680078913 c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256 :: TyFun [c6989586621680066253] ([d6989586621680066254] ~> ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip6Sym2 a6989586621680078914 a6989586621680078913 c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256 :: TyFun [c6989586621680066253] ([d6989586621680066254] ~> ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]))) -> Type) (a6989586621680078915 :: [c6989586621680066253]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip6Sym2 a6989586621680078914 a6989586621680078913 c6989586621680066253 d6989586621680066254 e6989586621680066255 f6989586621680066256 :: TyFun [c6989586621680066253] ([d6989586621680066254] ~> ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]))) -> Type) (a6989586621680078915 :: [c6989586621680066253]) = (Zip6Sym3 a6989586621680078914 a6989586621680078913 a6989586621680078915 d6989586621680066254 e6989586621680066255 f6989586621680066256 :: TyFun [d6989586621680066254] ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])) -> Type)

data Zip6Sym3 (a6989586621680078913 :: [a6989586621680066251]) (a6989586621680078914 :: [b6989586621680066252]) (a6989586621680078915 :: [c6989586621680066253]) :: forall d6989586621680066254 e6989586621680066255 f6989586621680066256. (~>) [d6989586621680066254] ((~>) [e6989586621680066255] ((~>) [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])) Source #

Instances
SuppressUnusedWarnings (Zip6Sym3 a6989586621680078915 a6989586621680078914 a6989586621680078913 d6989586621680066254 e6989586621680066255 f6989586621680066256 :: TyFun [d6989586621680066254] ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip6Sym3 a6989586621680078915 a6989586621680078914 a6989586621680078913 d6989586621680066254 e6989586621680066255 f6989586621680066256 :: TyFun [d6989586621680066254] ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])) -> Type) (a6989586621680078916 :: [d6989586621680066254]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip6Sym3 a6989586621680078915 a6989586621680078914 a6989586621680078913 d6989586621680066254 e6989586621680066255 f6989586621680066256 :: TyFun [d6989586621680066254] ([e6989586621680066255] ~> ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)])) -> Type) (a6989586621680078916 :: [d6989586621680066254]) = (Zip6Sym4 a6989586621680078915 a6989586621680078914 a6989586621680078913 a6989586621680078916 e6989586621680066255 f6989586621680066256 :: TyFun [e6989586621680066255] ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]) -> Type)

data Zip6Sym4 (a6989586621680078913 :: [a6989586621680066251]) (a6989586621680078914 :: [b6989586621680066252]) (a6989586621680078915 :: [c6989586621680066253]) (a6989586621680078916 :: [d6989586621680066254]) :: forall e6989586621680066255 f6989586621680066256. (~>) [e6989586621680066255] ((~>) [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]) Source #

Instances
SuppressUnusedWarnings (Zip6Sym4 a6989586621680078916 a6989586621680078915 a6989586621680078914 a6989586621680078913 e6989586621680066255 f6989586621680066256 :: TyFun [e6989586621680066255] ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip6Sym4 a6989586621680078916 a6989586621680078915 a6989586621680078914 a6989586621680078913 e6989586621680066255 f6989586621680066256 :: TyFun [e6989586621680066255] ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]) -> Type) (a6989586621680078917 :: [e6989586621680066255]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip6Sym4 a6989586621680078916 a6989586621680078915 a6989586621680078914 a6989586621680078913 e6989586621680066255 f6989586621680066256 :: TyFun [e6989586621680066255] ([f6989586621680066256] ~> [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)]) -> Type) (a6989586621680078917 :: [e6989586621680066255]) = (Zip6Sym5 a6989586621680078916 a6989586621680078915 a6989586621680078914 a6989586621680078913 a6989586621680078917 f6989586621680066256 :: TyFun [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)] -> Type)

data Zip6Sym5 (a6989586621680078913 :: [a6989586621680066251]) (a6989586621680078914 :: [b6989586621680066252]) (a6989586621680078915 :: [c6989586621680066253]) (a6989586621680078916 :: [d6989586621680066254]) (a6989586621680078917 :: [e6989586621680066255]) :: forall f6989586621680066256. (~>) [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)] Source #

Instances
SuppressUnusedWarnings (Zip6Sym5 a6989586621680078917 a6989586621680078916 a6989586621680078915 a6989586621680078914 a6989586621680078913 f6989586621680066256 :: TyFun [f6989586621680066256] [(a6989586621680066251, b6989586621680066252, c6989586621680066253, d6989586621680066254, e6989586621680066255, f6989586621680066256)] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip6Sym5 a6989586621680078917 a6989586621680078916 a6989586621680078915 a6989586621680078914 a6989586621680078913 f :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680078918 :: [f]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip6Sym5 a6989586621680078917 a6989586621680078916 a6989586621680078915 a6989586621680078914 a6989586621680078913 f :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680078918 :: [f]) = Zip6 a6989586621680078917 a6989586621680078916 a6989586621680078915 a6989586621680078914 a6989586621680078913 a6989586621680078918

type Zip6Sym6 (a6989586621680078913 :: [a6989586621680066251]) (a6989586621680078914 :: [b6989586621680066252]) (a6989586621680078915 :: [c6989586621680066253]) (a6989586621680078916 :: [d6989586621680066254]) (a6989586621680078917 :: [e6989586621680066255]) (a6989586621680078918 :: [f6989586621680066256]) = Zip6 a6989586621680078913 a6989586621680078914 a6989586621680078915 a6989586621680078916 a6989586621680078917 a6989586621680078918 Source #

data Zip7Sym0 :: forall a6989586621680066244 b6989586621680066245 c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250. (~>) [a6989586621680066244] ((~>) [b6989586621680066245] ((~>) [c6989586621680066246] ((~>) [d6989586621680066247] ((~>) [e6989586621680066248] ((~>) [f6989586621680066249] ((~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])))))) Source #

Instances
SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a6989586621680066244] ([b6989586621680066245] ~> ([c6989586621680066246] ~> ([d6989586621680066247] ~> ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym0 :: TyFun [a6989586621680066244] ([b6989586621680066245] ~> ([c6989586621680066246] ~> ([d6989586621680066247] ~> ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])))))) -> Type) (a6989586621680078880 :: [a6989586621680066244]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym0 :: TyFun [a6989586621680066244] ([b6989586621680066245] ~> ([c6989586621680066246] ~> ([d6989586621680066247] ~> ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])))))) -> Type) (a6989586621680078880 :: [a6989586621680066244]) = (Zip7Sym1 a6989586621680078880 b6989586621680066245 c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [b6989586621680066245] ([c6989586621680066246] ~> ([d6989586621680066247] ~> ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))))) -> Type)

data Zip7Sym1 (a6989586621680078880 :: [a6989586621680066244]) :: forall b6989586621680066245 c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250. (~>) [b6989586621680066245] ((~>) [c6989586621680066246] ((~>) [d6989586621680066247] ((~>) [e6989586621680066248] ((~>) [f6989586621680066249] ((~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))))) Source #

Instances
SuppressUnusedWarnings (Zip7Sym1 a6989586621680078880 b6989586621680066245 c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [b6989586621680066245] ([c6989586621680066246] ~> ([d6989586621680066247] ~> ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym1 a6989586621680078880 b6989586621680066245 c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [b6989586621680066245] ([c6989586621680066246] ~> ([d6989586621680066247] ~> ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))))) -> Type) (a6989586621680078881 :: [b6989586621680066245]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym1 a6989586621680078880 b6989586621680066245 c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [b6989586621680066245] ([c6989586621680066246] ~> ([d6989586621680066247] ~> ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))))) -> Type) (a6989586621680078881 :: [b6989586621680066245]) = (Zip7Sym2 a6989586621680078880 a6989586621680078881 c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [c6989586621680066246] ([d6989586621680066247] ~> ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])))) -> Type)

data Zip7Sym2 (a6989586621680078880 :: [a6989586621680066244]) (a6989586621680078881 :: [b6989586621680066245]) :: forall c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250. (~>) [c6989586621680066246] ((~>) [d6989586621680066247] ((~>) [e6989586621680066248] ((~>) [f6989586621680066249] ((~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])))) Source #

Instances
SuppressUnusedWarnings (Zip7Sym2 a6989586621680078881 a6989586621680078880 c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [c6989586621680066246] ([d6989586621680066247] ~> ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym2 a6989586621680078881 a6989586621680078880 c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [c6989586621680066246] ([d6989586621680066247] ~> ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])))) -> Type) (a6989586621680078882 :: [c6989586621680066246]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym2 a6989586621680078881 a6989586621680078880 c6989586621680066246 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [c6989586621680066246] ([d6989586621680066247] ~> ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])))) -> Type) (a6989586621680078882 :: [c6989586621680066246]) = (Zip7Sym3 a6989586621680078881 a6989586621680078880 a6989586621680078882 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [d6989586621680066247] ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))) -> Type)

data Zip7Sym3 (a6989586621680078880 :: [a6989586621680066244]) (a6989586621680078881 :: [b6989586621680066245]) (a6989586621680078882 :: [c6989586621680066246]) :: forall d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250. (~>) [d6989586621680066247] ((~>) [e6989586621680066248] ((~>) [f6989586621680066249] ((~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))) Source #

Instances
SuppressUnusedWarnings (Zip7Sym3 a6989586621680078882 a6989586621680078881 a6989586621680078880 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [d6989586621680066247] ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym3 a6989586621680078882 a6989586621680078881 a6989586621680078880 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [d6989586621680066247] ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))) -> Type) (a6989586621680078883 :: [d6989586621680066247]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym3 a6989586621680078882 a6989586621680078881 a6989586621680078880 d6989586621680066247 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [d6989586621680066247] ([e6989586621680066248] ~> ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]))) -> Type) (a6989586621680078883 :: [d6989586621680066247]) = (Zip7Sym4 a6989586621680078882 a6989586621680078881 a6989586621680078880 a6989586621680078883 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [e6989586621680066248] ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])) -> Type)

data Zip7Sym4 (a6989586621680078880 :: [a6989586621680066244]) (a6989586621680078881 :: [b6989586621680066245]) (a6989586621680078882 :: [c6989586621680066246]) (a6989586621680078883 :: [d6989586621680066247]) :: forall e6989586621680066248 f6989586621680066249 g6989586621680066250. (~>) [e6989586621680066248] ((~>) [f6989586621680066249] ((~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])) Source #

Instances
SuppressUnusedWarnings (Zip7Sym4 a6989586621680078883 a6989586621680078882 a6989586621680078881 a6989586621680078880 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [e6989586621680066248] ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym4 a6989586621680078883 a6989586621680078882 a6989586621680078881 a6989586621680078880 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [e6989586621680066248] ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])) -> Type) (a6989586621680078884 :: [e6989586621680066248]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym4 a6989586621680078883 a6989586621680078882 a6989586621680078881 a6989586621680078880 e6989586621680066248 f6989586621680066249 g6989586621680066250 :: TyFun [e6989586621680066248] ([f6989586621680066249] ~> ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)])) -> Type) (a6989586621680078884 :: [e6989586621680066248]) = (Zip7Sym5 a6989586621680078883 a6989586621680078882 a6989586621680078881 a6989586621680078880 a6989586621680078884 f6989586621680066249 g6989586621680066250 :: TyFun [f6989586621680066249] ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]) -> Type)

data Zip7Sym5 (a6989586621680078880 :: [a6989586621680066244]) (a6989586621680078881 :: [b6989586621680066245]) (a6989586621680078882 :: [c6989586621680066246]) (a6989586621680078883 :: [d6989586621680066247]) (a6989586621680078884 :: [e6989586621680066248]) :: forall f6989586621680066249 g6989586621680066250. (~>) [f6989586621680066249] ((~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]) Source #

Instances
SuppressUnusedWarnings (Zip7Sym5 a6989586621680078884 a6989586621680078883 a6989586621680078882 a6989586621680078881 a6989586621680078880 f6989586621680066249 g6989586621680066250 :: TyFun [f6989586621680066249] ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym5 a6989586621680078884 a6989586621680078883 a6989586621680078882 a6989586621680078881 a6989586621680078880 f6989586621680066249 g6989586621680066250 :: TyFun [f6989586621680066249] ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]) -> Type) (a6989586621680078885 :: [f6989586621680066249]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym5 a6989586621680078884 a6989586621680078883 a6989586621680078882 a6989586621680078881 a6989586621680078880 f6989586621680066249 g6989586621680066250 :: TyFun [f6989586621680066249] ([g6989586621680066250] ~> [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)]) -> Type) (a6989586621680078885 :: [f6989586621680066249]) = (Zip7Sym6 a6989586621680078884 a6989586621680078883 a6989586621680078882 a6989586621680078881 a6989586621680078880 a6989586621680078885 g6989586621680066250 :: TyFun [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)] -> Type)

data Zip7Sym6 (a6989586621680078880 :: [a6989586621680066244]) (a6989586621680078881 :: [b6989586621680066245]) (a6989586621680078882 :: [c6989586621680066246]) (a6989586621680078883 :: [d6989586621680066247]) (a6989586621680078884 :: [e6989586621680066248]) (a6989586621680078885 :: [f6989586621680066249]) :: forall g6989586621680066250. (~>) [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)] Source #

Instances
SuppressUnusedWarnings (Zip7Sym6 a6989586621680078885 a6989586621680078884 a6989586621680078883 a6989586621680078882 a6989586621680078881 a6989586621680078880 g6989586621680066250 :: TyFun [g6989586621680066250] [(a6989586621680066244, b6989586621680066245, c6989586621680066246, d6989586621680066247, e6989586621680066248, f6989586621680066249, g6989586621680066250)] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym6 a6989586621680078885 a6989586621680078884 a6989586621680078883 a6989586621680078882 a6989586621680078881 a6989586621680078880 g :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680078886 :: [g]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Zip7Sym6 a6989586621680078885 a6989586621680078884 a6989586621680078883 a6989586621680078882 a6989586621680078881 a6989586621680078880 g :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680078886 :: [g]) = Zip7 a6989586621680078885 a6989586621680078884 a6989586621680078883 a6989586621680078882 a6989586621680078881 a6989586621680078880 a6989586621680078886

type Zip7Sym7 (a6989586621680078880 :: [a6989586621680066244]) (a6989586621680078881 :: [b6989586621680066245]) (a6989586621680078882 :: [c6989586621680066246]) (a6989586621680078883 :: [d6989586621680066247]) (a6989586621680078884 :: [e6989586621680066248]) (a6989586621680078885 :: [f6989586621680066249]) (a6989586621680078886 :: [g6989586621680066250]) = Zip7 a6989586621680078880 a6989586621680078881 a6989586621680078882 a6989586621680078883 a6989586621680078884 a6989586621680078885 a6989586621680078886 Source #

data ZipWithSym0 :: forall a6989586621679940092 b6989586621679940093 c6989586621679940094. (~>) ((~>) a6989586621679940092 ((~>) b6989586621679940093 c6989586621679940094)) ((~>) [a6989586621679940092] ((~>) [b6989586621679940093] [c6989586621679940094])) Source #

Instances
SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a6989586621679940092 ~> (b6989586621679940093 ~> c6989586621679940094)) ([a6989586621679940092] ~> ([b6989586621679940093] ~> [c6989586621679940094])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWithSym0 :: TyFun (a6989586621679940092 ~> (b6989586621679940093 ~> c6989586621679940094)) ([a6989586621679940092] ~> ([b6989586621679940093] ~> [c6989586621679940094])) -> Type) (a6989586621679949903 :: a6989586621679940092 ~> (b6989586621679940093 ~> c6989586621679940094)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWithSym0 :: TyFun (a6989586621679940092 ~> (b6989586621679940093 ~> c6989586621679940094)) ([a6989586621679940092] ~> ([b6989586621679940093] ~> [c6989586621679940094])) -> Type) (a6989586621679949903 :: a6989586621679940092 ~> (b6989586621679940093 ~> c6989586621679940094)) = ZipWithSym1 a6989586621679949903

data ZipWithSym1 (a6989586621679949903 :: (~>) a6989586621679940092 ((~>) b6989586621679940093 c6989586621679940094)) :: (~>) [a6989586621679940092] ((~>) [b6989586621679940093] [c6989586621679940094]) Source #

Instances
SingI d => SingI (ZipWithSym1 d :: TyFun [a] ([b] ~> [c]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ZipWithSym1 d) Source #

SuppressUnusedWarnings (ZipWithSym1 a6989586621679949903 :: TyFun [a6989586621679940092] ([b6989586621679940093] ~> [c6989586621679940094]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWithSym1 a6989586621679949903 :: TyFun [a6989586621679940092] ([b6989586621679940093] ~> [c6989586621679940094]) -> Type) (a6989586621679949904 :: [a6989586621679940092]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWithSym1 a6989586621679949903 :: TyFun [a6989586621679940092] ([b6989586621679940093] ~> [c6989586621679940094]) -> Type) (a6989586621679949904 :: [a6989586621679940092]) = ZipWithSym2 a6989586621679949903 a6989586621679949904

data ZipWithSym2 (a6989586621679949903 :: (~>) a6989586621679940092 ((~>) b6989586621679940093 c6989586621679940094)) (a6989586621679949904 :: [a6989586621679940092]) :: (~>) [b6989586621679940093] [c6989586621679940094] Source #

Instances
(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ZipWithSym2 d1 d2) Source #

SuppressUnusedWarnings (ZipWithSym2 a6989586621679949904 a6989586621679949903 :: TyFun [b6989586621679940093] [c6989586621679940094] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWithSym2 a6989586621679949904 a6989586621679949903 :: TyFun [b] [c] -> Type) (a6989586621679949905 :: [b]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWithSym2 a6989586621679949904 a6989586621679949903 :: TyFun [b] [c] -> Type) (a6989586621679949905 :: [b]) = ZipWith a6989586621679949904 a6989586621679949903 a6989586621679949905

type ZipWithSym3 (a6989586621679949903 :: (~>) a6989586621679940092 ((~>) b6989586621679940093 c6989586621679940094)) (a6989586621679949904 :: [a6989586621679940092]) (a6989586621679949905 :: [b6989586621679940093]) = ZipWith a6989586621679949903 a6989586621679949904 a6989586621679949905 Source #

data ZipWith3Sym0 :: forall a6989586621679940088 b6989586621679940089 c6989586621679940090 d6989586621679940091. (~>) ((~>) a6989586621679940088 ((~>) b6989586621679940089 ((~>) c6989586621679940090 d6989586621679940091))) ((~>) [a6989586621679940088] ((~>) [b6989586621679940089] ((~>) [c6989586621679940090] [d6989586621679940091]))) Source #

Instances
SingI (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (a6989586621679940088 ~> (b6989586621679940089 ~> (c6989586621679940090 ~> d6989586621679940091))) ([a6989586621679940088] ~> ([b6989586621679940089] ~> ([c6989586621679940090] ~> [d6989586621679940091]))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith3Sym0 :: TyFun (a6989586621679940088 ~> (b6989586621679940089 ~> (c6989586621679940090 ~> d6989586621679940091))) ([a6989586621679940088] ~> ([b6989586621679940089] ~> ([c6989586621679940090] ~> [d6989586621679940091]))) -> Type) (a6989586621679949888 :: a6989586621679940088 ~> (b6989586621679940089 ~> (c6989586621679940090 ~> d6989586621679940091))) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith3Sym0 :: TyFun (a6989586621679940088 ~> (b6989586621679940089 ~> (c6989586621679940090 ~> d6989586621679940091))) ([a6989586621679940088] ~> ([b6989586621679940089] ~> ([c6989586621679940090] ~> [d6989586621679940091]))) -> Type) (a6989586621679949888 :: a6989586621679940088 ~> (b6989586621679940089 ~> (c6989586621679940090 ~> d6989586621679940091))) = ZipWith3Sym1 a6989586621679949888

data ZipWith3Sym1 (a6989586621679949888 :: (~>) a6989586621679940088 ((~>) b6989586621679940089 ((~>) c6989586621679940090 d6989586621679940091))) :: (~>) [a6989586621679940088] ((~>) [b6989586621679940089] ((~>) [c6989586621679940090] [d6989586621679940091])) Source #

Instances
SingI d2 => SingI (ZipWith3Sym1 d2 :: TyFun [a] ([b] ~> ([c] ~> [d1])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ZipWith3Sym1 d2) Source #

SuppressUnusedWarnings (ZipWith3Sym1 a6989586621679949888 :: TyFun [a6989586621679940088] ([b6989586621679940089] ~> ([c6989586621679940090] ~> [d6989586621679940091])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith3Sym1 a6989586621679949888 :: TyFun [a6989586621679940088] ([b6989586621679940089] ~> ([c6989586621679940090] ~> [d6989586621679940091])) -> Type) (a6989586621679949889 :: [a6989586621679940088]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith3Sym1 a6989586621679949888 :: TyFun [a6989586621679940088] ([b6989586621679940089] ~> ([c6989586621679940090] ~> [d6989586621679940091])) -> Type) (a6989586621679949889 :: [a6989586621679940088]) = ZipWith3Sym2 a6989586621679949888 a6989586621679949889

data ZipWith3Sym2 (a6989586621679949888 :: (~>) a6989586621679940088 ((~>) b6989586621679940089 ((~>) c6989586621679940090 d6989586621679940091))) (a6989586621679949889 :: [a6989586621679940088]) :: (~>) [b6989586621679940089] ((~>) [c6989586621679940090] [d6989586621679940091]) Source #

Instances
(SingI d2, SingI d3) => SingI (ZipWith3Sym2 d2 d3 :: TyFun [b] ([c] ~> [d1]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ZipWith3Sym2 d2 d3) Source #

SuppressUnusedWarnings (ZipWith3Sym2 a6989586621679949889 a6989586621679949888 :: TyFun [b6989586621679940089] ([c6989586621679940090] ~> [d6989586621679940091]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith3Sym2 a6989586621679949889 a6989586621679949888 :: TyFun [b6989586621679940089] ([c6989586621679940090] ~> [d6989586621679940091]) -> Type) (a6989586621679949890 :: [b6989586621679940089]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith3Sym2 a6989586621679949889 a6989586621679949888 :: TyFun [b6989586621679940089] ([c6989586621679940090] ~> [d6989586621679940091]) -> Type) (a6989586621679949890 :: [b6989586621679940089]) = ZipWith3Sym3 a6989586621679949889 a6989586621679949888 a6989586621679949890

data ZipWith3Sym3 (a6989586621679949888 :: (~>) a6989586621679940088 ((~>) b6989586621679940089 ((~>) c6989586621679940090 d6989586621679940091))) (a6989586621679949889 :: [a6989586621679940088]) (a6989586621679949890 :: [b6989586621679940089]) :: (~>) [c6989586621679940090] [d6989586621679940091] Source #

Instances
(SingI d2, SingI d3, SingI d4) => SingI (ZipWith3Sym3 d2 d3 d4 :: TyFun [c] [d1] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ZipWith3Sym3 d2 d3 d4) Source #

SuppressUnusedWarnings (ZipWith3Sym3 a6989586621679949890 a6989586621679949889 a6989586621679949888 :: TyFun [c6989586621679940090] [d6989586621679940091] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith3Sym3 a6989586621679949890 a6989586621679949889 a6989586621679949888 :: TyFun [c] [d] -> Type) (a6989586621679949891 :: [c]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith3Sym3 a6989586621679949890 a6989586621679949889 a6989586621679949888 :: TyFun [c] [d] -> Type) (a6989586621679949891 :: [c]) = ZipWith3 a6989586621679949890 a6989586621679949889 a6989586621679949888 a6989586621679949891

type ZipWith3Sym4 (a6989586621679949888 :: (~>) a6989586621679940088 ((~>) b6989586621679940089 ((~>) c6989586621679940090 d6989586621679940091))) (a6989586621679949889 :: [a6989586621679940088]) (a6989586621679949890 :: [b6989586621679940089]) (a6989586621679949891 :: [c6989586621679940090]) = ZipWith3 a6989586621679949888 a6989586621679949889 a6989586621679949890 a6989586621679949891 Source #

data ZipWith4Sym0 :: forall a6989586621680066239 b6989586621680066240 c6989586621680066241 d6989586621680066242 e6989586621680066243. (~>) ((~>) a6989586621680066239 ((~>) b6989586621680066240 ((~>) c6989586621680066241 ((~>) d6989586621680066242 e6989586621680066243)))) ((~>) [a6989586621680066239] ((~>) [b6989586621680066240] ((~>) [c6989586621680066241] ((~>) [d6989586621680066242] [e6989586621680066243])))) Source #

Instances
SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (a6989586621680066239 ~> (b6989586621680066240 ~> (c6989586621680066241 ~> (d6989586621680066242 ~> e6989586621680066243)))) ([a6989586621680066239] ~> ([b6989586621680066240] ~> ([c6989586621680066241] ~> ([d6989586621680066242] ~> [e6989586621680066243])))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith4Sym0 :: TyFun (a6989586621680066239 ~> (b6989586621680066240 ~> (c6989586621680066241 ~> (d6989586621680066242 ~> e6989586621680066243)))) ([a6989586621680066239] ~> ([b6989586621680066240] ~> ([c6989586621680066241] ~> ([d6989586621680066242] ~> [e6989586621680066243])))) -> Type) (a6989586621680078847 :: a6989586621680066239 ~> (b6989586621680066240 ~> (c6989586621680066241 ~> (d6989586621680066242 ~> e6989586621680066243)))) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith4Sym0 :: TyFun (a6989586621680066239 ~> (b6989586621680066240 ~> (c6989586621680066241 ~> (d6989586621680066242 ~> e6989586621680066243)))) ([a6989586621680066239] ~> ([b6989586621680066240] ~> ([c6989586621680066241] ~> ([d6989586621680066242] ~> [e6989586621680066243])))) -> Type) (a6989586621680078847 :: a6989586621680066239 ~> (b6989586621680066240 ~> (c6989586621680066241 ~> (d6989586621680066242 ~> e6989586621680066243)))) = ZipWith4Sym1 a6989586621680078847

data ZipWith4Sym1 (a6989586621680078847 :: (~>) a6989586621680066239 ((~>) b6989586621680066240 ((~>) c6989586621680066241 ((~>) d6989586621680066242 e6989586621680066243)))) :: (~>) [a6989586621680066239] ((~>) [b6989586621680066240] ((~>) [c6989586621680066241] ((~>) [d6989586621680066242] [e6989586621680066243]))) Source #

Instances
SuppressUnusedWarnings (ZipWith4Sym1 a6989586621680078847 :: TyFun [a6989586621680066239] ([b6989586621680066240] ~> ([c6989586621680066241] ~> ([d6989586621680066242] ~> [e6989586621680066243]))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith4Sym1 a6989586621680078847 :: TyFun [a6989586621680066239] ([b6989586621680066240] ~> ([c6989586621680066241] ~> ([d6989586621680066242] ~> [e6989586621680066243]))) -> Type) (a6989586621680078848 :: [a6989586621680066239]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith4Sym1 a6989586621680078847 :: TyFun [a6989586621680066239] ([b6989586621680066240] ~> ([c6989586621680066241] ~> ([d6989586621680066242] ~> [e6989586621680066243]))) -> Type) (a6989586621680078848 :: [a6989586621680066239]) = ZipWith4Sym2 a6989586621680078847 a6989586621680078848

data ZipWith4Sym2 (a6989586621680078847 :: (~>) a6989586621680066239 ((~>) b6989586621680066240 ((~>) c6989586621680066241 ((~>) d6989586621680066242 e6989586621680066243)))) (a6989586621680078848 :: [a6989586621680066239]) :: (~>) [b6989586621680066240] ((~>) [c6989586621680066241] ((~>) [d6989586621680066242] [e6989586621680066243])) Source #

Instances
SuppressUnusedWarnings (ZipWith4Sym2 a6989586621680078848 a6989586621680078847 :: TyFun [b6989586621680066240] ([c6989586621680066241] ~> ([d6989586621680066242] ~> [e6989586621680066243])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith4Sym2 a6989586621680078848 a6989586621680078847 :: TyFun [b6989586621680066240] ([c6989586621680066241] ~> ([d6989586621680066242] ~> [e6989586621680066243])) -> Type) (a6989586621680078849 :: [b6989586621680066240]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith4Sym2 a6989586621680078848 a6989586621680078847 :: TyFun [b6989586621680066240] ([c6989586621680066241] ~> ([d6989586621680066242] ~> [e6989586621680066243])) -> Type) (a6989586621680078849 :: [b6989586621680066240]) = ZipWith4Sym3 a6989586621680078848 a6989586621680078847 a6989586621680078849

data ZipWith4Sym3 (a6989586621680078847 :: (~>) a6989586621680066239 ((~>) b6989586621680066240 ((~>) c6989586621680066241 ((~>) d6989586621680066242 e6989586621680066243)))) (a6989586621680078848 :: [a6989586621680066239]) (a6989586621680078849 :: [b6989586621680066240]) :: (~>) [c6989586621680066241] ((~>) [d6989586621680066242] [e6989586621680066243]) Source #

Instances
SuppressUnusedWarnings (ZipWith4Sym3 a6989586621680078849 a6989586621680078848 a6989586621680078847 :: TyFun [c6989586621680066241] ([d6989586621680066242] ~> [e6989586621680066243]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith4Sym3 a6989586621680078849 a6989586621680078848 a6989586621680078847 :: TyFun [c6989586621680066241] ([d6989586621680066242] ~> [e6989586621680066243]) -> Type) (a6989586621680078850 :: [c6989586621680066241]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith4Sym3 a6989586621680078849 a6989586621680078848 a6989586621680078847 :: TyFun [c6989586621680066241] ([d6989586621680066242] ~> [e6989586621680066243]) -> Type) (a6989586621680078850 :: [c6989586621680066241]) = ZipWith4Sym4 a6989586621680078849 a6989586621680078848 a6989586621680078847 a6989586621680078850

data ZipWith4Sym4 (a6989586621680078847 :: (~>) a6989586621680066239 ((~>) b6989586621680066240 ((~>) c6989586621680066241 ((~>) d6989586621680066242 e6989586621680066243)))) (a6989586621680078848 :: [a6989586621680066239]) (a6989586621680078849 :: [b6989586621680066240]) (a6989586621680078850 :: [c6989586621680066241]) :: (~>) [d6989586621680066242] [e6989586621680066243] Source #

Instances
SuppressUnusedWarnings (ZipWith4Sym4 a6989586621680078850 a6989586621680078849 a6989586621680078848 a6989586621680078847 :: TyFun [d6989586621680066242] [e6989586621680066243] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith4Sym4 a6989586621680078850 a6989586621680078849 a6989586621680078848 a6989586621680078847 :: TyFun [d] [e] -> Type) (a6989586621680078851 :: [d]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith4Sym4 a6989586621680078850 a6989586621680078849 a6989586621680078848 a6989586621680078847 :: TyFun [d] [e] -> Type) (a6989586621680078851 :: [d]) = ZipWith4 a6989586621680078850 a6989586621680078849 a6989586621680078848 a6989586621680078847 a6989586621680078851

type ZipWith4Sym5 (a6989586621680078847 :: (~>) a6989586621680066239 ((~>) b6989586621680066240 ((~>) c6989586621680066241 ((~>) d6989586621680066242 e6989586621680066243)))) (a6989586621680078848 :: [a6989586621680066239]) (a6989586621680078849 :: [b6989586621680066240]) (a6989586621680078850 :: [c6989586621680066241]) (a6989586621680078851 :: [d6989586621680066242]) = ZipWith4 a6989586621680078847 a6989586621680078848 a6989586621680078849 a6989586621680078850 a6989586621680078851 Source #

data ZipWith5Sym0 :: forall a6989586621680066233 b6989586621680066234 c6989586621680066235 d6989586621680066236 e6989586621680066237 f6989586621680066238. (~>) ((~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) ((~>) [a6989586621680066233] ((~>) [b6989586621680066234] ((~>) [c6989586621680066235] ((~>) [d6989586621680066236] ((~>) [e6989586621680066237] [f6989586621680066238]))))) Source #

Instances
SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (a6989586621680066233 ~> (b6989586621680066234 ~> (c6989586621680066235 ~> (d6989586621680066236 ~> (e6989586621680066237 ~> f6989586621680066238))))) ([a6989586621680066233] ~> ([b6989586621680066234] ~> ([c6989586621680066235] ~> ([d6989586621680066236] ~> ([e6989586621680066237] ~> [f6989586621680066238]))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith5Sym0 :: TyFun (a6989586621680066233 ~> (b6989586621680066234 ~> (c6989586621680066235 ~> (d6989586621680066236 ~> (e6989586621680066237 ~> f6989586621680066238))))) ([a6989586621680066233] ~> ([b6989586621680066234] ~> ([c6989586621680066235] ~> ([d6989586621680066236] ~> ([e6989586621680066237] ~> [f6989586621680066238]))))) -> Type) (a6989586621680078824 :: a6989586621680066233 ~> (b6989586621680066234 ~> (c6989586621680066235 ~> (d6989586621680066236 ~> (e6989586621680066237 ~> f6989586621680066238))))) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith5Sym0 :: TyFun (a6989586621680066233 ~> (b6989586621680066234 ~> (c6989586621680066235 ~> (d6989586621680066236 ~> (e6989586621680066237 ~> f6989586621680066238))))) ([a6989586621680066233] ~> ([b6989586621680066234] ~> ([c6989586621680066235] ~> ([d6989586621680066236] ~> ([e6989586621680066237] ~> [f6989586621680066238]))))) -> Type) (a6989586621680078824 :: a6989586621680066233 ~> (b6989586621680066234 ~> (c6989586621680066235 ~> (d6989586621680066236 ~> (e6989586621680066237 ~> f6989586621680066238))))) = ZipWith5Sym1 a6989586621680078824

data ZipWith5Sym1 (a6989586621680078824 :: (~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) :: (~>) [a6989586621680066233] ((~>) [b6989586621680066234] ((~>) [c6989586621680066235] ((~>) [d6989586621680066236] ((~>) [e6989586621680066237] [f6989586621680066238])))) Source #

Instances
SuppressUnusedWarnings (ZipWith5Sym1 a6989586621680078824 :: TyFun [a6989586621680066233] ([b6989586621680066234] ~> ([c6989586621680066235] ~> ([d6989586621680066236] ~> ([e6989586621680066237] ~> [f6989586621680066238])))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith5Sym1 a6989586621680078824 :: TyFun [a6989586621680066233] ([b6989586621680066234] ~> ([c6989586621680066235] ~> ([d6989586621680066236] ~> ([e6989586621680066237] ~> [f6989586621680066238])))) -> Type) (a6989586621680078825 :: [a6989586621680066233]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith5Sym1 a6989586621680078824 :: TyFun [a6989586621680066233] ([b6989586621680066234] ~> ([c6989586621680066235] ~> ([d6989586621680066236] ~> ([e6989586621680066237] ~> [f6989586621680066238])))) -> Type) (a6989586621680078825 :: [a6989586621680066233]) = ZipWith5Sym2 a6989586621680078824 a6989586621680078825

data ZipWith5Sym2 (a6989586621680078824 :: (~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) (a6989586621680078825 :: [a6989586621680066233]) :: (~>) [b6989586621680066234] ((~>) [c6989586621680066235] ((~>) [d6989586621680066236] ((~>) [e6989586621680066237] [f6989586621680066238]))) Source #

Instances
SuppressUnusedWarnings (ZipWith5Sym2 a6989586621680078825 a6989586621680078824 :: TyFun [b6989586621680066234] ([c6989586621680066235] ~> ([d6989586621680066236] ~> ([e6989586621680066237] ~> [f6989586621680066238]))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith5Sym2 a6989586621680078825 a6989586621680078824 :: TyFun [b6989586621680066234] ([c6989586621680066235] ~> ([d6989586621680066236] ~> ([e6989586621680066237] ~> [f6989586621680066238]))) -> Type) (a6989586621680078826 :: [b6989586621680066234]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith5Sym2 a6989586621680078825 a6989586621680078824 :: TyFun [b6989586621680066234] ([c6989586621680066235] ~> ([d6989586621680066236] ~> ([e6989586621680066237] ~> [f6989586621680066238]))) -> Type) (a6989586621680078826 :: [b6989586621680066234]) = ZipWith5Sym3 a6989586621680078825 a6989586621680078824 a6989586621680078826

data ZipWith5Sym3 (a6989586621680078824 :: (~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) (a6989586621680078825 :: [a6989586621680066233]) (a6989586621680078826 :: [b6989586621680066234]) :: (~>) [c6989586621680066235] ((~>) [d6989586621680066236] ((~>) [e6989586621680066237] [f6989586621680066238])) Source #

Instances
SuppressUnusedWarnings (ZipWith5Sym3 a6989586621680078826 a6989586621680078825 a6989586621680078824 :: TyFun [c6989586621680066235] ([d6989586621680066236] ~> ([e6989586621680066237] ~> [f6989586621680066238])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith5Sym3 a6989586621680078826 a6989586621680078825 a6989586621680078824 :: TyFun [c6989586621680066235] ([d6989586621680066236] ~> ([e6989586621680066237] ~> [f6989586621680066238])) -> Type) (a6989586621680078827 :: [c6989586621680066235]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith5Sym3 a6989586621680078826 a6989586621680078825 a6989586621680078824 :: TyFun [c6989586621680066235] ([d6989586621680066236] ~> ([e6989586621680066237] ~> [f6989586621680066238])) -> Type) (a6989586621680078827 :: [c6989586621680066235]) = ZipWith5Sym4 a6989586621680078826 a6989586621680078825 a6989586621680078824 a6989586621680078827

data ZipWith5Sym4 (a6989586621680078824 :: (~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) (a6989586621680078825 :: [a6989586621680066233]) (a6989586621680078826 :: [b6989586621680066234]) (a6989586621680078827 :: [c6989586621680066235]) :: (~>) [d6989586621680066236] ((~>) [e6989586621680066237] [f6989586621680066238]) Source #

Instances
SuppressUnusedWarnings (ZipWith5Sym4 a6989586621680078827 a6989586621680078826 a6989586621680078825 a6989586621680078824 :: TyFun [d6989586621680066236] ([e6989586621680066237] ~> [f6989586621680066238]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith5Sym4 a6989586621680078827 a6989586621680078826 a6989586621680078825 a6989586621680078824 :: TyFun [d6989586621680066236] ([e6989586621680066237] ~> [f6989586621680066238]) -> Type) (a6989586621680078828 :: [d6989586621680066236]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith5Sym4 a6989586621680078827 a6989586621680078826 a6989586621680078825 a6989586621680078824 :: TyFun [d6989586621680066236] ([e6989586621680066237] ~> [f6989586621680066238]) -> Type) (a6989586621680078828 :: [d6989586621680066236]) = ZipWith5Sym5 a6989586621680078827 a6989586621680078826 a6989586621680078825 a6989586621680078824 a6989586621680078828

data ZipWith5Sym5 (a6989586621680078824 :: (~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) (a6989586621680078825 :: [a6989586621680066233]) (a6989586621680078826 :: [b6989586621680066234]) (a6989586621680078827 :: [c6989586621680066235]) (a6989586621680078828 :: [d6989586621680066236]) :: (~>) [e6989586621680066237] [f6989586621680066238] Source #

Instances
SuppressUnusedWarnings (ZipWith5Sym5 a6989586621680078828 a6989586621680078827 a6989586621680078826 a6989586621680078825 a6989586621680078824 :: TyFun [e6989586621680066237] [f6989586621680066238] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith5Sym5 a6989586621680078828 a6989586621680078827 a6989586621680078826 a6989586621680078825 a6989586621680078824 :: TyFun [e] [f] -> Type) (a6989586621680078829 :: [e]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith5Sym5 a6989586621680078828 a6989586621680078827 a6989586621680078826 a6989586621680078825 a6989586621680078824 :: TyFun [e] [f] -> Type) (a6989586621680078829 :: [e]) = ZipWith5 a6989586621680078828 a6989586621680078827 a6989586621680078826 a6989586621680078825 a6989586621680078824 a6989586621680078829

type ZipWith5Sym6 (a6989586621680078824 :: (~>) a6989586621680066233 ((~>) b6989586621680066234 ((~>) c6989586621680066235 ((~>) d6989586621680066236 ((~>) e6989586621680066237 f6989586621680066238))))) (a6989586621680078825 :: [a6989586621680066233]) (a6989586621680078826 :: [b6989586621680066234]) (a6989586621680078827 :: [c6989586621680066235]) (a6989586621680078828 :: [d6989586621680066236]) (a6989586621680078829 :: [e6989586621680066237]) = ZipWith5 a6989586621680078824 a6989586621680078825 a6989586621680078826 a6989586621680078827 a6989586621680078828 a6989586621680078829 Source #

data ZipWith6Sym0 :: forall a6989586621680066226 b6989586621680066227 c6989586621680066228 d6989586621680066229 e6989586621680066230 f6989586621680066231 g6989586621680066232. (~>) ((~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) ((~>) [a6989586621680066226] ((~>) [b6989586621680066227] ((~>) [c6989586621680066228] ((~>) [d6989586621680066229] ((~>) [e6989586621680066230] ((~>) [f6989586621680066231] [g6989586621680066232])))))) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (a6989586621680066226 ~> (b6989586621680066227 ~> (c6989586621680066228 ~> (d6989586621680066229 ~> (e6989586621680066230 ~> (f6989586621680066231 ~> g6989586621680066232)))))) ([a6989586621680066226] ~> ([b6989586621680066227] ~> ([c6989586621680066228] ~> ([d6989586621680066229] ~> ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232])))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym0 :: TyFun (a6989586621680066226 ~> (b6989586621680066227 ~> (c6989586621680066228 ~> (d6989586621680066229 ~> (e6989586621680066230 ~> (f6989586621680066231 ~> g6989586621680066232)))))) ([a6989586621680066226] ~> ([b6989586621680066227] ~> ([c6989586621680066228] ~> ([d6989586621680066229] ~> ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232])))))) -> Type) (a6989586621680078797 :: a6989586621680066226 ~> (b6989586621680066227 ~> (c6989586621680066228 ~> (d6989586621680066229 ~> (e6989586621680066230 ~> (f6989586621680066231 ~> g6989586621680066232)))))) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym0 :: TyFun (a6989586621680066226 ~> (b6989586621680066227 ~> (c6989586621680066228 ~> (d6989586621680066229 ~> (e6989586621680066230 ~> (f6989586621680066231 ~> g6989586621680066232)))))) ([a6989586621680066226] ~> ([b6989586621680066227] ~> ([c6989586621680066228] ~> ([d6989586621680066229] ~> ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232])))))) -> Type) (a6989586621680078797 :: a6989586621680066226 ~> (b6989586621680066227 ~> (c6989586621680066228 ~> (d6989586621680066229 ~> (e6989586621680066230 ~> (f6989586621680066231 ~> g6989586621680066232)))))) = ZipWith6Sym1 a6989586621680078797

data ZipWith6Sym1 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) :: (~>) [a6989586621680066226] ((~>) [b6989586621680066227] ((~>) [c6989586621680066228] ((~>) [d6989586621680066229] ((~>) [e6989586621680066230] ((~>) [f6989586621680066231] [g6989586621680066232]))))) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym1 a6989586621680078797 :: TyFun [a6989586621680066226] ([b6989586621680066227] ~> ([c6989586621680066228] ~> ([d6989586621680066229] ~> ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232]))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym1 a6989586621680078797 :: TyFun [a6989586621680066226] ([b6989586621680066227] ~> ([c6989586621680066228] ~> ([d6989586621680066229] ~> ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232]))))) -> Type) (a6989586621680078798 :: [a6989586621680066226]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym1 a6989586621680078797 :: TyFun [a6989586621680066226] ([b6989586621680066227] ~> ([c6989586621680066228] ~> ([d6989586621680066229] ~> ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232]))))) -> Type) (a6989586621680078798 :: [a6989586621680066226]) = ZipWith6Sym2 a6989586621680078797 a6989586621680078798

data ZipWith6Sym2 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) (a6989586621680078798 :: [a6989586621680066226]) :: (~>) [b6989586621680066227] ((~>) [c6989586621680066228] ((~>) [d6989586621680066229] ((~>) [e6989586621680066230] ((~>) [f6989586621680066231] [g6989586621680066232])))) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym2 a6989586621680078798 a6989586621680078797 :: TyFun [b6989586621680066227] ([c6989586621680066228] ~> ([d6989586621680066229] ~> ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232])))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym2 a6989586621680078798 a6989586621680078797 :: TyFun [b6989586621680066227] ([c6989586621680066228] ~> ([d6989586621680066229] ~> ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232])))) -> Type) (a6989586621680078799 :: [b6989586621680066227]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym2 a6989586621680078798 a6989586621680078797 :: TyFun [b6989586621680066227] ([c6989586621680066228] ~> ([d6989586621680066229] ~> ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232])))) -> Type) (a6989586621680078799 :: [b6989586621680066227]) = ZipWith6Sym3 a6989586621680078798 a6989586621680078797 a6989586621680078799

data ZipWith6Sym3 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) (a6989586621680078798 :: [a6989586621680066226]) (a6989586621680078799 :: [b6989586621680066227]) :: (~>) [c6989586621680066228] ((~>) [d6989586621680066229] ((~>) [e6989586621680066230] ((~>) [f6989586621680066231] [g6989586621680066232]))) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym3 a6989586621680078799 a6989586621680078798 a6989586621680078797 :: TyFun [c6989586621680066228] ([d6989586621680066229] ~> ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232]))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym3 a6989586621680078799 a6989586621680078798 a6989586621680078797 :: TyFun [c6989586621680066228] ([d6989586621680066229] ~> ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232]))) -> Type) (a6989586621680078800 :: [c6989586621680066228]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym3 a6989586621680078799 a6989586621680078798 a6989586621680078797 :: TyFun [c6989586621680066228] ([d6989586621680066229] ~> ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232]))) -> Type) (a6989586621680078800 :: [c6989586621680066228]) = ZipWith6Sym4 a6989586621680078799 a6989586621680078798 a6989586621680078797 a6989586621680078800

data ZipWith6Sym4 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) (a6989586621680078798 :: [a6989586621680066226]) (a6989586621680078799 :: [b6989586621680066227]) (a6989586621680078800 :: [c6989586621680066228]) :: (~>) [d6989586621680066229] ((~>) [e6989586621680066230] ((~>) [f6989586621680066231] [g6989586621680066232])) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym4 a6989586621680078800 a6989586621680078799 a6989586621680078798 a6989586621680078797 :: TyFun [d6989586621680066229] ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym4 a6989586621680078800 a6989586621680078799 a6989586621680078798 a6989586621680078797 :: TyFun [d6989586621680066229] ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232])) -> Type) (a6989586621680078801 :: [d6989586621680066229]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym4 a6989586621680078800 a6989586621680078799 a6989586621680078798 a6989586621680078797 :: TyFun [d6989586621680066229] ([e6989586621680066230] ~> ([f6989586621680066231] ~> [g6989586621680066232])) -> Type) (a6989586621680078801 :: [d6989586621680066229]) = ZipWith6Sym5 a6989586621680078800 a6989586621680078799 a6989586621680078798 a6989586621680078797 a6989586621680078801

data ZipWith6Sym5 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) (a6989586621680078798 :: [a6989586621680066226]) (a6989586621680078799 :: [b6989586621680066227]) (a6989586621680078800 :: [c6989586621680066228]) (a6989586621680078801 :: [d6989586621680066229]) :: (~>) [e6989586621680066230] ((~>) [f6989586621680066231] [g6989586621680066232]) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym5 a6989586621680078801 a6989586621680078800 a6989586621680078799 a6989586621680078798 a6989586621680078797 :: TyFun [e6989586621680066230] ([f6989586621680066231] ~> [g6989586621680066232]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym5 a6989586621680078801 a6989586621680078800 a6989586621680078799 a6989586621680078798 a6989586621680078797 :: TyFun [e6989586621680066230] ([f6989586621680066231] ~> [g6989586621680066232]) -> Type) (a6989586621680078802 :: [e6989586621680066230]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym5 a6989586621680078801 a6989586621680078800 a6989586621680078799 a6989586621680078798 a6989586621680078797 :: TyFun [e6989586621680066230] ([f6989586621680066231] ~> [g6989586621680066232]) -> Type) (a6989586621680078802 :: [e6989586621680066230]) = ZipWith6Sym6 a6989586621680078801 a6989586621680078800 a6989586621680078799 a6989586621680078798 a6989586621680078797 a6989586621680078802

data ZipWith6Sym6 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) (a6989586621680078798 :: [a6989586621680066226]) (a6989586621680078799 :: [b6989586621680066227]) (a6989586621680078800 :: [c6989586621680066228]) (a6989586621680078801 :: [d6989586621680066229]) (a6989586621680078802 :: [e6989586621680066230]) :: (~>) [f6989586621680066231] [g6989586621680066232] Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym6 a6989586621680078802 a6989586621680078801 a6989586621680078800 a6989586621680078799 a6989586621680078798 a6989586621680078797 :: TyFun [f6989586621680066231] [g6989586621680066232] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym6 a6989586621680078802 a6989586621680078801 a6989586621680078800 a6989586621680078799 a6989586621680078798 a6989586621680078797 :: TyFun [f] [g] -> Type) (a6989586621680078803 :: [f]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith6Sym6 a6989586621680078802 a6989586621680078801 a6989586621680078800 a6989586621680078799 a6989586621680078798 a6989586621680078797 :: TyFun [f] [g] -> Type) (a6989586621680078803 :: [f]) = ZipWith6 a6989586621680078802 a6989586621680078801 a6989586621680078800 a6989586621680078799 a6989586621680078798 a6989586621680078797 a6989586621680078803

type ZipWith6Sym7 (a6989586621680078797 :: (~>) a6989586621680066226 ((~>) b6989586621680066227 ((~>) c6989586621680066228 ((~>) d6989586621680066229 ((~>) e6989586621680066230 ((~>) f6989586621680066231 g6989586621680066232)))))) (a6989586621680078798 :: [a6989586621680066226]) (a6989586621680078799 :: [b6989586621680066227]) (a6989586621680078800 :: [c6989586621680066228]) (a6989586621680078801 :: [d6989586621680066229]) (a6989586621680078802 :: [e6989586621680066230]) (a6989586621680078803 :: [f6989586621680066231]) = ZipWith6 a6989586621680078797 a6989586621680078798 a6989586621680078799 a6989586621680078800 a6989586621680078801 a6989586621680078802 a6989586621680078803 Source #

data ZipWith7Sym0 :: forall a6989586621680066218 b6989586621680066219 c6989586621680066220 d6989586621680066221 e6989586621680066222 f6989586621680066223 g6989586621680066224 h6989586621680066225. (~>) ((~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) ((~>) [a6989586621680066218] ((~>) [b6989586621680066219] ((~>) [c6989586621680066220] ((~>) [d6989586621680066221] ((~>) [e6989586621680066222] ((~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225]))))))) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym0 :: TyFun (a6989586621680066218 ~> (b6989586621680066219 ~> (c6989586621680066220 ~> (d6989586621680066221 ~> (e6989586621680066222 ~> (f6989586621680066223 ~> (g6989586621680066224 ~> h6989586621680066225))))))) ([a6989586621680066218] ~> ([b6989586621680066219] ~> ([c6989586621680066220] ~> ([d6989586621680066221] ~> ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225]))))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym0 :: TyFun (a6989586621680066218 ~> (b6989586621680066219 ~> (c6989586621680066220 ~> (d6989586621680066221 ~> (e6989586621680066222 ~> (f6989586621680066223 ~> (g6989586621680066224 ~> h6989586621680066225))))))) ([a6989586621680066218] ~> ([b6989586621680066219] ~> ([c6989586621680066220] ~> ([d6989586621680066221] ~> ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225]))))))) -> Type) (a6989586621680078766 :: a6989586621680066218 ~> (b6989586621680066219 ~> (c6989586621680066220 ~> (d6989586621680066221 ~> (e6989586621680066222 ~> (f6989586621680066223 ~> (g6989586621680066224 ~> h6989586621680066225))))))) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym0 :: TyFun (a6989586621680066218 ~> (b6989586621680066219 ~> (c6989586621680066220 ~> (d6989586621680066221 ~> (e6989586621680066222 ~> (f6989586621680066223 ~> (g6989586621680066224 ~> h6989586621680066225))))))) ([a6989586621680066218] ~> ([b6989586621680066219] ~> ([c6989586621680066220] ~> ([d6989586621680066221] ~> ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225]))))))) -> Type) (a6989586621680078766 :: a6989586621680066218 ~> (b6989586621680066219 ~> (c6989586621680066220 ~> (d6989586621680066221 ~> (e6989586621680066222 ~> (f6989586621680066223 ~> (g6989586621680066224 ~> h6989586621680066225))))))) = ZipWith7Sym1 a6989586621680078766

data ZipWith7Sym1 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) :: (~>) [a6989586621680066218] ((~>) [b6989586621680066219] ((~>) [c6989586621680066220] ((~>) [d6989586621680066221] ((~>) [e6989586621680066222] ((~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225])))))) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym1 a6989586621680078766 :: TyFun [a6989586621680066218] ([b6989586621680066219] ~> ([c6989586621680066220] ~> ([d6989586621680066221] ~> ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225])))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym1 a6989586621680078766 :: TyFun [a6989586621680066218] ([b6989586621680066219] ~> ([c6989586621680066220] ~> ([d6989586621680066221] ~> ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225])))))) -> Type) (a6989586621680078767 :: [a6989586621680066218]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym1 a6989586621680078766 :: TyFun [a6989586621680066218] ([b6989586621680066219] ~> ([c6989586621680066220] ~> ([d6989586621680066221] ~> ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225])))))) -> Type) (a6989586621680078767 :: [a6989586621680066218]) = ZipWith7Sym2 a6989586621680078766 a6989586621680078767

data ZipWith7Sym2 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) :: (~>) [b6989586621680066219] ((~>) [c6989586621680066220] ((~>) [d6989586621680066221] ((~>) [e6989586621680066222] ((~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225]))))) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym2 a6989586621680078767 a6989586621680078766 :: TyFun [b6989586621680066219] ([c6989586621680066220] ~> ([d6989586621680066221] ~> ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225]))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym2 a6989586621680078767 a6989586621680078766 :: TyFun [b6989586621680066219] ([c6989586621680066220] ~> ([d6989586621680066221] ~> ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225]))))) -> Type) (a6989586621680078768 :: [b6989586621680066219]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym2 a6989586621680078767 a6989586621680078766 :: TyFun [b6989586621680066219] ([c6989586621680066220] ~> ([d6989586621680066221] ~> ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225]))))) -> Type) (a6989586621680078768 :: [b6989586621680066219]) = ZipWith7Sym3 a6989586621680078767 a6989586621680078766 a6989586621680078768

data ZipWith7Sym3 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) (a6989586621680078768 :: [b6989586621680066219]) :: (~>) [c6989586621680066220] ((~>) [d6989586621680066221] ((~>) [e6989586621680066222] ((~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225])))) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym3 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [c6989586621680066220] ([d6989586621680066221] ~> ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225])))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym3 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [c6989586621680066220] ([d6989586621680066221] ~> ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225])))) -> Type) (a6989586621680078769 :: [c6989586621680066220]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym3 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [c6989586621680066220] ([d6989586621680066221] ~> ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225])))) -> Type) (a6989586621680078769 :: [c6989586621680066220]) = ZipWith7Sym4 a6989586621680078768 a6989586621680078767 a6989586621680078766 a6989586621680078769

data ZipWith7Sym4 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) (a6989586621680078768 :: [b6989586621680066219]) (a6989586621680078769 :: [c6989586621680066220]) :: (~>) [d6989586621680066221] ((~>) [e6989586621680066222] ((~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225]))) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym4 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [d6989586621680066221] ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225]))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym4 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [d6989586621680066221] ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225]))) -> Type) (a6989586621680078770 :: [d6989586621680066221]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym4 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [d6989586621680066221] ([e6989586621680066222] ~> ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225]))) -> Type) (a6989586621680078770 :: [d6989586621680066221]) = ZipWith7Sym5 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 a6989586621680078770

data ZipWith7Sym5 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) (a6989586621680078768 :: [b6989586621680066219]) (a6989586621680078769 :: [c6989586621680066220]) (a6989586621680078770 :: [d6989586621680066221]) :: (~>) [e6989586621680066222] ((~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225])) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym5 a6989586621680078770 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [e6989586621680066222] ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym5 a6989586621680078770 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [e6989586621680066222] ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225])) -> Type) (a6989586621680078771 :: [e6989586621680066222]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym5 a6989586621680078770 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [e6989586621680066222] ([f6989586621680066223] ~> ([g6989586621680066224] ~> [h6989586621680066225])) -> Type) (a6989586621680078771 :: [e6989586621680066222]) = ZipWith7Sym6 a6989586621680078770 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 a6989586621680078771

data ZipWith7Sym6 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) (a6989586621680078768 :: [b6989586621680066219]) (a6989586621680078769 :: [c6989586621680066220]) (a6989586621680078770 :: [d6989586621680066221]) (a6989586621680078771 :: [e6989586621680066222]) :: (~>) [f6989586621680066223] ((~>) [g6989586621680066224] [h6989586621680066225]) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym6 a6989586621680078771 a6989586621680078770 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [f6989586621680066223] ([g6989586621680066224] ~> [h6989586621680066225]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym6 a6989586621680078771 a6989586621680078770 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [f6989586621680066223] ([g6989586621680066224] ~> [h6989586621680066225]) -> Type) (a6989586621680078772 :: [f6989586621680066223]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym6 a6989586621680078771 a6989586621680078770 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [f6989586621680066223] ([g6989586621680066224] ~> [h6989586621680066225]) -> Type) (a6989586621680078772 :: [f6989586621680066223]) = ZipWith7Sym7 a6989586621680078771 a6989586621680078770 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 a6989586621680078772

data ZipWith7Sym7 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) (a6989586621680078768 :: [b6989586621680066219]) (a6989586621680078769 :: [c6989586621680066220]) (a6989586621680078770 :: [d6989586621680066221]) (a6989586621680078771 :: [e6989586621680066222]) (a6989586621680078772 :: [f6989586621680066223]) :: (~>) [g6989586621680066224] [h6989586621680066225] Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym7 a6989586621680078772 a6989586621680078771 a6989586621680078770 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [g6989586621680066224] [h6989586621680066225] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym7 a6989586621680078772 a6989586621680078771 a6989586621680078770 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [g] [h] -> Type) (a6989586621680078773 :: [g]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ZipWith7Sym7 a6989586621680078772 a6989586621680078771 a6989586621680078770 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 :: TyFun [g] [h] -> Type) (a6989586621680078773 :: [g]) = ZipWith7 a6989586621680078772 a6989586621680078771 a6989586621680078770 a6989586621680078769 a6989586621680078768 a6989586621680078767 a6989586621680078766 a6989586621680078773

type ZipWith7Sym8 (a6989586621680078766 :: (~>) a6989586621680066218 ((~>) b6989586621680066219 ((~>) c6989586621680066220 ((~>) d6989586621680066221 ((~>) e6989586621680066222 ((~>) f6989586621680066223 ((~>) g6989586621680066224 h6989586621680066225))))))) (a6989586621680078767 :: [a6989586621680066218]) (a6989586621680078768 :: [b6989586621680066219]) (a6989586621680078769 :: [c6989586621680066220]) (a6989586621680078770 :: [d6989586621680066221]) (a6989586621680078771 :: [e6989586621680066222]) (a6989586621680078772 :: [f6989586621680066223]) (a6989586621680078773 :: [g6989586621680066224]) = ZipWith7 a6989586621680078766 a6989586621680078767 a6989586621680078768 a6989586621680078769 a6989586621680078770 a6989586621680078771 a6989586621680078772 a6989586621680078773 Source #

data UnzipSym0 :: forall a6989586621679940086 b6989586621679940087. (~>) [(a6989586621679940086, b6989586621679940087)] ([a6989586621679940086], [b6989586621679940087]) Source #

Instances
SingI (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a6989586621679940086, b6989586621679940087)] ([a6989586621679940086], [b6989586621679940087]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679949869 :: [(a, b)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679949869 :: [(a, b)]) = Unzip a6989586621679949869

type UnzipSym1 (a6989586621679949869 :: [(a6989586621679940086, b6989586621679940087)]) = Unzip a6989586621679949869 Source #

data Unzip3Sym0 :: forall a6989586621679940083 b6989586621679940084 c6989586621679940085. (~>) [(a6989586621679940083, b6989586621679940084, c6989586621679940085)] ([a6989586621679940083], [b6989586621679940084], [c6989586621679940085]) Source #

Instances
SingI (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a6989586621679940083, b6989586621679940084, c6989586621679940085)] ([a6989586621679940083], [b6989586621679940084], [c6989586621679940085]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679949848 :: [(a, b, c)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679949848 :: [(a, b, c)]) = Unzip3 a6989586621679949848

type Unzip3Sym1 (a6989586621679949848 :: [(a6989586621679940083, b6989586621679940084, c6989586621679940085)]) = Unzip3 a6989586621679949848 Source #

data Unzip4Sym0 :: forall a6989586621679940079 b6989586621679940080 c6989586621679940081 d6989586621679940082. (~>) [(a6989586621679940079, b6989586621679940080, c6989586621679940081, d6989586621679940082)] ([a6989586621679940079], [b6989586621679940080], [c6989586621679940081], [d6989586621679940082]) Source #

Instances
SingI (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a6989586621679940079, b6989586621679940080, c6989586621679940081, d6989586621679940082)] ([a6989586621679940079], [b6989586621679940080], [c6989586621679940081], [d6989586621679940082]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679949825 :: [(a, b, c, d)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679949825 :: [(a, b, c, d)]) = Unzip4 a6989586621679949825

type Unzip4Sym1 (a6989586621679949825 :: [(a6989586621679940079, b6989586621679940080, c6989586621679940081, d6989586621679940082)]) = Unzip4 a6989586621679949825 Source #

data Unzip5Sym0 :: forall a6989586621679940074 b6989586621679940075 c6989586621679940076 d6989586621679940077 e6989586621679940078. (~>) [(a6989586621679940074, b6989586621679940075, c6989586621679940076, d6989586621679940077, e6989586621679940078)] ([a6989586621679940074], [b6989586621679940075], [c6989586621679940076], [d6989586621679940077], [e6989586621679940078]) Source #

Instances
SingI (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a6989586621679940074, b6989586621679940075, c6989586621679940076, d6989586621679940077, e6989586621679940078)] ([a6989586621679940074], [b6989586621679940075], [c6989586621679940076], [d6989586621679940077], [e6989586621679940078]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679949800 :: [(a, b, c, d, e)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679949800 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679949800

type Unzip5Sym1 (a6989586621679949800 :: [(a6989586621679940074, b6989586621679940075, c6989586621679940076, d6989586621679940077, e6989586621679940078)]) = Unzip5 a6989586621679949800 Source #

data Unzip6Sym0 :: forall a6989586621679940068 b6989586621679940069 c6989586621679940070 d6989586621679940071 e6989586621679940072 f6989586621679940073. (~>) [(a6989586621679940068, b6989586621679940069, c6989586621679940070, d6989586621679940071, e6989586621679940072, f6989586621679940073)] ([a6989586621679940068], [b6989586621679940069], [c6989586621679940070], [d6989586621679940071], [e6989586621679940072], [f6989586621679940073]) Source #

Instances
SingI (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a6989586621679940068, b6989586621679940069, c6989586621679940070, d6989586621679940071, e6989586621679940072, f6989586621679940073)] ([a6989586621679940068], [b6989586621679940069], [c6989586621679940070], [d6989586621679940071], [e6989586621679940072], [f6989586621679940073]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679949773 :: [(a, b, c, d, e, f)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679949773 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679949773

type Unzip6Sym1 (a6989586621679949773 :: [(a6989586621679940068, b6989586621679940069, c6989586621679940070, d6989586621679940071, e6989586621679940072, f6989586621679940073)]) = Unzip6 a6989586621679949773 Source #

data Unzip7Sym0 :: forall a6989586621679940061 b6989586621679940062 c6989586621679940063 d6989586621679940064 e6989586621679940065 f6989586621679940066 g6989586621679940067. (~>) [(a6989586621679940061, b6989586621679940062, c6989586621679940063, d6989586621679940064, e6989586621679940065, f6989586621679940066, g6989586621679940067)] ([a6989586621679940061], [b6989586621679940062], [c6989586621679940063], [d6989586621679940064], [e6989586621679940065], [f6989586621679940066], [g6989586621679940067]) Source #

Instances
SingI (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a6989586621679940061, b6989586621679940062, c6989586621679940063, d6989586621679940064, e6989586621679940065, f6989586621679940066, g6989586621679940067)] ([a6989586621679940061], [b6989586621679940062], [c6989586621679940063], [d6989586621679940064], [e6989586621679940065], [f6989586621679940066], [g6989586621679940067]) -> Type) Source # 
Instance details

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) (a6989586621679949744 :: [(a, b, c, d, e, f, g)]) Source # 
Instance details

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) (a6989586621679949744 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679949744

type Unzip7Sym1 (a6989586621679949744 :: [(a6989586621679940061, b6989586621679940062, c6989586621679940063, d6989586621679940064, e6989586621679940065, f6989586621679940066, g6989586621679940067)]) = Unzip7 a6989586621679949744 Source #

data UnlinesSym0 :: (~>) [Symbol] Symbol Source #

Instances
SingI UnlinesSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings UnlinesSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply UnlinesSym0 (a6989586621679949740 :: [Symbol]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply UnlinesSym0 (a6989586621679949740 :: [Symbol]) = Unlines a6989586621679949740

type UnlinesSym1 (a6989586621679949740 :: [Symbol]) = Unlines a6989586621679949740 Source #

data UnwordsSym0 :: (~>) [Symbol] Symbol Source #

Instances
SingI UnwordsSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings UnwordsSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply UnwordsSym0 (a6989586621679949729 :: [Symbol]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply UnwordsSym0 (a6989586621679949729 :: [Symbol]) = Unwords a6989586621679949729

type UnwordsSym1 (a6989586621679949729 :: [Symbol]) = Unwords a6989586621679949729 Source #

data NubSym0 :: forall a6989586621679940020. (~>) [a6989586621679940020] [a6989586621679940020] Source #

Instances
SEq a => SingI (NubSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (NubSym0 :: TyFun [a6989586621679940020] [a6989586621679940020] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NubSym0 :: TyFun [a] [a] -> Type) (a6989586621679949998 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NubSym0 :: TyFun [a] [a] -> Type) (a6989586621679949998 :: [a]) = Nub a6989586621679949998

type NubSym1 (a6989586621679949998 :: [a6989586621679940020]) = Nub a6989586621679949998 Source #

data DeleteSym0 :: forall a6989586621679940060. (~>) a6989586621679940060 ((~>) [a6989586621679940060] [a6989586621679940060]) Source #

Instances
SEq a => SingI (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DeleteSym0 :: TyFun a6989586621679940060 ([a6989586621679940060] ~> [a6989586621679940060]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteSym0 :: TyFun a6989586621679940060 ([a6989586621679940060] ~> [a6989586621679940060]) -> Type) (a6989586621679949713 :: a6989586621679940060) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteSym0 :: TyFun a6989586621679940060 ([a6989586621679940060] ~> [a6989586621679940060]) -> Type) (a6989586621679949713 :: a6989586621679940060) = DeleteSym1 a6989586621679949713

data DeleteSym1 (a6989586621679949713 :: a6989586621679940060) :: (~>) [a6989586621679940060] [a6989586621679940060] Source #

Instances
(SEq a, SingI d) => SingI (DeleteSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (DeleteSym1 d) Source #

SuppressUnusedWarnings (DeleteSym1 a6989586621679949713 :: TyFun [a6989586621679940060] [a6989586621679940060] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteSym1 a6989586621679949713 :: TyFun [a] [a] -> Type) (a6989586621679949714 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteSym1 a6989586621679949713 :: TyFun [a] [a] -> Type) (a6989586621679949714 :: [a]) = Delete a6989586621679949713 a6989586621679949714

type DeleteSym2 (a6989586621679949713 :: a6989586621679940060) (a6989586621679949714 :: [a6989586621679940060]) = Delete a6989586621679949713 a6989586621679949714 Source #

data (\\@#@$) :: forall a6989586621679940059. (~>) [a6989586621679940059] ((~>) [a6989586621679940059] [a6989586621679940059]) infix 5 Source #

Instances
SEq a => SingI ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings ((\\@#@$) :: TyFun [a6989586621679940059] ([a6989586621679940059] ~> [a6989586621679940059]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply ((\\@#@$) :: TyFun [a6989586621679940059] ([a6989586621679940059] ~> [a6989586621679940059]) -> Type) (a6989586621679949723 :: [a6989586621679940059]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply ((\\@#@$) :: TyFun [a6989586621679940059] ([a6989586621679940059] ~> [a6989586621679940059]) -> Type) (a6989586621679949723 :: [a6989586621679940059]) = (\\@#@$$) a6989586621679949723

data (\\@#@$$) (a6989586621679949723 :: [a6989586621679940059]) :: (~>) [a6989586621679940059] [a6989586621679940059] infix 5 Source #

Instances
(SEq a, SingI d) => SingI ((\\@#@$$) d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing ((\\@#@$$) d) Source #

SuppressUnusedWarnings ((\\@#@$$) a6989586621679949723 :: TyFun [a6989586621679940059] [a6989586621679940059] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply ((\\@#@$$) a6989586621679949723 :: TyFun [a] [a] -> Type) (a6989586621679949724 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply ((\\@#@$$) a6989586621679949723 :: TyFun [a] [a] -> Type) (a6989586621679949724 :: [a]) = a6989586621679949723 \\ a6989586621679949724

type (\\@#@$$$) (a6989586621679949723 :: [a6989586621679940059]) (a6989586621679949724 :: [a6989586621679940059]) = (\\) a6989586621679949723 a6989586621679949724 Source #

data UnionSym0 :: forall a6989586621679940016. (~>) [a6989586621679940016] ((~>) [a6989586621679940016] [a6989586621679940016]) Source #

Instances
SEq a => SingI (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (UnionSym0 :: TyFun [a6989586621679940016] ([a6989586621679940016] ~> [a6989586621679940016]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionSym0 :: TyFun [a6989586621679940016] ([a6989586621679940016] ~> [a6989586621679940016]) -> Type) (a6989586621679949703 :: [a6989586621679940016]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionSym0 :: TyFun [a6989586621679940016] ([a6989586621679940016] ~> [a6989586621679940016]) -> Type) (a6989586621679949703 :: [a6989586621679940016]) = UnionSym1 a6989586621679949703

data UnionSym1 (a6989586621679949703 :: [a6989586621679940016]) :: (~>) [a6989586621679940016] [a6989586621679940016] Source #

Instances
(SEq a, SingI d) => SingI (UnionSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (UnionSym1 d) Source #

SuppressUnusedWarnings (UnionSym1 a6989586621679949703 :: TyFun [a6989586621679940016] [a6989586621679940016] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionSym1 a6989586621679949703 :: TyFun [a] [a] -> Type) (a6989586621679949704 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionSym1 a6989586621679949703 :: TyFun [a] [a] -> Type) (a6989586621679949704 :: [a]) = Union a6989586621679949703 a6989586621679949704

type UnionSym2 (a6989586621679949703 :: [a6989586621679940016]) (a6989586621679949704 :: [a6989586621679940016]) = Union a6989586621679949703 a6989586621679949704 Source #

data IntersectSym0 :: forall a6989586621679940046. (~>) [a6989586621679940046] ((~>) [a6989586621679940046] [a6989586621679940046]) Source #

Instances
SEq a => SingI (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntersectSym0 :: TyFun [a6989586621679940046] ([a6989586621679940046] ~> [a6989586621679940046]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectSym0 :: TyFun [a6989586621679940046] ([a6989586621679940046] ~> [a6989586621679940046]) -> Type) (a6989586621679950298 :: [a6989586621679940046]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectSym0 :: TyFun [a6989586621679940046] ([a6989586621679940046] ~> [a6989586621679940046]) -> Type) (a6989586621679950298 :: [a6989586621679940046]) = IntersectSym1 a6989586621679950298

data IntersectSym1 (a6989586621679950298 :: [a6989586621679940046]) :: (~>) [a6989586621679940046] [a6989586621679940046] Source #

Instances
(SEq a, SingI d) => SingI (IntersectSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntersectSym1 a6989586621679950298 :: TyFun [a6989586621679940046] [a6989586621679940046] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectSym1 a6989586621679950298 :: TyFun [a] [a] -> Type) (a6989586621679950299 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectSym1 a6989586621679950298 :: TyFun [a] [a] -> Type) (a6989586621679950299 :: [a]) = Intersect a6989586621679950298 a6989586621679950299

type IntersectSym2 (a6989586621679950298 :: [a6989586621679940046]) (a6989586621679950299 :: [a6989586621679940046]) = Intersect a6989586621679950298 a6989586621679950299 Source #

data InsertSym0 :: forall a6989586621679940033. (~>) a6989586621679940033 ((~>) [a6989586621679940033] [a6989586621679940033]) Source #

Instances
SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621679940033 ([a6989586621679940033] ~> [a6989586621679940033]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InsertSym0 :: TyFun a6989586621679940033 ([a6989586621679940033] ~> [a6989586621679940033]) -> Type) (a6989586621679949640 :: a6989586621679940033) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InsertSym0 :: TyFun a6989586621679940033 ([a6989586621679940033] ~> [a6989586621679940033]) -> Type) (a6989586621679949640 :: a6989586621679940033) = InsertSym1 a6989586621679949640

data InsertSym1 (a6989586621679949640 :: a6989586621679940033) :: (~>) [a6989586621679940033] [a6989586621679940033] Source #

Instances
(SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (InsertSym1 d) Source #

SuppressUnusedWarnings (InsertSym1 a6989586621679949640 :: TyFun [a6989586621679940033] [a6989586621679940033] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InsertSym1 a6989586621679949640 :: TyFun [a] [a] -> Type) (a6989586621679949641 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InsertSym1 a6989586621679949640 :: TyFun [a] [a] -> Type) (a6989586621679949641 :: [a]) = Insert a6989586621679949640 a6989586621679949641

type InsertSym2 (a6989586621679949640 :: a6989586621679940033) (a6989586621679949641 :: [a6989586621679940033]) = Insert a6989586621679949640 a6989586621679949641 Source #

data SortSym0 :: forall a6989586621679940032. (~>) [a6989586621679940032] [a6989586621679940032] Source #

Instances
SOrd a => SingI (SortSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (SortSym0 :: TyFun [a6989586621679940032] [a6989586621679940032] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SortSym0 :: TyFun [a] [a] -> Type) (a6989586621679949656 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SortSym0 :: TyFun [a] [a] -> Type) (a6989586621679949656 :: [a]) = Sort a6989586621679949656

type SortSym1 (a6989586621679949656 :: [a6989586621679940032]) = Sort a6989586621679949656 Source #

data NubBySym0 :: forall a6989586621679940019. (~>) ((~>) a6989586621679940019 ((~>) a6989586621679940019 Bool)) ((~>) [a6989586621679940019] [a6989586621679940019]) Source #

Instances
SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (NubBySym0 :: TyFun (a6989586621679940019 ~> (a6989586621679940019 ~> Bool)) ([a6989586621679940019] ~> [a6989586621679940019]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NubBySym0 :: TyFun (a6989586621679940019 ~> (a6989586621679940019 ~> Bool)) ([a6989586621679940019] ~> [a6989586621679940019]) -> Type) (a6989586621679949286 :: a6989586621679940019 ~> (a6989586621679940019 ~> Bool)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NubBySym0 :: TyFun (a6989586621679940019 ~> (a6989586621679940019 ~> Bool)) ([a6989586621679940019] ~> [a6989586621679940019]) -> Type) (a6989586621679949286 :: a6989586621679940019 ~> (a6989586621679940019 ~> Bool)) = NubBySym1 a6989586621679949286

data NubBySym1 (a6989586621679949286 :: (~>) a6989586621679940019 ((~>) a6989586621679940019 Bool)) :: (~>) [a6989586621679940019] [a6989586621679940019] Source #

Instances
SingI d => SingI (NubBySym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (NubBySym1 d) Source #

SuppressUnusedWarnings (NubBySym1 a6989586621679949286 :: TyFun [a6989586621679940019] [a6989586621679940019] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NubBySym1 a6989586621679949286 :: TyFun [a] [a] -> Type) (a6989586621679949287 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NubBySym1 a6989586621679949286 :: TyFun [a] [a] -> Type) (a6989586621679949287 :: [a]) = NubBy a6989586621679949286 a6989586621679949287

type NubBySym2 (a6989586621679949286 :: (~>) a6989586621679940019 ((~>) a6989586621679940019 Bool)) (a6989586621679949287 :: [a6989586621679940019]) = NubBy a6989586621679949286 a6989586621679949287 Source #

data DeleteBySym0 :: forall a6989586621679940058. (~>) ((~>) a6989586621679940058 ((~>) a6989586621679940058 Bool)) ((~>) a6989586621679940058 ((~>) [a6989586621679940058] [a6989586621679940058])) Source #

Instances
SingI (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DeleteBySym0 :: TyFun (a6989586621679940058 ~> (a6989586621679940058 ~> Bool)) (a6989586621679940058 ~> ([a6989586621679940058] ~> [a6989586621679940058])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteBySym0 :: TyFun (a6989586621679940058 ~> (a6989586621679940058 ~> Bool)) (a6989586621679940058 ~> ([a6989586621679940058] ~> [a6989586621679940058])) -> Type) (a6989586621679949659 :: a6989586621679940058 ~> (a6989586621679940058 ~> Bool)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteBySym0 :: TyFun (a6989586621679940058 ~> (a6989586621679940058 ~> Bool)) (a6989586621679940058 ~> ([a6989586621679940058] ~> [a6989586621679940058])) -> Type) (a6989586621679949659 :: a6989586621679940058 ~> (a6989586621679940058 ~> Bool)) = DeleteBySym1 a6989586621679949659

data DeleteBySym1 (a6989586621679949659 :: (~>) a6989586621679940058 ((~>) a6989586621679940058 Bool)) :: (~>) a6989586621679940058 ((~>) [a6989586621679940058] [a6989586621679940058]) Source #

Instances
SingI d => SingI (DeleteBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (DeleteBySym1 d) Source #

SuppressUnusedWarnings (DeleteBySym1 a6989586621679949659 :: TyFun a6989586621679940058 ([a6989586621679940058] ~> [a6989586621679940058]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteBySym1 a6989586621679949659 :: TyFun a6989586621679940058 ([a6989586621679940058] ~> [a6989586621679940058]) -> Type) (a6989586621679949660 :: a6989586621679940058) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteBySym1 a6989586621679949659 :: TyFun a6989586621679940058 ([a6989586621679940058] ~> [a6989586621679940058]) -> Type) (a6989586621679949660 :: a6989586621679940058) = DeleteBySym2 a6989586621679949659 a6989586621679949660

data DeleteBySym2 (a6989586621679949659 :: (~>) a6989586621679940058 ((~>) a6989586621679940058 Bool)) (a6989586621679949660 :: a6989586621679940058) :: (~>) [a6989586621679940058] [a6989586621679940058] Source #

Instances
(SingI d1, SingI d2) => SingI (DeleteBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (DeleteBySym2 d1 d2) Source #

SuppressUnusedWarnings (DeleteBySym2 a6989586621679949660 a6989586621679949659 :: TyFun [a6989586621679940058] [a6989586621679940058] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteBySym2 a6989586621679949660 a6989586621679949659 :: TyFun [a] [a] -> Type) (a6989586621679949661 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteBySym2 a6989586621679949660 a6989586621679949659 :: TyFun [a] [a] -> Type) (a6989586621679949661 :: [a]) = DeleteBy a6989586621679949660 a6989586621679949659 a6989586621679949661

type DeleteBySym3 (a6989586621679949659 :: (~>) a6989586621679940058 ((~>) a6989586621679940058 Bool)) (a6989586621679949660 :: a6989586621679940058) (a6989586621679949661 :: [a6989586621679940058]) = DeleteBy a6989586621679949659 a6989586621679949660 a6989586621679949661 Source #

data DeleteFirstsBySym0 :: forall a6989586621679940057. (~>) ((~>) a6989586621679940057 ((~>) a6989586621679940057 Bool)) ((~>) [a6989586621679940057] ((~>) [a6989586621679940057] [a6989586621679940057])) Source #

Instances
SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (a6989586621679940057 ~> (a6989586621679940057 ~> Bool)) ([a6989586621679940057] ~> ([a6989586621679940057] ~> [a6989586621679940057])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679940057 ~> (a6989586621679940057 ~> Bool)) ([a6989586621679940057] ~> ([a6989586621679940057] ~> [a6989586621679940057])) -> Type) (a6989586621679949677 :: a6989586621679940057 ~> (a6989586621679940057 ~> Bool)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679940057 ~> (a6989586621679940057 ~> Bool)) ([a6989586621679940057] ~> ([a6989586621679940057] ~> [a6989586621679940057])) -> Type) (a6989586621679949677 :: a6989586621679940057 ~> (a6989586621679940057 ~> Bool)) = DeleteFirstsBySym1 a6989586621679949677

data DeleteFirstsBySym1 (a6989586621679949677 :: (~>) a6989586621679940057 ((~>) a6989586621679940057 Bool)) :: (~>) [a6989586621679940057] ((~>) [a6989586621679940057] [a6989586621679940057]) Source #

Instances
SingI d => SingI (DeleteFirstsBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DeleteFirstsBySym1 a6989586621679949677 :: TyFun [a6989586621679940057] ([a6989586621679940057] ~> [a6989586621679940057]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteFirstsBySym1 a6989586621679949677 :: TyFun [a6989586621679940057] ([a6989586621679940057] ~> [a6989586621679940057]) -> Type) (a6989586621679949678 :: [a6989586621679940057]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteFirstsBySym1 a6989586621679949677 :: TyFun [a6989586621679940057] ([a6989586621679940057] ~> [a6989586621679940057]) -> Type) (a6989586621679949678 :: [a6989586621679940057]) = DeleteFirstsBySym2 a6989586621679949677 a6989586621679949678

data DeleteFirstsBySym2 (a6989586621679949677 :: (~>) a6989586621679940057 ((~>) a6989586621679940057 Bool)) (a6989586621679949678 :: [a6989586621679940057]) :: (~>) [a6989586621679940057] [a6989586621679940057] Source #

Instances
(SingI d1, SingI d2) => SingI (DeleteFirstsBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (DeleteFirstsBySym2 d1 d2) Source #

SuppressUnusedWarnings (DeleteFirstsBySym2 a6989586621679949678 a6989586621679949677 :: TyFun [a6989586621679940057] [a6989586621679940057] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteFirstsBySym2 a6989586621679949678 a6989586621679949677 :: TyFun [a] [a] -> Type) (a6989586621679949679 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteFirstsBySym2 a6989586621679949678 a6989586621679949677 :: TyFun [a] [a] -> Type) (a6989586621679949679 :: [a]) = DeleteFirstsBy a6989586621679949678 a6989586621679949677 a6989586621679949679

type DeleteFirstsBySym3 (a6989586621679949677 :: (~>) a6989586621679940057 ((~>) a6989586621679940057 Bool)) (a6989586621679949678 :: [a6989586621679940057]) (a6989586621679949679 :: [a6989586621679940057]) = DeleteFirstsBy a6989586621679949677 a6989586621679949678 a6989586621679949679 Source #

data UnionBySym0 :: forall a6989586621679940017. (~>) ((~>) a6989586621679940017 ((~>) a6989586621679940017 Bool)) ((~>) [a6989586621679940017] ((~>) [a6989586621679940017] [a6989586621679940017])) Source #

Instances
SingI (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (UnionBySym0 :: TyFun (a6989586621679940017 ~> (a6989586621679940017 ~> Bool)) ([a6989586621679940017] ~> ([a6989586621679940017] ~> [a6989586621679940017])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionBySym0 :: TyFun (a6989586621679940017 ~> (a6989586621679940017 ~> Bool)) ([a6989586621679940017] ~> ([a6989586621679940017] ~> [a6989586621679940017])) -> Type) (a6989586621679949690 :: a6989586621679940017 ~> (a6989586621679940017 ~> Bool)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionBySym0 :: TyFun (a6989586621679940017 ~> (a6989586621679940017 ~> Bool)) ([a6989586621679940017] ~> ([a6989586621679940017] ~> [a6989586621679940017])) -> Type) (a6989586621679949690 :: a6989586621679940017 ~> (a6989586621679940017 ~> Bool)) = UnionBySym1 a6989586621679949690

data UnionBySym1 (a6989586621679949690 :: (~>) a6989586621679940017 ((~>) a6989586621679940017 Bool)) :: (~>) [a6989586621679940017] ((~>) [a6989586621679940017] [a6989586621679940017]) Source #

Instances
SingI d => SingI (UnionBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (UnionBySym1 d) Source #

SuppressUnusedWarnings (UnionBySym1 a6989586621679949690 :: TyFun [a6989586621679940017] ([a6989586621679940017] ~> [a6989586621679940017]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionBySym1 a6989586621679949690 :: TyFun [a6989586621679940017] ([a6989586621679940017] ~> [a6989586621679940017]) -> Type) (a6989586621679949691 :: [a6989586621679940017]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionBySym1 a6989586621679949690 :: TyFun [a6989586621679940017] ([a6989586621679940017] ~> [a6989586621679940017]) -> Type) (a6989586621679949691 :: [a6989586621679940017]) = UnionBySym2 a6989586621679949690 a6989586621679949691

data UnionBySym2 (a6989586621679949690 :: (~>) a6989586621679940017 ((~>) a6989586621679940017 Bool)) (a6989586621679949691 :: [a6989586621679940017]) :: (~>) [a6989586621679940017] [a6989586621679940017] Source #

Instances
(SingI d1, SingI d2) => SingI (UnionBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (UnionBySym2 d1 d2) Source #

SuppressUnusedWarnings (UnionBySym2 a6989586621679949691 a6989586621679949690 :: TyFun [a6989586621679940017] [a6989586621679940017] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionBySym2 a6989586621679949691 a6989586621679949690 :: TyFun [a] [a] -> Type) (a6989586621679949692 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionBySym2 a6989586621679949691 a6989586621679949690 :: TyFun [a] [a] -> Type) (a6989586621679949692 :: [a]) = UnionBy a6989586621679949691 a6989586621679949690 a6989586621679949692

type UnionBySym3 (a6989586621679949690 :: (~>) a6989586621679940017 ((~>) a6989586621679940017 Bool)) (a6989586621679949691 :: [a6989586621679940017]) (a6989586621679949692 :: [a6989586621679940017]) = UnionBy a6989586621679949690 a6989586621679949691 a6989586621679949692 Source #

data IntersectBySym0 :: forall a6989586621679940045. (~>) ((~>) a6989586621679940045 ((~>) a6989586621679940045 Bool)) ((~>) [a6989586621679940045] ((~>) [a6989586621679940045] [a6989586621679940045])) Source #

Instances
SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntersectBySym0 :: TyFun (a6989586621679940045 ~> (a6989586621679940045 ~> Bool)) ([a6989586621679940045] ~> ([a6989586621679940045] ~> [a6989586621679940045])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectBySym0 :: TyFun (a6989586621679940045 ~> (a6989586621679940045 ~> Bool)) ([a6989586621679940045] ~> ([a6989586621679940045] ~> [a6989586621679940045])) -> Type) (a6989586621679950262 :: a6989586621679940045 ~> (a6989586621679940045 ~> Bool)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectBySym0 :: TyFun (a6989586621679940045 ~> (a6989586621679940045 ~> Bool)) ([a6989586621679940045] ~> ([a6989586621679940045] ~> [a6989586621679940045])) -> Type) (a6989586621679950262 :: a6989586621679940045 ~> (a6989586621679940045 ~> Bool)) = IntersectBySym1 a6989586621679950262

data IntersectBySym1 (a6989586621679950262 :: (~>) a6989586621679940045 ((~>) a6989586621679940045 Bool)) :: (~>) [a6989586621679940045] ((~>) [a6989586621679940045] [a6989586621679940045]) Source #

Instances
SingI d => SingI (IntersectBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntersectBySym1 a6989586621679950262 :: TyFun [a6989586621679940045] ([a6989586621679940045] ~> [a6989586621679940045]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectBySym1 a6989586621679950262 :: TyFun [a6989586621679940045] ([a6989586621679940045] ~> [a6989586621679940045]) -> Type) (a6989586621679950263 :: [a6989586621679940045]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectBySym1 a6989586621679950262 :: TyFun [a6989586621679940045] ([a6989586621679940045] ~> [a6989586621679940045]) -> Type) (a6989586621679950263 :: [a6989586621679940045]) = IntersectBySym2 a6989586621679950262 a6989586621679950263

data IntersectBySym2 (a6989586621679950262 :: (~>) a6989586621679940045 ((~>) a6989586621679940045 Bool)) (a6989586621679950263 :: [a6989586621679940045]) :: (~>) [a6989586621679940045] [a6989586621679940045] Source #

Instances
(SingI d1, SingI d2) => SingI (IntersectBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (IntersectBySym2 d1 d2) Source #

SuppressUnusedWarnings (IntersectBySym2 a6989586621679950263 a6989586621679950262 :: TyFun [a6989586621679940045] [a6989586621679940045] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectBySym2 a6989586621679950263 a6989586621679950262 :: TyFun [a] [a] -> Type) (a6989586621679950264 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectBySym2 a6989586621679950263 a6989586621679950262 :: TyFun [a] [a] -> Type) (a6989586621679950264 :: [a]) = IntersectBy a6989586621679950263 a6989586621679950262 a6989586621679950264

type IntersectBySym3 (a6989586621679950262 :: (~>) a6989586621679940045 ((~>) a6989586621679940045 Bool)) (a6989586621679950263 :: [a6989586621679940045]) (a6989586621679950264 :: [a6989586621679940045]) = IntersectBy a6989586621679950262 a6989586621679950263 a6989586621679950264 Source #

data GroupBySym0 :: forall a6989586621679940031. (~>) ((~>) a6989586621679940031 ((~>) a6989586621679940031 Bool)) ((~>) [a6989586621679940031] [[a6989586621679940031]]) Source #

Instances
SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (GroupBySym0 :: TyFun (a6989586621679940031 ~> (a6989586621679940031 ~> Bool)) ([a6989586621679940031] ~> [[a6989586621679940031]]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GroupBySym0 :: TyFun (a6989586621679940031 ~> (a6989586621679940031 ~> Bool)) ([a6989586621679940031] ~> [[a6989586621679940031]]) -> Type) (a6989586621679949527 :: a6989586621679940031 ~> (a6989586621679940031 ~> Bool)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GroupBySym0 :: TyFun (a6989586621679940031 ~> (a6989586621679940031 ~> Bool)) ([a6989586621679940031] ~> [[a6989586621679940031]]) -> Type) (a6989586621679949527 :: a6989586621679940031 ~> (a6989586621679940031 ~> Bool)) = GroupBySym1 a6989586621679949527

data GroupBySym1 (a6989586621679949527 :: (~>) a6989586621679940031 ((~>) a6989586621679940031 Bool)) :: (~>) [a6989586621679940031] [[a6989586621679940031]] Source #

Instances
SingI d => SingI (GroupBySym1 d :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (GroupBySym1 d) Source #

SuppressUnusedWarnings (GroupBySym1 a6989586621679949527 :: TyFun [a6989586621679940031] [[a6989586621679940031]] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GroupBySym1 a6989586621679949527 :: TyFun [a] [[a]] -> Type) (a6989586621679949528 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GroupBySym1 a6989586621679949527 :: TyFun [a] [[a]] -> Type) (a6989586621679949528 :: [a]) = GroupBy a6989586621679949527 a6989586621679949528

type GroupBySym2 (a6989586621679949527 :: (~>) a6989586621679940031 ((~>) a6989586621679940031 Bool)) (a6989586621679949528 :: [a6989586621679940031]) = GroupBy a6989586621679949527 a6989586621679949528 Source #

data SortBySym0 :: forall a6989586621679940056. (~>) ((~>) a6989586621679940056 ((~>) a6989586621679940056 Ordering)) ((~>) [a6989586621679940056] [a6989586621679940056]) Source #

Instances
SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (SortBySym0 :: TyFun (a6989586621679940056 ~> (a6989586621679940056 ~> Ordering)) ([a6989586621679940056] ~> [a6989586621679940056]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SortBySym0 :: TyFun (a6989586621679940056 ~> (a6989586621679940056 ~> Ordering)) ([a6989586621679940056] ~> [a6989586621679940056]) -> Type) (a6989586621679949646 :: a6989586621679940056 ~> (a6989586621679940056 ~> Ordering)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SortBySym0 :: TyFun (a6989586621679940056 ~> (a6989586621679940056 ~> Ordering)) ([a6989586621679940056] ~> [a6989586621679940056]) -> Type) (a6989586621679949646 :: a6989586621679940056 ~> (a6989586621679940056 ~> Ordering)) = SortBySym1 a6989586621679949646

data SortBySym1 (a6989586621679949646 :: (~>) a6989586621679940056 ((~>) a6989586621679940056 Ordering)) :: (~>) [a6989586621679940056] [a6989586621679940056] Source #

Instances
SingI d => SingI (SortBySym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (SortBySym1 d) Source #

SuppressUnusedWarnings (SortBySym1 a6989586621679949646 :: TyFun [a6989586621679940056] [a6989586621679940056] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SortBySym1 a6989586621679949646 :: TyFun [a] [a] -> Type) (a6989586621679949647 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SortBySym1 a6989586621679949646 :: TyFun [a] [a] -> Type) (a6989586621679949647 :: [a]) = SortBy a6989586621679949646 a6989586621679949647

type SortBySym2 (a6989586621679949646 :: (~>) a6989586621679940056 ((~>) a6989586621679940056 Ordering)) (a6989586621679949647 :: [a6989586621679940056]) = SortBy a6989586621679949646 a6989586621679949647 Source #

data InsertBySym0 :: forall a6989586621679940055. (~>) ((~>) a6989586621679940055 ((~>) a6989586621679940055 Ordering)) ((~>) a6989586621679940055 ((~>) [a6989586621679940055] [a6989586621679940055])) Source #

Instances
SingI (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (InsertBySym0 :: TyFun (a6989586621679940055 ~> (a6989586621679940055 ~> Ordering)) (a6989586621679940055 ~> ([a6989586621679940055] ~> [a6989586621679940055])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InsertBySym0 :: TyFun (a6989586621679940055 ~> (a6989586621679940055 ~> Ordering)) (a6989586621679940055 ~> ([a6989586621679940055] ~> [a6989586621679940055])) -> Type) (a6989586621679949616 :: a6989586621679940055 ~> (a6989586621679940055 ~> Ordering)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InsertBySym0 :: TyFun (a6989586621679940055 ~> (a6989586621679940055 ~> Ordering)) (a6989586621679940055 ~> ([a6989586621679940055] ~> [a6989586621679940055])) -> Type) (a6989586621679949616 :: a6989586621679940055 ~> (a6989586621679940055 ~> Ordering)) = InsertBySym1 a6989586621679949616

data InsertBySym1 (a6989586621679949616 :: (~>) a6989586621679940055 ((~>) a6989586621679940055 Ordering)) :: (~>) a6989586621679940055 ((~>) [a6989586621679940055] [a6989586621679940055]) Source #

Instances
SingI d => SingI (InsertBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (InsertBySym1 d) Source #

SuppressUnusedWarnings (InsertBySym1 a6989586621679949616 :: TyFun a6989586621679940055 ([a6989586621679940055] ~> [a6989586621679940055]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InsertBySym1 a6989586621679949616 :: TyFun a6989586621679940055 ([a6989586621679940055] ~> [a6989586621679940055]) -> Type) (a6989586621679949617 :: a6989586621679940055) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InsertBySym1 a6989586621679949616 :: TyFun a6989586621679940055 ([a6989586621679940055] ~> [a6989586621679940055]) -> Type) (a6989586621679949617 :: a6989586621679940055) = InsertBySym2 a6989586621679949616 a6989586621679949617

data InsertBySym2 (a6989586621679949616 :: (~>) a6989586621679940055 ((~>) a6989586621679940055 Ordering)) (a6989586621679949617 :: a6989586621679940055) :: (~>) [a6989586621679940055] [a6989586621679940055] Source #

Instances
(SingI d1, SingI d2) => SingI (InsertBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (InsertBySym2 d1 d2) Source #

SuppressUnusedWarnings (InsertBySym2 a6989586621679949617 a6989586621679949616 :: TyFun [a6989586621679940055] [a6989586621679940055] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InsertBySym2 a6989586621679949617 a6989586621679949616 :: TyFun [a] [a] -> Type) (a6989586621679949618 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (InsertBySym2 a6989586621679949617 a6989586621679949616 :: TyFun [a] [a] -> Type) (a6989586621679949618 :: [a]) = InsertBy a6989586621679949617 a6989586621679949616 a6989586621679949618

type InsertBySym3 (a6989586621679949616 :: (~>) a6989586621679940055 ((~>) a6989586621679940055 Ordering)) (a6989586621679949617 :: a6989586621679940055) (a6989586621679949618 :: [a6989586621679940055]) = InsertBy a6989586621679949616 a6989586621679949617 a6989586621679949618 Source #

data MaximumBySym0 :: forall a6989586621680452638 t6989586621680452637. (~>) ((~>) a6989586621680452638 ((~>) a6989586621680452638 Ordering)) ((~>) (t6989586621680452637 a6989586621680452638) a6989586621680452638) Source #

Instances
SFoldable t => SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MaximumBySym0 :: TyFun (a6989586621680452638 ~> (a6989586621680452638 ~> Ordering)) (t6989586621680452637 a6989586621680452638 ~> a6989586621680452638) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumBySym0 :: TyFun (a6989586621680452638 ~> (a6989586621680452638 ~> Ordering)) (t6989586621680452637 a6989586621680452638 ~> a6989586621680452638) -> Type) (a6989586621680453149 :: a6989586621680452638 ~> (a6989586621680452638 ~> Ordering)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumBySym0 :: TyFun (a6989586621680452638 ~> (a6989586621680452638 ~> Ordering)) (t6989586621680452637 a6989586621680452638 ~> a6989586621680452638) -> Type) (a6989586621680453149 :: a6989586621680452638 ~> (a6989586621680452638 ~> Ordering)) = (MaximumBySym1 a6989586621680453149 t6989586621680452637 :: TyFun (t6989586621680452637 a6989586621680452638) a6989586621680452638 -> Type)

data MaximumBySym1 (a6989586621680453149 :: (~>) a6989586621680452638 ((~>) a6989586621680452638 Ordering)) :: forall t6989586621680452637. (~>) (t6989586621680452637 a6989586621680452638) a6989586621680452638 Source #

Instances
(SFoldable t, SingI d) => SingI (MaximumBySym1 d t :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (MaximumBySym1 d t) Source #

SuppressUnusedWarnings (MaximumBySym1 a6989586621680453149 t6989586621680452637 :: TyFun (t6989586621680452637 a6989586621680452638) a6989586621680452638 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumBySym1 a6989586621680453149 t :: TyFun (t a) a -> Type) (a6989586621680453150 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaximumBySym1 a6989586621680453149 t :: TyFun (t a) a -> Type) (a6989586621680453150 :: t a) = MaximumBy a6989586621680453149 a6989586621680453150

type MaximumBySym2 (a6989586621680453149 :: (~>) a6989586621680452638 ((~>) a6989586621680452638 Ordering)) (a6989586621680453150 :: t6989586621680452637 a6989586621680452638) = MaximumBy a6989586621680453149 a6989586621680453150 Source #

data MinimumBySym0 :: forall a6989586621680452636 t6989586621680452635. (~>) ((~>) a6989586621680452636 ((~>) a6989586621680452636 Ordering)) ((~>) (t6989586621680452635 a6989586621680452636) a6989586621680452636) Source #

Instances
SFoldable t => SingI (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MinimumBySym0 :: TyFun (a6989586621680452636 ~> (a6989586621680452636 ~> Ordering)) (t6989586621680452635 a6989586621680452636 ~> a6989586621680452636) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumBySym0 :: TyFun (a6989586621680452636 ~> (a6989586621680452636 ~> Ordering)) (t6989586621680452635 a6989586621680452636 ~> a6989586621680452636) -> Type) (a6989586621680453124 :: a6989586621680452636 ~> (a6989586621680452636 ~> Ordering)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumBySym0 :: TyFun (a6989586621680452636 ~> (a6989586621680452636 ~> Ordering)) (t6989586621680452635 a6989586621680452636 ~> a6989586621680452636) -> Type) (a6989586621680453124 :: a6989586621680452636 ~> (a6989586621680452636 ~> Ordering)) = (MinimumBySym1 a6989586621680453124 t6989586621680452635 :: TyFun (t6989586621680452635 a6989586621680452636) a6989586621680452636 -> Type)

data MinimumBySym1 (a6989586621680453124 :: (~>) a6989586621680452636 ((~>) a6989586621680452636 Ordering)) :: forall t6989586621680452635. (~>) (t6989586621680452635 a6989586621680452636) a6989586621680452636 Source #

Instances
(SFoldable t, SingI d) => SingI (MinimumBySym1 d t :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (MinimumBySym1 d t) Source #

SuppressUnusedWarnings (MinimumBySym1 a6989586621680453124 t6989586621680452635 :: TyFun (t6989586621680452635 a6989586621680452636) a6989586621680452636 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumBySym1 a6989586621680453124 t :: TyFun (t a) a -> Type) (a6989586621680453125 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinimumBySym1 a6989586621680453124 t :: TyFun (t a) a -> Type) (a6989586621680453125 :: t a) = MinimumBy a6989586621680453124 a6989586621680453125

type MinimumBySym2 (a6989586621680453124 :: (~>) a6989586621680452636 ((~>) a6989586621680452636 Ordering)) (a6989586621680453125 :: t6989586621680452635 a6989586621680452636) = MinimumBy a6989586621680453124 a6989586621680453125 Source #

data GenericLengthSym0 :: forall a6989586621679940015 i6989586621679940014. (~>) [a6989586621679940015] i6989586621679940014 Source #

Instances
SNum i => SingI (GenericLengthSym0 :: TyFun [a] i -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a6989586621679940015] i6989586621679940014 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679949273 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679949273 :: [a]) = (GenericLength a6989586621679949273 :: k2)

type GenericLengthSym1 (a6989586621679949273 :: [a6989586621679940015]) = GenericLength a6989586621679949273 Source #

data GenericTakeSym0 :: forall a6989586621680066217 i6989586621680066216. (~>) i6989586621680066216 ((~>) [a6989586621680066217] [a6989586621680066217]) Source #

Instances
SuppressUnusedWarnings (GenericTakeSym0 :: TyFun i6989586621680066216 ([a6989586621680066217] ~> [a6989586621680066217]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericTakeSym0 :: TyFun i6989586621680066216 ([a6989586621680066217] ~> [a6989586621680066217]) -> Type) (a6989586621680078760 :: i6989586621680066216) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericTakeSym0 :: TyFun i6989586621680066216 ([a6989586621680066217] ~> [a6989586621680066217]) -> Type) (a6989586621680078760 :: i6989586621680066216) = (GenericTakeSym1 a6989586621680078760 a6989586621680066217 :: TyFun [a6989586621680066217] [a6989586621680066217] -> Type)

data GenericTakeSym1 (a6989586621680078760 :: i6989586621680066216) :: forall a6989586621680066217. (~>) [a6989586621680066217] [a6989586621680066217] Source #

Instances
SuppressUnusedWarnings (GenericTakeSym1 a6989586621680078760 a6989586621680066217 :: TyFun [a6989586621680066217] [a6989586621680066217] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericTakeSym1 a6989586621680078760 a :: TyFun [a] [a] -> Type) (a6989586621680078761 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericTakeSym1 a6989586621680078760 a :: TyFun [a] [a] -> Type) (a6989586621680078761 :: [a]) = GenericTake a6989586621680078760 a6989586621680078761

type GenericTakeSym2 (a6989586621680078760 :: i6989586621680066216) (a6989586621680078761 :: [a6989586621680066217]) = GenericTake a6989586621680078760 a6989586621680078761 Source #

data GenericDropSym0 :: forall a6989586621680066215 i6989586621680066214. (~>) i6989586621680066214 ((~>) [a6989586621680066215] [a6989586621680066215]) Source #

Instances
SuppressUnusedWarnings (GenericDropSym0 :: TyFun i6989586621680066214 ([a6989586621680066215] ~> [a6989586621680066215]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericDropSym0 :: TyFun i6989586621680066214 ([a6989586621680066215] ~> [a6989586621680066215]) -> Type) (a6989586621680078750 :: i6989586621680066214) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericDropSym0 :: TyFun i6989586621680066214 ([a6989586621680066215] ~> [a6989586621680066215]) -> Type) (a6989586621680078750 :: i6989586621680066214) = (GenericDropSym1 a6989586621680078750 a6989586621680066215 :: TyFun [a6989586621680066215] [a6989586621680066215] -> Type)

data GenericDropSym1 (a6989586621680078750 :: i6989586621680066214) :: forall a6989586621680066215. (~>) [a6989586621680066215] [a6989586621680066215] Source #

Instances
SuppressUnusedWarnings (GenericDropSym1 a6989586621680078750 a6989586621680066215 :: TyFun [a6989586621680066215] [a6989586621680066215] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericDropSym1 a6989586621680078750 a :: TyFun [a] [a] -> Type) (a6989586621680078751 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericDropSym1 a6989586621680078750 a :: TyFun [a] [a] -> Type) (a6989586621680078751 :: [a]) = GenericDrop a6989586621680078750 a6989586621680078751

type GenericDropSym2 (a6989586621680078750 :: i6989586621680066214) (a6989586621680078751 :: [a6989586621680066215]) = GenericDrop a6989586621680078750 a6989586621680078751 Source #

data GenericSplitAtSym0 :: forall a6989586621680066213 i6989586621680066212. (~>) i6989586621680066212 ((~>) [a6989586621680066213] ([a6989586621680066213], [a6989586621680066213])) Source #

Instances
SuppressUnusedWarnings (GenericSplitAtSym0 :: TyFun i6989586621680066212 ([a6989586621680066213] ~> ([a6989586621680066213], [a6989586621680066213])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericSplitAtSym0 :: TyFun i6989586621680066212 ([a6989586621680066213] ~> ([a6989586621680066213], [a6989586621680066213])) -> Type) (a6989586621680078740 :: i6989586621680066212) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericSplitAtSym0 :: TyFun i6989586621680066212 ([a6989586621680066213] ~> ([a6989586621680066213], [a6989586621680066213])) -> Type) (a6989586621680078740 :: i6989586621680066212) = (GenericSplitAtSym1 a6989586621680078740 a6989586621680066213 :: TyFun [a6989586621680066213] ([a6989586621680066213], [a6989586621680066213]) -> Type)

data GenericSplitAtSym1 (a6989586621680078740 :: i6989586621680066212) :: forall a6989586621680066213. (~>) [a6989586621680066213] ([a6989586621680066213], [a6989586621680066213]) Source #

Instances
SuppressUnusedWarnings (GenericSplitAtSym1 a6989586621680078740 a6989586621680066213 :: TyFun [a6989586621680066213] ([a6989586621680066213], [a6989586621680066213]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericSplitAtSym1 a6989586621680078740 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621680078741 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericSplitAtSym1 a6989586621680078740 a :: TyFun [a] ([a], [a]) -> Type) (a6989586621680078741 :: [a]) = GenericSplitAt a6989586621680078740 a6989586621680078741

type GenericSplitAtSym2 (a6989586621680078740 :: i6989586621680066212) (a6989586621680078741 :: [a6989586621680066213]) = GenericSplitAt a6989586621680078740 a6989586621680078741 Source #

data GenericIndexSym0 :: forall a6989586621680066211 i6989586621680066210. (~>) [a6989586621680066211] ((~>) i6989586621680066210 a6989586621680066211) Source #

Instances
SuppressUnusedWarnings (GenericIndexSym0 :: TyFun [a6989586621680066211] (i6989586621680066210 ~> a6989586621680066211) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericIndexSym0 :: TyFun [a6989586621680066211] (i6989586621680066210 ~> a6989586621680066211) -> Type) (a6989586621680078730 :: [a6989586621680066211]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericIndexSym0 :: TyFun [a6989586621680066211] (i6989586621680066210 ~> a6989586621680066211) -> Type) (a6989586621680078730 :: [a6989586621680066211]) = (GenericIndexSym1 a6989586621680078730 i6989586621680066210 :: TyFun i6989586621680066210 a6989586621680066211 -> Type)

data GenericIndexSym1 (a6989586621680078730 :: [a6989586621680066211]) :: forall i6989586621680066210. (~>) i6989586621680066210 a6989586621680066211 Source #

Instances
SuppressUnusedWarnings (GenericIndexSym1 a6989586621680078730 i6989586621680066210 :: TyFun i6989586621680066210 a6989586621680066211 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericIndexSym1 a6989586621680078730 i :: TyFun i a -> Type) (a6989586621680078731 :: i) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericIndexSym1 a6989586621680078730 i :: TyFun i a -> Type) (a6989586621680078731 :: i) = GenericIndex a6989586621680078730 a6989586621680078731

type GenericIndexSym2 (a6989586621680078730 :: [a6989586621680066211]) (a6989586621680078731 :: i6989586621680066210) = GenericIndex a6989586621680078730 a6989586621680078731 Source #

data GenericReplicateSym0 :: forall a6989586621680066209 i6989586621680066208. (~>) i6989586621680066208 ((~>) a6989586621680066209 [a6989586621680066209]) Source #

Instances
SuppressUnusedWarnings (GenericReplicateSym0 :: TyFun i6989586621680066208 (a6989586621680066209 ~> [a6989586621680066209]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericReplicateSym0 :: TyFun i6989586621680066208 (a6989586621680066209 ~> [a6989586621680066209]) -> Type) (a6989586621680078720 :: i6989586621680066208) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericReplicateSym0 :: TyFun i6989586621680066208 (a6989586621680066209 ~> [a6989586621680066209]) -> Type) (a6989586621680078720 :: i6989586621680066208) = (GenericReplicateSym1 a6989586621680078720 a6989586621680066209 :: TyFun a6989586621680066209 [a6989586621680066209] -> Type)

data GenericReplicateSym1 (a6989586621680078720 :: i6989586621680066208) :: forall a6989586621680066209. (~>) a6989586621680066209 [a6989586621680066209] Source #

Instances
SuppressUnusedWarnings (GenericReplicateSym1 a6989586621680078720 a6989586621680066209 :: TyFun a6989586621680066209 [a6989586621680066209] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericReplicateSym1 a6989586621680078720 a :: TyFun a [a] -> Type) (a6989586621680078721 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GenericReplicateSym1 a6989586621680078720 a :: TyFun a [a] -> Type) (a6989586621680078721 :: a) = GenericReplicate a6989586621680078720 a6989586621680078721

type GenericReplicateSym2 (a6989586621680078720 :: i6989586621680066208) (a6989586621680078721 :: a6989586621680066209) = GenericReplicate a6989586621680078720 a6989586621680078721 Source #