singletons-2.6: 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

Description

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

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

Synopsis
  • type family Sing :: k -> Type
  • data SList :: forall a. [a] -> Type where
  • type family (a :: [a]) ++ (a :: [a]) :: [a] where ...
  • (%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a])
  • type family Head (a :: [a]) :: a where ...
  • sHead :: forall a (t :: [a]). Sing t -> Sing (Apply HeadSym0 t :: a)
  • type family Last (a :: [a]) :: a where ...
  • sLast :: forall a (t :: [a]). Sing t -> Sing (Apply LastSym0 t :: a)
  • type family Tail (a :: [a]) :: [a] where ...
  • sTail :: forall a (t :: [a]). Sing t -> Sing (Apply TailSym0 t :: [a])
  • type family Init (a :: [a]) :: [a] where ...
  • sInit :: forall a (t :: [a]). Sing t -> Sing (Apply InitSym0 t :: [a])
  • type family Null (arg :: t a) :: Bool
  • sNull :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply NullSym0 t :: Bool)
  • type family Length (arg :: t a) :: Nat
  • sLength :: forall a (t :: t a). SFoldable t => Sing t -> Sing (Apply LengthSym0 t :: Nat)
  • type family Map (a :: (~>) a b) (a :: [a]) :: [b] where ...
  • sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b])
  • type family Reverse (a :: [a]) :: [a] where ...
  • sReverse :: forall a (t :: [a]). Sing t -> Sing (Apply ReverseSym0 t :: [a])
  • type family Intersperse (a :: a) (a :: [a]) :: [a] where ...
  • sIntersperse :: forall a (t :: a) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a])
  • type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ...
  • sIntercalate :: forall a (t :: [a]) (t :: [[a]]). Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a])
  • type family Transpose (a :: [[a]]) :: [[a]] where ...
  • sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply TransposeSym0 t :: [[a]])
  • type family Subsequences (a :: [a]) :: [[a]] where ...
  • sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]])
  • type family Permutations (a :: [a]) :: [[a]] where ...
  • sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]])
  • type family Foldl (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
  • sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b)
  • type family Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b
  • sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b)
  • type family Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
  • sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a)
  • type family Foldl1' (a :: (~>) a ((~>) a a)) (a :: [a]) :: a where ...
  • sFoldl1' :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a)
  • type family Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b
  • sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b)
  • type family Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a
  • sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a)
  • type family Concat (a :: t [a]) :: [a] where ...
  • sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a])
  • type family ConcatMap (a :: (~>) a [b]) (a :: t a) :: [b] where ...
  • sConcatMap :: forall a b t (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b])
  • type family And (a :: t Bool) :: Bool where ...
  • sAnd :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool)
  • type family Or (a :: t Bool) :: Bool where ...
  • sOr :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool)
  • type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ...
  • sAny :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool)
  • type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ...
  • sAll :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool)
  • type family Sum (arg :: t a) :: a
  • sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a)
  • type family Product (arg :: t a) :: a
  • sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a)
  • type family Maximum (arg :: t a) :: a
  • sMaximum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a)
  • type family Minimum (arg :: t a) :: a
  • sMinimum :: forall a (t :: t a). (SFoldable t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a)
  • type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: [b] where ...
  • sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b])
  • type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
  • sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a])
  • type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: [b] where ...
  • sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b])
  • type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: [a]) :: [a] where ...
  • sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a])
  • type family MapAccumL (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
  • sMapAccumL :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (a, t c))
  • type family MapAccumR (a :: (~>) a ((~>) b (a, c))) (a :: a) (a :: t b) :: (a, t c) where ...
  • sMapAccumR :: forall a b c t (t :: (~>) a ((~>) b (a, c))) (t :: a) (t :: t b). STraversable t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (a, t c))
  • type family Replicate (a :: Nat) (a :: a) :: [a] where ...
  • sReplicate :: forall a (t :: Nat) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a])
  • type family Unfoldr (a :: (~>) b (Maybe (a, b))) (a :: b) :: [a] where ...
  • sUnfoldr :: forall b a (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a])
  • type family Take (a :: Nat) (a :: [a]) :: [a] where ...
  • sTake :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a])
  • type family Drop (a :: Nat) (a :: [a]) :: [a] where ...
  • sDrop :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a])
  • type family SplitAt (a :: Nat) (a :: [a]) :: ([a], [a]) where ...
  • sSplitAt :: forall a (t :: Nat) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a]))
  • type family TakeWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
  • sTakeWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a])
  • type family DropWhile (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
  • sDropWhile :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a])
  • type family DropWhileEnd (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
  • sDropWhileEnd :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a])
  • type family Span (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
  • sSpan :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a]))
  • type family Break (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
  • sBreak :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a]))
  • type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ...
  • type family Group (a :: [a]) :: [[a]] where ...
  • sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [[a]])
  • type family Inits (a :: [a]) :: [[a]] where ...
  • sInits :: forall a (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: [[a]])
  • type family Tails (a :: [a]) :: [[a]] where ...
  • sTails :: forall a (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: [[a]])
  • type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ...
  • sIsPrefixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool)
  • type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ...
  • sIsSuffixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool)
  • type family IsInfixOf (a :: [a]) (a :: [a]) :: Bool where ...
  • sIsInfixOf :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool)
  • type family Elem (arg :: a) (arg :: t a) :: Bool
  • sElem :: forall a (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool)
  • type family NotElem (a :: a) (a :: t a) :: Bool where ...
  • sNotElem :: forall a t (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool)
  • type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ...
  • sLookup :: forall a b (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b)
  • type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ...
  • sFind :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a)
  • type family Filter (a :: (~>) a Bool) (a :: [a]) :: [a] where ...
  • sFilter :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
  • type family Partition (a :: (~>) a Bool) (a :: [a]) :: ([a], [a]) where ...
  • sPartition :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
  • type family (a :: [a]) !! (a :: Nat) :: a where ...
  • (%!!) :: forall a (t :: [a]) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a)
  • type family ElemIndex (a :: a) (a :: [a]) :: Maybe Nat where ...
  • sElemIndex :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat)
  • type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ...
  • sElemIndices :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat])
  • type family FindIndex (a :: (~>) a Bool) (a :: [a]) :: Maybe Nat where ...
  • sFindIndex :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat)
  • type family FindIndices (a :: (~>) a Bool) (a :: [a]) :: [Nat] where ...
  • sFindIndices :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat])
  • type family Zip (a :: [a]) (a :: [b]) :: [(a, b)] where ...
  • sZip :: forall a b (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)])
  • type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ...
  • sZip3 :: forall a b c (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)])
  • type family Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ...
  • type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ...
  • type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ...
  • type family Zip7 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [(a, b, c, d, e, f, g)] where ...
  • type family ZipWith (a :: (~>) a ((~>) b c)) (a :: [a]) (a :: [b]) :: [c] where ...
  • sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: [a]) (t :: [b]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c])
  • type family ZipWith3 (a :: (~>) a ((~>) b ((~>) c d))) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ...
  • sZipWith3 :: forall a b c d (t :: (~>) a ((~>) b ((~>) c d))) (t :: [a]) (t :: [b]) (t :: [c]). Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d])
  • type family ZipWith4 (a :: (~>) a ((~>) b ((~>) c ((~>) d e)))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ...
  • type family ZipWith5 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e f))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ...
  • type family ZipWith6 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f g)))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ...
  • type family ZipWith7 (a :: (~>) a ((~>) b ((~>) c ((~>) d ((~>) e ((~>) f ((~>) g h))))))) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ...
  • type family Unzip (a :: [(a, b)]) :: ([a], [b]) where ...
  • sUnzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b]))
  • type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ...
  • sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c]))
  • type family Unzip4 (a :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
  • sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d]))
  • type family Unzip5 (a :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ...
  • sUnzip5 :: forall a b c d e (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e]))
  • type family Unzip6 (a :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ...
  • sUnzip6 :: forall a b c d e f (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f]))
  • type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
  • sUnzip7 :: forall a b c d e f g (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g]))
  • type family Unlines (a :: [Symbol]) :: Symbol where ...
  • sUnlines :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnlinesSym0 t :: Symbol)
  • type family Unwords (a :: [Symbol]) :: Symbol where ...
  • sUnwords :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnwordsSym0 t :: Symbol)
  • type family Nub (a :: [a]) :: [a] where ...
  • sNub :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply NubSym0 t :: [a])
  • type family Delete (a :: a) (a :: [a]) :: [a] where ...
  • sDelete :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a])
  • type family (a :: [a]) \\ (a :: [a]) :: [a] where ...
  • (%\\) :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply (\\@#@$) t) t :: [a])
  • type family Union (a :: [a]) (a :: [a]) :: [a] where ...
  • sUnion :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a])
  • type family Intersect (a :: [a]) (a :: [a]) :: [a] where ...
  • sIntersect :: forall a (t :: [a]) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a])
  • type family Insert (a :: a) (a :: [a]) :: [a] where ...
  • sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a])
  • type family Sort (a :: [a]) :: [a] where ...
  • sSort :: forall a (t :: [a]). SOrd a => Sing t -> Sing (Apply SortSym0 t :: [a])
  • type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [a] where ...
  • sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a])
  • type family DeleteBy (a :: (~>) a ((~>) a Bool)) (a :: a) (a :: [a]) :: [a] where ...
  • sDeleteBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a])
  • type family DeleteFirstsBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
  • sDeleteFirstsBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a])
  • type family UnionBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
  • sUnionBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a])
  • type family IntersectBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) (a :: [a]) :: [a] where ...
  • sIntersectBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a])
  • type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [[a]] where ...
  • sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]])
  • type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: [a]) :: [a] where ...
  • sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a])
  • type family InsertBy (a :: (~>) a ((~>) a Ordering)) (a :: a) (a :: [a]) :: [a] where ...
  • sInsertBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: a) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a])
  • type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
  • sMaximumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a)
  • type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ...
  • sMinimumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a)
  • type family GenericLength (a :: [a]) :: i where ...
  • sGenericLength :: forall a i (t :: [a]). SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i)
  • type family GenericTake (a :: i) (a :: [a]) :: [a] where ...
  • type family GenericDrop (a :: i) (a :: [a]) :: [a] where ...
  • type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ...
  • type family GenericIndex (a :: [a]) (a :: i) :: a where ...
  • type family GenericReplicate (a :: i) (a :: a) :: [a] where ...
  • type NilSym0 = '[]
  • data (:@#@$) :: forall (a3530822107858468865 :: Type). (~>) a3530822107858468865 ((~>) [a3530822107858468865] [a3530822107858468865 :: Type])
  • data (:@#@$$) (t6989586621679315156 :: a3530822107858468865 :: Type) :: (~>) [a3530822107858468865] [a3530822107858468865 :: Type]
  • type (:@#@$$$) (t6989586621679315156 :: a3530822107858468865) (t6989586621679315157 :: [a3530822107858468865]) = '(:) t6989586621679315156 t6989586621679315157
  • type (++@#@$$$) (a6989586621679545630 :: [a6989586621679545433]) (a6989586621679545631 :: [a6989586621679545433]) = (++) a6989586621679545630 a6989586621679545631
  • data (++@#@$$) (a6989586621679545630 :: [a6989586621679545433]) :: (~>) [a6989586621679545433] [a6989586621679545433]
  • data (++@#@$) :: forall a6989586621679545433. (~>) [a6989586621679545433] ((~>) [a6989586621679545433] [a6989586621679545433])
  • data HeadSym0 :: forall a6989586621679974183. (~>) [a6989586621679974183] a6989586621679974183
  • type HeadSym1 (a6989586621679979530 :: [a6989586621679974183]) = Head a6989586621679979530
  • data LastSym0 :: forall a6989586621679974182. (~>) [a6989586621679974182] a6989586621679974182
  • type LastSym1 (a6989586621679979525 :: [a6989586621679974182]) = Last a6989586621679979525
  • data TailSym0 :: forall a6989586621679974181. (~>) [a6989586621679974181] [a6989586621679974181]
  • type TailSym1 (a6989586621679979522 :: [a6989586621679974181]) = Tail a6989586621679979522
  • data InitSym0 :: forall a6989586621679974180. (~>) [a6989586621679974180] [a6989586621679974180]
  • type InitSym1 (a6989586621679979508 :: [a6989586621679974180]) = Init a6989586621679979508
  • data NullSym0 :: forall t6989586621680490502 a6989586621680490517. (~>) (t6989586621680490502 a6989586621680490517) Bool
  • type NullSym1 (arg6989586621680491161 :: t6989586621680490502 a6989586621680490517) = Null arg6989586621680491161
  • data LengthSym0 :: forall t6989586621680490502 a6989586621680490518. (~>) (t6989586621680490502 a6989586621680490518) Nat
  • type LengthSym1 (arg6989586621680491163 :: t6989586621680490502 a6989586621680490518) = Length arg6989586621680491163
  • data MapSym0 :: forall a6989586621679545434 b6989586621679545435. (~>) ((~>) a6989586621679545434 b6989586621679545435) ((~>) [a6989586621679545434] [b6989586621679545435])
  • data MapSym1 (a6989586621679545638 :: (~>) a6989586621679545434 b6989586621679545435) :: (~>) [a6989586621679545434] [b6989586621679545435]
  • type MapSym2 (a6989586621679545638 :: (~>) a6989586621679545434 b6989586621679545435) (a6989586621679545639 :: [a6989586621679545434]) = Map a6989586621679545638 a6989586621679545639
  • data ReverseSym0 :: forall a6989586621679974178. (~>) [a6989586621679974178] [a6989586621679974178]
  • type ReverseSym1 (a6989586621679979493 :: [a6989586621679974178]) = Reverse a6989586621679979493
  • data IntersperseSym0 :: forall a6989586621679974177. (~>) a6989586621679974177 ((~>) [a6989586621679974177] [a6989586621679974177])
  • data IntersperseSym1 (a6989586621679979486 :: a6989586621679974177) :: (~>) [a6989586621679974177] [a6989586621679974177]
  • type IntersperseSym2 (a6989586621679979486 :: a6989586621679974177) (a6989586621679979487 :: [a6989586621679974177]) = Intersperse a6989586621679979486 a6989586621679979487
  • data IntercalateSym0 :: forall a6989586621679974176. (~>) [a6989586621679974176] ((~>) [[a6989586621679974176]] [a6989586621679974176])
  • data IntercalateSym1 (a6989586621679979480 :: [a6989586621679974176]) :: (~>) [[a6989586621679974176]] [a6989586621679974176]
  • type IntercalateSym2 (a6989586621679979480 :: [a6989586621679974176]) (a6989586621679979481 :: [[a6989586621679974176]]) = Intercalate a6989586621679979480 a6989586621679979481
  • data TransposeSym0 :: forall a6989586621679974063. (~>) [[a6989586621679974063]] [[a6989586621679974063]]
  • type TransposeSym1 (a6989586621679978223 :: [[a6989586621679974063]]) = Transpose a6989586621679978223
  • data SubsequencesSym0 :: forall a6989586621679974175. (~>) [a6989586621679974175] [[a6989586621679974175]]
  • type SubsequencesSym1 (a6989586621679979477 :: [a6989586621679974175]) = Subsequences a6989586621679979477
  • data PermutationsSym0 :: forall a6989586621679974172. (~>) [a6989586621679974172] [[a6989586621679974172]]
  • type PermutationsSym1 (a6989586621679979359 :: [a6989586621679974172]) = Permutations a6989586621679979359
  • data FoldlSym0 :: forall b6989586621680490510 a6989586621680490511 t6989586621680490502. (~>) ((~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) ((~>) b6989586621680490510 ((~>) (t6989586621680490502 a6989586621680490511) b6989586621680490510))
  • data FoldlSym1 (arg6989586621680491139 :: (~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) :: forall t6989586621680490502. (~>) b6989586621680490510 ((~>) (t6989586621680490502 a6989586621680490511) b6989586621680490510)
  • data FoldlSym2 (arg6989586621680491139 :: (~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) (arg6989586621680491140 :: b6989586621680490510) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490511) b6989586621680490510
  • type FoldlSym3 (arg6989586621680491139 :: (~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) (arg6989586621680491140 :: b6989586621680490510) (arg6989586621680491141 :: t6989586621680490502 a6989586621680490511) = Foldl arg6989586621680491139 arg6989586621680491140 arg6989586621680491141
  • data Foldl'Sym0 :: forall b6989586621680490512 a6989586621680490513 t6989586621680490502. (~>) ((~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) ((~>) b6989586621680490512 ((~>) (t6989586621680490502 a6989586621680490513) b6989586621680490512))
  • data Foldl'Sym1 (arg6989586621680491145 :: (~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) :: forall t6989586621680490502. (~>) b6989586621680490512 ((~>) (t6989586621680490502 a6989586621680490513) b6989586621680490512)
  • data Foldl'Sym2 (arg6989586621680491145 :: (~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) (arg6989586621680491146 :: b6989586621680490512) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490513) b6989586621680490512
  • type Foldl'Sym3 (arg6989586621680491145 :: (~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) (arg6989586621680491146 :: b6989586621680490512) (arg6989586621680491147 :: t6989586621680490502 a6989586621680490513) = Foldl' arg6989586621680491145 arg6989586621680491146 arg6989586621680491147
  • data Foldl1Sym0 :: forall a6989586621680490515 t6989586621680490502. (~>) ((~>) a6989586621680490515 ((~>) a6989586621680490515 a6989586621680490515)) ((~>) (t6989586621680490502 a6989586621680490515) a6989586621680490515)
  • data Foldl1Sym1 (arg6989586621680491155 :: (~>) a6989586621680490515 ((~>) a6989586621680490515 a6989586621680490515)) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490515) a6989586621680490515
  • type Foldl1Sym2 (arg6989586621680491155 :: (~>) a6989586621680490515 ((~>) a6989586621680490515 a6989586621680490515)) (arg6989586621680491156 :: t6989586621680490502 a6989586621680490515) = Foldl1 arg6989586621680491155 arg6989586621680491156
  • data Foldl1'Sym0 :: forall a6989586621679974168. (~>) ((~>) a6989586621679974168 ((~>) a6989586621679974168 a6989586621679974168)) ((~>) [a6989586621679974168] a6989586621679974168)
  • data Foldl1'Sym1 (a6989586621679979317 :: (~>) a6989586621679974168 ((~>) a6989586621679974168 a6989586621679974168)) :: (~>) [a6989586621679974168] a6989586621679974168
  • type Foldl1'Sym2 (a6989586621679979317 :: (~>) a6989586621679974168 ((~>) a6989586621679974168 a6989586621679974168)) (a6989586621679979318 :: [a6989586621679974168]) = Foldl1' a6989586621679979317 a6989586621679979318
  • data FoldrSym0 :: forall a6989586621680490506 b6989586621680490507 t6989586621680490502. (~>) ((~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) ((~>) b6989586621680490507 ((~>) (t6989586621680490502 a6989586621680490506) b6989586621680490507))
  • data FoldrSym1 (arg6989586621680491127 :: (~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) :: forall t6989586621680490502. (~>) b6989586621680490507 ((~>) (t6989586621680490502 a6989586621680490506) b6989586621680490507)
  • data FoldrSym2 (arg6989586621680491127 :: (~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) (arg6989586621680491128 :: b6989586621680490507) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490506) b6989586621680490507
  • type FoldrSym3 (arg6989586621680491127 :: (~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) (arg6989586621680491128 :: b6989586621680490507) (arg6989586621680491129 :: t6989586621680490502 a6989586621680490506) = Foldr arg6989586621680491127 arg6989586621680491128 arg6989586621680491129
  • data Foldr1Sym0 :: forall a6989586621680490514 t6989586621680490502. (~>) ((~>) a6989586621680490514 ((~>) a6989586621680490514 a6989586621680490514)) ((~>) (t6989586621680490502 a6989586621680490514) a6989586621680490514)
  • data Foldr1Sym1 (arg6989586621680491151 :: (~>) a6989586621680490514 ((~>) a6989586621680490514 a6989586621680490514)) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490514) a6989586621680490514
  • type Foldr1Sym2 (arg6989586621680491151 :: (~>) a6989586621680490514 ((~>) a6989586621680490514 a6989586621680490514)) (arg6989586621680491152 :: t6989586621680490502 a6989586621680490514) = Foldr1 arg6989586621680491151 arg6989586621680491152
  • data ConcatSym0 :: forall t6989586621680490427 a6989586621680490428. (~>) (t6989586621680490427 [a6989586621680490428]) [a6989586621680490428]
  • type ConcatSym1 (a6989586621680491009 :: t6989586621680490427 [a6989586621680490428]) = Concat a6989586621680491009
  • data ConcatMapSym0 :: forall a6989586621680490425 b6989586621680490426 t6989586621680490424. (~>) ((~>) a6989586621680490425 [b6989586621680490426]) ((~>) (t6989586621680490424 a6989586621680490425) [b6989586621680490426])
  • data ConcatMapSym1 (a6989586621680490993 :: (~>) a6989586621680490425 [b6989586621680490426]) :: forall t6989586621680490424. (~>) (t6989586621680490424 a6989586621680490425) [b6989586621680490426]
  • type ConcatMapSym2 (a6989586621680490993 :: (~>) a6989586621680490425 [b6989586621680490426]) (a6989586621680490994 :: t6989586621680490424 a6989586621680490425) = ConcatMap a6989586621680490993 a6989586621680490994
  • data AndSym0 :: forall t6989586621680490423. (~>) (t6989586621680490423 Bool) Bool
  • type AndSym1 (a6989586621680490984 :: t6989586621680490423 Bool) = And a6989586621680490984
  • data OrSym0 :: forall t6989586621680490422. (~>) (t6989586621680490422 Bool) Bool
  • type OrSym1 (a6989586621680490975 :: t6989586621680490422 Bool) = Or a6989586621680490975
  • data AnySym0 :: forall a6989586621680490421 t6989586621680490420. (~>) ((~>) a6989586621680490421 Bool) ((~>) (t6989586621680490420 a6989586621680490421) Bool)
  • data AnySym1 (a6989586621680490962 :: (~>) a6989586621680490421 Bool) :: forall t6989586621680490420. (~>) (t6989586621680490420 a6989586621680490421) Bool
  • type AnySym2 (a6989586621680490962 :: (~>) a6989586621680490421 Bool) (a6989586621680490963 :: t6989586621680490420 a6989586621680490421) = Any a6989586621680490962 a6989586621680490963
  • data AllSym0 :: forall a6989586621680490419 t6989586621680490418. (~>) ((~>) a6989586621680490419 Bool) ((~>) (t6989586621680490418 a6989586621680490419) Bool)
  • data AllSym1 (a6989586621680490949 :: (~>) a6989586621680490419 Bool) :: forall t6989586621680490418. (~>) (t6989586621680490418 a6989586621680490419) Bool
  • type AllSym2 (a6989586621680490949 :: (~>) a6989586621680490419 Bool) (a6989586621680490950 :: t6989586621680490418 a6989586621680490419) = All a6989586621680490949 a6989586621680490950
  • data SumSym0 :: forall t6989586621680490502 a6989586621680490522. (~>) (t6989586621680490502 a6989586621680490522) a6989586621680490522
  • type SumSym1 (arg6989586621680491173 :: t6989586621680490502 a6989586621680490522) = Sum arg6989586621680491173
  • data ProductSym0 :: forall t6989586621680490502 a6989586621680490523. (~>) (t6989586621680490502 a6989586621680490523) a6989586621680490523
  • type ProductSym1 (arg6989586621680491175 :: t6989586621680490502 a6989586621680490523) = Product arg6989586621680491175
  • data MaximumSym0 :: forall t6989586621680490502 a6989586621680490520. (~>) (t6989586621680490502 a6989586621680490520) a6989586621680490520
  • type MaximumSym1 (arg6989586621680491169 :: t6989586621680490502 a6989586621680490520) = Maximum arg6989586621680491169
  • data MinimumSym0 :: forall t6989586621680490502 a6989586621680490521. (~>) (t6989586621680490502 a6989586621680490521) a6989586621680490521
  • type MinimumSym1 (arg6989586621680491171 :: t6989586621680490502 a6989586621680490521) = Minimum arg6989586621680491171
  • data ScanlSym0 :: forall b6989586621679974160 a6989586621679974161. (~>) ((~>) b6989586621679974160 ((~>) a6989586621679974161 b6989586621679974160)) ((~>) b6989586621679974160 ((~>) [a6989586621679974161] [b6989586621679974160]))
  • data ScanlSym1 (a6989586621679979254 :: (~>) b6989586621679974160 ((~>) a6989586621679974161 b6989586621679974160)) :: (~>) b6989586621679974160 ((~>) [a6989586621679974161] [b6989586621679974160])
  • data ScanlSym2 (a6989586621679979254 :: (~>) b6989586621679974160 ((~>) a6989586621679974161 b6989586621679974160)) (a6989586621679979255 :: b6989586621679974160) :: (~>) [a6989586621679974161] [b6989586621679974160]
  • type ScanlSym3 (a6989586621679979254 :: (~>) b6989586621679974160 ((~>) a6989586621679974161 b6989586621679974160)) (a6989586621679979255 :: b6989586621679974160) (a6989586621679979256 :: [a6989586621679974161]) = Scanl a6989586621679979254 a6989586621679979255 a6989586621679979256
  • data Scanl1Sym0 :: forall a6989586621679974159. (~>) ((~>) a6989586621679974159 ((~>) a6989586621679974159 a6989586621679974159)) ((~>) [a6989586621679974159] [a6989586621679974159])
  • data Scanl1Sym1 (a6989586621679979247 :: (~>) a6989586621679974159 ((~>) a6989586621679974159 a6989586621679974159)) :: (~>) [a6989586621679974159] [a6989586621679974159]
  • type Scanl1Sym2 (a6989586621679979247 :: (~>) a6989586621679974159 ((~>) a6989586621679974159 a6989586621679974159)) (a6989586621679979248 :: [a6989586621679974159]) = Scanl1 a6989586621679979247 a6989586621679979248
  • data ScanrSym0 :: forall a6989586621679974157 b6989586621679974158. (~>) ((~>) a6989586621679974157 ((~>) b6989586621679974158 b6989586621679974158)) ((~>) b6989586621679974158 ((~>) [a6989586621679974157] [b6989586621679974158]))
  • data ScanrSym1 (a6989586621679979226 :: (~>) a6989586621679974157 ((~>) b6989586621679974158 b6989586621679974158)) :: (~>) b6989586621679974158 ((~>) [a6989586621679974157] [b6989586621679974158])
  • data ScanrSym2 (a6989586621679979226 :: (~>) a6989586621679974157 ((~>) b6989586621679974158 b6989586621679974158)) (a6989586621679979227 :: b6989586621679974158) :: (~>) [a6989586621679974157] [b6989586621679974158]
  • type ScanrSym3 (a6989586621679979226 :: (~>) a6989586621679974157 ((~>) b6989586621679974158 b6989586621679974158)) (a6989586621679979227 :: b6989586621679974158) (a6989586621679979228 :: [a6989586621679974157]) = Scanr a6989586621679979226 a6989586621679979227 a6989586621679979228
  • data Scanr1Sym0 :: forall a6989586621679974156. (~>) ((~>) a6989586621679974156 ((~>) a6989586621679974156 a6989586621679974156)) ((~>) [a6989586621679974156] [a6989586621679974156])
  • data Scanr1Sym1 (a6989586621679979202 :: (~>) a6989586621679974156 ((~>) a6989586621679974156 a6989586621679974156)) :: (~>) [a6989586621679974156] [a6989586621679974156]
  • type Scanr1Sym2 (a6989586621679979202 :: (~>) a6989586621679974156 ((~>) a6989586621679974156 a6989586621679974156)) (a6989586621679979203 :: [a6989586621679974156]) = Scanr1 a6989586621679979202 a6989586621679979203
  • data MapAccumLSym0 :: forall a6989586621680804227 b6989586621680804228 c6989586621680804229 t6989586621680804226. (~>) ((~>) a6989586621680804227 ((~>) b6989586621680804228 (a6989586621680804227, c6989586621680804229))) ((~>) a6989586621680804227 ((~>) (t6989586621680804226 b6989586621680804228) (a6989586621680804227, t6989586621680804226 c6989586621680804229)))
  • data MapAccumLSym1 (a6989586621680804730 :: (~>) a6989586621680804227 ((~>) b6989586621680804228 (a6989586621680804227, c6989586621680804229))) :: forall t6989586621680804226. (~>) a6989586621680804227 ((~>) (t6989586621680804226 b6989586621680804228) (a6989586621680804227, t6989586621680804226 c6989586621680804229))
  • data MapAccumLSym2 (a6989586621680804730 :: (~>) a6989586621680804227 ((~>) b6989586621680804228 (a6989586621680804227, c6989586621680804229))) (a6989586621680804731 :: a6989586621680804227) :: forall t6989586621680804226. (~>) (t6989586621680804226 b6989586621680804228) (a6989586621680804227, t6989586621680804226 c6989586621680804229)
  • type MapAccumLSym3 (a6989586621680804730 :: (~>) a6989586621680804227 ((~>) b6989586621680804228 (a6989586621680804227, c6989586621680804229))) (a6989586621680804731 :: a6989586621680804227) (a6989586621680804732 :: t6989586621680804226 b6989586621680804228) = MapAccumL a6989586621680804730 a6989586621680804731 a6989586621680804732
  • data MapAccumRSym0 :: forall a6989586621680804223 b6989586621680804224 c6989586621680804225 t6989586621680804222. (~>) ((~>) a6989586621680804223 ((~>) b6989586621680804224 (a6989586621680804223, c6989586621680804225))) ((~>) a6989586621680804223 ((~>) (t6989586621680804222 b6989586621680804224) (a6989586621680804223, t6989586621680804222 c6989586621680804225)))
  • data MapAccumRSym1 (a6989586621680804713 :: (~>) a6989586621680804223 ((~>) b6989586621680804224 (a6989586621680804223, c6989586621680804225))) :: forall t6989586621680804222. (~>) a6989586621680804223 ((~>) (t6989586621680804222 b6989586621680804224) (a6989586621680804223, t6989586621680804222 c6989586621680804225))
  • data MapAccumRSym2 (a6989586621680804713 :: (~>) a6989586621680804223 ((~>) b6989586621680804224 (a6989586621680804223, c6989586621680804225))) (a6989586621680804714 :: a6989586621680804223) :: forall t6989586621680804222. (~>) (t6989586621680804222 b6989586621680804224) (a6989586621680804223, t6989586621680804222 c6989586621680804225)
  • type MapAccumRSym3 (a6989586621680804713 :: (~>) a6989586621680804223 ((~>) b6989586621680804224 (a6989586621680804223, c6989586621680804225))) (a6989586621680804714 :: a6989586621680804223) (a6989586621680804715 :: t6989586621680804222 b6989586621680804224) = MapAccumR a6989586621680804713 a6989586621680804714 a6989586621680804715
  • data ReplicateSym0 :: forall a6989586621679974064. (~>) Nat ((~>) a6989586621679974064 [a6989586621679974064])
  • data ReplicateSym1 (a6989586621679978229 :: Nat) :: forall a6989586621679974064. (~>) a6989586621679974064 [a6989586621679974064]
  • type ReplicateSym2 (a6989586621679978229 :: Nat) (a6989586621679978230 :: a6989586621679974064) = Replicate a6989586621679978229 a6989586621679978230
  • data UnfoldrSym0 :: forall b6989586621679974148 a6989586621679974149. (~>) ((~>) b6989586621679974148 (Maybe (a6989586621679974149, b6989586621679974148))) ((~>) b6989586621679974148 [a6989586621679974149])
  • data UnfoldrSym1 (a6989586621679979060 :: (~>) b6989586621679974148 (Maybe (a6989586621679974149, b6989586621679974148))) :: (~>) b6989586621679974148 [a6989586621679974149]
  • type UnfoldrSym2 (a6989586621679979060 :: (~>) b6989586621679974148 (Maybe (a6989586621679974149, b6989586621679974148))) (a6989586621679979061 :: b6989586621679974148) = Unfoldr a6989586621679979060 a6989586621679979061
  • data TakeSym0 :: forall a6989586621679974080. (~>) Nat ((~>) [a6989586621679974080] [a6989586621679974080])
  • data TakeSym1 (a6989586621679978390 :: Nat) :: forall a6989586621679974080. (~>) [a6989586621679974080] [a6989586621679974080]
  • type TakeSym2 (a6989586621679978390 :: Nat) (a6989586621679978391 :: [a6989586621679974080]) = Take a6989586621679978390 a6989586621679978391
  • data DropSym0 :: forall a6989586621679974079. (~>) Nat ((~>) [a6989586621679974079] [a6989586621679974079])
  • data DropSym1 (a6989586621679978376 :: Nat) :: forall a6989586621679974079. (~>) [a6989586621679974079] [a6989586621679974079]
  • type DropSym2 (a6989586621679978376 :: Nat) (a6989586621679978377 :: [a6989586621679974079]) = Drop a6989586621679978376 a6989586621679978377
  • data SplitAtSym0 :: forall a6989586621679974078. (~>) Nat ((~>) [a6989586621679974078] ([a6989586621679974078], [a6989586621679974078]))
  • data SplitAtSym1 (a6989586621679978370 :: Nat) :: forall a6989586621679974078. (~>) [a6989586621679974078] ([a6989586621679974078], [a6989586621679974078])
  • type SplitAtSym2 (a6989586621679978370 :: Nat) (a6989586621679978371 :: [a6989586621679974078]) = SplitAt a6989586621679978370 a6989586621679978371
  • data TakeWhileSym0 :: forall a6989586621679974085. (~>) ((~>) a6989586621679974085 Bool) ((~>) [a6989586621679974085] [a6989586621679974085])
  • data TakeWhileSym1 (a6989586621679978534 :: (~>) a6989586621679974085 Bool) :: (~>) [a6989586621679974085] [a6989586621679974085]
  • type TakeWhileSym2 (a6989586621679978534 :: (~>) a6989586621679974085 Bool) (a6989586621679978535 :: [a6989586621679974085]) = TakeWhile a6989586621679978534 a6989586621679978535
  • data DropWhileSym0 :: forall a6989586621679974084. (~>) ((~>) a6989586621679974084 Bool) ((~>) [a6989586621679974084] [a6989586621679974084])
  • data DropWhileSym1 (a6989586621679978516 :: (~>) a6989586621679974084 Bool) :: (~>) [a6989586621679974084] [a6989586621679974084]
  • type DropWhileSym2 (a6989586621679978516 :: (~>) a6989586621679974084 Bool) (a6989586621679978517 :: [a6989586621679974084]) = DropWhile a6989586621679978516 a6989586621679978517
  • data DropWhileEndSym0 :: forall a6989586621679974083. (~>) ((~>) a6989586621679974083 Bool) ((~>) [a6989586621679974083] [a6989586621679974083])
  • data DropWhileEndSym1 (a6989586621679978490 :: (~>) a6989586621679974083 Bool) :: (~>) [a6989586621679974083] [a6989586621679974083]
  • type DropWhileEndSym2 (a6989586621679978490 :: (~>) a6989586621679974083 Bool) (a6989586621679978491 :: [a6989586621679974083]) = DropWhileEnd a6989586621679978490 a6989586621679978491
  • data SpanSym0 :: forall a6989586621679974082. (~>) ((~>) a6989586621679974082 Bool) ((~>) [a6989586621679974082] ([a6989586621679974082], [a6989586621679974082]))
  • data SpanSym1 (a6989586621679978447 :: (~>) a6989586621679974082 Bool) :: (~>) [a6989586621679974082] ([a6989586621679974082], [a6989586621679974082])
  • type SpanSym2 (a6989586621679978447 :: (~>) a6989586621679974082 Bool) (a6989586621679978448 :: [a6989586621679974082]) = Span a6989586621679978447 a6989586621679978448
  • data BreakSym0 :: forall a6989586621679974081. (~>) ((~>) a6989586621679974081 Bool) ((~>) [a6989586621679974081] ([a6989586621679974081], [a6989586621679974081]))
  • data BreakSym1 (a6989586621679978404 :: (~>) a6989586621679974081 Bool) :: (~>) [a6989586621679974081] ([a6989586621679974081], [a6989586621679974081])
  • type BreakSym2 (a6989586621679978404 :: (~>) a6989586621679974081 Bool) (a6989586621679978405 :: [a6989586621679974081]) = Break a6989586621679978404 a6989586621679978405
  • data StripPrefixSym0 :: forall a6989586621680096271. (~>) [a6989586621680096271] ((~>) [a6989586621680096271] (Maybe [a6989586621680096271]))
  • data StripPrefixSym1 (a6989586621680097967 :: [a6989586621680096271]) :: (~>) [a6989586621680096271] (Maybe [a6989586621680096271])
  • type StripPrefixSym2 (a6989586621680097967 :: [a6989586621680096271]) (a6989586621680097968 :: [a6989586621680096271]) = StripPrefix a6989586621680097967 a6989586621680097968
  • data GroupSym0 :: forall a6989586621679974077. (~>) [a6989586621679974077] [[a6989586621679974077]]
  • type GroupSym1 (a6989586621679978367 :: [a6989586621679974077]) = Group a6989586621679978367
  • data InitsSym0 :: forall a6989586621679974147. (~>) [a6989586621679974147] [[a6989586621679974147]]
  • type InitsSym1 (a6989586621679979052 :: [a6989586621679974147]) = Inits a6989586621679979052
  • data TailsSym0 :: forall a6989586621679974146. (~>) [a6989586621679974146] [[a6989586621679974146]]
  • type TailsSym1 (a6989586621679979045 :: [a6989586621679974146]) = Tails a6989586621679979045
  • data IsPrefixOfSym0 :: forall a6989586621679974145. (~>) [a6989586621679974145] ((~>) [a6989586621679974145] Bool)
  • data IsPrefixOfSym1 (a6989586621679979037 :: [a6989586621679974145]) :: (~>) [a6989586621679974145] Bool
  • type IsPrefixOfSym2 (a6989586621679979037 :: [a6989586621679974145]) (a6989586621679979038 :: [a6989586621679974145]) = IsPrefixOf a6989586621679979037 a6989586621679979038
  • data IsSuffixOfSym0 :: forall a6989586621679974144. (~>) [a6989586621679974144] ((~>) [a6989586621679974144] Bool)
  • data IsSuffixOfSym1 (a6989586621679979031 :: [a6989586621679974144]) :: (~>) [a6989586621679974144] Bool
  • type IsSuffixOfSym2 (a6989586621679979031 :: [a6989586621679974144]) (a6989586621679979032 :: [a6989586621679974144]) = IsSuffixOf a6989586621679979031 a6989586621679979032
  • data IsInfixOfSym0 :: forall a6989586621679974143. (~>) [a6989586621679974143] ((~>) [a6989586621679974143] Bool)
  • data IsInfixOfSym1 (a6989586621679979025 :: [a6989586621679974143]) :: (~>) [a6989586621679974143] Bool
  • type IsInfixOfSym2 (a6989586621679979025 :: [a6989586621679974143]) (a6989586621679979026 :: [a6989586621679974143]) = IsInfixOf a6989586621679979025 a6989586621679979026
  • data ElemSym0 :: forall a6989586621680490519 t6989586621680490502. (~>) a6989586621680490519 ((~>) (t6989586621680490502 a6989586621680490519) Bool)
  • data ElemSym1 (arg6989586621680491165 :: a6989586621680490519) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490519) Bool
  • type ElemSym2 (arg6989586621680491165 :: a6989586621680490519) (arg6989586621680491166 :: t6989586621680490502 a6989586621680490519) = Elem arg6989586621680491165 arg6989586621680491166
  • data NotElemSym0 :: forall a6989586621680490413 t6989586621680490412. (~>) a6989586621680490413 ((~>) (t6989586621680490412 a6989586621680490413) Bool)
  • data NotElemSym1 (a6989586621680490891 :: a6989586621680490413) :: forall t6989586621680490412. (~>) (t6989586621680490412 a6989586621680490413) Bool
  • type NotElemSym2 (a6989586621680490891 :: a6989586621680490413) (a6989586621680490892 :: t6989586621680490412 a6989586621680490413) = NotElem a6989586621680490891 a6989586621680490892
  • data LookupSym0 :: forall a6989586621679974070 b6989586621679974071. (~>) a6989586621679974070 ((~>) [(a6989586621679974070, b6989586621679974071)] (Maybe b6989586621679974071))
  • data LookupSym1 (a6989586621679978294 :: a6989586621679974070) :: forall b6989586621679974071. (~>) [(a6989586621679974070, b6989586621679974071)] (Maybe b6989586621679974071)
  • type LookupSym2 (a6989586621679978294 :: a6989586621679974070) (a6989586621679978295 :: [(a6989586621679974070, b6989586621679974071)]) = Lookup a6989586621679978294 a6989586621679978295
  • data FindSym0 :: forall a6989586621680490411 t6989586621680490410. (~>) ((~>) a6989586621680490411 Bool) ((~>) (t6989586621680490410 a6989586621680490411) (Maybe a6989586621680490411))
  • data FindSym1 (a6989586621680490864 :: (~>) a6989586621680490411 Bool) :: forall t6989586621680490410. (~>) (t6989586621680490410 a6989586621680490411) (Maybe a6989586621680490411)
  • type FindSym2 (a6989586621680490864 :: (~>) a6989586621680490411 Bool) (a6989586621680490865 :: t6989586621680490410 a6989586621680490411) = Find a6989586621680490864 a6989586621680490865
  • data FilterSym0 :: forall a6989586621679974093. (~>) ((~>) a6989586621679974093 Bool) ((~>) [a6989586621679974093] [a6989586621679974093])
  • data FilterSym1 (a6989586621679978648 :: (~>) a6989586621679974093 Bool) :: (~>) [a6989586621679974093] [a6989586621679974093]
  • type FilterSym2 (a6989586621679978648 :: (~>) a6989586621679974093 Bool) (a6989586621679978649 :: [a6989586621679974093]) = Filter a6989586621679978648 a6989586621679978649
  • data PartitionSym0 :: forall a6989586621679974069. (~>) ((~>) a6989586621679974069 Bool) ((~>) [a6989586621679974069] ([a6989586621679974069], [a6989586621679974069]))
  • data PartitionSym1 (a6989586621679978288 :: (~>) a6989586621679974069 Bool) :: (~>) [a6989586621679974069] ([a6989586621679974069], [a6989586621679974069])
  • type PartitionSym2 (a6989586621679978288 :: (~>) a6989586621679974069 Bool) (a6989586621679978289 :: [a6989586621679974069]) = Partition a6989586621679978288 a6989586621679978289
  • data (!!@#@$) :: forall a6989586621679974062. (~>) [a6989586621679974062] ((~>) Nat a6989586621679974062)
  • data (!!@#@$$) (a6989586621679978209 :: [a6989586621679974062]) :: (~>) Nat a6989586621679974062
  • type (!!@#@$$$) (a6989586621679978209 :: [a6989586621679974062]) (a6989586621679978210 :: Nat) = (!!) a6989586621679978209 a6989586621679978210
  • data ElemIndexSym0 :: forall a6989586621679974091. (~>) a6989586621679974091 ((~>) [a6989586621679974091] (Maybe Nat))
  • data ElemIndexSym1 (a6989586621679978632 :: a6989586621679974091) :: (~>) [a6989586621679974091] (Maybe Nat)
  • type ElemIndexSym2 (a6989586621679978632 :: a6989586621679974091) (a6989586621679978633 :: [a6989586621679974091]) = ElemIndex a6989586621679978632 a6989586621679978633
  • data ElemIndicesSym0 :: forall a6989586621679974090. (~>) a6989586621679974090 ((~>) [a6989586621679974090] [Nat])
  • data ElemIndicesSym1 (a6989586621679978624 :: a6989586621679974090) :: (~>) [a6989586621679974090] [Nat]
  • type ElemIndicesSym2 (a6989586621679978624 :: a6989586621679974090) (a6989586621679978625 :: [a6989586621679974090]) = ElemIndices a6989586621679978624 a6989586621679978625
  • data FindIndexSym0 :: forall a6989586621679974089. (~>) ((~>) a6989586621679974089 Bool) ((~>) [a6989586621679974089] (Maybe Nat))
  • data FindIndexSym1 (a6989586621679978616 :: (~>) a6989586621679974089 Bool) :: (~>) [a6989586621679974089] (Maybe Nat)
  • type FindIndexSym2 (a6989586621679978616 :: (~>) a6989586621679974089 Bool) (a6989586621679978617 :: [a6989586621679974089]) = FindIndex a6989586621679978616 a6989586621679978617
  • data FindIndicesSym0 :: forall a6989586621679974088. (~>) ((~>) a6989586621679974088 Bool) ((~>) [a6989586621679974088] [Nat])
  • data FindIndicesSym1 (a6989586621679978590 :: (~>) a6989586621679974088 Bool) :: (~>) [a6989586621679974088] [Nat]
  • type FindIndicesSym2 (a6989586621679978590 :: (~>) a6989586621679974088 Bool) (a6989586621679978591 :: [a6989586621679974088]) = FindIndices a6989586621679978590 a6989586621679978591
  • data ZipSym0 :: forall a6989586621679974139 b6989586621679974140. (~>) [a6989586621679974139] ((~>) [b6989586621679974140] [(a6989586621679974139, b6989586621679974140)])
  • data ZipSym1 (a6989586621679979003 :: [a6989586621679974139]) :: forall b6989586621679974140. (~>) [b6989586621679974140] [(a6989586621679974139, b6989586621679974140)]
  • type ZipSym2 (a6989586621679979003 :: [a6989586621679974139]) (a6989586621679979004 :: [b6989586621679974140]) = Zip a6989586621679979003 a6989586621679979004
  • data Zip3Sym0 :: forall a6989586621679974136 b6989586621679974137 c6989586621679974138. (~>) [a6989586621679974136] ((~>) [b6989586621679974137] ((~>) [c6989586621679974138] [(a6989586621679974136, b6989586621679974137, c6989586621679974138)]))
  • data Zip3Sym1 (a6989586621679978991 :: [a6989586621679974136]) :: forall b6989586621679974137 c6989586621679974138. (~>) [b6989586621679974137] ((~>) [c6989586621679974138] [(a6989586621679974136, b6989586621679974137, c6989586621679974138)])
  • data Zip3Sym2 (a6989586621679978991 :: [a6989586621679974136]) (a6989586621679978992 :: [b6989586621679974137]) :: forall c6989586621679974138. (~>) [c6989586621679974138] [(a6989586621679974136, b6989586621679974137, c6989586621679974138)]
  • type Zip3Sym3 (a6989586621679978991 :: [a6989586621679974136]) (a6989586621679978992 :: [b6989586621679974137]) (a6989586621679978993 :: [c6989586621679974138]) = Zip3 a6989586621679978991 a6989586621679978992 a6989586621679978993
  • data Zip4Sym0 :: forall a6989586621680096267 b6989586621680096268 c6989586621680096269 d6989586621680096270. (~>) [a6989586621680096267] ((~>) [b6989586621680096268] ((~>) [c6989586621680096269] ((~>) [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)])))
  • data Zip4Sym1 (a6989586621680097955 :: [a6989586621680096267]) :: forall b6989586621680096268 c6989586621680096269 d6989586621680096270. (~>) [b6989586621680096268] ((~>) [c6989586621680096269] ((~>) [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]))
  • data Zip4Sym2 (a6989586621680097955 :: [a6989586621680096267]) (a6989586621680097956 :: [b6989586621680096268]) :: forall c6989586621680096269 d6989586621680096270. (~>) [c6989586621680096269] ((~>) [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)])
  • data Zip4Sym3 (a6989586621680097955 :: [a6989586621680096267]) (a6989586621680097956 :: [b6989586621680096268]) (a6989586621680097957 :: [c6989586621680096269]) :: forall d6989586621680096270. (~>) [d6989586621680096270] [(a6989586621680096267, b6989586621680096268, c6989586621680096269, d6989586621680096270)]
  • type Zip4Sym4 (a6989586621680097955 :: [a6989586621680096267]) (a6989586621680097956 :: [b6989586621680096268]) (a6989586621680097957 :: [c6989586621680096269]) (a6989586621680097958 :: [d6989586621680096270]) = Zip4 a6989586621680097955 a6989586621680097956 a6989586621680097957 a6989586621680097958
  • data Zip5Sym0 :: forall a6989586621680096262 b6989586621680096263 c6989586621680096264 d6989586621680096265 e6989586621680096266. (~>) [a6989586621680096262] ((~>) [b6989586621680096263] ((~>) [c6989586621680096264] ((~>) [d6989586621680096265] ((~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]))))
  • data Zip5Sym1 (a6989586621680097932 :: [a6989586621680096262]) :: forall b6989586621680096263 c6989586621680096264 d6989586621680096265 e6989586621680096266. (~>) [b6989586621680096263] ((~>) [c6989586621680096264] ((~>) [d6989586621680096265] ((~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])))
  • data Zip5Sym2 (a6989586621680097932 :: [a6989586621680096262]) (a6989586621680097933 :: [b6989586621680096263]) :: forall c6989586621680096264 d6989586621680096265 e6989586621680096266. (~>) [c6989586621680096264] ((~>) [d6989586621680096265] ((~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]))
  • data Zip5Sym3 (a6989586621680097932 :: [a6989586621680096262]) (a6989586621680097933 :: [b6989586621680096263]) (a6989586621680097934 :: [c6989586621680096264]) :: forall d6989586621680096265 e6989586621680096266. (~>) [d6989586621680096265] ((~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)])
  • data Zip5Sym4 (a6989586621680097932 :: [a6989586621680096262]) (a6989586621680097933 :: [b6989586621680096263]) (a6989586621680097934 :: [c6989586621680096264]) (a6989586621680097935 :: [d6989586621680096265]) :: forall e6989586621680096266. (~>) [e6989586621680096266] [(a6989586621680096262, b6989586621680096263, c6989586621680096264, d6989586621680096265, e6989586621680096266)]
  • type Zip5Sym5 (a6989586621680097932 :: [a6989586621680096262]) (a6989586621680097933 :: [b6989586621680096263]) (a6989586621680097934 :: [c6989586621680096264]) (a6989586621680097935 :: [d6989586621680096265]) (a6989586621680097936 :: [e6989586621680096266]) = Zip5 a6989586621680097932 a6989586621680097933 a6989586621680097934 a6989586621680097935 a6989586621680097936
  • data Zip6Sym0 :: forall a6989586621680096256 b6989586621680096257 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261. (~>) [a6989586621680096256] ((~>) [b6989586621680096257] ((~>) [c6989586621680096258] ((~>) [d6989586621680096259] ((~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])))))
  • data Zip6Sym1 (a6989586621680097904 :: [a6989586621680096256]) :: forall b6989586621680096257 c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261. (~>) [b6989586621680096257] ((~>) [c6989586621680096258] ((~>) [d6989586621680096259] ((~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))))
  • data Zip6Sym2 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) :: forall c6989586621680096258 d6989586621680096259 e6989586621680096260 f6989586621680096261. (~>) [c6989586621680096258] ((~>) [d6989586621680096259] ((~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])))
  • data Zip6Sym3 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) (a6989586621680097906 :: [c6989586621680096258]) :: forall d6989586621680096259 e6989586621680096260 f6989586621680096261. (~>) [d6989586621680096259] ((~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]))
  • data Zip6Sym4 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) (a6989586621680097906 :: [c6989586621680096258]) (a6989586621680097907 :: [d6989586621680096259]) :: forall e6989586621680096260 f6989586621680096261. (~>) [e6989586621680096260] ((~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)])
  • data Zip6Sym5 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) (a6989586621680097906 :: [c6989586621680096258]) (a6989586621680097907 :: [d6989586621680096259]) (a6989586621680097908 :: [e6989586621680096260]) :: forall f6989586621680096261. (~>) [f6989586621680096261] [(a6989586621680096256, b6989586621680096257, c6989586621680096258, d6989586621680096259, e6989586621680096260, f6989586621680096261)]
  • type Zip6Sym6 (a6989586621680097904 :: [a6989586621680096256]) (a6989586621680097905 :: [b6989586621680096257]) (a6989586621680097906 :: [c6989586621680096258]) (a6989586621680097907 :: [d6989586621680096259]) (a6989586621680097908 :: [e6989586621680096260]) (a6989586621680097909 :: [f6989586621680096261]) = Zip6 a6989586621680097904 a6989586621680097905 a6989586621680097906 a6989586621680097907 a6989586621680097908 a6989586621680097909
  • data Zip7Sym0 :: forall a6989586621680096249 b6989586621680096250 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [a6989586621680096249] ((~>) [b6989586621680096250] ((~>) [c6989586621680096251] ((~>) [d6989586621680096252] ((~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))))))
  • data Zip7Sym1 (a6989586621680097871 :: [a6989586621680096249]) :: forall b6989586621680096250 c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [b6989586621680096250] ((~>) [c6989586621680096251] ((~>) [d6989586621680096252] ((~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))))
  • data Zip7Sym2 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) :: forall c6989586621680096251 d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [c6989586621680096251] ((~>) [d6989586621680096252] ((~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))))
  • data Zip7Sym3 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) :: forall d6989586621680096252 e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [d6989586621680096252] ((~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])))
  • data Zip7Sym4 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) (a6989586621680097874 :: [d6989586621680096252]) :: forall e6989586621680096253 f6989586621680096254 g6989586621680096255. (~>) [e6989586621680096253] ((~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]))
  • data Zip7Sym5 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) (a6989586621680097874 :: [d6989586621680096252]) (a6989586621680097875 :: [e6989586621680096253]) :: forall f6989586621680096254 g6989586621680096255. (~>) [f6989586621680096254] ((~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)])
  • data Zip7Sym6 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) (a6989586621680097874 :: [d6989586621680096252]) (a6989586621680097875 :: [e6989586621680096253]) (a6989586621680097876 :: [f6989586621680096254]) :: forall g6989586621680096255. (~>) [g6989586621680096255] [(a6989586621680096249, b6989586621680096250, c6989586621680096251, d6989586621680096252, e6989586621680096253, f6989586621680096254, g6989586621680096255)]
  • type Zip7Sym7 (a6989586621680097871 :: [a6989586621680096249]) (a6989586621680097872 :: [b6989586621680096250]) (a6989586621680097873 :: [c6989586621680096251]) (a6989586621680097874 :: [d6989586621680096252]) (a6989586621680097875 :: [e6989586621680096253]) (a6989586621680097876 :: [f6989586621680096254]) (a6989586621680097877 :: [g6989586621680096255]) = Zip7 a6989586621680097871 a6989586621680097872 a6989586621680097873 a6989586621680097874 a6989586621680097875 a6989586621680097876 a6989586621680097877
  • data ZipWithSym0 :: forall a6989586621679974133 b6989586621679974134 c6989586621679974135. (~>) ((~>) a6989586621679974133 ((~>) b6989586621679974134 c6989586621679974135)) ((~>) [a6989586621679974133] ((~>) [b6989586621679974134] [c6989586621679974135]))
  • data ZipWithSym1 (a6989586621679978980 :: (~>) a6989586621679974133 ((~>) b6989586621679974134 c6989586621679974135)) :: (~>) [a6989586621679974133] ((~>) [b6989586621679974134] [c6989586621679974135])
  • data ZipWithSym2 (a6989586621679978980 :: (~>) a6989586621679974133 ((~>) b6989586621679974134 c6989586621679974135)) (a6989586621679978981 :: [a6989586621679974133]) :: (~>) [b6989586621679974134] [c6989586621679974135]
  • type ZipWithSym3 (a6989586621679978980 :: (~>) a6989586621679974133 ((~>) b6989586621679974134 c6989586621679974135)) (a6989586621679978981 :: [a6989586621679974133]) (a6989586621679978982 :: [b6989586621679974134]) = ZipWith a6989586621679978980 a6989586621679978981 a6989586621679978982
  • data ZipWith3Sym0 :: forall a6989586621679974129 b6989586621679974130 c6989586621679974131 d6989586621679974132. (~>) ((~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) ((~>) [a6989586621679974129] ((~>) [b6989586621679974130] ((~>) [c6989586621679974131] [d6989586621679974132])))
  • data ZipWith3Sym1 (a6989586621679978965 :: (~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) :: (~>) [a6989586621679974129] ((~>) [b6989586621679974130] ((~>) [c6989586621679974131] [d6989586621679974132]))
  • data ZipWith3Sym2 (a6989586621679978965 :: (~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) (a6989586621679978966 :: [a6989586621679974129]) :: (~>) [b6989586621679974130] ((~>) [c6989586621679974131] [d6989586621679974132])
  • data ZipWith3Sym3 (a6989586621679978965 :: (~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) (a6989586621679978966 :: [a6989586621679974129]) (a6989586621679978967 :: [b6989586621679974130]) :: (~>) [c6989586621679974131] [d6989586621679974132]
  • type ZipWith3Sym4 (a6989586621679978965 :: (~>) a6989586621679974129 ((~>) b6989586621679974130 ((~>) c6989586621679974131 d6989586621679974132))) (a6989586621679978966 :: [a6989586621679974129]) (a6989586621679978967 :: [b6989586621679974130]) (a6989586621679978968 :: [c6989586621679974131]) = ZipWith3 a6989586621679978965 a6989586621679978966 a6989586621679978967 a6989586621679978968
  • data ZipWith4Sym0 :: forall a6989586621680096244 b6989586621680096245 c6989586621680096246 d6989586621680096247 e6989586621680096248. (~>) ((~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) ((~>) [a6989586621680096244] ((~>) [b6989586621680096245] ((~>) [c6989586621680096246] ((~>) [d6989586621680096247] [e6989586621680096248]))))
  • data ZipWith4Sym1 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) :: (~>) [a6989586621680096244] ((~>) [b6989586621680096245] ((~>) [c6989586621680096246] ((~>) [d6989586621680096247] [e6989586621680096248])))
  • data ZipWith4Sym2 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) (a6989586621680097839 :: [a6989586621680096244]) :: (~>) [b6989586621680096245] ((~>) [c6989586621680096246] ((~>) [d6989586621680096247] [e6989586621680096248]))
  • data ZipWith4Sym3 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) (a6989586621680097839 :: [a6989586621680096244]) (a6989586621680097840 :: [b6989586621680096245]) :: (~>) [c6989586621680096246] ((~>) [d6989586621680096247] [e6989586621680096248])
  • data ZipWith4Sym4 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) (a6989586621680097839 :: [a6989586621680096244]) (a6989586621680097840 :: [b6989586621680096245]) (a6989586621680097841 :: [c6989586621680096246]) :: (~>) [d6989586621680096247] [e6989586621680096248]
  • type ZipWith4Sym5 (a6989586621680097838 :: (~>) a6989586621680096244 ((~>) b6989586621680096245 ((~>) c6989586621680096246 ((~>) d6989586621680096247 e6989586621680096248)))) (a6989586621680097839 :: [a6989586621680096244]) (a6989586621680097840 :: [b6989586621680096245]) (a6989586621680097841 :: [c6989586621680096246]) (a6989586621680097842 :: [d6989586621680096247]) = ZipWith4 a6989586621680097838 a6989586621680097839 a6989586621680097840 a6989586621680097841 a6989586621680097842
  • data ZipWith5Sym0 :: forall a6989586621680096238 b6989586621680096239 c6989586621680096240 d6989586621680096241 e6989586621680096242 f6989586621680096243. (~>) ((~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) ((~>) [a6989586621680096238] ((~>) [b6989586621680096239] ((~>) [c6989586621680096240] ((~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243])))))
  • data ZipWith5Sym1 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) :: (~>) [a6989586621680096238] ((~>) [b6989586621680096239] ((~>) [c6989586621680096240] ((~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243]))))
  • data ZipWith5Sym2 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) :: (~>) [b6989586621680096239] ((~>) [c6989586621680096240] ((~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243])))
  • data ZipWith5Sym3 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) (a6989586621680097817 :: [b6989586621680096239]) :: (~>) [c6989586621680096240] ((~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243]))
  • data ZipWith5Sym4 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) (a6989586621680097817 :: [b6989586621680096239]) (a6989586621680097818 :: [c6989586621680096240]) :: (~>) [d6989586621680096241] ((~>) [e6989586621680096242] [f6989586621680096243])
  • data ZipWith5Sym5 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) (a6989586621680097817 :: [b6989586621680096239]) (a6989586621680097818 :: [c6989586621680096240]) (a6989586621680097819 :: [d6989586621680096241]) :: (~>) [e6989586621680096242] [f6989586621680096243]
  • type ZipWith5Sym6 (a6989586621680097815 :: (~>) a6989586621680096238 ((~>) b6989586621680096239 ((~>) c6989586621680096240 ((~>) d6989586621680096241 ((~>) e6989586621680096242 f6989586621680096243))))) (a6989586621680097816 :: [a6989586621680096238]) (a6989586621680097817 :: [b6989586621680096239]) (a6989586621680097818 :: [c6989586621680096240]) (a6989586621680097819 :: [d6989586621680096241]) (a6989586621680097820 :: [e6989586621680096242]) = ZipWith5 a6989586621680097815 a6989586621680097816 a6989586621680097817 a6989586621680097818 a6989586621680097819 a6989586621680097820
  • data ZipWith6Sym0 :: forall a6989586621680096231 b6989586621680096232 c6989586621680096233 d6989586621680096234 e6989586621680096235 f6989586621680096236 g6989586621680096237. (~>) ((~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) ((~>) [a6989586621680096231] ((~>) [b6989586621680096232] ((~>) [c6989586621680096233] ((~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237]))))))
  • data ZipWith6Sym1 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) :: (~>) [a6989586621680096231] ((~>) [b6989586621680096232] ((~>) [c6989586621680096233] ((~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237])))))
  • data ZipWith6Sym2 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) :: (~>) [b6989586621680096232] ((~>) [c6989586621680096233] ((~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237]))))
  • data ZipWith6Sym3 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) :: (~>) [c6989586621680096233] ((~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237])))
  • data ZipWith6Sym4 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) (a6989586621680097791 :: [c6989586621680096233]) :: (~>) [d6989586621680096234] ((~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237]))
  • data ZipWith6Sym5 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) (a6989586621680097791 :: [c6989586621680096233]) (a6989586621680097792 :: [d6989586621680096234]) :: (~>) [e6989586621680096235] ((~>) [f6989586621680096236] [g6989586621680096237])
  • data ZipWith6Sym6 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) (a6989586621680097791 :: [c6989586621680096233]) (a6989586621680097792 :: [d6989586621680096234]) (a6989586621680097793 :: [e6989586621680096235]) :: (~>) [f6989586621680096236] [g6989586621680096237]
  • type ZipWith6Sym7 (a6989586621680097788 :: (~>) a6989586621680096231 ((~>) b6989586621680096232 ((~>) c6989586621680096233 ((~>) d6989586621680096234 ((~>) e6989586621680096235 ((~>) f6989586621680096236 g6989586621680096237)))))) (a6989586621680097789 :: [a6989586621680096231]) (a6989586621680097790 :: [b6989586621680096232]) (a6989586621680097791 :: [c6989586621680096233]) (a6989586621680097792 :: [d6989586621680096234]) (a6989586621680097793 :: [e6989586621680096235]) (a6989586621680097794 :: [f6989586621680096236]) = ZipWith6 a6989586621680097788 a6989586621680097789 a6989586621680097790 a6989586621680097791 a6989586621680097792 a6989586621680097793 a6989586621680097794
  • data ZipWith7Sym0 :: forall a6989586621680096223 b6989586621680096224 c6989586621680096225 d6989586621680096226 e6989586621680096227 f6989586621680096228 g6989586621680096229 h6989586621680096230. (~>) ((~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) ((~>) [a6989586621680096223] ((~>) [b6989586621680096224] ((~>) [c6989586621680096225] ((~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230])))))))
  • data ZipWith7Sym1 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) :: (~>) [a6989586621680096223] ((~>) [b6989586621680096224] ((~>) [c6989586621680096225] ((~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230]))))))
  • data ZipWith7Sym2 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) :: (~>) [b6989586621680096224] ((~>) [c6989586621680096225] ((~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230])))))
  • data ZipWith7Sym3 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) :: (~>) [c6989586621680096225] ((~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230]))))
  • data ZipWith7Sym4 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) :: (~>) [d6989586621680096226] ((~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230])))
  • data ZipWith7Sym5 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) (a6989586621680097761 :: [d6989586621680096226]) :: (~>) [e6989586621680096227] ((~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230]))
  • data ZipWith7Sym6 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) (a6989586621680097761 :: [d6989586621680096226]) (a6989586621680097762 :: [e6989586621680096227]) :: (~>) [f6989586621680096228] ((~>) [g6989586621680096229] [h6989586621680096230])
  • data ZipWith7Sym7 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) (a6989586621680097761 :: [d6989586621680096226]) (a6989586621680097762 :: [e6989586621680096227]) (a6989586621680097763 :: [f6989586621680096228]) :: (~>) [g6989586621680096229] [h6989586621680096230]
  • type ZipWith7Sym8 (a6989586621680097757 :: (~>) a6989586621680096223 ((~>) b6989586621680096224 ((~>) c6989586621680096225 ((~>) d6989586621680096226 ((~>) e6989586621680096227 ((~>) f6989586621680096228 ((~>) g6989586621680096229 h6989586621680096230))))))) (a6989586621680097758 :: [a6989586621680096223]) (a6989586621680097759 :: [b6989586621680096224]) (a6989586621680097760 :: [c6989586621680096225]) (a6989586621680097761 :: [d6989586621680096226]) (a6989586621680097762 :: [e6989586621680096227]) (a6989586621680097763 :: [f6989586621680096228]) (a6989586621680097764 :: [g6989586621680096229]) = ZipWith7 a6989586621680097757 a6989586621680097758 a6989586621680097759 a6989586621680097760 a6989586621680097761 a6989586621680097762 a6989586621680097763 a6989586621680097764
  • data UnzipSym0 :: forall a6989586621679974127 b6989586621679974128. (~>) [(a6989586621679974127, b6989586621679974128)] ([a6989586621679974127], [b6989586621679974128])
  • type UnzipSym1 (a6989586621679978946 :: [(a6989586621679974127, b6989586621679974128)]) = Unzip a6989586621679978946
  • data Unzip3Sym0 :: forall a6989586621679974124 b6989586621679974125 c6989586621679974126. (~>) [(a6989586621679974124, b6989586621679974125, c6989586621679974126)] ([a6989586621679974124], [b6989586621679974125], [c6989586621679974126])
  • type Unzip3Sym1 (a6989586621679978925 :: [(a6989586621679974124, b6989586621679974125, c6989586621679974126)]) = Unzip3 a6989586621679978925
  • data Unzip4Sym0 :: forall a6989586621679974120 b6989586621679974121 c6989586621679974122 d6989586621679974123. (~>) [(a6989586621679974120, b6989586621679974121, c6989586621679974122, d6989586621679974123)] ([a6989586621679974120], [b6989586621679974121], [c6989586621679974122], [d6989586621679974123])
  • type Unzip4Sym1 (a6989586621679978902 :: [(a6989586621679974120, b6989586621679974121, c6989586621679974122, d6989586621679974123)]) = Unzip4 a6989586621679978902
  • data Unzip5Sym0 :: forall a6989586621679974115 b6989586621679974116 c6989586621679974117 d6989586621679974118 e6989586621679974119. (~>) [(a6989586621679974115, b6989586621679974116, c6989586621679974117, d6989586621679974118, e6989586621679974119)] ([a6989586621679974115], [b6989586621679974116], [c6989586621679974117], [d6989586621679974118], [e6989586621679974119])
  • type Unzip5Sym1 (a6989586621679978877 :: [(a6989586621679974115, b6989586621679974116, c6989586621679974117, d6989586621679974118, e6989586621679974119)]) = Unzip5 a6989586621679978877
  • data Unzip6Sym0 :: forall a6989586621679974109 b6989586621679974110 c6989586621679974111 d6989586621679974112 e6989586621679974113 f6989586621679974114. (~>) [(a6989586621679974109, b6989586621679974110, c6989586621679974111, d6989586621679974112, e6989586621679974113, f6989586621679974114)] ([a6989586621679974109], [b6989586621679974110], [c6989586621679974111], [d6989586621679974112], [e6989586621679974113], [f6989586621679974114])
  • type Unzip6Sym1 (a6989586621679978850 :: [(a6989586621679974109, b6989586621679974110, c6989586621679974111, d6989586621679974112, e6989586621679974113, f6989586621679974114)]) = Unzip6 a6989586621679978850
  • data Unzip7Sym0 :: forall a6989586621679974102 b6989586621679974103 c6989586621679974104 d6989586621679974105 e6989586621679974106 f6989586621679974107 g6989586621679974108. (~>) [(a6989586621679974102, b6989586621679974103, c6989586621679974104, d6989586621679974105, e6989586621679974106, f6989586621679974107, g6989586621679974108)] ([a6989586621679974102], [b6989586621679974103], [c6989586621679974104], [d6989586621679974105], [e6989586621679974106], [f6989586621679974107], [g6989586621679974108])
  • type Unzip7Sym1 (a6989586621679978821 :: [(a6989586621679974102, b6989586621679974103, c6989586621679974104, d6989586621679974105, e6989586621679974106, f6989586621679974107, g6989586621679974108)]) = Unzip7 a6989586621679978821
  • data UnlinesSym0 :: (~>) [Symbol] Symbol
  • type UnlinesSym1 (a6989586621679978817 :: [Symbol]) = Unlines a6989586621679978817
  • data UnwordsSym0 :: (~>) [Symbol] Symbol
  • type UnwordsSym1 (a6989586621679978806 :: [Symbol]) = Unwords a6989586621679978806
  • data NubSym0 :: forall a6989586621679974061. (~>) [a6989586621679974061] [a6989586621679974061]
  • type NubSym1 (a6989586621679978189 :: [a6989586621679974061]) = Nub a6989586621679978189
  • data DeleteSym0 :: forall a6989586621679974101. (~>) a6989586621679974101 ((~>) [a6989586621679974101] [a6989586621679974101])
  • data DeleteSym1 (a6989586621679978800 :: a6989586621679974101) :: (~>) [a6989586621679974101] [a6989586621679974101]
  • type DeleteSym2 (a6989586621679978800 :: a6989586621679974101) (a6989586621679978801 :: [a6989586621679974101]) = Delete a6989586621679978800 a6989586621679978801
  • data (\\@#@$) :: forall a6989586621679974100. (~>) [a6989586621679974100] ((~>) [a6989586621679974100] [a6989586621679974100])
  • data (\\@#@$$) (a6989586621679978790 :: [a6989586621679974100]) :: (~>) [a6989586621679974100] [a6989586621679974100]
  • type (\\@#@$$$) (a6989586621679978790 :: [a6989586621679974100]) (a6989586621679978791 :: [a6989586621679974100]) = (\\) a6989586621679978790 a6989586621679978791
  • data UnionSym0 :: forall a6989586621679974057. (~>) [a6989586621679974057] ((~>) [a6989586621679974057] [a6989586621679974057])
  • data UnionSym1 (a6989586621679978139 :: [a6989586621679974057]) :: (~>) [a6989586621679974057] [a6989586621679974057]
  • type UnionSym2 (a6989586621679978139 :: [a6989586621679974057]) (a6989586621679978140 :: [a6989586621679974057]) = Union a6989586621679978139 a6989586621679978140
  • data IntersectSym0 :: forall a6989586621679974087. (~>) [a6989586621679974087] ((~>) [a6989586621679974087] [a6989586621679974087])
  • data IntersectSym1 (a6989586621679978584 :: [a6989586621679974087]) :: (~>) [a6989586621679974087] [a6989586621679974087]
  • type IntersectSym2 (a6989586621679978584 :: [a6989586621679974087]) (a6989586621679978585 :: [a6989586621679974087]) = Intersect a6989586621679978584 a6989586621679978585
  • data InsertSym0 :: forall a6989586621679974074. (~>) a6989586621679974074 ((~>) [a6989586621679974074] [a6989586621679974074])
  • data InsertSym1 (a6989586621679978347 :: a6989586621679974074) :: (~>) [a6989586621679974074] [a6989586621679974074]
  • type InsertSym2 (a6989586621679978347 :: a6989586621679974074) (a6989586621679978348 :: [a6989586621679974074]) = Insert a6989586621679978347 a6989586621679978348
  • data SortSym0 :: forall a6989586621679974073. (~>) [a6989586621679974073] [a6989586621679974073]
  • type SortSym1 (a6989586621679978344 :: [a6989586621679974073]) = Sort a6989586621679978344
  • data NubBySym0 :: forall a6989586621679974060. (~>) ((~>) a6989586621679974060 ((~>) a6989586621679974060 Bool)) ((~>) [a6989586621679974060] [a6989586621679974060])
  • data NubBySym1 (a6989586621679978164 :: (~>) a6989586621679974060 ((~>) a6989586621679974060 Bool)) :: (~>) [a6989586621679974060] [a6989586621679974060]
  • type NubBySym2 (a6989586621679978164 :: (~>) a6989586621679974060 ((~>) a6989586621679974060 Bool)) (a6989586621679978165 :: [a6989586621679974060]) = NubBy a6989586621679978164 a6989586621679978165
  • data DeleteBySym0 :: forall a6989586621679974099. (~>) ((~>) a6989586621679974099 ((~>) a6989586621679974099 Bool)) ((~>) a6989586621679974099 ((~>) [a6989586621679974099] [a6989586621679974099]))
  • data DeleteBySym1 (a6989586621679978768 :: (~>) a6989586621679974099 ((~>) a6989586621679974099 Bool)) :: (~>) a6989586621679974099 ((~>) [a6989586621679974099] [a6989586621679974099])
  • data DeleteBySym2 (a6989586621679978768 :: (~>) a6989586621679974099 ((~>) a6989586621679974099 Bool)) (a6989586621679978769 :: a6989586621679974099) :: (~>) [a6989586621679974099] [a6989586621679974099]
  • type DeleteBySym3 (a6989586621679978768 :: (~>) a6989586621679974099 ((~>) a6989586621679974099 Bool)) (a6989586621679978769 :: a6989586621679974099) (a6989586621679978770 :: [a6989586621679974099]) = DeleteBy a6989586621679978768 a6989586621679978769 a6989586621679978770
  • data DeleteFirstsBySym0 :: forall a6989586621679974098. (~>) ((~>) a6989586621679974098 ((~>) a6989586621679974098 Bool)) ((~>) [a6989586621679974098] ((~>) [a6989586621679974098] [a6989586621679974098]))
  • data DeleteFirstsBySym1 (a6989586621679978755 :: (~>) a6989586621679974098 ((~>) a6989586621679974098 Bool)) :: (~>) [a6989586621679974098] ((~>) [a6989586621679974098] [a6989586621679974098])
  • data DeleteFirstsBySym2 (a6989586621679978755 :: (~>) a6989586621679974098 ((~>) a6989586621679974098 Bool)) (a6989586621679978756 :: [a6989586621679974098]) :: (~>) [a6989586621679974098] [a6989586621679974098]
  • type DeleteFirstsBySym3 (a6989586621679978755 :: (~>) a6989586621679974098 ((~>) a6989586621679974098 Bool)) (a6989586621679978756 :: [a6989586621679974098]) (a6989586621679978757 :: [a6989586621679974098]) = DeleteFirstsBy a6989586621679978755 a6989586621679978756 a6989586621679978757
  • data UnionBySym0 :: forall a6989586621679974058. (~>) ((~>) a6989586621679974058 ((~>) a6989586621679974058 Bool)) ((~>) [a6989586621679974058] ((~>) [a6989586621679974058] [a6989586621679974058]))
  • data UnionBySym1 (a6989586621679978145 :: (~>) a6989586621679974058 ((~>) a6989586621679974058 Bool)) :: (~>) [a6989586621679974058] ((~>) [a6989586621679974058] [a6989586621679974058])
  • data UnionBySym2 (a6989586621679978145 :: (~>) a6989586621679974058 ((~>) a6989586621679974058 Bool)) (a6989586621679978146 :: [a6989586621679974058]) :: (~>) [a6989586621679974058] [a6989586621679974058]
  • type UnionBySym3 (a6989586621679978145 :: (~>) a6989586621679974058 ((~>) a6989586621679974058 Bool)) (a6989586621679978146 :: [a6989586621679974058]) (a6989586621679978147 :: [a6989586621679974058]) = UnionBy a6989586621679978145 a6989586621679978146 a6989586621679978147
  • data IntersectBySym0 :: forall a6989586621679974086. (~>) ((~>) a6989586621679974086 ((~>) a6989586621679974086 Bool)) ((~>) [a6989586621679974086] ((~>) [a6989586621679974086] [a6989586621679974086]))
  • data IntersectBySym1 (a6989586621679978548 :: (~>) a6989586621679974086 ((~>) a6989586621679974086 Bool)) :: (~>) [a6989586621679974086] ((~>) [a6989586621679974086] [a6989586621679974086])
  • data IntersectBySym2 (a6989586621679978548 :: (~>) a6989586621679974086 ((~>) a6989586621679974086 Bool)) (a6989586621679978549 :: [a6989586621679974086]) :: (~>) [a6989586621679974086] [a6989586621679974086]
  • type IntersectBySym3 (a6989586621679978548 :: (~>) a6989586621679974086 ((~>) a6989586621679974086 Bool)) (a6989586621679978549 :: [a6989586621679974086]) (a6989586621679978550 :: [a6989586621679974086]) = IntersectBy a6989586621679978548 a6989586621679978549 a6989586621679978550
  • data GroupBySym0 :: forall a6989586621679974072. (~>) ((~>) a6989586621679974072 ((~>) a6989586621679974072 Bool)) ((~>) [a6989586621679974072] [[a6989586621679974072]])
  • data GroupBySym1 (a6989586621679978311 :: (~>) a6989586621679974072 ((~>) a6989586621679974072 Bool)) :: (~>) [a6989586621679974072] [[a6989586621679974072]]
  • type GroupBySym2 (a6989586621679978311 :: (~>) a6989586621679974072 ((~>) a6989586621679974072 Bool)) (a6989586621679978312 :: [a6989586621679974072]) = GroupBy a6989586621679978311 a6989586621679978312
  • data SortBySym0 :: forall a6989586621679974097. (~>) ((~>) a6989586621679974097 ((~>) a6989586621679974097 Ordering)) ((~>) [a6989586621679974097] [a6989586621679974097])
  • data SortBySym1 (a6989586621679978747 :: (~>) a6989586621679974097 ((~>) a6989586621679974097 Ordering)) :: (~>) [a6989586621679974097] [a6989586621679974097]
  • type SortBySym2 (a6989586621679978747 :: (~>) a6989586621679974097 ((~>) a6989586621679974097 Ordering)) (a6989586621679978748 :: [a6989586621679974097]) = SortBy a6989586621679978747 a6989586621679978748
  • data InsertBySym0 :: forall a6989586621679974096. (~>) ((~>) a6989586621679974096 ((~>) a6989586621679974096 Ordering)) ((~>) a6989586621679974096 ((~>) [a6989586621679974096] [a6989586621679974096]))
  • data InsertBySym1 (a6989586621679978723 :: (~>) a6989586621679974096 ((~>) a6989586621679974096 Ordering)) :: (~>) a6989586621679974096 ((~>) [a6989586621679974096] [a6989586621679974096])
  • data InsertBySym2 (a6989586621679978723 :: (~>) a6989586621679974096 ((~>) a6989586621679974096 Ordering)) (a6989586621679978724 :: a6989586621679974096) :: (~>) [a6989586621679974096] [a6989586621679974096]
  • type InsertBySym3 (a6989586621679978723 :: (~>) a6989586621679974096 ((~>) a6989586621679974096 Ordering)) (a6989586621679978724 :: a6989586621679974096) (a6989586621679978725 :: [a6989586621679974096]) = InsertBy a6989586621679978723 a6989586621679978724 a6989586621679978725
  • data MaximumBySym0 :: forall a6989586621680490417 t6989586621680490416. (~>) ((~>) a6989586621680490417 ((~>) a6989586621680490417 Ordering)) ((~>) (t6989586621680490416 a6989586621680490417) a6989586621680490417)
  • data MaximumBySym1 (a6989586621680490924 :: (~>) a6989586621680490417 ((~>) a6989586621680490417 Ordering)) :: forall t6989586621680490416. (~>) (t6989586621680490416 a6989586621680490417) a6989586621680490417
  • type MaximumBySym2 (a6989586621680490924 :: (~>) a6989586621680490417 ((~>) a6989586621680490417 Ordering)) (a6989586621680490925 :: t6989586621680490416 a6989586621680490417) = MaximumBy a6989586621680490924 a6989586621680490925
  • data MinimumBySym0 :: forall a6989586621680490415 t6989586621680490414. (~>) ((~>) a6989586621680490415 ((~>) a6989586621680490415 Ordering)) ((~>) (t6989586621680490414 a6989586621680490415) a6989586621680490415)
  • data MinimumBySym1 (a6989586621680490899 :: (~>) a6989586621680490415 ((~>) a6989586621680490415 Ordering)) :: forall t6989586621680490414. (~>) (t6989586621680490414 a6989586621680490415) a6989586621680490415
  • type MinimumBySym2 (a6989586621680490899 :: (~>) a6989586621680490415 ((~>) a6989586621680490415 Ordering)) (a6989586621680490900 :: t6989586621680490414 a6989586621680490415) = MinimumBy a6989586621680490899 a6989586621680490900
  • data GenericLengthSym0 :: forall a6989586621679974056 i6989586621679974055. (~>) [a6989586621679974056] i6989586621679974055
  • type GenericLengthSym1 (a6989586621679978132 :: [a6989586621679974056]) = GenericLength a6989586621679978132
  • data GenericTakeSym0 :: forall i6989586621680096221 a6989586621680096222. (~>) i6989586621680096221 ((~>) [a6989586621680096222] [a6989586621680096222])
  • data GenericTakeSym1 (a6989586621680097751 :: i6989586621680096221) :: forall a6989586621680096222. (~>) [a6989586621680096222] [a6989586621680096222]
  • type GenericTakeSym2 (a6989586621680097751 :: i6989586621680096221) (a6989586621680097752 :: [a6989586621680096222]) = GenericTake a6989586621680097751 a6989586621680097752
  • data GenericDropSym0 :: forall i6989586621680096219 a6989586621680096220. (~>) i6989586621680096219 ((~>) [a6989586621680096220] [a6989586621680096220])
  • data GenericDropSym1 (a6989586621680097741 :: i6989586621680096219) :: forall a6989586621680096220. (~>) [a6989586621680096220] [a6989586621680096220]
  • type GenericDropSym2 (a6989586621680097741 :: i6989586621680096219) (a6989586621680097742 :: [a6989586621680096220]) = GenericDrop a6989586621680097741 a6989586621680097742
  • data GenericSplitAtSym0 :: forall i6989586621680096217 a6989586621680096218. (~>) i6989586621680096217 ((~>) [a6989586621680096218] ([a6989586621680096218], [a6989586621680096218]))
  • data GenericSplitAtSym1 (a6989586621680097731 :: i6989586621680096217) :: forall a6989586621680096218. (~>) [a6989586621680096218] ([a6989586621680096218], [a6989586621680096218])
  • type GenericSplitAtSym2 (a6989586621680097731 :: i6989586621680096217) (a6989586621680097732 :: [a6989586621680096218]) = GenericSplitAt a6989586621680097731 a6989586621680097732
  • data GenericIndexSym0 :: forall a6989586621680096216 i6989586621680096215. (~>) [a6989586621680096216] ((~>) i6989586621680096215 a6989586621680096216)
  • data GenericIndexSym1 (a6989586621680097721 :: [a6989586621680096216]) :: forall i6989586621680096215. (~>) i6989586621680096215 a6989586621680096216
  • type GenericIndexSym2 (a6989586621680097721 :: [a6989586621680096216]) (a6989586621680097722 :: i6989586621680096215) = GenericIndex a6989586621680097721 a6989586621680097722
  • data GenericReplicateSym0 :: forall i6989586621680096213 a6989586621680096214. (~>) i6989586621680096213 ((~>) a6989586621680096214 [a6989586621680096214])
  • data GenericReplicateSym1 (a6989586621680097711 :: i6989586621680096213) :: forall a6989586621680096214. (~>) a6989586621680096214 [a6989586621680096214]
  • type GenericReplicateSym2 (a6989586621680097711 :: i6989586621680096213) (a6989586621680097712 :: a6989586621680096214) = GenericReplicate a6989586621680097711 a6989586621680097712

The singleton for lists

type family Sing :: k -> Type Source #

The singleton kind-indexed type family.

Instances

Instances details
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SBool
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Sing = SNat
type Sing Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Sing = SSymbol
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple0
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SVoid
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SAll
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SAny
type Sing Source # 
Instance details

Defined in Data.Singletons.TypeError

type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SList :: [a] -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SMaybe :: Maybe a -> Type
type Sing 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` 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

type Sing = TypeRep :: TYPE rep -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SMin :: Min a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SMax :: Max a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SFirst :: First a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SLast :: Last a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SOption :: Option a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SIdentity :: Identity a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Sing = SFirst :: First a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Sing = SLast :: Last a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SDual :: Dual a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SSum :: Sum a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SProduct :: Product a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Sing = SDown :: Down a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SNonEmpty :: NonEmpty a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SEither :: Either a b -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple2 :: (a, b) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sing = SArg :: Arg a b -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Internal

type Sing = SLambda :: (k1 ~> k2) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Internal

type Sing Source # 
Instance details

Defined in Data.Singletons.Sigma

type Sing = SSigma :: Sigma s t -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple3 :: (a, b, c) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Sing = SConst :: Const a b -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple4 :: (a, b, c, d) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple5 :: (a, b, c, d, e) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple6 :: (a, b, c, d, e, f) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple7 :: (a, b, c, d, e, f, g) -> Type

data SList :: forall a. [a] -> Type where Source #

Constructors

SNil :: SList '[] 
SCons :: forall a (n :: a) (n :: [a]). (Sing (n :: a)) -> (Sing (n :: [a])) -> SList ('(:) n n) infixr 5 

Instances

Instances details
(SDecide a, SDecide [a]) => TestCoercion (SList :: [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

testCoercion :: forall (a0 :: k) (b :: k). SList a0 -> SList b -> Maybe (Coercion a0 b) #

(SDecide a, SDecide [a]) => TestEquality (SList :: [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

testEquality :: forall (a0 :: k) (b :: k). SList a0 -> SList b -> Maybe (a0 :~: b) #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: SList z -> String #

showList :: [SList z] -> ShowS #

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 (Let6989586621679979512Init'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

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

Defined in Data.Singletons.Prelude.Foldable

type Null (a :: [a6989586621680490517])
type Null (arg0 :: Maybe a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (arg0 :: Maybe a0)
type Null (arg0 :: Min a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Null (arg0 :: Min a0)
type Null (arg0 :: Max a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Null (arg0 :: Max a0)
type Null (arg0 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Null (arg0 :: First a0)
type Null (arg0 :: Last a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Null (arg0 :: Last a0)
type Null (arg0 :: Option a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Null (arg0 :: Option a0)
type Null (a :: Identity a6989586621680490517) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Null (a :: Identity a6989586621680490517)
type Null (arg0 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (arg0 :: First a0)
type Null (arg0 :: Last a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (arg0 :: Last a0)
type Null (a :: Dual a6989586621680490517) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Null (a :: Product a6989586621680490517)
type Null (arg0 :: NonEmpty a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (arg0 :: NonEmpty a0)
type Null (a2 :: Either a1 a6989586621680490517) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (a2 :: Either a1 a6989586621680490517)
type Null (arg0 :: (a, a0)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (arg0 :: (a, a0))
type Null (arg0 :: Arg a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Null (arg0 :: Arg a a0)
type Null (arg0 :: Const m a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Null (arg0 :: Const m a0)

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

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

Defined in Data.Singletons.Prelude.Foldable

type Length (a :: [a6989586621680490518])
type Length (arg0 :: Maybe a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (arg0 :: Maybe a0)
type Length (arg0 :: Min a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Length (arg0 :: Min a0)
type Length (arg0 :: Max a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Length (arg0 :: Max a0)
type Length (arg0 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Length (arg0 :: First a0)
type Length (arg0 :: Last a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Length (arg0 :: Last a0)
type Length (arg0 :: Option a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Length (arg0 :: Option a0)
type Length (a :: Identity a6989586621680490518) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Length (a :: Identity a6989586621680490518)
type Length (arg0 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (arg0 :: First a0)
type Length (arg0 :: Last a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (arg0 :: Last a0)
type Length (a :: Dual a6989586621680490518) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Length (a :: Product a6989586621680490518)
type Length (arg0 :: NonEmpty a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (arg0 :: NonEmpty a0)
type Length (a2 :: Either a1 a6989586621680490518) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (a2 :: Either a1 a6989586621680490518)
type Length (arg0 :: (a, a0)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (arg0 :: (a, a0))
type Length (arg0 :: Arg a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Length (arg0 :: Arg a a0)
type Length (arg0 :: Const m a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Length (arg0 :: Const m a0)

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 (Let6989586621679979496RevSym1 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 (Let6989586621679979362PermsSym1 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

Instances details
type Foldl (a1 :: k2 ~> (a6989586621680490511 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680490511) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Foldl (a1 :: k2 ~> (a6989586621680490511 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680490511)
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Last a0)
type Foldl (a1 :: k2 ~> (a6989586621680490511 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680490511) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Foldl (a1 :: k2 ~> (a6989586621680490511 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680490511)
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Min a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Option a0)
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Either a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Either a a0)
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: (a, a0)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: (a, a0))
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Arg a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Arg a a0)
type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Const m a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Foldl (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Const m a0)

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

Instances details
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Maybe a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Maybe a0)
type Foldl' (a1 :: k2 ~> (a6989586621680490513 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680490513]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (a1 :: k2 ~> (a6989586621680490513 ~> k2)) (a2 :: k2) (a3 :: [a6989586621680490513])
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: NonEmpty a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: NonEmpty a0)
type Foldl' (a1 :: k2 ~> (a6989586621680490513 ~> k2)) (a2 :: k2) (a3 :: Dual a6989586621680490513) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (a1 :: k2 ~> (a6989586621680490513 ~> k2)) (a2 :: k2) (a3 :: Product a6989586621680490513)
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Last a0)
type Foldl' (a1 :: k2 ~> (a6989586621680490513 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680490513) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Foldl' (a1 :: k2 ~> (a6989586621680490513 ~> k2)) (a2 :: k2) (a3 :: Identity a6989586621680490513)
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Min a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Option a0)
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Either a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Either a a0)
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: (a, a0)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: (a, a0))
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Arg a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Arg a a0)
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Const m a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Const m a0)

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

Instances details
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Maybe a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Maybe a0)
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 (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 (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 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Last a0)
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 :: a0 ~> (a0 ~> a0)) (arg2 :: Min a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Either a a0)
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: (a, a0)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: (a, a0))
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Arg a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

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

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

type Foldr (a1 :: a6989586621680490506 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Last a6989586621680490506)
type Foldr (arg1 :: a0 ~> (b0 ~> b0)) (arg2 :: b0) (arg3 :: Option a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Foldr (arg1 :: a0 ~> (b0 ~> b0)) (arg2 :: b0) (arg3 :: Option a0)
type Foldr (a2 :: a6989586621680490506 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Either a1 a6989586621680490506) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

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

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

Instances details
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Maybe a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Maybe a0)
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 (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 (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 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Last a0)
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 :: a0 ~> (a0 ~> a0)) (arg2 :: Min a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Either a a0)
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: (a, a0)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: (a, a0))
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Arg a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

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

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_6989586621680491012Sym0 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_6989586621680490999Sym0 f) xs)) '[]) xs 

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

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

Equations

And x = Case_6989586621680490989 x (Let6989586621680490987Scrutinee_6989586621680490749Sym1 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_6989586621680490980 x (Let6989586621680490978Scrutinee_6989586621680490751Sym1 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_6989586621680490971 p x (Let6989586621680490968Scrutinee_6989586621680490753Sym2 p x) 

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

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

Equations

All p x = Case_6989586621680490958 p x (Let6989586621680490955Scrutinee_6989586621680490755Sym2 p x) 

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

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

Instances

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg0 :: Maybe a0)
type Sum (arg0 :: Min a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sum (arg0 :: Min a0)
type Sum (arg0 :: Max a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sum (arg0 :: Max a0)
type Sum (arg0 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sum (arg0 :: First a0)
type Sum (arg0 :: Last a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sum (arg0 :: Last a0)
type Sum (arg0 :: Option a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg0 :: First a0)
type Sum (arg0 :: Last a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg0 :: Last a0)
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 (arg0 :: NonEmpty a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg0 :: NonEmpty a0)
type Sum (arg0 :: Either a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg0 :: Either a a0)
type Sum (arg0 :: (a, a0)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg0 :: (a, a0))
type Sum (arg0 :: Arg a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sum (arg0 :: Arg a a0)
type Sum (arg0 :: Const m a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Sum (arg0 :: Const m a0)

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Product (arg0 :: Maybe a0)
type Product (arg0 :: Min a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Product (arg0 :: Min a0)
type Product (arg0 :: Max a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Product (arg0 :: Max a0)
type Product (arg0 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Product (arg0 :: First a0)
type Product (arg0 :: Last a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Product (arg0 :: Last a0)
type Product (arg0 :: Option a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

type Product (arg0 :: First a0)
type Product (arg0 :: Last a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg0 :: Last a0)
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 (arg0 :: NonEmpty a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg0 :: NonEmpty a0)
type Product (arg0 :: Either a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg0 :: Either a a0)
type Product (arg0 :: (a, a0)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg0 :: (a, a0))
type Product (arg0 :: Arg a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Product (arg0 :: Arg a a0)
type Product (arg0 :: Const m a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Product (arg0 :: Const m a0)

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg0 :: Maybe a0)
type Maximum (arg0 :: Min a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Maximum (arg0 :: Min a0)
type Maximum (arg0 :: Max a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Maximum (arg0 :: Max a0)
type Maximum (arg0 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Maximum (arg0 :: First a0)
type Maximum (arg0 :: Last a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Maximum (arg0 :: Last a0)
type Maximum (arg0 :: Option a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg0 :: First a0)
type Maximum (arg0 :: Last a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg0 :: Last a0)
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 (arg0 :: NonEmpty a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg0 :: NonEmpty a0)
type Maximum (arg0 :: Either a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg0 :: Either a a0)
type Maximum (arg0 :: (a, a0)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg0 :: (a, a0))
type Maximum (arg0 :: Arg a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Maximum (arg0 :: Arg a a0)
type Maximum (arg0 :: Const m a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Maximum (arg0 :: Const m a0)

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg0 :: Maybe a0)
type Minimum (arg0 :: Min a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Minimum (arg0 :: Min a0)
type Minimum (arg0 :: Max a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Minimum (arg0 :: Max a0)
type Minimum (arg0 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Minimum (arg0 :: First a0)
type Minimum (arg0 :: Last a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Minimum (arg0 :: Last a0)
type Minimum (arg0 :: Option a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg0 :: First a0)
type Minimum (arg0 :: Last a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg0 :: Last a0)
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 (arg0 :: NonEmpty a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg0 :: NonEmpty a0)
type Minimum (arg0 :: Either a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg0 :: Either a a0)
type Minimum (arg0 :: (a, a0)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg0 :: (a, a0))
type Minimum (arg0 :: Arg a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Minimum (arg0 :: Arg a a0)
type Minimum (arg0 :: Const m a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Minimum (arg0 :: Const m a0)

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_6989586621679979263 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_6989586621679979242 f q0 x xs (Let6989586621679979237Scrutinee_6989586621679974651Sym4 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_6989586621679974663 wild_6989586621679974665)) = Case_6989586621679979221 f x wild_6989586621679974663 wild_6989586621679974665 (Let6989586621679979216Scrutinee_6989586621679974657Sym4 f x wild_6989586621679974663 wild_6989586621679974665) 

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

Accumulating maps

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

Equations

MapAccumL f s t = Case_6989586621680804743 f s t (Let6989586621680804739Scrutinee_6989586621680804310Sym3 f s t) 

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

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

Equations

MapAccumR f s t = Case_6989586621680804726 f s t (Let6989586621680804722Scrutinee_6989586621680804314Sym3 f s t) 

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

Cyclical lists

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

Equations

Replicate n x = Case_6989586621679978238 n x (Let6989586621679978235Scrutinee_6989586621679974759Sym2 n x) 

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

Unfolding

type family Unfoldr (a :: (~>) b (Maybe (a, b))) (a :: b) :: [a] where ... Source #

Equations

Unfoldr f b = Case_6989586621679979069 f b (Let6989586621679979066Scrutinee_6989586621679974667Sym2 f b) 

sUnfoldr :: forall b a (t :: (~>) b (Maybe (a, b))) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a]) Source #

Sublists

Extracting sublists

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

Equations

Take _ '[] = '[] 
Take n ('(:) x xs) = Case_6989586621679978401 n x xs (Let6989586621679978397Scrutinee_6989586621679974743Sym3 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_6989586621679978387 n x xs (Let6989586621679978383Scrutinee_6989586621679974745Sym3 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_6989586621679978545 p x xs (Let6989586621679978541Scrutinee_6989586621679974733Sym3 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_6989586621679978531 p x xs' (Let6989586621679978527Scrutinee_6989586621679974735Sym3 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_6989586621679978494 = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_6989586621679978498Sym0 p) a_6989586621679978494)) '[]) a_6989586621679978494 

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 Let6989586621679978451XsSym0) Let6989586621679978451XsSym0 
Span p ('(:) x xs') = Case_6989586621679978463 p x xs' (Let6989586621679978459Scrutinee_6989586621679974739Sym3 p x xs') 

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

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

Equations

Break _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679978408XsSym0) Let6989586621679978408XsSym0 
Break p ('(:) x xs') = Case_6989586621679978420 p x xs' (Let6989586621679978416Scrutinee_6989586621679974741Sym3 p x xs') 

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

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

Equations

StripPrefix '[] ys = Apply JustSym0 ys 
StripPrefix arg_6989586621680096339 arg_6989586621680096341 = Case_6989586621680097974 arg_6989586621680096339 arg_6989586621680096341 (Apply (Apply Tuple2Sym0 arg_6989586621680096339) arg_6989586621680096341) 

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

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_6989586621679979055 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_6989586621679979048 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

Instances details
type Elem (arg1 :: a0) (arg2 :: Maybe a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Elem (arg1 :: a0) (arg2 :: NonEmpty a0)
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 :: a0) (arg2 :: First a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Elem (arg1 :: a0) (arg2 :: Last a0)
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 :: a0) (arg2 :: Min a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Foldable

type Elem (arg1 :: a0) (arg2 :: Either a a0)
type Elem (arg1 :: a0) (arg2 :: (a, a0)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (arg1 :: a0) (arg2 :: (a, a0))
type Elem (arg1 :: a0) (arg2 :: Arg a a0) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

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

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_6989586621680490895 = Apply (Apply (Apply (.@#@$) NotSym0) (Apply ElemSym0 x)) a_6989586621680490895 

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

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

Equations

Lookup _key '[] = NothingSym0 
Lookup key ('(:) '(x, y) xys) = Case_6989586621679978308 key x y xys (Let6989586621679978303Scrutinee_6989586621679974755Sym4 key x y xys) 

sLookup :: forall a b (t :: a) (t :: [(a, b)]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b) Source #

Searching with a predicate

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

Equations

Find p y = Case_6989586621680490887 p y (Let6989586621680490870Scrutinee_6989586621680490761Sym2 p y) 

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

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

Equations

Filter _p '[] = '[] 
Filter p ('(:) x xs) = Case_6989586621679978660 p x xs (Let6989586621679978656Scrutinee_6989586621679974721Sym3 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_6989586621679978220 x xs n (Let6989586621679978216Scrutinee_6989586621679974761Sym3 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_6989586621679978636 = Apply (Apply FindIndexSym0 (Apply (==@#@$) x)) a_6989586621679978636 

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

sElemIndices :: forall a (t :: a) (t :: [a]). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat]) Source #

type family FindIndex (a :: (~>) a Bool) (a :: [a]) :: Maybe Nat where ... Source #

Equations

FindIndex p a_6989586621679978620 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679978620 

sFindIndex :: forall a (t :: (~>) a Bool) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat) Source #

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_6989586621679978605Sym0 p) xs)) (Apply (Apply ZipSym0 xs) (Apply (Apply (Let6989586621679978596BuildListSym2 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_6989586621680097947 a_6989586621680097949 a_6989586621680097951 a_6989586621680097953 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621680097947) a_6989586621680097949) a_6989586621680097951) a_6989586621680097953 

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

Equations

Zip5 a_6989586621680097922 a_6989586621680097924 a_6989586621680097926 a_6989586621680097928 a_6989586621680097930 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621680097922) a_6989586621680097924) a_6989586621680097926) a_6989586621680097928) a_6989586621680097930 

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

Equations

Zip6 a_6989586621680097892 a_6989586621680097894 a_6989586621680097896 a_6989586621680097898 a_6989586621680097900 a_6989586621680097902 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621680097892) a_6989586621680097894) a_6989586621680097896) a_6989586621680097898) a_6989586621680097900) a_6989586621680097902 

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

Equations

Zip7 a_6989586621680097857 a_6989586621680097859 a_6989586621680097861 a_6989586621680097863 a_6989586621680097865 a_6989586621680097867 a_6989586621680097869 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621680097857) a_6989586621680097859) a_6989586621680097861) a_6989586621680097863) a_6989586621680097865) a_6989586621680097867) a_6989586621680097869 

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_6989586621679978949Sym0 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_6989586621679978928Sym0 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_6989586621679978905Sym0 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_6989586621679978880Sym0 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_6989586621679978853Sym0 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_6989586621679978824Sym0 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 (Let6989586621679978810GoSym2 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 (Let6989586621679978192Nub'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_6989586621679978796 a_6989586621679978798 = Apply (Apply (Apply DeleteBySym0 (==@#@$)) a_6989586621679978796) a_6989586621679978798 

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_6989586621679978786 \\ a_6989586621679978788 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 DeleteSym0)) a_6989586621679978786) a_6989586621679978788 

(%\\) :: 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_6989586621679978135 a_6989586621679978137 = Apply (Apply (Apply UnionBySym0 (==@#@$)) a_6989586621679978135) a_6989586621679978137 

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_6989586621679978580 a_6989586621679978582 = Apply (Apply (Apply IntersectBySym0 (==@#@$)) a_6989586621679978580) a_6989586621679978582 

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_6989586621679978342 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679978342 

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 (Let6989586621679978170NubBy'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_6989586621679978783 eq x y ys (Let6989586621679978778Scrutinee_6989586621679974705Sym4 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_6989586621679978761 a_6989586621679978763 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679978761) a_6989586621679978763 

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

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_6989586621679974725 wild_6989586621679974727) ('(:) wild_6989586621679974729 wild_6989586621679974731) = Apply (Apply (>>=@#@$) (Let6989586621679978559XsSym5 eq wild_6989586621679974725 wild_6989586621679974727 wild_6989586621679974729 wild_6989586621679974731)) (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679978570Sym0 eq) wild_6989586621679974725) wild_6989586621679974727) wild_6989586621679974729) wild_6989586621679974731) 

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

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

Equations

GroupBy _ '[] = '[] 
GroupBy eq ('(:) x xs) = Apply (Apply (:@#@$) (Apply (Apply (:@#@$) x) (Let6989586621679978318YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621679978318ZsSym3 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_6989586621679978751 = Apply (Apply (Apply FoldrSym0 (Apply InsertBySym0 cmp)) '[]) a_6989586621679978751 

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_6989586621679978744 cmp x y ys' (Let6989586621679978739Scrutinee_6989586621679974707Sym4 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_6989586621680490928 = Apply (Apply Foldl1Sym0 (Let6989586621680490932Max'Sym2 cmp a_6989586621680490928)) a_6989586621680490928 

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

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

Equations

MinimumBy cmp a_6989586621680490903 = Apply (Apply Foldl1Sym0 (Let6989586621680490907Min'Sym2 cmp a_6989586621680490903)) a_6989586621680490903 

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

The "generic" operations

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

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

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

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

Equations

GenericTake a_6989586621680097747 a_6989586621680097749 = Apply (Apply TakeSym0 a_6989586621680097747) a_6989586621680097749 

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

Equations

GenericDrop a_6989586621680097737 a_6989586621680097739 = Apply (Apply DropSym0 a_6989586621680097737) a_6989586621680097739 

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

Equations

GenericSplitAt a_6989586621680097727 a_6989586621680097729 = Apply (Apply SplitAtSym0 a_6989586621680097727) a_6989586621680097729 

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

Equations

GenericIndex a_6989586621680097717 a_6989586621680097719 = Apply (Apply (!!@#@$) a_6989586621680097717) a_6989586621680097719 

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

Equations

GenericReplicate a_6989586621680097707 a_6989586621680097709 = Apply (Apply ReplicateSym0 a_6989586621680097707) a_6989586621680097709 

Defunctionalization symbols

type NilSym0 = '[] Source #

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

Instances

Instances details
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) (t6989586621679315156 :: a3530822107858468865) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

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

Instances

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

Defined in Data.Singletons.Prelude.Instances

Methods

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

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

type (:@#@$$$) (t6989586621679315156 :: a3530822107858468865) (t6989586621679315157 :: [a3530822107858468865]) = '(:) t6989586621679315156 t6989586621679315157 Source #

type (++@#@$$$) (a6989586621679545630 :: [a6989586621679545433]) (a6989586621679545631 :: [a6989586621679545433]) = (++) a6989586621679545630 a6989586621679545631 Source #

data (++@#@$$) (a6989586621679545630 :: [a6989586621679545433]) :: (~>) [a6989586621679545433] [a6989586621679545433] infixr 5 Source #

Instances

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

Defined in Data.Singletons.Prelude.Base

Methods

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

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

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

Instances

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

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

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type HeadSym1 (a6989586621679979530 :: [a6989586621679974183]) = Head a6989586621679979530 Source #

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

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type LastSym1 (a6989586621679979525 :: [a6989586621679974182]) = Last a6989586621679979525 Source #

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

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type TailSym1 (a6989586621679979522 :: [a6989586621679974181]) = Tail a6989586621679979522 Source #

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

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type InitSym1 (a6989586621679979508 :: [a6989586621679974180]) = Init a6989586621679979508 Source #

data NullSym0 :: forall t6989586621680490502 a6989586621680490517. (~>) (t6989586621680490502 a6989586621680490517) Bool Source #

Instances

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680490502 a6989586621680490517) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type NullSym1 (arg6989586621680491161 :: t6989586621680490502 a6989586621680490517) = Null arg6989586621680491161 Source #

data LengthSym0 :: forall t6989586621680490502 a6989586621680490518. (~>) (t6989586621680490502 a6989586621680490518) Nat Source #

Instances

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (LengthSym0 :: TyFun (t6989586621680490502 a6989586621680490518) Nat -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type LengthSym1 (arg6989586621680491163 :: t6989586621680490502 a6989586621680490518) = Length arg6989586621680491163 Source #

data MapSym0 :: forall a6989586621679545434 b6989586621679545435. (~>) ((~>) a6989586621679545434 b6989586621679545435) ((~>) [a6989586621679545434] [b6989586621679545435]) Source #

Instances

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym0 :: TyFun (a6989586621679545434 ~> b6989586621679545435) ([a6989586621679545434] ~> [b6989586621679545435]) -> Type) (a6989586621679545638 :: a6989586621679545434 ~> b6989586621679545435) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym0 :: TyFun (a6989586621679545434 ~> b6989586621679545435) ([a6989586621679545434] ~> [b6989586621679545435]) -> Type) (a6989586621679545638 :: a6989586621679545434 ~> b6989586621679545435) = MapSym1 a6989586621679545638

data MapSym1 (a6989586621679545638 :: (~>) a6989586621679545434 b6989586621679545435) :: (~>) [a6989586621679545434] [b6989586621679545435] Source #

Instances

Instances details
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 a6989586621679545638 :: TyFun [a6989586621679545434] [b6989586621679545435] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

type MapSym2 (a6989586621679545638 :: (~>) a6989586621679545434 b6989586621679545435) (a6989586621679545639 :: [a6989586621679545434]) = Map a6989586621679545638 a6989586621679545639 Source #

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

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type ReverseSym1 (a6989586621679979493 :: [a6989586621679974178]) = Reverse a6989586621679979493 Source #

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

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersperseSym0 :: TyFun a6989586621679974177 ([a6989586621679974177] ~> [a6989586621679974177]) -> Type) (a6989586621679979486 :: a6989586621679974177) = IntersperseSym1 a6989586621679979486

data IntersperseSym1 (a6989586621679979486 :: a6989586621679974177) :: (~>) [a6989586621679974177] [a6989586621679974177] Source #

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntersperseSym1 a6989586621679979486 :: TyFun [a6989586621679974177] [a6989586621679974177] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersperseSym1 a6989586621679979486 :: TyFun [a] [a] -> Type) (a6989586621679979487 :: [a]) = Intersperse a6989586621679979486 a6989586621679979487

type IntersperseSym2 (a6989586621679979486 :: a6989586621679974177) (a6989586621679979487 :: [a6989586621679974177]) = Intersperse a6989586621679979486 a6989586621679979487 Source #

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

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntercalateSym0 :: TyFun [a6989586621679974176] ([[a6989586621679974176]] ~> [a6989586621679974176]) -> Type) (a6989586621679979480 :: [a6989586621679974176]) = IntercalateSym1 a6989586621679979480

data IntercalateSym1 (a6989586621679979480 :: [a6989586621679974176]) :: (~>) [[a6989586621679974176]] [a6989586621679974176] Source #

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntercalateSym1 a6989586621679979480 :: TyFun [[a6989586621679974176]] [a6989586621679974176] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntercalateSym1 a6989586621679979480 :: TyFun [[a]] [a] -> Type) (a6989586621679979481 :: [[a]]) = Intercalate a6989586621679979480 a6989586621679979481

type IntercalateSym2 (a6989586621679979480 :: [a6989586621679974176]) (a6989586621679979481 :: [[a6989586621679974176]]) = Intercalate a6989586621679979480 a6989586621679979481 Source #

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

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type TransposeSym1 (a6989586621679978223 :: [[a6989586621679974063]]) = Transpose a6989586621679978223 Source #

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

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type SubsequencesSym1 (a6989586621679979477 :: [a6989586621679974175]) = Subsequences a6989586621679979477 Source #

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

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type PermutationsSym1 (a6989586621679979359 :: [a6989586621679974172]) = Permutations a6989586621679979359 Source #

data FoldlSym0 :: forall b6989586621680490510 a6989586621680490511 t6989586621680490502. (~>) ((~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) ((~>) b6989586621680490510 ((~>) (t6989586621680490502 a6989586621680490511) b6989586621680490510)) Source #

Instances

Instances details
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 (b6989586621680490510 ~> (a6989586621680490511 ~> b6989586621680490510)) (b6989586621680490510 ~> (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym0 :: TyFun (b6989586621680490510 ~> (a6989586621680490511 ~> b6989586621680490510)) (b6989586621680490510 ~> (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510)) -> Type) (arg6989586621680491139 :: b6989586621680490510 ~> (a6989586621680490511 ~> b6989586621680490510)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym0 :: TyFun (b6989586621680490510 ~> (a6989586621680490511 ~> b6989586621680490510)) (b6989586621680490510 ~> (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510)) -> Type) (arg6989586621680491139 :: b6989586621680490510 ~> (a6989586621680490511 ~> b6989586621680490510)) = FoldlSym1 arg6989586621680491139 t6989586621680490502 :: TyFun b6989586621680490510 (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510) -> Type

data FoldlSym1 (arg6989586621680491139 :: (~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) :: forall t6989586621680490502. (~>) b6989586621680490510 ((~>) (t6989586621680490502 a6989586621680490511) b6989586621680490510) Source #

Instances

Instances details
(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 arg6989586621680491139 t6989586621680490502 :: TyFun b6989586621680490510 (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym1 arg6989586621680491139 t6989586621680490502 :: TyFun b6989586621680490510 (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510) -> Type) (arg6989586621680491140 :: b6989586621680490510) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym1 arg6989586621680491139 t6989586621680490502 :: TyFun b6989586621680490510 (t6989586621680490502 a6989586621680490511 ~> b6989586621680490510) -> Type) (arg6989586621680491140 :: b6989586621680490510) = FoldlSym2 arg6989586621680491139 arg6989586621680491140 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490511) b6989586621680490510 -> Type

data FoldlSym2 (arg6989586621680491139 :: (~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) (arg6989586621680491140 :: b6989586621680490510) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490511) b6989586621680490510 Source #

Instances

Instances details
(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 arg6989586621680491140 arg6989586621680491139 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490511) b6989586621680490510 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym2 arg6989586621680491140 arg6989586621680491139 t :: TyFun (t a) b -> Type) (arg6989586621680491141 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldlSym2 arg6989586621680491140 arg6989586621680491139 t :: TyFun (t a) b -> Type) (arg6989586621680491141 :: t a) = Foldl arg6989586621680491140 arg6989586621680491139 arg6989586621680491141

type FoldlSym3 (arg6989586621680491139 :: (~>) b6989586621680490510 ((~>) a6989586621680490511 b6989586621680490510)) (arg6989586621680491140 :: b6989586621680490510) (arg6989586621680491141 :: t6989586621680490502 a6989586621680490511) = Foldl arg6989586621680491139 arg6989586621680491140 arg6989586621680491141 Source #

data Foldl'Sym0 :: forall b6989586621680490512 a6989586621680490513 t6989586621680490502. (~>) ((~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) ((~>) b6989586621680490512 ((~>) (t6989586621680490502 a6989586621680490513) b6989586621680490512)) Source #

Instances

Instances details
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 (b6989586621680490512 ~> (a6989586621680490513 ~> b6989586621680490512)) (b6989586621680490512 ~> (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym0 :: TyFun (b6989586621680490512 ~> (a6989586621680490513 ~> b6989586621680490512)) (b6989586621680490512 ~> (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512)) -> Type) (arg6989586621680491145 :: b6989586621680490512 ~> (a6989586621680490513 ~> b6989586621680490512)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym0 :: TyFun (b6989586621680490512 ~> (a6989586621680490513 ~> b6989586621680490512)) (b6989586621680490512 ~> (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512)) -> Type) (arg6989586621680491145 :: b6989586621680490512 ~> (a6989586621680490513 ~> b6989586621680490512)) = Foldl'Sym1 arg6989586621680491145 t6989586621680490502 :: TyFun b6989586621680490512 (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512) -> Type

data Foldl'Sym1 (arg6989586621680491145 :: (~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) :: forall t6989586621680490502. (~>) b6989586621680490512 ((~>) (t6989586621680490502 a6989586621680490513) b6989586621680490512) Source #

Instances

Instances details
(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 arg6989586621680491145 t6989586621680490502 :: TyFun b6989586621680490512 (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym1 arg6989586621680491145 t6989586621680490502 :: TyFun b6989586621680490512 (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512) -> Type) (arg6989586621680491146 :: b6989586621680490512) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym1 arg6989586621680491145 t6989586621680490502 :: TyFun b6989586621680490512 (t6989586621680490502 a6989586621680490513 ~> b6989586621680490512) -> Type) (arg6989586621680491146 :: b6989586621680490512) = Foldl'Sym2 arg6989586621680491145 arg6989586621680491146 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490513) b6989586621680490512 -> Type

data Foldl'Sym2 (arg6989586621680491145 :: (~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) (arg6989586621680491146 :: b6989586621680490512) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490513) b6989586621680490512 Source #

Instances

Instances details
(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 arg6989586621680491146 arg6989586621680491145 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490513) b6989586621680490512 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym2 arg6989586621680491146 arg6989586621680491145 t :: TyFun (t a) b -> Type) (arg6989586621680491147 :: t a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl'Sym2 arg6989586621680491146 arg6989586621680491145 t :: TyFun (t a) b -> Type) (arg6989586621680491147 :: t a) = Foldl' arg6989586621680491146 arg6989586621680491145 arg6989586621680491147

type Foldl'Sym3 (arg6989586621680491145 :: (~>) b6989586621680490512 ((~>) a6989586621680490513 b6989586621680490512)) (arg6989586621680491146 :: b6989586621680490512) (arg6989586621680491147 :: t6989586621680490502 a6989586621680490513) = Foldl' arg6989586621680491145 arg6989586621680491146 arg6989586621680491147 Source #

data Foldl1Sym0 :: forall a6989586621680490515 t6989586621680490502. (~>) ((~>) a6989586621680490515 ((~>) a6989586621680490515 a6989586621680490515)) ((~>) (t6989586621680490502 a6989586621680490515) a6989586621680490515) Source #

Instances

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (a6989586621680490515 ~> (a6989586621680490515 ~> a6989586621680490515)) (t6989586621680490502 a6989586621680490515 ~> a6989586621680490515) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym0 :: TyFun (a6989586621680490515 ~> (a6989586621680490515 ~> a6989586621680490515)) (t6989586621680490502 a6989586621680490515 ~> a6989586621680490515) -> Type) (arg6989586621680491155 :: a6989586621680490515 ~> (a6989586621680490515 ~> a6989586621680490515)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym0 :: TyFun (a6989586621680490515 ~> (a6989586621680490515 ~> a6989586621680490515)) (t6989586621680490502 a6989586621680490515 ~> a6989586621680490515) -> Type) (arg6989586621680491155 :: a6989586621680490515 ~> (a6989586621680490515 ~> a6989586621680490515)) = Foldl1Sym1 arg6989586621680491155 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490515) a6989586621680490515 -> Type

data Foldl1Sym1 (arg6989586621680491155 :: (~>) a6989586621680490515 ((~>) a6989586621680490515 a6989586621680490515)) :: forall t6989586621680490502. (~>) (t6989586621680490502 a6989586621680490515) a6989586621680490515 Source #

Instances

Instances details
(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 arg6989586621680491155 t6989586621680490502 :: TyFun (t6989586621680490502 a6989586621680490515) a6989586621680490515 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl1Sym1 arg6989586621680491155 t :: TyFun (t a) a -> Type) (arg6989586621680491156 :: t a) = Foldl1 arg6989586621680491155 arg6989586621680491156

type Foldl1Sym2 (arg6989586621680491155 :: (~>) a6989586621680490515 ((~>) a6989586621680490515 a6989586621680490515)) (arg6989586621680491156 :: t6989586621680490502 a6989586621680490515) = Foldl1 arg6989586621680491155 arg6989586621680491156 Source #

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

Instances

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

data Foldl1'Sym1 (a6989586621679979317 :: (~>) a6989586621679974168 ((~>) a6989586621679974168 a6989586621679974168)) :: (~>) [a6989586621679974168] a6989586621679974168 Source #

Instances

Instances details
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 a6989586621679979317 :: TyFun [a6989586621679974168] a6989586621679974168 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type Foldl1'Sym2 (a6989586621679979317 :: (~>) a6989586621679974168 ((~>) a6989586621679974168 a6989586621679974168)) (a6989586621679979318 :: [a6989586621679974168]) = Foldl1' a6989586621679979317 a6989586621679979318 Source #

data FoldrSym0 :: forall a6989586621680490506 b6989586621680490507 t6989586621680490502. (~>) ((~>) a6989586621680490506 ((~>) b6989586621680490507 b6989586621680490507)) ((~>) b6989586621680490507 ((~>) (t6989586621680490502 a6989586621680490506) b6989586621680490507)) Source #

Instances

Instances details
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 (a6989586621680490506 ~> (b6989586621680490