singletons-2.5.1: A framework for generating singleton types

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

Data.Singletons.Prelude.List

Contents

Description

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

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

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

The singleton for lists

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

The singleton kind-indexed data family.

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

Defined in Data.Singletons.Decide

Methods

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

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

Defined in Data.Singletons.Decide

Methods

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

Show (SSymbol s) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: SSymbol s -> String #

showList :: [SSymbol s] -> ShowS #

Show (SNat n) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: SNat n -> String #

showList :: [SNat n] -> ShowS #

Eq (Sing a) Source # 
Instance details

Defined in Data.Singletons.TypeRepTYPE

Methods

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

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

Ord (Sing a) Source # 
Instance details

Defined in Data.Singletons.TypeRepTYPE

Methods

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

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

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

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

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

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

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

Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing a) Source # 
Instance details

Defined in Data.Singletons.TypeRepTYPE

Methods

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

show :: Sing a -> String #

showList :: [Sing a] -> ShowS #

Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Monoid

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Monoid

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.TypeLits.Internal

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

Defined in Data.Singletons.TypeLits.Internal

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.TypeError

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

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

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

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

Instance details

Defined in Data.Singletons.TypeRepTYPE

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Internal

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Const

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

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

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

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

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

Basic functions

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

type Null (arg :: Const m a)

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

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

type Length (arg :: Const m a)

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

List transformations

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

Equations

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

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

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

Equations

Reverse l = Apply (Apply (Let6989586621679939996RevSym1 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 (Let6989586621679939862PermsSym1 xs0) xs0) '[]) 

sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply PermutationsSym0 t :: [[a]]) Source #

Reducing lists (folds)

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

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

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

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

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

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

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

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

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

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

Equations

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

sFoldl1' :: forall a (t :: (~>) a ((~>) a a)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a) Source #

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

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

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

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

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

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

Special folds

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

Equations

Concat xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621680439040Sym0 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_6989586621680439027Sym0 f) xs)) '[]) xs 

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

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

Equations

And x = Case_6989586621680439017 x (Let6989586621680439015Scrutinee_6989586621680438773Sym1 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_6989586621680439008 x (Let6989586621680439006Scrutinee_6989586621680438775Sym1 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_6989586621680438999 p x (Let6989586621680438996Scrutinee_6989586621680438777Sym2 p x) 

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

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

Equations

All p x = Case_6989586621680438986 p x (Let6989586621680438983Scrutinee_6989586621680438779Sym2 p x) 

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

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

type Sum (arg :: Const m a)

sSum :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a) Source #

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

type Product (arg :: Const m a)

sProduct :: forall a (t :: t a). (SFoldable t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a) Source #

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

type Maximum (arg :: Const m a)

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

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

type Minimum (arg :: Const m a)

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

Building lists

Scans

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

Equations

Scanl f q ls = Apply (Apply (:@#@$) q) (Case_6989586621679939634 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_6989586621679939620 f q0 x xs (Let6989586621679939615Scrutinee_6989586621679930008Sym4 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_6989586621679930020 wild_6989586621679930022)) = Case_6989586621679939599 f x wild_6989586621679930020 wild_6989586621679930022 (Let6989586621679939594Scrutinee_6989586621679930014Sym4 f x wild_6989586621679930020 wild_6989586621679930022) 

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

Accumulating maps

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

Equations

MapAccumL f s t = Case_6989586621680741097 f s t (Let6989586621680741093Scrutinee_6989586621680740628Sym3 f s t) 

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

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

Equations

MapAccumR f s t = Case_6989586621680741080 f s t (Let6989586621680741076Scrutinee_6989586621680740632Sym3 f s t) 

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

Cyclical lists

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

Equations

Replicate n x = Case_6989586621679938731 n x (Let6989586621679938728Scrutinee_6989586621679930116Sym2 n x) 

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

Unfolding

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

Equations

Unfoldr f b = Case_6989586621679939447 f b (Let6989586621679939444Scrutinee_6989586621679930024Sym2 f b) 

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

Sublists

Extracting sublists

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

Equations

Take _ '[] = '[] 
Take n ((:) x xs) = Case_6989586621679938829 n x xs (Let6989586621679938825Scrutinee_6989586621679930100Sym3 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_6989586621679938815 n x xs (Let6989586621679938811Scrutinee_6989586621679930102Sym3 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_6989586621679938987 p x xs (Let6989586621679938983Scrutinee_6989586621679930090Sym3 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_6989586621679938973 p x xs' (Let6989586621679938969Scrutinee_6989586621679930092Sym3 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_6989586621679940018 = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_6989586621679940022Sym0 p) a_6989586621679940018)) '[]) a_6989586621679940018 

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 Let6989586621679938885XsSym0) Let6989586621679938885XsSym0 
Span p ((:) x xs') = Case_6989586621679938897 p x xs' (Let6989586621679938893Scrutinee_6989586621679930096Sym3 p x xs') 

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

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

Equations

Break _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679938842XsSym0) Let6989586621679938842XsSym0 
Break p ((:) x xs') = Case_6989586621679938854 p x xs' (Let6989586621679938850Scrutinee_6989586621679930098Sym3 p x xs') 

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

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

Equations

StripPrefix '[] ys = Apply JustSym0 ys 
StripPrefix arg_6989586621680055731 arg_6989586621680055733 = Case_6989586621680068380 arg_6989586621680055731 arg_6989586621680055733 (Apply (Apply Tuple2Sym0 arg_6989586621680055731) arg_6989586621680055733) 

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

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_6989586621679939433 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_6989586621679939426 xs xs) 

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

Predicates

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

Equations

IsPrefixOf '[] '[] = TrueSym0 
IsPrefixOf '[] ((:) _ _) = TrueSym0 
IsPrefixOf ((:) _ _) '[] = FalseSym0 
IsPrefixOf ((:) x xs) ((:) y ys) = Apply (Apply (&&@#@$) (Apply (Apply (==@#@$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) 

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

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

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

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

Equations

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

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

Searching lists

Searching by equality

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

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Const

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

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

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

Equations

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

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

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

Equations

Lookup _key '[] = NothingSym0 
Lookup key ((:) '(x, y) xys) = Case_6989586621679938801 key x y xys (Let6989586621679938796Scrutinee_6989586621679930112Sym4 key x y xys) 

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

Searching with a predicate

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

Equations

Find p y = Case_6989586621680438915 p y (Let6989586621680438898Scrutinee_6989586621680438785Sym2 p y) 

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

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

Equations

Filter _p '[] = '[] 
Filter p ((:) x xs) = Case_6989586621679939002 p x xs (Let6989586621679938998Scrutinee_6989586621679930078Sym3 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_6989586621679938719 x xs n (Let6989586621679938715Scrutinee_6989586621679930118Sym3 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_6989586621679939377 = Apply (Apply FindIndexSym0 (Apply (==@#@$) x)) a_6989586621679939377 

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

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

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

Equations

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

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

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_6989586621679939346Sym0 p) xs)) (Apply (Apply ZipSym0 xs) (Apply (Apply (Let6989586621679939337BuildListSym2 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_6989586621680068353 a_6989586621680068355 a_6989586621680068357 a_6989586621680068359 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621680068353) a_6989586621680068355) a_6989586621680068357) a_6989586621680068359 

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

Equations

Zip5 a_6989586621680068328 a_6989586621680068330 a_6989586621680068332 a_6989586621680068334 a_6989586621680068336 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621680068328) a_6989586621680068330) a_6989586621680068332) a_6989586621680068334) a_6989586621680068336 

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

Equations

Zip6 a_6989586621680068298 a_6989586621680068300 a_6989586621680068302 a_6989586621680068304 a_6989586621680068306 a_6989586621680068308 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621680068298) a_6989586621680068300) a_6989586621680068302) a_6989586621680068304) a_6989586621680068306) a_6989586621680068308 

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

Equations

Zip7 a_6989586621680068263 a_6989586621680068265 a_6989586621680068267 a_6989586621680068269 a_6989586621680068271 a_6989586621680068273 a_6989586621680068275 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621680068263) a_6989586621680068265) a_6989586621680068267) a_6989586621680068269) a_6989586621680068271) a_6989586621680068273) a_6989586621680068275 

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_6989586621679939269Sym0 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_6989586621679939248Sym0 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_6989586621679939225Sym0 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_6989586621679939200Sym0 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_6989586621679939173Sym0 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_6989586621679939144Sym0 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 (Let6989586621679939130GoSym2 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 (Let6989586621679939398Nub'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_6989586621679939106 a_6989586621679939108 = Apply (Apply (Apply DeleteBySym0 (==@#@$)) a_6989586621679939106) a_6989586621679939108 

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_6989586621679939116 \\ a_6989586621679939118 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 DeleteSym0)) a_6989586621679939116) a_6989586621679939118 

(%\\) :: 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_6989586621679939096 a_6989586621679939098 = Apply (Apply (Apply UnionBySym0 (==@#@$)) a_6989586621679939096) a_6989586621679939098 

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_6989586621679939691 a_6989586621679939693 = Apply (Apply (Apply IntersectBySym0 (==@#@$)) a_6989586621679939691) a_6989586621679939693 

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_6989586621679939051 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679939051 

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 (Let6989586621679938689NubBy'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_6989586621679939071 eq x y ys (Let6989586621679939066Scrutinee_6989586621679930062Sym4 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_6989586621679939080 a_6989586621679939082 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679939080) a_6989586621679939082 

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

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_6989586621679930082 wild_6989586621679930084) ((:) wild_6989586621679930086 wild_6989586621679930088) = Apply (Apply (>>=@#@$) (Let6989586621679939670XsSym5 eq wild_6989586621679930082 wild_6989586621679930084 wild_6989586621679930086 wild_6989586621679930088)) (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679939681Sym0 eq) wild_6989586621679930082) wild_6989586621679930084) wild_6989586621679930086) wild_6989586621679930088) 

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

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

Equations

GroupBy _ '[] = '[] 
GroupBy eq ((:) x xs) = Apply (Apply (:@#@$) (Apply (Apply (:@#@$) x) (Let6989586621679938931YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621679938931ZsSym3 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_6989586621679939047 = Apply (Apply (Apply FoldrSym0 (Apply InsertBySym0 cmp)) '[]) a_6989586621679939047 

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_6989586621679939034 cmp x y ys' (Let6989586621679939029Scrutinee_6989586621679930064Sym4 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_6989586621680438956 = Apply (Apply Foldl1Sym0 (Let6989586621680438960Max'Sym2 cmp a_6989586621680438956)) a_6989586621680438956 

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

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

Equations

MinimumBy cmp a_6989586621680438931 = Apply (Apply Foldl1Sym0 (Let6989586621680438935Min'Sym2 cmp a_6989586621680438931)) a_6989586621680438931 

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

The "generic" operations

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

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

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

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

Equations

GenericTake a_6989586621680068153 a_6989586621680068155 = Apply (Apply TakeSym0 a_6989586621680068153) a_6989586621680068155 

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

Equations

GenericDrop a_6989586621680068143 a_6989586621680068145 = Apply (Apply DropSym0 a_6989586621680068143) a_6989586621680068145 

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

Equations

GenericSplitAt a_6989586621680068133 a_6989586621680068135 = Apply (Apply SplitAtSym0 a_6989586621680068133) a_6989586621680068135 

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

Equations

GenericIndex a_6989586621680068123 a_6989586621680068125 = Apply (Apply (!!@#@$) a_6989586621680068123) a_6989586621680068125 

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

Equations

GenericReplicate a_6989586621680068113 a_6989586621680068115 = Apply (Apply ReplicateSym0 a_6989586621680068113) a_6989586621680068115 

Defunctionalization symbols

type NilSym0 = '[] Source #

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

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

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

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

Defined in Data.Singletons.Prelude.Instances

Methods

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

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

type (:@#@$$$) (t6989586621679291660 :: a3530822107858468865) (t6989586621679291661 :: [a3530822107858468865]) = (:) t6989586621679291660 t6989586621679291661 Source #

type (++@#@$$$) (a6989586621679511994 :: [a6989586621679511797]) (a6989586621679511995 :: [a6989586621679511797]) = (++) a6989586621679511994 a6989586621679511995 Source #

data (++@#@$$) (a6989586621679511994 :: [a6989586621679511797]) :: (~>) [a6989586621679511797] [a6989586621679511797] infixr 5 Source #

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

Defined in Data.Singletons.Prelude.Base

Methods

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

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

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

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type HeadSym1 (a6989586621679940062 :: [a6989586621679929539]) = Head a6989586621679940062 Source #

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type LastSym1 (a6989586621679940057 :: [a6989586621679929538]) = Last a6989586621679940057 Source #

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type TailSym1 (a6989586621679940054 :: [a6989586621679929537]) = Tail a6989586621679940054 Source #

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type InitSym1 (a6989586621679940040 :: [a6989586621679929536]) = Init a6989586621679940040 Source #

data NullSym0 :: forall a6989586621680438541 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438541) Bool Source #

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680438526 a6989586621680438541) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type NullSym1 (arg6989586621680439189 :: t6989586621680438526 a6989586621680438541) = Null arg6989586621680439189 Source #

data LengthSym0 :: forall a6989586621680438542 t6989586621680438526. (~>) (t6989586621680438526 a6989586621680438542) Nat Source #

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (LengthSym0 :: TyFun (t6989586621680438526 a6989586621680438542) Nat -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

type LengthSym1 (arg6989586621680439191 :: t6989586621680438526 a6989586621680438542) = Length arg6989586621680439191 Source #

data MapSym0 :: forall a6989586621679511798 b6989586621679511799. (~>) ((~>) a6989586621679511798 b6989586621679511799) ((~>) [a6989586621679511798] [b6989586621679511799]) Source #

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym0 :: TyFun (a6989586621679511798 ~> b6989586621679511799) ([a6989586621679511798] ~> [b6989586621679511799]) -> Type) (a6989586621679512002 :: a6989586621679511798 ~> b6989586621679511799) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym0 :: TyFun (a6989586621679511798 ~> b6989586621679511799) ([a6989586621679511798] ~> [b6989586621679511799]) -> Type) (a6989586621679512002 :: a6989586621679511798 ~> b6989586621679511799) = MapSym1 a6989586621679512002

data MapSym1 (a6989586621679512002 :: (~>) a6989586621679511798 b6989586621679511799) :: (~>) [a6989586621679511798] [b6989586621679511799] Source #

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

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (MapSym1 d) Source #

SuppressUnusedWarnings (MapSym1 a6989586621679512002 :: TyFun [a6989586621679511798] [b6989586621679511799] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

type MapSym2 (a6989586621679512002 :: (~>) a6989586621679511798 b6989586621679511799) (a6989586621679512003 :: [a6989586621679511798]) = Map a6989586621679512002 a6989586621679512003 Source #

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type ReverseSym1 (a6989586621679939993 :: [a6989586621679929534]) = Reverse a6989586621679939993 Source #

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersperseSym0 :: TyFun a6989586621679929533 ([a6989586621679929533] ~> [a6989586621679929533]) -> Type) (a6989586621679939980 :: a6989586621679929533) = IntersperseSym1 a6989586621679939980

data IntersperseSym1 (a6989586621679939980 :: a6989586621679929533) :: (~>) [a6989586621679929533] [a6989586621679929533] Source #

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntersperseSym1 a6989586621679939980 :: TyFun [a6989586621679929533] [a6989586621679929533] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersperseSym1 a6989586621679939980 :: TyFun [a] [a] -> Type) (a6989586621679939981 :: [a]) = Intersperse a6989586621679939980 a6989586621679939981

type IntersperseSym2 (a6989586621679939980 :: a6989586621679929533) (a6989586621679939981 :: [a6989586621679929533]) = Intersperse a6989586621679939980 a6989586621679939981 Source #

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntercalateSym0 :: TyFun [a6989586621679929532] ([[a6989586621679929532]] ~> [a6989586621679929532]) -> Type) (a6989586621679939987 :: [a6989586621679929532]) = IntercalateSym1 a6989586621679939987

data IntercalateSym1 (a6989586621679939987 :: [a6989586621679929532]) :: (~>) [[a6989586621679929532]] [a6989586621679929532] Source #

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntercalateSym1 a6989586621679939987 :: TyFun [[a6989586621679929532]] [a6989586621679929532] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntercalateSym1 a6989586621679939987 :: TyFun [[a]] [a] -> Type) (a6989586621679939988 :: [[a]]) = Intercalate a6989586621679939987 a6989586621679939988

type IntercalateSym2 (a6989586621679939987 :: [a6989586621679929532]) (a6989586621679939988 :: [[a6989586621679929532]]) = Intercalate a6989586621679939987 a6989586621679939988 Source #

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type TransposeSym1 (a6989586621679940065 :: [[a6989586621679929419]]) = Transpose a6989586621679940065 Source #

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

type SubsequencesSym1 (a6989586621679939977 :: [a6989586621679929531]) = Subsequences a6989586621679939977 Source #

data