singletons-2.4.1: A framework for generating singleton types

Copyright(C) 2014 Jan Stolarek
LicenseBSD-style (see LICENSE)
MaintainerJan Stolarek (jan.stolarek@p.lodz.pl)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Promotion.Prelude.List

Contents

Description

Defines promoted functions and datatypes relating to List, including a promoted version of all the definitions in Data.List.

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

Synopsis
  • type family (a :: [a]) ++ (a :: [a]) :: [a] where ...
  • type family Head (a :: [a]) :: a where ...
  • type family Last (a :: [a]) :: a where ...
  • type family Tail (a :: [a]) :: [a] where ...
  • type family Init (a :: [a]) :: [a] where ...
  • type family Null (a :: [a]) :: Bool where ...
  • type family Length (a :: [a]) :: Nat where ...
  • type family Map (a :: TyFun a b -> Type) (a :: [a]) :: [b] where ...
  • type family Reverse (a :: [a]) :: [a] where ...
  • type family Intersperse (a :: a) (a :: [a]) :: [a] where ...
  • type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ...
  • type family Transpose (a :: [[a]]) :: [[a]] where ...
  • type family Subsequences (a :: [a]) :: [[a]] where ...
  • type family Permutations (a :: [a]) :: [[a]] where ...
  • type family Foldl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
  • type family Foldl' (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
  • type family Foldl1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
  • type family Foldl1' (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
  • type family Foldr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
  • type family Foldr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
  • type family Concat (a :: [[a]]) :: [a] where ...
  • type family ConcatMap (a :: TyFun a [b] -> Type) (a :: [a]) :: [b] where ...
  • type family And (a :: [Bool]) :: Bool where ...
  • type family Or (a :: [Bool]) :: Bool where ...
  • type family Any (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ...
  • type family All (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ...
  • type family Sum (a :: [a]) :: a where ...
  • type family Product (a :: [a]) :: a where ...
  • type family Maximum (a :: [a]) :: a where ...
  • type family Minimum (a :: [a]) :: a where ...
  • type family Scanl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ...
  • type family Scanl1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ...
  • type family Scanr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ...
  • type family Scanr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ...
  • type family MapAccumL (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ...
  • type family MapAccumR (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ...
  • type family Replicate (a :: Nat) (a :: a) :: [a] where ...
  • type family Unfoldr (a :: TyFun b (Maybe (a, b)) -> Type) (a :: b) :: [a] where ...
  • type family Take (a :: Nat) (a :: [a]) :: [a] where ...
  • type family Drop (a :: Nat) (a :: [a]) :: [a] where ...
  • type family SplitAt (a :: Nat) (a :: [a]) :: ([a], [a]) where ...
  • type family TakeWhile (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ...
  • type family DropWhile (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ...
  • type family DropWhileEnd (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ...
  • type family Span (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ...
  • type family Break (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ...
  • type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ...
  • type family Group (a :: [a]) :: [[a]] where ...
  • type family Inits (a :: [a]) :: [[a]] where ...
  • type family Tails (a :: [a]) :: [[a]] where ...
  • type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ...
  • type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ...
  • type family IsInfixOf (a :: [a]) (a :: [a]) :: Bool where ...
  • type family Elem (a :: a) (a :: [a]) :: Bool where ...
  • type family NotElem (a :: a) (a :: [a]) :: Bool where ...
  • type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ...
  • type family Find (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe a where ...
  • type family Filter (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ...
  • type family Partition (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ...
  • type family (a :: [a]) !! (a :: Nat) :: a where ...
  • type family ElemIndex (a :: a) (a :: [a]) :: Maybe Nat where ...
  • type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ...
  • type family FindIndex (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe Nat where ...
  • type family FindIndices (a :: TyFun a Bool -> Type) (a :: [a]) :: [Nat] where ...
  • type family Zip (a :: [a]) (a :: [b]) :: [(a, b)] where ...
  • type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ...
  • 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 :: TyFun a (TyFun b c -> Type) -> Type) (a :: [a]) (a :: [b]) :: [c] where ...
  • type family ZipWith3 (a :: TyFun a (TyFun b (TyFun c d -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ...
  • type family ZipWith4 (a :: TyFun a (TyFun b (TyFun c (TyFun d e -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ...
  • type family ZipWith5 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e f -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ...
  • type family ZipWith6 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e (TyFun f g -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ...
  • type family ZipWith7 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e (TyFun f (TyFun g h -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (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 ...
  • type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ...
  • type family Unzip4 (a :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
  • type family Unzip5 (a :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ...
  • type family Unzip6 (a :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ...
  • type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
  • type family Unlines (a :: [Symbol]) :: Symbol where ...
  • type family Unwords (a :: [Symbol]) :: Symbol where ...
  • type family Nub (a :: [a]) :: [a] where ...
  • type family Delete (a :: a) (a :: [a]) :: [a] where ...
  • type family (a :: [a]) \\ (a :: [a]) :: [a] where ...
  • type family Union (a :: [a]) (a :: [a]) :: [a] where ...
  • type family Intersect (a :: [a]) (a :: [a]) :: [a] where ...
  • type family Sort (a :: [a]) :: [a] where ...
  • type family Insert (a :: a) (a :: [a]) :: [a] where ...
  • type family NubBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [a] where ...
  • type family DeleteBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ...
  • type family DeleteFirstsBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ...
  • type family UnionBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ...
  • type family GroupBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [[a]] where ...
  • type family IntersectBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ...
  • type family SortBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: [a] where ...
  • type family InsertBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ...
  • type family MaximumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ...
  • type family MinimumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ...
  • type family GenericLength (a :: [a]) :: i where ...
  • 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 (:@#@$) (l :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type))
  • data (l :: a3530822107858468865) :@#@$$ (l :: TyFun [a3530822107858468865] [a3530822107858468865])
  • type (:@#@$$$) (t :: a3530822107858468865) (t :: [a3530822107858468865]) = (:) t t
  • type (++@#@$$$) (t :: [a6989586621679422444]) (t :: [a6989586621679422444]) = (++) t t
  • data (l :: [a6989586621679422444]) ++@#@$$ (l :: TyFun [a6989586621679422444] [a6989586621679422444])
  • data (++@#@$) (l :: TyFun [a6989586621679422444] (TyFun [a6989586621679422444] [a6989586621679422444] -> Type))
  • data HeadSym0 (l :: TyFun [a6989586621679445081] a6989586621679445081)
  • type HeadSym1 (t :: [a6989586621679445081]) = Head t
  • data LastSym0 (l :: TyFun [a6989586621679445080] a6989586621679445080)
  • type LastSym1 (t :: [a6989586621679445080]) = Last t
  • data TailSym0 (l :: TyFun [a6989586621679445079] [a6989586621679445079])
  • type TailSym1 (t :: [a6989586621679445079]) = Tail t
  • data InitSym0 (l :: TyFun [a6989586621679445078] [a6989586621679445078])
  • type InitSym1 (t :: [a6989586621679445078]) = Init t
  • data NullSym0 (l :: TyFun [a6989586621679445077] Bool)
  • type NullSym1 (t :: [a6989586621679445077]) = Null t
  • data MapSym0 (l :: TyFun (TyFun a6989586621679422445 b6989586621679422446 -> Type) (TyFun [a6989586621679422445] [b6989586621679422446] -> Type))
  • data MapSym1 (l :: TyFun a6989586621679422445 b6989586621679422446 -> Type) (l :: TyFun [a6989586621679422445] [b6989586621679422446])
  • type MapSym2 (t :: TyFun a6989586621679422445 b6989586621679422446 -> Type) (t :: [a6989586621679422445]) = Map t t
  • data ReverseSym0 (l :: TyFun [a6989586621679445076] [a6989586621679445076])
  • type ReverseSym1 (t :: [a6989586621679445076]) = Reverse t
  • data IntersperseSym0 (l :: TyFun a6989586621679445075 (TyFun [a6989586621679445075] [a6989586621679445075] -> Type))
  • data IntersperseSym1 (l :: a6989586621679445075) (l :: TyFun [a6989586621679445075] [a6989586621679445075])
  • type IntersperseSym2 (t :: a6989586621679445075) (t :: [a6989586621679445075]) = Intersperse t t
  • data IntercalateSym0 (l :: TyFun [a6989586621679445074] (TyFun [[a6989586621679445074]] [a6989586621679445074] -> Type))
  • data IntercalateSym1 (l :: [a6989586621679445074]) (l :: TyFun [[a6989586621679445074]] [a6989586621679445074])
  • type IntercalateSym2 (t :: [a6989586621679445074]) (t :: [[a6989586621679445074]]) = Intercalate t t
  • data SubsequencesSym0 (l :: TyFun [a6989586621679445073] [[a6989586621679445073]])
  • type SubsequencesSym1 (t :: [a6989586621679445073]) = Subsequences t
  • data PermutationsSym0 (l :: TyFun [a6989586621679445070] [[a6989586621679445070]])
  • type PermutationsSym1 (t :: [a6989586621679445070]) = Permutations t
  • data FoldlSym0 (l :: TyFun (TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) (TyFun b6989586621679261435 (TyFun [a6989586621679261434] b6989586621679261435 -> Type) -> Type))
  • data FoldlSym1 (l :: TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) (l :: TyFun b6989586621679261435 (TyFun [a6989586621679261434] b6989586621679261435 -> Type))
  • data FoldlSym2 (l :: TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) (l :: b6989586621679261435) (l :: TyFun [a6989586621679261434] b6989586621679261435)
  • type FoldlSym3 (t :: TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) (t :: b6989586621679261435) (t :: [a6989586621679261434]) = Foldl t t t
  • data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) (TyFun b6989586621679445069 (TyFun [a6989586621679445068] b6989586621679445069 -> Type) -> Type))
  • data Foldl'Sym1 (l :: TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) (l :: TyFun b6989586621679445069 (TyFun [a6989586621679445068] b6989586621679445069 -> Type))
  • data Foldl'Sym2 (l :: TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) (l :: b6989586621679445069) (l :: TyFun [a6989586621679445068] b6989586621679445069)
  • type Foldl'Sym3 (t :: TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) (t :: b6989586621679445069) (t :: [a6989586621679445068]) = Foldl' t t t
  • data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679445067 (TyFun a6989586621679445067 a6989586621679445067 -> Type) -> Type) (TyFun [a6989586621679445067] a6989586621679445067 -> Type))
  • data Foldl1Sym1 (l :: TyFun a6989586621679445067 (TyFun a6989586621679445067 a6989586621679445067 -> Type) -> Type) (l :: TyFun [a6989586621679445067] a6989586621679445067)
  • type Foldl1Sym2 (t :: TyFun a6989586621679445067 (TyFun a6989586621679445067 a6989586621679445067 -> Type) -> Type) (t :: [a6989586621679445067]) = Foldl1 t t
  • data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679445066 (TyFun a6989586621679445066 a6989586621679445066 -> Type) -> Type) (TyFun [a6989586621679445066] a6989586621679445066 -> Type))
  • data Foldl1'Sym1 (l :: TyFun a6989586621679445066 (TyFun a6989586621679445066 a6989586621679445066 -> Type) -> Type) (l :: TyFun [a6989586621679445066] a6989586621679445066)
  • type Foldl1'Sym2 (t :: TyFun a6989586621679445066 (TyFun a6989586621679445066 a6989586621679445066 -> Type) -> Type) (t :: [a6989586621679445066]) = Foldl1' t t
  • data FoldrSym0 (l :: TyFun (TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) (TyFun b6989586621679422448 (TyFun [a6989586621679422447] b6989586621679422448 -> Type) -> Type))
  • data FoldrSym1 (l :: TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) (l :: TyFun b6989586621679422448 (TyFun [a6989586621679422447] b6989586621679422448 -> Type))
  • data FoldrSym2 (l :: TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) (l :: b6989586621679422448) (l :: TyFun [a6989586621679422447] b6989586621679422448)
  • type FoldrSym3 (t :: TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) (t :: b6989586621679422448) (t :: [a6989586621679422447]) = Foldr t t t
  • data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679445065 (TyFun a6989586621679445065 a6989586621679445065 -> Type) -> Type) (TyFun [a6989586621679445065] a6989586621679445065 -> Type))
  • data Foldr1Sym1 (l :: TyFun a6989586621679445065 (TyFun a6989586621679445065 a6989586621679445065 -> Type) -> Type) (l :: TyFun [a6989586621679445065] a6989586621679445065)
  • type Foldr1Sym2 (t :: TyFun a6989586621679445065 (TyFun a6989586621679445065 a6989586621679445065 -> Type) -> Type) (t :: [a6989586621679445065]) = Foldr1 t t
  • data ConcatSym0 (l :: TyFun [[a6989586621679445064]] [a6989586621679445064])
  • type ConcatSym1 (t :: [[a6989586621679445064]]) = Concat t
  • data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679445062 [b6989586621679445063] -> Type) (TyFun [a6989586621679445062] [b6989586621679445063] -> Type))
  • data ConcatMapSym1 (l :: TyFun a6989586621679445062 [b6989586621679445063] -> Type) (l :: TyFun [a6989586621679445062] [b6989586621679445063])
  • type ConcatMapSym2 (t :: TyFun a6989586621679445062 [b6989586621679445063] -> Type) (t :: [a6989586621679445062]) = ConcatMap t t
  • data AndSym0 (l :: TyFun [Bool] Bool)
  • type AndSym1 (t :: [Bool]) = And t
  • data OrSym0 (l :: TyFun [Bool] Bool)
  • type OrSym1 (t :: [Bool]) = Or t
  • data AnySym0 (l :: TyFun (TyFun a6989586621679445060 Bool -> Type) (TyFun [a6989586621679445060] Bool -> Type))
  • data AnySym1 (l :: TyFun a6989586621679445060 Bool -> Type) (l :: TyFun [a6989586621679445060] Bool)
  • type AnySym2 (t :: TyFun a6989586621679445060 Bool -> Type) (t :: [a6989586621679445060]) = Any t t
  • data AllSym0 (l :: TyFun (TyFun a6989586621679445061 Bool -> Type) (TyFun [a6989586621679445061] Bool -> Type))
  • data AllSym1 (l :: TyFun a6989586621679445061 Bool -> Type) (l :: TyFun [a6989586621679445061] Bool)
  • type AllSym2 (t :: TyFun a6989586621679445061 Bool -> Type) (t :: [a6989586621679445061]) = All t t
  • data ScanlSym0 (l :: TyFun (TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) (TyFun b6989586621679445058 (TyFun [a6989586621679445059] [b6989586621679445058] -> Type) -> Type))
  • data ScanlSym1 (l :: TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) (l :: TyFun b6989586621679445058 (TyFun [a6989586621679445059] [b6989586621679445058] -> Type))
  • data ScanlSym2 (l :: TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) (l :: b6989586621679445058) (l :: TyFun [a6989586621679445059] [b6989586621679445058])
  • type ScanlSym3 (t :: TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) (t :: b6989586621679445058) (t :: [a6989586621679445059]) = Scanl t t t
  • data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679445057 (TyFun a6989586621679445057 a6989586621679445057 -> Type) -> Type) (TyFun [a6989586621679445057] [a6989586621679445057] -> Type))
  • data Scanl1Sym1 (l :: TyFun a6989586621679445057 (TyFun a6989586621679445057 a6989586621679445057 -> Type) -> Type) (l :: TyFun [a6989586621679445057] [a6989586621679445057])
  • type Scanl1Sym2 (t :: TyFun a6989586621679445057 (TyFun a6989586621679445057 a6989586621679445057 -> Type) -> Type) (t :: [a6989586621679445057]) = Scanl1 t t
  • data ScanrSym0 (l :: TyFun (TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) (TyFun b6989586621679445056 (TyFun [a6989586621679445055] [b6989586621679445056] -> Type) -> Type))
  • data ScanrSym1 (l :: TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) (l :: TyFun b6989586621679445056 (TyFun [a6989586621679445055] [b6989586621679445056] -> Type))
  • data ScanrSym2 (l :: TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) (l :: b6989586621679445056) (l :: TyFun [a6989586621679445055] [b6989586621679445056])
  • type ScanrSym3 (t :: TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) (t :: b6989586621679445056) (t :: [a6989586621679445055]) = Scanr t t t
  • data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679445054 (TyFun a6989586621679445054 a6989586621679445054 -> Type) -> Type) (TyFun [a6989586621679445054] [a6989586621679445054] -> Type))
  • data Scanr1Sym1 (l :: TyFun a6989586621679445054 (TyFun a6989586621679445054 a6989586621679445054 -> Type) -> Type) (l :: TyFun [a6989586621679445054] [a6989586621679445054])
  • type Scanr1Sym2 (t :: TyFun a6989586621679445054 (TyFun a6989586621679445054 a6989586621679445054 -> Type) -> Type) (t :: [a6989586621679445054]) = Scanr1 t t
  • data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) (TyFun acc6989586621679445051 (TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053]) -> Type) -> Type))
  • data MapAccumLSym1 (l :: TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) (l :: TyFun acc6989586621679445051 (TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053]) -> Type))
  • data MapAccumLSym2 (l :: TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) (l :: acc6989586621679445051) (l :: TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053]))
  • type MapAccumLSym3 (t :: TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) (t :: acc6989586621679445051) (t :: [x6989586621679445052]) = MapAccumL t t t
  • data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) (TyFun acc6989586621679445048 (TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050]) -> Type) -> Type))
  • data MapAccumRSym1 (l :: TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) (l :: TyFun acc6989586621679445048 (TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050]) -> Type))
  • data MapAccumRSym2 (l :: TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) (l :: acc6989586621679445048) (l :: TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050]))
  • type MapAccumRSym3 (t :: TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) (t :: acc6989586621679445048) (t :: [x6989586621679445049]) = MapAccumR t t t
  • data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679445046 (Maybe (a6989586621679445047, b6989586621679445046)) -> Type) (TyFun b6989586621679445046 [a6989586621679445047] -> Type))
  • data UnfoldrSym1 (l :: TyFun b6989586621679445046 (Maybe (a6989586621679445047, b6989586621679445046)) -> Type) (l :: TyFun b6989586621679445046 [a6989586621679445047])
  • type UnfoldrSym2 (t :: TyFun b6989586621679445046 (Maybe (a6989586621679445047, b6989586621679445046)) -> Type) (t :: b6989586621679445046) = Unfoldr t t
  • data InitsSym0 (l :: TyFun [a6989586621679445045] [[a6989586621679445045]])
  • type InitsSym1 (t :: [a6989586621679445045]) = Inits t
  • data TailsSym0 (l :: TyFun [a6989586621679445044] [[a6989586621679445044]])
  • type TailsSym1 (t :: [a6989586621679445044]) = Tails t
  • data IsPrefixOfSym0 (l :: TyFun [a6989586621679445043] (TyFun [a6989586621679445043] Bool -> Type))
  • data IsPrefixOfSym1 (l :: [a6989586621679445043]) (l :: TyFun [a6989586621679445043] Bool)
  • type IsPrefixOfSym2 (t :: [a6989586621679445043]) (t :: [a6989586621679445043]) = IsPrefixOf t t
  • data IsSuffixOfSym0 (l :: TyFun [a6989586621679445042] (TyFun [a6989586621679445042] Bool -> Type))
  • data IsSuffixOfSym1 (l :: [a6989586621679445042]) (l :: TyFun [a6989586621679445042] Bool)
  • type IsSuffixOfSym2 (t :: [a6989586621679445042]) (t :: [a6989586621679445042]) = IsSuffixOf t t
  • data IsInfixOfSym0 (l :: TyFun [a6989586621679445041] (TyFun [a6989586621679445041] Bool -> Type))
  • data IsInfixOfSym1 (l :: [a6989586621679445041]) (l :: TyFun [a6989586621679445041] Bool)
  • type IsInfixOfSym2 (t :: [a6989586621679445041]) (t :: [a6989586621679445041]) = IsInfixOf t t
  • data ElemSym0 (l :: TyFun a6989586621679445040 (TyFun [a6989586621679445040] Bool -> Type))
  • data ElemSym1 (l :: a6989586621679445040) (l :: TyFun [a6989586621679445040] Bool)
  • type ElemSym2 (t :: a6989586621679445040) (t :: [a6989586621679445040]) = Elem t t
  • data NotElemSym0 (l :: TyFun a6989586621679445039 (TyFun [a6989586621679445039] Bool -> Type))
  • data NotElemSym1 (l :: a6989586621679445039) (l :: TyFun [a6989586621679445039] Bool)
  • type NotElemSym2 (t :: a6989586621679445039) (t :: [a6989586621679445039]) = NotElem t t
  • data ZipSym0 (l :: TyFun [a6989586621679445037] (TyFun [b6989586621679445038] [(a6989586621679445037, b6989586621679445038)] -> Type))
  • data ZipSym1 (l :: [a6989586621679445037]) (l :: TyFun [b6989586621679445038] [(a6989586621679445037, b6989586621679445038)])
  • type ZipSym2 (t :: [a6989586621679445037]) (t :: [b6989586621679445038]) = Zip t t
  • data Zip3Sym0 (l :: TyFun [a6989586621679445034] (TyFun [b6989586621679445035] (TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> Type) -> Type))
  • data Zip3Sym1 (l :: [a6989586621679445034]) (l :: TyFun [b6989586621679445035] (TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> Type))
  • data Zip3Sym2 (l :: [a6989586621679445034]) (l :: [b6989586621679445035]) (l :: TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)])
  • type Zip3Sym3 (t :: [a6989586621679445034]) (t :: [b6989586621679445035]) (t :: [c6989586621679445036]) = Zip3 t t t
  • data ZipWithSym0 (l :: TyFun (TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) (TyFun [a6989586621679445031] (TyFun [b6989586621679445032] [c6989586621679445033] -> Type) -> Type))
  • data ZipWithSym1 (l :: TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) (l :: TyFun [a6989586621679445031] (TyFun [b6989586621679445032] [c6989586621679445033] -> Type))
  • data ZipWithSym2 (l :: TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) (l :: [a6989586621679445031]) (l :: TyFun [b6989586621679445032] [c6989586621679445033])
  • type ZipWithSym3 (t :: TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) (t :: [a6989586621679445031]) (t :: [b6989586621679445032]) = ZipWith t t t
  • data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (TyFun [a6989586621679445027] (TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> Type) -> Type))
  • data ZipWith3Sym1 (l :: TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679445027] (TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> Type))
  • data ZipWith3Sym2 (l :: TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (l :: [a6989586621679445027]) (l :: TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type))
  • data ZipWith3Sym3 (l :: TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (l :: [a6989586621679445027]) (l :: [b6989586621679445028]) (l :: TyFun [c6989586621679445029] [d6989586621679445030])
  • type ZipWith3Sym4 (t :: TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (t :: [a6989586621679445027]) (t :: [b6989586621679445028]) (t :: [c6989586621679445029]) = ZipWith3 t t t t
  • data UnzipSym0 (l :: TyFun [(a6989586621679445025, b6989586621679445026)] ([a6989586621679445025], [b6989586621679445026]))
  • type UnzipSym1 (t :: [(a6989586621679445025, b6989586621679445026)]) = Unzip t
  • data Unzip3Sym0 (l :: TyFun [(a6989586621679445022, b6989586621679445023, c6989586621679445024)] ([a6989586621679445022], [b6989586621679445023], [c6989586621679445024]))
  • type Unzip3Sym1 (t :: [(a6989586621679445022, b6989586621679445023, c6989586621679445024)]) = Unzip3 t
  • data Unzip4Sym0 (l :: TyFun [(a6989586621679445018, b6989586621679445019, c6989586621679445020, d6989586621679445021)] ([a6989586621679445018], [b6989586621679445019], [c6989586621679445020], [d6989586621679445021]))
  • type Unzip4Sym1 (t :: [(a6989586621679445018, b6989586621679445019, c6989586621679445020, d6989586621679445021)]) = Unzip4 t
  • data Unzip5Sym0 (l :: TyFun [(a6989586621679445013, b6989586621679445014, c6989586621679445015, d6989586621679445016, e6989586621679445017)] ([a6989586621679445013], [b6989586621679445014], [c6989586621679445015], [d6989586621679445016], [e6989586621679445017]))
  • type Unzip5Sym1 (t :: [(a6989586621679445013, b6989586621679445014, c6989586621679445015, d6989586621679445016, e6989586621679445017)]) = Unzip5 t
  • data Unzip6Sym0 (l :: TyFun [(a6989586621679445007, b6989586621679445008, c6989586621679445009, d6989586621679445010, e6989586621679445011, f6989586621679445012)] ([a6989586621679445007], [b6989586621679445008], [c6989586621679445009], [d6989586621679445010], [e6989586621679445011], [f6989586621679445012]))
  • type Unzip6Sym1 (t :: [(a6989586621679445007, b6989586621679445008, c6989586621679445009, d6989586621679445010, e6989586621679445011, f6989586621679445012)]) = Unzip6 t
  • data Unzip7Sym0 (l :: TyFun [(a6989586621679445000, b6989586621679445001, c6989586621679445002, d6989586621679445003, e6989586621679445004, f6989586621679445005, g6989586621679445006)] ([a6989586621679445000], [b6989586621679445001], [c6989586621679445002], [d6989586621679445003], [e6989586621679445004], [f6989586621679445005], [g6989586621679445006]))
  • type Unzip7Sym1 (t :: [(a6989586621679445000, b6989586621679445001, c6989586621679445002, d6989586621679445003, e6989586621679445004, f6989586621679445005, g6989586621679445006)]) = Unzip7 t
  • data DeleteSym0 (l :: TyFun a6989586621679444999 (TyFun [a6989586621679444999] [a6989586621679444999] -> Type))
  • data DeleteSym1 (l :: a6989586621679444999) (l :: TyFun [a6989586621679444999] [a6989586621679444999])
  • type DeleteSym2 (t :: a6989586621679444999) (t :: [a6989586621679444999]) = Delete t t
  • data (\\@#@$) (l :: TyFun [a6989586621679444998] (TyFun [a6989586621679444998] [a6989586621679444998] -> Type))
  • data (l :: [a6989586621679444998]) \\@#@$$ (l :: TyFun [a6989586621679444998] [a6989586621679444998])
  • type (\\@#@$$$) (t :: [a6989586621679444998]) (t :: [a6989586621679444998]) = (\\) t t
  • data IntersectSym0 (l :: TyFun [a6989586621679444985] (TyFun [a6989586621679444985] [a6989586621679444985] -> Type))
  • data IntersectSym1 (l :: [a6989586621679444985]) (l :: TyFun [a6989586621679444985] [a6989586621679444985])
  • type IntersectSym2 (t :: [a6989586621679444985]) (t :: [a6989586621679444985]) = Intersect t t
  • data InsertSym0 (l :: TyFun a6989586621679444972 (TyFun [a6989586621679444972] [a6989586621679444972] -> Type))
  • data InsertSym1 (l :: a6989586621679444972) (l :: TyFun [a6989586621679444972] [a6989586621679444972])
  • type InsertSym2 (t :: a6989586621679444972) (t :: [a6989586621679444972]) = Insert t t
  • data SortSym0 (l :: TyFun [a6989586621679444971] [a6989586621679444971])
  • type SortSym1 (t :: [a6989586621679444971]) = Sort t
  • data DeleteBySym0 (l :: TyFun (TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) (TyFun a6989586621679444997 (TyFun [a6989586621679444997] [a6989586621679444997] -> Type) -> Type))
  • data DeleteBySym1 (l :: TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) (l :: TyFun a6989586621679444997 (TyFun [a6989586621679444997] [a6989586621679444997] -> Type))
  • data DeleteBySym2 (l :: TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) (l :: a6989586621679444997) (l :: TyFun [a6989586621679444997] [a6989586621679444997])
  • type DeleteBySym3 (t :: TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) (t :: a6989586621679444997) (t :: [a6989586621679444997]) = DeleteBy t t t
  • data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) (TyFun [a6989586621679444996] (TyFun [a6989586621679444996] [a6989586621679444996] -> Type) -> Type))
  • data DeleteFirstsBySym1 (l :: TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) (l :: TyFun [a6989586621679444996] (TyFun [a6989586621679444996] [a6989586621679444996] -> Type))
  • data DeleteFirstsBySym2 (l :: TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) (l :: [a6989586621679444996]) (l :: TyFun [a6989586621679444996] [a6989586621679444996])
  • type DeleteFirstsBySym3 (t :: TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) (t :: [a6989586621679444996]) (t :: [a6989586621679444996]) = DeleteFirstsBy t t t
  • data IntersectBySym0 (l :: TyFun (TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) (TyFun [a6989586621679444984] (TyFun [a6989586621679444984] [a6989586621679444984] -> Type) -> Type))
  • data IntersectBySym1 (l :: TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) (l :: TyFun [a6989586621679444984] (TyFun [a6989586621679444984] [a6989586621679444984] -> Type))
  • data IntersectBySym2 (l :: TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) (l :: [a6989586621679444984]) (l :: TyFun [a6989586621679444984] [a6989586621679444984])
  • data SortBySym0 (l :: TyFun (TyFun a6989586621679444995 (TyFun a6989586621679444995 Ordering -> Type) -> Type) (TyFun [a6989586621679444995] [a6989586621679444995] -> Type))
  • data SortBySym1 (l :: TyFun a6989586621679444995 (TyFun a6989586621679444995 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679444995] [a6989586621679444995])
  • type SortBySym2 (t :: TyFun a6989586621679444995 (TyFun a6989586621679444995 Ordering -> Type) -> Type) (t :: [a6989586621679444995]) = SortBy t t
  • data InsertBySym0 (l :: TyFun (TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) (TyFun a6989586621679444994 (TyFun [a6989586621679444994] [a6989586621679444994] -> Type) -> Type))
  • data InsertBySym1 (l :: TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) (l :: TyFun a6989586621679444994 (TyFun [a6989586621679444994] [a6989586621679444994] -> Type))
  • data InsertBySym2 (l :: TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) (l :: a6989586621679444994) (l :: TyFun [a6989586621679444994] [a6989586621679444994])
  • type InsertBySym3 (t :: TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) (t :: a6989586621679444994) (t :: [a6989586621679444994]) = InsertBy t t t
  • data MaximumBySym0 (l :: TyFun (TyFun a6989586621679444993 (TyFun a6989586621679444993 Ordering -> Type) -> Type) (TyFun [a6989586621679444993] a6989586621679444993 -> Type))
  • data MaximumBySym1 (l :: TyFun a6989586621679444993 (TyFun a6989586621679444993 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679444993] a6989586621679444993)
  • type MaximumBySym2 (t :: TyFun a6989586621679444993 (TyFun a6989586621679444993 Ordering -> Type) -> Type) (t :: [a6989586621679444993]) = MaximumBy t t
  • data MinimumBySym0 (l :: TyFun (TyFun a6989586621679444992 (TyFun a6989586621679444992 Ordering -> Type) -> Type) (TyFun [a6989586621679444992] a6989586621679444992 -> Type))
  • data MinimumBySym1 (l :: TyFun a6989586621679444992 (TyFun a6989586621679444992 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679444992] a6989586621679444992)
  • type MinimumBySym2 (t :: TyFun a6989586621679444992 (TyFun a6989586621679444992 Ordering -> Type) -> Type) (t :: [a6989586621679444992]) = MinimumBy t t
  • data LengthSym0 (l :: TyFun [a6989586621679444963] Nat)
  • type LengthSym1 (t :: [a6989586621679444963]) = Length t
  • data SumSym0 (l :: TyFun [a6989586621679444965] a6989586621679444965)
  • type SumSym1 (t :: [a6989586621679444965]) = Sum t
  • data ProductSym0 (l :: TyFun [a6989586621679444964] a6989586621679444964)
  • type ProductSym1 (t :: [a6989586621679444964]) = Product t
  • data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679444962 [a6989586621679444962] -> Type))
  • data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679444962 [a6989586621679444962])
  • type ReplicateSym2 (t :: Nat) (t :: a6989586621679444962) = Replicate t t
  • data TransposeSym0 (l :: TyFun [[a6989586621679444961]] [[a6989586621679444961]])
  • type TransposeSym1 (t :: [[a6989586621679444961]]) = Transpose t
  • data TakeSym0 (l :: TyFun Nat (TyFun [a6989586621679444978] [a6989586621679444978] -> Type))
  • data TakeSym1 (l :: Nat) (l :: TyFun [a6989586621679444978] [a6989586621679444978])
  • type TakeSym2 (t :: Nat) (t :: [a6989586621679444978]) = Take t t
  • data DropSym0 (l :: TyFun Nat (TyFun [a6989586621679444977] [a6989586621679444977] -> Type))
  • data DropSym1 (l :: Nat) (l :: TyFun [a6989586621679444977] [a6989586621679444977])
  • type DropSym2 (t :: Nat) (t :: [a6989586621679444977]) = Drop t t
  • data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679444976] ([a6989586621679444976], [a6989586621679444976]) -> Type))
  • data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679444976] ([a6989586621679444976], [a6989586621679444976]))
  • type SplitAtSym2 (t :: Nat) (t :: [a6989586621679444976]) = SplitAt t t
  • data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679444983 Bool -> Type) (TyFun [a6989586621679444983] [a6989586621679444983] -> Type))
  • data TakeWhileSym1 (l :: TyFun a6989586621679444983 Bool -> Type) (l :: TyFun [a6989586621679444983] [a6989586621679444983])
  • type TakeWhileSym2 (t :: TyFun a6989586621679444983 Bool -> Type) (t :: [a6989586621679444983]) = TakeWhile t t
  • data DropWhileSym0 (l :: TyFun (TyFun a6989586621679444982 Bool -> Type) (TyFun [a6989586621679444982] [a6989586621679444982] -> Type))
  • data DropWhileSym1 (l :: TyFun a6989586621679444982 Bool -> Type) (l :: TyFun [a6989586621679444982] [a6989586621679444982])
  • type DropWhileSym2 (t :: TyFun a6989586621679444982 Bool -> Type) (t :: [a6989586621679444982]) = DropWhile t t
  • data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679444981 Bool -> Type) (TyFun [a6989586621679444981] [a6989586621679444981] -> Type))
  • data DropWhileEndSym1 (l :: TyFun a6989586621679444981 Bool -> Type) (l :: TyFun [a6989586621679444981] [a6989586621679444981])
  • type DropWhileEndSym2 (t :: TyFun a6989586621679444981 Bool -> Type) (t :: [a6989586621679444981]) = DropWhileEnd t t
  • data SpanSym0 (l :: TyFun (TyFun a6989586621679444980 Bool -> Type) (TyFun [a6989586621679444980] ([a6989586621679444980], [a6989586621679444980]) -> Type))
  • data SpanSym1 (l :: TyFun a6989586621679444980 Bool -> Type) (l :: TyFun [a6989586621679444980] ([a6989586621679444980], [a6989586621679444980]))
  • type SpanSym2 (t :: TyFun a6989586621679444980 Bool -> Type) (t :: [a6989586621679444980]) = Span t t
  • data BreakSym0 (l :: TyFun (TyFun a6989586621679444979 Bool -> Type) (TyFun [a6989586621679444979] ([a6989586621679444979], [a6989586621679444979]) -> Type))
  • data BreakSym1 (l :: TyFun a6989586621679444979 Bool -> Type) (l :: TyFun [a6989586621679444979] ([a6989586621679444979], [a6989586621679444979]))
  • type BreakSym2 (t :: TyFun a6989586621679444979 Bool -> Type) (t :: [a6989586621679444979]) = Break t t
  • data StripPrefixSym0 (l :: TyFun [a6989586621679924863] (TyFun [a6989586621679924863] (Maybe [a6989586621679924863]) -> Type))
  • data StripPrefixSym1 (l :: [a6989586621679924863]) (l :: TyFun [a6989586621679924863] (Maybe [a6989586621679924863]))
  • type StripPrefixSym2 (t :: [a6989586621679924863]) (t :: [a6989586621679924863]) = StripPrefix t t
  • data MaximumSym0 (l :: TyFun [a6989586621679444974] a6989586621679444974)
  • type MaximumSym1 (t :: [a6989586621679444974]) = Maximum t
  • data MinimumSym0 (l :: TyFun [a6989586621679444973] a6989586621679444973)
  • type MinimumSym1 (t :: [a6989586621679444973]) = Minimum t
  • data GroupSym0 (l :: TyFun [a6989586621679444975] [[a6989586621679444975]])
  • type GroupSym1 (t :: [a6989586621679444975]) = Group t
  • data GroupBySym0 (l :: TyFun (TyFun a6989586621679444970 (TyFun a6989586621679444970 Bool -> Type) -> Type) (TyFun [a6989586621679444970] [[a6989586621679444970]] -> Type))
  • data GroupBySym1 (l :: TyFun a6989586621679444970 (TyFun a6989586621679444970 Bool -> Type) -> Type) (l :: TyFun [a6989586621679444970] [[a6989586621679444970]])
  • type GroupBySym2 (t :: TyFun a6989586621679444970 (TyFun a6989586621679444970 Bool -> Type) -> Type) (t :: [a6989586621679444970]) = GroupBy t t
  • data LookupSym0 (l :: TyFun a6989586621679444968 (TyFun [(a6989586621679444968, b6989586621679444969)] (Maybe b6989586621679444969) -> Type))
  • data LookupSym1 (l :: a6989586621679444968) (l :: TyFun [(a6989586621679444968, b6989586621679444969)] (Maybe b6989586621679444969))
  • type LookupSym2 (t :: a6989586621679444968) (t :: [(a6989586621679444968, b6989586621679444969)]) = Lookup t t
  • data FindSym0 (l :: TyFun (TyFun a6989586621679444990 Bool -> Type) (TyFun [a6989586621679444990] (Maybe a6989586621679444990) -> Type))
  • data FindSym1 (l :: TyFun a6989586621679444990 Bool -> Type) (l :: TyFun [a6989586621679444990] (Maybe a6989586621679444990))
  • type FindSym2 (t :: TyFun a6989586621679444990 Bool -> Type) (t :: [a6989586621679444990]) = Find t t
  • data FilterSym0 (l :: TyFun (TyFun a6989586621679444991 Bool -> Type) (TyFun [a6989586621679444991] [a6989586621679444991] -> Type))
  • data FilterSym1 (l :: TyFun a6989586621679444991 Bool -> Type) (l :: TyFun [a6989586621679444991] [a6989586621679444991])
  • type FilterSym2 (t :: TyFun a6989586621679444991 Bool -> Type) (t :: [a6989586621679444991]) = Filter t t
  • data PartitionSym0 (l :: TyFun (TyFun a6989586621679444967 Bool -> Type) (TyFun [a6989586621679444967] ([a6989586621679444967], [a6989586621679444967]) -> Type))
  • data PartitionSym1 (l :: TyFun a6989586621679444967 Bool -> Type) (l :: TyFun [a6989586621679444967] ([a6989586621679444967], [a6989586621679444967]))
  • type PartitionSym2 (t :: TyFun a6989586621679444967 Bool -> Type) (t :: [a6989586621679444967]) = Partition t t
  • data (!!@#@$) (l :: TyFun [a6989586621679444960] (TyFun Nat a6989586621679444960 -> Type))
  • data (l :: [a6989586621679444960]) !!@#@$$ (l :: TyFun Nat a6989586621679444960)
  • type (!!@#@$$$) (t :: [a6989586621679444960]) (t :: Nat) = (!!) t t
  • data ElemIndexSym0 (l :: TyFun a6989586621679444989 (TyFun [a6989586621679444989] (Maybe Nat) -> Type))
  • data ElemIndexSym1 (l :: a6989586621679444989) (l :: TyFun [a6989586621679444989] (Maybe Nat))
  • type ElemIndexSym2 (t :: a6989586621679444989) (t :: [a6989586621679444989]) = ElemIndex t t
  • data ElemIndicesSym0 (l :: TyFun a6989586621679444988 (TyFun [a6989586621679444988] [Nat] -> Type))
  • data ElemIndicesSym1 (l :: a6989586621679444988) (l :: TyFun [a6989586621679444988] [Nat])
  • type ElemIndicesSym2 (t :: a6989586621679444988) (t :: [a6989586621679444988]) = ElemIndices t t
  • data FindIndexSym0 (l :: TyFun (TyFun a6989586621679444987 Bool -> Type) (TyFun [a6989586621679444987] (Maybe Nat) -> Type))
  • data FindIndexSym1 (l :: TyFun a6989586621679444987 Bool -> Type) (l :: TyFun [a6989586621679444987] (Maybe Nat))
  • type FindIndexSym2 (t :: TyFun a6989586621679444987 Bool -> Type) (t :: [a6989586621679444987]) = FindIndex t t
  • data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679444986 Bool -> Type) (TyFun [a6989586621679444986] [Nat] -> Type))
  • data FindIndicesSym1 (l :: TyFun a6989586621679444986 Bool -> Type) (l :: TyFun [a6989586621679444986] [Nat])
  • type FindIndicesSym2 (t :: TyFun a6989586621679444986 Bool -> Type) (t :: [a6989586621679444986]) = FindIndices t t
  • data Zip4Sym0 (l :: TyFun [a6989586621679924859] (TyFun [b6989586621679924860] (TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> Type) -> Type))
  • data Zip4Sym1 (l :: [a6989586621679924859]) (l :: TyFun [b6989586621679924860] (TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> Type))
  • data Zip4Sym2 (l :: [a6989586621679924859]) (l :: [b6989586621679924860]) (l :: TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type))
  • data Zip4Sym3 (l :: [a6989586621679924859]) (l :: [b6989586621679924860]) (l :: [c6989586621679924861]) (l :: TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)])
  • type Zip4Sym4 (t :: [a6989586621679924859]) (t :: [b6989586621679924860]) (t :: [c6989586621679924861]) (t :: [d6989586621679924862]) = Zip4 t t t t
  • data Zip5Sym0 (l :: TyFun [a6989586621679924854] (TyFun [b6989586621679924855] (TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> Type) -> Type))
  • data Zip5Sym1 (l :: [a6989586621679924854]) (l :: TyFun [b6989586621679924855] (TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> Type))
  • data Zip5Sym2 (l :: [a6989586621679924854]) (l :: [b6989586621679924855]) (l :: TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type))
  • data Zip5Sym3 (l :: [a6989586621679924854]) (l :: [b6989586621679924855]) (l :: [c6989586621679924856]) (l :: TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type))
  • data Zip5Sym4 (l :: [a6989586621679924854]) (l :: [b6989586621679924855]) (l :: [c6989586621679924856]) (l :: [d6989586621679924857]) (l :: TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)])
  • type Zip5Sym5 (t :: [a6989586621679924854]) (t :: [b6989586621679924855]) (t :: [c6989586621679924856]) (t :: [d6989586621679924857]) (t :: [e6989586621679924858]) = Zip5 t t t t t
  • data Zip6Sym0 (l :: TyFun [a6989586621679924848] (TyFun [b6989586621679924849] (TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> Type) -> Type))
  • data Zip6Sym1 (l :: [a6989586621679924848]) (l :: TyFun [b6989586621679924849] (TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> Type))
  • data Zip6Sym2 (l :: [a6989586621679924848]) (l :: [b6989586621679924849]) (l :: TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type))
  • data Zip6Sym3 (l :: [a6989586621679924848]) (l :: [b6989586621679924849]) (l :: [c6989586621679924850]) (l :: TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type))
  • data Zip6Sym4 (l :: [a6989586621679924848]) (l :: [b6989586621679924849]) (l :: [c6989586621679924850]) (l :: [d6989586621679924851]) (l :: TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type))
  • data Zip6Sym5 (l :: [a6989586621679924848]) (l :: [b6989586621679924849]) (l :: [c6989586621679924850]) (l :: [d6989586621679924851]) (l :: [e6989586621679924852]) (l :: TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)])
  • type Zip6Sym6 (t :: [a6989586621679924848]) (t :: [b6989586621679924849]) (t :: [c6989586621679924850]) (t :: [d6989586621679924851]) (t :: [e6989586621679924852]) (t :: [f6989586621679924853]) = Zip6 t t t t t t
  • data Zip7Sym0 (l :: TyFun [a6989586621679924841] (TyFun [b6989586621679924842] (TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type))
  • data Zip7Sym1 (l :: [a6989586621679924841]) (l :: TyFun [b6989586621679924842] (TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> Type))
  • data Zip7Sym2 (l :: [a6989586621679924841]) (l :: [b6989586621679924842]) (l :: TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type))
  • data Zip7Sym3 (l :: [a6989586621679924841]) (l :: [b6989586621679924842]) (l :: [c6989586621679924843]) (l :: TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type))
  • data Zip7Sym4 (l :: [a6989586621679924841]) (l :: [b6989586621679924842]) (l :: [c6989586621679924843]) (l :: [d6989586621679924844]) (l :: TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type))
  • data Zip7Sym5 (l :: [a6989586621679924841]) (l :: [b6989586621679924842]) (l :: [c6989586621679924843]) (l :: [d6989586621679924844]) (l :: [e6989586621679924845]) (l :: TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type))
  • data Zip7Sym6 (l :: [a6989586621679924841]) (l :: [b6989586621679924842]) (l :: [c6989586621679924843]) (l :: [d6989586621679924844]) (l :: [e6989586621679924845]) (l :: [f6989586621679924846]) (l :: TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)])
  • type Zip7Sym7 (t :: [a6989586621679924841]) (t :: [b6989586621679924842]) (t :: [c6989586621679924843]) (t :: [d6989586621679924844]) (t :: [e6989586621679924845]) (t :: [f6989586621679924846]) (t :: [g6989586621679924847]) = Zip7 t t t t t t t
  • data ZipWith4Sym0 (l :: TyFun (TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924836] (TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> Type) -> Type))
  • data ZipWith4Sym1 (l :: TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679924836] (TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> Type))
  • data ZipWith4Sym2 (l :: TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924836]) (l :: TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type))
  • data ZipWith4Sym3 (l :: TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924836]) (l :: [b6989586621679924837]) (l :: TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type))
  • data ZipWith4Sym4 (l :: TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924836]) (l :: [b6989586621679924837]) (l :: [c6989586621679924838]) (l :: TyFun [d6989586621679924839] [e6989586621679924840])
  • type ZipWith4Sym5 (t :: TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679924836]) (t :: [b6989586621679924837]) (t :: [c6989586621679924838]) (t :: [d6989586621679924839]) = ZipWith4 t t t t t
  • data ZipWith5Sym0 (l :: TyFun (TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924830] (TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> Type) -> Type))
  • data ZipWith5Sym1 (l :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679924830] (TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> Type))
  • data ZipWith5Sym2 (l :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924830]) (l :: TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type))
  • data ZipWith5Sym3 (l :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924830]) (l :: [b6989586621679924831]) (l :: TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type))
  • data ZipWith5Sym4 (l :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924830]) (l :: [b6989586621679924831]) (l :: [c6989586621679924832]) (l :: TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type))
  • data ZipWith5Sym5 (l :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924830]) (l :: [b6989586621679924831]) (l :: [c6989586621679924832]) (l :: [d6989586621679924833]) (l :: TyFun [e6989586621679924834] [f6989586621679924835])
  • type ZipWith5Sym6 (t :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679924830]) (t :: [b6989586621679924831]) (t :: [c6989586621679924832]) (t :: [d6989586621679924833]) (t :: [e6989586621679924834]) = ZipWith5 t t t t t t
  • data ZipWith6Sym0 (l :: TyFun (TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924823] (TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type))
  • data ZipWith6Sym1 (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679924823] (TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> Type))
  • data ZipWith6Sym2 (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924823]) (l :: TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type))
  • data ZipWith6Sym3 (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924823]) (l :: [b6989586621679924824]) (l :: TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type))
  • data ZipWith6Sym4 (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924823]) (l :: [b6989586621679924824]) (l :: [c6989586621679924825]) (l :: TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type))
  • data ZipWith6Sym5 (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924823]) (l :: [b6989586621679924824]) (l :: [c6989586621679924825]) (l :: [d6989586621679924826]) (l :: TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type))
  • data ZipWith6Sym6 (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924823]) (l :: [b6989586621679924824]) (l :: [c6989586621679924825]) (l :: [d6989586621679924826]) (l :: [e6989586621679924827]) (l :: TyFun [f6989586621679924828] [g6989586621679924829])
  • type ZipWith6Sym7 (t :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679924823]) (t :: [b6989586621679924824]) (t :: [c6989586621679924825]) (t :: [d6989586621679924826]) (t :: [e6989586621679924827]) (t :: [f6989586621679924828]) = ZipWith6 t t t t t t t
  • data ZipWith7Sym0 (l :: TyFun (TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924815] (TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type))
  • data ZipWith7Sym1 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679924815] (TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type))
  • data ZipWith7Sym2 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924815]) (l :: TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type))
  • data ZipWith7Sym3 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924815]) (l :: [b6989586621679924816]) (l :: TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type))
  • data ZipWith7Sym4 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924815]) (l :: [b6989586621679924816]) (l :: [c6989586621679924817]) (l :: TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type))
  • data ZipWith7Sym5 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924815]) (l :: [b6989586621679924816]) (l :: [c6989586621679924817]) (l :: [d6989586621679924818]) (l :: TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type))
  • data ZipWith7Sym6 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924815]) (l :: [b6989586621679924816]) (l :: [c6989586621679924817]) (l :: [d6989586621679924818]) (l :: [e6989586621679924819]) (l :: TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type))
  • data ZipWith7Sym7 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924815]) (l :: [b6989586621679924816]) (l :: [c6989586621679924817]) (l :: [d6989586621679924818]) (l :: [e6989586621679924819]) (l :: [f6989586621679924820]) (l :: TyFun [g6989586621679924821] [h6989586621679924822])
  • type ZipWith7Sym8 (t :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679924815]) (t :: [b6989586621679924816]) (t :: [c6989586621679924817]) (t :: [d6989586621679924818]) (t :: [e6989586621679924819]) (t :: [f6989586621679924820]) (t :: [g6989586621679924821]) = ZipWith7 t t t t t t t t
  • data UnlinesSym0 (l :: TyFun [Symbol] Symbol)
  • type UnlinesSym1 (t :: [Symbol]) = Unlines t
  • data UnwordsSym0 (l :: TyFun [Symbol] Symbol)
  • type UnwordsSym1 (t :: [Symbol]) = Unwords t
  • data NubSym0 (l :: TyFun [a6989586621679444959] [a6989586621679444959])
  • type NubSym1 (t :: [a6989586621679444959]) = Nub t
  • data NubBySym0 (l :: TyFun (TyFun a6989586621679444958 (TyFun a6989586621679444958 Bool -> Type) -> Type) (TyFun [a6989586621679444958] [a6989586621679444958] -> Type))
  • data NubBySym1 (l :: TyFun a6989586621679444958 (TyFun a6989586621679444958 Bool -> Type) -> Type) (l :: TyFun [a6989586621679444958] [a6989586621679444958])
  • type NubBySym2 (t :: TyFun a6989586621679444958 (TyFun a6989586621679444958 Bool -> Type) -> Type) (t :: [a6989586621679444958]) = NubBy t t
  • data UnionSym0 (l :: TyFun [a6989586621679444955] (TyFun [a6989586621679444955] [a6989586621679444955] -> Type))
  • data UnionSym1 (l :: [a6989586621679444955]) (l :: TyFun [a6989586621679444955] [a6989586621679444955])
  • type UnionSym2 (t :: [a6989586621679444955]) (t :: [a6989586621679444955]) = Union t t
  • data UnionBySym0 (l :: TyFun (TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) (TyFun [a6989586621679444956] (TyFun [a6989586621679444956] [a6989586621679444956] -> Type) -> Type))
  • data UnionBySym1 (l :: TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) (l :: TyFun [a6989586621679444956] (TyFun [a6989586621679444956] [a6989586621679444956] -> Type))
  • data UnionBySym2 (l :: TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) (l :: [a6989586621679444956]) (l :: TyFun [a6989586621679444956] [a6989586621679444956])
  • type UnionBySym3 (t :: TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) (t :: [a6989586621679444956]) (t :: [a6989586621679444956]) = UnionBy t t t
  • data GenericLengthSym0 (l :: TyFun [a6989586621679444954] i6989586621679444953)
  • type GenericLengthSym1 (t :: [a6989586621679444954]) = GenericLength t
  • data GenericTakeSym0 (l :: TyFun i6989586621679924813 (TyFun [a6989586621679924814] [a6989586621679924814] -> Type))
  • data GenericTakeSym1 (l :: i6989586621679924813) (l :: TyFun [a6989586621679924814] [a6989586621679924814])
  • type GenericTakeSym2 (t :: i6989586621679924813) (t :: [a6989586621679924814]) = GenericTake t t
  • data GenericDropSym0 (l :: TyFun i6989586621679924811 (TyFun [a6989586621679924812] [a6989586621679924812] -> Type))
  • data GenericDropSym1 (l :: i6989586621679924811) (l :: TyFun [a6989586621679924812] [a6989586621679924812])
  • type GenericDropSym2 (t :: i6989586621679924811) (t :: [a6989586621679924812]) = GenericDrop t t
  • data GenericSplitAtSym0 (l :: TyFun i6989586621679924809 (TyFun [a6989586621679924810] ([a6989586621679924810], [a6989586621679924810]) -> Type))
  • data GenericSplitAtSym1 (l :: i6989586621679924809) (l :: TyFun [a6989586621679924810] ([a6989586621679924810], [a6989586621679924810]))
  • type GenericSplitAtSym2 (t :: i6989586621679924809) (t :: [a6989586621679924810]) = GenericSplitAt t t
  • data GenericIndexSym0 (l :: TyFun [a6989586621679924808] (TyFun i6989586621679924807 a6989586621679924808 -> Type))
  • data GenericIndexSym1 (l :: [a6989586621679924808]) (l :: TyFun i6989586621679924807 a6989586621679924808)
  • type GenericIndexSym2 (t :: [a6989586621679924808]) (t :: i6989586621679924807) = GenericIndex t t
  • data GenericReplicateSym0 (l :: TyFun i6989586621679924805 (TyFun a6989586621679924806 [a6989586621679924806] -> Type))
  • data GenericReplicateSym1 (l :: i6989586621679924805) (l :: TyFun a6989586621679924806 [a6989586621679924806])
  • type GenericReplicateSym2 (t :: i6989586621679924805) (t :: a6989586621679924806) = GenericReplicate t t

Basic functions

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

Equations

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

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

Equations

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

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) 

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

Equations

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

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

Equations

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

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

Equations

Null '[] = TrueSym0 
Null ((:) _ _) = FalseSym0 

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

Equations

Length '[] = FromInteger 0 
Length ((:) _ xs) = Apply (Apply (+@#@$) (FromInteger 1)) (Apply LengthSym0 xs) 

List transformations

type family Map (a :: TyFun a b -> Type) (a :: [a]) :: [b] where ... Source #

Equations

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

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

Equations

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

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

Equations

Intersperse _ '[] = '[] 
Intersperse sep ((:) x xs) = Apply (Apply (:@#@$) x) (Apply (Apply PrependToAllSym0 sep) xs) 

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

Equations

Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) 

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))) 

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

Equations

Subsequences xs = Apply (Apply (:@#@$) '[]) (Apply NonEmptySubsequencesSym0 xs) 

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

Equations

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

Reducing lists (folds)

type family Foldl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #

Equations

Foldl f z0 xs0 = Apply (Apply (Let6989586621679261487LgoSym3 f z0 xs0) z0) xs0 

type family Foldl' (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #

Equations

Foldl' f z0 xs0 = Apply (Apply (Let6989586621679456585LgoSym3 f z0 xs0) z0) xs0 

type family Foldl1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ... Source #

Equations

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

type family Foldl1' (a :: TyFun a (TyFun a a -> Type) -> Type) (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" 

type family Foldr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #

Equations

Foldr k z a_6989586621679422712 = Apply (Let6989586621679422717GoSym3 k z a_6989586621679422712) a_6989586621679422712 

type family Foldr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ... Source #

Equations

Foldr1 _ '[x] = x 
Foldr1 f ((:) x ((:) wild_6989586621679445542 wild_6989586621679445544)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let6989586621679456340XsSym4 f x wild_6989586621679445542 wild_6989586621679445544)) 
Foldr1 _ '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" 

Special folds

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

Equations

Concat a_6989586621679456319 = Apply (Apply (Apply FoldrSym0 (++@#@$)) '[]) a_6989586621679456319 

type family ConcatMap (a :: TyFun a [b] -> Type) (a :: [a]) :: [b] where ... Source #

Equations

ConcatMap f a_6989586621679456315 = Apply (Apply (Apply FoldrSym0 (Apply (Apply (.@#@$) (++@#@$)) f)) '[]) a_6989586621679456315 

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

Equations

And '[] = TrueSym0 
And ((:) x xs) = Apply (Apply (&&@#@$) x) (Apply AndSym0 xs) 

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

Equations

Or '[] = FalseSym0 
Or ((:) x xs) = Apply (Apply (||@#@$) x) (Apply OrSym0 xs) 

type family Any (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ... Source #

Equations

Any _ '[] = FalseSym0 
Any p ((:) x xs) = Apply (Apply (||@#@$) (Apply p x)) (Apply (Apply AnySym0 p) xs) 

type family All (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ... Source #

Equations

All _ '[] = TrueSym0 
All p ((:) x xs) = Apply (Apply (&&@#@$) (Apply p x)) (Apply (Apply AllSym0 p) xs) 

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

Equations

Sum l = Apply (Apply (Let6989586621679454390Sum'Sym1 l) l) (FromInteger 0) 

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

Equations

Product l = Apply (Apply (Let6989586621679454366ProdSym1 l) l) (FromInteger 1) 

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

Equations

Maximum '[] = Apply ErrorSym0 "Data.Singletons.List.maximum: empty list" 
Maximum ((:) wild_6989586621679445646 wild_6989586621679445648) = Apply (Apply Foldl1Sym0 MaxSym0) (Let6989586621679456545XsSym2 wild_6989586621679445646 wild_6989586621679445648) 

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

Equations

Minimum '[] = Apply ErrorSym0 "Data.Singletons.List.minimum: empty list" 
Minimum ((:) wild_6989586621679445650 wild_6989586621679445652) = Apply (Apply Foldl1Sym0 MinSym0) (Let6989586621679456559XsSym2 wild_6989586621679445650 wild_6989586621679445652) 

Building lists

Scans

type family Scanl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ... Source #

Equations

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

type family Scanl1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ... Source #

Equations

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

type family Scanr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ... Source #

Equations

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

type family Scanr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ... Source #

Equations

Scanr1 _ '[] = '[] 
Scanr1 _ '[x] = Apply (Apply (:@#@$) x) '[] 
Scanr1 f ((:) x ((:) wild_6989586621679445562 wild_6989586621679445564)) = Case_6989586621679456052 f x wild_6989586621679445562 wild_6989586621679445564 (Let6989586621679456033Scrutinee_6989586621679445556Sym4 f x wild_6989586621679445562 wild_6989586621679445564) 

Accumulating maps

type family MapAccumL (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... Source #

Equations

MapAccumL _ s '[] = Apply (Apply Tuple2Sym0 s) '[] 
MapAccumL f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let6989586621679455863S''Sym4 f s x xs)) (Apply (Apply (:@#@$) (Let6989586621679455863YSym4 f s x xs)) (Let6989586621679455863YsSym4 f s x xs)) 

type family MapAccumR (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... Source #

Equations

MapAccumR _ s '[] = Apply (Apply Tuple2Sym0 s) '[] 
MapAccumR f s ((:) x xs) = Apply (Apply Tuple2Sym0 (Let6989586621679455706S''Sym4 f s x xs)) (Apply (Apply (:@#@$) (Let6989586621679455706YSym4 f s x xs)) (Let6989586621679455706YsSym4 f s x xs)) 

Infinite lists

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

Equations

Replicate n x = Case_6989586621679454353 n x (Let6989586621679454345Scrutinee_6989586621679445658Sym2 n x) 

Unfolding

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

Equations

Unfoldr f b = Case_6989586621679455681 f b (Let6989586621679455673Scrutinee_6989586621679445566Sym2 f b) 

Sublists

Extracting sublists

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

Equations

Take _ '[] = '[] 
Take n ((:) x xs) = Case_6989586621679454550 n x xs (Let6989586621679454537Scrutinee_6989586621679445642Sym3 n x xs) 

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

Equations

Drop _ '[] = '[] 
Drop n ((:) x xs) = Case_6989586621679454522 n x xs (Let6989586621679454509Scrutinee_6989586621679445644Sym3 n x xs) 

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) 

type family TakeWhile (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ... Source #

Equations

TakeWhile _ '[] = '[] 
TakeWhile p ((:) x xs) = Case_6989586621679454884 p x xs (Let6989586621679454871Scrutinee_6989586621679445632Sym3 p x xs) 

type family DropWhile (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ... Source #

Equations

DropWhile _ '[] = '[] 
DropWhile p ((:) x xs') = Case_6989586621679454856 p x xs' (Let6989586621679454843Scrutinee_6989586621679445634Sym3 p x xs') 

type family DropWhileEnd (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ... Source #

Equations

DropWhileEnd p a_6989586621679457137 = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_6989586621679457141Sym0 p) a_6989586621679457137)) '[]) a_6989586621679457137 

type family Span (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... Source #

Equations

Span _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679454666XsSym0) Let6989586621679454666XsSym0 
Span p ((:) x xs') = Case_6989586621679454696 p x xs' (Let6989586621679454683Scrutinee_6989586621679445638Sym3 p x xs') 

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

Equations

Break _ '[] = Apply (Apply Tuple2Sym0 Let6989586621679454573XsSym0) Let6989586621679454573XsSym0 
Break p ((:) x xs') = Case_6989586621679454603 p x xs' (Let6989586621679454590Scrutinee_6989586621679445640Sym3 p x xs') 

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

Equations

StripPrefix '[] ys = Apply JustSym0 ys 
StripPrefix arg_6989586621679924931 arg_6989586621679924933 = Case_6989586621679937832 arg_6989586621679924931 arg_6989586621679924933 (Apply (Apply Tuple2Sym0 arg_6989586621679924931) arg_6989586621679924933) 

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

Equations

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

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

Equations

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

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

Equations

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

Predicates

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

Equations

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

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

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

Equations

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

Searching lists

Searching by equality

type family Elem (a :: a) (a :: [a]) :: Bool where ... infix 4 Source #

Equations

Elem _ '[] = FalseSym0 
Elem x ((:) y ys) = Apply (Apply (||@#@$) (Apply (Apply (==@#@$) x) y)) (Apply (Apply ElemSym0 x) ys) 

type family NotElem (a :: a) (a :: [a]) :: Bool where ... infix 4 Source #

Equations

NotElem _ '[] = TrueSym0 
NotElem x ((:) y ys) = Apply (Apply (&&@#@$) (Apply (Apply (/=@#@$) x) y)) (Apply (Apply NotElemSym0 x) ys) 

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

Equations

Lookup _key '[] = NothingSym0 
Lookup key ((:) '(x, y) xys) = Case_6989586621679454494 key x y xys (Let6989586621679454475Scrutinee_6989586621679445654Sym4 key x y xys) 

Searching with a predicate

type family Find (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe a where ... Source #

Equations

Find p a_6989586621679454925 = Apply (Apply (Apply (.@#@$) ListToMaybeSym0) (Apply FilterSym0 p)) a_6989586621679454925 

type family Filter (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ... Source #

Equations

Filter _p '[] = '[] 
Filter p ((:) x xs) = Case_6989586621679454913 p x xs (Let6989586621679454900Scrutinee_6989586621679445620Sym3 p x xs) 

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

Equations

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

Indexing lists

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

Equations

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

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

Equations

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

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

Equations

ElemIndices x a_6989586621679455531 = Apply (Apply FindIndicesSym0 (Apply (==@#@$) x)) a_6989586621679455531 

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

Equations

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

type family FindIndices (a :: TyFun a Bool -> Type) (a :: [a]) :: [Nat] where ... Source #

Equations

FindIndices p xs = Apply (Apply MapSym0 SndSym0) (Apply (Apply FilterSym0 (Apply (Apply Lambda_6989586621679455502Sym0 p) xs)) (Apply (Apply ZipSym0 xs) (Apply (Apply (Let6989586621679455479BuildListSym2 p xs) (FromInteger 0)) xs))) 

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

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

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

Equations

Zip4 a_6989586621679937786 a_6989586621679937788 a_6989586621679937790 a_6989586621679937792 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621679937786) a_6989586621679937788) a_6989586621679937790) a_6989586621679937792 

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

Equations

Zip5 a_6989586621679937741 a_6989586621679937743 a_6989586621679937745 a_6989586621679937747 a_6989586621679937749 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621679937741) a_6989586621679937743) a_6989586621679937745) a_6989586621679937747) a_6989586621679937749 

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_6989586621679937684 a_6989586621679937686 a_6989586621679937688 a_6989586621679937690 a_6989586621679937692 a_6989586621679937694 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621679937684) a_6989586621679937686) a_6989586621679937688) a_6989586621679937690) a_6989586621679937692) a_6989586621679937694 

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_6989586621679937614 a_6989586621679937616 a_6989586621679937618 a_6989586621679937620 a_6989586621679937622 a_6989586621679937624 a_6989586621679937626 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621679937614) a_6989586621679937616) a_6989586621679937618) a_6989586621679937620) a_6989586621679937622) a_6989586621679937624) a_6989586621679937626 

type family ZipWith (a :: TyFun a (TyFun b c -> Type) -> Type) (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 _ '[] ((:) _ _) = '[] 

type family ZipWith3 (a :: TyFun a (TyFun b (TyFun c d -> Type) -> Type) -> Type) (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 _ ((:) _ _) ((:) _ _) '[] = '[] 

type family ZipWith4 (a :: TyFun a (TyFun b (TyFun c (TyFun d e -> Type) -> Type) -> Type) -> Type) (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 :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e f -> Type) -> Type) -> Type) -> Type) -> Type) (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 :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e (TyFun f g -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (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 :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e (TyFun f (TyFun g h -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (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_6989586621679455360Sym0 xs)) (Apply (Apply Tuple2Sym0 '[]) '[])) xs 

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

Equations

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

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

Equations

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

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_6989586621679455258Sym0 xs)) (Apply (Apply (Apply (Apply (Apply Tuple5Sym0 '[]) '[]) '[]) '[]) '[])) xs 

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_6989586621679455220Sym0 xs)) (Apply (Apply (Apply (Apply (Apply (Apply Tuple6Sym0 '[]) '[]) '[]) '[]) '[]) '[])) xs 

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_6989586621679455180Sym0 xs)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply Tuple7Sym0 '[]) '[]) '[]) '[]) '[]) '[]) '[])) xs 

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)) 

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

Equations

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

"Set" operations

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

Equations

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

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

Equations

Delete a_6989586621679455117 a_6989586621679455119 = Apply (Apply (Apply DeleteBySym0 (==@#@$)) a_6989586621679455117) a_6989586621679455119 

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

Equations

a_6989586621679455132 \\ a_6989586621679455134 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 DeleteSym0)) a_6989586621679455132) a_6989586621679455134 

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

Equations

Union a_6989586621679455102 a_6989586621679455104 = Apply (Apply (Apply UnionBySym0 (==@#@$)) a_6989586621679455102) a_6989586621679455104 

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

Equations

Intersect a_6989586621679456267 a_6989586621679456269 = Apply (Apply (Apply IntersectBySym0 (==@#@$)) a_6989586621679456267) a_6989586621679456269 

Ordered lists

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

Equations

Sort a_6989586621679455014 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679455014 

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

Equations

Insert e ls = Apply (Apply (Apply InsertBySym0 CompareSym0) e) ls 

Generalized functions

The "By" operations

User-supplied equality (replacing an Eq context)

type family NubBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [a] where ... Source #

Equations

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

type family DeleteBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... Source #

Equations

DeleteBy _ _ '[] = '[] 
DeleteBy eq x ((:) y ys) = Case_6989586621679455059 eq x y ys (Let6989586621679455040Scrutinee_6989586621679445604Sym4 eq x y ys) 

type family DeleteFirstsBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... Source #

Equations

DeleteFirstsBy eq a_6989586621679455077 a_6989586621679455079 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679455077) a_6989586621679455079 

type family UnionBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (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) 

type family GroupBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [[a]] where ... Source #

Equations

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

type family IntersectBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... Source #

Equations

IntersectBy _ '[] '[] = '[] 
IntersectBy _ '[] ((:) _ _) = '[] 
IntersectBy _ ((:) _ _) '[] = '[] 
IntersectBy eq ((:) wild_6989586621679445624 wild_6989586621679445626) ((:) wild_6989586621679445628 wild_6989586621679445630) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679456230Sym0 eq) wild_6989586621679445624) wild_6989586621679445626) wild_6989586621679445628) wild_6989586621679445630)) (Let6989586621679456179XsSym5 eq wild_6989586621679445624 wild_6989586621679445626 wild_6989586621679445628 wild_6989586621679445630) 

User-supplied comparison (replacing an Ord context)

type family SortBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: [a] where ... Source #

Equations

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

type family InsertBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... Source #

Equations

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

type family MaximumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... Source #

Equations

MaximumBy _ '[] = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" 
MaximumBy cmp ((:) wild_6989586621679445610 wild_6989586621679445612) = Apply (Apply Foldl1Sym0 (Let6989586621679456396MaxBySym3 cmp wild_6989586621679445610 wild_6989586621679445612)) (Let6989586621679456383XsSym3 cmp wild_6989586621679445610 wild_6989586621679445612) 

type family MinimumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... Source #

Equations

MinimumBy _ '[] = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" 
MinimumBy cmp ((:) wild_6989586621679445616 wild_6989586621679445618) = Apply (Apply Foldl1Sym0 (Let6989586621679456480MinBySym3 cmp wild_6989586621679445616 wild_6989586621679445618)) (Let6989586621679456467XsSym3 cmp wild_6989586621679445616 wild_6989586621679445618) 

The "generic" operations

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

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

Equations

GenericTake a_6989586621679937373 a_6989586621679937375 = Apply (Apply TakeSym0 a_6989586621679937373) a_6989586621679937375 

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

Equations

GenericDrop a_6989586621679937358 a_6989586621679937360 = Apply (Apply DropSym0 a_6989586621679937358) a_6989586621679937360 

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

Equations

GenericSplitAt a_6989586621679937343 a_6989586621679937345 = Apply (Apply SplitAtSym0 a_6989586621679937343) a_6989586621679937345 

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

Equations

GenericIndex a_6989586621679937328 a_6989586621679937330 = Apply (Apply (!!@#@$) a_6989586621679937328) a_6989586621679937330 

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

Equations

GenericReplicate a_6989586621679937313 a_6989586621679937315 = Apply (Apply ReplicateSym0 a_6989586621679937313) a_6989586621679937315 

Defunctionalization symbols

type NilSym0 = '[] Source #

data (:@#@$) (l :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type)) Source #

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

data (l :: a3530822107858468865) :@#@$$ (l :: TyFun [a3530822107858468865] [a3530822107858468865]) Source #

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

Defined in Data.Singletons.Prelude.Instances

type Apply ((:@#@$$) l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:@#@$$) l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = l1 ': l2

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

type (++@#@$$$) (t :: [a6989586621679422444]) (t :: [a6989586621679422444]) = (++) t t Source #

data (l :: [a6989586621679422444]) ++@#@$$ (l :: TyFun [a6989586621679422444] [a6989586621679422444]) Source #

Instances
SuppressUnusedWarnings ((++@#@$$) :: [a6989586621679422444] -> TyFun [a6989586621679422444] [a6989586621679422444] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((++@#@$$) l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((++@#@$$) l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = l1 ++ l2

data (++@#@$) (l :: TyFun [a6989586621679422444] (TyFun [a6989586621679422444] [a6989586621679422444] -> Type)) Source #

Instances
SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679422444] (TyFun [a6989586621679422444] [a6989586621679422444] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((++@#@$) :: TyFun [a6989586621679422444] (TyFun [a6989586621679422444] [a6989586621679422444] -> Type) -> *) (l :: [a6989586621679422444]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((++@#@$) :: TyFun [a6989586621679422444] (TyFun [a6989586621679422444] [a6989586621679422444] -> Type) -> *) (l :: [a6989586621679422444]) = (++@#@$$) l

data HeadSym0 (l :: TyFun [a6989586621679445081] a6989586621679445081) Source #

Instances
SuppressUnusedWarnings (HeadSym0 :: TyFun [a6989586621679445081] a6989586621679445081 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

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

Defined in Data.Singletons.Prelude.List

type Apply (HeadSym0 :: TyFun [a] a -> *) (l :: [a]) = Head l

type HeadSym1 (t :: [a6989586621679445081]) = Head t Source #

data LastSym0 (l :: TyFun [a6989586621679445080] a6989586621679445080) Source #

Instances
SuppressUnusedWarnings (LastSym0 :: TyFun [a6989586621679445080] a6989586621679445080 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

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

Defined in Data.Singletons.Prelude.List

type Apply (LastSym0 :: TyFun [a] a -> *) (l :: [a]) = Last l

type LastSym1 (t :: [a6989586621679445080]) = Last t Source #

data TailSym0 (l :: TyFun [a6989586621679445079] [a6989586621679445079]) Source #

Instances
SuppressUnusedWarnings (TailSym0 :: TyFun [a6989586621679445079] [a6989586621679445079] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

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

Defined in Data.Singletons.Prelude.List

type Apply (TailSym0 :: TyFun [a] [a] -> *) (l :: [a]) = Tail l

type TailSym1 (t :: [a6989586621679445079]) = Tail t Source #

data InitSym0 (l :: TyFun [a6989586621679445078] [a6989586621679445078]) Source #

Instances
SuppressUnusedWarnings (InitSym0 :: TyFun [a6989586621679445078] [a6989586621679445078] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

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

Defined in Data.Singletons.Prelude.List

type Apply (InitSym0 :: TyFun [a] [a] -> *) (l :: [a]) = Init l

type InitSym1 (t :: [a6989586621679445078]) = Init t Source #

data NullSym0 (l :: TyFun [a6989586621679445077] Bool) Source #

Instances
SuppressUnusedWarnings (NullSym0 :: TyFun [a6989586621679445077] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (NullSym0 :: TyFun [a] Bool -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (NullSym0 :: TyFun [a] Bool -> *) (l :: [a]) = Null l

type NullSym1 (t :: [a6989586621679445077]) = Null t Source #

data MapSym0 (l :: TyFun (TyFun a6989586621679422445 b6989586621679422446 -> Type) (TyFun [a6989586621679422445] [b6989586621679422446] -> Type)) Source #

Instances
SuppressUnusedWarnings (MapSym0 :: TyFun (TyFun a6989586621679422445 b6989586621679422446 -> Type) (TyFun [a6989586621679422445] [b6989586621679422446] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym0 :: TyFun (TyFun a6989586621679422445 b6989586621679422446 -> Type) (TyFun [a6989586621679422445] [b6989586621679422446] -> Type) -> *) (l :: TyFun a6989586621679422445 b6989586621679422446 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym0 :: TyFun (TyFun a6989586621679422445 b6989586621679422446 -> Type) (TyFun [a6989586621679422445] [b6989586621679422446] -> Type) -> *) (l :: TyFun a6989586621679422445 b6989586621679422446 -> Type) = MapSym1 l

data MapSym1 (l :: TyFun a6989586621679422445 b6989586621679422446 -> Type) (l :: TyFun [a6989586621679422445] [b6989586621679422446]) Source #

Instances
SuppressUnusedWarnings (MapSym1 :: (TyFun a6989586621679422445 b6989586621679422446 -> Type) -> TyFun [a6989586621679422445] [b6989586621679422446] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym1 l1 :: TyFun [a] [b] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym1 l1 :: TyFun [a] [b] -> *) (l2 :: [a]) = Map l1 l2

type MapSym2 (t :: TyFun a6989586621679422445 b6989586621679422446 -> Type) (t :: [a6989586621679422445]) = Map t t Source #

data ReverseSym0 (l :: TyFun [a6989586621679445076] [a6989586621679445076]) Source #

Instances
SuppressUnusedWarnings (ReverseSym0 :: TyFun [a6989586621679445076] [a6989586621679445076] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

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

Defined in Data.Singletons.Prelude.List

type Apply (ReverseSym0 :: TyFun [a] [a] -> *) (l :: [a]) = Reverse l

type ReverseSym1 (t :: [a6989586621679445076]) = Reverse t Source #

data IntersperseSym0 (l :: TyFun a6989586621679445075 (TyFun [a6989586621679445075] [a6989586621679445075] -> Type)) Source #

Instances
SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679445075 (TyFun [a6989586621679445075] [a6989586621679445075] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersperseSym0 :: TyFun a6989586621679445075 (TyFun [a6989586621679445075] [a6989586621679445075] -> Type) -> *) (l :: a6989586621679445075) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersperseSym0 :: TyFun a6989586621679445075 (TyFun [a6989586621679445075] [a6989586621679445075] -> Type) -> *) (l :: a6989586621679445075) = IntersperseSym1 l

data IntersperseSym1 (l :: a6989586621679445075) (l :: TyFun [a6989586621679445075] [a6989586621679445075]) Source #

Instances
SuppressUnusedWarnings (IntersperseSym1 :: a6989586621679445075 -> TyFun [a6989586621679445075] [a6989586621679445075] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersperseSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersperseSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = Intersperse l1 l2

type IntersperseSym2 (t :: a6989586621679445075) (t :: [a6989586621679445075]) = Intersperse t t Source #

data IntercalateSym0 (l :: TyFun [a6989586621679445074] (TyFun [[a6989586621679445074]] [a6989586621679445074] -> Type)) Source #

Instances
SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a6989586621679445074] (TyFun [[a6989586621679445074]] [a6989586621679445074] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntercalateSym0 :: TyFun [a6989586621679445074] (TyFun [[a6989586621679445074]] [a6989586621679445074] -> Type) -> *) (l :: [a6989586621679445074]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntercalateSym0 :: TyFun [a6989586621679445074] (TyFun [[a6989586621679445074]] [a6989586621679445074] -> Type) -> *) (l :: [a6989586621679445074]) = IntercalateSym1 l

data IntercalateSym1 (l :: [a6989586621679445074]) (l :: TyFun [[a6989586621679445074]] [a6989586621679445074]) Source #

Instances
SuppressUnusedWarnings (IntercalateSym1 :: [a6989586621679445074] -> TyFun [[a6989586621679445074]] [a6989586621679445074] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntercalateSym1 l1 :: TyFun [[a]] [a] -> *) (l2 :: [[a]]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntercalateSym1 l1 :: TyFun [[a]] [a] -> *) (l2 :: [[a]]) = Intercalate l1 l2

type IntercalateSym2 (t :: [a6989586621679445074]) (t :: [[a6989586621679445074]]) = Intercalate t t Source #

data SubsequencesSym0 (l :: TyFun [a6989586621679445073] [[a6989586621679445073]]) Source #

Instances
SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a6989586621679445073] [[a6989586621679445073]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

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

Defined in Data.Singletons.Prelude.List

type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> *) (l :: [a]) = Subsequences l

type SubsequencesSym1 (t :: [a6989586621679445073]) = Subsequences t Source #

data PermutationsSym0 (l :: TyFun [a6989586621679445070] [[a6989586621679445070]]) Source #

Instances
SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a6989586621679445070] [[a6989586621679445070]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

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

Defined in Data.Singletons.Prelude.List

type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> *) (l :: [a]) = Permutations l

type PermutationsSym1 (t :: [a6989586621679445070]) = Permutations t Source #

data FoldlSym0 (l :: TyFun (TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) (TyFun b6989586621679261435 (TyFun [a6989586621679261434] b6989586621679261435 -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (FoldlSym0 :: TyFun (TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) (TyFun b6989586621679261435 (TyFun [a6989586621679261434] b6989586621679261435 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (FoldlSym0 :: TyFun (TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) (TyFun b6989586621679261435 (TyFun [a6989586621679261434] b6989586621679261435 -> Type) -> Type) -> *) (l :: TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (FoldlSym0 :: TyFun (TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) (TyFun b6989586621679261435 (TyFun [a6989586621679261434] b6989586621679261435 -> Type) -> Type) -> *) (l :: TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) = FoldlSym1 l

data FoldlSym1 (l :: TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) (l :: TyFun b6989586621679261435 (TyFun [a6989586621679261434] b6989586621679261435 -> Type)) Source #

Instances
SuppressUnusedWarnings (FoldlSym1 :: (TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) -> TyFun b6989586621679261435 (TyFun [a6989586621679261434] b6989586621679261435 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (FoldlSym1 l1 :: TyFun b6989586621679261435 (TyFun [a6989586621679261434] b6989586621679261435 -> Type) -> *) (l2 :: b6989586621679261435) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (FoldlSym1 l1 :: TyFun b6989586621679261435 (TyFun [a6989586621679261434] b6989586621679261435 -> Type) -> *) (l2 :: b6989586621679261435) = FoldlSym2 l1 l2

data FoldlSym2 (l :: TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) (l :: b6989586621679261435) (l :: TyFun [a6989586621679261434] b6989586621679261435) Source #

Instances
SuppressUnusedWarnings (FoldlSym2 :: (TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) -> b6989586621679261435 -> TyFun [a6989586621679261434] b6989586621679261435 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (FoldlSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (FoldlSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) = Foldl l1 l2 l3

type FoldlSym3 (t :: TyFun b6989586621679261435 (TyFun a6989586621679261434 b6989586621679261435 -> Type) -> Type) (t :: b6989586621679261435) (t :: [a6989586621679261434]) = Foldl t t t Source #

data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) (TyFun b6989586621679445069 (TyFun [a6989586621679445068] b6989586621679445069 -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) (TyFun b6989586621679445069 (TyFun [a6989586621679445068] b6989586621679445069 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl'Sym0 :: TyFun (TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) (TyFun b6989586621679445069 (TyFun [a6989586621679445068] b6989586621679445069 -> Type) -> Type) -> *) (l :: TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl'Sym0 :: TyFun (TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) (TyFun b6989586621679445069 (TyFun [a6989586621679445068] b6989586621679445069 -> Type) -> Type) -> *) (l :: TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) = Foldl'Sym1 l

data Foldl'Sym1 (l :: TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) (l :: TyFun b6989586621679445069 (TyFun [a6989586621679445068] b6989586621679445069 -> Type)) Source #

Instances
SuppressUnusedWarnings (Foldl'Sym1 :: (TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) -> TyFun b6989586621679445069 (TyFun [a6989586621679445068] b6989586621679445069 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl'Sym1 l1 :: TyFun b6989586621679445069 (TyFun [a6989586621679445068] b6989586621679445069 -> Type) -> *) (l2 :: b6989586621679445069) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl'Sym1 l1 :: TyFun b6989586621679445069 (TyFun [a6989586621679445068] b6989586621679445069 -> Type) -> *) (l2 :: b6989586621679445069) = Foldl'Sym2 l1 l2

data Foldl'Sym2 (l :: TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) (l :: b6989586621679445069) (l :: TyFun [a6989586621679445068] b6989586621679445069) Source #

Instances
SuppressUnusedWarnings (Foldl'Sym2 :: (TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) -> b6989586621679445069 -> TyFun [a6989586621679445068] b6989586621679445069 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl'Sym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl'Sym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) = Foldl' l1 l2 l3

type Foldl'Sym3 (t :: TyFun b6989586621679445069 (TyFun a6989586621679445068 b6989586621679445069 -> Type) -> Type) (t :: b6989586621679445069) (t :: [a6989586621679445068]) = Foldl' t t t Source #

data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679445067 (TyFun a6989586621679445067 a6989586621679445067 -> Type) -> Type) (TyFun [a6989586621679445067] a6989586621679445067 -> Type)) Source #

Instances
SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (TyFun a6989586621679445067 (TyFun a6989586621679445067 a6989586621679445067 -> Type) -> Type) (TyFun [a6989586621679445067] a6989586621679445067 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl1Sym0 :: TyFun (TyFun a6989586621679445067 (TyFun a6989586621679445067 a6989586621679445067 -> Type) -> Type) (TyFun [a6989586621679445067] a6989586621679445067 -> Type) -> *) (l :: TyFun a6989586621679445067 (TyFun a6989586621679445067 a6989586621679445067 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl1Sym0 :: TyFun (TyFun a6989586621679445067 (TyFun a6989586621679445067 a6989586621679445067 -> Type) -> Type) (TyFun [a6989586621679445067] a6989586621679445067 -> Type) -> *) (l :: TyFun a6989586621679445067 (TyFun a6989586621679445067 a6989586621679445067 -> Type) -> Type) = Foldl1Sym1 l

data Foldl1Sym1 (l :: TyFun a6989586621679445067 (TyFun a6989586621679445067 a6989586621679445067 -> Type) -> Type) (l :: TyFun [a6989586621679445067] a6989586621679445067) Source #

Instances
SuppressUnusedWarnings (Foldl1Sym1 :: (TyFun a6989586621679445067 (TyFun a6989586621679445067 a6989586621679445067 -> Type) -> Type) -> TyFun [a6989586621679445067] a6989586621679445067 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl1Sym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl1Sym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) = Foldl1 l1 l2

type Foldl1Sym2 (t :: TyFun a6989586621679445067 (TyFun a6989586621679445067 a6989586621679445067 -> Type) -> Type) (t :: [a6989586621679445067]) = Foldl1 t t Source #

data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679445066 (TyFun a6989586621679445066 a6989586621679445066 -> Type) -> Type) (TyFun [a6989586621679445066] a6989586621679445066 -> Type)) Source #

Instances
SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (TyFun a6989586621679445066 (TyFun a6989586621679445066 a6989586621679445066 -> Type) -> Type) (TyFun [a6989586621679445066] a6989586621679445066 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl1'Sym0 :: TyFun (TyFun a6989586621679445066 (TyFun a6989586621679445066 a6989586621679445066 -> Type) -> Type) (TyFun [a6989586621679445066] a6989586621679445066 -> Type) -> *) (l :: TyFun a6989586621679445066 (TyFun a6989586621679445066 a6989586621679445066 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl1'Sym0 :: TyFun (TyFun a6989586621679445066 (TyFun a6989586621679445066 a6989586621679445066 -> Type) -> Type) (TyFun [a6989586621679445066] a6989586621679445066 -> Type) -> *) (l :: TyFun a6989586621679445066 (TyFun a6989586621679445066 a6989586621679445066 -> Type) -> Type) = Foldl1'Sym1 l

data Foldl1'Sym1 (l :: TyFun a6989586621679445066 (TyFun a6989586621679445066 a6989586621679445066 -> Type) -> Type) (l :: TyFun [a6989586621679445066] a6989586621679445066) Source #

Instances
SuppressUnusedWarnings (Foldl1'Sym1 :: (TyFun a6989586621679445066 (TyFun a6989586621679445066 a6989586621679445066 -> Type) -> Type) -> TyFun [a6989586621679445066] a6989586621679445066 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl1'Sym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldl1'Sym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) = Foldl1' l1 l2

type Foldl1'Sym2 (t :: TyFun a6989586621679445066 (TyFun a6989586621679445066 a6989586621679445066 -> Type) -> Type) (t :: [a6989586621679445066]) = Foldl1' t t Source #

data FoldrSym0 (l :: TyFun (TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) (TyFun b6989586621679422448 (TyFun [a6989586621679422447] b6989586621679422448 -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (FoldrSym0 :: TyFun (TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) (TyFun b6989586621679422448 (TyFun [a6989586621679422447] b6989586621679422448 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym0 :: TyFun (TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) (TyFun b6989586621679422448 (TyFun [a6989586621679422447] b6989586621679422448 -> Type) -> Type) -> *) (l :: TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym0 :: TyFun (TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) (TyFun b6989586621679422448 (TyFun [a6989586621679422447] b6989586621679422448 -> Type) -> Type) -> *) (l :: TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) = FoldrSym1 l

data FoldrSym1 (l :: TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) (l :: TyFun b6989586621679422448 (TyFun [a6989586621679422447] b6989586621679422448 -> Type)) Source #

Instances
SuppressUnusedWarnings (FoldrSym1 :: (TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) -> TyFun b6989586621679422448 (TyFun [a6989586621679422447] b6989586621679422448 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym1 l1 :: TyFun b6989586621679422448 (TyFun [a6989586621679422447] b6989586621679422448 -> Type) -> *) (l2 :: b6989586621679422448) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym1 l1 :: TyFun b6989586621679422448 (TyFun [a6989586621679422447] b6989586621679422448 -> Type) -> *) (l2 :: b6989586621679422448) = FoldrSym2 l1 l2

data FoldrSym2 (l :: TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) (l :: b6989586621679422448) (l :: TyFun [a6989586621679422447] b6989586621679422448) Source #

Instances
SuppressUnusedWarnings (FoldrSym2 :: (TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) -> b6989586621679422448 -> TyFun [a6989586621679422447] b6989586621679422448 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) = Foldr l1 l2 l3

type FoldrSym3 (t :: TyFun a6989586621679422447 (TyFun b6989586621679422448 b6989586621679422448 -> Type) -> Type) (t :: b6989586621679422448) (t :: [a6989586621679422447]) = Foldr t t t Source #

data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679445065 (TyFun a6989586621679445065 a6989586621679445065 -> Type) -> Type) (TyFun [a6989586621679445065] a6989586621679445065 -> Type)) Source #

Instances
SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (TyFun a6989586621679445065 (TyFun a6989586621679445065 a6989586621679445065 -> Type) -> Type) (TyFun [a6989586621679445065] a6989586621679445065 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldr1Sym0 :: TyFun (TyFun a6989586621679445065 (TyFun a6989586621679445065 a6989586621679445065 -> Type) -> Type) (TyFun [a6989586621679445065] a6989586621679445065 -> Type) -> *) (l :: TyFun a6989586621679445065 (TyFun a6989586621679445065 a6989586621679445065 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldr1Sym0 :: TyFun (TyFun a6989586621679445065 (TyFun a6989586621679445065 a6989586621679445065 -> Type) -> Type) (TyFun [a6989586621679445065] a6989586621679445065 -> Type) -> *) (l :: TyFun a6989586621679445065 (TyFun a6989586621679445065 a6989586621679445065 -> Type) -> Type) = Foldr1Sym1 l

data Foldr1Sym1 (l :: TyFun a6989586621679445065 (TyFun a6989586621679445065 a6989586621679445065 -> Type) -> Type) (l :: TyFun [a6989586621679445065] a6989586621679445065) Source #

Instances
SuppressUnusedWarnings (Foldr1Sym1 :: (TyFun a6989586621679445065 (TyFun a6989586621679445065 a6989586621679445065 -> Type) -> Type) -> TyFun [a6989586621679445065] a6989586621679445065 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldr1Sym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Foldr1Sym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) = Foldr1 l1 l2

type Foldr1Sym2 (t :: TyFun a6989586621679445065 (TyFun a6989586621679445065 a6989586621679445065 -> Type) -> Type) (t :: [a6989586621679445065]) = Foldr1 t t Source #

data ConcatSym0 (l :: TyFun [[a6989586621679445064]] [a6989586621679445064]) Source #

Instances
SuppressUnusedWarnings (ConcatSym0 :: TyFun [[a6989586621679445064]] [a6989586621679445064] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ConcatSym0 :: TyFun [[a]] [a] -> *) (l :: [[a]]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ConcatSym0 :: TyFun [[a]] [a] -> *) (l :: [[a]]) = Concat l

type ConcatSym1 (t :: [[a6989586621679445064]]) = Concat t Source #

data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679445062 [b6989586621679445063] -> Type) (TyFun [a6989586621679445062] [b6989586621679445063] -> Type)) Source #

Instances
SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (TyFun a6989586621679445062 [b6989586621679445063] -> Type) (TyFun [a6989586621679445062] [b6989586621679445063] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ConcatMapSym0 :: TyFun (TyFun a6989586621679445062 [b6989586621679445063] -> Type) (TyFun [a6989586621679445062] [b6989586621679445063] -> Type) -> *) (l :: TyFun a6989586621679445062 [b6989586621679445063] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ConcatMapSym0 :: TyFun (TyFun a6989586621679445062 [b6989586621679445063] -> Type) (TyFun [a6989586621679445062] [b6989586621679445063] -> Type) -> *) (l :: TyFun a6989586621679445062 [b6989586621679445063] -> Type) = ConcatMapSym1 l

data ConcatMapSym1 (l :: TyFun a6989586621679445062 [b6989586621679445063] -> Type) (l :: TyFun [a6989586621679445062] [b6989586621679445063]) Source #

Instances
SuppressUnusedWarnings (ConcatMapSym1 :: (TyFun a6989586621679445062 [b6989586621679445063] -> Type) -> TyFun [a6989586621679445062] [b6989586621679445063] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ConcatMapSym1 l1 :: TyFun [a] [b] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ConcatMapSym1 l1 :: TyFun [a] [b] -> *) (l2 :: [a]) = ConcatMap l1 l2

type ConcatMapSym2 (t :: TyFun a6989586621679445062 [b6989586621679445063] -> Type) (t :: [a6989586621679445062]) = ConcatMap t t Source #

data AndSym0 (l :: TyFun [Bool] Bool) Source #

Instances
SuppressUnusedWarnings AndSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply AndSym0 (l :: [Bool]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply AndSym0 (l :: [Bool]) = And l

type AndSym1 (t :: [Bool]) = And t Source #

data OrSym0 (l :: TyFun [Bool] Bool) Source #

Instances
SuppressUnusedWarnings OrSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply OrSym0 (l :: [Bool]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply OrSym0 (l :: [Bool]) = Or l

type OrSym1 (t :: [Bool]) = Or t Source #

data AnySym0 (l :: TyFun (TyFun a6989586621679445060 Bool -> Type) (TyFun [a6989586621679445060] Bool -> Type)) Source #

Instances
SuppressUnusedWarnings (AnySym0 :: TyFun (TyFun a6989586621679445060 Bool -> Type) (TyFun [a6989586621679445060] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (AnySym0 :: TyFun (TyFun a6989586621679445060 Bool -> Type) (TyFun [a6989586621679445060] Bool -> Type) -> *) (l :: TyFun a6989586621679445060 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (AnySym0 :: TyFun (TyFun a6989586621679445060 Bool -> Type) (TyFun [a6989586621679445060] Bool -> Type) -> *) (l :: TyFun a6989586621679445060 Bool -> Type) = AnySym1 l

data AnySym1 (l :: TyFun a6989586621679445060 Bool -> Type) (l :: TyFun [a6989586621679445060] Bool) Source #

Instances
SuppressUnusedWarnings (AnySym1 :: (TyFun a6989586621679445060 Bool -> Type) -> TyFun [a6989586621679445060] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (AnySym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (AnySym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) = Any l1 l2

type AnySym2 (t :: TyFun a6989586621679445060 Bool -> Type) (t :: [a6989586621679445060]) = Any t t Source #

data AllSym0 (l :: TyFun (TyFun a6989586621679445061 Bool -> Type) (TyFun [a6989586621679445061] Bool -> Type)) Source #

Instances
SuppressUnusedWarnings (AllSym0 :: TyFun (TyFun a6989586621679445061 Bool -> Type) (TyFun [a6989586621679445061] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (AllSym0 :: TyFun (TyFun a6989586621679445061 Bool -> Type) (TyFun [a6989586621679445061] Bool -> Type) -> *) (l :: TyFun a6989586621679445061 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (AllSym0 :: TyFun (TyFun a6989586621679445061 Bool -> Type) (TyFun [a6989586621679445061] Bool -> Type) -> *) (l :: TyFun a6989586621679445061 Bool -> Type) = AllSym1 l

data AllSym1 (l :: TyFun a6989586621679445061 Bool -> Type) (l :: TyFun [a6989586621679445061] Bool) Source #

Instances
SuppressUnusedWarnings (AllSym1 :: (TyFun a6989586621679445061 Bool -> Type) -> TyFun [a6989586621679445061] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (AllSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (AllSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) = All l1 l2

type AllSym2 (t :: TyFun a6989586621679445061 Bool -> Type) (t :: [a6989586621679445061]) = All t t Source #

data ScanlSym0 (l :: TyFun (TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) (TyFun b6989586621679445058 (TyFun [a6989586621679445059] [b6989586621679445058] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ScanlSym0 :: TyFun (TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) (TyFun b6989586621679445058 (TyFun [a6989586621679445059] [b6989586621679445058] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ScanlSym0 :: TyFun (TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) (TyFun b6989586621679445058 (TyFun [a6989586621679445059] [b6989586621679445058] -> Type) -> Type) -> *) (l :: TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ScanlSym0 :: TyFun (TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) (TyFun b6989586621679445058 (TyFun [a6989586621679445059] [b6989586621679445058] -> Type) -> Type) -> *) (l :: TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) = ScanlSym1 l

data ScanlSym1 (l :: TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) (l :: TyFun b6989586621679445058 (TyFun [a6989586621679445059] [b6989586621679445058] -> Type)) Source #

Instances
SuppressUnusedWarnings (ScanlSym1 :: (TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) -> TyFun b6989586621679445058 (TyFun [a6989586621679445059] [b6989586621679445058] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ScanlSym1 l1 :: TyFun b6989586621679445058 (TyFun [a6989586621679445059] [b6989586621679445058] -> Type) -> *) (l2 :: b6989586621679445058) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ScanlSym1 l1 :: TyFun b6989586621679445058 (TyFun [a6989586621679445059] [b6989586621679445058] -> Type) -> *) (l2 :: b6989586621679445058) = ScanlSym2 l1 l2

data ScanlSym2 (l :: TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) (l :: b6989586621679445058) (l :: TyFun [a6989586621679445059] [b6989586621679445058]) Source #

Instances
SuppressUnusedWarnings (ScanlSym2 :: (TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) -> b6989586621679445058 -> TyFun [a6989586621679445059] [b6989586621679445058] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ScanlSym2 l1 l2 :: TyFun [a] [b] -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ScanlSym2 l1 l2 :: TyFun [a] [b] -> *) (l3 :: [a]) = Scanl l1 l2 l3

type ScanlSym3 (t :: TyFun b6989586621679445058 (TyFun a6989586621679445059 b6989586621679445058 -> Type) -> Type) (t :: b6989586621679445058) (t :: [a6989586621679445059]) = Scanl t t t Source #

data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679445057 (TyFun a6989586621679445057 a6989586621679445057 -> Type) -> Type) (TyFun [a6989586621679445057] [a6989586621679445057] -> Type)) Source #

Instances
SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (TyFun a6989586621679445057 (TyFun a6989586621679445057 a6989586621679445057 -> Type) -> Type) (TyFun [a6989586621679445057] [a6989586621679445057] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Scanl1Sym0 :: TyFun (TyFun a6989586621679445057 (TyFun a6989586621679445057 a6989586621679445057 -> Type) -> Type) (TyFun [a6989586621679445057] [a6989586621679445057] -> Type) -> *) (l :: TyFun a6989586621679445057 (TyFun a6989586621679445057 a6989586621679445057 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Scanl1Sym0 :: TyFun (TyFun a6989586621679445057 (TyFun a6989586621679445057 a6989586621679445057 -> Type) -> Type) (TyFun [a6989586621679445057] [a6989586621679445057] -> Type) -> *) (l :: TyFun a6989586621679445057 (TyFun a6989586621679445057 a6989586621679445057 -> Type) -> Type) = Scanl1Sym1 l

data Scanl1Sym1 (l :: TyFun a6989586621679445057 (TyFun a6989586621679445057 a6989586621679445057 -> Type) -> Type) (l :: TyFun [a6989586621679445057] [a6989586621679445057]) Source #

Instances
SuppressUnusedWarnings (Scanl1Sym1 :: (TyFun a6989586621679445057 (TyFun a6989586621679445057 a6989586621679445057 -> Type) -> Type) -> TyFun [a6989586621679445057] [a6989586621679445057] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Scanl1Sym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Scanl1Sym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = Scanl1 l1 l2

type Scanl1Sym2 (t :: TyFun a6989586621679445057 (TyFun a6989586621679445057 a6989586621679445057 -> Type) -> Type) (t :: [a6989586621679445057]) = Scanl1 t t Source #

data ScanrSym0 (l :: TyFun (TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) (TyFun b6989586621679445056 (TyFun [a6989586621679445055] [b6989586621679445056] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ScanrSym0 :: TyFun (TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) (TyFun b6989586621679445056 (TyFun [a6989586621679445055] [b6989586621679445056] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ScanrSym0 :: TyFun (TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) (TyFun b6989586621679445056 (TyFun [a6989586621679445055] [b6989586621679445056] -> Type) -> Type) -> *) (l :: TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ScanrSym0 :: TyFun (TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) (TyFun b6989586621679445056 (TyFun [a6989586621679445055] [b6989586621679445056] -> Type) -> Type) -> *) (l :: TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) = ScanrSym1 l

data ScanrSym1 (l :: TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) (l :: TyFun b6989586621679445056 (TyFun [a6989586621679445055] [b6989586621679445056] -> Type)) Source #

Instances
SuppressUnusedWarnings (ScanrSym1 :: (TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) -> TyFun b6989586621679445056 (TyFun [a6989586621679445055] [b6989586621679445056] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ScanrSym1 l1 :: TyFun b6989586621679445056 (TyFun [a6989586621679445055] [b6989586621679445056] -> Type) -> *) (l2 :: b6989586621679445056) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ScanrSym1 l1 :: TyFun b6989586621679445056 (TyFun [a6989586621679445055] [b6989586621679445056] -> Type) -> *) (l2 :: b6989586621679445056) = ScanrSym2 l1 l2

data ScanrSym2 (l :: TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) (l :: b6989586621679445056) (l :: TyFun [a6989586621679445055] [b6989586621679445056]) Source #

Instances
SuppressUnusedWarnings (ScanrSym2 :: (TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) -> b6989586621679445056 -> TyFun [a6989586621679445055] [b6989586621679445056] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ScanrSym2 l1 l2 :: TyFun [a] [b] -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ScanrSym2 l1 l2 :: TyFun [a] [b] -> *) (l3 :: [a]) = Scanr l1 l2 l3

type ScanrSym3 (t :: TyFun a6989586621679445055 (TyFun b6989586621679445056 b6989586621679445056 -> Type) -> Type) (t :: b6989586621679445056) (t :: [a6989586621679445055]) = Scanr t t t Source #

data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679445054 (TyFun a6989586621679445054 a6989586621679445054 -> Type) -> Type) (TyFun [a6989586621679445054] [a6989586621679445054] -> Type)) Source #

Instances
SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (TyFun a6989586621679445054 (TyFun a6989586621679445054 a6989586621679445054 -> Type) -> Type) (TyFun [a6989586621679445054] [a6989586621679445054] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Scanr1Sym0 :: TyFun (TyFun a6989586621679445054 (TyFun a6989586621679445054 a6989586621679445054 -> Type) -> Type) (TyFun [a6989586621679445054] [a6989586621679445054] -> Type) -> *) (l :: TyFun a6989586621679445054 (TyFun a6989586621679445054 a6989586621679445054 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Scanr1Sym0 :: TyFun (TyFun a6989586621679445054 (TyFun a6989586621679445054 a6989586621679445054 -> Type) -> Type) (TyFun [a6989586621679445054] [a6989586621679445054] -> Type) -> *) (l :: TyFun a6989586621679445054 (TyFun a6989586621679445054 a6989586621679445054 -> Type) -> Type) = Scanr1Sym1 l

data Scanr1Sym1 (l :: TyFun a6989586621679445054 (TyFun a6989586621679445054 a6989586621679445054 -> Type) -> Type) (l :: TyFun [a6989586621679445054] [a6989586621679445054]) Source #

Instances
SuppressUnusedWarnings (Scanr1Sym1 :: (TyFun a6989586621679445054 (TyFun a6989586621679445054 a6989586621679445054 -> Type) -> Type) -> TyFun [a6989586621679445054] [a6989586621679445054] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Scanr1Sym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Scanr1Sym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = Scanr1 l1 l2

type Scanr1Sym2 (t :: TyFun a6989586621679445054 (TyFun a6989586621679445054 a6989586621679445054 -> Type) -> Type) (t :: [a6989586621679445054]) = Scanr1 t t Source #

data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) (TyFun acc6989586621679445051 (TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053]) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) (TyFun acc6989586621679445051 (TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053]) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MapAccumLSym0 :: TyFun (TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) (TyFun acc6989586621679445051 (TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053]) -> Type) -> Type) -> *) (l :: TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MapAccumLSym0 :: TyFun (TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) (TyFun acc6989586621679445051 (TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053]) -> Type) -> Type) -> *) (l :: TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) = MapAccumLSym1 l

data MapAccumLSym1 (l :: TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) (l :: TyFun acc6989586621679445051 (TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053]) -> Type)) Source #

Instances
SuppressUnusedWarnings (MapAccumLSym1 :: (TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) -> TyFun acc6989586621679445051 (TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MapAccumLSym1 l1 :: TyFun acc6989586621679445051 (TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053]) -> Type) -> *) (l2 :: acc6989586621679445051) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MapAccumLSym1 l1 :: TyFun acc6989586621679445051 (TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053]) -> Type) -> *) (l2 :: acc6989586621679445051) = MapAccumLSym2 l1 l2

data MapAccumLSym2 (l :: TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) (l :: acc6989586621679445051) (l :: TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053])) Source #

Instances
SuppressUnusedWarnings (MapAccumLSym2 :: (TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) -> acc6989586621679445051 -> TyFun [x6989586621679445052] (acc6989586621679445051, [y6989586621679445053]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MapAccumLSym2 l1 l2 :: TyFun [x] (acc, [y]) -> *) (l3 :: [x]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MapAccumLSym2 l1 l2 :: TyFun [x] (acc, [y]) -> *) (l3 :: [x]) = MapAccumL l1 l2 l3

type MapAccumLSym3 (t :: TyFun acc6989586621679445051 (TyFun x6989586621679445052 (acc6989586621679445051, y6989586621679445053) -> Type) -> Type) (t :: acc6989586621679445051) (t :: [x6989586621679445052]) = MapAccumL t t t Source #

data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) (TyFun acc6989586621679445048 (TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050]) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) (TyFun acc6989586621679445048 (TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050]) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MapAccumRSym0 :: TyFun (TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) (TyFun acc6989586621679445048 (TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050]) -> Type) -> Type) -> *) (l :: TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MapAccumRSym0 :: TyFun (TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) (TyFun acc6989586621679445048 (TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050]) -> Type) -> Type) -> *) (l :: TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) = MapAccumRSym1 l

data MapAccumRSym1 (l :: TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) (l :: TyFun acc6989586621679445048 (TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050]) -> Type)) Source #

Instances
SuppressUnusedWarnings (MapAccumRSym1 :: (TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) -> TyFun acc6989586621679445048 (TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MapAccumRSym1 l1 :: TyFun acc6989586621679445048 (TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050]) -> Type) -> *) (l2 :: acc6989586621679445048) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MapAccumRSym1 l1 :: TyFun acc6989586621679445048 (TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050]) -> Type) -> *) (l2 :: acc6989586621679445048) = MapAccumRSym2 l1 l2

data MapAccumRSym2 (l :: TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) (l :: acc6989586621679445048) (l :: TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050])) Source #

Instances
SuppressUnusedWarnings (MapAccumRSym2 :: (TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) -> acc6989586621679445048 -> TyFun [x6989586621679445049] (acc6989586621679445048, [y6989586621679445050]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MapAccumRSym2 l1 l2 :: TyFun [x] (acc, [y]) -> *) (l3 :: [x]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MapAccumRSym2 l1 l2 :: TyFun [x] (acc, [y]) -> *) (l3 :: [x]) = MapAccumR l1 l2 l3

type MapAccumRSym3 (t :: TyFun acc6989586621679445048 (TyFun x6989586621679445049 (acc6989586621679445048, y6989586621679445050) -> Type) -> Type) (t :: acc6989586621679445048) (t :: [x6989586621679445049]) = MapAccumR t t t Source #

data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679445046 (Maybe (a6989586621679445047, b6989586621679445046)) -> Type) (TyFun b6989586621679445046 [a6989586621679445047] -> Type)) Source #

Instances
SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (TyFun b6989586621679445046 (Maybe (a6989586621679445047, b6989586621679445046)) -> Type) (TyFun b6989586621679445046 [a6989586621679445047] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnfoldrSym0 :: TyFun (TyFun b6989586621679445046 (Maybe (a6989586621679445047, b6989586621679445046)) -> Type) (TyFun b6989586621679445046 [a6989586621679445047] -> Type) -> *) (l :: TyFun b6989586621679445046 (Maybe (a6989586621679445047, b6989586621679445046)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnfoldrSym0 :: TyFun (TyFun b6989586621679445046 (Maybe (a6989586621679445047, b6989586621679445046)) -> Type) (TyFun b6989586621679445046 [a6989586621679445047] -> Type) -> *) (l :: TyFun b6989586621679445046 (Maybe (a6989586621679445047, b6989586621679445046)) -> Type) = UnfoldrSym1 l

data UnfoldrSym1 (l :: TyFun b6989586621679445046 (Maybe (a6989586621679445047, b6989586621679445046)) -> Type) (l :: TyFun b6989586621679445046 [a6989586621679445047]) Source #

Instances
SuppressUnusedWarnings (UnfoldrSym1 :: (TyFun b6989586621679445046 (Maybe (a6989586621679445047, b6989586621679445046)) -> Type) -> TyFun b6989586621679445046 [a6989586621679445047] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnfoldrSym1 l1 :: TyFun b [a] -> *) (l2 :: b) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnfoldrSym1 l1 :: TyFun b [a] -> *) (l2 :: b) = Unfoldr l1 l2

type UnfoldrSym2 (t :: TyFun b6989586621679445046 (Maybe (a6989586621679445047, b6989586621679445046)) -> Type) (t :: b6989586621679445046) = Unfoldr t t Source #

data InitsSym0 (l :: TyFun [a6989586621679445045] [[a6989586621679445045]]) Source #

Instances
SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621679445045] [[a6989586621679445045]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (InitsSym0 :: TyFun [a] [[a]] -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (InitsSym0 :: TyFun [a] [[a]] -> *) (l :: [a]) = Inits l

type InitsSym1 (t :: [a6989586621679445045]) = Inits t Source #

data TailsSym0 (l :: TyFun [a6989586621679445044] [[a6989586621679445044]]) Source #

Instances
SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621679445044] [[a6989586621679445044]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (TailsSym0 :: TyFun [a] [[a]] -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (TailsSym0 :: TyFun [a] [[a]] -> *) (l :: [a]) = Tails l

type TailsSym1 (t :: [a6989586621679445044]) = Tails t Source #

data IsPrefixOfSym0 (l :: TyFun [a6989586621679445043] (TyFun [a6989586621679445043] Bool -> Type)) Source #

Instances
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679445043] (TyFun [a6989586621679445043] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679445043] (TyFun [a6989586621679445043] Bool -> Type) -> *) (l :: [a6989586621679445043]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679445043] (TyFun [a6989586621679445043] Bool -> Type) -> *) (l :: [a6989586621679445043]) = IsPrefixOfSym1 l

data IsPrefixOfSym1 (l :: [a6989586621679445043]) (l :: TyFun [a6989586621679445043] Bool) Source #

Instances
SuppressUnusedWarnings (IsPrefixOfSym1 :: [a6989586621679445043] -> TyFun [a6989586621679445043] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IsPrefixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IsPrefixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) = IsPrefixOf l1 l2

type IsPrefixOfSym2 (t :: [a6989586621679445043]) (t :: [a6989586621679445043]) = IsPrefixOf t t Source #

data IsSuffixOfSym0 (l :: TyFun [a6989586621679445042] (TyFun [a6989586621679445042] Bool -> Type)) Source #

Instances
SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679445042] (TyFun [a6989586621679445042] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679445042] (TyFun [a6989586621679445042] Bool -> Type) -> *) (l :: [a6989586621679445042]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679445042] (TyFun [a6989586621679445042] Bool -> Type) -> *) (l :: [a6989586621679445042]) = IsSuffixOfSym1 l

data IsSuffixOfSym1 (l :: [a6989586621679445042]) (l :: TyFun [a6989586621679445042] Bool) Source #

Instances
SuppressUnusedWarnings (IsSuffixOfSym1 :: [a6989586621679445042] -> TyFun [a6989586621679445042] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IsSuffixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IsSuffixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) = IsSuffixOf l1 l2

type IsSuffixOfSym2 (t :: [a6989586621679445042]) (t :: [a6989586621679445042]) = IsSuffixOf t t Source #

data IsInfixOfSym0 (l :: TyFun [a6989586621679445041] (TyFun [a6989586621679445041] Bool -> Type)) Source #

Instances
SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a6989586621679445041] (TyFun [a6989586621679445041] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IsInfixOfSym0 :: TyFun [a6989586621679445041] (TyFun [a6989586621679445041] Bool -> Type) -> *) (l :: [a6989586621679445041]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IsInfixOfSym0 :: TyFun [a6989586621679445041] (TyFun [a6989586621679445041] Bool -> Type) -> *) (l :: [a6989586621679445041]) = IsInfixOfSym1 l

data IsInfixOfSym1 (l :: [a6989586621679445041]) (l :: TyFun [a6989586621679445041] Bool) Source #

Instances
SuppressUnusedWarnings (IsInfixOfSym1 :: [a6989586621679445041] -> TyFun [a6989586621679445041] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IsInfixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IsInfixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) = IsInfixOf l1 l2

type IsInfixOfSym2 (t :: [a6989586621679445041]) (t :: [a6989586621679445041]) = IsInfixOf t t Source #

data ElemSym0 (l :: TyFun a6989586621679445040 (TyFun [a6989586621679445040] Bool -> Type)) Source #

Instances
SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621679445040 (TyFun [a6989586621679445040] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ElemSym0 :: TyFun a6989586621679445040 (TyFun [a6989586621679445040] Bool -> Type) -> *) (l :: a6989586621679445040) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ElemSym0 :: TyFun a6989586621679445040 (TyFun [a6989586621679445040] Bool -> Type) -> *) (l :: a6989586621679445040) = ElemSym1 l

data ElemSym1 (l :: a6989586621679445040) (l :: TyFun [a6989586621679445040] Bool) Source #

Instances
SuppressUnusedWarnings (ElemSym1 :: a6989586621679445040 -> TyFun [a6989586621679445040] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ElemSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ElemSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) = Elem l1 l2

type ElemSym2 (t :: a6989586621679445040) (t :: [a6989586621679445040]) = Elem t t Source #

data NotElemSym0 (l :: TyFun a6989586621679445039 (TyFun [a6989586621679445039] Bool -> Type)) Source #

Instances
SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621679445039 (TyFun [a6989586621679445039] Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (NotElemSym0 :: TyFun a6989586621679445039 (TyFun [a6989586621679445039] Bool -> Type) -> *) (l :: a6989586621679445039) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (NotElemSym0 :: TyFun a6989586621679445039 (TyFun [a6989586621679445039] Bool -> Type) -> *) (l :: a6989586621679445039) = NotElemSym1 l

data NotElemSym1 (l :: a6989586621679445039) (l :: TyFun [a6989586621679445039] Bool) Source #

Instances
SuppressUnusedWarnings (NotElemSym1 :: a6989586621679445039 -> TyFun [a6989586621679445039] Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (NotElemSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (NotElemSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) = NotElem l1 l2

type NotElemSym2 (t :: a6989586621679445039) (t :: [a6989586621679445039]) = NotElem t t Source #

data ZipSym0 (l :: TyFun [a6989586621679445037] (TyFun [b6989586621679445038] [(a6989586621679445037, b6989586621679445038)] -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipSym0 :: TyFun [a6989586621679445037] (TyFun [b6989586621679445038] [(a6989586621679445037, b6989586621679445038)] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipSym0 :: TyFun [a6989586621679445037] (TyFun [b6989586621679445038] [(a6989586621679445037, b6989586621679445038)] -> Type) -> *) (l :: [a6989586621679445037]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipSym0 :: TyFun [a6989586621679445037] (TyFun [b6989586621679445038] [(a6989586621679445037, b6989586621679445038)] -> Type) -> *) (l :: [a6989586621679445037]) = (ZipSym1 l :: TyFun [b6989586621679445038] [(a6989586621679445037, b6989586621679445038)] -> *)

data ZipSym1 (l :: [a6989586621679445037]) (l :: TyFun [b6989586621679445038] [(a6989586621679445037, b6989586621679445038)]) Source #

Instances
SuppressUnusedWarnings (ZipSym1 :: [a6989586621679445037] -> TyFun [b6989586621679445038] [(a6989586621679445037, b6989586621679445038)] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipSym1 l1 :: TyFun [b] [(a, b)] -> *) (l2 :: [b]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipSym1 l1 :: TyFun [b] [(a, b)] -> *) (l2 :: [b]) = Zip l1 l2

type ZipSym2 (t :: [a6989586621679445037]) (t :: [b6989586621679445038]) = Zip t t Source #

data Zip3Sym0 (l :: TyFun [a6989586621679445034] (TyFun [b6989586621679445035] (TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a6989586621679445034] (TyFun [b6989586621679445035] (TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Zip3Sym0 :: TyFun [a6989586621679445034] (TyFun [b6989586621679445035] (TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> Type) -> Type) -> *) (l :: [a6989586621679445034]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Zip3Sym0 :: TyFun [a6989586621679445034] (TyFun [b6989586621679445035] (TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> Type) -> Type) -> *) (l :: [a6989586621679445034]) = (Zip3Sym1 l :: TyFun [b6989586621679445035] (TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> Type) -> *)

data Zip3Sym1 (l :: [a6989586621679445034]) (l :: TyFun [b6989586621679445035] (TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip3Sym1 :: [a6989586621679445034] -> TyFun [b6989586621679445035] (TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Zip3Sym1 l1 :: TyFun [b6989586621679445035] (TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> Type) -> *) (l2 :: [b6989586621679445035]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Zip3Sym1 l1 :: TyFun [b6989586621679445035] (TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> Type) -> *) (l2 :: [b6989586621679445035]) = (Zip3Sym2 l1 l2 :: TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> *)

data Zip3Sym2 (l :: [a6989586621679445034]) (l :: [b6989586621679445035]) (l :: TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)]) Source #

Instances
SuppressUnusedWarnings (Zip3Sym2 :: [a6989586621679445034] -> [b6989586621679445035] -> TyFun [c6989586621679445036] [(a6989586621679445034, b6989586621679445035, c6989586621679445036)] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Zip3Sym2 l1 l2 :: TyFun [c] [(a, b, c)] -> *) (l3 :: [c]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Zip3Sym2 l1 l2 :: TyFun [c] [(a, b, c)] -> *) (l3 :: [c]) = Zip3 l1 l2 l3

type Zip3Sym3 (t :: [a6989586621679445034]) (t :: [b6989586621679445035]) (t :: [c6989586621679445036]) = Zip3 t t t Source #

data ZipWithSym0 (l :: TyFun (TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) (TyFun [a6989586621679445031] (TyFun [b6989586621679445032] [c6989586621679445033] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWithSym0 :: TyFun (TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) (TyFun [a6989586621679445031] (TyFun [b6989586621679445032] [c6989586621679445033] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWithSym0 :: TyFun (TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) (TyFun [a6989586621679445031] (TyFun [b6989586621679445032] [c6989586621679445033] -> Type) -> Type) -> *) (l :: TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWithSym0 :: TyFun (TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) (TyFun [a6989586621679445031] (TyFun [b6989586621679445032] [c6989586621679445033] -> Type) -> Type) -> *) (l :: TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) = ZipWithSym1 l

data ZipWithSym1 (l :: TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) (l :: TyFun [a6989586621679445031] (TyFun [b6989586621679445032] [c6989586621679445033] -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWithSym1 :: (TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) -> TyFun [a6989586621679445031] (TyFun [b6989586621679445032] [c6989586621679445033] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWithSym1 l1 :: TyFun [a6989586621679445031] (TyFun [b6989586621679445032] [c6989586621679445033] -> Type) -> *) (l2 :: [a6989586621679445031]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWithSym1 l1 :: TyFun [a6989586621679445031] (TyFun [b6989586621679445032] [c6989586621679445033] -> Type) -> *) (l2 :: [a6989586621679445031]) = ZipWithSym2 l1 l2

data ZipWithSym2 (l :: TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) (l :: [a6989586621679445031]) (l :: TyFun [b6989586621679445032] [c6989586621679445033]) Source #

Instances
SuppressUnusedWarnings (ZipWithSym2 :: (TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) -> [a6989586621679445031] -> TyFun [b6989586621679445032] [c6989586621679445033] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWithSym2 l1 l2 :: TyFun [b] [c] -> *) (l3 :: [b]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWithSym2 l1 l2 :: TyFun [b] [c] -> *) (l3 :: [b]) = ZipWith l1 l2 l3

type ZipWithSym3 (t :: TyFun a6989586621679445031 (TyFun b6989586621679445032 c6989586621679445033 -> Type) -> Type) (t :: [a6989586621679445031]) (t :: [b6989586621679445032]) = ZipWith t t t Source #

data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (TyFun [a6989586621679445027] (TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (TyFun [a6989586621679445027] (TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWith3Sym0 :: TyFun (TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (TyFun [a6989586621679445027] (TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWith3Sym0 :: TyFun (TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (TyFun [a6989586621679445027] (TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) = ZipWith3Sym1 l

data ZipWith3Sym1 (l :: TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679445027] (TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith3Sym1 :: (TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) -> TyFun [a6989586621679445027] (TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWith3Sym1 l1 :: TyFun [a6989586621679445027] (TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> Type) -> *) (l2 :: [a6989586621679445027]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWith3Sym1 l1 :: TyFun [a6989586621679445027] (TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> Type) -> *) (l2 :: [a6989586621679445027]) = ZipWith3Sym2 l1 l2

data ZipWith3Sym2 (l :: TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (l :: [a6989586621679445027]) (l :: TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith3Sym2 :: (TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) -> [a6989586621679445027] -> TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWith3Sym2 l1 l2 :: TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> *) (l3 :: [b6989586621679445028]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWith3Sym2 l1 l2 :: TyFun [b6989586621679445028] (TyFun [c6989586621679445029] [d6989586621679445030] -> Type) -> *) (l3 :: [b6989586621679445028]) = ZipWith3Sym3 l1 l2 l3

data ZipWith3Sym3 (l :: TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (l :: [a6989586621679445027]) (l :: [b6989586621679445028]) (l :: TyFun [c6989586621679445029] [d6989586621679445030]) Source #

Instances
SuppressUnusedWarnings (ZipWith3Sym3 :: (TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) -> [a6989586621679445027] -> [b6989586621679445028] -> TyFun [c6989586621679445029] [d6989586621679445030] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWith3Sym3 l1 l2 l3 :: TyFun [c] [d] -> *) (l4 :: [c]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ZipWith3Sym3 l1 l2 l3 :: TyFun [c] [d] -> *) (l4 :: [c]) = ZipWith3 l1 l2 l3 l4

type ZipWith3Sym4 (t :: TyFun a6989586621679445027 (TyFun b6989586621679445028 (TyFun c6989586621679445029 d6989586621679445030 -> Type) -> Type) -> Type) (t :: [a6989586621679445027]) (t :: [b6989586621679445028]) (t :: [c6989586621679445029]) = ZipWith3 t t t t Source #

data UnzipSym0 (l :: TyFun [(a6989586621679445025, b6989586621679445026)] ([a6989586621679445025], [b6989586621679445026])) Source #

Instances
SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a6989586621679445025, b6989586621679445026)] ([a6989586621679445025], [b6989586621679445026]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> *) (l :: [(a, b)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> *) (l :: [(a, b)]) = Unzip l

type UnzipSym1 (t :: [(a6989586621679445025, b6989586621679445026)]) = Unzip t Source #

data Unzip3Sym0 (l :: TyFun [(a6989586621679445022, b6989586621679445023, c6989586621679445024)] ([a6989586621679445022], [b6989586621679445023], [c6989586621679445024])) Source #

Instances
SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a6989586621679445022, b6989586621679445023, c6989586621679445024)] ([a6989586621679445022], [b6989586621679445023], [c6989586621679445024]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> *) (l :: [(a, b, c)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> *) (l :: [(a, b, c)]) = Unzip3 l

type Unzip3Sym1 (t :: [(a6989586621679445022, b6989586621679445023, c6989586621679445024)]) = Unzip3 t Source #

data Unzip4Sym0 (l :: TyFun [(a6989586621679445018, b6989586621679445019, c6989586621679445020, d6989586621679445021)] ([a6989586621679445018], [b6989586621679445019], [c6989586621679445020], [d6989586621679445021])) Source #

Instances
SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a6989586621679445018, b6989586621679445019, c6989586621679445020, d6989586621679445021)] ([a6989586621679445018], [b6989586621679445019], [c6989586621679445020], [d6989586621679445021]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> *) (l :: [(a, b, c, d)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> *) (l :: [(a, b, c, d)]) = Unzip4 l

type Unzip4Sym1 (t :: [(a6989586621679445018, b6989586621679445019, c6989586621679445020, d6989586621679445021)]) = Unzip4 t Source #

data Unzip5Sym0 (l :: TyFun [(a6989586621679445013, b6989586621679445014, c6989586621679445015, d6989586621679445016, e6989586621679445017)] ([a6989586621679445013], [b6989586621679445014], [c6989586621679445015], [d6989586621679445016], [e6989586621679445017])) Source #

Instances
SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a6989586621679445013, b6989586621679445014, c6989586621679445015, d6989586621679445016, e6989586621679445017)] ([a6989586621679445013], [b6989586621679445014], [c6989586621679445015], [d6989586621679445016], [e6989586621679445017]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> *) (l :: [(a, b, c, d, e)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> *) (l :: [(a, b, c, d, e)]) = Unzip5 l

type Unzip5Sym1 (t :: [(a6989586621679445013, b6989586621679445014, c6989586621679445015, d6989586621679445016, e6989586621679445017)]) = Unzip5 t Source #

data Unzip6Sym0 (l :: TyFun [(a6989586621679445007, b6989586621679445008, c6989586621679445009, d6989586621679445010, e6989586621679445011, f6989586621679445012)] ([a6989586621679445007], [b6989586621679445008], [c6989586621679445009], [d6989586621679445010], [e6989586621679445011], [f6989586621679445012])) Source #

Instances
SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a6989586621679445007, b6989586621679445008, c6989586621679445009, d6989586621679445010, e6989586621679445011, f6989586621679445012)] ([a6989586621679445007], [b6989586621679445008], [c6989586621679445009], [d6989586621679445010], [e6989586621679445011], [f6989586621679445012]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> *) (l :: [(a, b, c, d, e, f)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> *) (l :: [(a, b, c, d, e, f)]) = Unzip6 l

type Unzip6Sym1 (t :: [(a6989586621679445007, b6989586621679445008, c6989586621679445009, d6989586621679445010, e6989586621679445011, f6989586621679445012)]) = Unzip6 t Source #

data Unzip7Sym0 (l :: TyFun [(a6989586621679445000, b6989586621679445001, c6989586621679445002, d6989586621679445003, e6989586621679445004, f6989586621679445005, g6989586621679445006)] ([a6989586621679445000], [b6989586621679445001], [c6989586621679445002], [d6989586621679445003], [e6989586621679445004], [f6989586621679445005], [g6989586621679445006])) Source #

Instances
SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a6989586621679445000, b6989586621679445001, c6989586621679445002, d6989586621679445003, e6989586621679445004, f6989586621679445005, g6989586621679445006)] ([a6989586621679445000], [b6989586621679445001], [c6989586621679445002], [d6989586621679445003], [e6989586621679445004], [f6989586621679445005], [g6989586621679445006]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> *) (l :: [(a, b, c, d, e, f, g)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> *) (l :: [(a, b, c, d, e, f, g)]) = Unzip7 l

type Unzip7Sym1 (t :: [(a6989586621679445000, b6989586621679445001, c6989586621679445002, d6989586621679445003, e6989586621679445004, f6989586621679445005, g6989586621679445006)]) = Unzip7 t Source #

data DeleteSym0 (l :: TyFun a6989586621679444999 (TyFun [a6989586621679444999] [a6989586621679444999] -> Type)) Source #

Instances
SuppressUnusedWarnings (DeleteSym0 :: TyFun a6989586621679444999 (TyFun [a6989586621679444999] [a6989586621679444999] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteSym0 :: TyFun a6989586621679444999 (TyFun [a6989586621679444999] [a6989586621679444999] -> Type) -> *) (l :: a6989586621679444999) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteSym0 :: TyFun a6989586621679444999 (TyFun [a6989586621679444999] [a6989586621679444999] -> Type) -> *) (l :: a6989586621679444999) = DeleteSym1 l

data DeleteSym1 (l :: a6989586621679444999) (l :: TyFun [a6989586621679444999] [a6989586621679444999]) Source #

Instances
SuppressUnusedWarnings (DeleteSym1 :: a6989586621679444999 -> TyFun [a6989586621679444999] [a6989586621679444999] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = Delete l1 l2

type DeleteSym2 (t :: a6989586621679444999) (t :: [a6989586621679444999]) = Delete t t Source #

data (\\@#@$) (l :: TyFun [a6989586621679444998] (TyFun [a6989586621679444998] [a6989586621679444998] -> Type)) Source #

Instances
SuppressUnusedWarnings ((\\@#@$) :: TyFun [a6989586621679444998] (TyFun [a6989586621679444998] [a6989586621679444998] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply ((\\@#@$) :: TyFun [a6989586621679444998] (TyFun [a6989586621679444998] [a6989586621679444998] -> Type) -> *) (l :: [a6989586621679444998]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply ((\\@#@$) :: TyFun [a6989586621679444998] (TyFun [a6989586621679444998] [a6989586621679444998] -> Type) -> *) (l :: [a6989586621679444998]) = (\\@#@$$) l

data (l :: [a6989586621679444998]) \\@#@$$ (l :: TyFun [a6989586621679444998] [a6989586621679444998]) Source #

Instances
SuppressUnusedWarnings ((\\@#@$$) :: [a6989586621679444998] -> TyFun [a6989586621679444998] [a6989586621679444998] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply ((\\@#@$$) l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply ((\\@#@$$) l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = l1 \\ l2

type (\\@#@$$$) (t :: [a6989586621679444998]) (t :: [a6989586621679444998]) = (\\) t t Source #

data IntersectSym0 (l :: TyFun [a6989586621679444985] (TyFun [a6989586621679444985] [a6989586621679444985] -> Type)) Source #

Instances
SuppressUnusedWarnings (IntersectSym0 :: TyFun [a6989586621679444985] (TyFun [a6989586621679444985] [a6989586621679444985] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersectSym0 :: TyFun [a6989586621679444985] (TyFun [a6989586621679444985] [a6989586621679444985] -> Type) -> *) (l :: [a6989586621679444985]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersectSym0 :: TyFun [a6989586621679444985] (TyFun [a6989586621679444985] [a6989586621679444985] -> Type) -> *) (l :: [a6989586621679444985]) = IntersectSym1 l

data IntersectSym1 (l :: [a6989586621679444985]) (l :: TyFun [a6989586621679444985] [a6989586621679444985]) Source #

Instances
SuppressUnusedWarnings (IntersectSym1 :: [a6989586621679444985] -> TyFun [a6989586621679444985] [a6989586621679444985] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersectSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersectSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = Intersect l1 l2

type IntersectSym2 (t :: [a6989586621679444985]) (t :: [a6989586621679444985]) = Intersect t t Source #

data InsertSym0 (l :: TyFun a6989586621679444972 (TyFun [a6989586621679444972] [a6989586621679444972] -> Type)) Source #

Instances
SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621679444972 (TyFun [a6989586621679444972] [a6989586621679444972] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (InsertSym0 :: TyFun a6989586621679444972 (TyFun [a6989586621679444972] [a6989586621679444972] -> Type) -> *) (l :: a6989586621679444972) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (InsertSym0 :: TyFun a6989586621679444972 (TyFun [a6989586621679444972] [a6989586621679444972] -> Type) -> *) (l :: a6989586621679444972) = InsertSym1 l

data InsertSym1 (l :: a6989586621679444972) (l :: TyFun [a6989586621679444972] [a6989586621679444972]) Source #

Instances
SuppressUnusedWarnings (InsertSym1 :: a6989586621679444972 -> TyFun [a6989586621679444972] [a6989586621679444972] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (InsertSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (InsertSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = Insert l1 l2

type InsertSym2 (t :: a6989586621679444972) (t :: [a6989586621679444972]) = Insert t t Source #

data SortSym0 (l :: TyFun [a6989586621679444971] [a6989586621679444971]) Source #

Instances
SuppressUnusedWarnings (SortSym0 :: TyFun [a6989586621679444971] [a6989586621679444971] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SortSym0 :: TyFun [a] [a] -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SortSym0 :: TyFun [a] [a] -> *) (l :: [a]) = Sort l

type SortSym1 (t :: [a6989586621679444971]) = Sort t Source #

data DeleteBySym0 (l :: TyFun (TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) (TyFun a6989586621679444997 (TyFun [a6989586621679444997] [a6989586621679444997] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (DeleteBySym0 :: TyFun (TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) (TyFun a6989586621679444997 (TyFun [a6989586621679444997] [a6989586621679444997] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteBySym0 :: TyFun (TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) (TyFun a6989586621679444997 (TyFun [a6989586621679444997] [a6989586621679444997] -> Type) -> Type) -> *) (l :: TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteBySym0 :: TyFun (TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) (TyFun a6989586621679444997 (TyFun [a6989586621679444997] [a6989586621679444997] -> Type) -> Type) -> *) (l :: TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) = DeleteBySym1 l

data DeleteBySym1 (l :: TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) (l :: TyFun a6989586621679444997 (TyFun [a6989586621679444997] [a6989586621679444997] -> Type)) Source #

Instances
SuppressUnusedWarnings (DeleteBySym1 :: (TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) -> TyFun a6989586621679444997 (TyFun [a6989586621679444997] [a6989586621679444997] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteBySym1 l1 :: TyFun a6989586621679444997 (TyFun [a6989586621679444997] [a6989586621679444997] -> Type) -> *) (l2 :: a6989586621679444997) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteBySym1 l1 :: TyFun a6989586621679444997 (TyFun [a6989586621679444997] [a6989586621679444997] -> Type) -> *) (l2 :: a6989586621679444997) = DeleteBySym2 l1 l2

data DeleteBySym2 (l :: TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) (l :: a6989586621679444997) (l :: TyFun [a6989586621679444997] [a6989586621679444997]) Source #

Instances
SuppressUnusedWarnings (DeleteBySym2 :: (TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) -> a6989586621679444997 -> TyFun [a6989586621679444997] [a6989586621679444997] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) = DeleteBy l1 l2 l3

type DeleteBySym3 (t :: TyFun a6989586621679444997 (TyFun a6989586621679444997 Bool -> Type) -> Type) (t :: a6989586621679444997) (t :: [a6989586621679444997]) = DeleteBy t t t Source #

data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) (TyFun [a6989586621679444996] (TyFun [a6989586621679444996] [a6989586621679444996] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) (TyFun [a6989586621679444996] (TyFun [a6989586621679444996] [a6989586621679444996] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) (TyFun [a6989586621679444996] (TyFun [a6989586621679444996] [a6989586621679444996] -> Type) -> Type) -> *) (l :: TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) (TyFun [a6989586621679444996] (TyFun [a6989586621679444996] [a6989586621679444996] -> Type) -> Type) -> *) (l :: TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) = DeleteFirstsBySym1 l

data DeleteFirstsBySym1 (l :: TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) (l :: TyFun [a6989586621679444996] (TyFun [a6989586621679444996] [a6989586621679444996] -> Type)) Source #

Instances
SuppressUnusedWarnings (DeleteFirstsBySym1 :: (TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) -> TyFun [a6989586621679444996] (TyFun [a6989586621679444996] [a6989586621679444996] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteFirstsBySym1 l1 :: TyFun [a6989586621679444996] (TyFun [a6989586621679444996] [a6989586621679444996] -> Type) -> *) (l2 :: [a6989586621679444996]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteFirstsBySym1 l1 :: TyFun [a6989586621679444996] (TyFun [a6989586621679444996] [a6989586621679444996] -> Type) -> *) (l2 :: [a6989586621679444996]) = DeleteFirstsBySym2 l1 l2

data DeleteFirstsBySym2 (l :: TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) (l :: [a6989586621679444996]) (l :: TyFun [a6989586621679444996] [a6989586621679444996]) Source #

Instances
SuppressUnusedWarnings (DeleteFirstsBySym2 :: (TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) -> [a6989586621679444996] -> TyFun [a6989586621679444996] [a6989586621679444996] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteFirstsBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DeleteFirstsBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) = DeleteFirstsBy l1 l2 l3

type DeleteFirstsBySym3 (t :: TyFun a6989586621679444996 (TyFun a6989586621679444996 Bool -> Type) -> Type) (t :: [a6989586621679444996]) (t :: [a6989586621679444996]) = DeleteFirstsBy t t t Source #

data IntersectBySym0 (l :: TyFun (TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) (TyFun [a6989586621679444984] (TyFun [a6989586621679444984] [a6989586621679444984] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (IntersectBySym0 :: TyFun (TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) (TyFun [a6989586621679444984] (TyFun [a6989586621679444984] [a6989586621679444984] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersectBySym0 :: TyFun (TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) (TyFun [a6989586621679444984] (TyFun [a6989586621679444984] [a6989586621679444984] -> Type) -> Type) -> *) (l :: TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersectBySym0 :: TyFun (TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) (TyFun [a6989586621679444984] (TyFun [a6989586621679444984] [a6989586621679444984] -> Type) -> Type) -> *) (l :: TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) = IntersectBySym1 l

data IntersectBySym1 (l :: TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) (l :: TyFun [a6989586621679444984] (TyFun [a6989586621679444984] [a6989586621679444984] -> Type)) Source #

Instances
SuppressUnusedWarnings (IntersectBySym1 :: (TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) -> TyFun [a6989586621679444984] (TyFun [a6989586621679444984] [a6989586621679444984] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersectBySym1 l1 :: TyFun [a6989586621679444984] (TyFun [a6989586621679444984] [a6989586621679444984] -> Type) -> *) (l2 :: [a6989586621679444984]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersectBySym1 l1 :: TyFun [a6989586621679444984] (TyFun [a6989586621679444984] [a6989586621679444984] -> Type) -> *) (l2 :: [a6989586621679444984]) = IntersectBySym2 l1 l2

data IntersectBySym2 (l :: TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) (l :: [a6989586621679444984]) (l :: TyFun [a6989586621679444984] [a6989586621679444984]) Source #

Instances
SuppressUnusedWarnings (IntersectBySym2 :: (TyFun a6989586621679444984 (TyFun a6989586621679444984 Bool -> Type) -> Type) -> [a6989586621679444984] -> TyFun [a6989586621679444984] [a6989586621679444984] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersectBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (IntersectBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) = IntersectBy l1 l2 l3

data SortBySym0 (l :: TyFun (TyFun a6989586621679444995 (TyFun a6989586621679444995 Ordering -> Type) -> Type) (TyFun [a6989586621679444995] [a6989586621679444995] -> Type)) Source #

Instances
SuppressUnusedWarnings (SortBySym0 :: TyFun (TyFun a6989586621679444995 (TyFun a6989586621679444995 Ordering -> Type) -> Type) (TyFun [a6989586621679444995] [a6989586621679444995] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SortBySym0 :: TyFun (TyFun a6989586621679444995 (TyFun a6989586621679444995 Ordering -> Type) -> Type) (TyFun [a6989586621679444995] [a6989586621679444995] -> Type) -> *) (l :: TyFun a6989586621679444995 (TyFun a6989586621679444995 Ordering -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SortBySym0 :: TyFun (TyFun a6989586621679444995 (TyFun a6989586621679444995 Ordering -> Type) -> Type) (TyFun [a6989586621679444995] [a6989586621679444995] -> Type) -> *) (l :: TyFun a6989586621679444995 (TyFun a6989586621679444995 Ordering -> Type) -> Type) = SortBySym1 l

data SortBySym1 (l :: TyFun a6989586621679444995 (TyFun a6989586621679444995 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679444995] [a6989586621679444995]) Source #

Instances
SuppressUnusedWarnings (SortBySym1 :: (TyFun a6989586621679444995 (TyFun a6989586621679444995 Ordering -> Type) -> Type) -> TyFun [a6989586621679444995] [a6989586621679444995] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SortBySym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SortBySym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = SortBy l1 l2

type SortBySym2 (t :: TyFun a6989586621679444995 (TyFun a6989586621679444995 Ordering -> Type) -> Type) (t :: [a6989586621679444995]) = SortBy t t Source #

data InsertBySym0 (l :: TyFun (TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) (TyFun a6989586621679444994 (TyFun [a6989586621679444994] [a6989586621679444994] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (InsertBySym0 :: TyFun (TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) (TyFun a6989586621679444994 (TyFun [a6989586621679444994] [a6989586621679444994] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (InsertBySym0 :: TyFun (TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) (TyFun a6989586621679444994 (TyFun [a6989586621679444994] [a6989586621679444994] -> Type) -> Type) -> *) (l :: TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (InsertBySym0 :: TyFun (TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) (TyFun a6989586621679444994 (TyFun [a6989586621679444994] [a6989586621679444994] -> Type) -> Type) -> *) (l :: TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) = InsertBySym1 l

data InsertBySym1 (l :: TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) (l :: TyFun a6989586621679444994 (TyFun [a6989586621679444994] [a6989586621679444994] -> Type)) Source #

Instances
SuppressUnusedWarnings (InsertBySym1 :: (TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) -> TyFun a6989586621679444994 (TyFun [a6989586621679444994] [a6989586621679444994] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (InsertBySym1 l1 :: TyFun a6989586621679444994 (TyFun [a6989586621679444994] [a6989586621679444994] -> Type) -> *) (l2 :: a6989586621679444994) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (InsertBySym1 l1 :: TyFun a6989586621679444994 (TyFun [a6989586621679444994] [a6989586621679444994] -> Type) -> *) (l2 :: a6989586621679444994) = InsertBySym2 l1 l2

data InsertBySym2 (l :: TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) (l :: a6989586621679444994) (l :: TyFun [a6989586621679444994] [a6989586621679444994]) Source #

Instances
SuppressUnusedWarnings (InsertBySym2 :: (TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) -> a6989586621679444994 -> TyFun [a6989586621679444994] [a6989586621679444994] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (InsertBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (InsertBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) = InsertBy l1 l2 l3

type InsertBySym3 (t :: TyFun a6989586621679444994 (TyFun a6989586621679444994 Ordering -> Type) -> Type) (t :: a6989586621679444994) (t :: [a6989586621679444994]) = InsertBy t t t Source #

data MaximumBySym0 (l :: TyFun (TyFun a6989586621679444993 (TyFun a6989586621679444993 Ordering -> Type) -> Type) (TyFun [a6989586621679444993] a6989586621679444993 -> Type)) Source #

Instances
SuppressUnusedWarnings (MaximumBySym0 :: TyFun (TyFun a6989586621679444993 (TyFun a6989586621679444993 Ordering -> Type) -> Type) (TyFun [a6989586621679444993] a6989586621679444993 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MaximumBySym0 :: TyFun (TyFun a6989586621679444993 (TyFun a6989586621679444993 Ordering -> Type) -> Type) (TyFun [a6989586621679444993] a6989586621679444993 -> Type) -> *) (l :: TyFun a6989586621679444993 (TyFun a6989586621679444993 Ordering -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MaximumBySym0 :: TyFun (TyFun a6989586621679444993 (TyFun a6989586621679444993 Ordering -> Type) -> Type) (TyFun [a6989586621679444993] a6989586621679444993 -> Type) -> *) (l :: TyFun a6989586621679444993 (TyFun a6989586621679444993 Ordering -> Type) -> Type) = MaximumBySym1 l

data MaximumBySym1 (l :: TyFun a6989586621679444993 (TyFun a6989586621679444993 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679444993] a6989586621679444993) Source #

Instances
SuppressUnusedWarnings (MaximumBySym1 :: (TyFun a6989586621679444993 (TyFun a6989586621679444993 Ordering -> Type) -> Type) -> TyFun [a6989586621679444993] a6989586621679444993 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MaximumBySym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MaximumBySym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) = MaximumBy l1 l2

type MaximumBySym2 (t :: TyFun a6989586621679444993 (TyFun a6989586621679444993 Ordering -> Type) -> Type) (t :: [a6989586621679444993]) = MaximumBy t t Source #

data MinimumBySym0 (l :: TyFun (TyFun a6989586621679444992 (TyFun a6989586621679444992 Ordering -> Type) -> Type) (TyFun [a6989586621679444992] a6989586621679444992 -> Type)) Source #

Instances
SuppressUnusedWarnings (MinimumBySym0 :: TyFun (TyFun a6989586621679444992 (TyFun a6989586621679444992 Ordering -> Type) -> Type) (TyFun [a6989586621679444992] a6989586621679444992 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MinimumBySym0 :: TyFun (TyFun a6989586621679444992 (TyFun a6989586621679444992 Ordering -> Type) -> Type) (TyFun [a6989586621679444992] a6989586621679444992 -> Type) -> *) (l :: TyFun a6989586621679444992 (TyFun a6989586621679444992 Ordering -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MinimumBySym0 :: TyFun (TyFun a6989586621679444992 (TyFun a6989586621679444992 Ordering -> Type) -> Type) (TyFun [a6989586621679444992] a6989586621679444992 -> Type) -> *) (l :: TyFun a6989586621679444992 (TyFun a6989586621679444992 Ordering -> Type) -> Type) = MinimumBySym1 l

data MinimumBySym1 (l :: TyFun a6989586621679444992 (TyFun a6989586621679444992 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679444992] a6989586621679444992) Source #

Instances
SuppressUnusedWarnings (MinimumBySym1 :: (TyFun a6989586621679444992 (TyFun a6989586621679444992 Ordering -> Type) -> Type) -> TyFun [a6989586621679444992] a6989586621679444992 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MinimumBySym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MinimumBySym1 l1 :: TyFun [a] a -> *) (l2 :: [a]) = MinimumBy l1 l2

type MinimumBySym2 (t :: TyFun a6989586621679444992 (TyFun a6989586621679444992 Ordering -> Type) -> Type) (t :: [a6989586621679444992]) = MinimumBy t t Source #

data LengthSym0 (l :: TyFun [a6989586621679444963] Nat) Source #

Instances
SuppressUnusedWarnings (LengthSym0 :: TyFun [a6989586621679444963] Nat -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (LengthSym0 :: TyFun [a] Nat -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (LengthSym0 :: TyFun [a] Nat -> *) (l :: [a]) = Length l

type LengthSym1 (t :: [a6989586621679444963]) = Length t Source #

data SumSym0 (l :: TyFun [a6989586621679444965] a6989586621679444965) Source #

Instances
SuppressUnusedWarnings (SumSym0 :: TyFun [a6989586621679444965] a6989586621679444965 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SumSym0 :: TyFun [a] a -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SumSym0 :: TyFun [a] a -> *) (l :: [a]) = Sum l

type SumSym1 (t :: [a6989586621679444965]) = Sum t Source #

data ProductSym0 (l :: TyFun [a6989586621679444964] a6989586621679444964) Source #

Instances
SuppressUnusedWarnings (ProductSym0 :: TyFun [a6989586621679444964] a6989586621679444964 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ProductSym0 :: TyFun [a] a -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ProductSym0 :: TyFun [a] a -> *) (l :: [a]) = Product l

type ProductSym1 (t :: [a6989586621679444964]) = Product t Source #

data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679444962 [a6989586621679444962] -> Type)) Source #

Instances
SuppressUnusedWarnings (ReplicateSym0 :: TyFun Nat (TyFun a6989586621679444962 [a6989586621679444962] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ReplicateSym0 :: TyFun Nat (TyFun a6989586621679444962 [a6989586621679444962] -> Type) -> *) (l :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ReplicateSym0 :: TyFun Nat (TyFun a6989586621679444962 [a6989586621679444962] -> Type) -> *) (l :: Nat) = (ReplicateSym1 l :: TyFun a6989586621679444962 [a6989586621679444962] -> *)

data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679444962 [a6989586621679444962]) Source #

Instances
SuppressUnusedWarnings (ReplicateSym1 :: Nat -> TyFun a6989586621679444962 [a6989586621679444962] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ReplicateSym1 l1 :: TyFun a [a] -> *) (l2 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ReplicateSym1 l1 :: TyFun a [a] -> *) (l2 :: a) = Replicate l1 l2

type ReplicateSym2 (t :: Nat) (t :: a6989586621679444962) = Replicate t t Source #

data TransposeSym0 (l :: TyFun [[a6989586621679444961]] [[a6989586621679444961]]) Source #

Instances
SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a6989586621679444961]] [[a6989586621679444961]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

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

Defined in Data.Singletons.Prelude.List

type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> *) (l :: [[a]]) = Transpose l

type TransposeSym1 (t :: [[a6989586621679444961]]) = Transpose t Source #

data TakeSym0 (l :: TyFun Nat (TyFun [a6989586621679444978] [a6989586621679444978] -> Type)) Source #

Instances
SuppressUnusedWarnings (TakeSym0 :: TyFun Nat (TyFun [a6989586621679444978] [a6989586621679444978] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (TakeSym0 :: TyFun Nat (TyFun [a6989586621679444978] [a6989586621679444978] -> Type) -> *) (l :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (TakeSym0 :: TyFun Nat (TyFun [a6989586621679444978] [a6989586621679444978] -> Type) -> *) (l :: Nat) = (TakeSym1 l :: TyFun [a6989586621679444978] [a6989586621679444978] -> *)

data TakeSym1 (l :: Nat) (l :: TyFun [a6989586621679444978] [a6989586621679444978]) Source #

Instances
SuppressUnusedWarnings (TakeSym1 :: Nat -> TyFun [a6989586621679444978] [a6989586621679444978] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (TakeSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (TakeSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = Take l1 l2

type TakeSym2 (t :: Nat) (t :: [a6989586621679444978]) = Take t t Source #

data DropSym0 (l :: TyFun Nat (TyFun [a6989586621679444977] [a6989586621679444977] -> Type)) Source #

Instances
SuppressUnusedWarnings (DropSym0 :: TyFun Nat (TyFun [a6989586621679444977] [a6989586621679444977] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DropSym0 :: TyFun Nat (TyFun [a6989586621679444977] [a6989586621679444977] -> Type) -> *) (l :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DropSym0 :: TyFun Nat (TyFun [a6989586621679444977] [a6989586621679444977] -> Type) -> *) (l :: Nat) = (DropSym1 l :: TyFun [a6989586621679444977] [a6989586621679444977] -> *)

data DropSym1 (l :: Nat) (l :: TyFun [a6989586621679444977] [a6989586621679444977]) Source #

Instances
SuppressUnusedWarnings (DropSym1 :: Nat -> TyFun [a6989586621679444977] [a6989586621679444977] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DropSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DropSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = Drop l1 l2

type DropSym2 (t :: Nat) (t :: [a6989586621679444977]) = Drop t t Source #

data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679444976] ([a6989586621679444976], [a6989586621679444976]) -> Type)) Source #

Instances
SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat (TyFun [a6989586621679444976] ([a6989586621679444976], [a6989586621679444976]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SplitAtSym0 :: TyFun Nat (TyFun [a6989586621679444976] ([a6989586621679444976], [a6989586621679444976]) -> Type) -> *) (l :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SplitAtSym0 :: TyFun Nat (TyFun [a6989586621679444976] ([a6989586621679444976], [a6989586621679444976]) -> Type) -> *) (l :: Nat) = (SplitAtSym1 l :: TyFun [a6989586621679444976] ([a6989586621679444976], [a6989586621679444976]) -> *)

data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679444976] ([a6989586621679444976], [a6989586621679444976])) Source #

Instances
SuppressUnusedWarnings (SplitAtSym1 :: Nat -> TyFun [a6989586621679444976] ([a6989586621679444976], [a6989586621679444976]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SplitAtSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SplitAtSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) = SplitAt l1 l2

type SplitAtSym2 (t :: Nat) (t :: [a6989586621679444976]) = SplitAt t t Source #

data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679444983 Bool -> Type) (TyFun [a6989586621679444983] [a6989586621679444983] -> Type)) Source #

Instances
SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (TyFun a6989586621679444983 Bool -> Type) (TyFun [a6989586621679444983] [a6989586621679444983] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (TakeWhileSym0 :: TyFun (TyFun a6989586621679444983 Bool -> Type) (TyFun [a6989586621679444983] [a6989586621679444983] -> Type) -> *) (l :: TyFun a6989586621679444983 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (TakeWhileSym0 :: TyFun (TyFun a6989586621679444983 Bool -> Type) (TyFun [a6989586621679444983] [a6989586621679444983] -> Type) -> *) (l :: TyFun a6989586621679444983 Bool -> Type) = TakeWhileSym1 l

data TakeWhileSym1 (l :: TyFun a6989586621679444983 Bool -> Type) (l :: TyFun [a6989586621679444983] [a6989586621679444983]) Source #

Instances
SuppressUnusedWarnings (TakeWhileSym1 :: (TyFun a6989586621679444983 Bool -> Type) -> TyFun [a6989586621679444983] [a6989586621679444983] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (TakeWhileSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (TakeWhileSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = TakeWhile l1 l2

type TakeWhileSym2 (t :: TyFun a6989586621679444983 Bool -> Type) (t :: [a6989586621679444983]) = TakeWhile t t Source #

data DropWhileSym0 (l :: TyFun (TyFun a6989586621679444982 Bool -> Type) (TyFun [a6989586621679444982] [a6989586621679444982] -> Type)) Source #

Instances
SuppressUnusedWarnings (DropWhileSym0 :: TyFun (TyFun a6989586621679444982 Bool -> Type) (TyFun [a6989586621679444982] [a6989586621679444982] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DropWhileSym0 :: TyFun (TyFun a6989586621679444982 Bool -> Type) (TyFun [a6989586621679444982] [a6989586621679444982] -> Type) -> *) (l :: TyFun a6989586621679444982 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DropWhileSym0 :: TyFun (TyFun a6989586621679444982 Bool -> Type) (TyFun [a6989586621679444982] [a6989586621679444982] -> Type) -> *) (l :: TyFun a6989586621679444982 Bool -> Type) = DropWhileSym1 l

data DropWhileSym1 (l :: TyFun a6989586621679444982 Bool -> Type) (l :: TyFun [a6989586621679444982] [a6989586621679444982]) Source #

Instances
SuppressUnusedWarnings (DropWhileSym1 :: (TyFun a6989586621679444982 Bool -> Type) -> TyFun [a6989586621679444982] [a6989586621679444982] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DropWhileSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DropWhileSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = DropWhile l1 l2

type DropWhileSym2 (t :: TyFun a6989586621679444982 Bool -> Type) (t :: [a6989586621679444982]) = DropWhile t t Source #

data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679444981 Bool -> Type) (TyFun [a6989586621679444981] [a6989586621679444981] -> Type)) Source #

Instances
SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (TyFun a6989586621679444981 Bool -> Type) (TyFun [a6989586621679444981] [a6989586621679444981] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DropWhileEndSym0 :: TyFun (TyFun a6989586621679444981 Bool -> Type) (TyFun [a6989586621679444981] [a6989586621679444981] -> Type) -> *) (l :: TyFun a6989586621679444981 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DropWhileEndSym0 :: TyFun (TyFun a6989586621679444981 Bool -> Type) (TyFun [a6989586621679444981] [a6989586621679444981] -> Type) -> *) (l :: TyFun a6989586621679444981 Bool -> Type) = DropWhileEndSym1 l

data DropWhileEndSym1 (l :: TyFun a6989586621679444981 Bool -> Type) (l :: TyFun [a6989586621679444981] [a6989586621679444981]) Source #

Instances
SuppressUnusedWarnings (DropWhileEndSym1 :: (TyFun a6989586621679444981 Bool -> Type) -> TyFun [a6989586621679444981] [a6989586621679444981] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DropWhileEndSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (DropWhileEndSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = DropWhileEnd l1 l2

type DropWhileEndSym2 (t :: TyFun a6989586621679444981 Bool -> Type) (t :: [a6989586621679444981]) = DropWhileEnd t t Source #

data SpanSym0 (l :: TyFun (TyFun a6989586621679444980 Bool -> Type) (TyFun [a6989586621679444980] ([a6989586621679444980], [a6989586621679444980]) -> Type)) Source #

Instances
SuppressUnusedWarnings (SpanSym0 :: TyFun (TyFun a6989586621679444980 Bool -> Type) (TyFun [a6989586621679444980] ([a6989586621679444980], [a6989586621679444980]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SpanSym0 :: TyFun (TyFun a6989586621679444980 Bool -> Type) (TyFun [a6989586621679444980] ([a6989586621679444980], [a6989586621679444980]) -> Type) -> *) (l :: TyFun a6989586621679444980 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SpanSym0 :: TyFun (TyFun a6989586621679444980 Bool -> Type) (TyFun [a6989586621679444980] ([a6989586621679444980], [a6989586621679444980]) -> Type) -> *) (l :: TyFun a6989586621679444980 Bool -> Type) = SpanSym1 l

data SpanSym1 (l :: TyFun a6989586621679444980 Bool -> Type) (l :: TyFun [a6989586621679444980] ([a6989586621679444980], [a6989586621679444980])) Source #

Instances
SuppressUnusedWarnings (SpanSym1 :: (TyFun a6989586621679444980 Bool -> Type) -> TyFun [a6989586621679444980] ([a6989586621679444980], [a6989586621679444980]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SpanSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (SpanSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) = Span l1 l2

type SpanSym2 (t :: TyFun a6989586621679444980 Bool -> Type) (t :: [a6989586621679444980]) = Span t t Source #

data BreakSym0 (l :: TyFun (TyFun a6989586621679444979 Bool -> Type) (TyFun [a6989586621679444979] ([a6989586621679444979], [a6989586621679444979]) -> Type)) Source #

Instances
SuppressUnusedWarnings (BreakSym0 :: TyFun (TyFun a6989586621679444979 Bool -> Type) (TyFun [a6989586621679444979] ([a6989586621679444979], [a6989586621679444979]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (BreakSym0 :: TyFun (TyFun a6989586621679444979 Bool -> Type) (TyFun [a6989586621679444979] ([a6989586621679444979], [a6989586621679444979]) -> Type) -> *) (l :: TyFun a6989586621679444979 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (BreakSym0 :: TyFun (TyFun a6989586621679444979 Bool -> Type) (TyFun [a6989586621679444979] ([a6989586621679444979], [a6989586621679444979]) -> Type) -> *) (l :: TyFun a6989586621679444979 Bool -> Type) = BreakSym1 l

data BreakSym1 (l :: TyFun a6989586621679444979 Bool -> Type) (l :: TyFun [a6989586621679444979] ([a6989586621679444979], [a6989586621679444979])) Source #

Instances
SuppressUnusedWarnings (BreakSym1 :: (TyFun a6989586621679444979 Bool -> Type) -> TyFun [a6989586621679444979] ([a6989586621679444979], [a6989586621679444979]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (BreakSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (BreakSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) = Break l1 l2

type BreakSym2 (t :: TyFun a6989586621679444979 Bool -> Type) (t :: [a6989586621679444979]) = Break t t Source #

data StripPrefixSym0 (l :: TyFun [a6989586621679924863] (TyFun [a6989586621679924863] (Maybe [a6989586621679924863]) -> Type)) Source #

Instances
SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a6989586621679924863] (TyFun [a6989586621679924863] (Maybe [a6989586621679924863]) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (StripPrefixSym0 :: TyFun [a6989586621679924863] (TyFun [a6989586621679924863] (Maybe [a6989586621679924863]) -> Type) -> *) (l :: [a6989586621679924863]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (StripPrefixSym0 :: TyFun [a6989586621679924863] (TyFun [a6989586621679924863] (Maybe [a6989586621679924863]) -> Type) -> *) (l :: [a6989586621679924863]) = StripPrefixSym1 l

data StripPrefixSym1 (l :: [a6989586621679924863]) (l :: TyFun [a6989586621679924863] (Maybe [a6989586621679924863])) Source #

Instances
SuppressUnusedWarnings (StripPrefixSym1 :: [a6989586621679924863] -> TyFun [a6989586621679924863] (Maybe [a6989586621679924863]) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (StripPrefixSym1 l1 :: TyFun [a] (Maybe [a]) -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (StripPrefixSym1 l1 :: TyFun [a] (Maybe [a]) -> *) (l2 :: [a]) = StripPrefix l1 l2

type StripPrefixSym2 (t :: [a6989586621679924863]) (t :: [a6989586621679924863]) = StripPrefix t t Source #

data MaximumSym0 (l :: TyFun [a6989586621679444974] a6989586621679444974) Source #

Instances
SuppressUnusedWarnings (MaximumSym0 :: TyFun [a6989586621679444974] a6989586621679444974 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MaximumSym0 :: TyFun [a] a -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MaximumSym0 :: TyFun [a] a -> *) (l :: [a]) = Maximum l

type MaximumSym1 (t :: [a6989586621679444974]) = Maximum t Source #

data MinimumSym0 (l :: TyFun [a6989586621679444973] a6989586621679444973) Source #

Instances
SuppressUnusedWarnings (MinimumSym0 :: TyFun [a6989586621679444973] a6989586621679444973 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MinimumSym0 :: TyFun [a] a -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (MinimumSym0 :: TyFun [a] a -> *) (l :: [a]) = Minimum l

type MinimumSym1 (t :: [a6989586621679444973]) = Minimum t Source #

data GroupSym0 (l :: TyFun [a6989586621679444975] [[a6989586621679444975]]) Source #

Instances
SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621679444975] [[a6989586621679444975]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (GroupSym0 :: TyFun [a] [[a]] -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (GroupSym0 :: TyFun [a] [[a]] -> *) (l :: [a]) = Group l

type GroupSym1 (t :: [a6989586621679444975]) = Group t Source #

data GroupBySym0 (l :: TyFun (TyFun a6989586621679444970 (TyFun a6989586621679444970 Bool -> Type) -> Type) (TyFun [a6989586621679444970] [[a6989586621679444970]] -> Type)) Source #

Instances
SuppressUnusedWarnings (GroupBySym0 :: TyFun (TyFun a6989586621679444970 (TyFun a6989586621679444970 Bool -> Type) -> Type) (TyFun [a6989586621679444970] [[a6989586621679444970]] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (GroupBySym0 :: TyFun (TyFun a6989586621679444970 (TyFun a6989586621679444970 Bool -> Type) -> Type) (TyFun [a6989586621679444970] [[a6989586621679444970]] -> Type) -> *) (l :: TyFun a6989586621679444970 (TyFun a6989586621679444970 Bool -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (GroupBySym0 :: TyFun (TyFun a6989586621679444970 (TyFun a6989586621679444970 Bool -> Type) -> Type) (TyFun [a6989586621679444970] [[a6989586621679444970]] -> Type) -> *) (l :: TyFun a6989586621679444970 (TyFun a6989586621679444970 Bool -> Type) -> Type) = GroupBySym1 l

data GroupBySym1 (l :: TyFun a6989586621679444970 (TyFun a6989586621679444970 Bool -> Type) -> Type) (l :: TyFun [a6989586621679444970] [[a6989586621679444970]]) Source #

Instances
SuppressUnusedWarnings (GroupBySym1 :: (TyFun a6989586621679444970 (TyFun a6989586621679444970 Bool -> Type) -> Type) -> TyFun [a6989586621679444970] [[a6989586621679444970]] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (GroupBySym1 l1 :: TyFun [a] [[a]] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (GroupBySym1 l1 :: TyFun [a] [[a]] -> *) (l2 :: [a]) = GroupBy l1 l2

type GroupBySym2 (t :: TyFun a6989586621679444970 (TyFun a6989586621679444970 Bool -> Type) -> Type) (t :: [a6989586621679444970]) = GroupBy t t Source #

data LookupSym0 (l :: TyFun a6989586621679444968 (TyFun [(a6989586621679444968, b6989586621679444969)] (Maybe b6989586621679444969) -> Type)) Source #

Instances
SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679444968 (TyFun [(a6989586621679444968, b6989586621679444969)] (Maybe b6989586621679444969) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (LookupSym0 :: TyFun a6989586621679444968 (TyFun [(a6989586621679444968, b6989586621679444969)] (Maybe b6989586621679444969) -> Type) -> *) (l :: a6989586621679444968) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (LookupSym0 :: TyFun a6989586621679444968 (TyFun [(a6989586621679444968, b6989586621679444969)] (Maybe b6989586621679444969) -> Type) -> *) (l :: a6989586621679444968) = (LookupSym1 l :: TyFun [(a6989586621679444968, b6989586621679444969)] (Maybe b6989586621679444969) -> *)

data LookupSym1 (l :: a6989586621679444968) (l :: TyFun [(a6989586621679444968, b6989586621679444969)] (Maybe b6989586621679444969)) Source #

Instances
SuppressUnusedWarnings (LookupSym1 :: a6989586621679444968 -> TyFun [(a6989586621679444968, b6989586621679444969)] (Maybe b6989586621679444969) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (LookupSym1 l1 :: TyFun [(a, b)] (Maybe b) -> *) (l2 :: [(a, b)]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (LookupSym1 l1 :: TyFun [(a, b)] (Maybe b) -> *) (l2 :: [(a, b)]) = Lookup l1 l2

type LookupSym2 (t :: a6989586621679444968) (t :: [(a6989586621679444968, b6989586621679444969)]) = Lookup t t Source #

data FindSym0 (l :: TyFun (TyFun a6989586621679444990 Bool -> Type) (TyFun [a6989586621679444990] (Maybe a6989586621679444990) -> Type)) Source #

Instances
SuppressUnusedWarnings (FindSym0 :: TyFun (TyFun a6989586621679444990 Bool -> Type) (TyFun [a6989586621679444990] (Maybe a6989586621679444990) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FindSym0 :: TyFun (TyFun a6989586621679444990 Bool -> Type) (TyFun [a6989586621679444990] (Maybe a6989586621679444990) -> Type) -> *) (l :: TyFun a6989586621679444990 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FindSym0 :: TyFun (TyFun a6989586621679444990 Bool -> Type) (TyFun [a6989586621679444990] (Maybe a6989586621679444990) -> Type) -> *) (l :: TyFun a6989586621679444990 Bool -> Type) = FindSym1 l

data FindSym1 (l :: TyFun a6989586621679444990 Bool -> Type) (l :: TyFun [a6989586621679444990] (Maybe a6989586621679444990)) Source #

Instances
SuppressUnusedWarnings (FindSym1 :: (TyFun a6989586621679444990 Bool -> Type) -> TyFun [a6989586621679444990] (Maybe a6989586621679444990) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FindSym1 l1 :: TyFun [a] (Maybe a) -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FindSym1 l1 :: TyFun [a] (Maybe a) -> *) (l2 :: [a]) = Find l1 l2

type FindSym2 (t :: TyFun a6989586621679444990 Bool -> Type) (t :: [a6989586621679444990]) = Find t t Source #

data FilterSym0 (l :: TyFun (TyFun a6989586621679444991 Bool -> Type) (TyFun [a6989586621679444991] [a6989586621679444991] -> Type)) Source #

Instances
SuppressUnusedWarnings (FilterSym0 :: TyFun (TyFun a6989586621679444991 Bool -> Type) (TyFun [a6989586621679444991] [a6989586621679444991] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FilterSym0 :: TyFun (TyFun a6989586621679444991 Bool -> Type) (TyFun [a6989586621679444991] [a6989586621679444991] -> Type) -> *) (l :: TyFun a6989586621679444991 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FilterSym0 :: TyFun (TyFun a6989586621679444991 Bool -> Type) (TyFun [a6989586621679444991] [a6989586621679444991] -> Type) -> *) (l :: TyFun a6989586621679444991 Bool -> Type) = FilterSym1 l

data FilterSym1 (l :: TyFun a6989586621679444991 Bool -> Type) (l :: TyFun [a6989586621679444991] [a6989586621679444991]) Source #

Instances
SuppressUnusedWarnings (FilterSym1 :: (TyFun a6989586621679444991 Bool -> Type) -> TyFun [a6989586621679444991] [a6989586621679444991] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FilterSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FilterSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = Filter l1 l2

type FilterSym2 (t :: TyFun a6989586621679444991 Bool -> Type) (t :: [a6989586621679444991]) = Filter t t Source #

data PartitionSym0 (l :: TyFun (TyFun a6989586621679444967 Bool -> Type) (TyFun [a6989586621679444967] ([a6989586621679444967], [a6989586621679444967]) -> Type)) Source #

Instances
SuppressUnusedWarnings (PartitionSym0 :: TyFun (TyFun a6989586621679444967 Bool -> Type) (TyFun [a6989586621679444967] ([a6989586621679444967], [a6989586621679444967]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (PartitionSym0 :: TyFun (TyFun a6989586621679444967 Bool -> Type) (TyFun [a6989586621679444967] ([a6989586621679444967], [a6989586621679444967]) -> Type) -> *) (l :: TyFun a6989586621679444967 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (PartitionSym0 :: TyFun (TyFun a6989586621679444967 Bool -> Type) (TyFun [a6989586621679444967] ([a6989586621679444967], [a6989586621679444967]) -> Type) -> *) (l :: TyFun a6989586621679444967 Bool -> Type) = PartitionSym1 l

data PartitionSym1 (l :: TyFun a6989586621679444967 Bool -> Type) (l :: TyFun [a6989586621679444967] ([a6989586621679444967], [a6989586621679444967])) Source #

Instances
SuppressUnusedWarnings (PartitionSym1 :: (TyFun a6989586621679444967 Bool -> Type) -> TyFun [a6989586621679444967] ([a6989586621679444967], [a6989586621679444967]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (PartitionSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (PartitionSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) = Partition l1 l2

type PartitionSym2 (t :: TyFun a6989586621679444967 Bool -> Type) (t :: [a6989586621679444967]) = Partition t t Source #

data (!!@#@$) (l :: TyFun [a6989586621679444960] (TyFun Nat a6989586621679444960 -> Type)) Source #

Instances
SuppressUnusedWarnings ((!!@#@$) :: TyFun [a6989586621679444960] (TyFun Nat a6989586621679444960 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply ((!!@#@$) :: TyFun [a6989586621679444960] (TyFun Nat a6989586621679444960 -> Type) -> *) (l :: [a6989586621679444960]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply ((!!@#@$) :: TyFun [a6989586621679444960] (TyFun Nat a6989586621679444960 -> Type) -> *) (l :: [a6989586621679444960]) = (!!@#@$$) l

data (l :: [a6989586621679444960]) !!@#@$$ (l :: TyFun Nat a6989586621679444960) Source #

Instances
SuppressUnusedWarnings ((!!@#@$$) :: [a6989586621679444960] -> TyFun Nat a6989586621679444960 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply ((!!@#@$$) l1 :: TyFun Nat a -> *) (l2 :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply ((!!@#@$$) l1 :: TyFun Nat a -> *) (l2 :: Nat) = l1 !! l2

type (!!@#@$$$) (t :: [a6989586621679444960]) (t :: Nat) = (!!) t t Source #

data ElemIndexSym0 (l :: TyFun a6989586621679444989 (TyFun [a6989586621679444989] (Maybe Nat) -> Type)) Source #

Instances
SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679444989 (TyFun [a6989586621679444989] (Maybe Nat) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ElemIndexSym0 :: TyFun a6989586621679444989 (TyFun [a6989586621679444989] (Maybe Nat) -> Type) -> *) (l :: a6989586621679444989) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ElemIndexSym0 :: TyFun a6989586621679444989 (TyFun [a6989586621679444989] (Maybe Nat) -> Type) -> *) (l :: a6989586621679444989) = ElemIndexSym1 l

data ElemIndexSym1 (l :: a6989586621679444989) (l :: TyFun [a6989586621679444989] (Maybe Nat)) Source #

Instances
SuppressUnusedWarnings (ElemIndexSym1 :: a6989586621679444989 -> TyFun [a6989586621679444989] (Maybe Nat) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ElemIndexSym1 l1 :: TyFun [a] (Maybe Nat) -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ElemIndexSym1 l1 :: TyFun [a] (Maybe Nat) -> *) (l2 :: [a]) = ElemIndex l1 l2

type ElemIndexSym2 (t :: a6989586621679444989) (t :: [a6989586621679444989]) = ElemIndex t t Source #

data ElemIndicesSym0 (l :: TyFun a6989586621679444988 (TyFun [a6989586621679444988] [Nat] -> Type)) Source #

Instances
SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a6989586621679444988 (TyFun [a6989586621679444988] [Nat] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ElemIndicesSym0 :: TyFun a6989586621679444988 (TyFun [a6989586621679444988] [Nat] -> Type) -> *) (l :: a6989586621679444988) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ElemIndicesSym0 :: TyFun a6989586621679444988 (TyFun [a6989586621679444988] [Nat] -> Type) -> *) (l :: a6989586621679444988) = ElemIndicesSym1 l

data ElemIndicesSym1 (l :: a6989586621679444988) (l :: TyFun [a6989586621679444988] [Nat]) Source #

Instances
SuppressUnusedWarnings (ElemIndicesSym1 :: a6989586621679444988 -> TyFun [a6989586621679444988] [Nat] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ElemIndicesSym1 l1 :: TyFun [a] [Nat] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (ElemIndicesSym1 l1 :: TyFun [a] [Nat] -> *) (l2 :: [a]) = ElemIndices l1 l2

type ElemIndicesSym2 (t :: a6989586621679444988) (t :: [a6989586621679444988]) = ElemIndices t t Source #

data FindIndexSym0 (l :: TyFun (TyFun a6989586621679444987 Bool -> Type) (TyFun [a6989586621679444987] (Maybe Nat) -> Type)) Source #

Instances
SuppressUnusedWarnings (FindIndexSym0 :: TyFun (TyFun a6989586621679444987 Bool -> Type) (TyFun [a6989586621679444987] (Maybe Nat) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FindIndexSym0 :: TyFun (TyFun a6989586621679444987 Bool -> Type) (TyFun [a6989586621679444987] (Maybe Nat) -> Type) -> *) (l :: TyFun a6989586621679444987 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FindIndexSym0 :: TyFun (TyFun a6989586621679444987 Bool -> Type) (TyFun [a6989586621679444987] (Maybe Nat) -> Type) -> *) (l :: TyFun a6989586621679444987 Bool -> Type) = FindIndexSym1 l

data FindIndexSym1 (l :: TyFun a6989586621679444987 Bool -> Type) (l :: TyFun [a6989586621679444987] (Maybe Nat)) Source #

Instances
SuppressUnusedWarnings (FindIndexSym1 :: (TyFun a6989586621679444987 Bool -> Type) -> TyFun [a6989586621679444987] (Maybe Nat) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FindIndexSym1 l1 :: TyFun [a] (Maybe Nat) -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FindIndexSym1 l1 :: TyFun [a] (Maybe Nat) -> *) (l2 :: [a]) = FindIndex l1 l2

type FindIndexSym2 (t :: TyFun a6989586621679444987 Bool -> Type) (t :: [a6989586621679444987]) = FindIndex t t Source #

data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679444986 Bool -> Type) (TyFun [a6989586621679444986] [Nat] -> Type)) Source #

Instances
SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (TyFun a6989586621679444986 Bool -> Type) (TyFun [a6989586621679444986] [Nat] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FindIndicesSym0 :: TyFun (TyFun a6989586621679444986 Bool -> Type) (TyFun [a6989586621679444986] [Nat] -> Type) -> *) (l :: TyFun a6989586621679444986 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FindIndicesSym0 :: TyFun (TyFun a6989586621679444986 Bool -> Type) (TyFun [a6989586621679444986] [Nat] -> Type) -> *) (l :: TyFun a6989586621679444986 Bool -> Type) = FindIndicesSym1 l

data FindIndicesSym1 (l :: TyFun a6989586621679444986 Bool -> Type) (l :: TyFun [a6989586621679444986] [Nat]) Source #

Instances
SuppressUnusedWarnings (FindIndicesSym1 :: (TyFun a6989586621679444986 Bool -> Type) -> TyFun [a6989586621679444986] [Nat] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FindIndicesSym1 l1 :: TyFun [a] [Nat] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (FindIndicesSym1 l1 :: TyFun [a] [Nat] -> *) (l2 :: [a]) = FindIndices l1 l2

type FindIndicesSym2 (t :: TyFun a6989586621679444986 Bool -> Type) (t :: [a6989586621679444986]) = FindIndices t t Source #

data Zip4Sym0 (l :: TyFun [a6989586621679924859] (TyFun [b6989586621679924860] (TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a6989586621679924859] (TyFun [b6989586621679924860] (TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip4Sym0 :: TyFun [a6989586621679924859] (TyFun [b6989586621679924860] (TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> Type) -> Type) -> *) (l :: [a6989586621679924859]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip4Sym0 :: TyFun [a6989586621679924859] (TyFun [b6989586621679924860] (TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> Type) -> Type) -> *) (l :: [a6989586621679924859]) = (Zip4Sym1 l :: TyFun [b6989586621679924860] (TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> Type) -> *)

data Zip4Sym1 (l :: [a6989586621679924859]) (l :: TyFun [b6989586621679924860] (TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip4Sym1 :: [a6989586621679924859] -> TyFun [b6989586621679924860] (TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip4Sym1 l1 :: TyFun [b6989586621679924860] (TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> Type) -> *) (l2 :: [b6989586621679924860]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip4Sym1 l1 :: TyFun [b6989586621679924860] (TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> Type) -> *) (l2 :: [b6989586621679924860]) = (Zip4Sym2 l1 l2 :: TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> *)

data Zip4Sym2 (l :: [a6989586621679924859]) (l :: [b6989586621679924860]) (l :: TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip4Sym2 :: [a6989586621679924859] -> [b6989586621679924860] -> TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip4Sym2 l1 l2 :: TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> *) (l3 :: [c6989586621679924861]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip4Sym2 l1 l2 :: TyFun [c6989586621679924861] (TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> Type) -> *) (l3 :: [c6989586621679924861]) = (Zip4Sym3 l1 l2 l3 :: TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> *)

data Zip4Sym3 (l :: [a6989586621679924859]) (l :: [b6989586621679924860]) (l :: [c6989586621679924861]) (l :: TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)]) Source #

Instances
SuppressUnusedWarnings (Zip4Sym3 :: [a6989586621679924859] -> [b6989586621679924860] -> [c6989586621679924861] -> TyFun [d6989586621679924862] [(a6989586621679924859, b6989586621679924860, c6989586621679924861, d6989586621679924862)] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip4Sym3 l1 l2 l3 :: TyFun [d] [(a, b, c, d)] -> *) (l4 :: [d]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip4Sym3 l1 l2 l3 :: TyFun [d] [(a, b, c, d)] -> *) (l4 :: [d]) = Zip4 l1 l2 l3 l4

type Zip4Sym4 (t :: [a6989586621679924859]) (t :: [b6989586621679924860]) (t :: [c6989586621679924861]) (t :: [d6989586621679924862]) = Zip4 t t t t Source #

data Zip5Sym0 (l :: TyFun [a6989586621679924854] (TyFun [b6989586621679924855] (TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a6989586621679924854] (TyFun [b6989586621679924855] (TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip5Sym0 :: TyFun [a6989586621679924854] (TyFun [b6989586621679924855] (TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> Type) -> Type) -> *) (l :: [a6989586621679924854]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip5Sym0 :: TyFun [a6989586621679924854] (TyFun [b6989586621679924855] (TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> Type) -> Type) -> *) (l :: [a6989586621679924854]) = (Zip5Sym1 l :: TyFun [b6989586621679924855] (TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> Type) -> *)

data Zip5Sym1 (l :: [a6989586621679924854]) (l :: TyFun [b6989586621679924855] (TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip5Sym1 :: [a6989586621679924854] -> TyFun [b6989586621679924855] (TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip5Sym1 l1 :: TyFun [b6989586621679924855] (TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> Type) -> *) (l2 :: [b6989586621679924855]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip5Sym1 l1 :: TyFun [b6989586621679924855] (TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> Type) -> *) (l2 :: [b6989586621679924855]) = (Zip5Sym2 l1 l2 :: TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> *)

data Zip5Sym2 (l :: [a6989586621679924854]) (l :: [b6989586621679924855]) (l :: TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip5Sym2 :: [a6989586621679924854] -> [b6989586621679924855] -> TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip5Sym2 l1 l2 :: TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> *) (l3 :: [c6989586621679924856]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip5Sym2 l1 l2 :: TyFun [c6989586621679924856] (TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> Type) -> *) (l3 :: [c6989586621679924856]) = (Zip5Sym3 l1 l2 l3 :: TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> *)

data Zip5Sym3 (l :: [a6989586621679924854]) (l :: [b6989586621679924855]) (l :: [c6989586621679924856]) (l :: TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip5Sym3 :: [a6989586621679924854] -> [b6989586621679924855] -> [c6989586621679924856] -> TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip5Sym3 l1 l2 l3 :: TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> *) (l4 :: [d6989586621679924857]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip5Sym3 l1 l2 l3 :: TyFun [d6989586621679924857] (TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> Type) -> *) (l4 :: [d6989586621679924857]) = (Zip5Sym4 l1 l2 l3 l4 :: TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> *)

data Zip5Sym4 (l :: [a6989586621679924854]) (l :: [b6989586621679924855]) (l :: [c6989586621679924856]) (l :: [d6989586621679924857]) (l :: TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)]) Source #

Instances
SuppressUnusedWarnings (Zip5Sym4 :: [a6989586621679924854] -> [b6989586621679924855] -> [c6989586621679924856] -> [d6989586621679924857] -> TyFun [e6989586621679924858] [(a6989586621679924854, b6989586621679924855, c6989586621679924856, d6989586621679924857, e6989586621679924858)] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip5Sym4 l1 l2 l3 l4 :: TyFun [e] [(a, b, c, d, e)] -> *) (l5 :: [e]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip5Sym4 l1 l2 l3 l4 :: TyFun [e] [(a, b, c, d, e)] -> *) (l5 :: [e]) = Zip5 l1 l2 l3 l4 l5

type Zip5Sym5 (t :: [a6989586621679924854]) (t :: [b6989586621679924855]) (t :: [c6989586621679924856]) (t :: [d6989586621679924857]) (t :: [e6989586621679924858]) = Zip5 t t t t t Source #

data Zip6Sym0 (l :: TyFun [a6989586621679924848] (TyFun [b6989586621679924849] (TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a6989586621679924848] (TyFun [b6989586621679924849] (TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip6Sym0 :: TyFun [a6989586621679924848] (TyFun [b6989586621679924849] (TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: [a6989586621679924848]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip6Sym0 :: TyFun [a6989586621679924848] (TyFun [b6989586621679924849] (TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: [a6989586621679924848]) = (Zip6Sym1 l :: TyFun [b6989586621679924849] (TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> Type) -> *)

data Zip6Sym1 (l :: [a6989586621679924848]) (l :: TyFun [b6989586621679924849] (TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip6Sym1 :: [a6989586621679924848] -> TyFun [b6989586621679924849] (TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip6Sym1 l1 :: TyFun [b6989586621679924849] (TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: [b6989586621679924849]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip6Sym1 l1 :: TyFun [b6989586621679924849] (TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: [b6989586621679924849]) = (Zip6Sym2 l1 l2 :: TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> *)

data Zip6Sym2 (l :: [a6989586621679924848]) (l :: [b6989586621679924849]) (l :: TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip6Sym2 :: [a6989586621679924848] -> [b6989586621679924849] -> TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip6Sym2 l1 l2 :: TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> *) (l3 :: [c6989586621679924850]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip6Sym2 l1 l2 :: TyFun [c6989586621679924850] (TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> Type) -> *) (l3 :: [c6989586621679924850]) = (Zip6Sym3 l1 l2 l3 :: TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> *)

data Zip6Sym3 (l :: [a6989586621679924848]) (l :: [b6989586621679924849]) (l :: [c6989586621679924850]) (l :: TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip6Sym3 :: [a6989586621679924848] -> [b6989586621679924849] -> [c6989586621679924850] -> TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip6Sym3 l1 l2 l3 :: TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> *) (l4 :: [d6989586621679924851]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip6Sym3 l1 l2 l3 :: TyFun [d6989586621679924851] (TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> Type) -> *) (l4 :: [d6989586621679924851]) = (Zip6Sym4 l1 l2 l3 l4 :: TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> *)

data Zip6Sym4 (l :: [a6989586621679924848]) (l :: [b6989586621679924849]) (l :: [c6989586621679924850]) (l :: [d6989586621679924851]) (l :: TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip6Sym4 :: [a6989586621679924848] -> [b6989586621679924849] -> [c6989586621679924850] -> [d6989586621679924851] -> TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip6Sym4 l1 l2 l3 l4 :: TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> *) (l5 :: [e6989586621679924852]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip6Sym4 l1 l2 l3 l4 :: TyFun [e6989586621679924852] (TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> Type) -> *) (l5 :: [e6989586621679924852]) = (Zip6Sym5 l1 l2 l3 l4 l5 :: TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> *)

data Zip6Sym5 (l :: [a6989586621679924848]) (l :: [b6989586621679924849]) (l :: [c6989586621679924850]) (l :: [d6989586621679924851]) (l :: [e6989586621679924852]) (l :: TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)]) Source #

Instances
SuppressUnusedWarnings (Zip6Sym5 :: [a6989586621679924848] -> [b6989586621679924849] -> [c6989586621679924850] -> [d6989586621679924851] -> [e6989586621679924852] -> TyFun [f6989586621679924853] [(a6989586621679924848, b6989586621679924849, c6989586621679924850, d6989586621679924851, e6989586621679924852, f6989586621679924853)] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip6Sym5 l1 l2 l3 l4 l5 :: TyFun [f] [(a, b, c, d, e, f)] -> *) (l6 :: [f]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip6Sym5 l1 l2 l3 l4 l5 :: TyFun [f] [(a, b, c, d, e, f)] -> *) (l6 :: [f]) = Zip6 l1 l2 l3 l4 l5 l6

type Zip6Sym6 (t :: [a6989586621679924848]) (t :: [b6989586621679924849]) (t :: [c6989586621679924850]) (t :: [d6989586621679924851]) (t :: [e6989586621679924852]) (t :: [f6989586621679924853]) = Zip6 t t t t t t Source #

data Zip7Sym0 (l :: TyFun [a6989586621679924841] (TyFun [b6989586621679924842] (TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a6989586621679924841] (TyFun [b6989586621679924842] (TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym0 :: TyFun [a6989586621679924841] (TyFun [b6989586621679924842] (TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: [a6989586621679924841]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym0 :: TyFun [a6989586621679924841] (TyFun [b6989586621679924842] (TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: [a6989586621679924841]) = (Zip7Sym1 l :: TyFun [b6989586621679924842] (TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *)

data Zip7Sym1 (l :: [a6989586621679924841]) (l :: TyFun [b6989586621679924842] (TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip7Sym1 :: [a6989586621679924841] -> TyFun [b6989586621679924842] (TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym1 l1 :: TyFun [b6989586621679924842] (TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: [b6989586621679924842]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym1 l1 :: TyFun [b6989586621679924842] (TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: [b6989586621679924842]) = (Zip7Sym2 l1 l2 :: TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> *)

data Zip7Sym2 (l :: [a6989586621679924841]) (l :: [b6989586621679924842]) (l :: TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip7Sym2 :: [a6989586621679924841] -> [b6989586621679924842] -> TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym2 l1 l2 :: TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> *) (l3 :: [c6989586621679924843]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym2 l1 l2 :: TyFun [c6989586621679924843] (TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> Type) -> *) (l3 :: [c6989586621679924843]) = (Zip7Sym3 l1 l2 l3 :: TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> *)

data Zip7Sym3 (l :: [a6989586621679924841]) (l :: [b6989586621679924842]) (l :: [c6989586621679924843]) (l :: TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip7Sym3 :: [a6989586621679924841] -> [b6989586621679924842] -> [c6989586621679924843] -> TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym3 l1 l2 l3 :: TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> *) (l4 :: [d6989586621679924844]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym3 l1 l2 l3 :: TyFun [d6989586621679924844] (TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> Type) -> *) (l4 :: [d6989586621679924844]) = (Zip7Sym4 l1 l2 l3 l4 :: TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> *)

data Zip7Sym4 (l :: [a6989586621679924841]) (l :: [b6989586621679924842]) (l :: [c6989586621679924843]) (l :: [d6989586621679924844]) (l :: TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip7Sym4 :: [a6989586621679924841] -> [b6989586621679924842] -> [c6989586621679924843] -> [d6989586621679924844] -> TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym4 l1 l2 l3 l4 :: TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> *) (l5 :: [e6989586621679924845]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym4 l1 l2 l3 l4 :: TyFun [e6989586621679924845] (TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> Type) -> *) (l5 :: [e6989586621679924845]) = (Zip7Sym5 l1 l2 l3 l4 l5 :: TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> *)

data Zip7Sym5 (l :: [a6989586621679924841]) (l :: [b6989586621679924842]) (l :: [c6989586621679924843]) (l :: [d6989586621679924844]) (l :: [e6989586621679924845]) (l :: TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type)) Source #

Instances
SuppressUnusedWarnings (Zip7Sym5 :: [a6989586621679924841] -> [b6989586621679924842] -> [c6989586621679924843] -> [d6989586621679924844] -> [e6989586621679924845] -> TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym5 l1 l2 l3 l4 l5 :: TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> *) (l6 :: [f6989586621679924846]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym5 l1 l2 l3 l4 l5 :: TyFun [f6989586621679924846] (TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> Type) -> *) (l6 :: [f6989586621679924846]) = (Zip7Sym6 l1 l2 l3 l4 l5 l6 :: TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> *)

data Zip7Sym6 (l :: [a6989586621679924841]) (l :: [b6989586621679924842]) (l :: [c6989586621679924843]) (l :: [d6989586621679924844]) (l :: [e6989586621679924845]) (l :: [f6989586621679924846]) (l :: TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)]) Source #

Instances
SuppressUnusedWarnings (Zip7Sym6 :: [a6989586621679924841] -> [b6989586621679924842] -> [c6989586621679924843] -> [d6989586621679924844] -> [e6989586621679924845] -> [f6989586621679924846] -> TyFun [g6989586621679924847] [(a6989586621679924841, b6989586621679924842, c6989586621679924843, d6989586621679924844, e6989586621679924845, f6989586621679924846, g6989586621679924847)] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym6 l1 l2 l3 l4 l5 l6 :: TyFun [g] [(a, b, c, d, e, f, g)] -> *) (l7 :: [g]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (Zip7Sym6 l1 l2 l3 l4 l5 l6 :: TyFun [g] [(a, b, c, d, e, f, g)] -> *) (l7 :: [g]) = Zip7 l1 l2 l3 l4 l5 l6 l7

type Zip7Sym7 (t :: [a6989586621679924841]) (t :: [b6989586621679924842]) (t :: [c6989586621679924843]) (t :: [d6989586621679924844]) (t :: [e6989586621679924845]) (t :: [f6989586621679924846]) (t :: [g6989586621679924847]) = Zip7 t t t t t t t Source #

data ZipWith4Sym0 (l :: TyFun (TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924836] (TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924836] (TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith4Sym0 :: TyFun (TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924836] (TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith4Sym0 :: TyFun (TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924836] (TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) = ZipWith4Sym1 l

data ZipWith4Sym1 (l :: TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679924836] (TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith4Sym1 :: (TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679924836] (TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith4Sym1 l1 :: TyFun [a6989586621679924836] (TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> Type) -> *) (l2 :: [a6989586621679924836]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith4Sym1 l1 :: TyFun [a6989586621679924836] (TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> Type) -> *) (l2 :: [a6989586621679924836]) = ZipWith4Sym2 l1 l2

data ZipWith4Sym2 (l :: TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924836]) (l :: TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith4Sym2 :: (TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924836] -> TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith4Sym2 l1 l2 :: TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> *) (l3 :: [b6989586621679924837]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith4Sym2 l1 l2 :: TyFun [b6989586621679924837] (TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> Type) -> *) (l3 :: [b6989586621679924837]) = ZipWith4Sym3 l1 l2 l3

data ZipWith4Sym3 (l :: TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924836]) (l :: [b6989586621679924837]) (l :: TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith4Sym3 :: (TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924836] -> [b6989586621679924837] -> TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith4Sym3 l1 l2 l3 :: TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> *) (l4 :: [c6989586621679924838]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith4Sym3 l1 l2 l3 :: TyFun [c6989586621679924838] (TyFun [d6989586621679924839] [e6989586621679924840] -> Type) -> *) (l4 :: [c6989586621679924838]) = ZipWith4Sym4 l1 l2 l3 l4

data ZipWith4Sym4 (l :: TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924836]) (l :: [b6989586621679924837]) (l :: [c6989586621679924838]) (l :: TyFun [d6989586621679924839] [e6989586621679924840]) Source #

Instances
SuppressUnusedWarnings (ZipWith4Sym4 :: (TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924836] -> [b6989586621679924837] -> [c6989586621679924838] -> TyFun [d6989586621679924839] [e6989586621679924840] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith4Sym4 l1 l2 l3 l4 :: TyFun [d] [e] -> *) (l5 :: [d]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith4Sym4 l1 l2 l3 l4 :: TyFun [d] [e] -> *) (l5 :: [d]) = ZipWith4 l1 l2 l3 l4 l5

type ZipWith4Sym5 (t :: TyFun a6989586621679924836 (TyFun b6989586621679924837 (TyFun c6989586621679924838 (TyFun d6989586621679924839 e6989586621679924840 -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679924836]) (t :: [b6989586621679924837]) (t :: [c6989586621679924838]) (t :: [d6989586621679924839]) = ZipWith4 t t t t t Source #

data ZipWith5Sym0 (l :: TyFun (TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924830] (TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924830] (TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith5Sym0 :: TyFun (TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924830] (TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith5Sym0 :: TyFun (TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924830] (TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) = ZipWith5Sym1 l

data ZipWith5Sym1 (l :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679924830] (TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith5Sym1 :: (TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679924830] (TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith5Sym1 l1 :: TyFun [a6989586621679924830] (TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: [a6989586621679924830]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith5Sym1 l1 :: TyFun [a6989586621679924830] (TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: [a6989586621679924830]) = ZipWith5Sym2 l1 l2

data ZipWith5Sym2 (l :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924830]) (l :: TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith5Sym2 :: (TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924830] -> TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith5Sym2 l1 l2 :: TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> *) (l3 :: [b6989586621679924831]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith5Sym2 l1 l2 :: TyFun [b6989586621679924831] (TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> Type) -> *) (l3 :: [b6989586621679924831]) = ZipWith5Sym3 l1 l2 l3

data ZipWith5Sym3 (l :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924830]) (l :: [b6989586621679924831]) (l :: TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith5Sym3 :: (TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924830] -> [b6989586621679924831] -> TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith5Sym3 l1 l2 l3 :: TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> *) (l4 :: [c6989586621679924832]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith5Sym3 l1 l2 l3 :: TyFun [c6989586621679924832] (TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> Type) -> *) (l4 :: [c6989586621679924832]) = ZipWith5Sym4 l1 l2 l3 l4

data ZipWith5Sym4 (l :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924830]) (l :: [b6989586621679924831]) (l :: [c6989586621679924832]) (l :: TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith5Sym4 :: (TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924830] -> [b6989586621679924831] -> [c6989586621679924832] -> TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith5Sym4 l1 l2 l3 l4 :: TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> *) (l5 :: [d6989586621679924833]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith5Sym4 l1 l2 l3 l4 :: TyFun [d6989586621679924833] (TyFun [e6989586621679924834] [f6989586621679924835] -> Type) -> *) (l5 :: [d6989586621679924833]) = ZipWith5Sym5 l1 l2 l3 l4 l5

data ZipWith5Sym5 (l :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924830]) (l :: [b6989586621679924831]) (l :: [c6989586621679924832]) (l :: [d6989586621679924833]) (l :: TyFun [e6989586621679924834] [f6989586621679924835]) Source #

Instances
SuppressUnusedWarnings (ZipWith5Sym5 :: (TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924830] -> [b6989586621679924831] -> [c6989586621679924832] -> [d6989586621679924833] -> TyFun [e6989586621679924834] [f6989586621679924835] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith5Sym5 l1 l2 l3 l4 l5 :: TyFun [e] [f] -> *) (l6 :: [e]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith5Sym5 l1 l2 l3 l4 l5 :: TyFun [e] [f] -> *) (l6 :: [e]) = ZipWith5 l1 l2 l3 l4 l5 l6

type ZipWith5Sym6 (t :: TyFun a6989586621679924830 (TyFun b6989586621679924831 (TyFun c6989586621679924832 (TyFun d6989586621679924833 (TyFun e6989586621679924834 f6989586621679924835 -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679924830]) (t :: [b6989586621679924831]) (t :: [c6989586621679924832]) (t :: [d6989586621679924833]) (t :: [e6989586621679924834]) = ZipWith5 t t t t t t Source #

data ZipWith6Sym0 (l :: TyFun (TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924823] (TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924823] (TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym0 :: TyFun (TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924823] (TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym0 :: TyFun (TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924823] (TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) = ZipWith6Sym1 l

data ZipWith6Sym1 (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679924823] (TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym1 :: (TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679924823] (TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym1 l1 :: TyFun [a6989586621679924823] (TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: [a6989586621679924823]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym1 l1 :: TyFun [a6989586621679924823] (TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: [a6989586621679924823]) = ZipWith6Sym2 l1 l2

data ZipWith6Sym2 (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924823]) (l :: TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym2 :: (TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924823] -> TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym2 l1 l2 :: TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> *) (l3 :: [b6989586621679924824]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym2 l1 l2 :: TyFun [b6989586621679924824] (TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> Type) -> *) (l3 :: [b6989586621679924824]) = ZipWith6Sym3 l1 l2 l3

data ZipWith6Sym3 (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924823]) (l :: [b6989586621679924824]) (l :: TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym3 :: (TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924823] -> [b6989586621679924824] -> TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym3 l1 l2 l3 :: TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> *) (l4 :: [c6989586621679924825]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym3 l1 l2 l3 :: TyFun [c6989586621679924825] (TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> Type) -> *) (l4 :: [c6989586621679924825]) = ZipWith6Sym4 l1 l2 l3 l4

data ZipWith6Sym4 (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924823]) (l :: [b6989586621679924824]) (l :: [c6989586621679924825]) (l :: TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym4 :: (TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924823] -> [b6989586621679924824] -> [c6989586621679924825] -> TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym4 l1 l2 l3 l4 :: TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> *) (l5 :: [d6989586621679924826]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym4 l1 l2 l3 l4 :: TyFun [d6989586621679924826] (TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> Type) -> *) (l5 :: [d6989586621679924826]) = ZipWith6Sym5 l1 l2 l3 l4 l5

data ZipWith6Sym5 (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924823]) (l :: [b6989586621679924824]) (l :: [c6989586621679924825]) (l :: [d6989586621679924826]) (l :: TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym5 :: (TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924823] -> [b6989586621679924824] -> [c6989586621679924825] -> [d6989586621679924826] -> TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym5 l1 l2 l3 l4 l5 :: TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> *) (l6 :: [e6989586621679924827]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym5 l1 l2 l3 l4 l5 :: TyFun [e6989586621679924827] (TyFun [f6989586621679924828] [g6989586621679924829] -> Type) -> *) (l6 :: [e6989586621679924827]) = ZipWith6Sym6 l1 l2 l3 l4 l5 l6

data ZipWith6Sym6 (l :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924823]) (l :: [b6989586621679924824]) (l :: [c6989586621679924825]) (l :: [d6989586621679924826]) (l :: [e6989586621679924827]) (l :: TyFun [f6989586621679924828] [g6989586621679924829]) Source #

Instances
SuppressUnusedWarnings (ZipWith6Sym6 :: (TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924823] -> [b6989586621679924824] -> [c6989586621679924825] -> [d6989586621679924826] -> [e6989586621679924827] -> TyFun [f6989586621679924828] [g6989586621679924829] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym6 l1 l2 l3 l4 l5 l6 :: TyFun [f] [g] -> *) (l7 :: [f]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith6Sym6 l1 l2 l3 l4 l5 l6 :: TyFun [f] [g] -> *) (l7 :: [f]) = ZipWith6 l1 l2 l3 l4 l5 l6 l7

type ZipWith6Sym7 (t :: TyFun a6989586621679924823 (TyFun b6989586621679924824 (TyFun c6989586621679924825 (TyFun d6989586621679924826 (TyFun e6989586621679924827 (TyFun f6989586621679924828 g6989586621679924829 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679924823]) (t :: [b6989586621679924824]) (t :: [c6989586621679924825]) (t :: [d6989586621679924826]) (t :: [e6989586621679924827]) (t :: [f6989586621679924828]) = ZipWith6 t t t t t t t Source #

data ZipWith7Sym0 (l :: TyFun (TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924815] (TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym0 :: TyFun (TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924815] (TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym0 :: TyFun (TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924815] (TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym0 :: TyFun (TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679924815] (TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) = ZipWith7Sym1 l

data ZipWith7Sym1 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679924815] (TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym1 :: (TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679924815] (TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym1 l1 :: TyFun [a6989586621679924815] (TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: [a6989586621679924815]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym1 l1 :: TyFun [a6989586621679924815] (TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l2 :: [a6989586621679924815]) = ZipWith7Sym2 l1 l2

data ZipWith7Sym2 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924815]) (l :: TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym2 :: (TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924815] -> TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym2 l1 l2 :: TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l3 :: [b6989586621679924816]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym2 l1 l2 :: TyFun [b6989586621679924816] (TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (l3 :: [b6989586621679924816]) = ZipWith7Sym3 l1 l2 l3

data ZipWith7Sym3 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924815]) (l :: [b6989586621679924816]) (l :: TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym3 :: (TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924815] -> [b6989586621679924816] -> TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym3 l1 l2 l3 :: TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> *) (l4 :: [c6989586621679924817]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym3 l1 l2 l3 :: TyFun [c6989586621679924817] (TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> Type) -> *) (l4 :: [c6989586621679924817]) = ZipWith7Sym4 l1 l2 l3 l4

data ZipWith7Sym4 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924815]) (l :: [b6989586621679924816]) (l :: [c6989586621679924817]) (l :: TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym4 :: (TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924815] -> [b6989586621679924816] -> [c6989586621679924817] -> TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym4 l1 l2 l3 l4 :: TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> *) (l5 :: [d6989586621679924818]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym4 l1 l2 l3 l4 :: TyFun [d6989586621679924818] (TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> Type) -> *) (l5 :: [d6989586621679924818]) = ZipWith7Sym5 l1 l2 l3 l4 l5

data ZipWith7Sym5 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924815]) (l :: [b6989586621679924816]) (l :: [c6989586621679924817]) (l :: [d6989586621679924818]) (l :: TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym5 :: (TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924815] -> [b6989586621679924816] -> [c6989586621679924817] -> [d6989586621679924818] -> TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym5 l1 l2 l3 l4 l5 :: TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> *) (l6 :: [e6989586621679924819]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym5 l1 l2 l3 l4 l5 :: TyFun [e6989586621679924819] (TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> Type) -> *) (l6 :: [e6989586621679924819]) = ZipWith7Sym6 l1 l2 l3 l4 l5 l6

data ZipWith7Sym6 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924815]) (l :: [b6989586621679924816]) (l :: [c6989586621679924817]) (l :: [d6989586621679924818]) (l :: [e6989586621679924819]) (l :: TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym6 :: (TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924815] -> [b6989586621679924816] -> [c6989586621679924817] -> [d6989586621679924818] -> [e6989586621679924819] -> TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym6 l1 l2 l3 l4 l5 l6 :: TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> *) (l7 :: [f6989586621679924820]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym6 l1 l2 l3 l4 l5 l6 :: TyFun [f6989586621679924820] (TyFun [g6989586621679924821] [h6989586621679924822] -> Type) -> *) (l7 :: [f6989586621679924820]) = ZipWith7Sym7 l1 l2 l3 l4 l5 l6 l7

data ZipWith7Sym7 (l :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679924815]) (l :: [b6989586621679924816]) (l :: [c6989586621679924817]) (l :: [d6989586621679924818]) (l :: [e6989586621679924819]) (l :: [f6989586621679924820]) (l :: TyFun [g6989586621679924821] [h6989586621679924822]) Source #

Instances
SuppressUnusedWarnings (ZipWith7Sym7 :: (TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679924815] -> [b6989586621679924816] -> [c6989586621679924817] -> [d6989586621679924818] -> [e6989586621679924819] -> [f6989586621679924820] -> TyFun [g6989586621679924821] [h6989586621679924822] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym7 l1 l2 l3 l4 l5 l6 l7 :: TyFun [g] [h] -> *) (l8 :: [g]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (ZipWith7Sym7 l1 l2 l3 l4 l5 l6 l7 :: TyFun [g] [h] -> *) (l8 :: [g]) = ZipWith7 l1 l2 l3 l4 l5 l6 l7 l8

type ZipWith7Sym8 (t :: TyFun a6989586621679924815 (TyFun b6989586621679924816 (TyFun c6989586621679924817 (TyFun d6989586621679924818 (TyFun e6989586621679924819 (TyFun f6989586621679924820 (TyFun g6989586621679924821 h6989586621679924822 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679924815]) (t :: [b6989586621679924816]) (t :: [c6989586621679924817]) (t :: [d6989586621679924818]) (t :: [e6989586621679924819]) (t :: [f6989586621679924820]) (t :: [g6989586621679924821]) = ZipWith7 t t t t t t t t Source #

data UnlinesSym0 (l :: TyFun [Symbol] Symbol) Source #

Instances
SuppressUnusedWarnings UnlinesSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply UnlinesSym0 (l :: [Symbol]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply UnlinesSym0 (l :: [Symbol]) = Unlines l

type UnlinesSym1 (t :: [Symbol]) = Unlines t Source #

data UnwordsSym0 (l :: TyFun [Symbol] Symbol) Source #

Instances
SuppressUnusedWarnings UnwordsSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply UnwordsSym0 (l :: [Symbol]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply UnwordsSym0 (l :: [Symbol]) = Unwords l

type UnwordsSym1 (t :: [Symbol]) = Unwords t Source #

data NubSym0 (l :: TyFun [a6989586621679444959] [a6989586621679444959]) Source #

Instances
SuppressUnusedWarnings (NubSym0 :: TyFun [a6989586621679444959] [a6989586621679444959] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (NubSym0 :: TyFun [a] [a] -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (NubSym0 :: TyFun [a] [a] -> *) (l :: [a]) = Nub l

type NubSym1 (t :: [a6989586621679444959]) = Nub t Source #

data NubBySym0 (l :: TyFun (TyFun a6989586621679444958 (TyFun a6989586621679444958 Bool -> Type) -> Type) (TyFun [a6989586621679444958] [a6989586621679444958] -> Type)) Source #

Instances
SuppressUnusedWarnings (NubBySym0 :: TyFun (TyFun a6989586621679444958 (TyFun a6989586621679444958 Bool -> Type) -> Type) (TyFun [a6989586621679444958] [a6989586621679444958] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (NubBySym0 :: TyFun (TyFun a6989586621679444958 (TyFun a6989586621679444958 Bool -> Type) -> Type) (TyFun [a6989586621679444958] [a6989586621679444958] -> Type) -> *) (l :: TyFun a6989586621679444958 (TyFun a6989586621679444958 Bool -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (NubBySym0 :: TyFun (TyFun a6989586621679444958 (TyFun a6989586621679444958 Bool -> Type) -> Type) (TyFun [a6989586621679444958] [a6989586621679444958] -> Type) -> *) (l :: TyFun a6989586621679444958 (TyFun a6989586621679444958 Bool -> Type) -> Type) = NubBySym1 l

data NubBySym1 (l :: TyFun a6989586621679444958 (TyFun a6989586621679444958 Bool -> Type) -> Type) (l :: TyFun [a6989586621679444958] [a6989586621679444958]) Source #

Instances
SuppressUnusedWarnings (NubBySym1 :: (TyFun a6989586621679444958 (TyFun a6989586621679444958 Bool -> Type) -> Type) -> TyFun [a6989586621679444958] [a6989586621679444958] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (NubBySym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (NubBySym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = NubBy l1 l2

type NubBySym2 (t :: TyFun a6989586621679444958 (TyFun a6989586621679444958 Bool -> Type) -> Type) (t :: [a6989586621679444958]) = NubBy t t Source #

data UnionSym0 (l :: TyFun [a6989586621679444955] (TyFun [a6989586621679444955] [a6989586621679444955] -> Type)) Source #

Instances
SuppressUnusedWarnings (UnionSym0 :: TyFun [a6989586621679444955] (TyFun [a6989586621679444955] [a6989586621679444955] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnionSym0 :: TyFun [a6989586621679444955] (TyFun [a6989586621679444955] [a6989586621679444955] -> Type) -> *) (l :: [a6989586621679444955]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnionSym0 :: TyFun [a6989586621679444955] (TyFun [a6989586621679444955] [a6989586621679444955] -> Type) -> *) (l :: [a6989586621679444955]) = UnionSym1 l

data UnionSym1 (l :: [a6989586621679444955]) (l :: TyFun [a6989586621679444955] [a6989586621679444955]) Source #

Instances
SuppressUnusedWarnings (UnionSym1 :: [a6989586621679444955] -> TyFun [a6989586621679444955] [a6989586621679444955] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnionSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnionSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = Union l1 l2

type UnionSym2 (t :: [a6989586621679444955]) (t :: [a6989586621679444955]) = Union t t Source #

data UnionBySym0 (l :: TyFun (TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) (TyFun [a6989586621679444956] (TyFun [a6989586621679444956] [a6989586621679444956] -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (UnionBySym0 :: TyFun (TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) (TyFun [a6989586621679444956] (TyFun [a6989586621679444956] [a6989586621679444956] -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnionBySym0 :: TyFun (TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) (TyFun [a6989586621679444956] (TyFun [a6989586621679444956] [a6989586621679444956] -> Type) -> Type) -> *) (l :: TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnionBySym0 :: TyFun (TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) (TyFun [a6989586621679444956] (TyFun [a6989586621679444956] [a6989586621679444956] -> Type) -> Type) -> *) (l :: TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) = UnionBySym1 l

data UnionBySym1 (l :: TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) (l :: TyFun [a6989586621679444956] (TyFun [a6989586621679444956] [a6989586621679444956] -> Type)) Source #

Instances
SuppressUnusedWarnings (UnionBySym1 :: (TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) -> TyFun [a6989586621679444956] (TyFun [a6989586621679444956] [a6989586621679444956] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnionBySym1 l1 :: TyFun [a6989586621679444956] (TyFun [a6989586621679444956] [a6989586621679444956] -> Type) -> *) (l2 :: [a6989586621679444956]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnionBySym1 l1 :: TyFun [a6989586621679444956] (TyFun [a6989586621679444956] [a6989586621679444956] -> Type) -> *) (l2 :: [a6989586621679444956]) = UnionBySym2 l1 l2

data UnionBySym2 (l :: TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) (l :: [a6989586621679444956]) (l :: TyFun [a6989586621679444956] [a6989586621679444956]) Source #

Instances
SuppressUnusedWarnings (UnionBySym2 :: (TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) -> [a6989586621679444956] -> TyFun [a6989586621679444956] [a6989586621679444956] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnionBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (UnionBySym2 l1 l2 :: TyFun [a] [a] -> *) (l3 :: [a]) = UnionBy l1 l2 l3

type UnionBySym3 (t :: TyFun a6989586621679444956 (TyFun a6989586621679444956 Bool -> Type) -> Type) (t :: [a6989586621679444956]) (t :: [a6989586621679444956]) = UnionBy t t t Source #

data GenericLengthSym0 (l :: TyFun [a6989586621679444954] i6989586621679444953) Source #

Instances
SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a6989586621679444954] i6989586621679444953 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (GenericLengthSym0 :: TyFun [a] k2 -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List

type Apply (GenericLengthSym0 :: TyFun [a] k2 -> *) (l :: [a]) = (GenericLength l :: k2)

type GenericLengthSym1 (t :: [a6989586621679444954]) = GenericLength t Source #

data GenericTakeSym0 (l :: TyFun i6989586621679924813 (TyFun [a6989586621679924814] [a6989586621679924814] -> Type)) Source #

Instances
SuppressUnusedWarnings (GenericTakeSym0 :: TyFun i6989586621679924813 (TyFun [a6989586621679924814] [a6989586621679924814] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericTakeSym0 :: TyFun i6989586621679924813 (TyFun [a6989586621679924814] [a6989586621679924814] -> Type) -> *) (l :: i6989586621679924813) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericTakeSym0 :: TyFun i6989586621679924813 (TyFun [a6989586621679924814] [a6989586621679924814] -> Type) -> *) (l :: i6989586621679924813) = (GenericTakeSym1 l :: TyFun [a6989586621679924814] [a6989586621679924814] -> *)

data GenericTakeSym1 (l :: i6989586621679924813) (l :: TyFun [a6989586621679924814] [a6989586621679924814]) Source #

Instances
SuppressUnusedWarnings (GenericTakeSym1 :: i6989586621679924813 -> TyFun [a6989586621679924814] [a6989586621679924814] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericTakeSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericTakeSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = GenericTake l1 l2

type GenericTakeSym2 (t :: i6989586621679924813) (t :: [a6989586621679924814]) = GenericTake t t Source #

data GenericDropSym0 (l :: TyFun i6989586621679924811 (TyFun [a6989586621679924812] [a6989586621679924812] -> Type)) Source #

Instances
SuppressUnusedWarnings (GenericDropSym0 :: TyFun i6989586621679924811 (TyFun [a6989586621679924812] [a6989586621679924812] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericDropSym0 :: TyFun i6989586621679924811 (TyFun [a6989586621679924812] [a6989586621679924812] -> Type) -> *) (l :: i6989586621679924811) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericDropSym0 :: TyFun i6989586621679924811 (TyFun [a6989586621679924812] [a6989586621679924812] -> Type) -> *) (l :: i6989586621679924811) = (GenericDropSym1 l :: TyFun [a6989586621679924812] [a6989586621679924812] -> *)

data GenericDropSym1 (l :: i6989586621679924811) (l :: TyFun [a6989586621679924812] [a6989586621679924812]) Source #

Instances
SuppressUnusedWarnings (GenericDropSym1 :: i6989586621679924811 -> TyFun [a6989586621679924812] [a6989586621679924812] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericDropSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericDropSym1 l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = GenericDrop l1 l2

type GenericDropSym2 (t :: i6989586621679924811) (t :: [a6989586621679924812]) = GenericDrop t t Source #

data GenericSplitAtSym0 (l :: TyFun i6989586621679924809 (TyFun [a6989586621679924810] ([a6989586621679924810], [a6989586621679924810]) -> Type)) Source #

Instances
SuppressUnusedWarnings (GenericSplitAtSym0 :: TyFun i6989586621679924809 (TyFun [a6989586621679924810] ([a6989586621679924810], [a6989586621679924810]) -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericSplitAtSym0 :: TyFun i6989586621679924809 (TyFun [a6989586621679924810] ([a6989586621679924810], [a6989586621679924810]) -> Type) -> *) (l :: i6989586621679924809) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericSplitAtSym0 :: TyFun i6989586621679924809 (TyFun [a6989586621679924810] ([a6989586621679924810], [a6989586621679924810]) -> Type) -> *) (l :: i6989586621679924809) = (GenericSplitAtSym1 l :: TyFun [a6989586621679924810] ([a6989586621679924810], [a6989586621679924810]) -> *)

data GenericSplitAtSym1 (l :: i6989586621679924809) (l :: TyFun [a6989586621679924810] ([a6989586621679924810], [a6989586621679924810])) Source #

Instances
SuppressUnusedWarnings (GenericSplitAtSym1 :: i6989586621679924809 -> TyFun [a6989586621679924810] ([a6989586621679924810], [a6989586621679924810]) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericSplitAtSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericSplitAtSym1 l1 :: TyFun [a] ([a], [a]) -> *) (l2 :: [a]) = GenericSplitAt l1 l2

type GenericSplitAtSym2 (t :: i6989586621679924809) (t :: [a6989586621679924810]) = GenericSplitAt t t Source #

data GenericIndexSym0 (l :: TyFun [a6989586621679924808] (TyFun i6989586621679924807 a6989586621679924808 -> Type)) Source #

Instances
SuppressUnusedWarnings (GenericIndexSym0 :: TyFun [a6989586621679924808] (TyFun i6989586621679924807 a6989586621679924808 -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericIndexSym0 :: TyFun [a6989586621679924808] (TyFun i6989586621679924807 a6989586621679924808 -> Type) -> *) (l :: [a6989586621679924808]) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericIndexSym0 :: TyFun [a6989586621679924808] (TyFun i6989586621679924807 a6989586621679924808 -> Type) -> *) (l :: [a6989586621679924808]) = (GenericIndexSym1 l :: TyFun i6989586621679924807 a6989586621679924808 -> *)

data GenericIndexSym1 (l :: [a6989586621679924808]) (l :: TyFun i6989586621679924807 a6989586621679924808) Source #

Instances
SuppressUnusedWarnings (GenericIndexSym1 :: [a6989586621679924808] -> TyFun i6989586621679924807 a6989586621679924808 -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericIndexSym1 l1 :: TyFun i a -> *) (l2 :: i) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericIndexSym1 l1 :: TyFun i a -> *) (l2 :: i) = GenericIndex l1 l2

type GenericIndexSym2 (t :: [a6989586621679924808]) (t :: i6989586621679924807) = GenericIndex t t Source #

data GenericReplicateSym0 (l :: TyFun i6989586621679924805 (TyFun a6989586621679924806 [a6989586621679924806] -> Type)) Source #

Instances
SuppressUnusedWarnings (GenericReplicateSym0 :: TyFun i6989586621679924805 (TyFun a6989586621679924806 [a6989586621679924806] -> Type) -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericReplicateSym0 :: TyFun i6989586621679924805 (TyFun a6989586621679924806 [a6989586621679924806] -> Type) -> *) (l :: i6989586621679924805) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericReplicateSym0 :: TyFun i6989586621679924805 (TyFun a6989586621679924806 [a6989586621679924806] -> Type) -> *) (l :: i6989586621679924805) = (GenericReplicateSym1 l :: TyFun a6989586621679924806 [a6989586621679924806] -> *)

data GenericReplicateSym1 (l :: i6989586621679924805) (l :: TyFun a6989586621679924806 [a6989586621679924806]) Source #

Instances
SuppressUnusedWarnings (GenericReplicateSym1 :: i6989586621679924805 -> TyFun a6989586621679924806 [a6989586621679924806] -> *) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericReplicateSym1 l1 :: TyFun a [a] -> *) (l2 :: a) Source # 
Instance details

Defined in Data.Promotion.Prelude.List

type Apply (GenericReplicateSym1 l1 :: TyFun a [a] -> *) (l2 :: a) = GenericReplicate l1 l2

type GenericReplicateSym2 (t :: i6989586621679924805) (t :: a6989586621679924806) = GenericReplicate t t Source #