Copyright | (C) 2014 Jan Stolarek |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Jan Stolarek (jan.stolarek@p.lodz.pl) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
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.
- 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 ...
- any_ :: (a -> Bool) -> [a] -> Bool
- 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 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 :: [a6989586621679244031]) (t :: [a6989586621679244031]) = (:++) t t
- data (l :: [a6989586621679244031]) :++$$ (l :: TyFun [a6989586621679244031] [a6989586621679244031])
- data (:++$) (l :: TyFun [a6989586621679244031] (TyFun [a6989586621679244031] [a6989586621679244031] -> Type))
- data HeadSym0 (l :: TyFun [a6989586621679389348] a6989586621679389348)
- type HeadSym1 (t :: [a6989586621679389348]) = Head t
- data LastSym0 (l :: TyFun [a6989586621679389347] a6989586621679389347)
- type LastSym1 (t :: [a6989586621679389347]) = Last t
- data TailSym0 (l :: TyFun [a6989586621679389346] [a6989586621679389346])
- type TailSym1 (t :: [a6989586621679389346]) = Tail t
- data InitSym0 (l :: TyFun [a6989586621679389345] [a6989586621679389345])
- type InitSym1 (t :: [a6989586621679389345]) = Init t
- data NullSym0 (l :: TyFun [a6989586621679389344] Bool)
- type NullSym1 (t :: [a6989586621679389344]) = Null t
- data MapSym0 (l :: TyFun (TyFun a6989586621679244032 b6989586621679244033 -> Type) (TyFun [a6989586621679244032] [b6989586621679244033] -> Type))
- data MapSym1 (l :: TyFun a6989586621679244032 b6989586621679244033 -> Type) (l :: TyFun [a6989586621679244032] [b6989586621679244033])
- type MapSym2 (t :: TyFun a6989586621679244032 b6989586621679244033 -> Type) (t :: [a6989586621679244032]) = Map t t
- data ReverseSym0 (l :: TyFun [a6989586621679389343] [a6989586621679389343])
- type ReverseSym1 (t :: [a6989586621679389343]) = Reverse t
- data IntersperseSym0 (l :: TyFun a6989586621679389342 (TyFun [a6989586621679389342] [a6989586621679389342] -> Type))
- data IntersperseSym1 (l :: a6989586621679389342) (l :: TyFun [a6989586621679389342] [a6989586621679389342])
- type IntersperseSym2 (t :: a6989586621679389342) (t :: [a6989586621679389342]) = Intersperse t t
- data IntercalateSym0 (l :: TyFun [a6989586621679389341] (TyFun [[a6989586621679389341]] [a6989586621679389341] -> Type))
- data IntercalateSym1 (l :: [a6989586621679389341]) (l :: TyFun [[a6989586621679389341]] [a6989586621679389341])
- type IntercalateSym2 (t :: [a6989586621679389341]) (t :: [[a6989586621679389341]]) = Intercalate t t
- data SubsequencesSym0 (l :: TyFun [a6989586621679389340] [[a6989586621679389340]])
- type SubsequencesSym1 (t :: [a6989586621679389340]) = Subsequences t
- data PermutationsSym0 (l :: TyFun [a6989586621679389337] [[a6989586621679389337]])
- type PermutationsSym1 (t :: [a6989586621679389337]) = Permutations t
- data FoldlSym0 (l :: TyFun (TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type) -> Type))
- data FoldlSym1 (l :: TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (l :: TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type))
- data FoldlSym2 (l :: TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (l :: b6989586621679213673) (l :: TyFun [a6989586621679213672] b6989586621679213673)
- type FoldlSym3 (t :: TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (t :: b6989586621679213673) (t :: [a6989586621679213672]) = Foldl t t t
- data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) (TyFun b6989586621679389336 (TyFun [a6989586621679389335] b6989586621679389336 -> Type) -> Type))
- data Foldl'Sym1 (l :: TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) (l :: TyFun b6989586621679389336 (TyFun [a6989586621679389335] b6989586621679389336 -> Type))
- data Foldl'Sym2 (l :: TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) (l :: b6989586621679389336) (l :: TyFun [a6989586621679389335] b6989586621679389336)
- type Foldl'Sym3 (t :: TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) (t :: b6989586621679389336) (t :: [a6989586621679389335]) = Foldl' t t t
- data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679389334 (TyFun a6989586621679389334 a6989586621679389334 -> Type) -> Type) (TyFun [a6989586621679389334] a6989586621679389334 -> Type))
- data Foldl1Sym1 (l :: TyFun a6989586621679389334 (TyFun a6989586621679389334 a6989586621679389334 -> Type) -> Type) (l :: TyFun [a6989586621679389334] a6989586621679389334)
- type Foldl1Sym2 (t :: TyFun a6989586621679389334 (TyFun a6989586621679389334 a6989586621679389334 -> Type) -> Type) (t :: [a6989586621679389334]) = Foldl1 t t
- data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679389333 (TyFun a6989586621679389333 a6989586621679389333 -> Type) -> Type) (TyFun [a6989586621679389333] a6989586621679389333 -> Type))
- data Foldl1'Sym1 (l :: TyFun a6989586621679389333 (TyFun a6989586621679389333 a6989586621679389333 -> Type) -> Type) (l :: TyFun [a6989586621679389333] a6989586621679389333)
- type Foldl1'Sym2 (t :: TyFun a6989586621679389333 (TyFun a6989586621679389333 a6989586621679389333 -> Type) -> Type) (t :: [a6989586621679389333]) = Foldl1' t t
- data FoldrSym0 (l :: TyFun (TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) (TyFun b6989586621679244035 (TyFun [a6989586621679244034] b6989586621679244035 -> Type) -> Type))
- data FoldrSym1 (l :: TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) (l :: TyFun b6989586621679244035 (TyFun [a6989586621679244034] b6989586621679244035 -> Type))
- data FoldrSym2 (l :: TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) (l :: b6989586621679244035) (l :: TyFun [a6989586621679244034] b6989586621679244035)
- type FoldrSym3 (t :: TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) (t :: b6989586621679244035) (t :: [a6989586621679244034]) = Foldr t t t
- data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679389332 (TyFun a6989586621679389332 a6989586621679389332 -> Type) -> Type) (TyFun [a6989586621679389332] a6989586621679389332 -> Type))
- data Foldr1Sym1 (l :: TyFun a6989586621679389332 (TyFun a6989586621679389332 a6989586621679389332 -> Type) -> Type) (l :: TyFun [a6989586621679389332] a6989586621679389332)
- type Foldr1Sym2 (t :: TyFun a6989586621679389332 (TyFun a6989586621679389332 a6989586621679389332 -> Type) -> Type) (t :: [a6989586621679389332]) = Foldr1 t t
- data ConcatSym0 (l :: TyFun [[a6989586621679389331]] [a6989586621679389331])
- type ConcatSym1 (t :: [[a6989586621679389331]]) = Concat t
- data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679389329 [b6989586621679389330] -> Type) (TyFun [a6989586621679389329] [b6989586621679389330] -> Type))
- data ConcatMapSym1 (l :: TyFun a6989586621679389329 [b6989586621679389330] -> Type) (l :: TyFun [a6989586621679389329] [b6989586621679389330])
- type ConcatMapSym2 (t :: TyFun a6989586621679389329 [b6989586621679389330] -> Type) (t :: [a6989586621679389329]) = 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 Any_Sym0 (l :: TyFun (TyFun a6989586621679379112 Bool -> Type) (TyFun [a6989586621679379112] Bool -> Type))
- data Any_Sym1 (l :: TyFun a6989586621679379112 Bool -> Type) (l :: TyFun [a6989586621679379112] Bool)
- type Any_Sym2 (t :: TyFun a6989586621679379112 Bool -> Type) (t :: [a6989586621679379112]) = Any_ t t
- data AllSym0 (l :: TyFun (TyFun a6989586621679389328 Bool -> Type) (TyFun [a6989586621679389328] Bool -> Type))
- data AllSym1 (l :: TyFun a6989586621679389328 Bool -> Type) (l :: TyFun [a6989586621679389328] Bool)
- type AllSym2 (t :: TyFun a6989586621679389328 Bool -> Type) (t :: [a6989586621679389328]) = All t t
- data ScanlSym0 (l :: TyFun (TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) (TyFun b6989586621679389326 (TyFun [a6989586621679389327] [b6989586621679389326] -> Type) -> Type))
- data ScanlSym1 (l :: TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) (l :: TyFun b6989586621679389326 (TyFun [a6989586621679389327] [b6989586621679389326] -> Type))
- data ScanlSym2 (l :: TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) (l :: b6989586621679389326) (l :: TyFun [a6989586621679389327] [b6989586621679389326])
- type ScanlSym3 (t :: TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) (t :: b6989586621679389326) (t :: [a6989586621679389327]) = Scanl t t t
- data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679389325 (TyFun a6989586621679389325 a6989586621679389325 -> Type) -> Type) (TyFun [a6989586621679389325] [a6989586621679389325] -> Type))
- data Scanl1Sym1 (l :: TyFun a6989586621679389325 (TyFun a6989586621679389325 a6989586621679389325 -> Type) -> Type) (l :: TyFun [a6989586621679389325] [a6989586621679389325])
- type Scanl1Sym2 (t :: TyFun a6989586621679389325 (TyFun a6989586621679389325 a6989586621679389325 -> Type) -> Type) (t :: [a6989586621679389325]) = Scanl1 t t
- data ScanrSym0 (l :: TyFun (TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) (TyFun b6989586621679389324 (TyFun [a6989586621679389323] [b6989586621679389324] -> Type) -> Type))
- data ScanrSym1 (l :: TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) (l :: TyFun b6989586621679389324 (TyFun [a6989586621679389323] [b6989586621679389324] -> Type))
- data ScanrSym2 (l :: TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) (l :: b6989586621679389324) (l :: TyFun [a6989586621679389323] [b6989586621679389324])
- type ScanrSym3 (t :: TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) (t :: b6989586621679389324) (t :: [a6989586621679389323]) = Scanr t t t
- data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679389322 (TyFun a6989586621679389322 a6989586621679389322 -> Type) -> Type) (TyFun [a6989586621679389322] [a6989586621679389322] -> Type))
- data Scanr1Sym1 (l :: TyFun a6989586621679389322 (TyFun a6989586621679389322 a6989586621679389322 -> Type) -> Type) (l :: TyFun [a6989586621679389322] [a6989586621679389322])
- type Scanr1Sym2 (t :: TyFun a6989586621679389322 (TyFun a6989586621679389322 a6989586621679389322 -> Type) -> Type) (t :: [a6989586621679389322]) = Scanr1 t t
- data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) (TyFun acc6989586621679389319 (TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]) -> Type) -> Type))
- data MapAccumLSym1 (l :: TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) (l :: TyFun acc6989586621679389319 (TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]) -> Type))
- data MapAccumLSym2 (l :: TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) (l :: acc6989586621679389319) (l :: TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]))
- type MapAccumLSym3 (t :: TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) (t :: acc6989586621679389319) (t :: [x6989586621679389320]) = MapAccumL t t t
- data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) (TyFun acc6989586621679389316 (TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]) -> Type) -> Type))
- data MapAccumRSym1 (l :: TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) (l :: TyFun acc6989586621679389316 (TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]) -> Type))
- data MapAccumRSym2 (l :: TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) (l :: acc6989586621679389316) (l :: TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]))
- type MapAccumRSym3 (t :: TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) (t :: acc6989586621679389316) (t :: [x6989586621679389317]) = MapAccumR t t t
- data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679389314 (Maybe (a6989586621679389315, b6989586621679389314)) -> Type) (TyFun b6989586621679389314 [a6989586621679389315] -> Type))
- data UnfoldrSym1 (l :: TyFun b6989586621679389314 (Maybe (a6989586621679389315, b6989586621679389314)) -> Type) (l :: TyFun b6989586621679389314 [a6989586621679389315])
- type UnfoldrSym2 (t :: TyFun b6989586621679389314 (Maybe (a6989586621679389315, b6989586621679389314)) -> Type) (t :: b6989586621679389314) = Unfoldr t t
- data InitsSym0 (l :: TyFun [a6989586621679389313] [[a6989586621679389313]])
- type InitsSym1 (t :: [a6989586621679389313]) = Inits t
- data TailsSym0 (l :: TyFun [a6989586621679389312] [[a6989586621679389312]])
- type TailsSym1 (t :: [a6989586621679389312]) = Tails t
- data IsPrefixOfSym0 (l :: TyFun [a6989586621679389311] (TyFun [a6989586621679389311] Bool -> Type))
- data IsPrefixOfSym1 (l :: [a6989586621679389311]) (l :: TyFun [a6989586621679389311] Bool)
- type IsPrefixOfSym2 (t :: [a6989586621679389311]) (t :: [a6989586621679389311]) = IsPrefixOf t t
- data IsSuffixOfSym0 (l :: TyFun [a6989586621679389310] (TyFun [a6989586621679389310] Bool -> Type))
- data IsSuffixOfSym1 (l :: [a6989586621679389310]) (l :: TyFun [a6989586621679389310] Bool)
- type IsSuffixOfSym2 (t :: [a6989586621679389310]) (t :: [a6989586621679389310]) = IsSuffixOf t t
- data IsInfixOfSym0 (l :: TyFun [a6989586621679389309] (TyFun [a6989586621679389309] Bool -> Type))
- data IsInfixOfSym1 (l :: [a6989586621679389309]) (l :: TyFun [a6989586621679389309] Bool)
- type IsInfixOfSym2 (t :: [a6989586621679389309]) (t :: [a6989586621679389309]) = IsInfixOf t t
- data ElemSym0 (l :: TyFun a6989586621679389308 (TyFun [a6989586621679389308] Bool -> Type))
- data ElemSym1 (l :: a6989586621679389308) (l :: TyFun [a6989586621679389308] Bool)
- type ElemSym2 (t :: a6989586621679389308) (t :: [a6989586621679389308]) = Elem t t
- data NotElemSym0 (l :: TyFun a6989586621679389307 (TyFun [a6989586621679389307] Bool -> Type))
- data NotElemSym1 (l :: a6989586621679389307) (l :: TyFun [a6989586621679389307] Bool)
- type NotElemSym2 (t :: a6989586621679389307) (t :: [a6989586621679389307]) = NotElem t t
- data ZipSym0 (l :: TyFun [a6989586621679389305] (TyFun [b6989586621679389306] [(a6989586621679389305, b6989586621679389306)] -> Type))
- data ZipSym1 (l :: [a6989586621679389305]) (l :: TyFun [b6989586621679389306] [(a6989586621679389305, b6989586621679389306)])
- type ZipSym2 (t :: [a6989586621679389305]) (t :: [b6989586621679389306]) = Zip t t
- data Zip3Sym0 (l :: TyFun [a6989586621679389302] (TyFun [b6989586621679389303] (TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)] -> Type) -> Type))
- data Zip3Sym1 (l :: [a6989586621679389302]) (l :: TyFun [b6989586621679389303] (TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)] -> Type))
- data Zip3Sym2 (l :: [a6989586621679389302]) (l :: [b6989586621679389303]) (l :: TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)])
- type Zip3Sym3 (t :: [a6989586621679389302]) (t :: [b6989586621679389303]) (t :: [c6989586621679389304]) = Zip3 t t t
- data ZipWithSym0 (l :: TyFun (TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) (TyFun [a6989586621679389299] (TyFun [b6989586621679389300] [c6989586621679389301] -> Type) -> Type))
- data ZipWithSym1 (l :: TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) (l :: TyFun [a6989586621679389299] (TyFun [b6989586621679389300] [c6989586621679389301] -> Type))
- data ZipWithSym2 (l :: TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) (l :: [a6989586621679389299]) (l :: TyFun [b6989586621679389300] [c6989586621679389301])
- type ZipWithSym3 (t :: TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) (t :: [a6989586621679389299]) (t :: [b6989586621679389300]) = ZipWith t t t
- data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (TyFun [a6989586621679389295] (TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) -> Type) -> Type))
- data ZipWith3Sym1 (l :: TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679389295] (TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) -> Type))
- data ZipWith3Sym2 (l :: TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (l :: [a6989586621679389295]) (l :: TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type))
- data ZipWith3Sym3 (l :: TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (l :: [a6989586621679389295]) (l :: [b6989586621679389296]) (l :: TyFun [c6989586621679389297] [d6989586621679389298])
- type ZipWith3Sym4 (t :: TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (t :: [a6989586621679389295]) (t :: [b6989586621679389296]) (t :: [c6989586621679389297]) = ZipWith3 t t t t
- data UnzipSym0 (l :: TyFun [(a6989586621679389293, b6989586621679389294)] ([a6989586621679389293], [b6989586621679389294]))
- type UnzipSym1 (t :: [(a6989586621679389293, b6989586621679389294)]) = Unzip t
- data Unzip3Sym0 (l :: TyFun [(a6989586621679389290, b6989586621679389291, c6989586621679389292)] ([a6989586621679389290], [b6989586621679389291], [c6989586621679389292]))
- type Unzip3Sym1 (t :: [(a6989586621679389290, b6989586621679389291, c6989586621679389292)]) = Unzip3 t
- data Unzip4Sym0 (l :: TyFun [(a6989586621679389286, b6989586621679389287, c6989586621679389288, d6989586621679389289)] ([a6989586621679389286], [b6989586621679389287], [c6989586621679389288], [d6989586621679389289]))
- type Unzip4Sym1 (t :: [(a6989586621679389286, b6989586621679389287, c6989586621679389288, d6989586621679389289)]) = Unzip4 t
- data Unzip5Sym0 (l :: TyFun [(a6989586621679389281, b6989586621679389282, c6989586621679389283, d6989586621679389284, e6989586621679389285)] ([a6989586621679389281], [b6989586621679389282], [c6989586621679389283], [d6989586621679389284], [e6989586621679389285]))
- type Unzip5Sym1 (t :: [(a6989586621679389281, b6989586621679389282, c6989586621679389283, d6989586621679389284, e6989586621679389285)]) = Unzip5 t
- data Unzip6Sym0 (l :: TyFun [(a6989586621679389275, b6989586621679389276, c6989586621679389277, d6989586621679389278, e6989586621679389279, f6989586621679389280)] ([a6989586621679389275], [b6989586621679389276], [c6989586621679389277], [d6989586621679389278], [e6989586621679389279], [f6989586621679389280]))
- type Unzip6Sym1 (t :: [(a6989586621679389275, b6989586621679389276, c6989586621679389277, d6989586621679389278, e6989586621679389279, f6989586621679389280)]) = Unzip6 t
- data Unzip7Sym0 (l :: TyFun [(a6989586621679389268, b6989586621679389269, c6989586621679389270, d6989586621679389271, e6989586621679389272, f6989586621679389273, g6989586621679389274)] ([a6989586621679389268], [b6989586621679389269], [c6989586621679389270], [d6989586621679389271], [e6989586621679389272], [f6989586621679389273], [g6989586621679389274]))
- type Unzip7Sym1 (t :: [(a6989586621679389268, b6989586621679389269, c6989586621679389270, d6989586621679389271, e6989586621679389272, f6989586621679389273, g6989586621679389274)]) = Unzip7 t
- data DeleteSym0 (l :: TyFun a6989586621679389267 (TyFun [a6989586621679389267] [a6989586621679389267] -> Type))
- data DeleteSym1 (l :: a6989586621679389267) (l :: TyFun [a6989586621679389267] [a6989586621679389267])
- type DeleteSym2 (t :: a6989586621679389267) (t :: [a6989586621679389267]) = Delete t t
- data (:\\$) (l :: TyFun [a6989586621679389266] (TyFun [a6989586621679389266] [a6989586621679389266] -> Type))
- data (l :: [a6989586621679389266]) :\\$$ (l :: TyFun [a6989586621679389266] [a6989586621679389266])
- type (:\\$$$) (t :: [a6989586621679389266]) (t :: [a6989586621679389266]) = (:\\) t t
- data IntersectSym0 (l :: TyFun [a6989586621679389253] (TyFun [a6989586621679389253] [a6989586621679389253] -> Type))
- data IntersectSym1 (l :: [a6989586621679389253]) (l :: TyFun [a6989586621679389253] [a6989586621679389253])
- type IntersectSym2 (t :: [a6989586621679389253]) (t :: [a6989586621679389253]) = Intersect t t
- data InsertSym0 (l :: TyFun a6989586621679389240 (TyFun [a6989586621679389240] [a6989586621679389240] -> Type))
- data InsertSym1 (l :: a6989586621679389240) (l :: TyFun [a6989586621679389240] [a6989586621679389240])
- type InsertSym2 (t :: a6989586621679389240) (t :: [a6989586621679389240]) = Insert t t
- data SortSym0 (l :: TyFun [a6989586621679389239] [a6989586621679389239])
- type SortSym1 (t :: [a6989586621679389239]) = Sort t
- data DeleteBySym0 (l :: TyFun (TyFun a6989586621679389265 (TyFun a6989586621679389265 Bool -> Type) -> Type) (TyFun a6989586621679389265 (TyFun [a6989586621679389265] [a6989586621679389265] -> Type) -> Type))
- data DeleteBySym1 (l :: TyFun a6989586621679389265 (TyFun a6989586621679389265 Bool -> Type) -> Type) (l :: TyFun a6989586621679389265 (TyFun [a6989586621679389265] [a6989586621679389265] -> Type))
- data DeleteBySym2 (l :: TyFun a6989586621679389265 (TyFun a6989586621679389265 Bool -> Type) -> Type) (l :: a6989586621679389265) (l :: TyFun [a6989586621679389265] [a6989586621679389265])
- type DeleteBySym3 (t :: TyFun a6989586621679389265 (TyFun a6989586621679389265 Bool -> Type) -> Type) (t :: a6989586621679389265) (t :: [a6989586621679389265]) = DeleteBy t t t
- data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679389264 (TyFun a6989586621679389264 Bool -> Type) -> Type) (TyFun [a6989586621679389264] (TyFun [a6989586621679389264] [a6989586621679389264] -> Type) -> Type))
- data DeleteFirstsBySym1 (l :: TyFun a6989586621679389264 (TyFun a6989586621679389264 Bool -> Type) -> Type) (l :: TyFun [a6989586621679389264] (TyFun [a6989586621679389264] [a6989586621679389264] -> Type))
- data DeleteFirstsBySym2 (l :: TyFun a6989586621679389264 (TyFun a6989586621679389264 Bool -> Type) -> Type) (l :: [a6989586621679389264]) (l :: TyFun [a6989586621679389264] [a6989586621679389264])
- type DeleteFirstsBySym3 (t :: TyFun a6989586621679389264 (TyFun a6989586621679389264 Bool -> Type) -> Type) (t :: [a6989586621679389264]) (t :: [a6989586621679389264]) = DeleteFirstsBy t t t
- data IntersectBySym0 (l :: TyFun (TyFun a6989586621679389252 (TyFun a6989586621679389252 Bool -> Type) -> Type) (TyFun [a6989586621679389252] (TyFun [a6989586621679389252] [a6989586621679389252] -> Type) -> Type))
- data IntersectBySym1 (l :: TyFun a6989586621679389252 (TyFun a6989586621679389252 Bool -> Type) -> Type) (l :: TyFun [a6989586621679389252] (TyFun [a6989586621679389252] [a6989586621679389252] -> Type))
- data IntersectBySym2 (l :: TyFun a6989586621679389252 (TyFun a6989586621679389252 Bool -> Type) -> Type) (l :: [a6989586621679389252]) (l :: TyFun [a6989586621679389252] [a6989586621679389252])
- data SortBySym0 (l :: TyFun (TyFun a6989586621679389263 (TyFun a6989586621679389263 Ordering -> Type) -> Type) (TyFun [a6989586621679389263] [a6989586621679389263] -> Type))
- data SortBySym1 (l :: TyFun a6989586621679389263 (TyFun a6989586621679389263 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679389263] [a6989586621679389263])
- type SortBySym2 (t :: TyFun a6989586621679389263 (TyFun a6989586621679389263 Ordering -> Type) -> Type) (t :: [a6989586621679389263]) = SortBy t t
- data InsertBySym0 (l :: TyFun (TyFun a6989586621679389262 (TyFun a6989586621679389262 Ordering -> Type) -> Type) (TyFun a6989586621679389262 (TyFun [a6989586621679389262] [a6989586621679389262] -> Type) -> Type))
- data InsertBySym1 (l :: TyFun a6989586621679389262 (TyFun a6989586621679389262 Ordering -> Type) -> Type) (l :: TyFun a6989586621679389262 (TyFun [a6989586621679389262] [a6989586621679389262] -> Type))
- data InsertBySym2 (l :: TyFun a6989586621679389262 (TyFun a6989586621679389262 Ordering -> Type) -> Type) (l :: a6989586621679389262) (l :: TyFun [a6989586621679389262] [a6989586621679389262])
- type InsertBySym3 (t :: TyFun a6989586621679389262 (TyFun a6989586621679389262 Ordering -> Type) -> Type) (t :: a6989586621679389262) (t :: [a6989586621679389262]) = InsertBy t t t
- data MaximumBySym0 (l :: TyFun (TyFun a6989586621679389261 (TyFun a6989586621679389261 Ordering -> Type) -> Type) (TyFun [a6989586621679389261] a6989586621679389261 -> Type))
- data MaximumBySym1 (l :: TyFun a6989586621679389261 (TyFun a6989586621679389261 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679389261] a6989586621679389261)
- type MaximumBySym2 (t :: TyFun a6989586621679389261 (TyFun a6989586621679389261 Ordering -> Type) -> Type) (t :: [a6989586621679389261]) = MaximumBy t t
- data MinimumBySym0 (l :: TyFun (TyFun a6989586621679389260 (TyFun a6989586621679389260 Ordering -> Type) -> Type) (TyFun [a6989586621679389260] a6989586621679389260 -> Type))
- data MinimumBySym1 (l :: TyFun a6989586621679389260 (TyFun a6989586621679389260 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679389260] a6989586621679389260)
- type MinimumBySym2 (t :: TyFun a6989586621679389260 (TyFun a6989586621679389260 Ordering -> Type) -> Type) (t :: [a6989586621679389260]) = MinimumBy t t
- data LengthSym0 (l :: TyFun [a6989586621679389231] Nat)
- type LengthSym1 (t :: [a6989586621679389231]) = Length t
- data SumSym0 (l :: TyFun [a6989586621679389233] a6989586621679389233)
- type SumSym1 (t :: [a6989586621679389233]) = Sum t
- data ProductSym0 (l :: TyFun [a6989586621679389232] a6989586621679389232)
- type ProductSym1 (t :: [a6989586621679389232]) = Product t
- data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679389230 [a6989586621679389230] -> Type))
- data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679389230 [a6989586621679389230])
- type ReplicateSym2 (t :: Nat) (t :: a6989586621679389230) = Replicate t t
- data TransposeSym0 (l :: TyFun [[a6989586621679389229]] [[a6989586621679389229]])
- type TransposeSym1 (t :: [[a6989586621679389229]]) = Transpose t
- data TakeSym0 (l :: TyFun Nat (TyFun [a6989586621679389246] [a6989586621679389246] -> Type))
- data TakeSym1 (l :: Nat) (l :: TyFun [a6989586621679389246] [a6989586621679389246])
- type TakeSym2 (t :: Nat) (t :: [a6989586621679389246]) = Take t t
- data DropSym0 (l :: TyFun Nat (TyFun [a6989586621679389245] [a6989586621679389245] -> Type))
- data DropSym1 (l :: Nat) (l :: TyFun [a6989586621679389245] [a6989586621679389245])
- type DropSym2 (t :: Nat) (t :: [a6989586621679389245]) = Drop t t
- data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679389244] ([a6989586621679389244], [a6989586621679389244]) -> Type))
- data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679389244] ([a6989586621679389244], [a6989586621679389244]))
- type SplitAtSym2 (t :: Nat) (t :: [a6989586621679389244]) = SplitAt t t
- data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679389251 Bool -> Type) (TyFun [a6989586621679389251] [a6989586621679389251] -> Type))
- data TakeWhileSym1 (l :: TyFun a6989586621679389251 Bool -> Type) (l :: TyFun [a6989586621679389251] [a6989586621679389251])
- type TakeWhileSym2 (t :: TyFun a6989586621679389251 Bool -> Type) (t :: [a6989586621679389251]) = TakeWhile t t
- data DropWhileSym0 (l :: TyFun (TyFun a6989586621679389250 Bool -> Type) (TyFun [a6989586621679389250] [a6989586621679389250] -> Type))
- data DropWhileSym1 (l :: TyFun a6989586621679389250 Bool -> Type) (l :: TyFun [a6989586621679389250] [a6989586621679389250])
- type DropWhileSym2 (t :: TyFun a6989586621679389250 Bool -> Type) (t :: [a6989586621679389250]) = DropWhile t t
- data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679389249 Bool -> Type) (TyFun [a6989586621679389249] [a6989586621679389249] -> Type))
- data DropWhileEndSym1 (l :: TyFun a6989586621679389249 Bool -> Type) (l :: TyFun [a6989586621679389249] [a6989586621679389249])
- type DropWhileEndSym2 (t :: TyFun a6989586621679389249 Bool -> Type) (t :: [a6989586621679389249]) = DropWhileEnd t t
- data SpanSym0 (l :: TyFun (TyFun a6989586621679389248 Bool -> Type) (TyFun [a6989586621679389248] ([a6989586621679389248], [a6989586621679389248]) -> Type))
- data SpanSym1 (l :: TyFun a6989586621679389248 Bool -> Type) (l :: TyFun [a6989586621679389248] ([a6989586621679389248], [a6989586621679389248]))
- type SpanSym2 (t :: TyFun a6989586621679389248 Bool -> Type) (t :: [a6989586621679389248]) = Span t t
- data BreakSym0 (l :: TyFun (TyFun a6989586621679389247 Bool -> Type) (TyFun [a6989586621679389247] ([a6989586621679389247], [a6989586621679389247]) -> Type))
- data BreakSym1 (l :: TyFun a6989586621679389247 Bool -> Type) (l :: TyFun [a6989586621679389247] ([a6989586621679389247], [a6989586621679389247]))
- type BreakSym2 (t :: TyFun a6989586621679389247 Bool -> Type) (t :: [a6989586621679389247]) = Break t t
- data StripPrefixSym0 (l :: TyFun [a6989586621679727944] (TyFun [a6989586621679727944] (Maybe [a6989586621679727944]) -> Type))
- data StripPrefixSym1 (l :: [a6989586621679727944]) (l :: TyFun [a6989586621679727944] (Maybe [a6989586621679727944]))
- type StripPrefixSym2 (t :: [a6989586621679727944]) (t :: [a6989586621679727944]) = StripPrefix t t
- data MaximumSym0 (l :: TyFun [a6989586621679389242] a6989586621679389242)
- type MaximumSym1 (t :: [a6989586621679389242]) = Maximum t
- data MinimumSym0 (l :: TyFun [a6989586621679389241] a6989586621679389241)
- type MinimumSym1 (t :: [a6989586621679389241]) = Minimum t
- data GroupSym0 (l :: TyFun [a6989586621679389243] [[a6989586621679389243]])
- type GroupSym1 (t :: [a6989586621679389243]) = Group t
- data GroupBySym0 (l :: TyFun (TyFun a6989586621679389238 (TyFun a6989586621679389238 Bool -> Type) -> Type) (TyFun [a6989586621679389238] [[a6989586621679389238]] -> Type))
- data GroupBySym1 (l :: TyFun a6989586621679389238 (TyFun a6989586621679389238 Bool -> Type) -> Type) (l :: TyFun [a6989586621679389238] [[a6989586621679389238]])
- type GroupBySym2 (t :: TyFun a6989586621679389238 (TyFun a6989586621679389238 Bool -> Type) -> Type) (t :: [a6989586621679389238]) = GroupBy t t
- data LookupSym0 (l :: TyFun a6989586621679389236 (TyFun [(a6989586621679389236, b6989586621679389237)] (Maybe b6989586621679389237) -> Type))
- data LookupSym1 (l :: a6989586621679389236) (l :: TyFun [(a6989586621679389236, b6989586621679389237)] (Maybe b6989586621679389237))
- type LookupSym2 (t :: a6989586621679389236) (t :: [(a6989586621679389236, b6989586621679389237)]) = Lookup t t
- data FindSym0 (l :: TyFun (TyFun a6989586621679389258 Bool -> Type) (TyFun [a6989586621679389258] (Maybe a6989586621679389258) -> Type))
- data FindSym1 (l :: TyFun a6989586621679389258 Bool -> Type) (l :: TyFun [a6989586621679389258] (Maybe a6989586621679389258))
- type FindSym2 (t :: TyFun a6989586621679389258 Bool -> Type) (t :: [a6989586621679389258]) = Find t t
- data FilterSym0 (l :: TyFun (TyFun a6989586621679389259 Bool -> Type) (TyFun [a6989586621679389259] [a6989586621679389259] -> Type))
- data FilterSym1 (l :: TyFun a6989586621679389259 Bool -> Type) (l :: TyFun [a6989586621679389259] [a6989586621679389259])
- type FilterSym2 (t :: TyFun a6989586621679389259 Bool -> Type) (t :: [a6989586621679389259]) = Filter t t
- data PartitionSym0 (l :: TyFun (TyFun a6989586621679389235 Bool -> Type) (TyFun [a6989586621679389235] ([a6989586621679389235], [a6989586621679389235]) -> Type))
- data PartitionSym1 (l :: TyFun a6989586621679389235 Bool -> Type) (l :: TyFun [a6989586621679389235] ([a6989586621679389235], [a6989586621679389235]))
- type PartitionSym2 (t :: TyFun a6989586621679389235 Bool -> Type) (t :: [a6989586621679389235]) = Partition t t
- data (:!!$) (l :: TyFun [a6989586621679389228] (TyFun Nat a6989586621679389228 -> Type))
- data (l :: [a6989586621679389228]) :!!$$ (l :: TyFun Nat a6989586621679389228)
- type (:!!$$$) (t :: [a6989586621679389228]) (t :: Nat) = (:!!) t t
- data ElemIndexSym0 (l :: TyFun a6989586621679389257 (TyFun [a6989586621679389257] (Maybe Nat) -> Type))
- data ElemIndexSym1 (l :: a6989586621679389257) (l :: TyFun [a6989586621679389257] (Maybe Nat))
- type ElemIndexSym2 (t :: a6989586621679389257) (t :: [a6989586621679389257]) = ElemIndex t t
- data ElemIndicesSym0 (l :: TyFun a6989586621679389256 (TyFun [a6989586621679389256] [Nat] -> Type))
- data ElemIndicesSym1 (l :: a6989586621679389256) (l :: TyFun [a6989586621679389256] [Nat])
- type ElemIndicesSym2 (t :: a6989586621679389256) (t :: [a6989586621679389256]) = ElemIndices t t
- data FindIndexSym0 (l :: TyFun (TyFun a6989586621679389255 Bool -> Type) (TyFun [a6989586621679389255] (Maybe Nat) -> Type))
- data FindIndexSym1 (l :: TyFun a6989586621679389255 Bool -> Type) (l :: TyFun [a6989586621679389255] (Maybe Nat))
- type FindIndexSym2 (t :: TyFun a6989586621679389255 Bool -> Type) (t :: [a6989586621679389255]) = FindIndex t t
- data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679389254 Bool -> Type) (TyFun [a6989586621679389254] [Nat] -> Type))
- data FindIndicesSym1 (l :: TyFun a6989586621679389254 Bool -> Type) (l :: TyFun [a6989586621679389254] [Nat])
- type FindIndicesSym2 (t :: TyFun a6989586621679389254 Bool -> Type) (t :: [a6989586621679389254]) = FindIndices t t
- data Zip4Sym0 (l :: TyFun [a6989586621679727940] (TyFun [b6989586621679727941] (TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) -> Type) -> Type))
- data Zip4Sym1 (l :: [a6989586621679727940]) (l :: TyFun [b6989586621679727941] (TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) -> Type))
- data Zip4Sym2 (l :: [a6989586621679727940]) (l :: [b6989586621679727941]) (l :: TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type))
- data Zip4Sym3 (l :: [a6989586621679727940]) (l :: [b6989586621679727941]) (l :: [c6989586621679727942]) (l :: TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)])
- type Zip4Sym4 (t :: [a6989586621679727940]) (t :: [b6989586621679727941]) (t :: [c6989586621679727942]) (t :: [d6989586621679727943]) = Zip4 t t t t
- data Zip5Sym0 (l :: TyFun [a6989586621679727935] (TyFun [b6989586621679727936] (TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) -> Type) -> Type))
- data Zip5Sym1 (l :: [a6989586621679727935]) (l :: TyFun [b6989586621679727936] (TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) -> Type))
- data Zip5Sym2 (l :: [a6989586621679727935]) (l :: [b6989586621679727936]) (l :: TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type))
- data Zip5Sym3 (l :: [a6989586621679727935]) (l :: [b6989586621679727936]) (l :: [c6989586621679727937]) (l :: TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type))
- data Zip5Sym4 (l :: [a6989586621679727935]) (l :: [b6989586621679727936]) (l :: [c6989586621679727937]) (l :: [d6989586621679727938]) (l :: TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)])
- type Zip5Sym5 (t :: [a6989586621679727935]) (t :: [b6989586621679727936]) (t :: [c6989586621679727937]) (t :: [d6989586621679727938]) (t :: [e6989586621679727939]) = Zip5 t t t t t
- data Zip6Sym0 (l :: TyFun [a6989586621679727929] (TyFun [b6989586621679727930] (TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) -> Type) -> Type))
- data Zip6Sym1 (l :: [a6989586621679727929]) (l :: TyFun [b6989586621679727930] (TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) -> Type))
- data Zip6Sym2 (l :: [a6989586621679727929]) (l :: [b6989586621679727930]) (l :: TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type))
- data Zip6Sym3 (l :: [a6989586621679727929]) (l :: [b6989586621679727930]) (l :: [c6989586621679727931]) (l :: TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type))
- data Zip6Sym4 (l :: [a6989586621679727929]) (l :: [b6989586621679727930]) (l :: [c6989586621679727931]) (l :: [d6989586621679727932]) (l :: TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type))
- data Zip6Sym5 (l :: [a6989586621679727929]) (l :: [b6989586621679727930]) (l :: [c6989586621679727931]) (l :: [d6989586621679727932]) (l :: [e6989586621679727933]) (l :: TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)])
- type Zip6Sym6 (t :: [a6989586621679727929]) (t :: [b6989586621679727930]) (t :: [c6989586621679727931]) (t :: [d6989586621679727932]) (t :: [e6989586621679727933]) (t :: [f6989586621679727934]) = Zip6 t t t t t t
- data Zip7Sym0 (l :: TyFun [a6989586621679727922] (TyFun [b6989586621679727923] (TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type))
- data Zip7Sym1 (l :: [a6989586621679727922]) (l :: TyFun [b6989586621679727923] (TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) -> Type))
- data Zip7Sym2 (l :: [a6989586621679727922]) (l :: [b6989586621679727923]) (l :: TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type))
- data Zip7Sym3 (l :: [a6989586621679727922]) (l :: [b6989586621679727923]) (l :: [c6989586621679727924]) (l :: TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type))
- data Zip7Sym4 (l :: [a6989586621679727922]) (l :: [b6989586621679727923]) (l :: [c6989586621679727924]) (l :: [d6989586621679727925]) (l :: TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type))
- data Zip7Sym5 (l :: [a6989586621679727922]) (l :: [b6989586621679727923]) (l :: [c6989586621679727924]) (l :: [d6989586621679727925]) (l :: [e6989586621679727926]) (l :: TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type))
- data Zip7Sym6 (l :: [a6989586621679727922]) (l :: [b6989586621679727923]) (l :: [c6989586621679727924]) (l :: [d6989586621679727925]) (l :: [e6989586621679727926]) (l :: [f6989586621679727927]) (l :: TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)])
- type Zip7Sym7 (t :: [a6989586621679727922]) (t :: [b6989586621679727923]) (t :: [c6989586621679727924]) (t :: [d6989586621679727925]) (t :: [e6989586621679727926]) (t :: [f6989586621679727927]) (t :: [g6989586621679727928]) = Zip7 t t t t t t t
- data ZipWith4Sym0 (l :: TyFun (TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727917] (TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) -> Type) -> Type))
- data ZipWith4Sym1 (l :: TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679727917] (TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) -> Type))
- data ZipWith4Sym2 (l :: TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727917]) (l :: TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type))
- data ZipWith4Sym3 (l :: TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727917]) (l :: [b6989586621679727918]) (l :: TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type))
- data ZipWith4Sym4 (l :: TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727917]) (l :: [b6989586621679727918]) (l :: [c6989586621679727919]) (l :: TyFun [d6989586621679727920] [e6989586621679727921])
- type ZipWith4Sym5 (t :: TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679727917]) (t :: [b6989586621679727918]) (t :: [c6989586621679727919]) (t :: [d6989586621679727920]) = ZipWith4 t t t t t
- data ZipWith5Sym0 (l :: TyFun (TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727911] (TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) -> Type) -> Type))
- data ZipWith5Sym1 (l :: TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679727911] (TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) -> Type))
- data ZipWith5Sym2 (l :: TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727911]) (l :: TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type))
- data ZipWith5Sym3 (l :: TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727911]) (l :: [b6989586621679727912]) (l :: TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type))
- data ZipWith5Sym4 (l :: TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727911]) (l :: [b6989586621679727912]) (l :: [c6989586621679727913]) (l :: TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type))
- data ZipWith5Sym5 (l :: TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727911]) (l :: [b6989586621679727912]) (l :: [c6989586621679727913]) (l :: [d6989586621679727914]) (l :: TyFun [e6989586621679727915] [f6989586621679727916])
- type ZipWith5Sym6 (t :: TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679727911]) (t :: [b6989586621679727912]) (t :: [c6989586621679727913]) (t :: [d6989586621679727914]) (t :: [e6989586621679727915]) = ZipWith5 t t t t t t
- data ZipWith6Sym0 (l :: TyFun (TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727904] (TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type))
- data ZipWith6Sym1 (l :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679727904] (TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) -> Type))
- data ZipWith6Sym2 (l :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727904]) (l :: TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type))
- data ZipWith6Sym3 (l :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727904]) (l :: [b6989586621679727905]) (l :: TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type))
- data ZipWith6Sym4 (l :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727904]) (l :: [b6989586621679727905]) (l :: [c6989586621679727906]) (l :: TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type))
- data ZipWith6Sym5 (l :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727904]) (l :: [b6989586621679727905]) (l :: [c6989586621679727906]) (l :: [d6989586621679727907]) (l :: TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type))
- data ZipWith6Sym6 (l :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727904]) (l :: [b6989586621679727905]) (l :: [c6989586621679727906]) (l :: [d6989586621679727907]) (l :: [e6989586621679727908]) (l :: TyFun [f6989586621679727909] [g6989586621679727910])
- type ZipWith6Sym7 (t :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679727904]) (t :: [b6989586621679727905]) (t :: [c6989586621679727906]) (t :: [d6989586621679727907]) (t :: [e6989586621679727908]) (t :: [f6989586621679727909]) = ZipWith6 t t t t t t t
- data ZipWith7Sym0 (l :: TyFun (TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727896] (TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type))
- data ZipWith7Sym1 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679727896] (TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type))
- data ZipWith7Sym2 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727896]) (l :: TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type))
- data ZipWith7Sym3 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727896]) (l :: [b6989586621679727897]) (l :: TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type))
- data ZipWith7Sym4 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727896]) (l :: [b6989586621679727897]) (l :: [c6989586621679727898]) (l :: TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type))
- data ZipWith7Sym5 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727896]) (l :: [b6989586621679727897]) (l :: [c6989586621679727898]) (l :: [d6989586621679727899]) (l :: TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type))
- data ZipWith7Sym6 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727896]) (l :: [b6989586621679727897]) (l :: [c6989586621679727898]) (l :: [d6989586621679727899]) (l :: [e6989586621679727900]) (l :: TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type))
- data ZipWith7Sym7 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727896]) (l :: [b6989586621679727897]) (l :: [c6989586621679727898]) (l :: [d6989586621679727899]) (l :: [e6989586621679727900]) (l :: [f6989586621679727901]) (l :: TyFun [g6989586621679727902] [h6989586621679727903])
- type ZipWith7Sym8 (t :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679727896]) (t :: [b6989586621679727897]) (t :: [c6989586621679727898]) (t :: [d6989586621679727899]) (t :: [e6989586621679727900]) (t :: [f6989586621679727901]) (t :: [g6989586621679727902]) = ZipWith7 t t t t t t t t
- data NubSym0 (l :: TyFun [a6989586621679389227] [a6989586621679389227])
- type NubSym1 (t :: [a6989586621679389227]) = Nub t
- data NubBySym0 (l :: TyFun (TyFun a6989586621679389226 (TyFun a6989586621679389226 Bool -> Type) -> Type) (TyFun [a6989586621679389226] [a6989586621679389226] -> Type))
- data NubBySym1 (l :: TyFun a6989586621679389226 (TyFun a6989586621679389226 Bool -> Type) -> Type) (l :: TyFun [a6989586621679389226] [a6989586621679389226])
- type NubBySym2 (t :: TyFun a6989586621679389226 (TyFun a6989586621679389226 Bool -> Type) -> Type) (t :: [a6989586621679389226]) = NubBy t t
- data UnionSym0 (l :: TyFun [a6989586621679389223] (TyFun [a6989586621679389223] [a6989586621679389223] -> Type))
- data UnionSym1 (l :: [a6989586621679389223]) (l :: TyFun [a6989586621679389223] [a6989586621679389223])
- type UnionSym2 (t :: [a6989586621679389223]) (t :: [a6989586621679389223]) = Union t t
- data UnionBySym0 (l :: TyFun (TyFun a6989586621679389224 (TyFun a6989586621679389224 Bool -> Type) -> Type) (TyFun [a6989586621679389224] (TyFun [a6989586621679389224] [a6989586621679389224] -> Type) -> Type))
- data UnionBySym1 (l :: TyFun a6989586621679389224 (TyFun a6989586621679389224 Bool -> Type) -> Type) (l :: TyFun [a6989586621679389224] (TyFun [a6989586621679389224] [a6989586621679389224] -> Type))
- data UnionBySym2 (l :: TyFun a6989586621679389224 (TyFun a6989586621679389224 Bool -> Type) -> Type) (l :: [a6989586621679389224]) (l :: TyFun [a6989586621679389224] [a6989586621679389224])
- type UnionBySym3 (t :: TyFun a6989586621679389224 (TyFun a6989586621679389224 Bool -> Type) -> Type) (t :: [a6989586621679389224]) (t :: [a6989586621679389224]) = UnionBy t t t
- data GenericLengthSym0 (l :: TyFun [a6989586621679389222] i6989586621679389221)
- type GenericLengthSym1 (t :: [a6989586621679389222]) = GenericLength t
- data GenericTakeSym0 (l :: TyFun i6989586621679727894 (TyFun [a6989586621679727895] [a6989586621679727895] -> Type))
- data GenericTakeSym1 (l :: i6989586621679727894) (l :: TyFun [a6989586621679727895] [a6989586621679727895])
- type GenericTakeSym2 (t :: i6989586621679727894) (t :: [a6989586621679727895]) = GenericTake t t
- data GenericDropSym0 (l :: TyFun i6989586621679727892 (TyFun [a6989586621679727893] [a6989586621679727893] -> Type))
- data GenericDropSym1 (l :: i6989586621679727892) (l :: TyFun [a6989586621679727893] [a6989586621679727893])
- type GenericDropSym2 (t :: i6989586621679727892) (t :: [a6989586621679727893]) = GenericDrop t t
- data GenericSplitAtSym0 (l :: TyFun i6989586621679727890 (TyFun [a6989586621679727891] ([a6989586621679727891], [a6989586621679727891]) -> Type))
- data GenericSplitAtSym1 (l :: i6989586621679727890) (l :: TyFun [a6989586621679727891] ([a6989586621679727891], [a6989586621679727891]))
- type GenericSplitAtSym2 (t :: i6989586621679727890) (t :: [a6989586621679727891]) = GenericSplitAt t t
- data GenericIndexSym0 (l :: TyFun [a6989586621679727889] (TyFun i6989586621679727888 a6989586621679727889 -> Type))
- data GenericIndexSym1 (l :: [a6989586621679727889]) (l :: TyFun i6989586621679727888 a6989586621679727889)
- type GenericIndexSym2 (t :: [a6989586621679727889]) (t :: i6989586621679727888) = GenericIndex t t
- data GenericReplicateSym0 (l :: TyFun i6989586621679727886 (TyFun a6989586621679727887 [a6989586621679727887] -> Type))
- data GenericReplicateSym1 (l :: i6989586621679727886) (l :: TyFun a6989586621679727887 [a6989586621679727887])
- type GenericReplicateSym2 (t :: i6989586621679727886) (t :: a6989586621679727887) = GenericReplicate t t
Basic functions
type family Length (a :: [a]) :: Nat where ... #
Equations
Length '[] = FromInteger 0 | |
Length ((:) _z_6989586621679390095 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply LengthSym0 xs) |
List transformations
type family Intersperse (a :: a) (a :: [a]) :: [a] where ... #
Equations
Intersperse _z_6989586621679393118 '[] = '[] | |
Intersperse sep ((:) x xs) = Apply (Apply (:$) x) (Apply (Apply PrependToAllSym0 sep) xs) |
type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ... #
Equations
Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) |
type family Subsequences (a :: [a]) :: [[a]] where ... #
Equations
Subsequences xs = Apply (Apply (:$) '[]) (Apply NonEmptySubsequencesSym0 xs) |
type family Permutations (a :: [a]) :: [[a]] where ... #
Reducing lists (folds)
type family Foldr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ... #
Equations
Foldr1 _z_6989586621679392342 '[x] = x | |
Foldr1 f ((:) x ((:) wild_6989586621679389796 wild_6989586621679389798)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let6989586621679392350XsSym4 f x wild_6989586621679389796 wild_6989586621679389798)) | |
Foldr1 _z_6989586621679392369 '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" |
Special folds
type family Sum (a :: [a]) :: a where ... #
Equations
Sum l = Apply (Apply (Let6989586621679390128Sum'Sym1 l) l) (FromInteger 0) |
type family Product (a :: [a]) :: a where ... #
Equations
Product l = Apply (Apply (Let6989586621679390104ProdSym1 l) l) (FromInteger 1) |
Building lists
Scans
type family Scanr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ... #
Equations
Scanr1 _z_6989586621679392147 '[] = '[] | |
Scanr1 _z_6989586621679392150 '[x] = Apply (Apply (:$) x) '[] | |
Scanr1 f ((:) x ((:) wild_6989586621679389804 wild_6989586621679389806)) = Case_6989586621679392196 f x wild_6989586621679389804 wild_6989586621679389806 (Let6989586621679392177Scrutinee_6989586621679389802Sym4 f x wild_6989586621679389804 wild_6989586621679389806) |
Accumulating maps
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 ... #
Infinite lists
type family Replicate (a :: Nat) (a :: a) :: [a] where ... #
Equations
Replicate n x = Case_6989586621679390088 n x (Let6989586621679390080Scrutinee_6989586621679389888Sym2 n x) |
Unfolding
type family Unfoldr (a :: TyFun b (Maybe (a, b)) -> Type) (a :: b) :: [a] where ... #
Equations
Unfoldr f b = Case_6989586621679391789 f b (Let6989586621679391781Scrutinee_6989586621679389808Sym2 f b) |
Sublists
Extracting sublists
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 ... #
Equations
Span _z_6989586621679390419 '[] = Apply (Apply Tuple2Sym0 Let6989586621679390422XsSym0) Let6989586621679390422XsSym0 | |
Span p ((:) x xs') = Case_6989586621679390452 p x xs' (Let6989586621679390439Scrutinee_6989586621679389868Sym3 p x xs') |
type family Break (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... #
Equations
Break _z_6989586621679390317 '[] = Apply (Apply Tuple2Sym0 Let6989586621679390320XsSym0) Let6989586621679390320XsSym0 | |
Break p ((:) x xs') = Case_6989586621679390350 p x xs' (Let6989586621679390337Scrutinee_6989586621679389870Sym3 p x xs') |
type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ... #
Equations
StripPrefix '[] ys = Apply JustSym0 ys | |
StripPrefix arg_6989586621679728012 arg_6989586621679728014 = Case_6989586621679728623 arg_6989586621679728012 arg_6989586621679728014 (Apply (Apply Tuple2Sym0 arg_6989586621679728012) arg_6989586621679728014) |
type family Group (a :: [a]) :: [[a]] where ... #
Equations
Group xs = Apply (Apply GroupBySym0 (:==$)) xs |
Predicates
type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... #
Equations
IsPrefixOf '[] '[] = TrueSym0 | |
IsPrefixOf '[] ((:) _z_6989586621679391721 _z_6989586621679391724) = TrueSym0 | |
IsPrefixOf ((:) _z_6989586621679391727 _z_6989586621679391730) '[] = 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 ... #
Equations
IsSuffixOf x y = Apply (Apply IsPrefixOfSym0 (Apply ReverseSym0 x)) (Apply ReverseSym0 y) |
Searching lists
Searching by equality
type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... #
Equations
Lookup _key '[] = NothingSym0 | |
Lookup key ((:) '(x, y) xys) = Case_6989586621679390232 key x y xys (Let6989586621679390213Scrutinee_6989586621679389884Sym4 key x y xys) |
Searching with a predicate
type family Find (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe a where ... #
Equations
Find p a_6989586621679390702 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FilterSym0 p)) a_6989586621679390702 |
Indexing lists
type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ... #
Equations
ElemIndices x a_6989586621679391604 = Apply (Apply FindIndicesSym0 (Apply (:==$) x)) a_6989586621679391604 |
type family FindIndex (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe Nat where ... #
Equations
FindIndex p a_6989586621679391617 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679391617 |
Zipping and unzipping lists
type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ... #
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 '[] '[] ((:) _z_6989586621679391453 _z_6989586621679391456) = '[] | |
Zip3 '[] ((:) _z_6989586621679391459 _z_6989586621679391462) '[] = '[] | |
Zip3 '[] ((:) _z_6989586621679391465 _z_6989586621679391468) ((:) _z_6989586621679391471 _z_6989586621679391474) = '[] | |
Zip3 ((:) _z_6989586621679391477 _z_6989586621679391480) '[] '[] = '[] | |
Zip3 ((:) _z_6989586621679391483 _z_6989586621679391486) '[] ((:) _z_6989586621679391489 _z_6989586621679391492) = '[] | |
Zip3 ((:) _z_6989586621679391495 _z_6989586621679391498) ((:) _z_6989586621679391501 _z_6989586621679391504) '[] = '[] |
type family Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ... #
Equations
Zip4 a_6989586621679728577 a_6989586621679728579 a_6989586621679728581 a_6989586621679728583 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621679728577) a_6989586621679728579) a_6989586621679728581) a_6989586621679728583 |
type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ... #
Equations
Zip5 a_6989586621679728532 a_6989586621679728534 a_6989586621679728536 a_6989586621679728538 a_6989586621679728540 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621679728532) a_6989586621679728534) a_6989586621679728536) a_6989586621679728538) a_6989586621679728540 |
type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ... #
Equations
Zip6 a_6989586621679728475 a_6989586621679728477 a_6989586621679728479 a_6989586621679728481 a_6989586621679728483 a_6989586621679728485 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621679728475) a_6989586621679728477) a_6989586621679728479) a_6989586621679728481) a_6989586621679728483) a_6989586621679728485 |
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 ... #
Equations
Zip7 a_6989586621679728405 a_6989586621679728407 a_6989586621679728409 a_6989586621679728411 a_6989586621679728413 a_6989586621679728415 a_6989586621679728417 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621679728405) a_6989586621679728407) a_6989586621679728409) a_6989586621679728411) a_6989586621679728413) a_6989586621679728415) a_6989586621679728417 |
type family ZipWith (a :: TyFun a (TyFun b c -> Type) -> Type) (a :: [a]) (a :: [b]) :: [c] where ... #
Equations
ZipWith f ((:) x xs) ((:) y ys) = Apply (Apply (:$) (Apply (Apply f x) y)) (Apply (Apply (Apply ZipWithSym0 f) xs) ys) | |
ZipWith _z_6989586621679391411 '[] '[] = '[] | |
ZipWith _z_6989586621679391414 ((:) _z_6989586621679391417 _z_6989586621679391420) '[] = '[] | |
ZipWith _z_6989586621679391423 '[] ((:) _z_6989586621679391426 _z_6989586621679391429) = '[] |
type family ZipWith3 (a :: TyFun a (TyFun b (TyFun c d -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ... #
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 _z_6989586621679391316 '[] '[] '[] = '[] | |
ZipWith3 _z_6989586621679391319 '[] '[] ((:) _z_6989586621679391322 _z_6989586621679391325) = '[] | |
ZipWith3 _z_6989586621679391328 '[] ((:) _z_6989586621679391331 _z_6989586621679391334) '[] = '[] | |
ZipWith3 _z_6989586621679391337 '[] ((:) _z_6989586621679391340 _z_6989586621679391343) ((:) _z_6989586621679391346 _z_6989586621679391349) = '[] | |
ZipWith3 _z_6989586621679391352 ((:) _z_6989586621679391355 _z_6989586621679391358) '[] '[] = '[] | |
ZipWith3 _z_6989586621679391361 ((:) _z_6989586621679391364 _z_6989586621679391367) '[] ((:) _z_6989586621679391370 _z_6989586621679391373) = '[] | |
ZipWith3 _z_6989586621679391376 ((:) _z_6989586621679391379 _z_6989586621679391382) ((:) _z_6989586621679391385 _z_6989586621679391388) '[] = '[] |
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 ... #
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 _z_6989586621679728390 _z_6989586621679728393 _z_6989586621679728396 _z_6989586621679728399 _z_6989586621679728402 = '[] |
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 ... #
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 _z_6989586621679728333 _z_6989586621679728336 _z_6989586621679728339 _z_6989586621679728342 _z_6989586621679728345 _z_6989586621679728348 = '[] |
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 ... #
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 _z_6989586621679728262 _z_6989586621679728265 _z_6989586621679728268 _z_6989586621679728271 _z_6989586621679728274 _z_6989586621679728277 _z_6989586621679728280 = '[] |
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 ... #
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 _z_6989586621679728176 _z_6989586621679728179 _z_6989586621679728182 _z_6989586621679728185 _z_6989586621679728188 _z_6989586621679728191 _z_6989586621679728194 _z_6989586621679728197 = '[] |
type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... #
Special lists
"Set" operations
Ordered lists
type family Sort (a :: [a]) :: [a] where ... #
Equations
Sort a_6989586621679390938 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679390938 |
type family Insert (a :: a) (a :: [a]) :: [a] where ... #
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 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 ... #
Equations
DeleteFirstsBy eq a_6989586621679391007 a_6989586621679391009 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679391007) a_6989586621679391009 |
type family UnionBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... #
type family IntersectBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... #
Equations
IntersectBy _z_6989586621679390721 '[] '[] = '[] | |
IntersectBy _z_6989586621679390724 '[] ((:) _z_6989586621679390727 _z_6989586621679390730) = '[] | |
IntersectBy _z_6989586621679390733 ((:) _z_6989586621679390736 _z_6989586621679390739) '[] = '[] | |
IntersectBy eq ((:) wild_6989586621679389854 wild_6989586621679389856) ((:) wild_6989586621679389858 wild_6989586621679389860) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679390798Sym0 eq) wild_6989586621679389854) wild_6989586621679389856) wild_6989586621679389858) wild_6989586621679389860)) (Let6989586621679390747XsSym5 eq wild_6989586621679389854 wild_6989586621679389856 wild_6989586621679389858 wild_6989586621679389860) |
User-supplied comparison (replacing an Ord
context)
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 ... #
Equations
MaximumBy _z_6989586621679392396 '[] = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" | |
MaximumBy cmp ((:) wild_6989586621679389840 wild_6989586621679389842) = Apply (Apply Foldl1Sym0 (Let6989586621679392415MaxBySym3 cmp wild_6989586621679389840 wild_6989586621679389842)) (Let6989586621679392402XsSym3 cmp wild_6989586621679389840 wild_6989586621679389842) |
type family MinimumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... #
Equations
MinimumBy _z_6989586621679392483 '[] = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" | |
MinimumBy cmp ((:) wild_6989586621679389846 wild_6989586621679389848) = Apply (Apply Foldl1Sym0 (Let6989586621679392502MinBySym3 cmp wild_6989586621679389846 wild_6989586621679389848)) (Let6989586621679392489XsSym3 cmp wild_6989586621679389846 wild_6989586621679389848) |
The "generic
" operations
type family GenericLength (a :: [a]) :: i where ... #
Equations
GenericLength '[] = FromInteger 0 | |
GenericLength ((:) _z_6989586621679389942 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
type family GenericTake (a :: i) (a :: [a]) :: [a] where ... #
Equations
GenericTake a_6989586621679728086 a_6989586621679728088 = Apply (Apply TakeSym0 a_6989586621679728086) a_6989586621679728088 |
type family GenericDrop (a :: i) (a :: [a]) :: [a] where ... #
Equations
GenericDrop a_6989586621679728071 a_6989586621679728073 = Apply (Apply DropSym0 a_6989586621679728071) a_6989586621679728073 |
type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ... #
Equations
GenericSplitAt a_6989586621679728056 a_6989586621679728058 = Apply (Apply SplitAtSym0 a_6989586621679728056) a_6989586621679728058 |
type family GenericIndex (a :: [a]) (a :: i) :: a where ... #
Equations
GenericIndex a_6989586621679728041 a_6989586621679728043 = Apply (Apply (:!!$) a_6989586621679728041) a_6989586621679728043 |
type family GenericReplicate (a :: i) (a :: a) :: [a] where ... #
Equations
GenericReplicate a_6989586621679728026 a_6989586621679728028 = Apply (Apply ReplicateSym0 a_6989586621679728026) a_6989586621679728028 |
Defunctionalization symbols
data (:$) (l :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type)) #
data (l :: [a6989586621679244031]) :++$$ (l :: TyFun [a6989586621679244031] [a6989586621679244031]) #
data (:++$) (l :: TyFun [a6989586621679244031] (TyFun [a6989586621679244031] [a6989586621679244031] -> Type)) #
data MapSym0 (l :: TyFun (TyFun a6989586621679244032 b6989586621679244033 -> Type) (TyFun [a6989586621679244032] [b6989586621679244033] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679244032 b6989586621679244033 -> Type) (TyFun [a6989586621679244032] [b6989586621679244033] -> Type) -> *) (MapSym0 a6989586621679244032 b6989586621679244033) # | |
type Apply (TyFun a6989586621679244032 b6989586621679244033 -> Type) (TyFun [a6989586621679244032] [b6989586621679244033] -> Type) (MapSym0 a6989586621679244032 b6989586621679244033) l # | |
data MapSym1 (l :: TyFun a6989586621679244032 b6989586621679244033 -> Type) (l :: TyFun [a6989586621679244032] [b6989586621679244033]) #
type MapSym2 (t :: TyFun a6989586621679244032 b6989586621679244033 -> Type) (t :: [a6989586621679244032]) = Map t t #
data ReverseSym0 (l :: TyFun [a6989586621679389343] [a6989586621679389343]) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389343] [a6989586621679389343] -> *) (ReverseSym0 a6989586621679389343) # | |
type Apply [a] [a] (ReverseSym0 a) l # | |
type ReverseSym1 (t :: [a6989586621679389343]) = Reverse t #
data IntersperseSym0 (l :: TyFun a6989586621679389342 (TyFun [a6989586621679389342] [a6989586621679389342] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun a6989586621679389342 (TyFun [a6989586621679389342] [a6989586621679389342] -> Type) -> *) (IntersperseSym0 a6989586621679389342) # | |
type Apply a6989586621679389342 (TyFun [a6989586621679389342] [a6989586621679389342] -> Type) (IntersperseSym0 a6989586621679389342) l # | |
data IntersperseSym1 (l :: a6989586621679389342) (l :: TyFun [a6989586621679389342] [a6989586621679389342]) #
Instances
SuppressUnusedWarnings (a6989586621679389342 -> TyFun [a6989586621679389342] [a6989586621679389342] -> *) (IntersperseSym1 a6989586621679389342) # | |
type Apply [a] [a] (IntersperseSym1 a l1) l2 # | |
type IntersperseSym2 (t :: a6989586621679389342) (t :: [a6989586621679389342]) = Intersperse t t #
data IntercalateSym0 (l :: TyFun [a6989586621679389341] (TyFun [[a6989586621679389341]] [a6989586621679389341] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389341] (TyFun [[a6989586621679389341]] [a6989586621679389341] -> Type) -> *) (IntercalateSym0 a6989586621679389341) # | |
type Apply [a6989586621679389341] (TyFun [[a6989586621679389341]] [a6989586621679389341] -> Type) (IntercalateSym0 a6989586621679389341) l # | |
data IntercalateSym1 (l :: [a6989586621679389341]) (l :: TyFun [[a6989586621679389341]] [a6989586621679389341]) #
Instances
SuppressUnusedWarnings ([a6989586621679389341] -> TyFun [[a6989586621679389341]] [a6989586621679389341] -> *) (IntercalateSym1 a6989586621679389341) # | |
type Apply [[a]] [a] (IntercalateSym1 a l1) l2 # | |
type IntercalateSym2 (t :: [a6989586621679389341]) (t :: [[a6989586621679389341]]) = Intercalate t t #
data SubsequencesSym0 (l :: TyFun [a6989586621679389340] [[a6989586621679389340]]) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389340] [[a6989586621679389340]] -> *) (SubsequencesSym0 a6989586621679389340) # | |
type Apply [a] [[a]] (SubsequencesSym0 a) l # | |
type SubsequencesSym1 (t :: [a6989586621679389340]) = Subsequences t #
data PermutationsSym0 (l :: TyFun [a6989586621679389337] [[a6989586621679389337]]) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389337] [[a6989586621679389337]] -> *) (PermutationsSym0 a6989586621679389337) # | |
type Apply [a] [[a]] (PermutationsSym0 a) l # | |
type PermutationsSym1 (t :: [a6989586621679389337]) = Permutations t #
data FoldlSym0 (l :: TyFun (TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679213672 b6989586621679213673) # | |
type Apply (TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type) -> Type) (FoldlSym0 a6989586621679213672 b6989586621679213673) l # | |
data FoldlSym1 (l :: TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (l :: TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) -> TyFun b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type) -> *) (FoldlSym1 a6989586621679213672 b6989586621679213673) # | |
type Apply b6989586621679213673 (TyFun [a6989586621679213672] b6989586621679213673 -> Type) (FoldlSym1 a6989586621679213672 b6989586621679213673 l1) l2 # | |
data FoldlSym2 (l :: TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (l :: b6989586621679213673) (l :: TyFun [a6989586621679213672] b6989586621679213673) #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) -> b6989586621679213673 -> TyFun [a6989586621679213672] b6989586621679213673 -> *) (FoldlSym2 a6989586621679213672 b6989586621679213673) # | |
type Apply [a] b (FoldlSym2 a b l1 l2) l3 # | |
type FoldlSym3 (t :: TyFun b6989586621679213673 (TyFun a6989586621679213672 b6989586621679213673 -> Type) -> Type) (t :: b6989586621679213673) (t :: [a6989586621679213672]) = Foldl t t t #
data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) (TyFun b6989586621679389336 (TyFun [a6989586621679389335] b6989586621679389336 -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) (TyFun b6989586621679389336 (TyFun [a6989586621679389335] b6989586621679389336 -> Type) -> Type) -> *) (Foldl'Sym0 a6989586621679389335 b6989586621679389336) # | |
type Apply (TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) (TyFun b6989586621679389336 (TyFun [a6989586621679389335] b6989586621679389336 -> Type) -> Type) (Foldl'Sym0 a6989586621679389335 b6989586621679389336) l # | |
data Foldl'Sym1 (l :: TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) (l :: TyFun b6989586621679389336 (TyFun [a6989586621679389335] b6989586621679389336 -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) -> TyFun b6989586621679389336 (TyFun [a6989586621679389335] b6989586621679389336 -> Type) -> *) (Foldl'Sym1 a6989586621679389335 b6989586621679389336) # | |
type Apply b6989586621679389336 (TyFun [a6989586621679389335] b6989586621679389336 -> Type) (Foldl'Sym1 a6989586621679389335 b6989586621679389336 l1) l2 # | |
data Foldl'Sym2 (l :: TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) (l :: b6989586621679389336) (l :: TyFun [a6989586621679389335] b6989586621679389336) #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) -> b6989586621679389336 -> TyFun [a6989586621679389335] b6989586621679389336 -> *) (Foldl'Sym2 a6989586621679389335 b6989586621679389336) # | |
type Apply [a] b (Foldl'Sym2 a b l1 l2) l3 # | |
type Foldl'Sym3 (t :: TyFun b6989586621679389336 (TyFun a6989586621679389335 b6989586621679389336 -> Type) -> Type) (t :: b6989586621679389336) (t :: [a6989586621679389335]) = Foldl' t t t #
data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679389334 (TyFun a6989586621679389334 a6989586621679389334 -> Type) -> Type) (TyFun [a6989586621679389334] a6989586621679389334 -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389334 (TyFun a6989586621679389334 a6989586621679389334 -> Type) -> Type) (TyFun [a6989586621679389334] a6989586621679389334 -> Type) -> *) (Foldl1Sym0 a6989586621679389334) # | |
type Apply (TyFun a6989586621679389334 (TyFun a6989586621679389334 a6989586621679389334 -> Type) -> Type) (TyFun [a6989586621679389334] a6989586621679389334 -> Type) (Foldl1Sym0 a6989586621679389334) l # | |
data Foldl1Sym1 (l :: TyFun a6989586621679389334 (TyFun a6989586621679389334 a6989586621679389334 -> Type) -> Type) (l :: TyFun [a6989586621679389334] a6989586621679389334) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389334 (TyFun a6989586621679389334 a6989586621679389334 -> Type) -> Type) -> TyFun [a6989586621679389334] a6989586621679389334 -> *) (Foldl1Sym1 a6989586621679389334) # | |
type Apply [a] a (Foldl1Sym1 a l1) l2 # | |
type Foldl1Sym2 (t :: TyFun a6989586621679389334 (TyFun a6989586621679389334 a6989586621679389334 -> Type) -> Type) (t :: [a6989586621679389334]) = Foldl1 t t #
data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679389333 (TyFun a6989586621679389333 a6989586621679389333 -> Type) -> Type) (TyFun [a6989586621679389333] a6989586621679389333 -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389333 (TyFun a6989586621679389333 a6989586621679389333 -> Type) -> Type) (TyFun [a6989586621679389333] a6989586621679389333 -> Type) -> *) (Foldl1'Sym0 a6989586621679389333) # | |
type Apply (TyFun a6989586621679389333 (TyFun a6989586621679389333 a6989586621679389333 -> Type) -> Type) (TyFun [a6989586621679389333] a6989586621679389333 -> Type) (Foldl1'Sym0 a6989586621679389333) l # | |
data Foldl1'Sym1 (l :: TyFun a6989586621679389333 (TyFun a6989586621679389333 a6989586621679389333 -> Type) -> Type) (l :: TyFun [a6989586621679389333] a6989586621679389333) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389333 (TyFun a6989586621679389333 a6989586621679389333 -> Type) -> Type) -> TyFun [a6989586621679389333] a6989586621679389333 -> *) (Foldl1'Sym1 a6989586621679389333) # | |
type Apply [a] a (Foldl1'Sym1 a l1) l2 # | |
type Foldl1'Sym2 (t :: TyFun a6989586621679389333 (TyFun a6989586621679389333 a6989586621679389333 -> Type) -> Type) (t :: [a6989586621679389333]) = Foldl1' t t #
data FoldrSym0 (l :: TyFun (TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) (TyFun b6989586621679244035 (TyFun [a6989586621679244034] b6989586621679244035 -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) (TyFun b6989586621679244035 (TyFun [a6989586621679244034] b6989586621679244035 -> Type) -> Type) -> *) (FoldrSym0 a6989586621679244034 b6989586621679244035) # | |
type Apply (TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) (TyFun b6989586621679244035 (TyFun [a6989586621679244034] b6989586621679244035 -> Type) -> Type) (FoldrSym0 a6989586621679244034 b6989586621679244035) l # | |
data FoldrSym1 (l :: TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) (l :: TyFun b6989586621679244035 (TyFun [a6989586621679244034] b6989586621679244035 -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) -> TyFun b6989586621679244035 (TyFun [a6989586621679244034] b6989586621679244035 -> Type) -> *) (FoldrSym1 a6989586621679244034 b6989586621679244035) # | |
type Apply b6989586621679244035 (TyFun [a6989586621679244034] b6989586621679244035 -> Type) (FoldrSym1 a6989586621679244034 b6989586621679244035 l1) l2 # | |
data FoldrSym2 (l :: TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) (l :: b6989586621679244035) (l :: TyFun [a6989586621679244034] b6989586621679244035) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) -> b6989586621679244035 -> TyFun [a6989586621679244034] b6989586621679244035 -> *) (FoldrSym2 a6989586621679244034 b6989586621679244035) # | |
type Apply [a] b (FoldrSym2 a b l1 l2) l3 # | |
type FoldrSym3 (t :: TyFun a6989586621679244034 (TyFun b6989586621679244035 b6989586621679244035 -> Type) -> Type) (t :: b6989586621679244035) (t :: [a6989586621679244034]) = Foldr t t t #
data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679389332 (TyFun a6989586621679389332 a6989586621679389332 -> Type) -> Type) (TyFun [a6989586621679389332] a6989586621679389332 -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389332 (TyFun a6989586621679389332 a6989586621679389332 -> Type) -> Type) (TyFun [a6989586621679389332] a6989586621679389332 -> Type) -> *) (Foldr1Sym0 a6989586621679389332) # | |
type Apply (TyFun a6989586621679389332 (TyFun a6989586621679389332 a6989586621679389332 -> Type) -> Type) (TyFun [a6989586621679389332] a6989586621679389332 -> Type) (Foldr1Sym0 a6989586621679389332) l # | |
data Foldr1Sym1 (l :: TyFun a6989586621679389332 (TyFun a6989586621679389332 a6989586621679389332 -> Type) -> Type) (l :: TyFun [a6989586621679389332] a6989586621679389332) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389332 (TyFun a6989586621679389332 a6989586621679389332 -> Type) -> Type) -> TyFun [a6989586621679389332] a6989586621679389332 -> *) (Foldr1Sym1 a6989586621679389332) # | |
type Apply [a] a (Foldr1Sym1 a l1) l2 # | |
type Foldr1Sym2 (t :: TyFun a6989586621679389332 (TyFun a6989586621679389332 a6989586621679389332 -> Type) -> Type) (t :: [a6989586621679389332]) = Foldr1 t t #
data ConcatSym0 (l :: TyFun [[a6989586621679389331]] [a6989586621679389331]) #
Instances
SuppressUnusedWarnings (TyFun [[a6989586621679389331]] [a6989586621679389331] -> *) (ConcatSym0 a6989586621679389331) # | |
type Apply [[a]] [a] (ConcatSym0 a) l # | |
type ConcatSym1 (t :: [[a6989586621679389331]]) = Concat t #
data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679389329 [b6989586621679389330] -> Type) (TyFun [a6989586621679389329] [b6989586621679389330] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389329 [b6989586621679389330] -> Type) (TyFun [a6989586621679389329] [b6989586621679389330] -> Type) -> *) (ConcatMapSym0 a6989586621679389329 b6989586621679389330) # | |
type Apply (TyFun a6989586621679389329 [b6989586621679389330] -> Type) (TyFun [a6989586621679389329] [b6989586621679389330] -> Type) (ConcatMapSym0 a6989586621679389329 b6989586621679389330) l # | |
data ConcatMapSym1 (l :: TyFun a6989586621679389329 [b6989586621679389330] -> Type) (l :: TyFun [a6989586621679389329] [b6989586621679389330]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389329 [b6989586621679389330] -> Type) -> TyFun [a6989586621679389329] [b6989586621679389330] -> *) (ConcatMapSym1 a6989586621679389329 b6989586621679389330) # | |
type Apply [a] [b] (ConcatMapSym1 a b l1) l2 # | |
type ConcatMapSym2 (t :: TyFun a6989586621679389329 [b6989586621679389330] -> Type) (t :: [a6989586621679389329]) = ConcatMap t t #
data Any_Sym0 (l :: TyFun (TyFun a6989586621679379112 Bool -> Type) (TyFun [a6989586621679379112] Bool -> Type)) #
data Any_Sym1 (l :: TyFun a6989586621679379112 Bool -> Type) (l :: TyFun [a6989586621679379112] Bool) #
type Any_Sym2 (t :: TyFun a6989586621679379112 Bool -> Type) (t :: [a6989586621679379112]) = Any_ t t #
data AllSym0 (l :: TyFun (TyFun a6989586621679389328 Bool -> Type) (TyFun [a6989586621679389328] Bool -> Type)) #
data AllSym1 (l :: TyFun a6989586621679389328 Bool -> Type) (l :: TyFun [a6989586621679389328] Bool) #
type AllSym2 (t :: TyFun a6989586621679389328 Bool -> Type) (t :: [a6989586621679389328]) = All t t #
data ScanlSym0 (l :: TyFun (TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) (TyFun b6989586621679389326 (TyFun [a6989586621679389327] [b6989586621679389326] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) (TyFun b6989586621679389326 (TyFun [a6989586621679389327] [b6989586621679389326] -> Type) -> Type) -> *) (ScanlSym0 a6989586621679389327 b6989586621679389326) # | |
type Apply (TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) (TyFun b6989586621679389326 (TyFun [a6989586621679389327] [b6989586621679389326] -> Type) -> Type) (ScanlSym0 a6989586621679389327 b6989586621679389326) l # | |
data ScanlSym1 (l :: TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) (l :: TyFun b6989586621679389326 (TyFun [a6989586621679389327] [b6989586621679389326] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) -> TyFun b6989586621679389326 (TyFun [a6989586621679389327] [b6989586621679389326] -> Type) -> *) (ScanlSym1 a6989586621679389327 b6989586621679389326) # | |
type Apply b6989586621679389326 (TyFun [a6989586621679389327] [b6989586621679389326] -> Type) (ScanlSym1 a6989586621679389327 b6989586621679389326 l1) l2 # | |
data ScanlSym2 (l :: TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) (l :: b6989586621679389326) (l :: TyFun [a6989586621679389327] [b6989586621679389326]) #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) -> b6989586621679389326 -> TyFun [a6989586621679389327] [b6989586621679389326] -> *) (ScanlSym2 a6989586621679389327 b6989586621679389326) # | |
type Apply [a] [b] (ScanlSym2 a b l1 l2) l3 # | |
type ScanlSym3 (t :: TyFun b6989586621679389326 (TyFun a6989586621679389327 b6989586621679389326 -> Type) -> Type) (t :: b6989586621679389326) (t :: [a6989586621679389327]) = Scanl t t t #
data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679389325 (TyFun a6989586621679389325 a6989586621679389325 -> Type) -> Type) (TyFun [a6989586621679389325] [a6989586621679389325] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389325 (TyFun a6989586621679389325 a6989586621679389325 -> Type) -> Type) (TyFun [a6989586621679389325] [a6989586621679389325] -> Type) -> *) (Scanl1Sym0 a6989586621679389325) # | |
type Apply (TyFun a6989586621679389325 (TyFun a6989586621679389325 a6989586621679389325 -> Type) -> Type) (TyFun [a6989586621679389325] [a6989586621679389325] -> Type) (Scanl1Sym0 a6989586621679389325) l # | |
data Scanl1Sym1 (l :: TyFun a6989586621679389325 (TyFun a6989586621679389325 a6989586621679389325 -> Type) -> Type) (l :: TyFun [a6989586621679389325] [a6989586621679389325]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389325 (TyFun a6989586621679389325 a6989586621679389325 -> Type) -> Type) -> TyFun [a6989586621679389325] [a6989586621679389325] -> *) (Scanl1Sym1 a6989586621679389325) # | |
type Apply [a] [a] (Scanl1Sym1 a l1) l2 # | |
type Scanl1Sym2 (t :: TyFun a6989586621679389325 (TyFun a6989586621679389325 a6989586621679389325 -> Type) -> Type) (t :: [a6989586621679389325]) = Scanl1 t t #
data ScanrSym0 (l :: TyFun (TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) (TyFun b6989586621679389324 (TyFun [a6989586621679389323] [b6989586621679389324] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) (TyFun b6989586621679389324 (TyFun [a6989586621679389323] [b6989586621679389324] -> Type) -> Type) -> *) (ScanrSym0 a6989586621679389323 b6989586621679389324) # | |
type Apply (TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) (TyFun b6989586621679389324 (TyFun [a6989586621679389323] [b6989586621679389324] -> Type) -> Type) (ScanrSym0 a6989586621679389323 b6989586621679389324) l # | |
data ScanrSym1 (l :: TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) (l :: TyFun b6989586621679389324 (TyFun [a6989586621679389323] [b6989586621679389324] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) -> TyFun b6989586621679389324 (TyFun [a6989586621679389323] [b6989586621679389324] -> Type) -> *) (ScanrSym1 a6989586621679389323 b6989586621679389324) # | |
type Apply b6989586621679389324 (TyFun [a6989586621679389323] [b6989586621679389324] -> Type) (ScanrSym1 a6989586621679389323 b6989586621679389324 l1) l2 # | |
data ScanrSym2 (l :: TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) (l :: b6989586621679389324) (l :: TyFun [a6989586621679389323] [b6989586621679389324]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) -> b6989586621679389324 -> TyFun [a6989586621679389323] [b6989586621679389324] -> *) (ScanrSym2 a6989586621679389323 b6989586621679389324) # | |
type Apply [a] [b] (ScanrSym2 a b l1 l2) l3 # | |
type ScanrSym3 (t :: TyFun a6989586621679389323 (TyFun b6989586621679389324 b6989586621679389324 -> Type) -> Type) (t :: b6989586621679389324) (t :: [a6989586621679389323]) = Scanr t t t #
data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679389322 (TyFun a6989586621679389322 a6989586621679389322 -> Type) -> Type) (TyFun [a6989586621679389322] [a6989586621679389322] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389322 (TyFun a6989586621679389322 a6989586621679389322 -> Type) -> Type) (TyFun [a6989586621679389322] [a6989586621679389322] -> Type) -> *) (Scanr1Sym0 a6989586621679389322) # | |
type Apply (TyFun a6989586621679389322 (TyFun a6989586621679389322 a6989586621679389322 -> Type) -> Type) (TyFun [a6989586621679389322] [a6989586621679389322] -> Type) (Scanr1Sym0 a6989586621679389322) l # | |
data Scanr1Sym1 (l :: TyFun a6989586621679389322 (TyFun a6989586621679389322 a6989586621679389322 -> Type) -> Type) (l :: TyFun [a6989586621679389322] [a6989586621679389322]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389322 (TyFun a6989586621679389322 a6989586621679389322 -> Type) -> Type) -> TyFun [a6989586621679389322] [a6989586621679389322] -> *) (Scanr1Sym1 a6989586621679389322) # | |
type Apply [a] [a] (Scanr1Sym1 a l1) l2 # | |
type Scanr1Sym2 (t :: TyFun a6989586621679389322 (TyFun a6989586621679389322 a6989586621679389322 -> Type) -> Type) (t :: [a6989586621679389322]) = Scanr1 t t #
data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) (TyFun acc6989586621679389319 (TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) (TyFun acc6989586621679389319 (TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]) -> Type) -> Type) -> *) (MapAccumLSym0 x6989586621679389320 acc6989586621679389319 y6989586621679389321) # | |
type Apply (TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) (TyFun acc6989586621679389319 (TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]) -> Type) -> Type) (MapAccumLSym0 x6989586621679389320 acc6989586621679389319 y6989586621679389321) l # | |
data MapAccumLSym1 (l :: TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) (l :: TyFun acc6989586621679389319 (TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) -> TyFun acc6989586621679389319 (TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]) -> Type) -> *) (MapAccumLSym1 x6989586621679389320 acc6989586621679389319 y6989586621679389321) # | |
type Apply acc6989586621679389319 (TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]) -> Type) (MapAccumLSym1 x6989586621679389320 acc6989586621679389319 y6989586621679389321 l1) l2 # | |
data MapAccumLSym2 (l :: TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) (l :: acc6989586621679389319) (l :: TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321])) #
Instances
SuppressUnusedWarnings ((TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) -> acc6989586621679389319 -> TyFun [x6989586621679389320] (acc6989586621679389319, [y6989586621679389321]) -> *) (MapAccumLSym2 x6989586621679389320 acc6989586621679389319 y6989586621679389321) # | |
type Apply [x] (acc, [y]) (MapAccumLSym2 x acc y l1 l2) l3 # | |
type MapAccumLSym3 (t :: TyFun acc6989586621679389319 (TyFun x6989586621679389320 (acc6989586621679389319, y6989586621679389321) -> Type) -> Type) (t :: acc6989586621679389319) (t :: [x6989586621679389320]) = MapAccumL t t t #
data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) (TyFun acc6989586621679389316 (TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) (TyFun acc6989586621679389316 (TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]) -> Type) -> Type) -> *) (MapAccumRSym0 x6989586621679389317 acc6989586621679389316 y6989586621679389318) # | |
type Apply (TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) (TyFun acc6989586621679389316 (TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]) -> Type) -> Type) (MapAccumRSym0 x6989586621679389317 acc6989586621679389316 y6989586621679389318) l # | |
data MapAccumRSym1 (l :: TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) (l :: TyFun acc6989586621679389316 (TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) -> TyFun acc6989586621679389316 (TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]) -> Type) -> *) (MapAccumRSym1 x6989586621679389317 acc6989586621679389316 y6989586621679389318) # | |
type Apply acc6989586621679389316 (TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]) -> Type) (MapAccumRSym1 x6989586621679389317 acc6989586621679389316 y6989586621679389318 l1) l2 # | |
data MapAccumRSym2 (l :: TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) (l :: acc6989586621679389316) (l :: TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318])) #
Instances
SuppressUnusedWarnings ((TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) -> acc6989586621679389316 -> TyFun [x6989586621679389317] (acc6989586621679389316, [y6989586621679389318]) -> *) (MapAccumRSym2 x6989586621679389317 acc6989586621679389316 y6989586621679389318) # | |
type Apply [x] (acc, [y]) (MapAccumRSym2 x acc y l1 l2) l3 # | |
type MapAccumRSym3 (t :: TyFun acc6989586621679389316 (TyFun x6989586621679389317 (acc6989586621679389316, y6989586621679389318) -> Type) -> Type) (t :: acc6989586621679389316) (t :: [x6989586621679389317]) = MapAccumR t t t #
data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679389314 (Maybe (a6989586621679389315, b6989586621679389314)) -> Type) (TyFun b6989586621679389314 [a6989586621679389315] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun b6989586621679389314 (Maybe (a6989586621679389315, b6989586621679389314)) -> Type) (TyFun b6989586621679389314 [a6989586621679389315] -> Type) -> *) (UnfoldrSym0 b6989586621679389314 a6989586621679389315) # | |
type Apply (TyFun b6989586621679389314 (Maybe (a6989586621679389315, b6989586621679389314)) -> Type) (TyFun b6989586621679389314 [a6989586621679389315] -> Type) (UnfoldrSym0 b6989586621679389314 a6989586621679389315) l # | |
data UnfoldrSym1 (l :: TyFun b6989586621679389314 (Maybe (a6989586621679389315, b6989586621679389314)) -> Type) (l :: TyFun b6989586621679389314 [a6989586621679389315]) #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679389314 (Maybe (a6989586621679389315, b6989586621679389314)) -> Type) -> TyFun b6989586621679389314 [a6989586621679389315] -> *) (UnfoldrSym1 b6989586621679389314 a6989586621679389315) # | |
type Apply b [a] (UnfoldrSym1 b a l1) l2 # | |
type UnfoldrSym2 (t :: TyFun b6989586621679389314 (Maybe (a6989586621679389315, b6989586621679389314)) -> Type) (t :: b6989586621679389314) = Unfoldr t t #
data IsPrefixOfSym0 (l :: TyFun [a6989586621679389311] (TyFun [a6989586621679389311] Bool -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389311] (TyFun [a6989586621679389311] Bool -> Type) -> *) (IsPrefixOfSym0 a6989586621679389311) # | |
type Apply [a6989586621679389311] (TyFun [a6989586621679389311] Bool -> Type) (IsPrefixOfSym0 a6989586621679389311) l # | |
data IsPrefixOfSym1 (l :: [a6989586621679389311]) (l :: TyFun [a6989586621679389311] Bool) #
Instances
SuppressUnusedWarnings ([a6989586621679389311] -> TyFun [a6989586621679389311] Bool -> *) (IsPrefixOfSym1 a6989586621679389311) # | |
type Apply [a] Bool (IsPrefixOfSym1 a l1) l2 # | |
type IsPrefixOfSym2 (t :: [a6989586621679389311]) (t :: [a6989586621679389311]) = IsPrefixOf t t #
data IsSuffixOfSym0 (l :: TyFun [a6989586621679389310] (TyFun [a6989586621679389310] Bool -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389310] (TyFun [a6989586621679389310] Bool -> Type) -> *) (IsSuffixOfSym0 a6989586621679389310) # | |
type Apply [a6989586621679389310] (TyFun [a6989586621679389310] Bool -> Type) (IsSuffixOfSym0 a6989586621679389310) l # | |
data IsSuffixOfSym1 (l :: [a6989586621679389310]) (l :: TyFun [a6989586621679389310] Bool) #
Instances
SuppressUnusedWarnings ([a6989586621679389310] -> TyFun [a6989586621679389310] Bool -> *) (IsSuffixOfSym1 a6989586621679389310) # | |
type Apply [a] Bool (IsSuffixOfSym1 a l1) l2 # | |
type IsSuffixOfSym2 (t :: [a6989586621679389310]) (t :: [a6989586621679389310]) = IsSuffixOf t t #
data IsInfixOfSym0 (l :: TyFun [a6989586621679389309] (TyFun [a6989586621679389309] Bool -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389309] (TyFun [a6989586621679389309] Bool -> Type) -> *) (IsInfixOfSym0 a6989586621679389309) # | |
type Apply [a6989586621679389309] (TyFun [a6989586621679389309] Bool -> Type) (IsInfixOfSym0 a6989586621679389309) l # | |
data IsInfixOfSym1 (l :: [a6989586621679389309]) (l :: TyFun [a6989586621679389309] Bool) #
Instances
SuppressUnusedWarnings ([a6989586621679389309] -> TyFun [a6989586621679389309] Bool -> *) (IsInfixOfSym1 a6989586621679389309) # | |
type Apply [a] Bool (IsInfixOfSym1 a l1) l2 # | |
type IsInfixOfSym2 (t :: [a6989586621679389309]) (t :: [a6989586621679389309]) = IsInfixOf t t #
data NotElemSym0 (l :: TyFun a6989586621679389307 (TyFun [a6989586621679389307] Bool -> Type)) #
Instances
SuppressUnusedWarnings (TyFun a6989586621679389307 (TyFun [a6989586621679389307] Bool -> Type) -> *) (NotElemSym0 a6989586621679389307) # | |
type Apply a6989586621679389307 (TyFun [a6989586621679389307] Bool -> Type) (NotElemSym0 a6989586621679389307) l # | |
data NotElemSym1 (l :: a6989586621679389307) (l :: TyFun [a6989586621679389307] Bool) #
Instances
SuppressUnusedWarnings (a6989586621679389307 -> TyFun [a6989586621679389307] Bool -> *) (NotElemSym1 a6989586621679389307) # | |
type Apply [a] Bool (NotElemSym1 a l1) l2 # | |
type NotElemSym2 (t :: a6989586621679389307) (t :: [a6989586621679389307]) = NotElem t t #
data ZipSym0 (l :: TyFun [a6989586621679389305] (TyFun [b6989586621679389306] [(a6989586621679389305, b6989586621679389306)] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389305] (TyFun [b6989586621679389306] [(a6989586621679389305, b6989586621679389306)] -> Type) -> *) (ZipSym0 a6989586621679389305 b6989586621679389306) # | |
type Apply [a6989586621679389305] (TyFun [b6989586621679389306] [(a6989586621679389305, b6989586621679389306)] -> Type) (ZipSym0 a6989586621679389305 b6989586621679389306) l # | |
data ZipSym1 (l :: [a6989586621679389305]) (l :: TyFun [b6989586621679389306] [(a6989586621679389305, b6989586621679389306)]) #
data Zip3Sym0 (l :: TyFun [a6989586621679389302] (TyFun [b6989586621679389303] (TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389302] (TyFun [b6989586621679389303] (TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)] -> Type) -> Type) -> *) (Zip3Sym0 a6989586621679389302 b6989586621679389303 c6989586621679389304) # | |
type Apply [a6989586621679389302] (TyFun [b6989586621679389303] (TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)] -> Type) -> Type) (Zip3Sym0 a6989586621679389302 b6989586621679389303 c6989586621679389304) l # | |
data Zip3Sym1 (l :: [a6989586621679389302]) (l :: TyFun [b6989586621679389303] (TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)] -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679389302] -> TyFun [b6989586621679389303] (TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)] -> Type) -> *) (Zip3Sym1 a6989586621679389302 b6989586621679389303 c6989586621679389304) # | |
type Apply [b6989586621679389303] (TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)] -> Type) (Zip3Sym1 a6989586621679389302 b6989586621679389303 c6989586621679389304 l1) l2 # | |
data Zip3Sym2 (l :: [a6989586621679389302]) (l :: [b6989586621679389303]) (l :: TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)]) #
Instances
SuppressUnusedWarnings ([a6989586621679389302] -> [b6989586621679389303] -> TyFun [c6989586621679389304] [(a6989586621679389302, b6989586621679389303, c6989586621679389304)] -> *) (Zip3Sym2 a6989586621679389302 b6989586621679389303 c6989586621679389304) # | |
type Apply [c] [(a, b, c)] (Zip3Sym2 a b c l1 l2) l3 # | |
type Zip3Sym3 (t :: [a6989586621679389302]) (t :: [b6989586621679389303]) (t :: [c6989586621679389304]) = Zip3 t t t #
data ZipWithSym0 (l :: TyFun (TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) (TyFun [a6989586621679389299] (TyFun [b6989586621679389300] [c6989586621679389301] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) (TyFun [a6989586621679389299] (TyFun [b6989586621679389300] [c6989586621679389301] -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679389299 b6989586621679389300 c6989586621679389301) # | |
type Apply (TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) (TyFun [a6989586621679389299] (TyFun [b6989586621679389300] [c6989586621679389301] -> Type) -> Type) (ZipWithSym0 a6989586621679389299 b6989586621679389300 c6989586621679389301) l # | |
data ZipWithSym1 (l :: TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) (l :: TyFun [a6989586621679389299] (TyFun [b6989586621679389300] [c6989586621679389301] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) -> TyFun [a6989586621679389299] (TyFun [b6989586621679389300] [c6989586621679389301] -> Type) -> *) (ZipWithSym1 a6989586621679389299 b6989586621679389300 c6989586621679389301) # | |
type Apply [a6989586621679389299] (TyFun [b6989586621679389300] [c6989586621679389301] -> Type) (ZipWithSym1 a6989586621679389299 b6989586621679389300 c6989586621679389301 l1) l2 # | |
data ZipWithSym2 (l :: TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) (l :: [a6989586621679389299]) (l :: TyFun [b6989586621679389300] [c6989586621679389301]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) -> [a6989586621679389299] -> TyFun [b6989586621679389300] [c6989586621679389301] -> *) (ZipWithSym2 a6989586621679389299 b6989586621679389300 c6989586621679389301) # | |
type Apply [b] [c] (ZipWithSym2 a b c l1 l2) l3 # | |
type ZipWithSym3 (t :: TyFun a6989586621679389299 (TyFun b6989586621679389300 c6989586621679389301 -> Type) -> Type) (t :: [a6989586621679389299]) (t :: [b6989586621679389300]) = ZipWith t t t #
data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (TyFun [a6989586621679389295] (TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (TyFun [a6989586621679389295] (TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) # | |
type Apply (TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (TyFun [a6989586621679389295] (TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) -> Type) -> Type) (ZipWith3Sym0 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) l # | |
data ZipWith3Sym1 (l :: TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679389295] (TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) -> TyFun [a6989586621679389295] (TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) -> Type) -> *) (ZipWith3Sym1 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) # | |
type Apply [a6989586621679389295] (TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) -> Type) (ZipWith3Sym1 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298 l1) l2 # | |
data ZipWith3Sym2 (l :: TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (l :: [a6989586621679389295]) (l :: TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) -> [a6989586621679389295] -> TyFun [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) -> *) (ZipWith3Sym2 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) # | |
type Apply [b6989586621679389296] (TyFun [c6989586621679389297] [d6989586621679389298] -> Type) (ZipWith3Sym2 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298 l1 l2) l3 # | |
data ZipWith3Sym3 (l :: TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (l :: [a6989586621679389295]) (l :: [b6989586621679389296]) (l :: TyFun [c6989586621679389297] [d6989586621679389298]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) -> [a6989586621679389295] -> [b6989586621679389296] -> TyFun [c6989586621679389297] [d6989586621679389298] -> *) (ZipWith3Sym3 a6989586621679389295 b6989586621679389296 c6989586621679389297 d6989586621679389298) # | |
type Apply [c] [d] (ZipWith3Sym3 a b c d l1 l2 l3) l4 # | |
type ZipWith3Sym4 (t :: TyFun a6989586621679389295 (TyFun b6989586621679389296 (TyFun c6989586621679389297 d6989586621679389298 -> Type) -> Type) -> Type) (t :: [a6989586621679389295]) (t :: [b6989586621679389296]) (t :: [c6989586621679389297]) = ZipWith3 t t t t #
data UnzipSym0 (l :: TyFun [(a6989586621679389293, b6989586621679389294)] ([a6989586621679389293], [b6989586621679389294])) #
data Unzip3Sym0 (l :: TyFun [(a6989586621679389290, b6989586621679389291, c6989586621679389292)] ([a6989586621679389290], [b6989586621679389291], [c6989586621679389292])) #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679389290, b6989586621679389291, c6989586621679389292)] ([a6989586621679389290], [b6989586621679389291], [c6989586621679389292]) -> *) (Unzip3Sym0 a6989586621679389290 b6989586621679389291 c6989586621679389292) # | |
type Apply [(a, b, c)] ([a], [b], [c]) (Unzip3Sym0 a b c) l # | |
type Unzip3Sym1 (t :: [(a6989586621679389290, b6989586621679389291, c6989586621679389292)]) = Unzip3 t #
data Unzip4Sym0 (l :: TyFun [(a6989586621679389286, b6989586621679389287, c6989586621679389288, d6989586621679389289)] ([a6989586621679389286], [b6989586621679389287], [c6989586621679389288], [d6989586621679389289])) #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679389286, b6989586621679389287, c6989586621679389288, d6989586621679389289)] ([a6989586621679389286], [b6989586621679389287], [c6989586621679389288], [d6989586621679389289]) -> *) (Unzip4Sym0 a6989586621679389286 b6989586621679389287 c6989586621679389288 d6989586621679389289) # | |
type Apply [(a, b, c, d)] ([a], [b], [c], [d]) (Unzip4Sym0 a b c d) l # | |
type Unzip4Sym1 (t :: [(a6989586621679389286, b6989586621679389287, c6989586621679389288, d6989586621679389289)]) = Unzip4 t #
data Unzip5Sym0 (l :: TyFun [(a6989586621679389281, b6989586621679389282, c6989586621679389283, d6989586621679389284, e6989586621679389285)] ([a6989586621679389281], [b6989586621679389282], [c6989586621679389283], [d6989586621679389284], [e6989586621679389285])) #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679389281, b6989586621679389282, c6989586621679389283, d6989586621679389284, e6989586621679389285)] ([a6989586621679389281], [b6989586621679389282], [c6989586621679389283], [d6989586621679389284], [e6989586621679389285]) -> *) (Unzip5Sym0 a6989586621679389281 b6989586621679389282 c6989586621679389283 d6989586621679389284 e6989586621679389285) # | |
type Apply [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) (Unzip5Sym0 a b c d e) l # | |
type Unzip5Sym1 (t :: [(a6989586621679389281, b6989586621679389282, c6989586621679389283, d6989586621679389284, e6989586621679389285)]) = Unzip5 t #
data Unzip6Sym0 (l :: TyFun [(a6989586621679389275, b6989586621679389276, c6989586621679389277, d6989586621679389278, e6989586621679389279, f6989586621679389280)] ([a6989586621679389275], [b6989586621679389276], [c6989586621679389277], [d6989586621679389278], [e6989586621679389279], [f6989586621679389280])) #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679389275, b6989586621679389276, c6989586621679389277, d6989586621679389278, e6989586621679389279, f6989586621679389280)] ([a6989586621679389275], [b6989586621679389276], [c6989586621679389277], [d6989586621679389278], [e6989586621679389279], [f6989586621679389280]) -> *) (Unzip6Sym0 a6989586621679389275 b6989586621679389276 c6989586621679389277 d6989586621679389278 e6989586621679389279 f6989586621679389280) # | |
type Apply [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) (Unzip6Sym0 a b c d e f) l # | |
type Unzip6Sym1 (t :: [(a6989586621679389275, b6989586621679389276, c6989586621679389277, d6989586621679389278, e6989586621679389279, f6989586621679389280)]) = Unzip6 t #
data Unzip7Sym0 (l :: TyFun [(a6989586621679389268, b6989586621679389269, c6989586621679389270, d6989586621679389271, e6989586621679389272, f6989586621679389273, g6989586621679389274)] ([a6989586621679389268], [b6989586621679389269], [c6989586621679389270], [d6989586621679389271], [e6989586621679389272], [f6989586621679389273], [g6989586621679389274])) #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679389268, b6989586621679389269, c6989586621679389270, d6989586621679389271, e6989586621679389272, f6989586621679389273, g6989586621679389274)] ([a6989586621679389268], [b6989586621679389269], [c6989586621679389270], [d6989586621679389271], [e6989586621679389272], [f6989586621679389273], [g6989586621679389274]) -> *) (Unzip7Sym0 a6989586621679389268 b6989586621679389269 c6989586621679389270 d6989586621679389271 e6989586621679389272 f6989586621679389273 g6989586621679389274) # | |
type Apply [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) (Unzip7Sym0 a b c d e f g) l # | |
type Unzip7Sym1 (t :: [(a6989586621679389268, b6989586621679389269, c6989586621679389270, d6989586621679389271, e6989586621679389272, f6989586621679389273, g6989586621679389274)]) = Unzip7 t #
data DeleteSym0 (l :: TyFun a6989586621679389267 (TyFun [a6989586621679389267] [a6989586621679389267] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun a6989586621679389267 (TyFun [a6989586621679389267] [a6989586621679389267] -> Type) -> *) (DeleteSym0 a6989586621679389267) # | |
type Apply a6989586621679389267 (TyFun [a6989586621679389267] [a6989586621679389267] -> Type) (DeleteSym0 a6989586621679389267) l # | |
data DeleteSym1 (l :: a6989586621679389267) (l :: TyFun [a6989586621679389267] [a6989586621679389267]) #
Instances
SuppressUnusedWarnings (a6989586621679389267 -> TyFun [a6989586621679389267] [a6989586621679389267] -> *) (DeleteSym1 a6989586621679389267) # | |
type Apply [a] [a] (DeleteSym1 a l1) l2 # | |
type DeleteSym2 (t :: a6989586621679389267) (t :: [a6989586621679389267]) = Delete t t #
data (:\\$) (l :: TyFun [a6989586621679389266] (TyFun [a6989586621679389266] [a6989586621679389266] -> Type)) #
data (l :: [a6989586621679389266]) :\\$$ (l :: TyFun [a6989586621679389266] [a6989586621679389266]) #
data IntersectSym0 (l :: TyFun [a6989586621679389253] (TyFun [a6989586621679389253] [a6989586621679389253] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389253] (TyFun [a6989586621679389253] [a6989586621679389253] -> Type) -> *) (IntersectSym0 a6989586621679389253) # | |
type Apply [a6989586621679389253] (TyFun [a6989586621679389253] [a6989586621679389253] -> Type) (IntersectSym0 a6989586621679389253) l # | |
data IntersectSym1 (l :: [a6989586621679389253]) (l :: TyFun [a6989586621679389253] [a6989586621679389253]) #
Instances
SuppressUnusedWarnings ([a6989586621679389253] -> TyFun [a6989586621679389253] [a6989586621679389253] -> *) (IntersectSym1 a6989586621679389253) # | |
type Apply [a] [a] (IntersectSym1 a l1) l2 # | |
type IntersectSym2 (t :: [a6989586621679389253]) (t :: [a6989586621679389253]) = Intersect t t #
data InsertSym0 (l :: TyFun a6989586621679389240 (TyFun [a6989586621679389240] [a6989586621679389240] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun a6989586621679389240 (TyFun [a6989586621679389240] [a6989586621679389240] -> Type) -> *) (InsertSym0 a6989586621679389240) # | |
type Apply a6989586621679389240 (TyFun [a6989586621679389240] [a6989586621679389240] -> Type) (InsertSym0 a6989586621679389240) l # | |
data InsertSym1 (l :: a6989586621679389240) (l :: TyFun [a6989586621679389240] [a6989586621679389240]) #
Instances
SuppressUnusedWarnings (a6989586621679389240 -> TyFun [a6989586621679389240] [a6989586621679389240] -> *) (InsertSym1 a6989586621679389240) # | |
type Apply [a] [a] (InsertSym1 a l1) l2 # | |
type InsertSym2 (t :: a6989586621679389240) (t :: [a6989586621679389240]) = Insert t t #
data DeleteBySym0 (l :: TyFun (TyFun a6989586621679389265 (TyFun a6989586621679389265 Bool -> Type) -> Type) (TyFun a6989586621679389265 (TyFun [a6989586621679389265] [a6989586621679389265] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389265 (TyFun a6989586621679389265 Bool -> Type) -> Type) (TyFun a6989586621679389265 (TyFun [a6989586621679389265] [a6989586621679389265] -> Type) -> Type) -> *) (DeleteBySym0 a6989586621679389265) # | |
type Apply (TyFun a6989586621679389265 (TyFun a6989586621679389265 Bool -> Type) -> Type) (TyFun a6989586621679389265 (TyFun [a6989586621679389265] [a6989586621679389265] -> Type) -> Type) (DeleteBySym0 a6989586621679389265) l # | |
data DeleteBySym1 (l :: TyFun a6989586621679389265 (TyFun a6989586621679389265 Bool -> Type) -> Type) (l :: TyFun a6989586621679389265 (TyFun [a6989586621679389265] [a6989586621679389265] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389265 (TyFun a6989586621679389265 Bool -> Type) -> Type) -> TyFun a6989586621679389265 (TyFun [a6989586621679389265] [a6989586621679389265] -> Type) -> *) (DeleteBySym1 a6989586621679389265) # | |
type Apply a6989586621679389265 (TyFun [a6989586621679389265] [a6989586621679389265] -> Type) (DeleteBySym1 a6989586621679389265 l1) l2 # | |
data DeleteBySym2 (l :: TyFun a6989586621679389265 (TyFun a6989586621679389265 Bool -> Type) -> Type) (l :: a6989586621679389265) (l :: TyFun [a6989586621679389265] [a6989586621679389265]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389265 (TyFun a6989586621679389265 Bool -> Type) -> Type) -> a6989586621679389265 -> TyFun [a6989586621679389265] [a6989586621679389265] -> *) (DeleteBySym2 a6989586621679389265) # | |
type Apply [a] [a] (DeleteBySym2 a l1 l2) l3 # | |
type DeleteBySym3 (t :: TyFun a6989586621679389265 (TyFun a6989586621679389265 Bool -> Type) -> Type) (t :: a6989586621679389265) (t :: [a6989586621679389265]) = DeleteBy t t t #
data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679389264 (TyFun a6989586621679389264 Bool -> Type) -> Type) (TyFun [a6989586621679389264] (TyFun [a6989586621679389264] [a6989586621679389264] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389264 (TyFun a6989586621679389264 Bool -> Type) -> Type) (TyFun [a6989586621679389264] (TyFun [a6989586621679389264] [a6989586621679389264] -> Type) -> Type) -> *) (DeleteFirstsBySym0 a6989586621679389264) # | |
type Apply (TyFun a6989586621679389264 (TyFun a6989586621679389264 Bool -> Type) -> Type) (TyFun [a6989586621679389264] (TyFun [a6989586621679389264] [a6989586621679389264] -> Type) -> Type) (DeleteFirstsBySym0 a6989586621679389264) l # | |
data DeleteFirstsBySym1 (l :: TyFun a6989586621679389264 (TyFun a6989586621679389264 Bool -> Type) -> Type) (l :: TyFun [a6989586621679389264] (TyFun [a6989586621679389264] [a6989586621679389264] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389264 (TyFun a6989586621679389264 Bool -> Type) -> Type) -> TyFun [a6989586621679389264] (TyFun [a6989586621679389264] [a6989586621679389264] -> Type) -> *) (DeleteFirstsBySym1 a6989586621679389264) # | |
type Apply [a6989586621679389264] (TyFun [a6989586621679389264] [a6989586621679389264] -> Type) (DeleteFirstsBySym1 a6989586621679389264 l1) l2 # | |
data DeleteFirstsBySym2 (l :: TyFun a6989586621679389264 (TyFun a6989586621679389264 Bool -> Type) -> Type) (l :: [a6989586621679389264]) (l :: TyFun [a6989586621679389264] [a6989586621679389264]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389264 (TyFun a6989586621679389264 Bool -> Type) -> Type) -> [a6989586621679389264] -> TyFun [a6989586621679389264] [a6989586621679389264] -> *) (DeleteFirstsBySym2 a6989586621679389264) # | |
type Apply [a] [a] (DeleteFirstsBySym2 a l1 l2) l3 # | |
type DeleteFirstsBySym3 (t :: TyFun a6989586621679389264 (TyFun a6989586621679389264 Bool -> Type) -> Type) (t :: [a6989586621679389264]) (t :: [a6989586621679389264]) = DeleteFirstsBy t t t #
data IntersectBySym0 (l :: TyFun (TyFun a6989586621679389252 (TyFun a6989586621679389252 Bool -> Type) -> Type) (TyFun [a6989586621679389252] (TyFun [a6989586621679389252] [a6989586621679389252] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389252 (TyFun a6989586621679389252 Bool -> Type) -> Type) (TyFun [a6989586621679389252] (TyFun [a6989586621679389252] [a6989586621679389252] -> Type) -> Type) -> *) (IntersectBySym0 a6989586621679389252) # | |
type Apply (TyFun a6989586621679389252 (TyFun a6989586621679389252 Bool -> Type) -> Type) (TyFun [a6989586621679389252] (TyFun [a6989586621679389252] [a6989586621679389252] -> Type) -> Type) (IntersectBySym0 a6989586621679389252) l # | |
data IntersectBySym1 (l :: TyFun a6989586621679389252 (TyFun a6989586621679389252 Bool -> Type) -> Type) (l :: TyFun [a6989586621679389252] (TyFun [a6989586621679389252] [a6989586621679389252] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389252 (TyFun a6989586621679389252 Bool -> Type) -> Type) -> TyFun [a6989586621679389252] (TyFun [a6989586621679389252] [a6989586621679389252] -> Type) -> *) (IntersectBySym1 a6989586621679389252) # | |
type Apply [a6989586621679389252] (TyFun [a6989586621679389252] [a6989586621679389252] -> Type) (IntersectBySym1 a6989586621679389252 l1) l2 # | |
data IntersectBySym2 (l :: TyFun a6989586621679389252 (TyFun a6989586621679389252 Bool -> Type) -> Type) (l :: [a6989586621679389252]) (l :: TyFun [a6989586621679389252] [a6989586621679389252]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389252 (TyFun a6989586621679389252 Bool -> Type) -> Type) -> [a6989586621679389252] -> TyFun [a6989586621679389252] [a6989586621679389252] -> *) (IntersectBySym2 a6989586621679389252) # | |
type Apply [a] [a] (IntersectBySym2 a l1 l2) l3 # | |
data SortBySym0 (l :: TyFun (TyFun a6989586621679389263 (TyFun a6989586621679389263 Ordering -> Type) -> Type) (TyFun [a6989586621679389263] [a6989586621679389263] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389263 (TyFun a6989586621679389263 Ordering -> Type) -> Type) (TyFun [a6989586621679389263] [a6989586621679389263] -> Type) -> *) (SortBySym0 a6989586621679389263) # | |
type Apply (TyFun a6989586621679389263 (TyFun a6989586621679389263 Ordering -> Type) -> Type) (TyFun [a6989586621679389263] [a6989586621679389263] -> Type) (SortBySym0 a6989586621679389263) l # | |
data SortBySym1 (l :: TyFun a6989586621679389263 (TyFun a6989586621679389263 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679389263] [a6989586621679389263]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389263 (TyFun a6989586621679389263 Ordering -> Type) -> Type) -> TyFun [a6989586621679389263] [a6989586621679389263] -> *) (SortBySym1 a6989586621679389263) # | |
type Apply [a] [a] (SortBySym1 a l1) l2 # | |
type SortBySym2 (t :: TyFun a6989586621679389263 (TyFun a6989586621679389263 Ordering -> Type) -> Type) (t :: [a6989586621679389263]) = SortBy t t #
data InsertBySym0 (l :: TyFun (TyFun a6989586621679389262 (TyFun a6989586621679389262 Ordering -> Type) -> Type) (TyFun a6989586621679389262 (TyFun [a6989586621679389262] [a6989586621679389262] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389262 (TyFun a6989586621679389262 Ordering -> Type) -> Type) (TyFun a6989586621679389262 (TyFun [a6989586621679389262] [a6989586621679389262] -> Type) -> Type) -> *) (InsertBySym0 a6989586621679389262) # | |
type Apply (TyFun a6989586621679389262 (TyFun a6989586621679389262 Ordering -> Type) -> Type) (TyFun a6989586621679389262 (TyFun [a6989586621679389262] [a6989586621679389262] -> Type) -> Type) (InsertBySym0 a6989586621679389262) l # | |
data InsertBySym1 (l :: TyFun a6989586621679389262 (TyFun a6989586621679389262 Ordering -> Type) -> Type) (l :: TyFun a6989586621679389262 (TyFun [a6989586621679389262] [a6989586621679389262] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389262 (TyFun a6989586621679389262 Ordering -> Type) -> Type) -> TyFun a6989586621679389262 (TyFun [a6989586621679389262] [a6989586621679389262] -> Type) -> *) (InsertBySym1 a6989586621679389262) # | |
type Apply a6989586621679389262 (TyFun [a6989586621679389262] [a6989586621679389262] -> Type) (InsertBySym1 a6989586621679389262 l1) l2 # | |
data InsertBySym2 (l :: TyFun a6989586621679389262 (TyFun a6989586621679389262 Ordering -> Type) -> Type) (l :: a6989586621679389262) (l :: TyFun [a6989586621679389262] [a6989586621679389262]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389262 (TyFun a6989586621679389262 Ordering -> Type) -> Type) -> a6989586621679389262 -> TyFun [a6989586621679389262] [a6989586621679389262] -> *) (InsertBySym2 a6989586621679389262) # | |
type Apply [a] [a] (InsertBySym2 a l1 l2) l3 # | |
type InsertBySym3 (t :: TyFun a6989586621679389262 (TyFun a6989586621679389262 Ordering -> Type) -> Type) (t :: a6989586621679389262) (t :: [a6989586621679389262]) = InsertBy t t t #
data MaximumBySym0 (l :: TyFun (TyFun a6989586621679389261 (TyFun a6989586621679389261 Ordering -> Type) -> Type) (TyFun [a6989586621679389261] a6989586621679389261 -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389261 (TyFun a6989586621679389261 Ordering -> Type) -> Type) (TyFun [a6989586621679389261] a6989586621679389261 -> Type) -> *) (MaximumBySym0 a6989586621679389261) # | |
type Apply (TyFun a6989586621679389261 (TyFun a6989586621679389261 Ordering -> Type) -> Type) (TyFun [a6989586621679389261] a6989586621679389261 -> Type) (MaximumBySym0 a6989586621679389261) l # | |
data MaximumBySym1 (l :: TyFun a6989586621679389261 (TyFun a6989586621679389261 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679389261] a6989586621679389261) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389261 (TyFun a6989586621679389261 Ordering -> Type) -> Type) -> TyFun [a6989586621679389261] a6989586621679389261 -> *) (MaximumBySym1 a6989586621679389261) # | |
type Apply [a] a (MaximumBySym1 a l1) l2 # | |
type MaximumBySym2 (t :: TyFun a6989586621679389261 (TyFun a6989586621679389261 Ordering -> Type) -> Type) (t :: [a6989586621679389261]) = MaximumBy t t #
data MinimumBySym0 (l :: TyFun (TyFun a6989586621679389260 (TyFun a6989586621679389260 Ordering -> Type) -> Type) (TyFun [a6989586621679389260] a6989586621679389260 -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389260 (TyFun a6989586621679389260 Ordering -> Type) -> Type) (TyFun [a6989586621679389260] a6989586621679389260 -> Type) -> *) (MinimumBySym0 a6989586621679389260) # | |
type Apply (TyFun a6989586621679389260 (TyFun a6989586621679389260 Ordering -> Type) -> Type) (TyFun [a6989586621679389260] a6989586621679389260 -> Type) (MinimumBySym0 a6989586621679389260) l # | |
data MinimumBySym1 (l :: TyFun a6989586621679389260 (TyFun a6989586621679389260 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679389260] a6989586621679389260) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389260 (TyFun a6989586621679389260 Ordering -> Type) -> Type) -> TyFun [a6989586621679389260] a6989586621679389260 -> *) (MinimumBySym1 a6989586621679389260) # | |
type Apply [a] a (MinimumBySym1 a l1) l2 # | |
type MinimumBySym2 (t :: TyFun a6989586621679389260 (TyFun a6989586621679389260 Ordering -> Type) -> Type) (t :: [a6989586621679389260]) = MinimumBy t t #
data LengthSym0 (l :: TyFun [a6989586621679389231] Nat) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389231] Nat -> *) (LengthSym0 a6989586621679389231) # | |
type Apply [a] Nat (LengthSym0 a) l # | |
type LengthSym1 (t :: [a6989586621679389231]) = Length t #
data ProductSym0 (l :: TyFun [a6989586621679389232] a6989586621679389232) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389232] a6989586621679389232 -> *) (ProductSym0 a6989586621679389232) # | |
type Apply [a] a (ProductSym0 a) l # | |
type ProductSym1 (t :: [a6989586621679389232]) = Product t #
data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679389230 [a6989586621679389230] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun Nat (TyFun a6989586621679389230 [a6989586621679389230] -> Type) -> *) (ReplicateSym0 a6989586621679389230) # | |
type Apply Nat (TyFun a6989586621679389230 [a6989586621679389230] -> Type) (ReplicateSym0 a6989586621679389230) l # | |
data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679389230 [a6989586621679389230]) #
Instances
SuppressUnusedWarnings (Nat -> TyFun a6989586621679389230 [a6989586621679389230] -> *) (ReplicateSym1 a6989586621679389230) # | |
type Apply a [a] (ReplicateSym1 a l1) l2 # | |
type ReplicateSym2 (t :: Nat) (t :: a6989586621679389230) = Replicate t t #
data TransposeSym0 (l :: TyFun [[a6989586621679389229]] [[a6989586621679389229]]) #
Instances
SuppressUnusedWarnings (TyFun [[a6989586621679389229]] [[a6989586621679389229]] -> *) (TransposeSym0 a6989586621679389229) # | |
type Apply [[a]] [[a]] (TransposeSym0 a) l # | |
type TransposeSym1 (t :: [[a6989586621679389229]]) = Transpose t #
data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679389244] ([a6989586621679389244], [a6989586621679389244]) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679389244] ([a6989586621679389244], [a6989586621679389244]) -> Type) -> *) (SplitAtSym0 a6989586621679389244) # | |
type Apply Nat (TyFun [a6989586621679389244] ([a6989586621679389244], [a6989586621679389244]) -> Type) (SplitAtSym0 a6989586621679389244) l # | |
data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679389244] ([a6989586621679389244], [a6989586621679389244])) #
Instances
SuppressUnusedWarnings (Nat -> TyFun [a6989586621679389244] ([a6989586621679389244], [a6989586621679389244]) -> *) (SplitAtSym1 a6989586621679389244) # | |
type Apply [a] ([a], [a]) (SplitAtSym1 a l1) l2 # | |
type SplitAtSym2 (t :: Nat) (t :: [a6989586621679389244]) = SplitAt t t #
data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679389251 Bool -> Type) (TyFun [a6989586621679389251] [a6989586621679389251] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389251 Bool -> Type) (TyFun [a6989586621679389251] [a6989586621679389251] -> Type) -> *) (TakeWhileSym0 a6989586621679389251) # | |
type Apply (TyFun a6989586621679389251 Bool -> Type) (TyFun [a6989586621679389251] [a6989586621679389251] -> Type) (TakeWhileSym0 a6989586621679389251) l # | |
data TakeWhileSym1 (l :: TyFun a6989586621679389251 Bool -> Type) (l :: TyFun [a6989586621679389251] [a6989586621679389251]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389251 Bool -> Type) -> TyFun [a6989586621679389251] [a6989586621679389251] -> *) (TakeWhileSym1 a6989586621679389251) # | |
type Apply [a] [a] (TakeWhileSym1 a l1) l2 # | |
type TakeWhileSym2 (t :: TyFun a6989586621679389251 Bool -> Type) (t :: [a6989586621679389251]) = TakeWhile t t #
data DropWhileSym0 (l :: TyFun (TyFun a6989586621679389250 Bool -> Type) (TyFun [a6989586621679389250] [a6989586621679389250] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389250 Bool -> Type) (TyFun [a6989586621679389250] [a6989586621679389250] -> Type) -> *) (DropWhileSym0 a6989586621679389250) # | |
type Apply (TyFun a6989586621679389250 Bool -> Type) (TyFun [a6989586621679389250] [a6989586621679389250] -> Type) (DropWhileSym0 a6989586621679389250) l # | |
data DropWhileSym1 (l :: TyFun a6989586621679389250 Bool -> Type) (l :: TyFun [a6989586621679389250] [a6989586621679389250]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389250 Bool -> Type) -> TyFun [a6989586621679389250] [a6989586621679389250] -> *) (DropWhileSym1 a6989586621679389250) # | |
type Apply [a] [a] (DropWhileSym1 a l1) l2 # | |
type DropWhileSym2 (t :: TyFun a6989586621679389250 Bool -> Type) (t :: [a6989586621679389250]) = DropWhile t t #
data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679389249 Bool -> Type) (TyFun [a6989586621679389249] [a6989586621679389249] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389249 Bool -> Type) (TyFun [a6989586621679389249] [a6989586621679389249] -> Type) -> *) (DropWhileEndSym0 a6989586621679389249) # | |
type Apply (TyFun a6989586621679389249 Bool -> Type) (TyFun [a6989586621679389249] [a6989586621679389249] -> Type) (DropWhileEndSym0 a6989586621679389249) l # | |
data DropWhileEndSym1 (l :: TyFun a6989586621679389249 Bool -> Type) (l :: TyFun [a6989586621679389249] [a6989586621679389249]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389249 Bool -> Type) -> TyFun [a6989586621679389249] [a6989586621679389249] -> *) (DropWhileEndSym1 a6989586621679389249) # | |
type Apply [a] [a] (DropWhileEndSym1 a l1) l2 # | |
type DropWhileEndSym2 (t :: TyFun a6989586621679389249 Bool -> Type) (t :: [a6989586621679389249]) = DropWhileEnd t t #
data SpanSym0 (l :: TyFun (TyFun a6989586621679389248 Bool -> Type) (TyFun [a6989586621679389248] ([a6989586621679389248], [a6989586621679389248]) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389248 Bool -> Type) (TyFun [a6989586621679389248] ([a6989586621679389248], [a6989586621679389248]) -> Type) -> *) (SpanSym0 a6989586621679389248) # | |
type Apply (TyFun a6989586621679389248 Bool -> Type) (TyFun [a6989586621679389248] ([a6989586621679389248], [a6989586621679389248]) -> Type) (SpanSym0 a6989586621679389248) l # | |
data SpanSym1 (l :: TyFun a6989586621679389248 Bool -> Type) (l :: TyFun [a6989586621679389248] ([a6989586621679389248], [a6989586621679389248])) #
type SpanSym2 (t :: TyFun a6989586621679389248 Bool -> Type) (t :: [a6989586621679389248]) = Span t t #
data BreakSym0 (l :: TyFun (TyFun a6989586621679389247 Bool -> Type) (TyFun [a6989586621679389247] ([a6989586621679389247], [a6989586621679389247]) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389247 Bool -> Type) (TyFun [a6989586621679389247] ([a6989586621679389247], [a6989586621679389247]) -> Type) -> *) (BreakSym0 a6989586621679389247) # | |
type Apply (TyFun a6989586621679389247 Bool -> Type) (TyFun [a6989586621679389247] ([a6989586621679389247], [a6989586621679389247]) -> Type) (BreakSym0 a6989586621679389247) l # | |
data BreakSym1 (l :: TyFun a6989586621679389247 Bool -> Type) (l :: TyFun [a6989586621679389247] ([a6989586621679389247], [a6989586621679389247])) #
type BreakSym2 (t :: TyFun a6989586621679389247 Bool -> Type) (t :: [a6989586621679389247]) = Break t t #
data StripPrefixSym0 (l :: TyFun [a6989586621679727944] (TyFun [a6989586621679727944] (Maybe [a6989586621679727944]) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679727944] (TyFun [a6989586621679727944] (Maybe [a6989586621679727944]) -> Type) -> *) (StripPrefixSym0 a6989586621679727944) # | |
type Apply [a6989586621679727944] (TyFun [a6989586621679727944] (Maybe [a6989586621679727944]) -> Type) (StripPrefixSym0 a6989586621679727944) l # | |
data StripPrefixSym1 (l :: [a6989586621679727944]) (l :: TyFun [a6989586621679727944] (Maybe [a6989586621679727944])) #
Instances
SuppressUnusedWarnings ([a6989586621679727944] -> TyFun [a6989586621679727944] (Maybe [a6989586621679727944]) -> *) (StripPrefixSym1 a6989586621679727944) # | |
type Apply [a] (Maybe [a]) (StripPrefixSym1 a l1) l2 # | |
type StripPrefixSym2 (t :: [a6989586621679727944]) (t :: [a6989586621679727944]) = StripPrefix t t #
data MaximumSym0 (l :: TyFun [a6989586621679389242] a6989586621679389242) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389242] a6989586621679389242 -> *) (MaximumSym0 a6989586621679389242) # | |
type Apply [a] a (MaximumSym0 a) l # | |
type MaximumSym1 (t :: [a6989586621679389242]) = Maximum t #
data MinimumSym0 (l :: TyFun [a6989586621679389241] a6989586621679389241) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389241] a6989586621679389241 -> *) (MinimumSym0 a6989586621679389241) # | |
type Apply [a] a (MinimumSym0 a) l # | |
type MinimumSym1 (t :: [a6989586621679389241]) = Minimum t #
data GroupBySym0 (l :: TyFun (TyFun a6989586621679389238 (TyFun a6989586621679389238 Bool -> Type) -> Type) (TyFun [a6989586621679389238] [[a6989586621679389238]] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389238 (TyFun a6989586621679389238 Bool -> Type) -> Type) (TyFun [a6989586621679389238] [[a6989586621679389238]] -> Type) -> *) (GroupBySym0 a6989586621679389238) # | |
type Apply (TyFun a6989586621679389238 (TyFun a6989586621679389238 Bool -> Type) -> Type) (TyFun [a6989586621679389238] [[a6989586621679389238]] -> Type) (GroupBySym0 a6989586621679389238) l # | |
data GroupBySym1 (l :: TyFun a6989586621679389238 (TyFun a6989586621679389238 Bool -> Type) -> Type) (l :: TyFun [a6989586621679389238] [[a6989586621679389238]]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389238 (TyFun a6989586621679389238 Bool -> Type) -> Type) -> TyFun [a6989586621679389238] [[a6989586621679389238]] -> *) (GroupBySym1 a6989586621679389238) # | |
type Apply [a] [[a]] (GroupBySym1 a l1) l2 # | |
type GroupBySym2 (t :: TyFun a6989586621679389238 (TyFun a6989586621679389238 Bool -> Type) -> Type) (t :: [a6989586621679389238]) = GroupBy t t #
data LookupSym0 (l :: TyFun a6989586621679389236 (TyFun [(a6989586621679389236, b6989586621679389237)] (Maybe b6989586621679389237) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun a6989586621679389236 (TyFun [(a6989586621679389236, b6989586621679389237)] (Maybe b6989586621679389237) -> Type) -> *) (LookupSym0 a6989586621679389236 b6989586621679389237) # | |
type Apply a6989586621679389236 (TyFun [(a6989586621679389236, b6989586621679389237)] (Maybe b6989586621679389237) -> Type) (LookupSym0 a6989586621679389236 b6989586621679389237) l # | |
data LookupSym1 (l :: a6989586621679389236) (l :: TyFun [(a6989586621679389236, b6989586621679389237)] (Maybe b6989586621679389237)) #
Instances
SuppressUnusedWarnings (a6989586621679389236 -> TyFun [(a6989586621679389236, b6989586621679389237)] (Maybe b6989586621679389237) -> *) (LookupSym1 a6989586621679389236 b6989586621679389237) # | |
type Apply [(a, b)] (Maybe b) (LookupSym1 a b l1) l2 # | |
type LookupSym2 (t :: a6989586621679389236) (t :: [(a6989586621679389236, b6989586621679389237)]) = Lookup t t #
data FindSym0 (l :: TyFun (TyFun a6989586621679389258 Bool -> Type) (TyFun [a6989586621679389258] (Maybe a6989586621679389258) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389258 Bool -> Type) (TyFun [a6989586621679389258] (Maybe a6989586621679389258) -> Type) -> *) (FindSym0 a6989586621679389258) # | |
type Apply (TyFun a6989586621679389258 Bool -> Type) (TyFun [a6989586621679389258] (Maybe a6989586621679389258) -> Type) (FindSym0 a6989586621679389258) l # | |
data FindSym1 (l :: TyFun a6989586621679389258 Bool -> Type) (l :: TyFun [a6989586621679389258] (Maybe a6989586621679389258)) #
type FindSym2 (t :: TyFun a6989586621679389258 Bool -> Type) (t :: [a6989586621679389258]) = Find t t #
data FilterSym0 (l :: TyFun (TyFun a6989586621679389259 Bool -> Type) (TyFun [a6989586621679389259] [a6989586621679389259] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389259 Bool -> Type) (TyFun [a6989586621679389259] [a6989586621679389259] -> Type) -> *) (FilterSym0 a6989586621679389259) # | |
type Apply (TyFun a6989586621679389259 Bool -> Type) (TyFun [a6989586621679389259] [a6989586621679389259] -> Type) (FilterSym0 a6989586621679389259) l # | |
data FilterSym1 (l :: TyFun a6989586621679389259 Bool -> Type) (l :: TyFun [a6989586621679389259] [a6989586621679389259]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389259 Bool -> Type) -> TyFun [a6989586621679389259] [a6989586621679389259] -> *) (FilterSym1 a6989586621679389259) # | |
type Apply [a] [a] (FilterSym1 a l1) l2 # | |
type FilterSym2 (t :: TyFun a6989586621679389259 Bool -> Type) (t :: [a6989586621679389259]) = Filter t t #
data PartitionSym0 (l :: TyFun (TyFun a6989586621679389235 Bool -> Type) (TyFun [a6989586621679389235] ([a6989586621679389235], [a6989586621679389235]) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389235 Bool -> Type) (TyFun [a6989586621679389235] ([a6989586621679389235], [a6989586621679389235]) -> Type) -> *) (PartitionSym0 a6989586621679389235) # | |
type Apply (TyFun a6989586621679389235 Bool -> Type) (TyFun [a6989586621679389235] ([a6989586621679389235], [a6989586621679389235]) -> Type) (PartitionSym0 a6989586621679389235) l # | |
data PartitionSym1 (l :: TyFun a6989586621679389235 Bool -> Type) (l :: TyFun [a6989586621679389235] ([a6989586621679389235], [a6989586621679389235])) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389235 Bool -> Type) -> TyFun [a6989586621679389235] ([a6989586621679389235], [a6989586621679389235]) -> *) (PartitionSym1 a6989586621679389235) # | |
type Apply [a] ([a], [a]) (PartitionSym1 a l1) l2 # | |
type PartitionSym2 (t :: TyFun a6989586621679389235 Bool -> Type) (t :: [a6989586621679389235]) = Partition t t #
data ElemIndexSym0 (l :: TyFun a6989586621679389257 (TyFun [a6989586621679389257] (Maybe Nat) -> Type)) #
data ElemIndexSym1 (l :: a6989586621679389257) (l :: TyFun [a6989586621679389257] (Maybe Nat)) #
Instances
SuppressUnusedWarnings (a6989586621679389257 -> TyFun [a6989586621679389257] (Maybe Nat) -> *) (ElemIndexSym1 a6989586621679389257) # | |
type Apply [a] (Maybe Nat) (ElemIndexSym1 a l1) l2 # | |
type ElemIndexSym2 (t :: a6989586621679389257) (t :: [a6989586621679389257]) = ElemIndex t t #
data ElemIndicesSym0 (l :: TyFun a6989586621679389256 (TyFun [a6989586621679389256] [Nat] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun a6989586621679389256 (TyFun [a6989586621679389256] [Nat] -> Type) -> *) (ElemIndicesSym0 a6989586621679389256) # | |
type Apply a6989586621679389256 (TyFun [a6989586621679389256] [Nat] -> Type) (ElemIndicesSym0 a6989586621679389256) l # | |
data ElemIndicesSym1 (l :: a6989586621679389256) (l :: TyFun [a6989586621679389256] [Nat]) #
Instances
SuppressUnusedWarnings (a6989586621679389256 -> TyFun [a6989586621679389256] [Nat] -> *) (ElemIndicesSym1 a6989586621679389256) # | |
type Apply [a] [Nat] (ElemIndicesSym1 a l1) l2 # | |
type ElemIndicesSym2 (t :: a6989586621679389256) (t :: [a6989586621679389256]) = ElemIndices t t #
data FindIndexSym0 (l :: TyFun (TyFun a6989586621679389255 Bool -> Type) (TyFun [a6989586621679389255] (Maybe Nat) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389255 Bool -> Type) (TyFun [a6989586621679389255] (Maybe Nat) -> Type) -> *) (FindIndexSym0 a6989586621679389255) # | |
type Apply (TyFun a6989586621679389255 Bool -> Type) (TyFun [a6989586621679389255] (Maybe Nat) -> Type) (FindIndexSym0 a6989586621679389255) l # | |
data FindIndexSym1 (l :: TyFun a6989586621679389255 Bool -> Type) (l :: TyFun [a6989586621679389255] (Maybe Nat)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389255 Bool -> Type) -> TyFun [a6989586621679389255] (Maybe Nat) -> *) (FindIndexSym1 a6989586621679389255) # | |
type Apply [a] (Maybe Nat) (FindIndexSym1 a l1) l2 # | |
type FindIndexSym2 (t :: TyFun a6989586621679389255 Bool -> Type) (t :: [a6989586621679389255]) = FindIndex t t #
data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679389254 Bool -> Type) (TyFun [a6989586621679389254] [Nat] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389254 Bool -> Type) (TyFun [a6989586621679389254] [Nat] -> Type) -> *) (FindIndicesSym0 a6989586621679389254) # | |
type Apply (TyFun a6989586621679389254 Bool -> Type) (TyFun [a6989586621679389254] [Nat] -> Type) (FindIndicesSym0 a6989586621679389254) l # | |
data FindIndicesSym1 (l :: TyFun a6989586621679389254 Bool -> Type) (l :: TyFun [a6989586621679389254] [Nat]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389254 Bool -> Type) -> TyFun [a6989586621679389254] [Nat] -> *) (FindIndicesSym1 a6989586621679389254) # | |
type Apply [a] [Nat] (FindIndicesSym1 a l1) l2 # | |
type FindIndicesSym2 (t :: TyFun a6989586621679389254 Bool -> Type) (t :: [a6989586621679389254]) = FindIndices t t #
data Zip4Sym0 (l :: TyFun [a6989586621679727940] (TyFun [b6989586621679727941] (TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679727940] (TyFun [b6989586621679727941] (TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) -> Type) -> Type) -> *) (Zip4Sym0 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) # | |
type Apply [a6989586621679727940] (TyFun [b6989586621679727941] (TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) -> Type) -> Type) (Zip4Sym0 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) l # | |
data Zip4Sym1 (l :: [a6989586621679727940]) (l :: TyFun [b6989586621679727941] (TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727940] -> TyFun [b6989586621679727941] (TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) -> Type) -> *) (Zip4Sym1 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) # | |
type Apply [b6989586621679727941] (TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) -> Type) (Zip4Sym1 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943 l1) l2 # | |
data Zip4Sym2 (l :: [a6989586621679727940]) (l :: [b6989586621679727941]) (l :: TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727940] -> [b6989586621679727941] -> TyFun [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) -> *) (Zip4Sym2 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) # | |
type Apply [c6989586621679727942] (TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> Type) (Zip4Sym2 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943 l1 l2) l3 # | |
data Zip4Sym3 (l :: [a6989586621679727940]) (l :: [b6989586621679727941]) (l :: [c6989586621679727942]) (l :: TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)]) #
Instances
SuppressUnusedWarnings ([a6989586621679727940] -> [b6989586621679727941] -> [c6989586621679727942] -> TyFun [d6989586621679727943] [(a6989586621679727940, b6989586621679727941, c6989586621679727942, d6989586621679727943)] -> *) (Zip4Sym3 a6989586621679727940 b6989586621679727941 c6989586621679727942 d6989586621679727943) # | |
type Apply [d] [(a, b, c, d)] (Zip4Sym3 a b c d l1 l2 l3) l4 # | |
type Zip4Sym4 (t :: [a6989586621679727940]) (t :: [b6989586621679727941]) (t :: [c6989586621679727942]) (t :: [d6989586621679727943]) = Zip4 t t t t #
data Zip5Sym0 (l :: TyFun [a6989586621679727935] (TyFun [b6989586621679727936] (TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679727935] (TyFun [b6989586621679727936] (TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip5Sym0 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) # | |
type Apply [a6989586621679727935] (TyFun [b6989586621679727936] (TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) -> Type) -> Type) (Zip5Sym0 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) l # | |
data Zip5Sym1 (l :: [a6989586621679727935]) (l :: TyFun [b6989586621679727936] (TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727935] -> TyFun [b6989586621679727936] (TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) -> Type) -> *) (Zip5Sym1 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) # | |
type Apply [b6989586621679727936] (TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) -> Type) (Zip5Sym1 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939 l1) l2 # | |
data Zip5Sym2 (l :: [a6989586621679727935]) (l :: [b6989586621679727936]) (l :: TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727935] -> [b6989586621679727936] -> TyFun [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) -> *) (Zip5Sym2 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) # | |
type Apply [c6989586621679727937] (TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> Type) (Zip5Sym2 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939 l1 l2) l3 # | |
data Zip5Sym3 (l :: [a6989586621679727935]) (l :: [b6989586621679727936]) (l :: [c6989586621679727937]) (l :: TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727935] -> [b6989586621679727936] -> [c6989586621679727937] -> TyFun [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) -> *) (Zip5Sym3 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) # | |
type Apply [d6989586621679727938] (TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> Type) (Zip5Sym3 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939 l1 l2 l3) l4 # | |
data Zip5Sym4 (l :: [a6989586621679727935]) (l :: [b6989586621679727936]) (l :: [c6989586621679727937]) (l :: [d6989586621679727938]) (l :: TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)]) #
Instances
SuppressUnusedWarnings ([a6989586621679727935] -> [b6989586621679727936] -> [c6989586621679727937] -> [d6989586621679727938] -> TyFun [e6989586621679727939] [(a6989586621679727935, b6989586621679727936, c6989586621679727937, d6989586621679727938, e6989586621679727939)] -> *) (Zip5Sym4 a6989586621679727935 b6989586621679727936 c6989586621679727937 d6989586621679727938 e6989586621679727939) # | |
type Apply [e] [(a, b, c, d, e)] (Zip5Sym4 a b c d e l1 l2 l3 l4) l5 # | |
type Zip5Sym5 (t :: [a6989586621679727935]) (t :: [b6989586621679727936]) (t :: [c6989586621679727937]) (t :: [d6989586621679727938]) (t :: [e6989586621679727939]) = Zip5 t t t t t #
data Zip6Sym0 (l :: TyFun [a6989586621679727929] (TyFun [b6989586621679727930] (TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679727929] (TyFun [b6989586621679727930] (TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym0 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) # | |
type Apply [a6989586621679727929] (TyFun [b6989586621679727930] (TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip6Sym0 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) l # | |
data Zip6Sym1 (l :: [a6989586621679727929]) (l :: TyFun [b6989586621679727930] (TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727929] -> TyFun [b6989586621679727930] (TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym1 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) # | |
type Apply [b6989586621679727930] (TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) -> Type) (Zip6Sym1 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934 l1) l2 # | |
data Zip6Sym2 (l :: [a6989586621679727929]) (l :: [b6989586621679727930]) (l :: TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727929] -> [b6989586621679727930] -> TyFun [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) -> *) (Zip6Sym2 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) # | |
type Apply [c6989586621679727931] (TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> Type) (Zip6Sym2 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934 l1 l2) l3 # | |
data Zip6Sym3 (l :: [a6989586621679727929]) (l :: [b6989586621679727930]) (l :: [c6989586621679727931]) (l :: TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727929] -> [b6989586621679727930] -> [c6989586621679727931] -> TyFun [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) -> *) (Zip6Sym3 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) # | |
type Apply [d6989586621679727932] (TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> Type) (Zip6Sym3 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934 l1 l2 l3) l4 # | |
data Zip6Sym4 (l :: [a6989586621679727929]) (l :: [b6989586621679727930]) (l :: [c6989586621679727931]) (l :: [d6989586621679727932]) (l :: TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727929] -> [b6989586621679727930] -> [c6989586621679727931] -> [d6989586621679727932] -> TyFun [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) -> *) (Zip6Sym4 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) # | |
type Apply [e6989586621679727933] (TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> Type) (Zip6Sym4 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934 l1 l2 l3 l4) l5 # | |
data Zip6Sym5 (l :: [a6989586621679727929]) (l :: [b6989586621679727930]) (l :: [c6989586621679727931]) (l :: [d6989586621679727932]) (l :: [e6989586621679727933]) (l :: TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)]) #
Instances
SuppressUnusedWarnings ([a6989586621679727929] -> [b6989586621679727930] -> [c6989586621679727931] -> [d6989586621679727932] -> [e6989586621679727933] -> TyFun [f6989586621679727934] [(a6989586621679727929, b6989586621679727930, c6989586621679727931, d6989586621679727932, e6989586621679727933, f6989586621679727934)] -> *) (Zip6Sym5 a6989586621679727929 b6989586621679727930 c6989586621679727931 d6989586621679727932 e6989586621679727933 f6989586621679727934) # | |
type Apply [f] [(a, b, c, d, e, f)] (Zip6Sym5 a b c d e f l1 l2 l3 l4 l5) l6 # | |
type Zip6Sym6 (t :: [a6989586621679727929]) (t :: [b6989586621679727930]) (t :: [c6989586621679727931]) (t :: [d6989586621679727932]) (t :: [e6989586621679727933]) (t :: [f6989586621679727934]) = Zip6 t t t t t t #
data Zip7Sym0 (l :: TyFun [a6989586621679727922] (TyFun [b6989586621679727923] (TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679727922] (TyFun [b6989586621679727923] (TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym0 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # | |
type Apply [a6989586621679727922] (TyFun [b6989586621679727923] (TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym0 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) l # | |
data Zip7Sym1 (l :: [a6989586621679727922]) (l :: TyFun [b6989586621679727923] (TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727922] -> TyFun [b6989586621679727923] (TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym1 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # | |
type Apply [b6989586621679727923] (TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym1 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928 l1) l2 # | |
data Zip7Sym2 (l :: [a6989586621679727922]) (l :: [b6989586621679727923]) (l :: TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727922] -> [b6989586621679727923] -> TyFun [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym2 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # | |
type Apply [c6989586621679727924] (TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> Type) (Zip7Sym2 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928 l1 l2) l3 # | |
data Zip7Sym3 (l :: [a6989586621679727922]) (l :: [b6989586621679727923]) (l :: [c6989586621679727924]) (l :: TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727922] -> [b6989586621679727923] -> [c6989586621679727924] -> TyFun [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) -> *) (Zip7Sym3 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # | |
type Apply [d6989586621679727925] (TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> Type) (Zip7Sym3 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928 l1 l2 l3) l4 # | |
data Zip7Sym4 (l :: [a6989586621679727922]) (l :: [b6989586621679727923]) (l :: [c6989586621679727924]) (l :: [d6989586621679727925]) (l :: TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727922] -> [b6989586621679727923] -> [c6989586621679727924] -> [d6989586621679727925] -> TyFun [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) -> *) (Zip7Sym4 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # | |
type Apply [e6989586621679727926] (TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> Type) (Zip7Sym4 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928 l1 l2 l3 l4) l5 # | |
data Zip7Sym5 (l :: [a6989586621679727922]) (l :: [b6989586621679727923]) (l :: [c6989586621679727924]) (l :: [d6989586621679727925]) (l :: [e6989586621679727926]) (l :: TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type)) #
Instances
SuppressUnusedWarnings ([a6989586621679727922] -> [b6989586621679727923] -> [c6989586621679727924] -> [d6989586621679727925] -> [e6989586621679727926] -> TyFun [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) -> *) (Zip7Sym5 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # | |
type Apply [f6989586621679727927] (TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> Type) (Zip7Sym5 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928 l1 l2 l3 l4 l5) l6 # | |
data Zip7Sym6 (l :: [a6989586621679727922]) (l :: [b6989586621679727923]) (l :: [c6989586621679727924]) (l :: [d6989586621679727925]) (l :: [e6989586621679727926]) (l :: [f6989586621679727927]) (l :: TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)]) #
Instances
SuppressUnusedWarnings ([a6989586621679727922] -> [b6989586621679727923] -> [c6989586621679727924] -> [d6989586621679727925] -> [e6989586621679727926] -> [f6989586621679727927] -> TyFun [g6989586621679727928] [(a6989586621679727922, b6989586621679727923, c6989586621679727924, d6989586621679727925, e6989586621679727926, f6989586621679727927, g6989586621679727928)] -> *) (Zip7Sym6 a6989586621679727922 b6989586621679727923 c6989586621679727924 d6989586621679727925 e6989586621679727926 f6989586621679727927 g6989586621679727928) # | |
type Apply [g] [(a, b, c, d, e, f, g)] (Zip7Sym6 a b c d e f g l1 l2 l3 l4 l5 l6) l7 # | |
type Zip7Sym7 (t :: [a6989586621679727922]) (t :: [b6989586621679727923]) (t :: [c6989586621679727924]) (t :: [d6989586621679727925]) (t :: [e6989586621679727926]) (t :: [f6989586621679727927]) (t :: [g6989586621679727928]) = Zip7 t t t t t t t #
data ZipWith4Sym0 (l :: TyFun (TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727917] (TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727917] (TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith4Sym0 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) # | |
type Apply (TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727917] (TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) -> Type) -> Type) (ZipWith4Sym0 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) l # | |
data ZipWith4Sym1 (l :: TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679727917] (TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679727917] (TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) -> Type) -> *) (ZipWith4Sym1 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) # | |
type Apply [a6989586621679727917] (TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) -> Type) (ZipWith4Sym1 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921 l1) l2 # | |
data ZipWith4Sym2 (l :: TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727917]) (l :: TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727917] -> TyFun [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) -> *) (ZipWith4Sym2 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) # | |
type Apply [b6989586621679727918] (TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> Type) (ZipWith4Sym2 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921 l1 l2) l3 # | |
data ZipWith4Sym3 (l :: TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727917]) (l :: [b6989586621679727918]) (l :: TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727917] -> [b6989586621679727918] -> TyFun [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) -> *) (ZipWith4Sym3 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) # | |
type Apply [c6989586621679727919] (TyFun [d6989586621679727920] [e6989586621679727921] -> Type) (ZipWith4Sym3 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921 l1 l2 l3) l4 # | |
data ZipWith4Sym4 (l :: TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727917]) (l :: [b6989586621679727918]) (l :: [c6989586621679727919]) (l :: TyFun [d6989586621679727920] [e6989586621679727921]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727917] -> [b6989586621679727918] -> [c6989586621679727919] -> TyFun [d6989586621679727920] [e6989586621679727921] -> *) (ZipWith4Sym4 a6989586621679727917 b6989586621679727918 c6989586621679727919 d6989586621679727920 e6989586621679727921) # | |
type Apply [d] [e] (ZipWith4Sym4 a b c d e l1 l2 l3 l4) l5 # | |
type ZipWith4Sym5 (t :: TyFun a6989586621679727917 (TyFun b6989586621679727918 (TyFun c6989586621679727919 (TyFun d6989586621679727920 e6989586621679727921 -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679727917]) (t :: [b6989586621679727918]) (t :: [c6989586621679727919]) (t :: [d6989586621679727920]) = ZipWith4 t t t t t #
data ZipWith5Sym0 (l :: TyFun (TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727911] (TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727911] (TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym0 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) # | |
type Apply (TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727911] (TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym0 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) l # | |
data ZipWith5Sym1 (l :: TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679727911] (TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679727911] (TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym1 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) # | |
type Apply [a6989586621679727911] (TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym1 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916 l1) l2 # | |
data ZipWith5Sym2 (l :: TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727911]) (l :: TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727911] -> TyFun [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) -> *) (ZipWith5Sym2 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) # | |
type Apply [b6989586621679727912] (TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> Type) (ZipWith5Sym2 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916 l1 l2) l3 # | |
data ZipWith5Sym3 (l :: TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727911]) (l :: [b6989586621679727912]) (l :: TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727911] -> [b6989586621679727912] -> TyFun [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) -> *) (ZipWith5Sym3 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) # | |
type Apply [c6989586621679727913] (TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> Type) (ZipWith5Sym3 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916 l1 l2 l3) l4 # | |
data ZipWith5Sym4 (l :: TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727911]) (l :: [b6989586621679727912]) (l :: [c6989586621679727913]) (l :: TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727911] -> [b6989586621679727912] -> [c6989586621679727913] -> TyFun [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) -> *) (ZipWith5Sym4 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) # | |
type Apply [d6989586621679727914] (TyFun [e6989586621679727915] [f6989586621679727916] -> Type) (ZipWith5Sym4 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916 l1 l2 l3 l4) l5 # | |
data ZipWith5Sym5 (l :: TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727911]) (l :: [b6989586621679727912]) (l :: [c6989586621679727913]) (l :: [d6989586621679727914]) (l :: TyFun [e6989586621679727915] [f6989586621679727916]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727911] -> [b6989586621679727912] -> [c6989586621679727913] -> [d6989586621679727914] -> TyFun [e6989586621679727915] [f6989586621679727916] -> *) (ZipWith5Sym5 a6989586621679727911 b6989586621679727912 c6989586621679727913 d6989586621679727914 e6989586621679727915 f6989586621679727916) # | |
type Apply [e] [f] (ZipWith5Sym5 a b c d e f l1 l2 l3 l4 l5) l6 # | |
type ZipWith5Sym6 (t :: TyFun a6989586621679727911 (TyFun b6989586621679727912 (TyFun c6989586621679727913 (TyFun d6989586621679727914 (TyFun e6989586621679727915 f6989586621679727916 -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679727911]) (t :: [b6989586621679727912]) (t :: [c6989586621679727913]) (t :: [d6989586621679727914]) (t :: [e6989586621679727915]) = ZipWith5 t t t t t t #
data ZipWith6Sym0 (l :: TyFun (TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727904] (TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727904] (TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym0 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # | |
type Apply (TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727904] (TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym0 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) l # | |
data ZipWith6Sym1 (l :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679727904] (TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679727904] (TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym1 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # | |
type Apply [a6989586621679727904] (TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym1 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910 l1) l2 # | |
data ZipWith6Sym2 (l :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727904]) (l :: TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727904] -> TyFun [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym2 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # | |
type Apply [b6989586621679727905] (TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym2 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910 l1 l2) l3 # | |
data ZipWith6Sym3 (l :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727904]) (l :: [b6989586621679727905]) (l :: TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727904] -> [b6989586621679727905] -> TyFun [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) -> *) (ZipWith6Sym3 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # | |
type Apply [c6989586621679727906] (TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> Type) (ZipWith6Sym3 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910 l1 l2 l3) l4 # | |
data ZipWith6Sym4 (l :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727904]) (l :: [b6989586621679727905]) (l :: [c6989586621679727906]) (l :: TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727904] -> [b6989586621679727905] -> [c6989586621679727906] -> TyFun [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) -> *) (ZipWith6Sym4 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # | |
type Apply [d6989586621679727907] (TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> Type) (ZipWith6Sym4 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910 l1 l2 l3 l4) l5 # | |
data ZipWith6Sym5 (l :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727904]) (l :: [b6989586621679727905]) (l :: [c6989586621679727906]) (l :: [d6989586621679727907]) (l :: TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727904] -> [b6989586621679727905] -> [c6989586621679727906] -> [d6989586621679727907] -> TyFun [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) -> *) (ZipWith6Sym5 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # | |
type Apply [e6989586621679727908] (TyFun [f6989586621679727909] [g6989586621679727910] -> Type) (ZipWith6Sym5 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910 l1 l2 l3 l4 l5) l6 # | |
data ZipWith6Sym6 (l :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727904]) (l :: [b6989586621679727905]) (l :: [c6989586621679727906]) (l :: [d6989586621679727907]) (l :: [e6989586621679727908]) (l :: TyFun [f6989586621679727909] [g6989586621679727910]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727904] -> [b6989586621679727905] -> [c6989586621679727906] -> [d6989586621679727907] -> [e6989586621679727908] -> TyFun [f6989586621679727909] [g6989586621679727910] -> *) (ZipWith6Sym6 a6989586621679727904 b6989586621679727905 c6989586621679727906 d6989586621679727907 e6989586621679727908 f6989586621679727909 g6989586621679727910) # | |
type Apply [f] [g] (ZipWith6Sym6 a b c d e f g l1 l2 l3 l4 l5 l6) l7 # | |
type ZipWith6Sym7 (t :: TyFun a6989586621679727904 (TyFun b6989586621679727905 (TyFun c6989586621679727906 (TyFun d6989586621679727907 (TyFun e6989586621679727908 (TyFun f6989586621679727909 g6989586621679727910 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679727904]) (t :: [b6989586621679727905]) (t :: [c6989586621679727906]) (t :: [d6989586621679727907]) (t :: [e6989586621679727908]) (t :: [f6989586621679727909]) = ZipWith6 t t t t t t t #
data ZipWith7Sym0 (l :: TyFun (TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727896] (TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727896] (TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym0 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # | |
type Apply (TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679727896] (TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym0 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) l # | |
data ZipWith7Sym1 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679727896] (TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679727896] (TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym1 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # | |
type Apply [a6989586621679727896] (TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym1 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903 l1) l2 # | |
data ZipWith7Sym2 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727896]) (l :: TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727896] -> TyFun [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym2 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # | |
type Apply [b6989586621679727897] (TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym2 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903 l1 l2) l3 # | |
data ZipWith7Sym3 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727896]) (l :: [b6989586621679727897]) (l :: TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727896] -> [b6989586621679727897] -> TyFun [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym3 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # | |
type Apply [c6989586621679727898] (TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym3 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903 l1 l2 l3) l4 # | |
data ZipWith7Sym4 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727896]) (l :: [b6989586621679727897]) (l :: [c6989586621679727898]) (l :: TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727896] -> [b6989586621679727897] -> [c6989586621679727898] -> TyFun [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) -> *) (ZipWith7Sym4 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # | |
type Apply [d6989586621679727899] (TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> Type) (ZipWith7Sym4 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903 l1 l2 l3 l4) l5 # | |
data ZipWith7Sym5 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727896]) (l :: [b6989586621679727897]) (l :: [c6989586621679727898]) (l :: [d6989586621679727899]) (l :: TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727896] -> [b6989586621679727897] -> [c6989586621679727898] -> [d6989586621679727899] -> TyFun [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) -> *) (ZipWith7Sym5 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # | |
type Apply [e6989586621679727900] (TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> Type) (ZipWith7Sym5 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903 l1 l2 l3 l4 l5) l6 # | |
data ZipWith7Sym6 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727896]) (l :: [b6989586621679727897]) (l :: [c6989586621679727898]) (l :: [d6989586621679727899]) (l :: [e6989586621679727900]) (l :: TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727896] -> [b6989586621679727897] -> [c6989586621679727898] -> [d6989586621679727899] -> [e6989586621679727900] -> TyFun [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) -> *) (ZipWith7Sym6 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # | |
type Apply [f6989586621679727901] (TyFun [g6989586621679727902] [h6989586621679727903] -> Type) (ZipWith7Sym6 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903 l1 l2 l3 l4 l5 l6) l7 # | |
data ZipWith7Sym7 (l :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679727896]) (l :: [b6989586621679727897]) (l :: [c6989586621679727898]) (l :: [d6989586621679727899]) (l :: [e6989586621679727900]) (l :: [f6989586621679727901]) (l :: TyFun [g6989586621679727902] [h6989586621679727903]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679727896] -> [b6989586621679727897] -> [c6989586621679727898] -> [d6989586621679727899] -> [e6989586621679727900] -> [f6989586621679727901] -> TyFun [g6989586621679727902] [h6989586621679727903] -> *) (ZipWith7Sym7 a6989586621679727896 b6989586621679727897 c6989586621679727898 d6989586621679727899 e6989586621679727900 f6989586621679727901 g6989586621679727902 h6989586621679727903) # | |
type Apply [g] [h] (ZipWith7Sym7 a b c d e f g h l1 l2 l3 l4 l5 l6 l7) l8 # | |
type ZipWith7Sym8 (t :: TyFun a6989586621679727896 (TyFun b6989586621679727897 (TyFun c6989586621679727898 (TyFun d6989586621679727899 (TyFun e6989586621679727900 (TyFun f6989586621679727901 (TyFun g6989586621679727902 h6989586621679727903 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679727896]) (t :: [b6989586621679727897]) (t :: [c6989586621679727898]) (t :: [d6989586621679727899]) (t :: [e6989586621679727900]) (t :: [f6989586621679727901]) (t :: [g6989586621679727902]) = ZipWith7 t t t t t t t t #
data NubBySym0 (l :: TyFun (TyFun a6989586621679389226 (TyFun a6989586621679389226 Bool -> Type) -> Type) (TyFun [a6989586621679389226] [a6989586621679389226] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389226 (TyFun a6989586621679389226 Bool -> Type) -> Type) (TyFun [a6989586621679389226] [a6989586621679389226] -> Type) -> *) (NubBySym0 a6989586621679389226) # | |
type Apply (TyFun a6989586621679389226 (TyFun a6989586621679389226 Bool -> Type) -> Type) (TyFun [a6989586621679389226] [a6989586621679389226] -> Type) (NubBySym0 a6989586621679389226) l # | |
data NubBySym1 (l :: TyFun a6989586621679389226 (TyFun a6989586621679389226 Bool -> Type) -> Type) (l :: TyFun [a6989586621679389226] [a6989586621679389226]) #
type NubBySym2 (t :: TyFun a6989586621679389226 (TyFun a6989586621679389226 Bool -> Type) -> Type) (t :: [a6989586621679389226]) = NubBy t t #
data UnionSym0 (l :: TyFun [a6989586621679389223] (TyFun [a6989586621679389223] [a6989586621679389223] -> Type)) #
data UnionSym1 (l :: [a6989586621679389223]) (l :: TyFun [a6989586621679389223] [a6989586621679389223]) #
data UnionBySym0 (l :: TyFun (TyFun a6989586621679389224 (TyFun a6989586621679389224 Bool -> Type) -> Type) (TyFun [a6989586621679389224] (TyFun [a6989586621679389224] [a6989586621679389224] -> Type) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679389224 (TyFun a6989586621679389224 Bool -> Type) -> Type) (TyFun [a6989586621679389224] (TyFun [a6989586621679389224] [a6989586621679389224] -> Type) -> Type) -> *) (UnionBySym0 a6989586621679389224) # | |
type Apply (TyFun a6989586621679389224 (TyFun a6989586621679389224 Bool -> Type) -> Type) (TyFun [a6989586621679389224] (TyFun [a6989586621679389224] [a6989586621679389224] -> Type) -> Type) (UnionBySym0 a6989586621679389224) l # | |
data UnionBySym1 (l :: TyFun a6989586621679389224 (TyFun a6989586621679389224 Bool -> Type) -> Type) (l :: TyFun [a6989586621679389224] (TyFun [a6989586621679389224] [a6989586621679389224] -> Type)) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389224 (TyFun a6989586621679389224 Bool -> Type) -> Type) -> TyFun [a6989586621679389224] (TyFun [a6989586621679389224] [a6989586621679389224] -> Type) -> *) (UnionBySym1 a6989586621679389224) # | |
type Apply [a6989586621679389224] (TyFun [a6989586621679389224] [a6989586621679389224] -> Type) (UnionBySym1 a6989586621679389224 l1) l2 # | |
data UnionBySym2 (l :: TyFun a6989586621679389224 (TyFun a6989586621679389224 Bool -> Type) -> Type) (l :: [a6989586621679389224]) (l :: TyFun [a6989586621679389224] [a6989586621679389224]) #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679389224 (TyFun a6989586621679389224 Bool -> Type) -> Type) -> [a6989586621679389224] -> TyFun [a6989586621679389224] [a6989586621679389224] -> *) (UnionBySym2 a6989586621679389224) # | |
type Apply [a] [a] (UnionBySym2 a l1 l2) l3 # | |
type UnionBySym3 (t :: TyFun a6989586621679389224 (TyFun a6989586621679389224 Bool -> Type) -> Type) (t :: [a6989586621679389224]) (t :: [a6989586621679389224]) = UnionBy t t t #
data GenericLengthSym0 (l :: TyFun [a6989586621679389222] i6989586621679389221) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679389222] i6989586621679389221 -> *) (GenericLengthSym0 a6989586621679389222 i6989586621679389221) # | |
type Apply [a] k2 (GenericLengthSym0 a k2) l # | |
type GenericLengthSym1 (t :: [a6989586621679389222]) = GenericLength t #
data GenericTakeSym0 (l :: TyFun i6989586621679727894 (TyFun [a6989586621679727895] [a6989586621679727895] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun i6989586621679727894 (TyFun [a6989586621679727895] [a6989586621679727895] -> Type) -> *) (GenericTakeSym0 i6989586621679727894 a6989586621679727895) # | |
type Apply i6989586621679727894 (TyFun [a6989586621679727895] [a6989586621679727895] -> Type) (GenericTakeSym0 i6989586621679727894 a6989586621679727895) l # | |
data GenericTakeSym1 (l :: i6989586621679727894) (l :: TyFun [a6989586621679727895] [a6989586621679727895]) #
Instances
SuppressUnusedWarnings (i6989586621679727894 -> TyFun [a6989586621679727895] [a6989586621679727895] -> *) (GenericTakeSym1 i6989586621679727894 a6989586621679727895) # | |
type Apply [a] [a] (GenericTakeSym1 i a l1) l2 # | |
type GenericTakeSym2 (t :: i6989586621679727894) (t :: [a6989586621679727895]) = GenericTake t t #
data GenericDropSym0 (l :: TyFun i6989586621679727892 (TyFun [a6989586621679727893] [a6989586621679727893] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun i6989586621679727892 (TyFun [a6989586621679727893] [a6989586621679727893] -> Type) -> *) (GenericDropSym0 i6989586621679727892 a6989586621679727893) # | |
type Apply i6989586621679727892 (TyFun [a6989586621679727893] [a6989586621679727893] -> Type) (GenericDropSym0 i6989586621679727892 a6989586621679727893) l # | |
data GenericDropSym1 (l :: i6989586621679727892) (l :: TyFun [a6989586621679727893] [a6989586621679727893]) #
Instances
SuppressUnusedWarnings (i6989586621679727892 -> TyFun [a6989586621679727893] [a6989586621679727893] -> *) (GenericDropSym1 i6989586621679727892 a6989586621679727893) # | |
type Apply [a] [a] (GenericDropSym1 i a l1) l2 # | |
type GenericDropSym2 (t :: i6989586621679727892) (t :: [a6989586621679727893]) = GenericDrop t t #
data GenericSplitAtSym0 (l :: TyFun i6989586621679727890 (TyFun [a6989586621679727891] ([a6989586621679727891], [a6989586621679727891]) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun i6989586621679727890 (TyFun [a6989586621679727891] ([a6989586621679727891], [a6989586621679727891]) -> Type) -> *) (GenericSplitAtSym0 i6989586621679727890 a6989586621679727891) # | |
type Apply i6989586621679727890 (TyFun [a6989586621679727891] ([a6989586621679727891], [a6989586621679727891]) -> Type) (GenericSplitAtSym0 i6989586621679727890 a6989586621679727891) l # | |
data GenericSplitAtSym1 (l :: i6989586621679727890) (l :: TyFun [a6989586621679727891] ([a6989586621679727891], [a6989586621679727891])) #
Instances
SuppressUnusedWarnings (i6989586621679727890 -> TyFun [a6989586621679727891] ([a6989586621679727891], [a6989586621679727891]) -> *) (GenericSplitAtSym1 i6989586621679727890 a6989586621679727891) # | |
type Apply [a] ([a], [a]) (GenericSplitAtSym1 i a l1) l2 # | |
type GenericSplitAtSym2 (t :: i6989586621679727890) (t :: [a6989586621679727891]) = GenericSplitAt t t #
data GenericIndexSym0 (l :: TyFun [a6989586621679727889] (TyFun i6989586621679727888 a6989586621679727889 -> Type)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679727889] (TyFun i6989586621679727888 a6989586621679727889 -> Type) -> *) (GenericIndexSym0 i6989586621679727888 a6989586621679727889) # | |
type Apply [a6989586621679727889] (TyFun i6989586621679727888 a6989586621679727889 -> Type) (GenericIndexSym0 i6989586621679727888 a6989586621679727889) l # | |
data GenericIndexSym1 (l :: [a6989586621679727889]) (l :: TyFun i6989586621679727888 a6989586621679727889) #
Instances
SuppressUnusedWarnings ([a6989586621679727889] -> TyFun i6989586621679727888 a6989586621679727889 -> *) (GenericIndexSym1 i6989586621679727888 a6989586621679727889) # | |
type Apply i a (GenericIndexSym1 i a l1) l2 # | |
type GenericIndexSym2 (t :: [a6989586621679727889]) (t :: i6989586621679727888) = GenericIndex t t #
data GenericReplicateSym0 (l :: TyFun i6989586621679727886 (TyFun a6989586621679727887 [a6989586621679727887] -> Type)) #
Instances
SuppressUnusedWarnings (TyFun i6989586621679727886 (TyFun a6989586621679727887 [a6989586621679727887] -> Type) -> *) (GenericReplicateSym0 i6989586621679727886 a6989586621679727887) # | |
type Apply i6989586621679727886 (TyFun a6989586621679727887 [a6989586621679727887] -> Type) (GenericReplicateSym0 i6989586621679727886 a6989586621679727887) l # | |
data GenericReplicateSym1 (l :: i6989586621679727886) (l :: TyFun a6989586621679727887 [a6989586621679727887]) #
Instances
SuppressUnusedWarnings (i6989586621679727886 -> TyFun a6989586621679727887 [a6989586621679727887] -> *) (GenericReplicateSym1 i6989586621679727886 a6989586621679727887) # | |
type Apply a [a] (GenericReplicateSym1 i a l1) l2 # | |
type GenericReplicateSym2 (t :: i6989586621679727886) (t :: a6989586621679727887) = GenericReplicate t t #