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 |
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 :: [a6989586621679281045]) (t :: [a6989586621679281045]) = (:++) t t
- data (l :: [a6989586621679281045]) :++$$ (l :: TyFun [a6989586621679281045] [a6989586621679281045])
- data (:++$) (l :: TyFun [a6989586621679281045] (TyFun [a6989586621679281045] [a6989586621679281045] -> Type))
- data HeadSym0 (l :: TyFun [a6989586621679458196] a6989586621679458196)
- type HeadSym1 (t :: [a6989586621679458196]) = Head t
- data LastSym0 (l :: TyFun [a6989586621679458195] a6989586621679458195)
- type LastSym1 (t :: [a6989586621679458195]) = Last t
- data TailSym0 (l :: TyFun [a6989586621679458194] [a6989586621679458194])
- type TailSym1 (t :: [a6989586621679458194]) = Tail t
- data InitSym0 (l :: TyFun [a6989586621679458193] [a6989586621679458193])
- type InitSym1 (t :: [a6989586621679458193]) = Init t
- data NullSym0 (l :: TyFun [a6989586621679458192] Bool)
- type NullSym1 (t :: [a6989586621679458192]) = Null t
- data MapSym0 (l :: TyFun (TyFun a6989586621679281046 b6989586621679281047 -> Type) (TyFun [a6989586621679281046] [b6989586621679281047] -> Type))
- data MapSym1 (l :: TyFun a6989586621679281046 b6989586621679281047 -> Type) (l :: TyFun [a6989586621679281046] [b6989586621679281047])
- type MapSym2 (t :: TyFun a6989586621679281046 b6989586621679281047 -> Type) (t :: [a6989586621679281046]) = Map t t
- data ReverseSym0 (l :: TyFun [a6989586621679458191] [a6989586621679458191])
- type ReverseSym1 (t :: [a6989586621679458191]) = Reverse t
- data IntersperseSym0 (l :: TyFun a6989586621679458190 (TyFun [a6989586621679458190] [a6989586621679458190] -> Type))
- data IntersperseSym1 (l :: a6989586621679458190) (l :: TyFun [a6989586621679458190] [a6989586621679458190])
- type IntersperseSym2 (t :: a6989586621679458190) (t :: [a6989586621679458190]) = Intersperse t t
- data IntercalateSym0 (l :: TyFun [a6989586621679458189] (TyFun [[a6989586621679458189]] [a6989586621679458189] -> Type))
- data IntercalateSym1 (l :: [a6989586621679458189]) (l :: TyFun [[a6989586621679458189]] [a6989586621679458189])
- type IntercalateSym2 (t :: [a6989586621679458189]) (t :: [[a6989586621679458189]]) = Intercalate t t
- data SubsequencesSym0 (l :: TyFun [a6989586621679458188] [[a6989586621679458188]])
- type SubsequencesSym1 (t :: [a6989586621679458188]) = Subsequences t
- data PermutationsSym0 (l :: TyFun [a6989586621679458185] [[a6989586621679458185]])
- type PermutationsSym1 (t :: [a6989586621679458185]) = Permutations t
- data FoldlSym0 (l :: TyFun (TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type) -> Type))
- data FoldlSym1 (l :: TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (l :: TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type))
- data FoldlSym2 (l :: TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (l :: b6989586621679242246) (l :: TyFun [a6989586621679242245] b6989586621679242246)
- type FoldlSym3 (t :: TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (t :: b6989586621679242246) (t :: [a6989586621679242245]) = Foldl t t t
- data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (TyFun b6989586621679458184 (TyFun [a6989586621679458183] b6989586621679458184 -> Type) -> Type))
- data Foldl'Sym1 (l :: TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (l :: TyFun b6989586621679458184 (TyFun [a6989586621679458183] b6989586621679458184 -> Type))
- data Foldl'Sym2 (l :: TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (l :: b6989586621679458184) (l :: TyFun [a6989586621679458183] b6989586621679458184)
- type Foldl'Sym3 (t :: TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (t :: b6989586621679458184) (t :: [a6989586621679458183]) = Foldl' t t t
- data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679458182 (TyFun a6989586621679458182 a6989586621679458182 -> Type) -> Type) (TyFun [a6989586621679458182] a6989586621679458182 -> Type))
- data Foldl1Sym1 (l :: TyFun a6989586621679458182 (TyFun a6989586621679458182 a6989586621679458182 -> Type) -> Type) (l :: TyFun [a6989586621679458182] a6989586621679458182)
- type Foldl1Sym2 (t :: TyFun a6989586621679458182 (TyFun a6989586621679458182 a6989586621679458182 -> Type) -> Type) (t :: [a6989586621679458182]) = Foldl1 t t
- data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679458181 (TyFun a6989586621679458181 a6989586621679458181 -> Type) -> Type) (TyFun [a6989586621679458181] a6989586621679458181 -> Type))
- data Foldl1'Sym1 (l :: TyFun a6989586621679458181 (TyFun a6989586621679458181 a6989586621679458181 -> Type) -> Type) (l :: TyFun [a6989586621679458181] a6989586621679458181)
- type Foldl1'Sym2 (t :: TyFun a6989586621679458181 (TyFun a6989586621679458181 a6989586621679458181 -> Type) -> Type) (t :: [a6989586621679458181]) = Foldl1' t t
- data FoldrSym0 (l :: TyFun (TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type) -> Type))
- data FoldrSym1 (l :: TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (l :: TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type))
- data FoldrSym2 (l :: TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (l :: b6989586621679281049) (l :: TyFun [a6989586621679281048] b6989586621679281049)
- type FoldrSym3 (t :: TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (t :: b6989586621679281049) (t :: [a6989586621679281048]) = Foldr t t t
- data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679458180 (TyFun a6989586621679458180 a6989586621679458180 -> Type) -> Type) (TyFun [a6989586621679458180] a6989586621679458180 -> Type))
- data Foldr1Sym1 (l :: TyFun a6989586621679458180 (TyFun a6989586621679458180 a6989586621679458180 -> Type) -> Type) (l :: TyFun [a6989586621679458180] a6989586621679458180)
- type Foldr1Sym2 (t :: TyFun a6989586621679458180 (TyFun a6989586621679458180 a6989586621679458180 -> Type) -> Type) (t :: [a6989586621679458180]) = Foldr1 t t
- data ConcatSym0 (l :: TyFun [[a6989586621679458179]] [a6989586621679458179])
- type ConcatSym1 (t :: [[a6989586621679458179]]) = Concat t
- data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679458177 [b6989586621679458178] -> Type) (TyFun [a6989586621679458177] [b6989586621679458178] -> Type))
- data ConcatMapSym1 (l :: TyFun a6989586621679458177 [b6989586621679458178] -> Type) (l :: TyFun [a6989586621679458177] [b6989586621679458178])
- type ConcatMapSym2 (t :: TyFun a6989586621679458177 [b6989586621679458178] -> Type) (t :: [a6989586621679458177]) = 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 a6989586621679447960 Bool -> Type) (TyFun [a6989586621679447960] Bool -> Type))
- data Any_Sym1 (l :: TyFun a6989586621679447960 Bool -> Type) (l :: TyFun [a6989586621679447960] Bool)
- type Any_Sym2 (t :: TyFun a6989586621679447960 Bool -> Type) (t :: [a6989586621679447960]) = Any_ t t
- data AllSym0 (l :: TyFun (TyFun a6989586621679458176 Bool -> Type) (TyFun [a6989586621679458176] Bool -> Type))
- data AllSym1 (l :: TyFun a6989586621679458176 Bool -> Type) (l :: TyFun [a6989586621679458176] Bool)
- type AllSym2 (t :: TyFun a6989586621679458176 Bool -> Type) (t :: [a6989586621679458176]) = All t t
- data ScanlSym0 (l :: TyFun (TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type) -> Type))
- data ScanlSym1 (l :: TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (l :: TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type))
- data ScanlSym2 (l :: TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (l :: b6989586621679458174) (l :: TyFun [a6989586621679458175] [b6989586621679458174])
- type ScanlSym3 (t :: TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (t :: b6989586621679458174) (t :: [a6989586621679458175]) = Scanl t t t
- data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679458173 (TyFun a6989586621679458173 a6989586621679458173 -> Type) -> Type) (TyFun [a6989586621679458173] [a6989586621679458173] -> Type))
- data Scanl1Sym1 (l :: TyFun a6989586621679458173 (TyFun a6989586621679458173 a6989586621679458173 -> Type) -> Type) (l :: TyFun [a6989586621679458173] [a6989586621679458173])
- type Scanl1Sym2 (t :: TyFun a6989586621679458173 (TyFun a6989586621679458173 a6989586621679458173 -> Type) -> Type) (t :: [a6989586621679458173]) = Scanl1 t t
- data ScanrSym0 (l :: TyFun (TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type) -> Type))
- data ScanrSym1 (l :: TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (l :: TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type))
- data ScanrSym2 (l :: TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (l :: b6989586621679458172) (l :: TyFun [a6989586621679458171] [b6989586621679458172])
- type ScanrSym3 (t :: TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (t :: b6989586621679458172) (t :: [a6989586621679458171]) = Scanr t t t
- data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679458170 (TyFun a6989586621679458170 a6989586621679458170 -> Type) -> Type) (TyFun [a6989586621679458170] [a6989586621679458170] -> Type))
- data Scanr1Sym1 (l :: TyFun a6989586621679458170 (TyFun a6989586621679458170 a6989586621679458170 -> Type) -> Type) (l :: TyFun [a6989586621679458170] [a6989586621679458170])
- type Scanr1Sym2 (t :: TyFun a6989586621679458170 (TyFun a6989586621679458170 a6989586621679458170 -> Type) -> Type) (t :: [a6989586621679458170]) = Scanr1 t t
- data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) -> Type))
- data MapAccumLSym1 (l :: TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (l :: TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type))
- data MapAccumLSym2 (l :: TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (l :: acc6989586621679458167) (l :: TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]))
- type MapAccumLSym3 (t :: TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (t :: acc6989586621679458167) (t :: [x6989586621679458168]) = MapAccumL t t t
- data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) -> Type))
- data MapAccumRSym1 (l :: TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (l :: TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type))
- data MapAccumRSym2 (l :: TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (l :: acc6989586621679458164) (l :: TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]))
- type MapAccumRSym3 (t :: TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (t :: acc6989586621679458164) (t :: [x6989586621679458165]) = MapAccumR t t t
- data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) (TyFun b6989586621679458162 [a6989586621679458163] -> Type))
- data UnfoldrSym1 (l :: TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) (l :: TyFun b6989586621679458162 [a6989586621679458163])
- type UnfoldrSym2 (t :: TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) (t :: b6989586621679458162) = Unfoldr t t
- data InitsSym0 (l :: TyFun [a6989586621679458161] [[a6989586621679458161]])
- type InitsSym1 (t :: [a6989586621679458161]) = Inits t
- data TailsSym0 (l :: TyFun [a6989586621679458160] [[a6989586621679458160]])
- type TailsSym1 (t :: [a6989586621679458160]) = Tails t
- data IsPrefixOfSym0 (l :: TyFun [a6989586621679458159] (TyFun [a6989586621679458159] Bool -> Type))
- data IsPrefixOfSym1 (l :: [a6989586621679458159]) (l :: TyFun [a6989586621679458159] Bool)
- type IsPrefixOfSym2 (t :: [a6989586621679458159]) (t :: [a6989586621679458159]) = IsPrefixOf t t
- data IsSuffixOfSym0 (l :: TyFun [a6989586621679458158] (TyFun [a6989586621679458158] Bool -> Type))
- data IsSuffixOfSym1 (l :: [a6989586621679458158]) (l :: TyFun [a6989586621679458158] Bool)
- type IsSuffixOfSym2 (t :: [a6989586621679458158]) (t :: [a6989586621679458158]) = IsSuffixOf t t
- data IsInfixOfSym0 (l :: TyFun [a6989586621679458157] (TyFun [a6989586621679458157] Bool -> Type))
- data IsInfixOfSym1 (l :: [a6989586621679458157]) (l :: TyFun [a6989586621679458157] Bool)
- type IsInfixOfSym2 (t :: [a6989586621679458157]) (t :: [a6989586621679458157]) = IsInfixOf t t
- data ElemSym0 (l :: TyFun a6989586621679458156 (TyFun [a6989586621679458156] Bool -> Type))
- data ElemSym1 (l :: a6989586621679458156) (l :: TyFun [a6989586621679458156] Bool)
- type ElemSym2 (t :: a6989586621679458156) (t :: [a6989586621679458156]) = Elem t t
- data NotElemSym0 (l :: TyFun a6989586621679458155 (TyFun [a6989586621679458155] Bool -> Type))
- data NotElemSym1 (l :: a6989586621679458155) (l :: TyFun [a6989586621679458155] Bool)
- type NotElemSym2 (t :: a6989586621679458155) (t :: [a6989586621679458155]) = NotElem t t
- data ZipSym0 (l :: TyFun [a6989586621679458153] (TyFun [b6989586621679458154] [(a6989586621679458153, b6989586621679458154)] -> Type))
- data ZipSym1 (l :: [a6989586621679458153]) (l :: TyFun [b6989586621679458154] [(a6989586621679458153, b6989586621679458154)])
- type ZipSym2 (t :: [a6989586621679458153]) (t :: [b6989586621679458154]) = Zip t t
- data Zip3Sym0 (l :: TyFun [a6989586621679458150] (TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) -> Type))
- data Zip3Sym1 (l :: [a6989586621679458150]) (l :: TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type))
- data Zip3Sym2 (l :: [a6989586621679458150]) (l :: [b6989586621679458151]) (l :: TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)])
- type Zip3Sym3 (t :: [a6989586621679458150]) (t :: [b6989586621679458151]) (t :: [c6989586621679458152]) = Zip3 t t t
- data ZipWithSym0 (l :: TyFun (TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) -> Type))
- data ZipWithSym1 (l :: TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (l :: TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type))
- data ZipWithSym2 (l :: TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (l :: [a6989586621679458147]) (l :: TyFun [b6989586621679458148] [c6989586621679458149])
- type ZipWithSym3 (t :: TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (t :: [a6989586621679458147]) (t :: [b6989586621679458148]) = ZipWith t t t
- data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) -> Type))
- data ZipWith3Sym1 (l :: TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type))
- data ZipWith3Sym2 (l :: TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (l :: [a6989586621679458143]) (l :: TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type))
- data ZipWith3Sym3 (l :: TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (l :: [a6989586621679458143]) (l :: [b6989586621679458144]) (l :: TyFun [c6989586621679458145] [d6989586621679458146])
- type ZipWith3Sym4 (t :: TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (t :: [a6989586621679458143]) (t :: [b6989586621679458144]) (t :: [c6989586621679458145]) = ZipWith3 t t t t
- data UnzipSym0 (l :: TyFun [(a6989586621679458141, b6989586621679458142)] ([a6989586621679458141], [b6989586621679458142]))
- type UnzipSym1 (t :: [(a6989586621679458141, b6989586621679458142)]) = Unzip t
- data Unzip3Sym0 (l :: TyFun [(a6989586621679458138, b6989586621679458139, c6989586621679458140)] ([a6989586621679458138], [b6989586621679458139], [c6989586621679458140]))
- type Unzip3Sym1 (t :: [(a6989586621679458138, b6989586621679458139, c6989586621679458140)]) = Unzip3 t
- data Unzip4Sym0 (l :: TyFun [(a6989586621679458134, b6989586621679458135, c6989586621679458136, d6989586621679458137)] ([a6989586621679458134], [b6989586621679458135], [c6989586621679458136], [d6989586621679458137]))
- type Unzip4Sym1 (t :: [(a6989586621679458134, b6989586621679458135, c6989586621679458136, d6989586621679458137)]) = Unzip4 t
- data Unzip5Sym0 (l :: TyFun [(a6989586621679458129, b6989586621679458130, c6989586621679458131, d6989586621679458132, e6989586621679458133)] ([a6989586621679458129], [b6989586621679458130], [c6989586621679458131], [d6989586621679458132], [e6989586621679458133]))
- type Unzip5Sym1 (t :: [(a6989586621679458129, b6989586621679458130, c6989586621679458131, d6989586621679458132, e6989586621679458133)]) = Unzip5 t
- data Unzip6Sym0 (l :: TyFun [(a6989586621679458123, b6989586621679458124, c6989586621679458125, d6989586621679458126, e6989586621679458127, f6989586621679458128)] ([a6989586621679458123], [b6989586621679458124], [c6989586621679458125], [d6989586621679458126], [e6989586621679458127], [f6989586621679458128]))
- type Unzip6Sym1 (t :: [(a6989586621679458123, b6989586621679458124, c6989586621679458125, d6989586621679458126, e6989586621679458127, f6989586621679458128)]) = Unzip6 t
- data Unzip7Sym0 (l :: TyFun [(a6989586621679458116, b6989586621679458117, c6989586621679458118, d6989586621679458119, e6989586621679458120, f6989586621679458121, g6989586621679458122)] ([a6989586621679458116], [b6989586621679458117], [c6989586621679458118], [d6989586621679458119], [e6989586621679458120], [f6989586621679458121], [g6989586621679458122]))
- type Unzip7Sym1 (t :: [(a6989586621679458116, b6989586621679458117, c6989586621679458118, d6989586621679458119, e6989586621679458120, f6989586621679458121, g6989586621679458122)]) = Unzip7 t
- data DeleteSym0 (l :: TyFun a6989586621679458115 (TyFun [a6989586621679458115] [a6989586621679458115] -> Type))
- data DeleteSym1 (l :: a6989586621679458115) (l :: TyFun [a6989586621679458115] [a6989586621679458115])
- type DeleteSym2 (t :: a6989586621679458115) (t :: [a6989586621679458115]) = Delete t t
- data (:\\$) (l :: TyFun [a6989586621679458114] (TyFun [a6989586621679458114] [a6989586621679458114] -> Type))
- data (l :: [a6989586621679458114]) :\\$$ (l :: TyFun [a6989586621679458114] [a6989586621679458114])
- type (:\\$$$) (t :: [a6989586621679458114]) (t :: [a6989586621679458114]) = (:\\) t t
- data IntersectSym0 (l :: TyFun [a6989586621679458101] (TyFun [a6989586621679458101] [a6989586621679458101] -> Type))
- data IntersectSym1 (l :: [a6989586621679458101]) (l :: TyFun [a6989586621679458101] [a6989586621679458101])
- type IntersectSym2 (t :: [a6989586621679458101]) (t :: [a6989586621679458101]) = Intersect t t
- data InsertSym0 (l :: TyFun a6989586621679458088 (TyFun [a6989586621679458088] [a6989586621679458088] -> Type))
- data InsertSym1 (l :: a6989586621679458088) (l :: TyFun [a6989586621679458088] [a6989586621679458088])
- type InsertSym2 (t :: a6989586621679458088) (t :: [a6989586621679458088]) = Insert t t
- data SortSym0 (l :: TyFun [a6989586621679458087] [a6989586621679458087])
- type SortSym1 (t :: [a6989586621679458087]) = Sort t
- data DeleteBySym0 (l :: TyFun (TyFun a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) (TyFun a6989586621679458113 (TyFun [a6989586621679458113] [a6989586621679458113] -> Type) -> Type))
- data DeleteBySym1 (l :: TyFun a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) (l :: TyFun a6989586621679458113 (TyFun [a6989586621679458113] [a6989586621679458113] -> Type))
- data DeleteBySym2 (l :: TyFun a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) (l :: a6989586621679458113) (l :: TyFun [a6989586621679458113] [a6989586621679458113])
- type DeleteBySym3 (t :: TyFun a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) (t :: a6989586621679458113) (t :: [a6989586621679458113]) = DeleteBy t t t
- data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) (TyFun [a6989586621679458112] (TyFun [a6989586621679458112] [a6989586621679458112] -> Type) -> Type))
- data DeleteFirstsBySym1 (l :: TyFun a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458112] (TyFun [a6989586621679458112] [a6989586621679458112] -> Type))
- data DeleteFirstsBySym2 (l :: TyFun a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) (l :: [a6989586621679458112]) (l :: TyFun [a6989586621679458112] [a6989586621679458112])
- type DeleteFirstsBySym3 (t :: TyFun a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) (t :: [a6989586621679458112]) (t :: [a6989586621679458112]) = DeleteFirstsBy t t t
- data IntersectBySym0 (l :: TyFun (TyFun a6989586621679458100 (TyFun a6989586621679458100 Bool -> Type) -> Type) (TyFun [a6989586621679458100] (TyFun [a6989586621679458100] [a6989586621679458100] -> Type) -> Type))
- data IntersectBySym1 (l :: TyFun a6989586621679458100 (TyFun a6989586621679458100 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458100] (TyFun [a6989586621679458100] [a6989586621679458100] -> Type))
- data IntersectBySym2 (l :: TyFun a6989586621679458100 (TyFun a6989586621679458100 Bool -> Type) -> Type) (l :: [a6989586621679458100]) (l :: TyFun [a6989586621679458100] [a6989586621679458100])
- data SortBySym0 (l :: TyFun (TyFun a6989586621679458111 (TyFun a6989586621679458111 Ordering -> Type) -> Type) (TyFun [a6989586621679458111] [a6989586621679458111] -> Type))
- data SortBySym1 (l :: TyFun a6989586621679458111 (TyFun a6989586621679458111 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679458111] [a6989586621679458111])
- type SortBySym2 (t :: TyFun a6989586621679458111 (TyFun a6989586621679458111 Ordering -> Type) -> Type) (t :: [a6989586621679458111]) = SortBy t t
- data InsertBySym0 (l :: TyFun (TyFun a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) (TyFun a6989586621679458110 (TyFun [a6989586621679458110] [a6989586621679458110] -> Type) -> Type))
- data InsertBySym1 (l :: TyFun a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) (l :: TyFun a6989586621679458110 (TyFun [a6989586621679458110] [a6989586621679458110] -> Type))
- data InsertBySym2 (l :: TyFun a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) (l :: a6989586621679458110) (l :: TyFun [a6989586621679458110] [a6989586621679458110])
- type InsertBySym3 (t :: TyFun a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) (t :: a6989586621679458110) (t :: [a6989586621679458110]) = InsertBy t t t
- data MaximumBySym0 (l :: TyFun (TyFun a6989586621679458109 (TyFun a6989586621679458109 Ordering -> Type) -> Type) (TyFun [a6989586621679458109] a6989586621679458109 -> Type))
- data MaximumBySym1 (l :: TyFun a6989586621679458109 (TyFun a6989586621679458109 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679458109] a6989586621679458109)
- type MaximumBySym2 (t :: TyFun a6989586621679458109 (TyFun a6989586621679458109 Ordering -> Type) -> Type) (t :: [a6989586621679458109]) = MaximumBy t t
- data MinimumBySym0 (l :: TyFun (TyFun a6989586621679458108 (TyFun a6989586621679458108 Ordering -> Type) -> Type) (TyFun [a6989586621679458108] a6989586621679458108 -> Type))
- data MinimumBySym1 (l :: TyFun a6989586621679458108 (TyFun a6989586621679458108 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679458108] a6989586621679458108)
- type MinimumBySym2 (t :: TyFun a6989586621679458108 (TyFun a6989586621679458108 Ordering -> Type) -> Type) (t :: [a6989586621679458108]) = MinimumBy t t
- data LengthSym0 (l :: TyFun [a6989586621679458079] Nat)
- type LengthSym1 (t :: [a6989586621679458079]) = Length t
- data SumSym0 (l :: TyFun [a6989586621679458081] a6989586621679458081)
- type SumSym1 (t :: [a6989586621679458081]) = Sum t
- data ProductSym0 (l :: TyFun [a6989586621679458080] a6989586621679458080)
- type ProductSym1 (t :: [a6989586621679458080]) = Product t
- data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679458078 [a6989586621679458078] -> Type))
- data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679458078 [a6989586621679458078])
- type ReplicateSym2 (t :: Nat) (t :: a6989586621679458078) = Replicate t t
- data TransposeSym0 (l :: TyFun [[a6989586621679458077]] [[a6989586621679458077]])
- type TransposeSym1 (t :: [[a6989586621679458077]]) = Transpose t
- data TakeSym0 (l :: TyFun Nat (TyFun [a6989586621679458094] [a6989586621679458094] -> Type))
- data TakeSym1 (l :: Nat) (l :: TyFun [a6989586621679458094] [a6989586621679458094])
- type TakeSym2 (t :: Nat) (t :: [a6989586621679458094]) = Take t t
- data DropSym0 (l :: TyFun Nat (TyFun [a6989586621679458093] [a6989586621679458093] -> Type))
- data DropSym1 (l :: Nat) (l :: TyFun [a6989586621679458093] [a6989586621679458093])
- type DropSym2 (t :: Nat) (t :: [a6989586621679458093]) = Drop t t
- data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679458092] ([a6989586621679458092], [a6989586621679458092]) -> Type))
- data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679458092] ([a6989586621679458092], [a6989586621679458092]))
- type SplitAtSym2 (t :: Nat) (t :: [a6989586621679458092]) = SplitAt t t
- data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679458099 Bool -> Type) (TyFun [a6989586621679458099] [a6989586621679458099] -> Type))
- data TakeWhileSym1 (l :: TyFun a6989586621679458099 Bool -> Type) (l :: TyFun [a6989586621679458099] [a6989586621679458099])
- type TakeWhileSym2 (t :: TyFun a6989586621679458099 Bool -> Type) (t :: [a6989586621679458099]) = TakeWhile t t
- data DropWhileSym0 (l :: TyFun (TyFun a6989586621679458098 Bool -> Type) (TyFun [a6989586621679458098] [a6989586621679458098] -> Type))
- data DropWhileSym1 (l :: TyFun a6989586621679458098 Bool -> Type) (l :: TyFun [a6989586621679458098] [a6989586621679458098])
- type DropWhileSym2 (t :: TyFun a6989586621679458098 Bool -> Type) (t :: [a6989586621679458098]) = DropWhile t t
- data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679458097 Bool -> Type) (TyFun [a6989586621679458097] [a6989586621679458097] -> Type))
- data DropWhileEndSym1 (l :: TyFun a6989586621679458097 Bool -> Type) (l :: TyFun [a6989586621679458097] [a6989586621679458097])
- type DropWhileEndSym2 (t :: TyFun a6989586621679458097 Bool -> Type) (t :: [a6989586621679458097]) = DropWhileEnd t t
- data SpanSym0 (l :: TyFun (TyFun a6989586621679458096 Bool -> Type) (TyFun [a6989586621679458096] ([a6989586621679458096], [a6989586621679458096]) -> Type))
- data SpanSym1 (l :: TyFun a6989586621679458096 Bool -> Type) (l :: TyFun [a6989586621679458096] ([a6989586621679458096], [a6989586621679458096]))
- type SpanSym2 (t :: TyFun a6989586621679458096 Bool -> Type) (t :: [a6989586621679458096]) = Span t t
- data BreakSym0 (l :: TyFun (TyFun a6989586621679458095 Bool -> Type) (TyFun [a6989586621679458095] ([a6989586621679458095], [a6989586621679458095]) -> Type))
- data BreakSym1 (l :: TyFun a6989586621679458095 Bool -> Type) (l :: TyFun [a6989586621679458095] ([a6989586621679458095], [a6989586621679458095]))
- type BreakSym2 (t :: TyFun a6989586621679458095 Bool -> Type) (t :: [a6989586621679458095]) = Break t t
- data StripPrefixSym0 (l :: TyFun [a6989586621679876709] (TyFun [a6989586621679876709] (Maybe [a6989586621679876709]) -> Type))
- data StripPrefixSym1 (l :: [a6989586621679876709]) (l :: TyFun [a6989586621679876709] (Maybe [a6989586621679876709]))
- type StripPrefixSym2 (t :: [a6989586621679876709]) (t :: [a6989586621679876709]) = StripPrefix t t
- data MaximumSym0 (l :: TyFun [a6989586621679458090] a6989586621679458090)
- type MaximumSym1 (t :: [a6989586621679458090]) = Maximum t
- data MinimumSym0 (l :: TyFun [a6989586621679458089] a6989586621679458089)
- type MinimumSym1 (t :: [a6989586621679458089]) = Minimum t
- data GroupSym0 (l :: TyFun [a6989586621679458091] [[a6989586621679458091]])
- type GroupSym1 (t :: [a6989586621679458091]) = Group t
- data GroupBySym0 (l :: TyFun (TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (TyFun [a6989586621679458086] [[a6989586621679458086]] -> Type))
- data GroupBySym1 (l :: TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458086] [[a6989586621679458086]])
- type GroupBySym2 (t :: TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (t :: [a6989586621679458086]) = GroupBy t t
- data LookupSym0 (l :: TyFun a6989586621679458084 (TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085) -> Type))
- data LookupSym1 (l :: a6989586621679458084) (l :: TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085))
- type LookupSym2 (t :: a6989586621679458084) (t :: [(a6989586621679458084, b6989586621679458085)]) = Lookup t t
- data FindSym0 (l :: TyFun (TyFun a6989586621679458106 Bool -> Type) (TyFun [a6989586621679458106] (Maybe a6989586621679458106) -> Type))
- data FindSym1 (l :: TyFun a6989586621679458106 Bool -> Type) (l :: TyFun [a6989586621679458106] (Maybe a6989586621679458106))
- type FindSym2 (t :: TyFun a6989586621679458106 Bool -> Type) (t :: [a6989586621679458106]) = Find t t
- data FilterSym0 (l :: TyFun (TyFun a6989586621679458107 Bool -> Type) (TyFun [a6989586621679458107] [a6989586621679458107] -> Type))
- data FilterSym1 (l :: TyFun a6989586621679458107 Bool -> Type) (l :: TyFun [a6989586621679458107] [a6989586621679458107])
- type FilterSym2 (t :: TyFun a6989586621679458107 Bool -> Type) (t :: [a6989586621679458107]) = Filter t t
- data PartitionSym0 (l :: TyFun (TyFun a6989586621679458083 Bool -> Type) (TyFun [a6989586621679458083] ([a6989586621679458083], [a6989586621679458083]) -> Type))
- data PartitionSym1 (l :: TyFun a6989586621679458083 Bool -> Type) (l :: TyFun [a6989586621679458083] ([a6989586621679458083], [a6989586621679458083]))
- type PartitionSym2 (t :: TyFun a6989586621679458083 Bool -> Type) (t :: [a6989586621679458083]) = Partition t t
- data (:!!$) (l :: TyFun [a6989586621679458076] (TyFun Nat a6989586621679458076 -> Type))
- data (l :: [a6989586621679458076]) :!!$$ (l :: TyFun Nat a6989586621679458076)
- type (:!!$$$) (t :: [a6989586621679458076]) (t :: Nat) = (:!!) t t
- data ElemIndexSym0 (l :: TyFun a6989586621679458105 (TyFun [a6989586621679458105] (Maybe Nat) -> Type))
- data ElemIndexSym1 (l :: a6989586621679458105) (l :: TyFun [a6989586621679458105] (Maybe Nat))
- type ElemIndexSym2 (t :: a6989586621679458105) (t :: [a6989586621679458105]) = ElemIndex t t
- data ElemIndicesSym0 (l :: TyFun a6989586621679458104 (TyFun [a6989586621679458104] [Nat] -> Type))
- data ElemIndicesSym1 (l :: a6989586621679458104) (l :: TyFun [a6989586621679458104] [Nat])
- type ElemIndicesSym2 (t :: a6989586621679458104) (t :: [a6989586621679458104]) = ElemIndices t t
- data FindIndexSym0 (l :: TyFun (TyFun a6989586621679458103 Bool -> Type) (TyFun [a6989586621679458103] (Maybe Nat) -> Type))
- data FindIndexSym1 (l :: TyFun a6989586621679458103 Bool -> Type) (l :: TyFun [a6989586621679458103] (Maybe Nat))
- type FindIndexSym2 (t :: TyFun a6989586621679458103 Bool -> Type) (t :: [a6989586621679458103]) = FindIndex t t
- data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679458102 Bool -> Type) (TyFun [a6989586621679458102] [Nat] -> Type))
- data FindIndicesSym1 (l :: TyFun a6989586621679458102 Bool -> Type) (l :: TyFun [a6989586621679458102] [Nat])
- type FindIndicesSym2 (t :: TyFun a6989586621679458102 Bool -> Type) (t :: [a6989586621679458102]) = FindIndices t t
- data Zip4Sym0 (l :: TyFun [a6989586621679876705] (TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) -> Type))
- data Zip4Sym1 (l :: [a6989586621679876705]) (l :: TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type))
- data Zip4Sym2 (l :: [a6989586621679876705]) (l :: [b6989586621679876706]) (l :: TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type))
- data Zip4Sym3 (l :: [a6989586621679876705]) (l :: [b6989586621679876706]) (l :: [c6989586621679876707]) (l :: TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)])
- type Zip4Sym4 (t :: [a6989586621679876705]) (t :: [b6989586621679876706]) (t :: [c6989586621679876707]) (t :: [d6989586621679876708]) = Zip4 t t t t
- data Zip5Sym0 (l :: TyFun [a6989586621679876700] (TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) -> Type))
- data Zip5Sym1 (l :: [a6989586621679876700]) (l :: TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type))
- data Zip5Sym2 (l :: [a6989586621679876700]) (l :: [b6989586621679876701]) (l :: TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type))
- data Zip5Sym3 (l :: [a6989586621679876700]) (l :: [b6989586621679876701]) (l :: [c6989586621679876702]) (l :: TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type))
- data Zip5Sym4 (l :: [a6989586621679876700]) (l :: [b6989586621679876701]) (l :: [c6989586621679876702]) (l :: [d6989586621679876703]) (l :: TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)])
- type Zip5Sym5 (t :: [a6989586621679876700]) (t :: [b6989586621679876701]) (t :: [c6989586621679876702]) (t :: [d6989586621679876703]) (t :: [e6989586621679876704]) = Zip5 t t t t t
- data Zip6Sym0 (l :: TyFun [a6989586621679876694] (TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) -> Type))
- data Zip6Sym1 (l :: [a6989586621679876694]) (l :: TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type))
- data Zip6Sym2 (l :: [a6989586621679876694]) (l :: [b6989586621679876695]) (l :: TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type))
- data Zip6Sym3 (l :: [a6989586621679876694]) (l :: [b6989586621679876695]) (l :: [c6989586621679876696]) (l :: TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type))
- data Zip6Sym4 (l :: [a6989586621679876694]) (l :: [b6989586621679876695]) (l :: [c6989586621679876696]) (l :: [d6989586621679876697]) (l :: TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type))
- data Zip6Sym5 (l :: [a6989586621679876694]) (l :: [b6989586621679876695]) (l :: [c6989586621679876696]) (l :: [d6989586621679876697]) (l :: [e6989586621679876698]) (l :: TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)])
- type Zip6Sym6 (t :: [a6989586621679876694]) (t :: [b6989586621679876695]) (t :: [c6989586621679876696]) (t :: [d6989586621679876697]) (t :: [e6989586621679876698]) (t :: [f6989586621679876699]) = Zip6 t t t t t t
- data Zip7Sym0 (l :: TyFun [a6989586621679876687] (TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type))
- data Zip7Sym1 (l :: [a6989586621679876687]) (l :: TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type))
- data Zip7Sym2 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type))
- data Zip7Sym3 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: [c6989586621679876689]) (l :: TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type))
- data Zip7Sym4 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: [c6989586621679876689]) (l :: [d6989586621679876690]) (l :: TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type))
- data Zip7Sym5 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: [c6989586621679876689]) (l :: [d6989586621679876690]) (l :: [e6989586621679876691]) (l :: TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type))
- data Zip7Sym6 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: [c6989586621679876689]) (l :: [d6989586621679876690]) (l :: [e6989586621679876691]) (l :: [f6989586621679876692]) (l :: TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)])
- type Zip7Sym7 (t :: [a6989586621679876687]) (t :: [b6989586621679876688]) (t :: [c6989586621679876689]) (t :: [d6989586621679876690]) (t :: [e6989586621679876691]) (t :: [f6989586621679876692]) (t :: [g6989586621679876693]) = Zip7 t t t t t t t
- data ZipWith4Sym0 (l :: TyFun (TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) -> Type))
- data ZipWith4Sym1 (l :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type))
- data ZipWith4Sym2 (l :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876682]) (l :: TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type))
- data ZipWith4Sym3 (l :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876682]) (l :: [b6989586621679876683]) (l :: TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type))
- data ZipWith4Sym4 (l :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876682]) (l :: [b6989586621679876683]) (l :: [c6989586621679876684]) (l :: TyFun [d6989586621679876685] [e6989586621679876686])
- type ZipWith4Sym5 (t :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679876682]) (t :: [b6989586621679876683]) (t :: [c6989586621679876684]) (t :: [d6989586621679876685]) = ZipWith4 t t t t t
- data ZipWith5Sym0 (l :: TyFun (TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) -> Type))
- data ZipWith5Sym1 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type))
- data ZipWith5Sym2 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876676]) (l :: TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type))
- data ZipWith5Sym3 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876676]) (l :: [b6989586621679876677]) (l :: TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type))
- data ZipWith5Sym4 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876676]) (l :: [b6989586621679876677]) (l :: [c6989586621679876678]) (l :: TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type))
- data ZipWith5Sym5 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876676]) (l :: [b6989586621679876677]) (l :: [c6989586621679876678]) (l :: [d6989586621679876679]) (l :: TyFun [e6989586621679876680] [f6989586621679876681])
- type ZipWith5Sym6 (t :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679876676]) (t :: [b6989586621679876677]) (t :: [c6989586621679876678]) (t :: [d6989586621679876679]) (t :: [e6989586621679876680]) = ZipWith5 t t t t t t
- data ZipWith6Sym0 (l :: TyFun (TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type))
- data ZipWith6Sym1 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type))
- data ZipWith6Sym2 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type))
- data ZipWith6Sym3 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: [b6989586621679876670]) (l :: TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type))
- data ZipWith6Sym4 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: [b6989586621679876670]) (l :: [c6989586621679876671]) (l :: TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type))
- data ZipWith6Sym5 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: [b6989586621679876670]) (l :: [c6989586621679876671]) (l :: [d6989586621679876672]) (l :: TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type))
- data ZipWith6Sym6 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: [b6989586621679876670]) (l :: [c6989586621679876671]) (l :: [d6989586621679876672]) (l :: [e6989586621679876673]) (l :: TyFun [f6989586621679876674] [g6989586621679876675])
- type ZipWith6Sym7 (t :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679876669]) (t :: [b6989586621679876670]) (t :: [c6989586621679876671]) (t :: [d6989586621679876672]) (t :: [e6989586621679876673]) (t :: [f6989586621679876674]) = ZipWith6 t t t t t t t
- data ZipWith7Sym0 (l :: TyFun (TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type))
- data ZipWith7Sym1 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type))
- data ZipWith7Sym2 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type))
- data ZipWith7Sym3 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type))
- data ZipWith7Sym4 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: [c6989586621679876663]) (l :: TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type))
- data ZipWith7Sym5 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: [c6989586621679876663]) (l :: [d6989586621679876664]) (l :: TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type))
- data ZipWith7Sym6 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: [c6989586621679876663]) (l :: [d6989586621679876664]) (l :: [e6989586621679876665]) (l :: TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type))
- data ZipWith7Sym7 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: [c6989586621679876663]) (l :: [d6989586621679876664]) (l :: [e6989586621679876665]) (l :: [f6989586621679876666]) (l :: TyFun [g6989586621679876667] [h6989586621679876668])
- type ZipWith7Sym8 (t :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679876661]) (t :: [b6989586621679876662]) (t :: [c6989586621679876663]) (t :: [d6989586621679876664]) (t :: [e6989586621679876665]) (t :: [f6989586621679876666]) (t :: [g6989586621679876667]) = ZipWith7 t t t t t t t t
- data NubSym0 (l :: TyFun [a6989586621679458075] [a6989586621679458075])
- type NubSym1 (t :: [a6989586621679458075]) = Nub t
- data NubBySym0 (l :: TyFun (TyFun a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (TyFun [a6989586621679458074] [a6989586621679458074] -> Type))
- data NubBySym1 (l :: TyFun a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458074] [a6989586621679458074])
- type NubBySym2 (t :: TyFun a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (t :: [a6989586621679458074]) = NubBy t t
- data UnionSym0 (l :: TyFun [a6989586621679458071] (TyFun [a6989586621679458071] [a6989586621679458071] -> Type))
- data UnionSym1 (l :: [a6989586621679458071]) (l :: TyFun [a6989586621679458071] [a6989586621679458071])
- type UnionSym2 (t :: [a6989586621679458071]) (t :: [a6989586621679458071]) = Union t t
- data UnionBySym0 (l :: TyFun (TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (TyFun [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type) -> Type))
- data UnionBySym1 (l :: TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type))
- data UnionBySym2 (l :: TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (l :: [a6989586621679458072]) (l :: TyFun [a6989586621679458072] [a6989586621679458072])
- type UnionBySym3 (t :: TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (t :: [a6989586621679458072]) (t :: [a6989586621679458072]) = UnionBy t t t
- data GenericLengthSym0 (l :: TyFun [a6989586621679458070] i6989586621679458069)
- type GenericLengthSym1 (t :: [a6989586621679458070]) = GenericLength t
- data GenericTakeSym0 (l :: TyFun i6989586621679876659 (TyFun [a6989586621679876660] [a6989586621679876660] -> Type))
- data GenericTakeSym1 (l :: i6989586621679876659) (l :: TyFun [a6989586621679876660] [a6989586621679876660])
- type GenericTakeSym2 (t :: i6989586621679876659) (t :: [a6989586621679876660]) = GenericTake t t
- data GenericDropSym0 (l :: TyFun i6989586621679876657 (TyFun [a6989586621679876658] [a6989586621679876658] -> Type))
- data GenericDropSym1 (l :: i6989586621679876657) (l :: TyFun [a6989586621679876658] [a6989586621679876658])
- type GenericDropSym2 (t :: i6989586621679876657) (t :: [a6989586621679876658]) = GenericDrop t t
- data GenericSplitAtSym0 (l :: TyFun i6989586621679876655 (TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]) -> Type))
- data GenericSplitAtSym1 (l :: i6989586621679876655) (l :: TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]))
- type GenericSplitAtSym2 (t :: i6989586621679876655) (t :: [a6989586621679876656]) = GenericSplitAt t t
- data GenericIndexSym0 (l :: TyFun [a6989586621679876654] (TyFun i6989586621679876653 a6989586621679876654 -> Type))
- data GenericIndexSym1 (l :: [a6989586621679876654]) (l :: TyFun i6989586621679876653 a6989586621679876654)
- type GenericIndexSym2 (t :: [a6989586621679876654]) (t :: i6989586621679876653) = GenericIndex t t
- data GenericReplicateSym0 (l :: TyFun i6989586621679876651 (TyFun a6989586621679876652 [a6989586621679876652] -> Type))
- data GenericReplicateSym1 (l :: i6989586621679876651) (l :: TyFun a6989586621679876652 [a6989586621679876652])
- type GenericReplicateSym2 (t :: i6989586621679876651) (t :: a6989586621679876652) = GenericReplicate t t
Basic functions
type family Length (a :: [a]) :: Nat where ... Source #
Length '[] = FromInteger 0 | |
Length ((:) _z_6989586621679458940 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply LengthSym0 xs) |
List transformations
type family Intersperse (a :: a) (a :: [a]) :: [a] where ... Source #
Intersperse _z_6989586621679461963 '[] = '[] | |
Intersperse sep ((:) x xs) = Apply (Apply (:$) x) (Apply (Apply PrependToAllSym0 sep) xs) |
type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ... Source #
Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) |
type family Subsequences (a :: [a]) :: [[a]] where ... Source #
Subsequences xs = Apply (Apply (:$) '[]) (Apply NonEmptySubsequencesSym0 xs) |
type family Permutations (a :: [a]) :: [[a]] where ... Source #
Reducing lists (folds)
type family Foldl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #
type family Foldl' (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #
type family Foldr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #
type family Foldr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ... Source #
Foldr1 _z_6989586621679461187 '[x] = x | |
Foldr1 f ((:) x ((:) wild_6989586621679458644 wild_6989586621679458646)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let6989586621679461195XsSym4 f x wild_6989586621679458644 wild_6989586621679458646)) | |
Foldr1 _z_6989586621679461214 '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" |
Special folds
type family Sum (a :: [a]) :: a where ... Source #
Sum l = Apply (Apply (Let6989586621679458973Sum'Sym1 l) l) (FromInteger 0) |
type family Product (a :: [a]) :: a where ... Source #
Product l = Apply (Apply (Let6989586621679458949ProdSym1 l) l) (FromInteger 1) |
Building lists
Scans
type family Scanl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ... Source #
type family Scanr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ... Source #
type family Scanr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ... Source #
Scanr1 _z_6989586621679460992 '[] = '[] | |
Scanr1 _z_6989586621679460995 '[x] = Apply (Apply (:$) x) '[] | |
Scanr1 f ((:) x ((:) wild_6989586621679458652 wild_6989586621679458654)) = Case_6989586621679461041 f x wild_6989586621679458652 wild_6989586621679458654 (Let6989586621679461022Scrutinee_6989586621679458650Sym4 f x wild_6989586621679458652 wild_6989586621679458654) |
Accumulating maps
type family MapAccumL (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... Source #
type family MapAccumR (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... Source #
Infinite lists
type family Replicate (a :: Nat) (a :: a) :: [a] where ... Source #
Replicate n x = Case_6989586621679458933 n x (Let6989586621679458925Scrutinee_6989586621679458736Sym2 n x) |
Unfolding
type family Unfoldr (a :: TyFun b (Maybe (a, b)) -> Type) (a :: b) :: [a] where ... Source #
Unfoldr f b = Case_6989586621679460634 f b (Let6989586621679460626Scrutinee_6989586621679458656Sym2 f b) |
Sublists
Extracting sublists
type family Span (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... Source #
Span _z_6989586621679459264 '[] = Apply (Apply Tuple2Sym0 Let6989586621679459267XsSym0) Let6989586621679459267XsSym0 | |
Span p ((:) x xs') = Case_6989586621679459297 p x xs' (Let6989586621679459284Scrutinee_6989586621679458716Sym3 p x xs') |
type family Break (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... Source #
Break _z_6989586621679459162 '[] = Apply (Apply Tuple2Sym0 Let6989586621679459165XsSym0) Let6989586621679459165XsSym0 | |
Break p ((:) x xs') = Case_6989586621679459195 p x xs' (Let6989586621679459182Scrutinee_6989586621679458718Sym3 p x xs') |
type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ... Source #
StripPrefix '[] ys = Apply JustSym0 ys | |
StripPrefix arg_6989586621679876777 arg_6989586621679876779 = Case_6989586621679877388 arg_6989586621679876777 arg_6989586621679876779 (Apply (Apply Tuple2Sym0 arg_6989586621679876777) arg_6989586621679876779) |
type family Group (a :: [a]) :: [[a]] where ... Source #
Group xs = Apply (Apply GroupBySym0 (:==$)) xs |
Predicates
type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
IsPrefixOf '[] '[] = TrueSym0 | |
IsPrefixOf '[] ((:) _z_6989586621679460566 _z_6989586621679460569) = TrueSym0 | |
IsPrefixOf ((:) _z_6989586621679460572 _z_6989586621679460575) '[] = FalseSym0 | |
IsPrefixOf ((:) x xs) ((:) y ys) = Apply (Apply (:&&$) (Apply (Apply (:==$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) |
type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
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 ... Source #
Lookup _key '[] = NothingSym0 | |
Lookup key ((:) '(x, y) xys) = Case_6989586621679459077 key x y xys (Let6989586621679459058Scrutinee_6989586621679458732Sym4 key x y xys) |
Searching with a predicate
type family Find (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe a where ... Source #
Find p a_6989586621679459547 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FilterSym0 p)) a_6989586621679459547 |
Indexing lists
type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ... Source #
ElemIndices x a_6989586621679460449 = Apply (Apply FindIndicesSym0 (Apply (:==$) x)) a_6989586621679460449 |
type family FindIndex (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe Nat where ... Source #
FindIndex p a_6989586621679460462 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679460462 |
Zipping and unzipping lists
type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ... Source #
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_6989586621679460298 _z_6989586621679460301) = '[] | |
Zip3 '[] ((:) _z_6989586621679460304 _z_6989586621679460307) '[] = '[] | |
Zip3 '[] ((:) _z_6989586621679460310 _z_6989586621679460313) ((:) _z_6989586621679460316 _z_6989586621679460319) = '[] | |
Zip3 ((:) _z_6989586621679460322 _z_6989586621679460325) '[] '[] = '[] | |
Zip3 ((:) _z_6989586621679460328 _z_6989586621679460331) '[] ((:) _z_6989586621679460334 _z_6989586621679460337) = '[] | |
Zip3 ((:) _z_6989586621679460340 _z_6989586621679460343) ((:) _z_6989586621679460346 _z_6989586621679460349) '[] = '[] |
type family Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ... Source #
Zip4 a_6989586621679877342 a_6989586621679877344 a_6989586621679877346 a_6989586621679877348 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621679877342) a_6989586621679877344) a_6989586621679877346) a_6989586621679877348 |
type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ... Source #
Zip5 a_6989586621679877297 a_6989586621679877299 a_6989586621679877301 a_6989586621679877303 a_6989586621679877305 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621679877297) a_6989586621679877299) a_6989586621679877301) a_6989586621679877303) a_6989586621679877305 |
type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ... Source #
Zip6 a_6989586621679877240 a_6989586621679877242 a_6989586621679877244 a_6989586621679877246 a_6989586621679877248 a_6989586621679877250 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621679877240) a_6989586621679877242) a_6989586621679877244) a_6989586621679877246) a_6989586621679877248) a_6989586621679877250 |
type family Zip7 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [(a, b, c, d, e, f, g)] where ... Source #
Zip7 a_6989586621679877170 a_6989586621679877172 a_6989586621679877174 a_6989586621679877176 a_6989586621679877178 a_6989586621679877180 a_6989586621679877182 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621679877170) a_6989586621679877172) a_6989586621679877174) a_6989586621679877176) a_6989586621679877178) a_6989586621679877180) a_6989586621679877182 |
type family ZipWith (a :: TyFun a (TyFun b c -> Type) -> Type) (a :: [a]) (a :: [b]) :: [c] where ... Source #
ZipWith f ((:) x xs) ((:) y ys) = Apply (Apply (:$) (Apply (Apply f x) y)) (Apply (Apply (Apply ZipWithSym0 f) xs) ys) | |
ZipWith _z_6989586621679460256 '[] '[] = '[] | |
ZipWith _z_6989586621679460259 ((:) _z_6989586621679460262 _z_6989586621679460265) '[] = '[] | |
ZipWith _z_6989586621679460268 '[] ((:) _z_6989586621679460271 _z_6989586621679460274) = '[] |
type family ZipWith3 (a :: TyFun a (TyFun b (TyFun c d -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ... Source #
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_6989586621679460161 '[] '[] '[] = '[] | |
ZipWith3 _z_6989586621679460164 '[] '[] ((:) _z_6989586621679460167 _z_6989586621679460170) = '[] | |
ZipWith3 _z_6989586621679460173 '[] ((:) _z_6989586621679460176 _z_6989586621679460179) '[] = '[] | |
ZipWith3 _z_6989586621679460182 '[] ((:) _z_6989586621679460185 _z_6989586621679460188) ((:) _z_6989586621679460191 _z_6989586621679460194) = '[] | |
ZipWith3 _z_6989586621679460197 ((:) _z_6989586621679460200 _z_6989586621679460203) '[] '[] = '[] | |
ZipWith3 _z_6989586621679460206 ((:) _z_6989586621679460209 _z_6989586621679460212) '[] ((:) _z_6989586621679460215 _z_6989586621679460218) = '[] | |
ZipWith3 _z_6989586621679460221 ((:) _z_6989586621679460224 _z_6989586621679460227) ((:) _z_6989586621679460230 _z_6989586621679460233) '[] = '[] |
type family ZipWith4 (a :: TyFun a (TyFun b (TyFun c (TyFun d e -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ... Source #
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_6989586621679877155 _z_6989586621679877158 _z_6989586621679877161 _z_6989586621679877164 _z_6989586621679877167 = '[] |
type family ZipWith5 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e f -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ... Source #
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_6989586621679877098 _z_6989586621679877101 _z_6989586621679877104 _z_6989586621679877107 _z_6989586621679877110 _z_6989586621679877113 = '[] |
type family ZipWith6 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e (TyFun f g -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ... Source #
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_6989586621679877027 _z_6989586621679877030 _z_6989586621679877033 _z_6989586621679877036 _z_6989586621679877039 _z_6989586621679877042 _z_6989586621679877045 = '[] |
type family ZipWith7 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e (TyFun f (TyFun g h -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ... Source #
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_6989586621679876941 _z_6989586621679876944 _z_6989586621679876947 _z_6989586621679876950 _z_6989586621679876953 _z_6989586621679876956 _z_6989586621679876959 _z_6989586621679876962 = '[] |
type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... Source #
Special lists
"Set" operations
Ordered lists
type family Sort (a :: [a]) :: [a] where ... Source #
Sort a_6989586621679459783 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679459783 |
type family Insert (a :: a) (a :: [a]) :: [a] where ... Source #
Insert e ls = Apply (Apply (Apply InsertBySym0 CompareSym0) e) ls |
Generalized functions
The "By
" operations
User-supplied equality (replacing an Eq
context)
type family NubBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [a] where ... Source #
type family DeleteBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... Source #
type family DeleteFirstsBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... Source #
DeleteFirstsBy eq a_6989586621679459852 a_6989586621679459854 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679459852) a_6989586621679459854 |
type family UnionBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... Source #
type family GroupBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [[a]] where ... Source #
type family IntersectBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... Source #
IntersectBy _z_6989586621679459566 '[] '[] = '[] | |
IntersectBy _z_6989586621679459569 '[] ((:) _z_6989586621679459572 _z_6989586621679459575) = '[] | |
IntersectBy _z_6989586621679459578 ((:) _z_6989586621679459581 _z_6989586621679459584) '[] = '[] | |
IntersectBy eq ((:) wild_6989586621679458702 wild_6989586621679458704) ((:) wild_6989586621679458706 wild_6989586621679458708) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679459643Sym0 eq) wild_6989586621679458702) wild_6989586621679458704) wild_6989586621679458706) wild_6989586621679458708)) (Let6989586621679459592XsSym5 eq wild_6989586621679458702 wild_6989586621679458704 wild_6989586621679458706 wild_6989586621679458708) |
User-supplied comparison (replacing an Ord
context)
type family SortBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: [a] where ... Source #
type family InsertBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... Source #
type family MaximumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... Source #
MaximumBy _z_6989586621679461241 '[] = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" | |
MaximumBy cmp ((:) wild_6989586621679458688 wild_6989586621679458690) = Apply (Apply Foldl1Sym0 (Let6989586621679461260MaxBySym3 cmp wild_6989586621679458688 wild_6989586621679458690)) (Let6989586621679461247XsSym3 cmp wild_6989586621679458688 wild_6989586621679458690) |
type family MinimumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... Source #
MinimumBy _z_6989586621679461328 '[] = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" | |
MinimumBy cmp ((:) wild_6989586621679458694 wild_6989586621679458696) = Apply (Apply Foldl1Sym0 (Let6989586621679461347MinBySym3 cmp wild_6989586621679458694 wild_6989586621679458696)) (Let6989586621679461334XsSym3 cmp wild_6989586621679458694 wild_6989586621679458696) |
The "generic
" operations
type family GenericLength (a :: [a]) :: i where ... Source #
GenericLength '[] = FromInteger 0 | |
GenericLength ((:) _z_6989586621679458787 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
type family GenericTake (a :: i) (a :: [a]) :: [a] where ... Source #
GenericTake a_6989586621679876851 a_6989586621679876853 = Apply (Apply TakeSym0 a_6989586621679876851) a_6989586621679876853 |
type family GenericDrop (a :: i) (a :: [a]) :: [a] where ... Source #
GenericDrop a_6989586621679876836 a_6989586621679876838 = Apply (Apply DropSym0 a_6989586621679876836) a_6989586621679876838 |
type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ... Source #
GenericSplitAt a_6989586621679876821 a_6989586621679876823 = Apply (Apply SplitAtSym0 a_6989586621679876821) a_6989586621679876823 |
type family GenericIndex (a :: [a]) (a :: i) :: a where ... Source #
GenericIndex a_6989586621679876806 a_6989586621679876808 = Apply (Apply (:!!$) a_6989586621679876806) a_6989586621679876808 |
type family GenericReplicate (a :: i) (a :: a) :: [a] where ... Source #
GenericReplicate a_6989586621679876791 a_6989586621679876793 = Apply (Apply ReplicateSym0 a_6989586621679876791) a_6989586621679876793 |
Defunctionalization symbols
data (:$) (l :: TyFun a3530822107858468865 (TyFun [a3530822107858468865] [a3530822107858468865] -> Type)) Source #
data (l :: a3530822107858468865) :$$ (l :: TyFun [a3530822107858468865] [a3530822107858468865]) Source #
data (l :: [a6989586621679281045]) :++$$ (l :: TyFun [a6989586621679281045] [a6989586621679281045]) Source #
data (:++$) (l :: TyFun [a6989586621679281045] (TyFun [a6989586621679281045] [a6989586621679281045] -> Type)) Source #
data MapSym0 (l :: TyFun (TyFun a6989586621679281046 b6989586621679281047 -> Type) (TyFun [a6989586621679281046] [b6989586621679281047] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679281046 b6989586621679281047 -> Type) (TyFun [a6989586621679281046] [b6989586621679281047] -> Type) -> *) (MapSym0 a6989586621679281046 b6989586621679281047) Source # | |
type Apply (TyFun a6989586621679281046 b6989586621679281047 -> Type) (TyFun [a6989586621679281046] [b6989586621679281047] -> Type) (MapSym0 a6989586621679281046 b6989586621679281047) l Source # | |
data MapSym1 (l :: TyFun a6989586621679281046 b6989586621679281047 -> Type) (l :: TyFun [a6989586621679281046] [b6989586621679281047]) Source #
type MapSym2 (t :: TyFun a6989586621679281046 b6989586621679281047 -> Type) (t :: [a6989586621679281046]) = Map t t Source #
data ReverseSym0 (l :: TyFun [a6989586621679458191] [a6989586621679458191]) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458191] [a6989586621679458191] -> *) (ReverseSym0 a6989586621679458191) Source # | |
type Apply [a] [a] (ReverseSym0 a) l Source # | |
type ReverseSym1 (t :: [a6989586621679458191]) = Reverse t Source #
data IntersperseSym0 (l :: TyFun a6989586621679458190 (TyFun [a6989586621679458190] [a6989586621679458190] -> Type)) Source #
SuppressUnusedWarnings (TyFun a6989586621679458190 (TyFun [a6989586621679458190] [a6989586621679458190] -> Type) -> *) (IntersperseSym0 a6989586621679458190) Source # | |
type Apply a6989586621679458190 (TyFun [a6989586621679458190] [a6989586621679458190] -> Type) (IntersperseSym0 a6989586621679458190) l Source # | |
data IntersperseSym1 (l :: a6989586621679458190) (l :: TyFun [a6989586621679458190] [a6989586621679458190]) Source #
SuppressUnusedWarnings (a6989586621679458190 -> TyFun [a6989586621679458190] [a6989586621679458190] -> *) (IntersperseSym1 a6989586621679458190) Source # | |
type Apply [a] [a] (IntersperseSym1 a l1) l2 Source # | |
type IntersperseSym2 (t :: a6989586621679458190) (t :: [a6989586621679458190]) = Intersperse t t Source #
data IntercalateSym0 (l :: TyFun [a6989586621679458189] (TyFun [[a6989586621679458189]] [a6989586621679458189] -> Type)) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458189] (TyFun [[a6989586621679458189]] [a6989586621679458189] -> Type) -> *) (IntercalateSym0 a6989586621679458189) Source # | |
type Apply [a6989586621679458189] (TyFun [[a6989586621679458189]] [a6989586621679458189] -> Type) (IntercalateSym0 a6989586621679458189) l Source # | |
data IntercalateSym1 (l :: [a6989586621679458189]) (l :: TyFun [[a6989586621679458189]] [a6989586621679458189]) Source #
SuppressUnusedWarnings ([a6989586621679458189] -> TyFun [[a6989586621679458189]] [a6989586621679458189] -> *) (IntercalateSym1 a6989586621679458189) Source # | |
type Apply [[a]] [a] (IntercalateSym1 a l1) l2 Source # | |
type IntercalateSym2 (t :: [a6989586621679458189]) (t :: [[a6989586621679458189]]) = Intercalate t t Source #
data SubsequencesSym0 (l :: TyFun [a6989586621679458188] [[a6989586621679458188]]) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458188] [[a6989586621679458188]] -> *) (SubsequencesSym0 a6989586621679458188) Source # | |
type Apply [a] [[a]] (SubsequencesSym0 a) l Source # | |
type SubsequencesSym1 (t :: [a6989586621679458188]) = Subsequences t Source #
data PermutationsSym0 (l :: TyFun [a6989586621679458185] [[a6989586621679458185]]) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458185] [[a6989586621679458185]] -> *) (PermutationsSym0 a6989586621679458185) Source # | |
type Apply [a] [[a]] (PermutationsSym0 a) l Source # | |
type PermutationsSym1 (t :: [a6989586621679458185]) = Permutations t Source #
data FoldlSym0 (l :: TyFun (TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679242245 b6989586621679242246) Source # | |
type Apply (TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type) -> Type) (FoldlSym0 a6989586621679242245 b6989586621679242246) l Source # | |
data FoldlSym1 (l :: TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (l :: TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type)) Source #
SuppressUnusedWarnings ((TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) -> TyFun b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type) -> *) (FoldlSym1 a6989586621679242245 b6989586621679242246) Source # | |
type Apply b6989586621679242246 (TyFun [a6989586621679242245] b6989586621679242246 -> Type) (FoldlSym1 a6989586621679242245 b6989586621679242246 l1) l2 Source # | |
data FoldlSym2 (l :: TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (l :: b6989586621679242246) (l :: TyFun [a6989586621679242245] b6989586621679242246) Source #
SuppressUnusedWarnings ((TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) -> b6989586621679242246 -> TyFun [a6989586621679242245] b6989586621679242246 -> *) (FoldlSym2 a6989586621679242245 b6989586621679242246) Source # | |
type Apply [a] b (FoldlSym2 a b l1 l2) l3 Source # | |
type FoldlSym3 (t :: TyFun b6989586621679242246 (TyFun a6989586621679242245 b6989586621679242246 -> Type) -> Type) (t :: b6989586621679242246) (t :: [a6989586621679242245]) = Foldl t t t Source #
data Foldl'Sym0 (l :: TyFun (TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (TyFun b6989586621679458184 (TyFun [a6989586621679458183] b6989586621679458184 -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (TyFun b6989586621679458184 (TyFun [a6989586621679458183] b6989586621679458184 -> Type) -> Type) -> *) (Foldl'Sym0 a6989586621679458183 b6989586621679458184) Source # | |
type Apply (TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (TyFun b6989586621679458184 (TyFun [a6989586621679458183] b6989586621679458184 -> Type) -> Type) (Foldl'Sym0 a6989586621679458183 b6989586621679458184) l Source # | |
data Foldl'Sym1 (l :: TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (l :: TyFun b6989586621679458184 (TyFun [a6989586621679458183] b6989586621679458184 -> Type)) Source #
SuppressUnusedWarnings ((TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) -> TyFun b6989586621679458184 (TyFun [a6989586621679458183] b6989586621679458184 -> Type) -> *) (Foldl'Sym1 a6989586621679458183 b6989586621679458184) Source # | |
type Apply b6989586621679458184 (TyFun [a6989586621679458183] b6989586621679458184 -> Type) (Foldl'Sym1 a6989586621679458183 b6989586621679458184 l1) l2 Source # | |
data Foldl'Sym2 (l :: TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (l :: b6989586621679458184) (l :: TyFun [a6989586621679458183] b6989586621679458184) Source #
SuppressUnusedWarnings ((TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) -> b6989586621679458184 -> TyFun [a6989586621679458183] b6989586621679458184 -> *) (Foldl'Sym2 a6989586621679458183 b6989586621679458184) Source # | |
type Apply [a] b (Foldl'Sym2 a b l1 l2) l3 Source # | |
type Foldl'Sym3 (t :: TyFun b6989586621679458184 (TyFun a6989586621679458183 b6989586621679458184 -> Type) -> Type) (t :: b6989586621679458184) (t :: [a6989586621679458183]) = Foldl' t t t Source #
data Foldl1Sym0 (l :: TyFun (TyFun a6989586621679458182 (TyFun a6989586621679458182 a6989586621679458182 -> Type) -> Type) (TyFun [a6989586621679458182] a6989586621679458182 -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458182 (TyFun a6989586621679458182 a6989586621679458182 -> Type) -> Type) (TyFun [a6989586621679458182] a6989586621679458182 -> Type) -> *) (Foldl1Sym0 a6989586621679458182) Source # | |
type Apply (TyFun a6989586621679458182 (TyFun a6989586621679458182 a6989586621679458182 -> Type) -> Type) (TyFun [a6989586621679458182] a6989586621679458182 -> Type) (Foldl1Sym0 a6989586621679458182) l Source # | |
data Foldl1Sym1 (l :: TyFun a6989586621679458182 (TyFun a6989586621679458182 a6989586621679458182 -> Type) -> Type) (l :: TyFun [a6989586621679458182] a6989586621679458182) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458182 (TyFun a6989586621679458182 a6989586621679458182 -> Type) -> Type) -> TyFun [a6989586621679458182] a6989586621679458182 -> *) (Foldl1Sym1 a6989586621679458182) Source # | |
type Apply [a] a (Foldl1Sym1 a l1) l2 Source # | |
type Foldl1Sym2 (t :: TyFun a6989586621679458182 (TyFun a6989586621679458182 a6989586621679458182 -> Type) -> Type) (t :: [a6989586621679458182]) = Foldl1 t t Source #
data Foldl1'Sym0 (l :: TyFun (TyFun a6989586621679458181 (TyFun a6989586621679458181 a6989586621679458181 -> Type) -> Type) (TyFun [a6989586621679458181] a6989586621679458181 -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458181 (TyFun a6989586621679458181 a6989586621679458181 -> Type) -> Type) (TyFun [a6989586621679458181] a6989586621679458181 -> Type) -> *) (Foldl1'Sym0 a6989586621679458181) Source # | |
type Apply (TyFun a6989586621679458181 (TyFun a6989586621679458181 a6989586621679458181 -> Type) -> Type) (TyFun [a6989586621679458181] a6989586621679458181 -> Type) (Foldl1'Sym0 a6989586621679458181) l Source # | |
data Foldl1'Sym1 (l :: TyFun a6989586621679458181 (TyFun a6989586621679458181 a6989586621679458181 -> Type) -> Type) (l :: TyFun [a6989586621679458181] a6989586621679458181) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458181 (TyFun a6989586621679458181 a6989586621679458181 -> Type) -> Type) -> TyFun [a6989586621679458181] a6989586621679458181 -> *) (Foldl1'Sym1 a6989586621679458181) Source # | |
type Apply [a] a (Foldl1'Sym1 a l1) l2 Source # | |
type Foldl1'Sym2 (t :: TyFun a6989586621679458181 (TyFun a6989586621679458181 a6989586621679458181 -> Type) -> Type) (t :: [a6989586621679458181]) = Foldl1' t t Source #
data FoldrSym0 (l :: TyFun (TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type) -> Type) -> *) (FoldrSym0 a6989586621679281048 b6989586621679281049) Source # | |
type Apply (TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type) -> Type) (FoldrSym0 a6989586621679281048 b6989586621679281049) l Source # | |
data FoldrSym1 (l :: TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (l :: TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) -> TyFun b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type) -> *) (FoldrSym1 a6989586621679281048 b6989586621679281049) Source # | |
type Apply b6989586621679281049 (TyFun [a6989586621679281048] b6989586621679281049 -> Type) (FoldrSym1 a6989586621679281048 b6989586621679281049 l1) l2 Source # | |
data FoldrSym2 (l :: TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (l :: b6989586621679281049) (l :: TyFun [a6989586621679281048] b6989586621679281049) Source #
SuppressUnusedWarnings ((TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) -> b6989586621679281049 -> TyFun [a6989586621679281048] b6989586621679281049 -> *) (FoldrSym2 a6989586621679281048 b6989586621679281049) Source # | |
type Apply [a] b (FoldrSym2 a b l1 l2) l3 Source # | |
type FoldrSym3 (t :: TyFun a6989586621679281048 (TyFun b6989586621679281049 b6989586621679281049 -> Type) -> Type) (t :: b6989586621679281049) (t :: [a6989586621679281048]) = Foldr t t t Source #
data Foldr1Sym0 (l :: TyFun (TyFun a6989586621679458180 (TyFun a6989586621679458180 a6989586621679458180 -> Type) -> Type) (TyFun [a6989586621679458180] a6989586621679458180 -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458180 (TyFun a6989586621679458180 a6989586621679458180 -> Type) -> Type) (TyFun [a6989586621679458180] a6989586621679458180 -> Type) -> *) (Foldr1Sym0 a6989586621679458180) Source # | |
type Apply (TyFun a6989586621679458180 (TyFun a6989586621679458180 a6989586621679458180 -> Type) -> Type) (TyFun [a6989586621679458180] a6989586621679458180 -> Type) (Foldr1Sym0 a6989586621679458180) l Source # | |
data Foldr1Sym1 (l :: TyFun a6989586621679458180 (TyFun a6989586621679458180 a6989586621679458180 -> Type) -> Type) (l :: TyFun [a6989586621679458180] a6989586621679458180) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458180 (TyFun a6989586621679458180 a6989586621679458180 -> Type) -> Type) -> TyFun [a6989586621679458180] a6989586621679458180 -> *) (Foldr1Sym1 a6989586621679458180) Source # | |
type Apply [a] a (Foldr1Sym1 a l1) l2 Source # | |
type Foldr1Sym2 (t :: TyFun a6989586621679458180 (TyFun a6989586621679458180 a6989586621679458180 -> Type) -> Type) (t :: [a6989586621679458180]) = Foldr1 t t Source #
data ConcatSym0 (l :: TyFun [[a6989586621679458179]] [a6989586621679458179]) Source #
SuppressUnusedWarnings (TyFun [[a6989586621679458179]] [a6989586621679458179] -> *) (ConcatSym0 a6989586621679458179) Source # | |
type Apply [[a]] [a] (ConcatSym0 a) l Source # | |
type ConcatSym1 (t :: [[a6989586621679458179]]) = Concat t Source #
data ConcatMapSym0 (l :: TyFun (TyFun a6989586621679458177 [b6989586621679458178] -> Type) (TyFun [a6989586621679458177] [b6989586621679458178] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458177 [b6989586621679458178] -> Type) (TyFun [a6989586621679458177] [b6989586621679458178] -> Type) -> *) (ConcatMapSym0 a6989586621679458177 b6989586621679458178) Source # | |
type Apply (TyFun a6989586621679458177 [b6989586621679458178] -> Type) (TyFun [a6989586621679458177] [b6989586621679458178] -> Type) (ConcatMapSym0 a6989586621679458177 b6989586621679458178) l Source # | |
data ConcatMapSym1 (l :: TyFun a6989586621679458177 [b6989586621679458178] -> Type) (l :: TyFun [a6989586621679458177] [b6989586621679458178]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458177 [b6989586621679458178] -> Type) -> TyFun [a6989586621679458177] [b6989586621679458178] -> *) (ConcatMapSym1 a6989586621679458177 b6989586621679458178) Source # | |
type Apply [a] [b] (ConcatMapSym1 a b l1) l2 Source # | |
type ConcatMapSym2 (t :: TyFun a6989586621679458177 [b6989586621679458178] -> Type) (t :: [a6989586621679458177]) = ConcatMap t t Source #
data Any_Sym0 (l :: TyFun (TyFun a6989586621679447960 Bool -> Type) (TyFun [a6989586621679447960] Bool -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679447960 Bool -> Type) (TyFun [a6989586621679447960] Bool -> Type) -> *) (Any_Sym0 a6989586621679447960) Source # | |
type Apply (TyFun a6989586621679447960 Bool -> Type) (TyFun [a6989586621679447960] Bool -> Type) (Any_Sym0 a6989586621679447960) l Source # | |
data Any_Sym1 (l :: TyFun a6989586621679447960 Bool -> Type) (l :: TyFun [a6989586621679447960] Bool) Source #
type Any_Sym2 (t :: TyFun a6989586621679447960 Bool -> Type) (t :: [a6989586621679447960]) = Any_ t t Source #
data AllSym0 (l :: TyFun (TyFun a6989586621679458176 Bool -> Type) (TyFun [a6989586621679458176] Bool -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458176 Bool -> Type) (TyFun [a6989586621679458176] Bool -> Type) -> *) (AllSym0 a6989586621679458176) Source # | |
type Apply (TyFun a6989586621679458176 Bool -> Type) (TyFun [a6989586621679458176] Bool -> Type) (AllSym0 a6989586621679458176) l Source # | |
data AllSym1 (l :: TyFun a6989586621679458176 Bool -> Type) (l :: TyFun [a6989586621679458176] Bool) Source #
type AllSym2 (t :: TyFun a6989586621679458176 Bool -> Type) (t :: [a6989586621679458176]) = All t t Source #
data ScanlSym0 (l :: TyFun (TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type) -> Type) -> *) (ScanlSym0 a6989586621679458175 b6989586621679458174) Source # | |
type Apply (TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type) -> Type) (ScanlSym0 a6989586621679458175 b6989586621679458174) l Source # | |
data ScanlSym1 (l :: TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (l :: TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type)) Source #
SuppressUnusedWarnings ((TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) -> TyFun b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type) -> *) (ScanlSym1 a6989586621679458175 b6989586621679458174) Source # | |
type Apply b6989586621679458174 (TyFun [a6989586621679458175] [b6989586621679458174] -> Type) (ScanlSym1 a6989586621679458175 b6989586621679458174 l1) l2 Source # | |
data ScanlSym2 (l :: TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (l :: b6989586621679458174) (l :: TyFun [a6989586621679458175] [b6989586621679458174]) Source #
SuppressUnusedWarnings ((TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) -> b6989586621679458174 -> TyFun [a6989586621679458175] [b6989586621679458174] -> *) (ScanlSym2 a6989586621679458175 b6989586621679458174) Source # | |
type Apply [a] [b] (ScanlSym2 a b l1 l2) l3 Source # | |
type ScanlSym3 (t :: TyFun b6989586621679458174 (TyFun a6989586621679458175 b6989586621679458174 -> Type) -> Type) (t :: b6989586621679458174) (t :: [a6989586621679458175]) = Scanl t t t Source #
data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679458173 (TyFun a6989586621679458173 a6989586621679458173 -> Type) -> Type) (TyFun [a6989586621679458173] [a6989586621679458173] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458173 (TyFun a6989586621679458173 a6989586621679458173 -> Type) -> Type) (TyFun [a6989586621679458173] [a6989586621679458173] -> Type) -> *) (Scanl1Sym0 a6989586621679458173) Source # | |
type Apply (TyFun a6989586621679458173 (TyFun a6989586621679458173 a6989586621679458173 -> Type) -> Type) (TyFun [a6989586621679458173] [a6989586621679458173] -> Type) (Scanl1Sym0 a6989586621679458173) l Source # | |
data Scanl1Sym1 (l :: TyFun a6989586621679458173 (TyFun a6989586621679458173 a6989586621679458173 -> Type) -> Type) (l :: TyFun [a6989586621679458173] [a6989586621679458173]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458173 (TyFun a6989586621679458173 a6989586621679458173 -> Type) -> Type) -> TyFun [a6989586621679458173] [a6989586621679458173] -> *) (Scanl1Sym1 a6989586621679458173) Source # | |
type Apply [a] [a] (Scanl1Sym1 a l1) l2 Source # | |
type Scanl1Sym2 (t :: TyFun a6989586621679458173 (TyFun a6989586621679458173 a6989586621679458173 -> Type) -> Type) (t :: [a6989586621679458173]) = Scanl1 t t Source #
data ScanrSym0 (l :: TyFun (TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type) -> Type) -> *) (ScanrSym0 a6989586621679458171 b6989586621679458172) Source # | |
type Apply (TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type) -> Type) (ScanrSym0 a6989586621679458171 b6989586621679458172) l Source # | |
data ScanrSym1 (l :: TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (l :: TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) -> TyFun b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type) -> *) (ScanrSym1 a6989586621679458171 b6989586621679458172) Source # | |
type Apply b6989586621679458172 (TyFun [a6989586621679458171] [b6989586621679458172] -> Type) (ScanrSym1 a6989586621679458171 b6989586621679458172 l1) l2 Source # | |
data ScanrSym2 (l :: TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (l :: b6989586621679458172) (l :: TyFun [a6989586621679458171] [b6989586621679458172]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) -> b6989586621679458172 -> TyFun [a6989586621679458171] [b6989586621679458172] -> *) (ScanrSym2 a6989586621679458171 b6989586621679458172) Source # | |
type Apply [a] [b] (ScanrSym2 a b l1 l2) l3 Source # | |
type ScanrSym3 (t :: TyFun a6989586621679458171 (TyFun b6989586621679458172 b6989586621679458172 -> Type) -> Type) (t :: b6989586621679458172) (t :: [a6989586621679458171]) = Scanr t t t Source #
data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679458170 (TyFun a6989586621679458170 a6989586621679458170 -> Type) -> Type) (TyFun [a6989586621679458170] [a6989586621679458170] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458170 (TyFun a6989586621679458170 a6989586621679458170 -> Type) -> Type) (TyFun [a6989586621679458170] [a6989586621679458170] -> Type) -> *) (Scanr1Sym0 a6989586621679458170) Source # | |
type Apply (TyFun a6989586621679458170 (TyFun a6989586621679458170 a6989586621679458170 -> Type) -> Type) (TyFun [a6989586621679458170] [a6989586621679458170] -> Type) (Scanr1Sym0 a6989586621679458170) l Source # | |
data Scanr1Sym1 (l :: TyFun a6989586621679458170 (TyFun a6989586621679458170 a6989586621679458170 -> Type) -> Type) (l :: TyFun [a6989586621679458170] [a6989586621679458170]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458170 (TyFun a6989586621679458170 a6989586621679458170 -> Type) -> Type) -> TyFun [a6989586621679458170] [a6989586621679458170] -> *) (Scanr1Sym1 a6989586621679458170) Source # | |
type Apply [a] [a] (Scanr1Sym1 a l1) l2 Source # | |
type Scanr1Sym2 (t :: TyFun a6989586621679458170 (TyFun a6989586621679458170 a6989586621679458170 -> Type) -> Type) (t :: [a6989586621679458170]) = Scanr1 t t Source #
data MapAccumLSym0 (l :: TyFun (TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) -> Type) -> *) (MapAccumLSym0 x6989586621679458168 acc6989586621679458167 y6989586621679458169) Source # | |
type Apply (TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) -> Type) (MapAccumLSym0 x6989586621679458168 acc6989586621679458167 y6989586621679458169) l Source # | |
data MapAccumLSym1 (l :: TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (l :: TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type)) Source #
SuppressUnusedWarnings ((TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) -> TyFun acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) -> *) (MapAccumLSym1 x6989586621679458168 acc6989586621679458167 y6989586621679458169) Source # | |
type Apply acc6989586621679458167 (TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> Type) (MapAccumLSym1 x6989586621679458168 acc6989586621679458167 y6989586621679458169 l1) l2 Source # | |
data MapAccumLSym2 (l :: TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (l :: acc6989586621679458167) (l :: TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169])) Source #
SuppressUnusedWarnings ((TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) -> acc6989586621679458167 -> TyFun [x6989586621679458168] (acc6989586621679458167, [y6989586621679458169]) -> *) (MapAccumLSym2 x6989586621679458168 acc6989586621679458167 y6989586621679458169) Source # | |
type Apply [x] (acc, [y]) (MapAccumLSym2 x acc y l1 l2) l3 Source # | |
type MapAccumLSym3 (t :: TyFun acc6989586621679458167 (TyFun x6989586621679458168 (acc6989586621679458167, y6989586621679458169) -> Type) -> Type) (t :: acc6989586621679458167) (t :: [x6989586621679458168]) = MapAccumL t t t Source #
data MapAccumRSym0 (l :: TyFun (TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) -> Type) -> *) (MapAccumRSym0 x6989586621679458165 acc6989586621679458164 y6989586621679458166) Source # | |
type Apply (TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) -> Type) (MapAccumRSym0 x6989586621679458165 acc6989586621679458164 y6989586621679458166) l Source # | |
data MapAccumRSym1 (l :: TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (l :: TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type)) Source #
SuppressUnusedWarnings ((TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) -> TyFun acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) -> *) (MapAccumRSym1 x6989586621679458165 acc6989586621679458164 y6989586621679458166) Source # | |
type Apply acc6989586621679458164 (TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> Type) (MapAccumRSym1 x6989586621679458165 acc6989586621679458164 y6989586621679458166 l1) l2 Source # | |
data MapAccumRSym2 (l :: TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (l :: acc6989586621679458164) (l :: TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166])) Source #
SuppressUnusedWarnings ((TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) -> acc6989586621679458164 -> TyFun [x6989586621679458165] (acc6989586621679458164, [y6989586621679458166]) -> *) (MapAccumRSym2 x6989586621679458165 acc6989586621679458164 y6989586621679458166) Source # | |
type Apply [x] (acc, [y]) (MapAccumRSym2 x acc y l1 l2) l3 Source # | |
type MapAccumRSym3 (t :: TyFun acc6989586621679458164 (TyFun x6989586621679458165 (acc6989586621679458164, y6989586621679458166) -> Type) -> Type) (t :: acc6989586621679458164) (t :: [x6989586621679458165]) = MapAccumR t t t Source #
data UnfoldrSym0 (l :: TyFun (TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) (TyFun b6989586621679458162 [a6989586621679458163] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) (TyFun b6989586621679458162 [a6989586621679458163] -> Type) -> *) (UnfoldrSym0 b6989586621679458162 a6989586621679458163) Source # | |
type Apply (TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) (TyFun b6989586621679458162 [a6989586621679458163] -> Type) (UnfoldrSym0 b6989586621679458162 a6989586621679458163) l Source # | |
data UnfoldrSym1 (l :: TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) (l :: TyFun b6989586621679458162 [a6989586621679458163]) Source #
SuppressUnusedWarnings ((TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) -> TyFun b6989586621679458162 [a6989586621679458163] -> *) (UnfoldrSym1 b6989586621679458162 a6989586621679458163) Source # | |
type Apply b [a] (UnfoldrSym1 b a l1) l2 Source # | |
type UnfoldrSym2 (t :: TyFun b6989586621679458162 (Maybe (a6989586621679458163, b6989586621679458162)) -> Type) (t :: b6989586621679458162) = Unfoldr t t Source #
data IsPrefixOfSym0 (l :: TyFun [a6989586621679458159] (TyFun [a6989586621679458159] Bool -> Type)) Source #
data IsPrefixOfSym1 (l :: [a6989586621679458159]) (l :: TyFun [a6989586621679458159] Bool) Source #
SuppressUnusedWarnings ([a6989586621679458159] -> TyFun [a6989586621679458159] Bool -> *) (IsPrefixOfSym1 a6989586621679458159) Source # | |
type Apply [a] Bool (IsPrefixOfSym1 a l1) l2 Source # | |
type IsPrefixOfSym2 (t :: [a6989586621679458159]) (t :: [a6989586621679458159]) = IsPrefixOf t t Source #
data IsSuffixOfSym0 (l :: TyFun [a6989586621679458158] (TyFun [a6989586621679458158] Bool -> Type)) Source #
data IsSuffixOfSym1 (l :: [a6989586621679458158]) (l :: TyFun [a6989586621679458158] Bool) Source #
SuppressUnusedWarnings ([a6989586621679458158] -> TyFun [a6989586621679458158] Bool -> *) (IsSuffixOfSym1 a6989586621679458158) Source # | |
type Apply [a] Bool (IsSuffixOfSym1 a l1) l2 Source # | |
type IsSuffixOfSym2 (t :: [a6989586621679458158]) (t :: [a6989586621679458158]) = IsSuffixOf t t Source #
data IsInfixOfSym0 (l :: TyFun [a6989586621679458157] (TyFun [a6989586621679458157] Bool -> Type)) Source #
data IsInfixOfSym1 (l :: [a6989586621679458157]) (l :: TyFun [a6989586621679458157] Bool) Source #
SuppressUnusedWarnings ([a6989586621679458157] -> TyFun [a6989586621679458157] Bool -> *) (IsInfixOfSym1 a6989586621679458157) Source # | |
type Apply [a] Bool (IsInfixOfSym1 a l1) l2 Source # | |
type IsInfixOfSym2 (t :: [a6989586621679458157]) (t :: [a6989586621679458157]) = IsInfixOf t t Source #
data ElemSym0 (l :: TyFun a6989586621679458156 (TyFun [a6989586621679458156] Bool -> Type)) Source #
data NotElemSym0 (l :: TyFun a6989586621679458155 (TyFun [a6989586621679458155] Bool -> Type)) Source #
data NotElemSym1 (l :: a6989586621679458155) (l :: TyFun [a6989586621679458155] Bool) Source #
SuppressUnusedWarnings (a6989586621679458155 -> TyFun [a6989586621679458155] Bool -> *) (NotElemSym1 a6989586621679458155) Source # | |
type Apply [a] Bool (NotElemSym1 a l1) l2 Source # | |
type NotElemSym2 (t :: a6989586621679458155) (t :: [a6989586621679458155]) = NotElem t t Source #
data ZipSym0 (l :: TyFun [a6989586621679458153] (TyFun [b6989586621679458154] [(a6989586621679458153, b6989586621679458154)] -> Type)) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458153] (TyFun [b6989586621679458154] [(a6989586621679458153, b6989586621679458154)] -> Type) -> *) (ZipSym0 a6989586621679458153 b6989586621679458154) Source # | |
type Apply [a6989586621679458153] (TyFun [b6989586621679458154] [(a6989586621679458153, b6989586621679458154)] -> Type) (ZipSym0 a6989586621679458153 b6989586621679458154) l Source # | |
data ZipSym1 (l :: [a6989586621679458153]) (l :: TyFun [b6989586621679458154] [(a6989586621679458153, b6989586621679458154)]) Source #
data Zip3Sym0 (l :: TyFun [a6989586621679458150] (TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458150] (TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) -> Type) -> *) (Zip3Sym0 a6989586621679458150 b6989586621679458151 c6989586621679458152) Source # | |
type Apply [a6989586621679458150] (TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) -> Type) (Zip3Sym0 a6989586621679458150 b6989586621679458151 c6989586621679458152) l Source # | |
data Zip3Sym1 (l :: [a6989586621679458150]) (l :: TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679458150] -> TyFun [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) -> *) (Zip3Sym1 a6989586621679458150 b6989586621679458151 c6989586621679458152) Source # | |
type Apply [b6989586621679458151] (TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> Type) (Zip3Sym1 a6989586621679458150 b6989586621679458151 c6989586621679458152 l1) l2 Source # | |
data Zip3Sym2 (l :: [a6989586621679458150]) (l :: [b6989586621679458151]) (l :: TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)]) Source #
SuppressUnusedWarnings ([a6989586621679458150] -> [b6989586621679458151] -> TyFun [c6989586621679458152] [(a6989586621679458150, b6989586621679458151, c6989586621679458152)] -> *) (Zip3Sym2 a6989586621679458150 b6989586621679458151 c6989586621679458152) Source # | |
type Apply [c] [(a, b, c)] (Zip3Sym2 a b c l1 l2) l3 Source # | |
type Zip3Sym3 (t :: [a6989586621679458150]) (t :: [b6989586621679458151]) (t :: [c6989586621679458152]) = Zip3 t t t Source #
data ZipWithSym0 (l :: TyFun (TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679458147 b6989586621679458148 c6989586621679458149) Source # | |
type Apply (TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) -> Type) (ZipWithSym0 a6989586621679458147 b6989586621679458148 c6989586621679458149) l Source # | |
data ZipWithSym1 (l :: TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (l :: TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) -> TyFun [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) -> *) (ZipWithSym1 a6989586621679458147 b6989586621679458148 c6989586621679458149) Source # | |
type Apply [a6989586621679458147] (TyFun [b6989586621679458148] [c6989586621679458149] -> Type) (ZipWithSym1 a6989586621679458147 b6989586621679458148 c6989586621679458149 l1) l2 Source # | |
data ZipWithSym2 (l :: TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (l :: [a6989586621679458147]) (l :: TyFun [b6989586621679458148] [c6989586621679458149]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) -> [a6989586621679458147] -> TyFun [b6989586621679458148] [c6989586621679458149] -> *) (ZipWithSym2 a6989586621679458147 b6989586621679458148 c6989586621679458149) Source # | |
type Apply [b] [c] (ZipWithSym2 a b c l1 l2) l3 Source # | |
type ZipWithSym3 (t :: TyFun a6989586621679458147 (TyFun b6989586621679458148 c6989586621679458149 -> Type) -> Type) (t :: [a6989586621679458147]) (t :: [b6989586621679458148]) = ZipWith t t t Source #
data ZipWith3Sym0 (l :: TyFun (TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) Source # | |
type Apply (TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) -> Type) (ZipWith3Sym0 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) l Source # | |
data ZipWith3Sym1 (l :: TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) -> TyFun [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) -> *) (ZipWith3Sym1 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) Source # | |
type Apply [a6989586621679458143] (TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> Type) (ZipWith3Sym1 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146 l1) l2 Source # | |
data ZipWith3Sym2 (l :: TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (l :: [a6989586621679458143]) (l :: TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) -> [a6989586621679458143] -> TyFun [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) -> *) (ZipWith3Sym2 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) Source # | |
type Apply [b6989586621679458144] (TyFun [c6989586621679458145] [d6989586621679458146] -> Type) (ZipWith3Sym2 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146 l1 l2) l3 Source # | |
data ZipWith3Sym3 (l :: TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (l :: [a6989586621679458143]) (l :: [b6989586621679458144]) (l :: TyFun [c6989586621679458145] [d6989586621679458146]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) -> [a6989586621679458143] -> [b6989586621679458144] -> TyFun [c6989586621679458145] [d6989586621679458146] -> *) (ZipWith3Sym3 a6989586621679458143 b6989586621679458144 c6989586621679458145 d6989586621679458146) Source # | |
type Apply [c] [d] (ZipWith3Sym3 a b c d l1 l2 l3) l4 Source # | |
type ZipWith3Sym4 (t :: TyFun a6989586621679458143 (TyFun b6989586621679458144 (TyFun c6989586621679458145 d6989586621679458146 -> Type) -> Type) -> Type) (t :: [a6989586621679458143]) (t :: [b6989586621679458144]) (t :: [c6989586621679458145]) = ZipWith3 t t t t Source #
data UnzipSym0 (l :: TyFun [(a6989586621679458141, b6989586621679458142)] ([a6989586621679458141], [b6989586621679458142])) Source #
data Unzip3Sym0 (l :: TyFun [(a6989586621679458138, b6989586621679458139, c6989586621679458140)] ([a6989586621679458138], [b6989586621679458139], [c6989586621679458140])) Source #
SuppressUnusedWarnings (TyFun [(a6989586621679458138, b6989586621679458139, c6989586621679458140)] ([a6989586621679458138], [b6989586621679458139], [c6989586621679458140]) -> *) (Unzip3Sym0 a6989586621679458138 b6989586621679458139 c6989586621679458140) Source # | |
type Apply [(a, b, c)] ([a], [b], [c]) (Unzip3Sym0 a b c) l Source # | |
type Unzip3Sym1 (t :: [(a6989586621679458138, b6989586621679458139, c6989586621679458140)]) = Unzip3 t Source #
data Unzip4Sym0 (l :: TyFun [(a6989586621679458134, b6989586621679458135, c6989586621679458136, d6989586621679458137)] ([a6989586621679458134], [b6989586621679458135], [c6989586621679458136], [d6989586621679458137])) Source #
SuppressUnusedWarnings (TyFun [(a6989586621679458134, b6989586621679458135, c6989586621679458136, d6989586621679458137)] ([a6989586621679458134], [b6989586621679458135], [c6989586621679458136], [d6989586621679458137]) -> *) (Unzip4Sym0 a6989586621679458134 b6989586621679458135 c6989586621679458136 d6989586621679458137) Source # | |
type Apply [(a, b, c, d)] ([a], [b], [c], [d]) (Unzip4Sym0 a b c d) l Source # | |
type Unzip4Sym1 (t :: [(a6989586621679458134, b6989586621679458135, c6989586621679458136, d6989586621679458137)]) = Unzip4 t Source #
data Unzip5Sym0 (l :: TyFun [(a6989586621679458129, b6989586621679458130, c6989586621679458131, d6989586621679458132, e6989586621679458133)] ([a6989586621679458129], [b6989586621679458130], [c6989586621679458131], [d6989586621679458132], [e6989586621679458133])) Source #
SuppressUnusedWarnings (TyFun [(a6989586621679458129, b6989586621679458130, c6989586621679458131, d6989586621679458132, e6989586621679458133)] ([a6989586621679458129], [b6989586621679458130], [c6989586621679458131], [d6989586621679458132], [e6989586621679458133]) -> *) (Unzip5Sym0 a6989586621679458129 b6989586621679458130 c6989586621679458131 d6989586621679458132 e6989586621679458133) Source # | |
type Apply [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) (Unzip5Sym0 a b c d e) l Source # | |
type Unzip5Sym1 (t :: [(a6989586621679458129, b6989586621679458130, c6989586621679458131, d6989586621679458132, e6989586621679458133)]) = Unzip5 t Source #
data Unzip6Sym0 (l :: TyFun [(a6989586621679458123, b6989586621679458124, c6989586621679458125, d6989586621679458126, e6989586621679458127, f6989586621679458128)] ([a6989586621679458123], [b6989586621679458124], [c6989586621679458125], [d6989586621679458126], [e6989586621679458127], [f6989586621679458128])) Source #
SuppressUnusedWarnings (TyFun [(a6989586621679458123, b6989586621679458124, c6989586621679458125, d6989586621679458126, e6989586621679458127, f6989586621679458128)] ([a6989586621679458123], [b6989586621679458124], [c6989586621679458125], [d6989586621679458126], [e6989586621679458127], [f6989586621679458128]) -> *) (Unzip6Sym0 a6989586621679458123 b6989586621679458124 c6989586621679458125 d6989586621679458126 e6989586621679458127 f6989586621679458128) Source # | |
type Apply [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) (Unzip6Sym0 a b c d e f) l Source # | |
type Unzip6Sym1 (t :: [(a6989586621679458123, b6989586621679458124, c6989586621679458125, d6989586621679458126, e6989586621679458127, f6989586621679458128)]) = Unzip6 t Source #
data Unzip7Sym0 (l :: TyFun [(a6989586621679458116, b6989586621679458117, c6989586621679458118, d6989586621679458119, e6989586621679458120, f6989586621679458121, g6989586621679458122)] ([a6989586621679458116], [b6989586621679458117], [c6989586621679458118], [d6989586621679458119], [e6989586621679458120], [f6989586621679458121], [g6989586621679458122])) Source #
SuppressUnusedWarnings (TyFun [(a6989586621679458116, b6989586621679458117, c6989586621679458118, d6989586621679458119, e6989586621679458120, f6989586621679458121, g6989586621679458122)] ([a6989586621679458116], [b6989586621679458117], [c6989586621679458118], [d6989586621679458119], [e6989586621679458120], [f6989586621679458121], [g6989586621679458122]) -> *) (Unzip7Sym0 a6989586621679458116 b6989586621679458117 c6989586621679458118 d6989586621679458119 e6989586621679458120 f6989586621679458121 g6989586621679458122) Source # | |
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 Source # | |
type Unzip7Sym1 (t :: [(a6989586621679458116, b6989586621679458117, c6989586621679458118, d6989586621679458119, e6989586621679458120, f6989586621679458121, g6989586621679458122)]) = Unzip7 t Source #
data DeleteSym0 (l :: TyFun a6989586621679458115 (TyFun [a6989586621679458115] [a6989586621679458115] -> Type)) Source #
SuppressUnusedWarnings (TyFun a6989586621679458115 (TyFun [a6989586621679458115] [a6989586621679458115] -> Type) -> *) (DeleteSym0 a6989586621679458115) Source # | |
type Apply a6989586621679458115 (TyFun [a6989586621679458115] [a6989586621679458115] -> Type) (DeleteSym0 a6989586621679458115) l Source # | |
data DeleteSym1 (l :: a6989586621679458115) (l :: TyFun [a6989586621679458115] [a6989586621679458115]) Source #
SuppressUnusedWarnings (a6989586621679458115 -> TyFun [a6989586621679458115] [a6989586621679458115] -> *) (DeleteSym1 a6989586621679458115) Source # | |
type Apply [a] [a] (DeleteSym1 a l1) l2 Source # | |
type DeleteSym2 (t :: a6989586621679458115) (t :: [a6989586621679458115]) = Delete t t Source #
data (:\\$) (l :: TyFun [a6989586621679458114] (TyFun [a6989586621679458114] [a6989586621679458114] -> Type)) Source #
data (l :: [a6989586621679458114]) :\\$$ (l :: TyFun [a6989586621679458114] [a6989586621679458114]) Source #
data IntersectSym0 (l :: TyFun [a6989586621679458101] (TyFun [a6989586621679458101] [a6989586621679458101] -> Type)) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458101] (TyFun [a6989586621679458101] [a6989586621679458101] -> Type) -> *) (IntersectSym0 a6989586621679458101) Source # | |
type Apply [a6989586621679458101] (TyFun [a6989586621679458101] [a6989586621679458101] -> Type) (IntersectSym0 a6989586621679458101) l Source # | |
data IntersectSym1 (l :: [a6989586621679458101]) (l :: TyFun [a6989586621679458101] [a6989586621679458101]) Source #
SuppressUnusedWarnings ([a6989586621679458101] -> TyFun [a6989586621679458101] [a6989586621679458101] -> *) (IntersectSym1 a6989586621679458101) Source # | |
type Apply [a] [a] (IntersectSym1 a l1) l2 Source # | |
type IntersectSym2 (t :: [a6989586621679458101]) (t :: [a6989586621679458101]) = Intersect t t Source #
data InsertSym0 (l :: TyFun a6989586621679458088 (TyFun [a6989586621679458088] [a6989586621679458088] -> Type)) Source #
SuppressUnusedWarnings (TyFun a6989586621679458088 (TyFun [a6989586621679458088] [a6989586621679458088] -> Type) -> *) (InsertSym0 a6989586621679458088) Source # | |
type Apply a6989586621679458088 (TyFun [a6989586621679458088] [a6989586621679458088] -> Type) (InsertSym0 a6989586621679458088) l Source # | |
data InsertSym1 (l :: a6989586621679458088) (l :: TyFun [a6989586621679458088] [a6989586621679458088]) Source #
SuppressUnusedWarnings (a6989586621679458088 -> TyFun [a6989586621679458088] [a6989586621679458088] -> *) (InsertSym1 a6989586621679458088) Source # | |
type Apply [a] [a] (InsertSym1 a l1) l2 Source # | |
type InsertSym2 (t :: a6989586621679458088) (t :: [a6989586621679458088]) = Insert t t Source #
data DeleteBySym0 (l :: TyFun (TyFun a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) (TyFun a6989586621679458113 (TyFun [a6989586621679458113] [a6989586621679458113] -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) (TyFun a6989586621679458113 (TyFun [a6989586621679458113] [a6989586621679458113] -> Type) -> Type) -> *) (DeleteBySym0 a6989586621679458113) Source # | |
type Apply (TyFun a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) (TyFun a6989586621679458113 (TyFun [a6989586621679458113] [a6989586621679458113] -> Type) -> Type) (DeleteBySym0 a6989586621679458113) l Source # | |
data DeleteBySym1 (l :: TyFun a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) (l :: TyFun a6989586621679458113 (TyFun [a6989586621679458113] [a6989586621679458113] -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) -> TyFun a6989586621679458113 (TyFun [a6989586621679458113] [a6989586621679458113] -> Type) -> *) (DeleteBySym1 a6989586621679458113) Source # | |
type Apply a6989586621679458113 (TyFun [a6989586621679458113] [a6989586621679458113] -> Type) (DeleteBySym1 a6989586621679458113 l1) l2 Source # | |
data DeleteBySym2 (l :: TyFun a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) (l :: a6989586621679458113) (l :: TyFun [a6989586621679458113] [a6989586621679458113]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) -> a6989586621679458113 -> TyFun [a6989586621679458113] [a6989586621679458113] -> *) (DeleteBySym2 a6989586621679458113) Source # | |
type Apply [a] [a] (DeleteBySym2 a l1 l2) l3 Source # | |
type DeleteBySym3 (t :: TyFun a6989586621679458113 (TyFun a6989586621679458113 Bool -> Type) -> Type) (t :: a6989586621679458113) (t :: [a6989586621679458113]) = DeleteBy t t t Source #
data DeleteFirstsBySym0 (l :: TyFun (TyFun a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) (TyFun [a6989586621679458112] (TyFun [a6989586621679458112] [a6989586621679458112] -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) (TyFun [a6989586621679458112] (TyFun [a6989586621679458112] [a6989586621679458112] -> Type) -> Type) -> *) (DeleteFirstsBySym0 a6989586621679458112) Source # | |
type Apply (TyFun a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) (TyFun [a6989586621679458112] (TyFun [a6989586621679458112] [a6989586621679458112] -> Type) -> Type) (DeleteFirstsBySym0 a6989586621679458112) l Source # | |
data DeleteFirstsBySym1 (l :: TyFun a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458112] (TyFun [a6989586621679458112] [a6989586621679458112] -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) -> TyFun [a6989586621679458112] (TyFun [a6989586621679458112] [a6989586621679458112] -> Type) -> *) (DeleteFirstsBySym1 a6989586621679458112) Source # | |
type Apply [a6989586621679458112] (TyFun [a6989586621679458112] [a6989586621679458112] -> Type) (DeleteFirstsBySym1 a6989586621679458112 l1) l2 Source # | |
data DeleteFirstsBySym2 (l :: TyFun a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) (l :: [a6989586621679458112]) (l :: TyFun [a6989586621679458112] [a6989586621679458112]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) -> [a6989586621679458112] -> TyFun [a6989586621679458112] [a6989586621679458112] -> *) (DeleteFirstsBySym2 a6989586621679458112) Source # | |
type Apply [a] [a] (DeleteFirstsBySym2 a l1 l2) l3 Source # | |
type DeleteFirstsBySym3 (t :: TyFun a6989586621679458112 (TyFun a6989586621679458112 Bool -> Type) -> Type) (t :: [a6989586621679458112]) (t :: [a6989586621679458112]) = DeleteFirstsBy t t t Source #
data IntersectBySym0 (l :: TyFun (TyFun a6989586621679458100 (TyFun a6989586621679458100 Bool -> Type) -> Type) (TyFun [a6989586621679458100] (TyFun [a6989586621679458100] [a6989586621679458100] -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458100 (TyFun a6989586621679458100 Bool -> Type) -> Type) (TyFun [a6989586621679458100] (TyFun [a6989586621679458100] [a6989586621679458100] -> Type) -> Type) -> *) (IntersectBySym0 a6989586621679458100) Source # | |
type Apply (TyFun a6989586621679458100 (TyFun a6989586621679458100 Bool -> Type) -> Type) (TyFun [a6989586621679458100] (TyFun [a6989586621679458100] [a6989586621679458100] -> Type) -> Type) (IntersectBySym0 a6989586621679458100) l Source # | |
data IntersectBySym1 (l :: TyFun a6989586621679458100 (TyFun a6989586621679458100 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458100] (TyFun [a6989586621679458100] [a6989586621679458100] -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458100 (TyFun a6989586621679458100 Bool -> Type) -> Type) -> TyFun [a6989586621679458100] (TyFun [a6989586621679458100] [a6989586621679458100] -> Type) -> *) (IntersectBySym1 a6989586621679458100) Source # | |
type Apply [a6989586621679458100] (TyFun [a6989586621679458100] [a6989586621679458100] -> Type) (IntersectBySym1 a6989586621679458100 l1) l2 Source # | |
data IntersectBySym2 (l :: TyFun a6989586621679458100 (TyFun a6989586621679458100 Bool -> Type) -> Type) (l :: [a6989586621679458100]) (l :: TyFun [a6989586621679458100] [a6989586621679458100]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458100 (TyFun a6989586621679458100 Bool -> Type) -> Type) -> [a6989586621679458100] -> TyFun [a6989586621679458100] [a6989586621679458100] -> *) (IntersectBySym2 a6989586621679458100) Source # | |
type Apply [a] [a] (IntersectBySym2 a l1 l2) l3 Source # | |
data SortBySym0 (l :: TyFun (TyFun a6989586621679458111 (TyFun a6989586621679458111 Ordering -> Type) -> Type) (TyFun [a6989586621679458111] [a6989586621679458111] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458111 (TyFun a6989586621679458111 Ordering -> Type) -> Type) (TyFun [a6989586621679458111] [a6989586621679458111] -> Type) -> *) (SortBySym0 a6989586621679458111) Source # | |
type Apply (TyFun a6989586621679458111 (TyFun a6989586621679458111 Ordering -> Type) -> Type) (TyFun [a6989586621679458111] [a6989586621679458111] -> Type) (SortBySym0 a6989586621679458111) l Source # | |
data SortBySym1 (l :: TyFun a6989586621679458111 (TyFun a6989586621679458111 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679458111] [a6989586621679458111]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458111 (TyFun a6989586621679458111 Ordering -> Type) -> Type) -> TyFun [a6989586621679458111] [a6989586621679458111] -> *) (SortBySym1 a6989586621679458111) Source # | |
type Apply [a] [a] (SortBySym1 a l1) l2 Source # | |
type SortBySym2 (t :: TyFun a6989586621679458111 (TyFun a6989586621679458111 Ordering -> Type) -> Type) (t :: [a6989586621679458111]) = SortBy t t Source #
data InsertBySym0 (l :: TyFun (TyFun a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) (TyFun a6989586621679458110 (TyFun [a6989586621679458110] [a6989586621679458110] -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) (TyFun a6989586621679458110 (TyFun [a6989586621679458110] [a6989586621679458110] -> Type) -> Type) -> *) (InsertBySym0 a6989586621679458110) Source # | |
type Apply (TyFun a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) (TyFun a6989586621679458110 (TyFun [a6989586621679458110] [a6989586621679458110] -> Type) -> Type) (InsertBySym0 a6989586621679458110) l Source # | |
data InsertBySym1 (l :: TyFun a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) (l :: TyFun a6989586621679458110 (TyFun [a6989586621679458110] [a6989586621679458110] -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) -> TyFun a6989586621679458110 (TyFun [a6989586621679458110] [a6989586621679458110] -> Type) -> *) (InsertBySym1 a6989586621679458110) Source # | |
type Apply a6989586621679458110 (TyFun [a6989586621679458110] [a6989586621679458110] -> Type) (InsertBySym1 a6989586621679458110 l1) l2 Source # | |
data InsertBySym2 (l :: TyFun a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) (l :: a6989586621679458110) (l :: TyFun [a6989586621679458110] [a6989586621679458110]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) -> a6989586621679458110 -> TyFun [a6989586621679458110] [a6989586621679458110] -> *) (InsertBySym2 a6989586621679458110) Source # | |
type Apply [a] [a] (InsertBySym2 a l1 l2) l3 Source # | |
type InsertBySym3 (t :: TyFun a6989586621679458110 (TyFun a6989586621679458110 Ordering -> Type) -> Type) (t :: a6989586621679458110) (t :: [a6989586621679458110]) = InsertBy t t t Source #
data MaximumBySym0 (l :: TyFun (TyFun a6989586621679458109 (TyFun a6989586621679458109 Ordering -> Type) -> Type) (TyFun [a6989586621679458109] a6989586621679458109 -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458109 (TyFun a6989586621679458109 Ordering -> Type) -> Type) (TyFun [a6989586621679458109] a6989586621679458109 -> Type) -> *) (MaximumBySym0 a6989586621679458109) Source # | |
type Apply (TyFun a6989586621679458109 (TyFun a6989586621679458109 Ordering -> Type) -> Type) (TyFun [a6989586621679458109] a6989586621679458109 -> Type) (MaximumBySym0 a6989586621679458109) l Source # | |
data MaximumBySym1 (l :: TyFun a6989586621679458109 (TyFun a6989586621679458109 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679458109] a6989586621679458109) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458109 (TyFun a6989586621679458109 Ordering -> Type) -> Type) -> TyFun [a6989586621679458109] a6989586621679458109 -> *) (MaximumBySym1 a6989586621679458109) Source # | |
type Apply [a] a (MaximumBySym1 a l1) l2 Source # | |
type MaximumBySym2 (t :: TyFun a6989586621679458109 (TyFun a6989586621679458109 Ordering -> Type) -> Type) (t :: [a6989586621679458109]) = MaximumBy t t Source #
data MinimumBySym0 (l :: TyFun (TyFun a6989586621679458108 (TyFun a6989586621679458108 Ordering -> Type) -> Type) (TyFun [a6989586621679458108] a6989586621679458108 -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458108 (TyFun a6989586621679458108 Ordering -> Type) -> Type) (TyFun [a6989586621679458108] a6989586621679458108 -> Type) -> *) (MinimumBySym0 a6989586621679458108) Source # | |
type Apply (TyFun a6989586621679458108 (TyFun a6989586621679458108 Ordering -> Type) -> Type) (TyFun [a6989586621679458108] a6989586621679458108 -> Type) (MinimumBySym0 a6989586621679458108) l Source # | |
data MinimumBySym1 (l :: TyFun a6989586621679458108 (TyFun a6989586621679458108 Ordering -> Type) -> Type) (l :: TyFun [a6989586621679458108] a6989586621679458108) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458108 (TyFun a6989586621679458108 Ordering -> Type) -> Type) -> TyFun [a6989586621679458108] a6989586621679458108 -> *) (MinimumBySym1 a6989586621679458108) Source # | |
type Apply [a] a (MinimumBySym1 a l1) l2 Source # | |
type MinimumBySym2 (t :: TyFun a6989586621679458108 (TyFun a6989586621679458108 Ordering -> Type) -> Type) (t :: [a6989586621679458108]) = MinimumBy t t Source #
data LengthSym0 (l :: TyFun [a6989586621679458079] Nat) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458079] Nat -> *) (LengthSym0 a6989586621679458079) Source # | |
type Apply [a] Nat (LengthSym0 a) l Source # | |
type LengthSym1 (t :: [a6989586621679458079]) = Length t Source #
data ProductSym0 (l :: TyFun [a6989586621679458080] a6989586621679458080) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458080] a6989586621679458080 -> *) (ProductSym0 a6989586621679458080) Source # | |
type Apply [a] a (ProductSym0 a) l Source # | |
type ProductSym1 (t :: [a6989586621679458080]) = Product t Source #
data ReplicateSym0 (l :: TyFun Nat (TyFun a6989586621679458078 [a6989586621679458078] -> Type)) Source #
data ReplicateSym1 (l :: Nat) (l :: TyFun a6989586621679458078 [a6989586621679458078]) Source #
SuppressUnusedWarnings (Nat -> TyFun a6989586621679458078 [a6989586621679458078] -> *) (ReplicateSym1 a6989586621679458078) Source # | |
type Apply a [a] (ReplicateSym1 a l1) l2 Source # | |
type ReplicateSym2 (t :: Nat) (t :: a6989586621679458078) = Replicate t t Source #
data TransposeSym0 (l :: TyFun [[a6989586621679458077]] [[a6989586621679458077]]) Source #
SuppressUnusedWarnings (TyFun [[a6989586621679458077]] [[a6989586621679458077]] -> *) (TransposeSym0 a6989586621679458077) Source # | |
type Apply [[a]] [[a]] (TransposeSym0 a) l Source # | |
type TransposeSym1 (t :: [[a6989586621679458077]]) = Transpose t Source #
data TakeSym0 (l :: TyFun Nat (TyFun [a6989586621679458094] [a6989586621679458094] -> Type)) Source #
data DropSym0 (l :: TyFun Nat (TyFun [a6989586621679458093] [a6989586621679458093] -> Type)) Source #
data SplitAtSym0 (l :: TyFun Nat (TyFun [a6989586621679458092] ([a6989586621679458092], [a6989586621679458092]) -> Type)) Source #
SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679458092] ([a6989586621679458092], [a6989586621679458092]) -> Type) -> *) (SplitAtSym0 a6989586621679458092) Source # | |
type Apply Nat (TyFun [a6989586621679458092] ([a6989586621679458092], [a6989586621679458092]) -> Type) (SplitAtSym0 a6989586621679458092) l Source # | |
data SplitAtSym1 (l :: Nat) (l :: TyFun [a6989586621679458092] ([a6989586621679458092], [a6989586621679458092])) Source #
SuppressUnusedWarnings (Nat -> TyFun [a6989586621679458092] ([a6989586621679458092], [a6989586621679458092]) -> *) (SplitAtSym1 a6989586621679458092) Source # | |
type Apply [a] ([a], [a]) (SplitAtSym1 a l1) l2 Source # | |
type SplitAtSym2 (t :: Nat) (t :: [a6989586621679458092]) = SplitAt t t Source #
data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679458099 Bool -> Type) (TyFun [a6989586621679458099] [a6989586621679458099] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458099 Bool -> Type) (TyFun [a6989586621679458099] [a6989586621679458099] -> Type) -> *) (TakeWhileSym0 a6989586621679458099) Source # | |
type Apply (TyFun a6989586621679458099 Bool -> Type) (TyFun [a6989586621679458099] [a6989586621679458099] -> Type) (TakeWhileSym0 a6989586621679458099) l Source # | |
data TakeWhileSym1 (l :: TyFun a6989586621679458099 Bool -> Type) (l :: TyFun [a6989586621679458099] [a6989586621679458099]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458099 Bool -> Type) -> TyFun [a6989586621679458099] [a6989586621679458099] -> *) (TakeWhileSym1 a6989586621679458099) Source # | |
type Apply [a] [a] (TakeWhileSym1 a l1) l2 Source # | |
type TakeWhileSym2 (t :: TyFun a6989586621679458099 Bool -> Type) (t :: [a6989586621679458099]) = TakeWhile t t Source #
data DropWhileSym0 (l :: TyFun (TyFun a6989586621679458098 Bool -> Type) (TyFun [a6989586621679458098] [a6989586621679458098] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458098 Bool -> Type) (TyFun [a6989586621679458098] [a6989586621679458098] -> Type) -> *) (DropWhileSym0 a6989586621679458098) Source # | |
type Apply (TyFun a6989586621679458098 Bool -> Type) (TyFun [a6989586621679458098] [a6989586621679458098] -> Type) (DropWhileSym0 a6989586621679458098) l Source # | |
data DropWhileSym1 (l :: TyFun a6989586621679458098 Bool -> Type) (l :: TyFun [a6989586621679458098] [a6989586621679458098]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458098 Bool -> Type) -> TyFun [a6989586621679458098] [a6989586621679458098] -> *) (DropWhileSym1 a6989586621679458098) Source # | |
type Apply [a] [a] (DropWhileSym1 a l1) l2 Source # | |
type DropWhileSym2 (t :: TyFun a6989586621679458098 Bool -> Type) (t :: [a6989586621679458098]) = DropWhile t t Source #
data DropWhileEndSym0 (l :: TyFun (TyFun a6989586621679458097 Bool -> Type) (TyFun [a6989586621679458097] [a6989586621679458097] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458097 Bool -> Type) (TyFun [a6989586621679458097] [a6989586621679458097] -> Type) -> *) (DropWhileEndSym0 a6989586621679458097) Source # | |
type Apply (TyFun a6989586621679458097 Bool -> Type) (TyFun [a6989586621679458097] [a6989586621679458097] -> Type) (DropWhileEndSym0 a6989586621679458097) l Source # | |
data DropWhileEndSym1 (l :: TyFun a6989586621679458097 Bool -> Type) (l :: TyFun [a6989586621679458097] [a6989586621679458097]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458097 Bool -> Type) -> TyFun [a6989586621679458097] [a6989586621679458097] -> *) (DropWhileEndSym1 a6989586621679458097) Source # | |
type Apply [a] [a] (DropWhileEndSym1 a l1) l2 Source # | |
type DropWhileEndSym2 (t :: TyFun a6989586621679458097 Bool -> Type) (t :: [a6989586621679458097]) = DropWhileEnd t t Source #
data SpanSym0 (l :: TyFun (TyFun a6989586621679458096 Bool -> Type) (TyFun [a6989586621679458096] ([a6989586621679458096], [a6989586621679458096]) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458096 Bool -> Type) (TyFun [a6989586621679458096] ([a6989586621679458096], [a6989586621679458096]) -> Type) -> *) (SpanSym0 a6989586621679458096) Source # | |
type Apply (TyFun a6989586621679458096 Bool -> Type) (TyFun [a6989586621679458096] ([a6989586621679458096], [a6989586621679458096]) -> Type) (SpanSym0 a6989586621679458096) l Source # | |
data SpanSym1 (l :: TyFun a6989586621679458096 Bool -> Type) (l :: TyFun [a6989586621679458096] ([a6989586621679458096], [a6989586621679458096])) Source #
type SpanSym2 (t :: TyFun a6989586621679458096 Bool -> Type) (t :: [a6989586621679458096]) = Span t t Source #
data BreakSym0 (l :: TyFun (TyFun a6989586621679458095 Bool -> Type) (TyFun [a6989586621679458095] ([a6989586621679458095], [a6989586621679458095]) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458095 Bool -> Type) (TyFun [a6989586621679458095] ([a6989586621679458095], [a6989586621679458095]) -> Type) -> *) (BreakSym0 a6989586621679458095) Source # | |
type Apply (TyFun a6989586621679458095 Bool -> Type) (TyFun [a6989586621679458095] ([a6989586621679458095], [a6989586621679458095]) -> Type) (BreakSym0 a6989586621679458095) l Source # | |
data BreakSym1 (l :: TyFun a6989586621679458095 Bool -> Type) (l :: TyFun [a6989586621679458095] ([a6989586621679458095], [a6989586621679458095])) Source #
type BreakSym2 (t :: TyFun a6989586621679458095 Bool -> Type) (t :: [a6989586621679458095]) = Break t t Source #
data StripPrefixSym0 (l :: TyFun [a6989586621679876709] (TyFun [a6989586621679876709] (Maybe [a6989586621679876709]) -> Type)) Source #
SuppressUnusedWarnings (TyFun [a6989586621679876709] (TyFun [a6989586621679876709] (Maybe [a6989586621679876709]) -> Type) -> *) (StripPrefixSym0 a6989586621679876709) Source # | |
type Apply [a6989586621679876709] (TyFun [a6989586621679876709] (Maybe [a6989586621679876709]) -> Type) (StripPrefixSym0 a6989586621679876709) l Source # | |
data StripPrefixSym1 (l :: [a6989586621679876709]) (l :: TyFun [a6989586621679876709] (Maybe [a6989586621679876709])) Source #
SuppressUnusedWarnings ([a6989586621679876709] -> TyFun [a6989586621679876709] (Maybe [a6989586621679876709]) -> *) (StripPrefixSym1 a6989586621679876709) Source # | |
type Apply [a] (Maybe [a]) (StripPrefixSym1 a l1) l2 Source # | |
type StripPrefixSym2 (t :: [a6989586621679876709]) (t :: [a6989586621679876709]) = StripPrefix t t Source #
data MaximumSym0 (l :: TyFun [a6989586621679458090] a6989586621679458090) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458090] a6989586621679458090 -> *) (MaximumSym0 a6989586621679458090) Source # | |
type Apply [a] a (MaximumSym0 a) l Source # | |
type MaximumSym1 (t :: [a6989586621679458090]) = Maximum t Source #
data MinimumSym0 (l :: TyFun [a6989586621679458089] a6989586621679458089) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458089] a6989586621679458089 -> *) (MinimumSym0 a6989586621679458089) Source # | |
type Apply [a] a (MinimumSym0 a) l Source # | |
type MinimumSym1 (t :: [a6989586621679458089]) = Minimum t Source #
data GroupBySym0 (l :: TyFun (TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (TyFun [a6989586621679458086] [[a6989586621679458086]] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (TyFun [a6989586621679458086] [[a6989586621679458086]] -> Type) -> *) (GroupBySym0 a6989586621679458086) Source # | |
type Apply (TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (TyFun [a6989586621679458086] [[a6989586621679458086]] -> Type) (GroupBySym0 a6989586621679458086) l Source # | |
data GroupBySym1 (l :: TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458086] [[a6989586621679458086]]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) -> TyFun [a6989586621679458086] [[a6989586621679458086]] -> *) (GroupBySym1 a6989586621679458086) Source # | |
type Apply [a] [[a]] (GroupBySym1 a l1) l2 Source # | |
type GroupBySym2 (t :: TyFun a6989586621679458086 (TyFun a6989586621679458086 Bool -> Type) -> Type) (t :: [a6989586621679458086]) = GroupBy t t Source #
data LookupSym0 (l :: TyFun a6989586621679458084 (TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085) -> Type)) Source #
SuppressUnusedWarnings (TyFun a6989586621679458084 (TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085) -> Type) -> *) (LookupSym0 a6989586621679458084 b6989586621679458085) Source # | |
type Apply a6989586621679458084 (TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085) -> Type) (LookupSym0 a6989586621679458084 b6989586621679458085) l Source # | |
data LookupSym1 (l :: a6989586621679458084) (l :: TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085)) Source #
SuppressUnusedWarnings (a6989586621679458084 -> TyFun [(a6989586621679458084, b6989586621679458085)] (Maybe b6989586621679458085) -> *) (LookupSym1 a6989586621679458084 b6989586621679458085) Source # | |
type Apply [(a, b)] (Maybe b) (LookupSym1 a b l1) l2 Source # | |
type LookupSym2 (t :: a6989586621679458084) (t :: [(a6989586621679458084, b6989586621679458085)]) = Lookup t t Source #
data FindSym0 (l :: TyFun (TyFun a6989586621679458106 Bool -> Type) (TyFun [a6989586621679458106] (Maybe a6989586621679458106) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458106 Bool -> Type) (TyFun [a6989586621679458106] (Maybe a6989586621679458106) -> Type) -> *) (FindSym0 a6989586621679458106) Source # | |
type Apply (TyFun a6989586621679458106 Bool -> Type) (TyFun [a6989586621679458106] (Maybe a6989586621679458106) -> Type) (FindSym0 a6989586621679458106) l Source # | |
data FindSym1 (l :: TyFun a6989586621679458106 Bool -> Type) (l :: TyFun [a6989586621679458106] (Maybe a6989586621679458106)) Source #
type FindSym2 (t :: TyFun a6989586621679458106 Bool -> Type) (t :: [a6989586621679458106]) = Find t t Source #
data FilterSym0 (l :: TyFun (TyFun a6989586621679458107 Bool -> Type) (TyFun [a6989586621679458107] [a6989586621679458107] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458107 Bool -> Type) (TyFun [a6989586621679458107] [a6989586621679458107] -> Type) -> *) (FilterSym0 a6989586621679458107) Source # | |
type Apply (TyFun a6989586621679458107 Bool -> Type) (TyFun [a6989586621679458107] [a6989586621679458107] -> Type) (FilterSym0 a6989586621679458107) l Source # | |
data FilterSym1 (l :: TyFun a6989586621679458107 Bool -> Type) (l :: TyFun [a6989586621679458107] [a6989586621679458107]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458107 Bool -> Type) -> TyFun [a6989586621679458107] [a6989586621679458107] -> *) (FilterSym1 a6989586621679458107) Source # | |
type Apply [a] [a] (FilterSym1 a l1) l2 Source # | |
type FilterSym2 (t :: TyFun a6989586621679458107 Bool -> Type) (t :: [a6989586621679458107]) = Filter t t Source #
data PartitionSym0 (l :: TyFun (TyFun a6989586621679458083 Bool -> Type) (TyFun [a6989586621679458083] ([a6989586621679458083], [a6989586621679458083]) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458083 Bool -> Type) (TyFun [a6989586621679458083] ([a6989586621679458083], [a6989586621679458083]) -> Type) -> *) (PartitionSym0 a6989586621679458083) Source # | |
type Apply (TyFun a6989586621679458083 Bool -> Type) (TyFun [a6989586621679458083] ([a6989586621679458083], [a6989586621679458083]) -> Type) (PartitionSym0 a6989586621679458083) l Source # | |
data PartitionSym1 (l :: TyFun a6989586621679458083 Bool -> Type) (l :: TyFun [a6989586621679458083] ([a6989586621679458083], [a6989586621679458083])) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458083 Bool -> Type) -> TyFun [a6989586621679458083] ([a6989586621679458083], [a6989586621679458083]) -> *) (PartitionSym1 a6989586621679458083) Source # | |
type Apply [a] ([a], [a]) (PartitionSym1 a l1) l2 Source # | |
type PartitionSym2 (t :: TyFun a6989586621679458083 Bool -> Type) (t :: [a6989586621679458083]) = Partition t t Source #
data ElemIndexSym0 (l :: TyFun a6989586621679458105 (TyFun [a6989586621679458105] (Maybe Nat) -> Type)) Source #
data ElemIndexSym1 (l :: a6989586621679458105) (l :: TyFun [a6989586621679458105] (Maybe Nat)) Source #
SuppressUnusedWarnings (a6989586621679458105 -> TyFun [a6989586621679458105] (Maybe Nat) -> *) (ElemIndexSym1 a6989586621679458105) Source # | |
type Apply [a] (Maybe Nat) (ElemIndexSym1 a l1) l2 Source # | |
type ElemIndexSym2 (t :: a6989586621679458105) (t :: [a6989586621679458105]) = ElemIndex t t Source #
data ElemIndicesSym0 (l :: TyFun a6989586621679458104 (TyFun [a6989586621679458104] [Nat] -> Type)) Source #
data ElemIndicesSym1 (l :: a6989586621679458104) (l :: TyFun [a6989586621679458104] [Nat]) Source #
SuppressUnusedWarnings (a6989586621679458104 -> TyFun [a6989586621679458104] [Nat] -> *) (ElemIndicesSym1 a6989586621679458104) Source # | |
type Apply [a] [Nat] (ElemIndicesSym1 a l1) l2 Source # | |
type ElemIndicesSym2 (t :: a6989586621679458104) (t :: [a6989586621679458104]) = ElemIndices t t Source #
data FindIndexSym0 (l :: TyFun (TyFun a6989586621679458103 Bool -> Type) (TyFun [a6989586621679458103] (Maybe Nat) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458103 Bool -> Type) (TyFun [a6989586621679458103] (Maybe Nat) -> Type) -> *) (FindIndexSym0 a6989586621679458103) Source # | |
type Apply (TyFun a6989586621679458103 Bool -> Type) (TyFun [a6989586621679458103] (Maybe Nat) -> Type) (FindIndexSym0 a6989586621679458103) l Source # | |
data FindIndexSym1 (l :: TyFun a6989586621679458103 Bool -> Type) (l :: TyFun [a6989586621679458103] (Maybe Nat)) Source #
type FindIndexSym2 (t :: TyFun a6989586621679458103 Bool -> Type) (t :: [a6989586621679458103]) = FindIndex t t Source #
data FindIndicesSym0 (l :: TyFun (TyFun a6989586621679458102 Bool -> Type) (TyFun [a6989586621679458102] [Nat] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458102 Bool -> Type) (TyFun [a6989586621679458102] [Nat] -> Type) -> *) (FindIndicesSym0 a6989586621679458102) Source # | |
type Apply (TyFun a6989586621679458102 Bool -> Type) (TyFun [a6989586621679458102] [Nat] -> Type) (FindIndicesSym0 a6989586621679458102) l Source # | |
data FindIndicesSym1 (l :: TyFun a6989586621679458102 Bool -> Type) (l :: TyFun [a6989586621679458102] [Nat]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458102 Bool -> Type) -> TyFun [a6989586621679458102] [Nat] -> *) (FindIndicesSym1 a6989586621679458102) Source # | |
type Apply [a] [Nat] (FindIndicesSym1 a l1) l2 Source # | |
type FindIndicesSym2 (t :: TyFun a6989586621679458102 Bool -> Type) (t :: [a6989586621679458102]) = FindIndices t t Source #
data Zip4Sym0 (l :: TyFun [a6989586621679876705] (TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun [a6989586621679876705] (TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) -> Type) -> *) (Zip4Sym0 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) Source # | |
type Apply [a6989586621679876705] (TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) -> Type) (Zip4Sym0 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) l Source # | |
data Zip4Sym1 (l :: [a6989586621679876705]) (l :: TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876705] -> TyFun [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) -> *) (Zip4Sym1 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) Source # | |
type Apply [b6989586621679876706] (TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> Type) (Zip4Sym1 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708 l1) l2 Source # | |
data Zip4Sym2 (l :: [a6989586621679876705]) (l :: [b6989586621679876706]) (l :: TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876705] -> [b6989586621679876706] -> TyFun [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) -> *) (Zip4Sym2 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) Source # | |
type Apply [c6989586621679876707] (TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> Type) (Zip4Sym2 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708 l1 l2) l3 Source # | |
data Zip4Sym3 (l :: [a6989586621679876705]) (l :: [b6989586621679876706]) (l :: [c6989586621679876707]) (l :: TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)]) Source #
SuppressUnusedWarnings ([a6989586621679876705] -> [b6989586621679876706] -> [c6989586621679876707] -> TyFun [d6989586621679876708] [(a6989586621679876705, b6989586621679876706, c6989586621679876707, d6989586621679876708)] -> *) (Zip4Sym3 a6989586621679876705 b6989586621679876706 c6989586621679876707 d6989586621679876708) Source # | |
type Apply [d] [(a, b, c, d)] (Zip4Sym3 a b c d l1 l2 l3) l4 Source # | |
type Zip4Sym4 (t :: [a6989586621679876705]) (t :: [b6989586621679876706]) (t :: [c6989586621679876707]) (t :: [d6989586621679876708]) = Zip4 t t t t Source #
data Zip5Sym0 (l :: TyFun [a6989586621679876700] (TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun [a6989586621679876700] (TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip5Sym0 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # | |
type Apply [a6989586621679876700] (TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) -> Type) (Zip5Sym0 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) l Source # | |
data Zip5Sym1 (l :: [a6989586621679876700]) (l :: TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876700] -> TyFun [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) -> *) (Zip5Sym1 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # | |
type Apply [b6989586621679876701] (TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> Type) (Zip5Sym1 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l1) l2 Source # | |
data Zip5Sym2 (l :: [a6989586621679876700]) (l :: [b6989586621679876701]) (l :: TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876700] -> [b6989586621679876701] -> TyFun [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) -> *) (Zip5Sym2 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # | |
type Apply [c6989586621679876702] (TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> Type) (Zip5Sym2 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l1 l2) l3 Source # | |
data Zip5Sym3 (l :: [a6989586621679876700]) (l :: [b6989586621679876701]) (l :: [c6989586621679876702]) (l :: TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876700] -> [b6989586621679876701] -> [c6989586621679876702] -> TyFun [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) -> *) (Zip5Sym3 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # | |
type Apply [d6989586621679876703] (TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> Type) (Zip5Sym3 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704 l1 l2 l3) l4 Source # | |
data Zip5Sym4 (l :: [a6989586621679876700]) (l :: [b6989586621679876701]) (l :: [c6989586621679876702]) (l :: [d6989586621679876703]) (l :: TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)]) Source #
SuppressUnusedWarnings ([a6989586621679876700] -> [b6989586621679876701] -> [c6989586621679876702] -> [d6989586621679876703] -> TyFun [e6989586621679876704] [(a6989586621679876700, b6989586621679876701, c6989586621679876702, d6989586621679876703, e6989586621679876704)] -> *) (Zip5Sym4 a6989586621679876700 b6989586621679876701 c6989586621679876702 d6989586621679876703 e6989586621679876704) Source # | |
type Apply [e] [(a, b, c, d, e)] (Zip5Sym4 a b c d e l1 l2 l3 l4) l5 Source # | |
type Zip5Sym5 (t :: [a6989586621679876700]) (t :: [b6989586621679876701]) (t :: [c6989586621679876702]) (t :: [d6989586621679876703]) (t :: [e6989586621679876704]) = Zip5 t t t t t Source #
data Zip6Sym0 (l :: TyFun [a6989586621679876694] (TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun [a6989586621679876694] (TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym0 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # | |
type Apply [a6989586621679876694] (TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip6Sym0 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) l Source # | |
data Zip6Sym1 (l :: [a6989586621679876694]) (l :: TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876694] -> TyFun [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym1 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # | |
type Apply [b6989586621679876695] (TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> Type) (Zip6Sym1 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1) l2 Source # | |
data Zip6Sym2 (l :: [a6989586621679876694]) (l :: [b6989586621679876695]) (l :: TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876694] -> [b6989586621679876695] -> TyFun [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) -> *) (Zip6Sym2 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # | |
type Apply [c6989586621679876696] (TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> Type) (Zip6Sym2 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2) l3 Source # | |
data Zip6Sym3 (l :: [a6989586621679876694]) (l :: [b6989586621679876695]) (l :: [c6989586621679876696]) (l :: TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876694] -> [b6989586621679876695] -> [c6989586621679876696] -> TyFun [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) -> *) (Zip6Sym3 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # | |
type Apply [d6989586621679876697] (TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> Type) (Zip6Sym3 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2 l3) l4 Source # | |
data Zip6Sym4 (l :: [a6989586621679876694]) (l :: [b6989586621679876695]) (l :: [c6989586621679876696]) (l :: [d6989586621679876697]) (l :: TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876694] -> [b6989586621679876695] -> [c6989586621679876696] -> [d6989586621679876697] -> TyFun [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) -> *) (Zip6Sym4 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # | |
type Apply [e6989586621679876698] (TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> Type) (Zip6Sym4 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699 l1 l2 l3 l4) l5 Source # | |
data Zip6Sym5 (l :: [a6989586621679876694]) (l :: [b6989586621679876695]) (l :: [c6989586621679876696]) (l :: [d6989586621679876697]) (l :: [e6989586621679876698]) (l :: TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)]) Source #
SuppressUnusedWarnings ([a6989586621679876694] -> [b6989586621679876695] -> [c6989586621679876696] -> [d6989586621679876697] -> [e6989586621679876698] -> TyFun [f6989586621679876699] [(a6989586621679876694, b6989586621679876695, c6989586621679876696, d6989586621679876697, e6989586621679876698, f6989586621679876699)] -> *) (Zip6Sym5 a6989586621679876694 b6989586621679876695 c6989586621679876696 d6989586621679876697 e6989586621679876698 f6989586621679876699) Source # | |
type Apply [f] [(a, b, c, d, e, f)] (Zip6Sym5 a b c d e f l1 l2 l3 l4 l5) l6 Source # | |
type Zip6Sym6 (t :: [a6989586621679876694]) (t :: [b6989586621679876695]) (t :: [c6989586621679876696]) (t :: [d6989586621679876697]) (t :: [e6989586621679876698]) (t :: [f6989586621679876699]) = Zip6 t t t t t t Source #
data Zip7Sym0 (l :: TyFun [a6989586621679876687] (TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun [a6989586621679876687] (TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym0 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # | |
type Apply [a6989586621679876687] (TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym0 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) l Source # | |
data Zip7Sym1 (l :: [a6989586621679876687]) (l :: TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876687] -> TyFun [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym1 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # | |
type Apply [b6989586621679876688] (TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym1 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1) l2 Source # | |
data Zip7Sym2 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> TyFun [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym2 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # | |
type Apply [c6989586621679876689] (TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> Type) (Zip7Sym2 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2) l3 Source # | |
data Zip7Sym3 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: [c6989586621679876689]) (l :: TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> [c6989586621679876689] -> TyFun [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) -> *) (Zip7Sym3 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # | |
type Apply [d6989586621679876690] (TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> Type) (Zip7Sym3 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3) l4 Source # | |
data Zip7Sym4 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: [c6989586621679876689]) (l :: [d6989586621679876690]) (l :: TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> [c6989586621679876689] -> [d6989586621679876690] -> TyFun [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) -> *) (Zip7Sym4 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # | |
type Apply [e6989586621679876691] (TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> Type) (Zip7Sym4 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3 l4) l5 Source # | |
data Zip7Sym5 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: [c6989586621679876689]) (l :: [d6989586621679876690]) (l :: [e6989586621679876691]) (l :: TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type)) Source #
SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> [c6989586621679876689] -> [d6989586621679876690] -> [e6989586621679876691] -> TyFun [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) -> *) (Zip7Sym5 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # | |
type Apply [f6989586621679876692] (TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> Type) (Zip7Sym5 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693 l1 l2 l3 l4 l5) l6 Source # | |
data Zip7Sym6 (l :: [a6989586621679876687]) (l :: [b6989586621679876688]) (l :: [c6989586621679876689]) (l :: [d6989586621679876690]) (l :: [e6989586621679876691]) (l :: [f6989586621679876692]) (l :: TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)]) Source #
SuppressUnusedWarnings ([a6989586621679876687] -> [b6989586621679876688] -> [c6989586621679876689] -> [d6989586621679876690] -> [e6989586621679876691] -> [f6989586621679876692] -> TyFun [g6989586621679876693] [(a6989586621679876687, b6989586621679876688, c6989586621679876689, d6989586621679876690, e6989586621679876691, f6989586621679876692, g6989586621679876693)] -> *) (Zip7Sym6 a6989586621679876687 b6989586621679876688 c6989586621679876689 d6989586621679876690 e6989586621679876691 f6989586621679876692 g6989586621679876693) Source # | |
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 Source # | |
type Zip7Sym7 (t :: [a6989586621679876687]) (t :: [b6989586621679876688]) (t :: [c6989586621679876689]) (t :: [d6989586621679876690]) (t :: [e6989586621679876691]) (t :: [f6989586621679876692]) (t :: [g6989586621679876693]) = Zip7 t t t t t t t Source #
data ZipWith4Sym0 (l :: TyFun (TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith4Sym0 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # | |
type Apply (TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) -> Type) (ZipWith4Sym0 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) l Source # | |
data ZipWith4Sym1 (l :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) -> *) (ZipWith4Sym1 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # | |
type Apply [a6989586621679876682] (TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> Type) (ZipWith4Sym1 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l1) l2 Source # | |
data ZipWith4Sym2 (l :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876682]) (l :: TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876682] -> TyFun [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) -> *) (ZipWith4Sym2 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # | |
type Apply [b6989586621679876683] (TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> Type) (ZipWith4Sym2 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l1 l2) l3 Source # | |
data ZipWith4Sym3 (l :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876682]) (l :: [b6989586621679876683]) (l :: TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876682] -> [b6989586621679876683] -> TyFun [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) -> *) (ZipWith4Sym3 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # | |
type Apply [c6989586621679876684] (TyFun [d6989586621679876685] [e6989586621679876686] -> Type) (ZipWith4Sym3 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686 l1 l2 l3) l4 Source # | |
data ZipWith4Sym4 (l :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876682]) (l :: [b6989586621679876683]) (l :: [c6989586621679876684]) (l :: TyFun [d6989586621679876685] [e6989586621679876686]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876682] -> [b6989586621679876683] -> [c6989586621679876684] -> TyFun [d6989586621679876685] [e6989586621679876686] -> *) (ZipWith4Sym4 a6989586621679876682 b6989586621679876683 c6989586621679876684 d6989586621679876685 e6989586621679876686) Source # | |
type Apply [d] [e] (ZipWith4Sym4 a b c d e l1 l2 l3 l4) l5 Source # | |
type ZipWith4Sym5 (t :: TyFun a6989586621679876682 (TyFun b6989586621679876683 (TyFun c6989586621679876684 (TyFun d6989586621679876685 e6989586621679876686 -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679876682]) (t :: [b6989586621679876683]) (t :: [c6989586621679876684]) (t :: [d6989586621679876685]) = ZipWith4 t t t t t Source #
data ZipWith5Sym0 (l :: TyFun (TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym0 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # | |
type Apply (TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym0 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) l Source # | |
data ZipWith5Sym1 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym1 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # | |
type Apply [a6989586621679876676] (TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym1 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1) l2 Source # | |
data ZipWith5Sym2 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876676]) (l :: TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876676] -> TyFun [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) -> *) (ZipWith5Sym2 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # | |
type Apply [b6989586621679876677] (TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> Type) (ZipWith5Sym2 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2) l3 Source # | |
data ZipWith5Sym3 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876676]) (l :: [b6989586621679876677]) (l :: TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876676] -> [b6989586621679876677] -> TyFun [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) -> *) (ZipWith5Sym3 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # | |
type Apply [c6989586621679876678] (TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> Type) (ZipWith5Sym3 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2 l3) l4 Source # | |
data ZipWith5Sym4 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876676]) (l :: [b6989586621679876677]) (l :: [c6989586621679876678]) (l :: TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876676] -> [b6989586621679876677] -> [c6989586621679876678] -> TyFun [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) -> *) (ZipWith5Sym4 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # | |
type Apply [d6989586621679876679] (TyFun [e6989586621679876680] [f6989586621679876681] -> Type) (ZipWith5Sym4 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681 l1 l2 l3 l4) l5 Source # | |
data ZipWith5Sym5 (l :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876676]) (l :: [b6989586621679876677]) (l :: [c6989586621679876678]) (l :: [d6989586621679876679]) (l :: TyFun [e6989586621679876680] [f6989586621679876681]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876676] -> [b6989586621679876677] -> [c6989586621679876678] -> [d6989586621679876679] -> TyFun [e6989586621679876680] [f6989586621679876681] -> *) (ZipWith5Sym5 a6989586621679876676 b6989586621679876677 c6989586621679876678 d6989586621679876679 e6989586621679876680 f6989586621679876681) Source # | |
type Apply [e] [f] (ZipWith5Sym5 a b c d e f l1 l2 l3 l4 l5) l6 Source # | |
type ZipWith5Sym6 (t :: TyFun a6989586621679876676 (TyFun b6989586621679876677 (TyFun c6989586621679876678 (TyFun d6989586621679876679 (TyFun e6989586621679876680 f6989586621679876681 -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679876676]) (t :: [b6989586621679876677]) (t :: [c6989586621679876678]) (t :: [d6989586621679876679]) (t :: [e6989586621679876680]) = ZipWith5 t t t t t t Source #
data ZipWith6Sym0 (l :: TyFun (TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym0 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # | |
type Apply (TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym0 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) l Source # | |
data ZipWith6Sym1 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym1 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # | |
type Apply [a6989586621679876669] (TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym1 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1) l2 Source # | |
data ZipWith6Sym2 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> TyFun [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym2 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # | |
type Apply [b6989586621679876670] (TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym2 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2) l3 Source # | |
data ZipWith6Sym3 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: [b6989586621679876670]) (l :: TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> [b6989586621679876670] -> TyFun [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) -> *) (ZipWith6Sym3 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # | |
type Apply [c6989586621679876671] (TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> Type) (ZipWith6Sym3 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3) l4 Source # | |
data ZipWith6Sym4 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: [b6989586621679876670]) (l :: [c6989586621679876671]) (l :: TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> [b6989586621679876670] -> [c6989586621679876671] -> TyFun [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) -> *) (ZipWith6Sym4 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # | |
type Apply [d6989586621679876672] (TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> Type) (ZipWith6Sym4 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3 l4) l5 Source # | |
data ZipWith6Sym5 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: [b6989586621679876670]) (l :: [c6989586621679876671]) (l :: [d6989586621679876672]) (l :: TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> [b6989586621679876670] -> [c6989586621679876671] -> [d6989586621679876672] -> TyFun [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) -> *) (ZipWith6Sym5 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # | |
type Apply [e6989586621679876673] (TyFun [f6989586621679876674] [g6989586621679876675] -> Type) (ZipWith6Sym5 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675 l1 l2 l3 l4 l5) l6 Source # | |
data ZipWith6Sym6 (l :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876669]) (l :: [b6989586621679876670]) (l :: [c6989586621679876671]) (l :: [d6989586621679876672]) (l :: [e6989586621679876673]) (l :: TyFun [f6989586621679876674] [g6989586621679876675]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876669] -> [b6989586621679876670] -> [c6989586621679876671] -> [d6989586621679876672] -> [e6989586621679876673] -> TyFun [f6989586621679876674] [g6989586621679876675] -> *) (ZipWith6Sym6 a6989586621679876669 b6989586621679876670 c6989586621679876671 d6989586621679876672 e6989586621679876673 f6989586621679876674 g6989586621679876675) Source # | |
type Apply [f] [g] (ZipWith6Sym6 a b c d e f g l1 l2 l3 l4 l5 l6) l7 Source # | |
type ZipWith6Sym7 (t :: TyFun a6989586621679876669 (TyFun b6989586621679876670 (TyFun c6989586621679876671 (TyFun d6989586621679876672 (TyFun e6989586621679876673 (TyFun f6989586621679876674 g6989586621679876675 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679876669]) (t :: [b6989586621679876670]) (t :: [c6989586621679876671]) (t :: [d6989586621679876672]) (t :: [e6989586621679876673]) (t :: [f6989586621679876674]) = ZipWith6 t t t t t t t Source #
data ZipWith7Sym0 (l :: TyFun (TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym0 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # | |
type Apply (TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym0 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) l Source # | |
data ZipWith7Sym1 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym1 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # | |
type Apply [a6989586621679876661] (TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym1 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1) l2 Source # | |
data ZipWith7Sym2 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> TyFun [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym2 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # | |
type Apply [b6989586621679876662] (TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym2 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2) l3 Source # | |
data ZipWith7Sym3 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> TyFun [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym3 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # | |
type Apply [c6989586621679876663] (TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym3 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3) l4 Source # | |
data ZipWith7Sym4 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: [c6989586621679876663]) (l :: TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> [c6989586621679876663] -> TyFun [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) -> *) (ZipWith7Sym4 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # | |
type Apply [d6989586621679876664] (TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> Type) (ZipWith7Sym4 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4) l5 Source # | |
data ZipWith7Sym5 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: [c6989586621679876663]) (l :: [d6989586621679876664]) (l :: TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> [c6989586621679876663] -> [d6989586621679876664] -> TyFun [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) -> *) (ZipWith7Sym5 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # | |
type Apply [e6989586621679876665] (TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> Type) (ZipWith7Sym5 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4 l5) l6 Source # | |
data ZipWith7Sym6 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: [c6989586621679876663]) (l :: [d6989586621679876664]) (l :: [e6989586621679876665]) (l :: TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> [c6989586621679876663] -> [d6989586621679876664] -> [e6989586621679876665] -> TyFun [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) -> *) (ZipWith7Sym6 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # | |
type Apply [f6989586621679876666] (TyFun [g6989586621679876667] [h6989586621679876668] -> Type) (ZipWith7Sym6 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668 l1 l2 l3 l4 l5 l6) l7 Source # | |
data ZipWith7Sym7 (l :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (l :: [a6989586621679876661]) (l :: [b6989586621679876662]) (l :: [c6989586621679876663]) (l :: [d6989586621679876664]) (l :: [e6989586621679876665]) (l :: [f6989586621679876666]) (l :: TyFun [g6989586621679876667] [h6989586621679876668]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679876661] -> [b6989586621679876662] -> [c6989586621679876663] -> [d6989586621679876664] -> [e6989586621679876665] -> [f6989586621679876666] -> TyFun [g6989586621679876667] [h6989586621679876668] -> *) (ZipWith7Sym7 a6989586621679876661 b6989586621679876662 c6989586621679876663 d6989586621679876664 e6989586621679876665 f6989586621679876666 g6989586621679876667 h6989586621679876668) Source # | |
type Apply [g] [h] (ZipWith7Sym7 a b c d e f g h l1 l2 l3 l4 l5 l6 l7) l8 Source # | |
type ZipWith7Sym8 (t :: TyFun a6989586621679876661 (TyFun b6989586621679876662 (TyFun c6989586621679876663 (TyFun d6989586621679876664 (TyFun e6989586621679876665 (TyFun f6989586621679876666 (TyFun g6989586621679876667 h6989586621679876668 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (t :: [a6989586621679876661]) (t :: [b6989586621679876662]) (t :: [c6989586621679876663]) (t :: [d6989586621679876664]) (t :: [e6989586621679876665]) (t :: [f6989586621679876666]) (t :: [g6989586621679876667]) = ZipWith7 t t t t t t t t Source #
data NubBySym0 (l :: TyFun (TyFun a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (TyFun [a6989586621679458074] [a6989586621679458074] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (TyFun [a6989586621679458074] [a6989586621679458074] -> Type) -> *) (NubBySym0 a6989586621679458074) Source # | |
type Apply (TyFun a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (TyFun [a6989586621679458074] [a6989586621679458074] -> Type) (NubBySym0 a6989586621679458074) l Source # | |
data NubBySym1 (l :: TyFun a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458074] [a6989586621679458074]) Source #
type NubBySym2 (t :: TyFun a6989586621679458074 (TyFun a6989586621679458074 Bool -> Type) -> Type) (t :: [a6989586621679458074]) = NubBy t t Source #
data UnionSym0 (l :: TyFun [a6989586621679458071] (TyFun [a6989586621679458071] [a6989586621679458071] -> Type)) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458071] (TyFun [a6989586621679458071] [a6989586621679458071] -> Type) -> *) (UnionSym0 a6989586621679458071) Source # | |
type Apply [a6989586621679458071] (TyFun [a6989586621679458071] [a6989586621679458071] -> Type) (UnionSym0 a6989586621679458071) l Source # | |
data UnionSym1 (l :: [a6989586621679458071]) (l :: TyFun [a6989586621679458071] [a6989586621679458071]) Source #
data UnionBySym0 (l :: TyFun (TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (TyFun [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (TyFun [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type) -> Type) -> *) (UnionBySym0 a6989586621679458072) Source # | |
type Apply (TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (TyFun [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type) -> Type) (UnionBySym0 a6989586621679458072) l Source # | |
data UnionBySym1 (l :: TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (l :: TyFun [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) -> TyFun [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type) -> *) (UnionBySym1 a6989586621679458072) Source # | |
type Apply [a6989586621679458072] (TyFun [a6989586621679458072] [a6989586621679458072] -> Type) (UnionBySym1 a6989586621679458072 l1) l2 Source # | |
data UnionBySym2 (l :: TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (l :: [a6989586621679458072]) (l :: TyFun [a6989586621679458072] [a6989586621679458072]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) -> [a6989586621679458072] -> TyFun [a6989586621679458072] [a6989586621679458072] -> *) (UnionBySym2 a6989586621679458072) Source # | |
type Apply [a] [a] (UnionBySym2 a l1 l2) l3 Source # | |
type UnionBySym3 (t :: TyFun a6989586621679458072 (TyFun a6989586621679458072 Bool -> Type) -> Type) (t :: [a6989586621679458072]) (t :: [a6989586621679458072]) = UnionBy t t t Source #
data GenericLengthSym0 (l :: TyFun [a6989586621679458070] i6989586621679458069) Source #
SuppressUnusedWarnings (TyFun [a6989586621679458070] i6989586621679458069 -> *) (GenericLengthSym0 a6989586621679458070 i6989586621679458069) Source # | |
type Apply [a] k2 (GenericLengthSym0 a k2) l Source # | |
type GenericLengthSym1 (t :: [a6989586621679458070]) = GenericLength t Source #
data GenericTakeSym0 (l :: TyFun i6989586621679876659 (TyFun [a6989586621679876660] [a6989586621679876660] -> Type)) Source #
SuppressUnusedWarnings (TyFun i6989586621679876659 (TyFun [a6989586621679876660] [a6989586621679876660] -> Type) -> *) (GenericTakeSym0 i6989586621679876659 a6989586621679876660) Source # | |
type Apply i6989586621679876659 (TyFun [a6989586621679876660] [a6989586621679876660] -> Type) (GenericTakeSym0 i6989586621679876659 a6989586621679876660) l Source # | |
data GenericTakeSym1 (l :: i6989586621679876659) (l :: TyFun [a6989586621679876660] [a6989586621679876660]) Source #
SuppressUnusedWarnings (i6989586621679876659 -> TyFun [a6989586621679876660] [a6989586621679876660] -> *) (GenericTakeSym1 i6989586621679876659 a6989586621679876660) Source # | |
type Apply [a] [a] (GenericTakeSym1 i a l1) l2 Source # | |
type GenericTakeSym2 (t :: i6989586621679876659) (t :: [a6989586621679876660]) = GenericTake t t Source #
data GenericDropSym0 (l :: TyFun i6989586621679876657 (TyFun [a6989586621679876658] [a6989586621679876658] -> Type)) Source #
SuppressUnusedWarnings (TyFun i6989586621679876657 (TyFun [a6989586621679876658] [a6989586621679876658] -> Type) -> *) (GenericDropSym0 i6989586621679876657 a6989586621679876658) Source # | |
type Apply i6989586621679876657 (TyFun [a6989586621679876658] [a6989586621679876658] -> Type) (GenericDropSym0 i6989586621679876657 a6989586621679876658) l Source # | |
data GenericDropSym1 (l :: i6989586621679876657) (l :: TyFun [a6989586621679876658] [a6989586621679876658]) Source #
SuppressUnusedWarnings (i6989586621679876657 -> TyFun [a6989586621679876658] [a6989586621679876658] -> *) (GenericDropSym1 i6989586621679876657 a6989586621679876658) Source # | |
type Apply [a] [a] (GenericDropSym1 i a l1) l2 Source # | |
type GenericDropSym2 (t :: i6989586621679876657) (t :: [a6989586621679876658]) = GenericDrop t t Source #
data GenericSplitAtSym0 (l :: TyFun i6989586621679876655 (TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]) -> Type)) Source #
SuppressUnusedWarnings (TyFun i6989586621679876655 (TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]) -> Type) -> *) (GenericSplitAtSym0 i6989586621679876655 a6989586621679876656) Source # | |
type Apply i6989586621679876655 (TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]) -> Type) (GenericSplitAtSym0 i6989586621679876655 a6989586621679876656) l Source # | |
data GenericSplitAtSym1 (l :: i6989586621679876655) (l :: TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656])) Source #
SuppressUnusedWarnings (i6989586621679876655 -> TyFun [a6989586621679876656] ([a6989586621679876656], [a6989586621679876656]) -> *) (GenericSplitAtSym1 i6989586621679876655 a6989586621679876656) Source # | |
type Apply [a] ([a], [a]) (GenericSplitAtSym1 i a l1) l2 Source # | |
type GenericSplitAtSym2 (t :: i6989586621679876655) (t :: [a6989586621679876656]) = GenericSplitAt t t Source #
data GenericIndexSym0 (l :: TyFun [a6989586621679876654] (TyFun i6989586621679876653 a6989586621679876654 -> Type)) Source #
SuppressUnusedWarnings (TyFun [a6989586621679876654] (TyFun i6989586621679876653 a6989586621679876654 -> Type) -> *) (GenericIndexSym0 i6989586621679876653 a6989586621679876654) Source # | |
type Apply [a6989586621679876654] (TyFun i6989586621679876653 a6989586621679876654 -> Type) (GenericIndexSym0 i6989586621679876653 a6989586621679876654) l Source # | |
data GenericIndexSym1 (l :: [a6989586621679876654]) (l :: TyFun i6989586621679876653 a6989586621679876654) Source #
SuppressUnusedWarnings ([a6989586621679876654] -> TyFun i6989586621679876653 a6989586621679876654 -> *) (GenericIndexSym1 i6989586621679876653 a6989586621679876654) Source # | |
type Apply i a (GenericIndexSym1 i a l1) l2 Source # | |
type GenericIndexSym2 (t :: [a6989586621679876654]) (t :: i6989586621679876653) = GenericIndex t t Source #
data GenericReplicateSym0 (l :: TyFun i6989586621679876651 (TyFun a6989586621679876652 [a6989586621679876652] -> Type)) Source #
SuppressUnusedWarnings (TyFun i6989586621679876651 (TyFun a6989586621679876652 [a6989586621679876652] -> Type) -> *) (GenericReplicateSym0 i6989586621679876651 a6989586621679876652) Source # | |
type Apply i6989586621679876651 (TyFun a6989586621679876652 [a6989586621679876652] -> Type) (GenericReplicateSym0 i6989586621679876651 a6989586621679876652) l Source # | |
data GenericReplicateSym1 (l :: i6989586621679876651) (l :: TyFun a6989586621679876652 [a6989586621679876652]) Source #
SuppressUnusedWarnings (i6989586621679876651 -> TyFun a6989586621679876652 [a6989586621679876652] -> *) (GenericReplicateSym1 i6989586621679876651 a6989586621679876652) Source # | |
type Apply a [a] (GenericReplicateSym1 i a l1) l2 Source # | |
type GenericReplicateSym2 (t :: i6989586621679876651) (t :: a6989586621679876652) = GenericReplicate t t Source #