Copyright | (C) 2014 Jan Stolarek |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Jan Stolarek (jan.stolarek@p.lodz.pl) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Data.Promotion.Prelude.List
Contents
Description
Defines promoted functions and datatypes relating to List
,
including a promoted version of all the definitions in Data.List
.
Because many of these definitions are produced by Template Haskell,
it is not possible to create proper Haddock documentation. Please look
up the corresponding operation in Data.List
. Also, please excuse
the apparent repeated variable names. This is due to an interaction
between Template Haskell and Haddock.
- type family (a :: [a]) :++ (a :: [a]) :: [a] where ...
- type family Head (a :: [a]) :: a where ...
- type family Last (a :: [a]) :: a where ...
- type family Tail (a :: [a]) :: [a] where ...
- type family Init (a :: [a]) :: [a] where ...
- type family Null (a :: [a]) :: Bool where ...
- type family Length (a :: [a]) :: Nat where ...
- type family Map (a :: TyFun a b -> Type) (a :: [a]) :: [b] where ...
- type family Reverse (a :: [a]) :: [a] where ...
- type family Intersperse (a :: a) (a :: [a]) :: [a] where ...
- type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ...
- type family Transpose (a :: [[a]]) :: [[a]] where ...
- type family Subsequences (a :: [a]) :: [[a]] where ...
- type family Permutations (a :: [a]) :: [[a]] where ...
- type family Foldl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- type family Foldl' (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- type family Foldl1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
- type family Foldl1' (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
- type family Foldr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- type family Foldr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
- type family Concat (a :: [[a]]) :: [a] where ...
- type family ConcatMap (a :: TyFun a [b] -> Type) (a :: [a]) :: [b] where ...
- type family And (a :: [Bool]) :: Bool where ...
- type family Or (a :: [Bool]) :: Bool where ...
- type family Any_ (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ...
- type family All (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ...
- type family Sum (a :: [a]) :: a where ...
- type family Product (a :: [a]) :: a where ...
- type family Maximum (a :: [a]) :: a where ...
- type family Minimum (a :: [a]) :: a where ...
- any_ :: forall a. (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
- data l :$$ l
- type (:$$$) t t = (:) t t
- type (:++$$$) t t = (:++) t t
- data l :++$$ l
- data (:++$) l
- data HeadSym0 l
- type HeadSym1 t = Head t
- data LastSym0 l
- type LastSym1 t = Last t
- data TailSym0 l
- type TailSym1 t = Tail t
- data InitSym0 l
- type InitSym1 t = Init t
- data NullSym0 l
- type NullSym1 t = Null t
- data MapSym0 l
- data MapSym1 l l
- type MapSym2 t t = Map t t
- data ReverseSym0 l
- type ReverseSym1 t = Reverse t
- data IntersperseSym0 l
- data IntersperseSym1 l l
- type IntersperseSym2 t t = Intersperse t t
- data IntercalateSym0 l
- data IntercalateSym1 l l
- type IntercalateSym2 t t = Intercalate t t
- data SubsequencesSym0 l
- type SubsequencesSym1 t = Subsequences t
- data PermutationsSym0 l
- type PermutationsSym1 t = Permutations t
- data FoldlSym0 l
- data FoldlSym1 l l
- data FoldlSym2 l l l
- type FoldlSym3 t t t = Foldl t t t
- data Foldl'Sym0 l
- data Foldl'Sym1 l l
- data Foldl'Sym2 l l l
- type Foldl'Sym3 t t t = Foldl' t t t
- data Foldl1Sym0 l
- data Foldl1Sym1 l l
- type Foldl1Sym2 t t = Foldl1 t t
- data Foldl1'Sym0 l
- data Foldl1'Sym1 l l
- type Foldl1'Sym2 t t = Foldl1' t t
- data FoldrSym0 l
- data FoldrSym1 l l
- data FoldrSym2 l l l
- type FoldrSym3 t t t = Foldr t t t
- data Foldr1Sym0 l
- data Foldr1Sym1 l l
- type Foldr1Sym2 t t = Foldr1 t t
- data ConcatSym0 l
- type ConcatSym1 t = Concat t
- data ConcatMapSym0 l
- data ConcatMapSym1 l l
- type ConcatMapSym2 t t = ConcatMap t t
- data AndSym0 l
- type AndSym1 t = And t
- data OrSym0 l
- type OrSym1 t = Or t
- data Any_Sym0 l
- data Any_Sym1 l l
- type Any_Sym2 t t = Any_ t t
- data AllSym0 l
- data AllSym1 l l
- type AllSym2 t t = All t t
- data ScanlSym0 l
- data ScanlSym1 l l
- data ScanlSym2 l l l
- type ScanlSym3 t t t = Scanl t t t
- data Scanl1Sym0 l
- data Scanl1Sym1 l l
- type Scanl1Sym2 t t = Scanl1 t t
- data ScanrSym0 l
- data ScanrSym1 l l
- data ScanrSym2 l l l
- type ScanrSym3 t t t = Scanr t t t
- data Scanr1Sym0 l
- data Scanr1Sym1 l l
- type Scanr1Sym2 t t = Scanr1 t t
- data MapAccumLSym0 l
- data MapAccumLSym1 l l
- data MapAccumLSym2 l l l
- type MapAccumLSym3 t t t = MapAccumL t t t
- data MapAccumRSym0 l
- data MapAccumRSym1 l l
- data MapAccumRSym2 l l l
- type MapAccumRSym3 t t t = MapAccumR t t t
- data UnfoldrSym0 l
- data UnfoldrSym1 l l
- type UnfoldrSym2 t t = Unfoldr t t
- data InitsSym0 l
- type InitsSym1 t = Inits t
- data TailsSym0 l
- type TailsSym1 t = Tails t
- data IsPrefixOfSym0 l
- data IsPrefixOfSym1 l l
- type IsPrefixOfSym2 t t = IsPrefixOf t t
- data IsSuffixOfSym0 l
- data IsSuffixOfSym1 l l
- type IsSuffixOfSym2 t t = IsSuffixOf t t
- data IsInfixOfSym0 l
- data IsInfixOfSym1 l l
- type IsInfixOfSym2 t t = IsInfixOf t t
- data ElemSym0 l
- data ElemSym1 l l
- type ElemSym2 t t = Elem t t
- data NotElemSym0 l
- data NotElemSym1 l l
- type NotElemSym2 t t = NotElem t t
- data ZipSym0 l
- data ZipSym1 l l
- type ZipSym2 t t = Zip t t
- data Zip3Sym0 l
- data Zip3Sym1 l l
- data Zip3Sym2 l l l
- type Zip3Sym3 t t t = Zip3 t t t
- data ZipWithSym0 l
- data ZipWithSym1 l l
- data ZipWithSym2 l l l
- type ZipWithSym3 t t t = ZipWith t t t
- data ZipWith3Sym0 l
- data ZipWith3Sym1 l l
- data ZipWith3Sym2 l l l
- data ZipWith3Sym3 l l l l
- type ZipWith3Sym4 t t t t = ZipWith3 t t t t
- data UnzipSym0 l
- type UnzipSym1 t = Unzip t
- data Unzip3Sym0 l
- type Unzip3Sym1 t = Unzip3 t
- data Unzip4Sym0 l
- type Unzip4Sym1 t = Unzip4 t
- data Unzip5Sym0 l
- type Unzip5Sym1 t = Unzip5 t
- data Unzip6Sym0 l
- type Unzip6Sym1 t = Unzip6 t
- data Unzip7Sym0 l
- type Unzip7Sym1 t = Unzip7 t
- data DeleteSym0 l
- data DeleteSym1 l l
- type DeleteSym2 t t = Delete t t
- data (:\\$) l
- data l :\\$$ l
- type (:\\$$$) t t = (:\\) t t
- data IntersectSym0 l
- data IntersectSym1 l l
- type IntersectSym2 t t = Intersect t t
- data InsertSym0 l
- data InsertSym1 l l
- type InsertSym2 t t = Insert t t
- data SortSym0 l
- type SortSym1 t = Sort t
- data DeleteBySym0 l
- data DeleteBySym1 l l
- data DeleteBySym2 l l l
- type DeleteBySym3 t t t = DeleteBy t t t
- data DeleteFirstsBySym0 l
- data DeleteFirstsBySym1 l l
- data DeleteFirstsBySym2 l l l
- type DeleteFirstsBySym3 t t t = DeleteFirstsBy t t t
- data IntersectBySym0 l
- data IntersectBySym1 l l
- data IntersectBySym2 l l l
- data SortBySym0 l
- data SortBySym1 l l
- type SortBySym2 t t = SortBy t t
- data InsertBySym0 l
- data InsertBySym1 l l
- data InsertBySym2 l l l
- type InsertBySym3 t t t = InsertBy t t t
- data MaximumBySym0 l
- data MaximumBySym1 l l
- type MaximumBySym2 t t = MaximumBy t t
- data MinimumBySym0 l
- data MinimumBySym1 l l
- type MinimumBySym2 t t = MinimumBy t t
- data LengthSym0 l
- type LengthSym1 t = Length t
- data SumSym0 l
- type SumSym1 t = Sum t
- data ProductSym0 l
- type ProductSym1 t = Product t
- data ReplicateSym0 l
- data ReplicateSym1 l l
- type ReplicateSym2 t t = Replicate t t
- data TransposeSym0 l
- type TransposeSym1 t = Transpose t
- data TakeSym0 l
- data TakeSym1 l l
- type TakeSym2 t t = Take t t
- data DropSym0 l
- data DropSym1 l l
- type DropSym2 t t = Drop t t
- data SplitAtSym0 l
- data SplitAtSym1 l l
- type SplitAtSym2 t t = SplitAt t t
- data TakeWhileSym0 l
- data TakeWhileSym1 l l
- type TakeWhileSym2 t t = TakeWhile t t
- data DropWhileSym0 l
- data DropWhileSym1 l l
- type DropWhileSym2 t t = DropWhile t t
- data DropWhileEndSym0 l
- data DropWhileEndSym1 l l
- type DropWhileEndSym2 t t = DropWhileEnd t t
- data SpanSym0 l
- data SpanSym1 l l
- type SpanSym2 t t = Span t t
- data BreakSym0 l
- data BreakSym1 l l
- type BreakSym2 t t = Break t t
- data StripPrefixSym0 l
- data StripPrefixSym1 l l
- type StripPrefixSym2 t t = StripPrefix t t
- data MaximumSym0 l
- type MaximumSym1 t = Maximum t
- data MinimumSym0 l
- type MinimumSym1 t = Minimum t
- data GroupSym0 l
- type GroupSym1 t = Group t
- data GroupBySym0 l
- data GroupBySym1 l l
- type GroupBySym2 t t = GroupBy t t
- data LookupSym0 l
- data LookupSym1 l l
- type LookupSym2 t t = Lookup t t
- data FindSym0 l
- data FindSym1 l l
- type FindSym2 t t = Find t t
- data FilterSym0 l
- data FilterSym1 l l
- type FilterSym2 t t = Filter t t
- data PartitionSym0 l
- data PartitionSym1 l l
- type PartitionSym2 t t = Partition t t
- data (:!!$) l
- data l :!!$$ l
- type (:!!$$$) t t = (:!!) t t
- data ElemIndexSym0 l
- data ElemIndexSym1 l l
- type ElemIndexSym2 t t = ElemIndex t t
- data ElemIndicesSym0 l
- data ElemIndicesSym1 l l
- type ElemIndicesSym2 t t = ElemIndices t t
- data FindIndexSym0 l
- data FindIndexSym1 l l
- type FindIndexSym2 t t = FindIndex t t
- data FindIndicesSym0 l
- data FindIndicesSym1 l l
- type FindIndicesSym2 t t = FindIndices t t
- data Zip4Sym0 l
- data Zip4Sym1 l l
- data Zip4Sym2 l l l
- data Zip4Sym3 l l l l
- type Zip4Sym4 t t t t = Zip4 t t t t
- data Zip5Sym0 l
- data Zip5Sym1 l l
- data Zip5Sym2 l l l
- data Zip5Sym3 l l l l
- data Zip5Sym4 l l l l l
- type Zip5Sym5 t t t t t = Zip5 t t t t t
- data Zip6Sym0 l
- data Zip6Sym1 l l
- data Zip6Sym2 l l l
- data Zip6Sym3 l l l l
- data Zip6Sym4 l l l l l
- data Zip6Sym5 l l l l l l
- type Zip6Sym6 t t t t t t = Zip6 t t t t t t
- data Zip7Sym0 l
- data Zip7Sym1 l l
- data Zip7Sym2 l l l
- data Zip7Sym3 l l l l
- data Zip7Sym4 l l l l l
- data Zip7Sym5 l l l l l l
- data Zip7Sym6 l l l l l l l
- type Zip7Sym7 t t t t t t t = Zip7 t t t t t t t
- data ZipWith4Sym0 l
- data ZipWith4Sym1 l l
- data ZipWith4Sym2 l l l
- data ZipWith4Sym3 l l l l
- data ZipWith4Sym4 l l l l l
- type ZipWith4Sym5 t t t t t = ZipWith4 t t t t t
- data ZipWith5Sym0 l
- data ZipWith5Sym1 l l
- data ZipWith5Sym2 l l l
- data ZipWith5Sym3 l l l l
- data ZipWith5Sym4 l l l l l
- data ZipWith5Sym5 l l l l l l
- type ZipWith5Sym6 t t t t t t = ZipWith5 t t t t t t
- data ZipWith6Sym0 l
- data ZipWith6Sym1 l l
- data ZipWith6Sym2 l l l
- data ZipWith6Sym3 l l l l
- data ZipWith6Sym4 l l l l l
- data ZipWith6Sym5 l l l l l l
- data ZipWith6Sym6 l l l l l l l
- type ZipWith6Sym7 t t t t t t t = ZipWith6 t t t t t t t
- data ZipWith7Sym0 l
- data ZipWith7Sym1 l l
- data ZipWith7Sym2 l l l
- data ZipWith7Sym3 l l l l
- data ZipWith7Sym4 l l l l l
- data ZipWith7Sym5 l l l l l l
- data ZipWith7Sym6 l l l l l l l
- data ZipWith7Sym7 l l l l l l l l
- type ZipWith7Sym8 t t t t t t t t = ZipWith7 t t t t t t t t
- data NubSym0 l
- type NubSym1 t = Nub t
- data NubBySym0 l
- data NubBySym1 l l
- type NubBySym2 t t = NubBy t t
- data UnionSym0 l
- data UnionSym1 l l
- type UnionSym2 t t = Union t t
- data UnionBySym0 l
- data UnionBySym1 l l
- data UnionBySym2 l l l
- type UnionBySym3 t t t = UnionBy t t t
- data GenericLengthSym0 l
- type GenericLengthSym1 t = GenericLength t
- data GenericTakeSym0 l
- data GenericTakeSym1 l l
- type GenericTakeSym2 t t = GenericTake t t
- data GenericDropSym0 l
- data GenericDropSym1 l l
- type GenericDropSym2 t t = GenericDrop t t
- data GenericSplitAtSym0 l
- data GenericSplitAtSym1 l l
- type GenericSplitAtSym2 t t = GenericSplitAt t t
- data GenericIndexSym0 l
- data GenericIndexSym1 l l
- type GenericIndexSym2 t t = GenericIndex t t
- data GenericReplicateSym0 l
- data GenericReplicateSym1 l l
- type GenericReplicateSym2 t t = GenericReplicate t t
Basic functions
type family Length (a :: [a]) :: Nat where ... #
Equations
Length '[] = FromInteger 0 | |
Length ((:) _z_6989586621679701637 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply LengthSym0 xs) |
List transformations
type family Intersperse (a :: a) (a :: [a]) :: [a] where ... #
Equations
Intersperse _z_6989586621679704666 '[] = '[] | |
Intersperse sep ((:) x xs) = Apply (Apply (:$) x) (Apply (Apply PrependToAllSym0 sep) xs) |
type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ... #
Equations
Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) |
type family Subsequences (a :: [a]) :: [[a]] where ... #
Equations
Subsequences xs = Apply (Apply (:$) '[]) (Apply NonEmptySubsequencesSym0 xs) |
type family Permutations (a :: [a]) :: [[a]] where ... #
Reducing lists (folds)
type family Foldr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ... #
Equations
Foldr1 _z_6989586621679703890 '[x] = x | |
Foldr1 f ((:) x ((:) wild_6989586621679700618 wild_6989586621679700620)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let6989586621679703898XsSym4 f x wild_6989586621679700618 wild_6989586621679700620)) | |
Foldr1 _z_6989586621679703917 '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" |
Special folds
type family Sum (a :: [a]) :: a where ... #
Equations
Sum l = Apply (Apply (Let6989586621679701670Sum'Sym1 l) l) (FromInteger 0) |
type family Product (a :: [a]) :: a where ... #
Equations
Product l = Apply (Apply (Let6989586621679701646ProdSym1 l) l) (FromInteger 1) |
Building lists
Scans
type family Scanr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ... #
Equations
Scanr1 _z_6989586621679703695 '[] = '[] | |
Scanr1 _z_6989586621679703698 '[x] = Apply (Apply (:$) x) '[] | |
Scanr1 f ((:) x ((:) wild_6989586621679700626 wild_6989586621679700628)) = Case_6989586621679703744 f x wild_6989586621679700626 wild_6989586621679700628 (Let6989586621679703725Scrutinee_6989586621679700624Sym4 f x wild_6989586621679700626 wild_6989586621679700628) |
Accumulating maps
type family MapAccumL (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... #
type family MapAccumR (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... #
Infinite lists
type family Replicate (a :: Nat) (a :: a) :: [a] where ... #
Equations
Replicate n x = Case_6989586621679701630 n x (Let6989586621679701622Scrutinee_6989586621679700710Sym2 n x) |
Unfolding
type family Unfoldr (a :: TyFun b (Maybe (a, b)) -> Type) (a :: b) :: [a] where ... #
Equations
Unfoldr f b = Case_6989586621679703337 f b (Let6989586621679703329Scrutinee_6989586621679700630Sym2 f b) |
Sublists
Extracting sublists
type family DropWhileEnd (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ... #
type family Span (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... #
Equations
Span _z_6989586621679701964 '[] = Apply (Apply Tuple2Sym0 (Let6989586621679701967XsSym1 _z_6989586621679701964)) (Let6989586621679701967XsSym1 _z_6989586621679701964) | |
Span p ((:) x xs') = Case_6989586621679702000 p x xs' (Let6989586621679701987Scrutinee_6989586621679700690Sym3 p x xs') |
type family Break (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... #
Equations
Break _z_6989586621679701859 '[] = Apply (Apply Tuple2Sym0 (Let6989586621679701862XsSym1 _z_6989586621679701859)) (Let6989586621679701862XsSym1 _z_6989586621679701859) | |
Break p ((:) x xs') = Case_6989586621679701895 p x xs' (Let6989586621679701882Scrutinee_6989586621679700692Sym3 p x xs') |
type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ... #
Equations
StripPrefix '[] ys = Apply JustSym0 ys | |
StripPrefix arg_6989586621679923145 arg_6989586621679923147 = Case_6989586621679923778 arg_6989586621679923145 arg_6989586621679923147 (Apply (Apply Tuple2Sym0 arg_6989586621679923145) arg_6989586621679923147) |
type family Group (a :: [a]) :: [[a]] where ... #
Equations
Group xs = Apply (Apply GroupBySym0 (:==$)) xs |
Predicates
type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... #
Equations
IsPrefixOf '[] '[] = TrueSym0 | |
IsPrefixOf '[] ((:) _z_6989586621679703269 _z_6989586621679703272) = TrueSym0 | |
IsPrefixOf ((:) _z_6989586621679703275 _z_6989586621679703278) '[] = FalseSym0 | |
IsPrefixOf ((:) x xs) ((:) y ys) = Apply (Apply (:&&$) (Apply (Apply (:==$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) |
type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ... #
Equations
IsSuffixOf x y = Apply (Apply IsPrefixOfSym0 (Apply ReverseSym0 x)) (Apply ReverseSym0 y) |
Searching lists
Searching by equality
type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... #
Equations
Lookup _key '[] = NothingSym0 | |
Lookup key ((:) '(x, y) xys) = Case_6989586621679701774 key x y xys (Let6989586621679701755Scrutinee_6989586621679700706Sym4 key x y xys) |
Searching with a predicate
type family Find (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe a where ... #
Equations
Find p a_6989586621679702250 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FilterSym0 p)) a_6989586621679702250 |
Indexing lists
type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ... #
Equations
ElemIndices x a_6989586621679703152 = Apply (Apply FindIndicesSym0 (Apply (:==$) x)) a_6989586621679703152 |
type family FindIndex (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe Nat where ... #
Equations
FindIndex p a_6989586621679703165 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621679703165 |
Zipping and unzipping lists
type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ... #
Equations
Zip3 ((:) a as) ((:) b bs) ((:) c cs) = Apply (Apply (:$) (Apply (Apply (Apply Tuple3Sym0 a) b) c)) (Apply (Apply (Apply Zip3Sym0 as) bs) cs) | |
Zip3 '[] '[] '[] = '[] | |
Zip3 '[] '[] ((:) _z_6989586621679703001 _z_6989586621679703004) = '[] | |
Zip3 '[] ((:) _z_6989586621679703007 _z_6989586621679703010) '[] = '[] | |
Zip3 '[] ((:) _z_6989586621679703013 _z_6989586621679703016) ((:) _z_6989586621679703019 _z_6989586621679703022) = '[] | |
Zip3 ((:) _z_6989586621679703025 _z_6989586621679703028) '[] '[] = '[] | |
Zip3 ((:) _z_6989586621679703031 _z_6989586621679703034) '[] ((:) _z_6989586621679703037 _z_6989586621679703040) = '[] | |
Zip3 ((:) _z_6989586621679703043 _z_6989586621679703046) ((:) _z_6989586621679703049 _z_6989586621679703052) '[] = '[] |
type family Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ... #
Equations
Zip4 a_6989586621679923732 a_6989586621679923734 a_6989586621679923736 a_6989586621679923738 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_6989586621679923732) a_6989586621679923734) a_6989586621679923736) a_6989586621679923738 |
type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ... #
Equations
Zip5 a_6989586621679923687 a_6989586621679923689 a_6989586621679923691 a_6989586621679923693 a_6989586621679923695 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_6989586621679923687) a_6989586621679923689) a_6989586621679923691) a_6989586621679923693) a_6989586621679923695 |
type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ... #
Equations
Zip6 a_6989586621679923630 a_6989586621679923632 a_6989586621679923634 a_6989586621679923636 a_6989586621679923638 a_6989586621679923640 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_6989586621679923630) a_6989586621679923632) a_6989586621679923634) a_6989586621679923636) a_6989586621679923638) a_6989586621679923640 |
type family Zip7 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [(a, b, c, d, e, f, g)] where ... #
Equations
Zip7 a_6989586621679923560 a_6989586621679923562 a_6989586621679923564 a_6989586621679923566 a_6989586621679923568 a_6989586621679923570 a_6989586621679923572 = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 Tuple7Sym0) a_6989586621679923560) a_6989586621679923562) a_6989586621679923564) a_6989586621679923566) a_6989586621679923568) a_6989586621679923570) a_6989586621679923572 |
type family ZipWith (a :: TyFun a (TyFun b c -> Type) -> Type) (a :: [a]) (a :: [b]) :: [c] where ... #
Equations
ZipWith f ((:) x xs) ((:) y ys) = Apply (Apply (:$) (Apply (Apply f x) y)) (Apply (Apply (Apply ZipWithSym0 f) xs) ys) | |
ZipWith _z_6989586621679702959 '[] '[] = '[] | |
ZipWith _z_6989586621679702962 ((:) _z_6989586621679702965 _z_6989586621679702968) '[] = '[] | |
ZipWith _z_6989586621679702971 '[] ((:) _z_6989586621679702974 _z_6989586621679702977) = '[] |
type family ZipWith3 (a :: TyFun a (TyFun b (TyFun c d -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ... #
Equations
ZipWith3 z ((:) a as) ((:) b bs) ((:) c cs) = Apply (Apply (:$) (Apply (Apply (Apply z a) b) c)) (Apply (Apply (Apply (Apply ZipWith3Sym0 z) as) bs) cs) | |
ZipWith3 _z_6989586621679702864 '[] '[] '[] = '[] | |
ZipWith3 _z_6989586621679702867 '[] '[] ((:) _z_6989586621679702870 _z_6989586621679702873) = '[] | |
ZipWith3 _z_6989586621679702876 '[] ((:) _z_6989586621679702879 _z_6989586621679702882) '[] = '[] | |
ZipWith3 _z_6989586621679702885 '[] ((:) _z_6989586621679702888 _z_6989586621679702891) ((:) _z_6989586621679702894 _z_6989586621679702897) = '[] | |
ZipWith3 _z_6989586621679702900 ((:) _z_6989586621679702903 _z_6989586621679702906) '[] '[] = '[] | |
ZipWith3 _z_6989586621679702909 ((:) _z_6989586621679702912 _z_6989586621679702915) '[] ((:) _z_6989586621679702918 _z_6989586621679702921) = '[] | |
ZipWith3 _z_6989586621679702924 ((:) _z_6989586621679702927 _z_6989586621679702930) ((:) _z_6989586621679702933 _z_6989586621679702936) '[] = '[] |
type family ZipWith4 (a :: TyFun a (TyFun b (TyFun c (TyFun d e -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ... #
Equations
ZipWith4 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) = Apply (Apply (:$) (Apply (Apply (Apply (Apply z a) b) c) d)) (Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 z) as) bs) cs) ds) | |
ZipWith4 _z_6989586621679923545 _z_6989586621679923548 _z_6989586621679923551 _z_6989586621679923554 _z_6989586621679923557 = '[] |
type family ZipWith5 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e f -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ... #
Equations
ZipWith5 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) ((:) e es) = Apply (Apply (:$) (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e)) (Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 z) as) bs) cs) ds) es) | |
ZipWith5 _z_6989586621679923488 _z_6989586621679923491 _z_6989586621679923494 _z_6989586621679923497 _z_6989586621679923500 _z_6989586621679923503 = '[] |
type family ZipWith6 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e (TyFun f g -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ... #
Equations
ZipWith6 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) ((:) e es) ((:) f fs) = Apply (Apply (:$) (Apply (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e) f)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 z) as) bs) cs) ds) es) fs) | |
ZipWith6 _z_6989586621679923417 _z_6989586621679923420 _z_6989586621679923423 _z_6989586621679923426 _z_6989586621679923429 _z_6989586621679923432 _z_6989586621679923435 = '[] |
type family ZipWith7 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e (TyFun f (TyFun g h -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ... #
Equations
ZipWith7 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) ((:) e es) ((:) f fs) ((:) g gs) = Apply (Apply (:$) (Apply (Apply (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e) f) g)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 z) as) bs) cs) ds) es) fs) gs) | |
ZipWith7 _z_6989586621679923331 _z_6989586621679923334 _z_6989586621679923337 _z_6989586621679923340 _z_6989586621679923343 _z_6989586621679923346 _z_6989586621679923349 _z_6989586621679923352 = '[] |
type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... #
Special lists
"Set" operations
Ordered lists
type family Sort (a :: [a]) :: [a] where ... #
Equations
Sort a_6989586621679702486 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679702486 |
type family Insert (a :: a) (a :: [a]) :: [a] where ... #
Equations
Insert e ls = Apply (Apply (Apply InsertBySym0 CompareSym0) e) ls |
Generalized functions
The "By
" operations
User-supplied equality (replacing an Eq
context)
type family DeleteBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... #
type family DeleteFirstsBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... #
Equations
DeleteFirstsBy eq a_6989586621679702555 a_6989586621679702557 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679702555) a_6989586621679702557 |
type family UnionBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... #
type family IntersectBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... #
Equations
IntersectBy _z_6989586621679702269 '[] '[] = '[] | |
IntersectBy _z_6989586621679702272 '[] ((:) _z_6989586621679702275 _z_6989586621679702278) = '[] | |
IntersectBy _z_6989586621679702281 ((:) _z_6989586621679702284 _z_6989586621679702287) '[] = '[] | |
IntersectBy eq ((:) wild_6989586621679700676 wild_6989586621679700678) ((:) wild_6989586621679700680 wild_6989586621679700682) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679702346Sym0 eq) wild_6989586621679700676) wild_6989586621679700678) wild_6989586621679700680) wild_6989586621679700682)) (Let6989586621679702295XsSym5 eq wild_6989586621679700676 wild_6989586621679700678 wild_6989586621679700680 wild_6989586621679700682) |
User-supplied comparison (replacing an Ord
context)
type family InsertBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... #
type family MaximumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... #
Equations
MaximumBy _z_6989586621679703944 '[] = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" | |
MaximumBy cmp ((:) wild_6989586621679700662 wild_6989586621679700664) = Apply (Apply Foldl1Sym0 (Let6989586621679703963MaxBySym3 cmp wild_6989586621679700662 wild_6989586621679700664)) (Let6989586621679703950XsSym3 cmp wild_6989586621679700662 wild_6989586621679700664) |
type family MinimumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... #
Equations
MinimumBy _z_6989586621679704031 '[] = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" | |
MinimumBy cmp ((:) wild_6989586621679700668 wild_6989586621679700670) = Apply (Apply Foldl1Sym0 (Let6989586621679704050MinBySym3 cmp wild_6989586621679700668 wild_6989586621679700670)) (Let6989586621679704037XsSym3 cmp wild_6989586621679700668 wild_6989586621679700670) |
The "generic
" operations
type family GenericLength (a :: [a]) :: i where ... #
Equations
GenericLength '[] = FromInteger 0 | |
GenericLength ((:) _z_6989586621679701484 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
type family GenericTake (a :: i) (a :: [a]) :: [a] where ... #
Equations
GenericTake a_6989586621679923241 a_6989586621679923243 = Apply (Apply TakeSym0 a_6989586621679923241) a_6989586621679923243 |
type family GenericDrop (a :: i) (a :: [a]) :: [a] where ... #
Equations
GenericDrop a_6989586621679923226 a_6989586621679923228 = Apply (Apply DropSym0 a_6989586621679923226) a_6989586621679923228 |
type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ... #
Equations
GenericSplitAt a_6989586621679923211 a_6989586621679923213 = Apply (Apply SplitAtSym0 a_6989586621679923211) a_6989586621679923213 |
type family GenericIndex (a :: [a]) (a :: i) :: a where ... #
Equations
GenericIndex a_6989586621679923196 a_6989586621679923198 = Apply (Apply (:!!$) a_6989586621679923196) a_6989586621679923198 |
type family GenericReplicate (a :: i) (a :: a) :: [a] where ... #
Equations
GenericReplicate a_6989586621679923181 a_6989586621679923183 = Apply (Apply ReplicateSym0 a_6989586621679923181) a_6989586621679923183 |
Defunctionalization symbols
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679482537 b6989586621679482538 -> Type) (TyFun [a6989586621679482537] [b6989586621679482538] -> Type) -> *) (MapSym0 a6989586621679482537 b6989586621679482538) # | |
type Apply (TyFun a6989586621679482537 b6989586621679482538 -> Type) (TyFun [a6989586621679482537] [b6989586621679482538] -> Type) (MapSym0 a6989586621679482537 b6989586621679482538) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679482537 b6989586621679482538 -> Type) -> TyFun [a6989586621679482537] [b6989586621679482538] -> *) (MapSym1 a6989586621679482537 b6989586621679482538) # | |
type Apply [a6989586621679482537] [b6989586621679482538] (MapSym1 a6989586621679482537 b6989586621679482538 l0) l1 # | |
data ReverseSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700166] [a6989586621679700166] -> *) (ReverseSym0 a6989586621679700166) # | |
type Apply [a6989586621679700166] [a6989586621679700166] (ReverseSym0 a6989586621679700166) l0 # | |
type ReverseSym1 t = Reverse t #
data IntersperseSym0 l #
Instances
SuppressUnusedWarnings (TyFun a6989586621679700165 (TyFun [a6989586621679700165] [a6989586621679700165] -> Type) -> *) (IntersperseSym0 a6989586621679700165) # | |
type Apply a6989586621679700165 (TyFun [a6989586621679700165] [a6989586621679700165] -> Type) (IntersperseSym0 a6989586621679700165) l0 # | |
data IntersperseSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679700165 -> TyFun [a6989586621679700165] [a6989586621679700165] -> *) (IntersperseSym1 a6989586621679700165) # | |
type Apply [a6989586621679700165] [a6989586621679700165] (IntersperseSym1 a6989586621679700165 l0) l1 # | |
type IntersperseSym2 t t = Intersperse t t #
data IntercalateSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700164] (TyFun [[a6989586621679700164]] [a6989586621679700164] -> Type) -> *) (IntercalateSym0 a6989586621679700164) # | |
type Apply [a6989586621679700164] (TyFun [[a6989586621679700164]] [a6989586621679700164] -> Type) (IntercalateSym0 a6989586621679700164) l0 # | |
data IntercalateSym1 l l #
Instances
SuppressUnusedWarnings ([a6989586621679700164] -> TyFun [[a6989586621679700164]] [a6989586621679700164] -> *) (IntercalateSym1 a6989586621679700164) # | |
type Apply [[a6989586621679700164]] [a6989586621679700164] (IntercalateSym1 a6989586621679700164 l0) l1 # | |
type IntercalateSym2 t t = Intercalate t t #
data SubsequencesSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700163] [[a6989586621679700163]] -> *) (SubsequencesSym0 a6989586621679700163) # | |
type Apply [a6989586621679700163] [[a6989586621679700163]] (SubsequencesSym0 a6989586621679700163) l0 # | |
type SubsequencesSym1 t = Subsequences t #
data PermutationsSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700160] [[a6989586621679700160]] -> *) (PermutationsSym0 a6989586621679700160) # | |
type Apply [a6989586621679700160] [[a6989586621679700160]] (PermutationsSym0 a6989586621679700160) l0 # | |
type PermutationsSym1 t = Permutations t #
Instances
SuppressUnusedWarnings (TyFun (TyFun b6989586621679448348 (TyFun a6989586621679448347 b6989586621679448348 -> Type) -> Type) (TyFun b6989586621679448348 (TyFun [a6989586621679448347] b6989586621679448348 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679448347 b6989586621679448348) # | |
type Apply (TyFun b6989586621679448348 (TyFun a6989586621679448347 b6989586621679448348 -> Type) -> Type) (TyFun b6989586621679448348 (TyFun [a6989586621679448347] b6989586621679448348 -> Type) -> Type) (FoldlSym0 a6989586621679448347 b6989586621679448348) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun b6989586621679448348 (TyFun a6989586621679448347 b6989586621679448348 -> Type) -> Type) -> TyFun b6989586621679448348 (TyFun [a6989586621679448347] b6989586621679448348 -> Type) -> *) (FoldlSym1 a6989586621679448347 b6989586621679448348) # | |
type Apply b6989586621679448348 (TyFun [a6989586621679448347] b6989586621679448348 -> Type) (FoldlSym1 a6989586621679448347 b6989586621679448348 l0) l1 # | |
Instances
SuppressUnusedWarnings ((TyFun b6989586621679448348 (TyFun a6989586621679448347 b6989586621679448348 -> Type) -> Type) -> b6989586621679448348 -> TyFun [a6989586621679448347] b6989586621679448348 -> *) (FoldlSym2 a6989586621679448347 b6989586621679448348) # | |
type Apply [a6989586621679448347] b6989586621679448348 (FoldlSym2 a6989586621679448347 b6989586621679448348 l1 l0) l2 # | |
data Foldl'Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun b6989586621679700159 (TyFun a6989586621679700158 b6989586621679700159 -> Type) -> Type) (TyFun b6989586621679700159 (TyFun [a6989586621679700158] b6989586621679700159 -> Type) -> Type) -> *) (Foldl'Sym0 a6989586621679700158 b6989586621679700159) # | |
type Apply (TyFun b6989586621679700159 (TyFun a6989586621679700158 b6989586621679700159 -> Type) -> Type) (TyFun b6989586621679700159 (TyFun [a6989586621679700158] b6989586621679700159 -> Type) -> Type) (Foldl'Sym0 a6989586621679700158 b6989586621679700159) l0 # | |
data Foldl'Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679700159 (TyFun a6989586621679700158 b6989586621679700159 -> Type) -> Type) -> TyFun b6989586621679700159 (TyFun [a6989586621679700158] b6989586621679700159 -> Type) -> *) (Foldl'Sym1 a6989586621679700158 b6989586621679700159) # | |
type Apply b6989586621679700159 (TyFun [a6989586621679700158] b6989586621679700159 -> Type) (Foldl'Sym1 a6989586621679700158 b6989586621679700159 l0) l1 # | |
data Foldl'Sym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679700159 (TyFun a6989586621679700158 b6989586621679700159 -> Type) -> Type) -> b6989586621679700159 -> TyFun [a6989586621679700158] b6989586621679700159 -> *) (Foldl'Sym2 a6989586621679700158 b6989586621679700159) # | |
type Apply [a6989586621679700158] b6989586621679700159 (Foldl'Sym2 a6989586621679700158 b6989586621679700159 l1 l0) l2 # | |
type Foldl'Sym3 t t t = Foldl' t t t #
data Foldl1Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700157 (TyFun a6989586621679700157 a6989586621679700157 -> Type) -> Type) (TyFun [a6989586621679700157] a6989586621679700157 -> Type) -> *) (Foldl1Sym0 a6989586621679700157) # | |
type Apply (TyFun a6989586621679700157 (TyFun a6989586621679700157 a6989586621679700157 -> Type) -> Type) (TyFun [a6989586621679700157] a6989586621679700157 -> Type) (Foldl1Sym0 a6989586621679700157) l0 # | |
data Foldl1Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700157 (TyFun a6989586621679700157 a6989586621679700157 -> Type) -> Type) -> TyFun [a6989586621679700157] a6989586621679700157 -> *) (Foldl1Sym1 a6989586621679700157) # | |
type Apply [a6989586621679700157] a6989586621679700157 (Foldl1Sym1 a6989586621679700157 l0) l1 # | |
type Foldl1Sym2 t t = Foldl1 t t #
data Foldl1'Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700156 (TyFun a6989586621679700156 a6989586621679700156 -> Type) -> Type) (TyFun [a6989586621679700156] a6989586621679700156 -> Type) -> *) (Foldl1'Sym0 a6989586621679700156) # | |
type Apply (TyFun a6989586621679700156 (TyFun a6989586621679700156 a6989586621679700156 -> Type) -> Type) (TyFun [a6989586621679700156] a6989586621679700156 -> Type) (Foldl1'Sym0 a6989586621679700156) l0 # | |
data Foldl1'Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700156 (TyFun a6989586621679700156 a6989586621679700156 -> Type) -> Type) -> TyFun [a6989586621679700156] a6989586621679700156 -> *) (Foldl1'Sym1 a6989586621679700156) # | |
type Apply [a6989586621679700156] a6989586621679700156 (Foldl1'Sym1 a6989586621679700156 l0) l1 # | |
type Foldl1'Sym2 t t = Foldl1' t t #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679482539 (TyFun b6989586621679482540 b6989586621679482540 -> Type) -> Type) (TyFun b6989586621679482540 (TyFun [a6989586621679482539] b6989586621679482540 -> Type) -> Type) -> *) (FoldrSym0 a6989586621679482539 b6989586621679482540) # | |
type Apply (TyFun a6989586621679482539 (TyFun b6989586621679482540 b6989586621679482540 -> Type) -> Type) (TyFun b6989586621679482540 (TyFun [a6989586621679482539] b6989586621679482540 -> Type) -> Type) (FoldrSym0 a6989586621679482539 b6989586621679482540) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679482539 (TyFun b6989586621679482540 b6989586621679482540 -> Type) -> Type) -> TyFun b6989586621679482540 (TyFun [a6989586621679482539] b6989586621679482540 -> Type) -> *) (FoldrSym1 a6989586621679482539 b6989586621679482540) # | |
type Apply b6989586621679482540 (TyFun [a6989586621679482539] b6989586621679482540 -> Type) (FoldrSym1 a6989586621679482539 b6989586621679482540 l0) l1 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679482539 (TyFun b6989586621679482540 b6989586621679482540 -> Type) -> Type) -> b6989586621679482540 -> TyFun [a6989586621679482539] b6989586621679482540 -> *) (FoldrSym2 a6989586621679482539 b6989586621679482540) # | |
type Apply [a6989586621679482539] b6989586621679482540 (FoldrSym2 a6989586621679482539 b6989586621679482540 l1 l0) l2 # | |
data Foldr1Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700155 (TyFun a6989586621679700155 a6989586621679700155 -> Type) -> Type) (TyFun [a6989586621679700155] a6989586621679700155 -> Type) -> *) (Foldr1Sym0 a6989586621679700155) # | |
type Apply (TyFun a6989586621679700155 (TyFun a6989586621679700155 a6989586621679700155 -> Type) -> Type) (TyFun [a6989586621679700155] a6989586621679700155 -> Type) (Foldr1Sym0 a6989586621679700155) l0 # | |
data Foldr1Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700155 (TyFun a6989586621679700155 a6989586621679700155 -> Type) -> Type) -> TyFun [a6989586621679700155] a6989586621679700155 -> *) (Foldr1Sym1 a6989586621679700155) # | |
type Apply [a6989586621679700155] a6989586621679700155 (Foldr1Sym1 a6989586621679700155 l0) l1 # | |
type Foldr1Sym2 t t = Foldr1 t t #
data ConcatSym0 l #
Instances
SuppressUnusedWarnings (TyFun [[a6989586621679700154]] [a6989586621679700154] -> *) (ConcatSym0 a6989586621679700154) # | |
type Apply [[a6989586621679700154]] [a6989586621679700154] (ConcatSym0 a6989586621679700154) l0 # | |
type ConcatSym1 t = Concat t #
data ConcatMapSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700152 [b6989586621679700153] -> Type) (TyFun [a6989586621679700152] [b6989586621679700153] -> Type) -> *) (ConcatMapSym0 a6989586621679700152 b6989586621679700153) # | |
type Apply (TyFun a6989586621679700152 [b6989586621679700153] -> Type) (TyFun [a6989586621679700152] [b6989586621679700153] -> Type) (ConcatMapSym0 a6989586621679700152 b6989586621679700153) l0 # | |
data ConcatMapSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700152 [b6989586621679700153] -> Type) -> TyFun [a6989586621679700152] [b6989586621679700153] -> *) (ConcatMapSym1 a6989586621679700152 b6989586621679700153) # | |
type Apply [a6989586621679700152] [b6989586621679700153] (ConcatMapSym1 a6989586621679700152 b6989586621679700153 l0) l1 # | |
type ConcatMapSym2 t t = ConcatMap t t #
Instances
SuppressUnusedWarnings (TyFun (TyFun b6989586621679700149 (TyFun a6989586621679700150 b6989586621679700149 -> Type) -> Type) (TyFun b6989586621679700149 (TyFun [a6989586621679700150] [b6989586621679700149] -> Type) -> Type) -> *) (ScanlSym0 a6989586621679700150 b6989586621679700149) # | |
type Apply (TyFun b6989586621679700149 (TyFun a6989586621679700150 b6989586621679700149 -> Type) -> Type) (TyFun b6989586621679700149 (TyFun [a6989586621679700150] [b6989586621679700149] -> Type) -> Type) (ScanlSym0 a6989586621679700150 b6989586621679700149) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun b6989586621679700149 (TyFun a6989586621679700150 b6989586621679700149 -> Type) -> Type) -> TyFun b6989586621679700149 (TyFun [a6989586621679700150] [b6989586621679700149] -> Type) -> *) (ScanlSym1 a6989586621679700150 b6989586621679700149) # | |
type Apply b6989586621679700149 (TyFun [a6989586621679700150] [b6989586621679700149] -> Type) (ScanlSym1 a6989586621679700150 b6989586621679700149 l0) l1 # | |
Instances
SuppressUnusedWarnings ((TyFun b6989586621679700149 (TyFun a6989586621679700150 b6989586621679700149 -> Type) -> Type) -> b6989586621679700149 -> TyFun [a6989586621679700150] [b6989586621679700149] -> *) (ScanlSym2 a6989586621679700150 b6989586621679700149) # | |
type Apply [a6989586621679700150] [b6989586621679700149] (ScanlSym2 a6989586621679700150 b6989586621679700149 l1 l0) l2 # | |
data Scanl1Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700148 (TyFun a6989586621679700148 a6989586621679700148 -> Type) -> Type) (TyFun [a6989586621679700148] [a6989586621679700148] -> Type) -> *) (Scanl1Sym0 a6989586621679700148) # | |
type Apply (TyFun a6989586621679700148 (TyFun a6989586621679700148 a6989586621679700148 -> Type) -> Type) (TyFun [a6989586621679700148] [a6989586621679700148] -> Type) (Scanl1Sym0 a6989586621679700148) l0 # | |
data Scanl1Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700148 (TyFun a6989586621679700148 a6989586621679700148 -> Type) -> Type) -> TyFun [a6989586621679700148] [a6989586621679700148] -> *) (Scanl1Sym1 a6989586621679700148) # | |
type Apply [a6989586621679700148] [a6989586621679700148] (Scanl1Sym1 a6989586621679700148 l0) l1 # | |
type Scanl1Sym2 t t = Scanl1 t t #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700146 (TyFun b6989586621679700147 b6989586621679700147 -> Type) -> Type) (TyFun b6989586621679700147 (TyFun [a6989586621679700146] [b6989586621679700147] -> Type) -> Type) -> *) (ScanrSym0 a6989586621679700146 b6989586621679700147) # | |
type Apply (TyFun a6989586621679700146 (TyFun b6989586621679700147 b6989586621679700147 -> Type) -> Type) (TyFun b6989586621679700147 (TyFun [a6989586621679700146] [b6989586621679700147] -> Type) -> Type) (ScanrSym0 a6989586621679700146 b6989586621679700147) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700146 (TyFun b6989586621679700147 b6989586621679700147 -> Type) -> Type) -> TyFun b6989586621679700147 (TyFun [a6989586621679700146] [b6989586621679700147] -> Type) -> *) (ScanrSym1 a6989586621679700146 b6989586621679700147) # | |
type Apply b6989586621679700147 (TyFun [a6989586621679700146] [b6989586621679700147] -> Type) (ScanrSym1 a6989586621679700146 b6989586621679700147 l0) l1 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700146 (TyFun b6989586621679700147 b6989586621679700147 -> Type) -> Type) -> b6989586621679700147 -> TyFun [a6989586621679700146] [b6989586621679700147] -> *) (ScanrSym2 a6989586621679700146 b6989586621679700147) # | |
type Apply [a6989586621679700146] [b6989586621679700147] (ScanrSym2 a6989586621679700146 b6989586621679700147 l1 l0) l2 # | |
data Scanr1Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700145 (TyFun a6989586621679700145 a6989586621679700145 -> Type) -> Type) (TyFun [a6989586621679700145] [a6989586621679700145] -> Type) -> *) (Scanr1Sym0 a6989586621679700145) # | |
type Apply (TyFun a6989586621679700145 (TyFun a6989586621679700145 a6989586621679700145 -> Type) -> Type) (TyFun [a6989586621679700145] [a6989586621679700145] -> Type) (Scanr1Sym0 a6989586621679700145) l0 # | |
data Scanr1Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700145 (TyFun a6989586621679700145 a6989586621679700145 -> Type) -> Type) -> TyFun [a6989586621679700145] [a6989586621679700145] -> *) (Scanr1Sym1 a6989586621679700145) # | |
type Apply [a6989586621679700145] [a6989586621679700145] (Scanr1Sym1 a6989586621679700145 l0) l1 # | |
type Scanr1Sym2 t t = Scanr1 t t #
data MapAccumLSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun acc6989586621679700142 (TyFun x6989586621679700143 (acc6989586621679700142, y6989586621679700144) -> Type) -> Type) (TyFun acc6989586621679700142 (TyFun [x6989586621679700143] (acc6989586621679700142, [y6989586621679700144]) -> Type) -> Type) -> *) (MapAccumLSym0 x6989586621679700143 acc6989586621679700142 y6989586621679700144) # | |
type Apply (TyFun acc6989586621679700142 (TyFun x6989586621679700143 (acc6989586621679700142, y6989586621679700144) -> Type) -> Type) (TyFun acc6989586621679700142 (TyFun [x6989586621679700143] (acc6989586621679700142, [y6989586621679700144]) -> Type) -> Type) (MapAccumLSym0 x6989586621679700143 acc6989586621679700142 y6989586621679700144) l0 # | |
data MapAccumLSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun acc6989586621679700142 (TyFun x6989586621679700143 (acc6989586621679700142, y6989586621679700144) -> Type) -> Type) -> TyFun acc6989586621679700142 (TyFun [x6989586621679700143] (acc6989586621679700142, [y6989586621679700144]) -> Type) -> *) (MapAccumLSym1 x6989586621679700143 acc6989586621679700142 y6989586621679700144) # | |
type Apply acc6989586621679700142 (TyFun [x6989586621679700143] (acc6989586621679700142, [y6989586621679700144]) -> Type) (MapAccumLSym1 x6989586621679700143 acc6989586621679700142 y6989586621679700144 l0) l1 # | |
data MapAccumLSym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun acc6989586621679700142 (TyFun x6989586621679700143 (acc6989586621679700142, y6989586621679700144) -> Type) -> Type) -> acc6989586621679700142 -> TyFun [x6989586621679700143] (acc6989586621679700142, [y6989586621679700144]) -> *) (MapAccumLSym2 x6989586621679700143 acc6989586621679700142 y6989586621679700144) # | |
type Apply [x6989586621679700143] (acc6989586621679700142, [y6989586621679700144]) (MapAccumLSym2 x6989586621679700143 acc6989586621679700142 y6989586621679700144 l1 l0) l2 # | |
type MapAccumLSym3 t t t = MapAccumL t t t #
data MapAccumRSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun acc6989586621679700139 (TyFun x6989586621679700140 (acc6989586621679700139, y6989586621679700141) -> Type) -> Type) (TyFun acc6989586621679700139 (TyFun [x6989586621679700140] (acc6989586621679700139, [y6989586621679700141]) -> Type) -> Type) -> *) (MapAccumRSym0 x6989586621679700140 acc6989586621679700139 y6989586621679700141) # | |
type Apply (TyFun acc6989586621679700139 (TyFun x6989586621679700140 (acc6989586621679700139, y6989586621679700141) -> Type) -> Type) (TyFun acc6989586621679700139 (TyFun [x6989586621679700140] (acc6989586621679700139, [y6989586621679700141]) -> Type) -> Type) (MapAccumRSym0 x6989586621679700140 acc6989586621679700139 y6989586621679700141) l0 # | |
data MapAccumRSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun acc6989586621679700139 (TyFun x6989586621679700140 (acc6989586621679700139, y6989586621679700141) -> Type) -> Type) -> TyFun acc6989586621679700139 (TyFun [x6989586621679700140] (acc6989586621679700139, [y6989586621679700141]) -> Type) -> *) (MapAccumRSym1 x6989586621679700140 acc6989586621679700139 y6989586621679700141) # | |
type Apply acc6989586621679700139 (TyFun [x6989586621679700140] (acc6989586621679700139, [y6989586621679700141]) -> Type) (MapAccumRSym1 x6989586621679700140 acc6989586621679700139 y6989586621679700141 l0) l1 # | |
data MapAccumRSym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun acc6989586621679700139 (TyFun x6989586621679700140 (acc6989586621679700139, y6989586621679700141) -> Type) -> Type) -> acc6989586621679700139 -> TyFun [x6989586621679700140] (acc6989586621679700139, [y6989586621679700141]) -> *) (MapAccumRSym2 x6989586621679700140 acc6989586621679700139 y6989586621679700141) # | |
type Apply [x6989586621679700140] (acc6989586621679700139, [y6989586621679700141]) (MapAccumRSym2 x6989586621679700140 acc6989586621679700139 y6989586621679700141 l1 l0) l2 # | |
type MapAccumRSym3 t t t = MapAccumR t t t #
data UnfoldrSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun b6989586621679700137 (Maybe (a6989586621679700138, b6989586621679700137)) -> Type) (TyFun b6989586621679700137 [a6989586621679700138] -> Type) -> *) (UnfoldrSym0 b6989586621679700137 a6989586621679700138) # | |
type Apply (TyFun b6989586621679700137 (Maybe (a6989586621679700138, b6989586621679700137)) -> Type) (TyFun b6989586621679700137 [a6989586621679700138] -> Type) (UnfoldrSym0 b6989586621679700137 a6989586621679700138) l0 # | |
data UnfoldrSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679700137 (Maybe (a6989586621679700138, b6989586621679700137)) -> Type) -> TyFun b6989586621679700137 [a6989586621679700138] -> *) (UnfoldrSym1 a6989586621679700138 b6989586621679700137) # | |
type Apply b6989586621679700137 [a6989586621679700138] (UnfoldrSym1 a6989586621679700138 b6989586621679700137 l0) l1 # | |
type UnfoldrSym2 t t = Unfoldr t t #
data IsPrefixOfSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700134] (TyFun [a6989586621679700134] Bool -> Type) -> *) (IsPrefixOfSym0 a6989586621679700134) # | |
type Apply [a6989586621679700134] (TyFun [a6989586621679700134] Bool -> Type) (IsPrefixOfSym0 a6989586621679700134) l0 # | |
data IsPrefixOfSym1 l l #
Instances
SuppressUnusedWarnings ([a6989586621679700134] -> TyFun [a6989586621679700134] Bool -> *) (IsPrefixOfSym1 a6989586621679700134) # | |
type Apply [a6989586621679700134] Bool (IsPrefixOfSym1 a6989586621679700134 l0) l1 # | |
type IsPrefixOfSym2 t t = IsPrefixOf t t #
data IsSuffixOfSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700133] (TyFun [a6989586621679700133] Bool -> Type) -> *) (IsSuffixOfSym0 a6989586621679700133) # | |
type Apply [a6989586621679700133] (TyFun [a6989586621679700133] Bool -> Type) (IsSuffixOfSym0 a6989586621679700133) l0 # | |
data IsSuffixOfSym1 l l #
Instances
SuppressUnusedWarnings ([a6989586621679700133] -> TyFun [a6989586621679700133] Bool -> *) (IsSuffixOfSym1 a6989586621679700133) # | |
type Apply [a6989586621679700133] Bool (IsSuffixOfSym1 a6989586621679700133 l0) l1 # | |
type IsSuffixOfSym2 t t = IsSuffixOf t t #
data IsInfixOfSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700132] (TyFun [a6989586621679700132] Bool -> Type) -> *) (IsInfixOfSym0 a6989586621679700132) # | |
type Apply [a6989586621679700132] (TyFun [a6989586621679700132] Bool -> Type) (IsInfixOfSym0 a6989586621679700132) l0 # | |
data IsInfixOfSym1 l l #
Instances
SuppressUnusedWarnings ([a6989586621679700132] -> TyFun [a6989586621679700132] Bool -> *) (IsInfixOfSym1 a6989586621679700132) # | |
type Apply [a6989586621679700132] Bool (IsInfixOfSym1 a6989586621679700132 l0) l1 # | |
type IsInfixOfSym2 t t = IsInfixOf t t #
data NotElemSym0 l #
Instances
SuppressUnusedWarnings (TyFun a6989586621679700130 (TyFun [a6989586621679700130] Bool -> Type) -> *) (NotElemSym0 a6989586621679700130) # | |
type Apply a6989586621679700130 (TyFun [a6989586621679700130] Bool -> Type) (NotElemSym0 a6989586621679700130) l0 # | |
data NotElemSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679700130 -> TyFun [a6989586621679700130] Bool -> *) (NotElemSym1 a6989586621679700130) # | |
type Apply [a6989586621679700130] Bool (NotElemSym1 a6989586621679700130 l0) l1 # | |
type NotElemSym2 t t = NotElem t t #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700128] (TyFun [b6989586621679700129] [(a6989586621679700128, b6989586621679700129)] -> Type) -> *) (ZipSym0 a6989586621679700128 b6989586621679700129) # | |
type Apply [a6989586621679700128] (TyFun [b6989586621679700129] [(a6989586621679700128, b6989586621679700129)] -> Type) (ZipSym0 a6989586621679700128 b6989586621679700129) l0 # | |
Instances
SuppressUnusedWarnings ([a6989586621679700128] -> TyFun [b6989586621679700129] [(a6989586621679700128, b6989586621679700129)] -> *) (ZipSym1 b6989586621679700129 a6989586621679700128) # | |
type Apply [b6989586621679700129] [(a6989586621679700128, b6989586621679700129)] (ZipSym1 b6989586621679700129 a6989586621679700128 l0) l1 # | |
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700125] (TyFun [b6989586621679700126] (TyFun [c6989586621679700127] [(a6989586621679700125, b6989586621679700126, c6989586621679700127)] -> Type) -> Type) -> *) (Zip3Sym0 a6989586621679700125 b6989586621679700126 c6989586621679700127) # | |
type Apply [a6989586621679700125] (TyFun [b6989586621679700126] (TyFun [c6989586621679700127] [(a6989586621679700125, b6989586621679700126, c6989586621679700127)] -> Type) -> Type) (Zip3Sym0 a6989586621679700125 b6989586621679700126 c6989586621679700127) l0 # | |
Instances
SuppressUnusedWarnings ([a6989586621679700125] -> TyFun [b6989586621679700126] (TyFun [c6989586621679700127] [(a6989586621679700125, b6989586621679700126, c6989586621679700127)] -> Type) -> *) (Zip3Sym1 b6989586621679700126 c6989586621679700127 a6989586621679700125) # | |
type Apply [b6989586621679700126] (TyFun [c6989586621679700127] [(a6989586621679700125, b6989586621679700126, c6989586621679700127)] -> Type) (Zip3Sym1 b6989586621679700126 c6989586621679700127 a6989586621679700125 l0) l1 # | |
Instances
SuppressUnusedWarnings ([a6989586621679700125] -> [b6989586621679700126] -> TyFun [c6989586621679700127] [(a6989586621679700125, b6989586621679700126, c6989586621679700127)] -> *) (Zip3Sym2 c6989586621679700127 b6989586621679700126 a6989586621679700125) # | |
type Apply [c6989586621679700127] [(a6989586621679700125, b6989586621679700126, c6989586621679700127)] (Zip3Sym2 c6989586621679700127 b6989586621679700126 a6989586621679700125 l1 l0) l2 # | |
data ZipWithSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700122 (TyFun b6989586621679700123 c6989586621679700124 -> Type) -> Type) (TyFun [a6989586621679700122] (TyFun [b6989586621679700123] [c6989586621679700124] -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679700122 b6989586621679700123 c6989586621679700124) # | |
type Apply (TyFun a6989586621679700122 (TyFun b6989586621679700123 c6989586621679700124 -> Type) -> Type) (TyFun [a6989586621679700122] (TyFun [b6989586621679700123] [c6989586621679700124] -> Type) -> Type) (ZipWithSym0 a6989586621679700122 b6989586621679700123 c6989586621679700124) l0 # | |
data ZipWithSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700122 (TyFun b6989586621679700123 c6989586621679700124 -> Type) -> Type) -> TyFun [a6989586621679700122] (TyFun [b6989586621679700123] [c6989586621679700124] -> Type) -> *) (ZipWithSym1 a6989586621679700122 b6989586621679700123 c6989586621679700124) # | |
type Apply [a6989586621679700122] (TyFun [b6989586621679700123] [c6989586621679700124] -> Type) (ZipWithSym1 a6989586621679700122 b6989586621679700123 c6989586621679700124 l0) l1 # | |
data ZipWithSym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700122 (TyFun b6989586621679700123 c6989586621679700124 -> Type) -> Type) -> [a6989586621679700122] -> TyFun [b6989586621679700123] [c6989586621679700124] -> *) (ZipWithSym2 a6989586621679700122 b6989586621679700123 c6989586621679700124) # | |
type Apply [b6989586621679700123] [c6989586621679700124] (ZipWithSym2 a6989586621679700122 b6989586621679700123 c6989586621679700124 l1 l0) l2 # | |
type ZipWithSym3 t t t = ZipWith t t t #
data ZipWith3Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700118 (TyFun b6989586621679700119 (TyFun c6989586621679700120 d6989586621679700121 -> Type) -> Type) -> Type) (TyFun [a6989586621679700118] (TyFun [b6989586621679700119] (TyFun [c6989586621679700120] [d6989586621679700121] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) # | |
type Apply (TyFun a6989586621679700118 (TyFun b6989586621679700119 (TyFun c6989586621679700120 d6989586621679700121 -> Type) -> Type) -> Type) (TyFun [a6989586621679700118] (TyFun [b6989586621679700119] (TyFun [c6989586621679700120] [d6989586621679700121] -> Type) -> Type) -> Type) (ZipWith3Sym0 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) l0 # | |
data ZipWith3Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700118 (TyFun b6989586621679700119 (TyFun c6989586621679700120 d6989586621679700121 -> Type) -> Type) -> Type) -> TyFun [a6989586621679700118] (TyFun [b6989586621679700119] (TyFun [c6989586621679700120] [d6989586621679700121] -> Type) -> Type) -> *) (ZipWith3Sym1 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) # | |
type Apply [a6989586621679700118] (TyFun [b6989586621679700119] (TyFun [c6989586621679700120] [d6989586621679700121] -> Type) -> Type) (ZipWith3Sym1 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121 l0) l1 # | |
data ZipWith3Sym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700118 (TyFun b6989586621679700119 (TyFun c6989586621679700120 d6989586621679700121 -> Type) -> Type) -> Type) -> [a6989586621679700118] -> TyFun [b6989586621679700119] (TyFun [c6989586621679700120] [d6989586621679700121] -> Type) -> *) (ZipWith3Sym2 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) # | |
type Apply [b6989586621679700119] (TyFun [c6989586621679700120] [d6989586621679700121] -> Type) (ZipWith3Sym2 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121 l1 l0) l2 # | |
data ZipWith3Sym3 l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700118 (TyFun b6989586621679700119 (TyFun c6989586621679700120 d6989586621679700121 -> Type) -> Type) -> Type) -> [a6989586621679700118] -> [b6989586621679700119] -> TyFun [c6989586621679700120] [d6989586621679700121] -> *) (ZipWith3Sym3 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121) # | |
type Apply [c6989586621679700120] [d6989586621679700121] (ZipWith3Sym3 a6989586621679700118 b6989586621679700119 c6989586621679700120 d6989586621679700121 l2 l1 l0) l3 # | |
type ZipWith3Sym4 t t t t = ZipWith3 t t t t #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679700116, b6989586621679700117)] ([a6989586621679700116], [b6989586621679700117]) -> *) (UnzipSym0 a6989586621679700116 b6989586621679700117) # | |
type Apply [(a6989586621679700116, b6989586621679700117)] ([a6989586621679700116], [b6989586621679700117]) (UnzipSym0 a6989586621679700116 b6989586621679700117) l0 # | |
data Unzip3Sym0 l #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679700113, b6989586621679700114, c6989586621679700115)] ([a6989586621679700113], [b6989586621679700114], [c6989586621679700115]) -> *) (Unzip3Sym0 a6989586621679700113 b6989586621679700114 c6989586621679700115) # | |
type Apply [(a6989586621679700113, b6989586621679700114, c6989586621679700115)] ([a6989586621679700113], [b6989586621679700114], [c6989586621679700115]) (Unzip3Sym0 a6989586621679700113 b6989586621679700114 c6989586621679700115) l0 # | |
type Unzip3Sym1 t = Unzip3 t #
data Unzip4Sym0 l #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679700109, b6989586621679700110, c6989586621679700111, d6989586621679700112)] ([a6989586621679700109], [b6989586621679700110], [c6989586621679700111], [d6989586621679700112]) -> *) (Unzip4Sym0 a6989586621679700109 b6989586621679700110 c6989586621679700111 d6989586621679700112) # | |
type Apply [(a6989586621679700109, b6989586621679700110, c6989586621679700111, d6989586621679700112)] ([a6989586621679700109], [b6989586621679700110], [c6989586621679700111], [d6989586621679700112]) (Unzip4Sym0 a6989586621679700109 b6989586621679700110 c6989586621679700111 d6989586621679700112) l0 # | |
type Unzip4Sym1 t = Unzip4 t #
data Unzip5Sym0 l #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679700104, b6989586621679700105, c6989586621679700106, d6989586621679700107, e6989586621679700108)] ([a6989586621679700104], [b6989586621679700105], [c6989586621679700106], [d6989586621679700107], [e6989586621679700108]) -> *) (Unzip5Sym0 a6989586621679700104 b6989586621679700105 c6989586621679700106 d6989586621679700107 e6989586621679700108) # | |
type Apply [(a6989586621679700104, b6989586621679700105, c6989586621679700106, d6989586621679700107, e6989586621679700108)] ([a6989586621679700104], [b6989586621679700105], [c6989586621679700106], [d6989586621679700107], [e6989586621679700108]) (Unzip5Sym0 a6989586621679700104 b6989586621679700105 c6989586621679700106 d6989586621679700107 e6989586621679700108) l0 # | |
type Unzip5Sym1 t = Unzip5 t #
data Unzip6Sym0 l #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679700098, b6989586621679700099, c6989586621679700100, d6989586621679700101, e6989586621679700102, f6989586621679700103)] ([a6989586621679700098], [b6989586621679700099], [c6989586621679700100], [d6989586621679700101], [e6989586621679700102], [f6989586621679700103]) -> *) (Unzip6Sym0 a6989586621679700098 b6989586621679700099 c6989586621679700100 d6989586621679700101 e6989586621679700102 f6989586621679700103) # | |
type Apply [(a6989586621679700098, b6989586621679700099, c6989586621679700100, d6989586621679700101, e6989586621679700102, f6989586621679700103)] ([a6989586621679700098], [b6989586621679700099], [c6989586621679700100], [d6989586621679700101], [e6989586621679700102], [f6989586621679700103]) (Unzip6Sym0 a6989586621679700098 b6989586621679700099 c6989586621679700100 d6989586621679700101 e6989586621679700102 f6989586621679700103) l0 # | |
type Unzip6Sym1 t = Unzip6 t #
data Unzip7Sym0 l #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679700091, b6989586621679700092, c6989586621679700093, d6989586621679700094, e6989586621679700095, f6989586621679700096, g6989586621679700097)] ([a6989586621679700091], [b6989586621679700092], [c6989586621679700093], [d6989586621679700094], [e6989586621679700095], [f6989586621679700096], [g6989586621679700097]) -> *) (Unzip7Sym0 a6989586621679700091 b6989586621679700092 c6989586621679700093 d6989586621679700094 e6989586621679700095 f6989586621679700096 g6989586621679700097) # | |
type Apply [(a6989586621679700091, b6989586621679700092, c6989586621679700093, d6989586621679700094, e6989586621679700095, f6989586621679700096, g6989586621679700097)] ([a6989586621679700091], [b6989586621679700092], [c6989586621679700093], [d6989586621679700094], [e6989586621679700095], [f6989586621679700096], [g6989586621679700097]) (Unzip7Sym0 a6989586621679700091 b6989586621679700092 c6989586621679700093 d6989586621679700094 e6989586621679700095 f6989586621679700096 g6989586621679700097) l0 # | |
type Unzip7Sym1 t = Unzip7 t #
data DeleteSym0 l #
Instances
SuppressUnusedWarnings (TyFun a6989586621679700090 (TyFun [a6989586621679700090] [a6989586621679700090] -> Type) -> *) (DeleteSym0 a6989586621679700090) # | |
type Apply a6989586621679700090 (TyFun [a6989586621679700090] [a6989586621679700090] -> Type) (DeleteSym0 a6989586621679700090) l0 # | |
data DeleteSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679700090 -> TyFun [a6989586621679700090] [a6989586621679700090] -> *) (DeleteSym1 a6989586621679700090) # | |
type Apply [a6989586621679700090] [a6989586621679700090] (DeleteSym1 a6989586621679700090 l0) l1 # | |
type DeleteSym2 t t = Delete t t #
data IntersectSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700076] (TyFun [a6989586621679700076] [a6989586621679700076] -> Type) -> *) (IntersectSym0 a6989586621679700076) # | |
type Apply [a6989586621679700076] (TyFun [a6989586621679700076] [a6989586621679700076] -> Type) (IntersectSym0 a6989586621679700076) l0 # | |
data IntersectSym1 l l #
Instances
SuppressUnusedWarnings ([a6989586621679700076] -> TyFun [a6989586621679700076] [a6989586621679700076] -> *) (IntersectSym1 a6989586621679700076) # | |
type Apply [a6989586621679700076] [a6989586621679700076] (IntersectSym1 a6989586621679700076 l0) l1 # | |
type IntersectSym2 t t = Intersect t t #
data InsertSym0 l #
Instances
SuppressUnusedWarnings (TyFun a6989586621679700063 (TyFun [a6989586621679700063] [a6989586621679700063] -> Type) -> *) (InsertSym0 a6989586621679700063) # | |
type Apply a6989586621679700063 (TyFun [a6989586621679700063] [a6989586621679700063] -> Type) (InsertSym0 a6989586621679700063) l0 # | |
data InsertSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679700063 -> TyFun [a6989586621679700063] [a6989586621679700063] -> *) (InsertSym1 a6989586621679700063) # | |
type Apply [a6989586621679700063] [a6989586621679700063] (InsertSym1 a6989586621679700063 l0) l1 # | |
type InsertSym2 t t = Insert t t #
data DeleteBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700088 (TyFun a6989586621679700088 Bool -> Type) -> Type) (TyFun a6989586621679700088 (TyFun [a6989586621679700088] [a6989586621679700088] -> Type) -> Type) -> *) (DeleteBySym0 a6989586621679700088) # | |
type Apply (TyFun a6989586621679700088 (TyFun a6989586621679700088 Bool -> Type) -> Type) (TyFun a6989586621679700088 (TyFun [a6989586621679700088] [a6989586621679700088] -> Type) -> Type) (DeleteBySym0 a6989586621679700088) l0 # | |
data DeleteBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700088 (TyFun a6989586621679700088 Bool -> Type) -> Type) -> TyFun a6989586621679700088 (TyFun [a6989586621679700088] [a6989586621679700088] -> Type) -> *) (DeleteBySym1 a6989586621679700088) # | |
type Apply a6989586621679700088 (TyFun [a6989586621679700088] [a6989586621679700088] -> Type) (DeleteBySym1 a6989586621679700088 l0) l1 # | |
data DeleteBySym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700088 (TyFun a6989586621679700088 Bool -> Type) -> Type) -> a6989586621679700088 -> TyFun [a6989586621679700088] [a6989586621679700088] -> *) (DeleteBySym2 a6989586621679700088) # | |
type Apply [a6989586621679700088] [a6989586621679700088] (DeleteBySym2 a6989586621679700088 l1 l0) l2 # | |
type DeleteBySym3 t t t = DeleteBy t t t #
data DeleteFirstsBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700087 (TyFun a6989586621679700087 Bool -> Type) -> Type) (TyFun [a6989586621679700087] (TyFun [a6989586621679700087] [a6989586621679700087] -> Type) -> Type) -> *) (DeleteFirstsBySym0 a6989586621679700087) # | |
type Apply (TyFun a6989586621679700087 (TyFun a6989586621679700087 Bool -> Type) -> Type) (TyFun [a6989586621679700087] (TyFun [a6989586621679700087] [a6989586621679700087] -> Type) -> Type) (DeleteFirstsBySym0 a6989586621679700087) l0 # | |
data DeleteFirstsBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700087 (TyFun a6989586621679700087 Bool -> Type) -> Type) -> TyFun [a6989586621679700087] (TyFun [a6989586621679700087] [a6989586621679700087] -> Type) -> *) (DeleteFirstsBySym1 a6989586621679700087) # | |
type Apply [a6989586621679700087] (TyFun [a6989586621679700087] [a6989586621679700087] -> Type) (DeleteFirstsBySym1 a6989586621679700087 l0) l1 # | |
data DeleteFirstsBySym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700087 (TyFun a6989586621679700087 Bool -> Type) -> Type) -> [a6989586621679700087] -> TyFun [a6989586621679700087] [a6989586621679700087] -> *) (DeleteFirstsBySym2 a6989586621679700087) # | |
type Apply [a6989586621679700087] [a6989586621679700087] (DeleteFirstsBySym2 a6989586621679700087 l1 l0) l2 # | |
type DeleteFirstsBySym3 t t t = DeleteFirstsBy t t t #
data IntersectBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700075 (TyFun a6989586621679700075 Bool -> Type) -> Type) (TyFun [a6989586621679700075] (TyFun [a6989586621679700075] [a6989586621679700075] -> Type) -> Type) -> *) (IntersectBySym0 a6989586621679700075) # | |
type Apply (TyFun a6989586621679700075 (TyFun a6989586621679700075 Bool -> Type) -> Type) (TyFun [a6989586621679700075] (TyFun [a6989586621679700075] [a6989586621679700075] -> Type) -> Type) (IntersectBySym0 a6989586621679700075) l0 # | |
data IntersectBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700075 (TyFun a6989586621679700075 Bool -> Type) -> Type) -> TyFun [a6989586621679700075] (TyFun [a6989586621679700075] [a6989586621679700075] -> Type) -> *) (IntersectBySym1 a6989586621679700075) # | |
type Apply [a6989586621679700075] (TyFun [a6989586621679700075] [a6989586621679700075] -> Type) (IntersectBySym1 a6989586621679700075 l0) l1 # | |
data IntersectBySym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700075 (TyFun a6989586621679700075 Bool -> Type) -> Type) -> [a6989586621679700075] -> TyFun [a6989586621679700075] [a6989586621679700075] -> *) (IntersectBySym2 a6989586621679700075) # | |
type Apply [a6989586621679700075] [a6989586621679700075] (IntersectBySym2 a6989586621679700075 l1 l0) l2 # | |
data SortBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700086 (TyFun a6989586621679700086 Ordering -> Type) -> Type) (TyFun [a6989586621679700086] [a6989586621679700086] -> Type) -> *) (SortBySym0 a6989586621679700086) # | |
type Apply (TyFun a6989586621679700086 (TyFun a6989586621679700086 Ordering -> Type) -> Type) (TyFun [a6989586621679700086] [a6989586621679700086] -> Type) (SortBySym0 a6989586621679700086) l0 # | |
data SortBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700086 (TyFun a6989586621679700086 Ordering -> Type) -> Type) -> TyFun [a6989586621679700086] [a6989586621679700086] -> *) (SortBySym1 a6989586621679700086) # | |
type Apply [a6989586621679700086] [a6989586621679700086] (SortBySym1 a6989586621679700086 l0) l1 # | |
type SortBySym2 t t = SortBy t t #
data InsertBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700085 (TyFun a6989586621679700085 Ordering -> Type) -> Type) (TyFun a6989586621679700085 (TyFun [a6989586621679700085] [a6989586621679700085] -> Type) -> Type) -> *) (InsertBySym0 a6989586621679700085) # | |
type Apply (TyFun a6989586621679700085 (TyFun a6989586621679700085 Ordering -> Type) -> Type) (TyFun a6989586621679700085 (TyFun [a6989586621679700085] [a6989586621679700085] -> Type) -> Type) (InsertBySym0 a6989586621679700085) l0 # | |
data InsertBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700085 (TyFun a6989586621679700085 Ordering -> Type) -> Type) -> TyFun a6989586621679700085 (TyFun [a6989586621679700085] [a6989586621679700085] -> Type) -> *) (InsertBySym1 a6989586621679700085) # | |
type Apply a6989586621679700085 (TyFun [a6989586621679700085] [a6989586621679700085] -> Type) (InsertBySym1 a6989586621679700085 l0) l1 # | |
data InsertBySym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700085 (TyFun a6989586621679700085 Ordering -> Type) -> Type) -> a6989586621679700085 -> TyFun [a6989586621679700085] [a6989586621679700085] -> *) (InsertBySym2 a6989586621679700085) # | |
type Apply [a6989586621679700085] [a6989586621679700085] (InsertBySym2 a6989586621679700085 l1 l0) l2 # | |
type InsertBySym3 t t t = InsertBy t t t #
data MaximumBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700084 (TyFun a6989586621679700084 Ordering -> Type) -> Type) (TyFun [a6989586621679700084] a6989586621679700084 -> Type) -> *) (MaximumBySym0 a6989586621679700084) # | |
type Apply (TyFun a6989586621679700084 (TyFun a6989586621679700084 Ordering -> Type) -> Type) (TyFun [a6989586621679700084] a6989586621679700084 -> Type) (MaximumBySym0 a6989586621679700084) l0 # | |
data MaximumBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700084 (TyFun a6989586621679700084 Ordering -> Type) -> Type) -> TyFun [a6989586621679700084] a6989586621679700084 -> *) (MaximumBySym1 a6989586621679700084) # | |
type Apply [a6989586621679700084] a6989586621679700084 (MaximumBySym1 a6989586621679700084 l0) l1 # | |
type MaximumBySym2 t t = MaximumBy t t #
data MinimumBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700083 (TyFun a6989586621679700083 Ordering -> Type) -> Type) (TyFun [a6989586621679700083] a6989586621679700083 -> Type) -> *) (MinimumBySym0 a6989586621679700083) # | |
type Apply (TyFun a6989586621679700083 (TyFun a6989586621679700083 Ordering -> Type) -> Type) (TyFun [a6989586621679700083] a6989586621679700083 -> Type) (MinimumBySym0 a6989586621679700083) l0 # | |
data MinimumBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700083 (TyFun a6989586621679700083 Ordering -> Type) -> Type) -> TyFun [a6989586621679700083] a6989586621679700083 -> *) (MinimumBySym1 a6989586621679700083) # | |
type Apply [a6989586621679700083] a6989586621679700083 (MinimumBySym1 a6989586621679700083 l0) l1 # | |
type MinimumBySym2 t t = MinimumBy t t #
data LengthSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700054] Nat -> *) (LengthSym0 a6989586621679700054) # | |
type Apply [a6989586621679700054] Nat (LengthSym0 a6989586621679700054) l0 # | |
type LengthSym1 t = Length t #
data ProductSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700055] a6989586621679700055 -> *) (ProductSym0 a6989586621679700055) # | |
type Apply [a6989586621679700055] a6989586621679700055 (ProductSym0 a6989586621679700055) l0 # | |
type ProductSym1 t = Product t #
data ReplicateSym0 l #
Instances
SuppressUnusedWarnings (TyFun Nat (TyFun a6989586621679700053 [a6989586621679700053] -> Type) -> *) (ReplicateSym0 a6989586621679700053) # | |
type Apply Nat (TyFun a6989586621679700053 [a6989586621679700053] -> Type) (ReplicateSym0 a6989586621679700053) l0 # | |
data ReplicateSym1 l l #
Instances
SuppressUnusedWarnings (Nat -> TyFun a6989586621679700053 [a6989586621679700053] -> *) (ReplicateSym1 a6989586621679700053) # | |
type Apply a6989586621679700053 [a6989586621679700053] (ReplicateSym1 a6989586621679700053 l0) l1 # | |
type ReplicateSym2 t t = Replicate t t #
data TransposeSym0 l #
Instances
SuppressUnusedWarnings (TyFun [[a6989586621679700052]] [[a6989586621679700052]] -> *) (TransposeSym0 a6989586621679700052) # | |
type Apply [[a6989586621679700052]] [[a6989586621679700052]] (TransposeSym0 a6989586621679700052) l0 # | |
type TransposeSym1 t = Transpose t #
data SplitAtSym0 l #
Instances
SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679700067] ([a6989586621679700067], [a6989586621679700067]) -> Type) -> *) (SplitAtSym0 a6989586621679700067) # | |
type Apply Nat (TyFun [a6989586621679700067] ([a6989586621679700067], [a6989586621679700067]) -> Type) (SplitAtSym0 a6989586621679700067) l0 # | |
data SplitAtSym1 l l #
Instances
SuppressUnusedWarnings (Nat -> TyFun [a6989586621679700067] ([a6989586621679700067], [a6989586621679700067]) -> *) (SplitAtSym1 a6989586621679700067) # | |
type Apply [a6989586621679700067] ([a6989586621679700067], [a6989586621679700067]) (SplitAtSym1 a6989586621679700067 l0) l1 # | |
type SplitAtSym2 t t = SplitAt t t #
data TakeWhileSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700074 Bool -> Type) (TyFun [a6989586621679700074] [a6989586621679700074] -> Type) -> *) (TakeWhileSym0 a6989586621679700074) # | |
type Apply (TyFun a6989586621679700074 Bool -> Type) (TyFun [a6989586621679700074] [a6989586621679700074] -> Type) (TakeWhileSym0 a6989586621679700074) l0 # | |
data TakeWhileSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700074 Bool -> Type) -> TyFun [a6989586621679700074] [a6989586621679700074] -> *) (TakeWhileSym1 a6989586621679700074) # | |
type Apply [a6989586621679700074] [a6989586621679700074] (TakeWhileSym1 a6989586621679700074 l0) l1 # | |
type TakeWhileSym2 t t = TakeWhile t t #
data DropWhileSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700073 Bool -> Type) (TyFun [a6989586621679700073] [a6989586621679700073] -> Type) -> *) (DropWhileSym0 a6989586621679700073) # | |
type Apply (TyFun a6989586621679700073 Bool -> Type) (TyFun [a6989586621679700073] [a6989586621679700073] -> Type) (DropWhileSym0 a6989586621679700073) l0 # | |
data DropWhileSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700073 Bool -> Type) -> TyFun [a6989586621679700073] [a6989586621679700073] -> *) (DropWhileSym1 a6989586621679700073) # | |
type Apply [a6989586621679700073] [a6989586621679700073] (DropWhileSym1 a6989586621679700073 l0) l1 # | |
type DropWhileSym2 t t = DropWhile t t #
data DropWhileEndSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700072 Bool -> Type) (TyFun [a6989586621679700072] [a6989586621679700072] -> Type) -> *) (DropWhileEndSym0 a6989586621679700072) # | |
type Apply (TyFun a6989586621679700072 Bool -> Type) (TyFun [a6989586621679700072] [a6989586621679700072] -> Type) (DropWhileEndSym0 a6989586621679700072) l0 # | |
data DropWhileEndSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700072 Bool -> Type) -> TyFun [a6989586621679700072] [a6989586621679700072] -> *) (DropWhileEndSym1 a6989586621679700072) # | |
type Apply [a6989586621679700072] [a6989586621679700072] (DropWhileEndSym1 a6989586621679700072 l0) l1 # | |
type DropWhileEndSym2 t t = DropWhileEnd t t #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700071 Bool -> Type) (TyFun [a6989586621679700071] ([a6989586621679700071], [a6989586621679700071]) -> Type) -> *) (SpanSym0 a6989586621679700071) # | |
type Apply (TyFun a6989586621679700071 Bool -> Type) (TyFun [a6989586621679700071] ([a6989586621679700071], [a6989586621679700071]) -> Type) (SpanSym0 a6989586621679700071) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700071 Bool -> Type) -> TyFun [a6989586621679700071] ([a6989586621679700071], [a6989586621679700071]) -> *) (SpanSym1 a6989586621679700071) # | |
type Apply [a6989586621679700071] ([a6989586621679700071], [a6989586621679700071]) (SpanSym1 a6989586621679700071 l0) l1 # | |
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700070 Bool -> Type) (TyFun [a6989586621679700070] ([a6989586621679700070], [a6989586621679700070]) -> Type) -> *) (BreakSym0 a6989586621679700070) # | |
type Apply (TyFun a6989586621679700070 Bool -> Type) (TyFun [a6989586621679700070] ([a6989586621679700070], [a6989586621679700070]) -> Type) (BreakSym0 a6989586621679700070) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700070 Bool -> Type) -> TyFun [a6989586621679700070] ([a6989586621679700070], [a6989586621679700070]) -> *) (BreakSym1 a6989586621679700070) # | |
type Apply [a6989586621679700070] ([a6989586621679700070], [a6989586621679700070]) (BreakSym1 a6989586621679700070 l0) l1 # | |
data StripPrefixSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679923077] (TyFun [a6989586621679923077] (Maybe [a6989586621679923077]) -> Type) -> *) (StripPrefixSym0 a6989586621679923077) # | |
type Apply [a6989586621679923077] (TyFun [a6989586621679923077] (Maybe [a6989586621679923077]) -> Type) (StripPrefixSym0 a6989586621679923077) l0 # | |
data StripPrefixSym1 l l #
Instances
SuppressUnusedWarnings ([a6989586621679923077] -> TyFun [a6989586621679923077] (Maybe [a6989586621679923077]) -> *) (StripPrefixSym1 a6989586621679923077) # | |
type Apply [a6989586621679923077] (Maybe [a6989586621679923077]) (StripPrefixSym1 a6989586621679923077 l0) l1 # | |
type StripPrefixSym2 t t = StripPrefix t t #
data MaximumSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700065] a6989586621679700065 -> *) (MaximumSym0 a6989586621679700065) # | |
type Apply [a6989586621679700065] a6989586621679700065 (MaximumSym0 a6989586621679700065) l0 # | |
type MaximumSym1 t = Maximum t #
data MinimumSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700064] a6989586621679700064 -> *) (MinimumSym0 a6989586621679700064) # | |
type Apply [a6989586621679700064] a6989586621679700064 (MinimumSym0 a6989586621679700064) l0 # | |
type MinimumSym1 t = Minimum t #
data GroupBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700061 (TyFun a6989586621679700061 Bool -> Type) -> Type) (TyFun [a6989586621679700061] [[a6989586621679700061]] -> Type) -> *) (GroupBySym0 a6989586621679700061) # | |
type Apply (TyFun a6989586621679700061 (TyFun a6989586621679700061 Bool -> Type) -> Type) (TyFun [a6989586621679700061] [[a6989586621679700061]] -> Type) (GroupBySym0 a6989586621679700061) l0 # | |
data GroupBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700061 (TyFun a6989586621679700061 Bool -> Type) -> Type) -> TyFun [a6989586621679700061] [[a6989586621679700061]] -> *) (GroupBySym1 a6989586621679700061) # | |
type Apply [a6989586621679700061] [[a6989586621679700061]] (GroupBySym1 a6989586621679700061 l0) l1 # | |
type GroupBySym2 t t = GroupBy t t #
data LookupSym0 l #
Instances
SuppressUnusedWarnings (TyFun a6989586621679700059 (TyFun [(a6989586621679700059, b6989586621679700060)] (Maybe b6989586621679700060) -> Type) -> *) (LookupSym0 a6989586621679700059 b6989586621679700060) # | |
type Apply a6989586621679700059 (TyFun [(a6989586621679700059, b6989586621679700060)] (Maybe b6989586621679700060) -> Type) (LookupSym0 a6989586621679700059 b6989586621679700060) l0 # | |
data LookupSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679700059 -> TyFun [(a6989586621679700059, b6989586621679700060)] (Maybe b6989586621679700060) -> *) (LookupSym1 b6989586621679700060 a6989586621679700059) # | |
type Apply [(a6989586621679700059, b6989586621679700060)] (Maybe b6989586621679700060) (LookupSym1 b6989586621679700060 a6989586621679700059 l0) l1 # | |
type LookupSym2 t t = Lookup t t #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700081 Bool -> Type) (TyFun [a6989586621679700081] (Maybe a6989586621679700081) -> Type) -> *) (FindSym0 a6989586621679700081) # | |
type Apply (TyFun a6989586621679700081 Bool -> Type) (TyFun [a6989586621679700081] (Maybe a6989586621679700081) -> Type) (FindSym0 a6989586621679700081) l0 # | |
data FilterSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700082 Bool -> Type) (TyFun [a6989586621679700082] [a6989586621679700082] -> Type) -> *) (FilterSym0 a6989586621679700082) # | |
type Apply (TyFun a6989586621679700082 Bool -> Type) (TyFun [a6989586621679700082] [a6989586621679700082] -> Type) (FilterSym0 a6989586621679700082) l0 # | |
data FilterSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700082 Bool -> Type) -> TyFun [a6989586621679700082] [a6989586621679700082] -> *) (FilterSym1 a6989586621679700082) # | |
type Apply [a6989586621679700082] [a6989586621679700082] (FilterSym1 a6989586621679700082 l0) l1 # | |
type FilterSym2 t t = Filter t t #
data PartitionSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700058 Bool -> Type) (TyFun [a6989586621679700058] ([a6989586621679700058], [a6989586621679700058]) -> Type) -> *) (PartitionSym0 a6989586621679700058) # | |
type Apply (TyFun a6989586621679700058 Bool -> Type) (TyFun [a6989586621679700058] ([a6989586621679700058], [a6989586621679700058]) -> Type) (PartitionSym0 a6989586621679700058) l0 # | |
data PartitionSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700058 Bool -> Type) -> TyFun [a6989586621679700058] ([a6989586621679700058], [a6989586621679700058]) -> *) (PartitionSym1 a6989586621679700058) # | |
type Apply [a6989586621679700058] ([a6989586621679700058], [a6989586621679700058]) (PartitionSym1 a6989586621679700058 l0) l1 # | |
type PartitionSym2 t t = Partition t t #
data ElemIndexSym0 l #
data ElemIndexSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679700080 -> TyFun [a6989586621679700080] (Maybe Nat) -> *) (ElemIndexSym1 a6989586621679700080) # | |
type Apply [a6989586621679700080] (Maybe Nat) (ElemIndexSym1 a6989586621679700080 l0) l1 # | |
type ElemIndexSym2 t t = ElemIndex t t #
data ElemIndicesSym0 l #
Instances
SuppressUnusedWarnings (TyFun a6989586621679700079 (TyFun [a6989586621679700079] [Nat] -> Type) -> *) (ElemIndicesSym0 a6989586621679700079) # | |
type Apply a6989586621679700079 (TyFun [a6989586621679700079] [Nat] -> Type) (ElemIndicesSym0 a6989586621679700079) l0 # | |
data ElemIndicesSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679700079 -> TyFun [a6989586621679700079] [Nat] -> *) (ElemIndicesSym1 a6989586621679700079) # | |
type Apply [a6989586621679700079] [Nat] (ElemIndicesSym1 a6989586621679700079 l0) l1 # | |
type ElemIndicesSym2 t t = ElemIndices t t #
data FindIndexSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700078 Bool -> Type) (TyFun [a6989586621679700078] (Maybe Nat) -> Type) -> *) (FindIndexSym0 a6989586621679700078) # | |
type Apply (TyFun a6989586621679700078 Bool -> Type) (TyFun [a6989586621679700078] (Maybe Nat) -> Type) (FindIndexSym0 a6989586621679700078) l0 # | |
data FindIndexSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700078 Bool -> Type) -> TyFun [a6989586621679700078] (Maybe Nat) -> *) (FindIndexSym1 a6989586621679700078) # | |
type Apply [a6989586621679700078] (Maybe Nat) (FindIndexSym1 a6989586621679700078 l0) l1 # | |
type FindIndexSym2 t t = FindIndex t t #
data FindIndicesSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700077 Bool -> Type) (TyFun [a6989586621679700077] [Nat] -> Type) -> *) (FindIndicesSym0 a6989586621679700077) # | |
type Apply (TyFun a6989586621679700077 Bool -> Type) (TyFun [a6989586621679700077] [Nat] -> Type) (FindIndicesSym0 a6989586621679700077) l0 # | |
data FindIndicesSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700077 Bool -> Type) -> TyFun [a6989586621679700077] [Nat] -> *) (FindIndicesSym1 a6989586621679700077) # | |
type Apply [a6989586621679700077] [Nat] (FindIndicesSym1 a6989586621679700077 l0) l1 # | |
type FindIndicesSym2 t t = FindIndices t t #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679923073] (TyFun [b6989586621679923074] (TyFun [c6989586621679923075] (TyFun [d6989586621679923076] [(a6989586621679923073, b6989586621679923074, c6989586621679923075, d6989586621679923076)] -> Type) -> Type) -> Type) -> *) (Zip4Sym0 a6989586621679923073 b6989586621679923074 c6989586621679923075 d6989586621679923076) # | |
type Apply [a6989586621679923073] (TyFun [b6989586621679923074] (TyFun [c6989586621679923075] (TyFun [d6989586621679923076] [(a6989586621679923073, b6989586621679923074, c6989586621679923075, d6989586621679923076)] -> Type) -> Type) -> Type) (Zip4Sym0 a6989586621679923073 b6989586621679923074 c6989586621679923075 d6989586621679923076) l0 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923073] -> TyFun [b6989586621679923074] (TyFun [c6989586621679923075] (TyFun [d6989586621679923076] [(a6989586621679923073, b6989586621679923074, c6989586621679923075, d6989586621679923076)] -> Type) -> Type) -> *) (Zip4Sym1 b6989586621679923074 c6989586621679923075 d6989586621679923076 a6989586621679923073) # | |
type Apply [b6989586621679923074] (TyFun [c6989586621679923075] (TyFun [d6989586621679923076] [(a6989586621679923073, b6989586621679923074, c6989586621679923075, d6989586621679923076)] -> Type) -> Type) (Zip4Sym1 b6989586621679923074 c6989586621679923075 d6989586621679923076 a6989586621679923073 l0) l1 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923073] -> [b6989586621679923074] -> TyFun [c6989586621679923075] (TyFun [d6989586621679923076] [(a6989586621679923073, b6989586621679923074, c6989586621679923075, d6989586621679923076)] -> Type) -> *) (Zip4Sym2 c6989586621679923075 d6989586621679923076 b6989586621679923074 a6989586621679923073) # | |
type Apply [c6989586621679923075] (TyFun [d6989586621679923076] [(a6989586621679923073, b6989586621679923074, c6989586621679923075, d6989586621679923076)] -> Type) (Zip4Sym2 c6989586621679923075 d6989586621679923076 b6989586621679923074 a6989586621679923073 l1 l0) l2 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923073] -> [b6989586621679923074] -> [c6989586621679923075] -> TyFun [d6989586621679923076] [(a6989586621679923073, b6989586621679923074, c6989586621679923075, d6989586621679923076)] -> *) (Zip4Sym3 d6989586621679923076 c6989586621679923075 b6989586621679923074 a6989586621679923073) # | |
type Apply [d6989586621679923076] [(a6989586621679923073, b6989586621679923074, c6989586621679923075, d6989586621679923076)] (Zip4Sym3 d6989586621679923076 c6989586621679923075 b6989586621679923074 a6989586621679923073 l2 l1 l0) l3 # | |
Instances
SuppressUnusedWarnings (TyFun [a6989586621679923068] (TyFun [b6989586621679923069] (TyFun [c6989586621679923070] (TyFun [d6989586621679923071] (TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip5Sym0 a6989586621679923068 b6989586621679923069 c6989586621679923070 d6989586621679923071 e6989586621679923072) # | |
type Apply [a6989586621679923068] (TyFun [b6989586621679923069] (TyFun [c6989586621679923070] (TyFun [d6989586621679923071] (TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> Type) -> Type) -> Type) -> Type) (Zip5Sym0 a6989586621679923068 b6989586621679923069 c6989586621679923070 d6989586621679923071 e6989586621679923072) l0 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923068] -> TyFun [b6989586621679923069] (TyFun [c6989586621679923070] (TyFun [d6989586621679923071] (TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> Type) -> Type) -> Type) -> *) (Zip5Sym1 b6989586621679923069 c6989586621679923070 d6989586621679923071 e6989586621679923072 a6989586621679923068) # | |
type Apply [b6989586621679923069] (TyFun [c6989586621679923070] (TyFun [d6989586621679923071] (TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> Type) -> Type) -> Type) (Zip5Sym1 b6989586621679923069 c6989586621679923070 d6989586621679923071 e6989586621679923072 a6989586621679923068 l0) l1 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923068] -> [b6989586621679923069] -> TyFun [c6989586621679923070] (TyFun [d6989586621679923071] (TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> Type) -> Type) -> *) (Zip5Sym2 c6989586621679923070 d6989586621679923071 e6989586621679923072 b6989586621679923069 a6989586621679923068) # | |
type Apply [c6989586621679923070] (TyFun [d6989586621679923071] (TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> Type) -> Type) (Zip5Sym2 c6989586621679923070 d6989586621679923071 e6989586621679923072 b6989586621679923069 a6989586621679923068 l1 l0) l2 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923068] -> [b6989586621679923069] -> [c6989586621679923070] -> TyFun [d6989586621679923071] (TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> Type) -> *) (Zip5Sym3 d6989586621679923071 e6989586621679923072 c6989586621679923070 b6989586621679923069 a6989586621679923068) # | |
type Apply [d6989586621679923071] (TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> Type) (Zip5Sym3 d6989586621679923071 e6989586621679923072 c6989586621679923070 b6989586621679923069 a6989586621679923068 l2 l1 l0) l3 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923068] -> [b6989586621679923069] -> [c6989586621679923070] -> [d6989586621679923071] -> TyFun [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] -> *) (Zip5Sym4 e6989586621679923072 d6989586621679923071 c6989586621679923070 b6989586621679923069 a6989586621679923068) # | |
type Apply [e6989586621679923072] [(a6989586621679923068, b6989586621679923069, c6989586621679923070, d6989586621679923071, e6989586621679923072)] (Zip5Sym4 e6989586621679923072 d6989586621679923071 c6989586621679923070 b6989586621679923069 a6989586621679923068 l3 l2 l1 l0) l4 # | |
Instances
SuppressUnusedWarnings (TyFun [a6989586621679923062] (TyFun [b6989586621679923063] (TyFun [c6989586621679923064] (TyFun [d6989586621679923065] (TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym0 a6989586621679923062 b6989586621679923063 c6989586621679923064 d6989586621679923065 e6989586621679923066 f6989586621679923067) # | |
type Apply [a6989586621679923062] (TyFun [b6989586621679923063] (TyFun [c6989586621679923064] (TyFun [d6989586621679923065] (TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip6Sym0 a6989586621679923062 b6989586621679923063 c6989586621679923064 d6989586621679923065 e6989586621679923066 f6989586621679923067) l0 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923062] -> TyFun [b6989586621679923063] (TyFun [c6989586621679923064] (TyFun [d6989586621679923065] (TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym1 b6989586621679923063 c6989586621679923064 d6989586621679923065 e6989586621679923066 f6989586621679923067 a6989586621679923062) # | |
type Apply [b6989586621679923063] (TyFun [c6989586621679923064] (TyFun [d6989586621679923065] (TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> Type) -> Type) -> Type) (Zip6Sym1 b6989586621679923063 c6989586621679923064 d6989586621679923065 e6989586621679923066 f6989586621679923067 a6989586621679923062 l0) l1 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923062] -> [b6989586621679923063] -> TyFun [c6989586621679923064] (TyFun [d6989586621679923065] (TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> Type) -> Type) -> *) (Zip6Sym2 c6989586621679923064 d6989586621679923065 e6989586621679923066 f6989586621679923067 b6989586621679923063 a6989586621679923062) # | |
type Apply [c6989586621679923064] (TyFun [d6989586621679923065] (TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> Type) -> Type) (Zip6Sym2 c6989586621679923064 d6989586621679923065 e6989586621679923066 f6989586621679923067 b6989586621679923063 a6989586621679923062 l1 l0) l2 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923062] -> [b6989586621679923063] -> [c6989586621679923064] -> TyFun [d6989586621679923065] (TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> Type) -> *) (Zip6Sym3 d6989586621679923065 e6989586621679923066 f6989586621679923067 c6989586621679923064 b6989586621679923063 a6989586621679923062) # | |
type Apply [d6989586621679923065] (TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> Type) (Zip6Sym3 d6989586621679923065 e6989586621679923066 f6989586621679923067 c6989586621679923064 b6989586621679923063 a6989586621679923062 l2 l1 l0) l3 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923062] -> [b6989586621679923063] -> [c6989586621679923064] -> [d6989586621679923065] -> TyFun [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) -> *) (Zip6Sym4 e6989586621679923066 f6989586621679923067 d6989586621679923065 c6989586621679923064 b6989586621679923063 a6989586621679923062) # | |
type Apply [e6989586621679923066] (TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> Type) (Zip6Sym4 e6989586621679923066 f6989586621679923067 d6989586621679923065 c6989586621679923064 b6989586621679923063 a6989586621679923062 l3 l2 l1 l0) l4 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923062] -> [b6989586621679923063] -> [c6989586621679923064] -> [d6989586621679923065] -> [e6989586621679923066] -> TyFun [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] -> *) (Zip6Sym5 f6989586621679923067 e6989586621679923066 d6989586621679923065 c6989586621679923064 b6989586621679923063 a6989586621679923062) # | |
type Apply [f6989586621679923067] [(a6989586621679923062, b6989586621679923063, c6989586621679923064, d6989586621679923065, e6989586621679923066, f6989586621679923067)] (Zip6Sym5 f6989586621679923067 e6989586621679923066 d6989586621679923065 c6989586621679923064 b6989586621679923063 a6989586621679923062 l4 l3 l2 l1 l0) l5 # | |
Instances
SuppressUnusedWarnings (TyFun [a6989586621679923055] (TyFun [b6989586621679923056] (TyFun [c6989586621679923057] (TyFun [d6989586621679923058] (TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym0 a6989586621679923055 b6989586621679923056 c6989586621679923057 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061) # | |
type Apply [a6989586621679923055] (TyFun [b6989586621679923056] (TyFun [c6989586621679923057] (TyFun [d6989586621679923058] (TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym0 a6989586621679923055 b6989586621679923056 c6989586621679923057 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061) l0 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923055] -> TyFun [b6989586621679923056] (TyFun [c6989586621679923057] (TyFun [d6989586621679923058] (TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym1 b6989586621679923056 c6989586621679923057 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061 a6989586621679923055) # | |
type Apply [b6989586621679923056] (TyFun [c6989586621679923057] (TyFun [d6989586621679923058] (TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym1 b6989586621679923056 c6989586621679923057 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061 a6989586621679923055 l0) l1 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923055] -> [b6989586621679923056] -> TyFun [c6989586621679923057] (TyFun [d6989586621679923058] (TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym2 c6989586621679923057 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061 b6989586621679923056 a6989586621679923055) # | |
type Apply [c6989586621679923057] (TyFun [d6989586621679923058] (TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> Type) -> Type) (Zip7Sym2 c6989586621679923057 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061 b6989586621679923056 a6989586621679923055 l1 l0) l2 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923055] -> [b6989586621679923056] -> [c6989586621679923057] -> TyFun [d6989586621679923058] (TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> Type) -> *) (Zip7Sym3 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061 c6989586621679923057 b6989586621679923056 a6989586621679923055) # | |
type Apply [d6989586621679923058] (TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> Type) (Zip7Sym3 d6989586621679923058 e6989586621679923059 f6989586621679923060 g6989586621679923061 c6989586621679923057 b6989586621679923056 a6989586621679923055 l2 l1 l0) l3 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923055] -> [b6989586621679923056] -> [c6989586621679923057] -> [d6989586621679923058] -> TyFun [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) -> *) (Zip7Sym4 e6989586621679923059 f6989586621679923060 g6989586621679923061 d6989586621679923058 c6989586621679923057 b6989586621679923056 a6989586621679923055) # | |
type Apply [e6989586621679923059] (TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> Type) (Zip7Sym4 e6989586621679923059 f6989586621679923060 g6989586621679923061 d6989586621679923058 c6989586621679923057 b6989586621679923056 a6989586621679923055 l3 l2 l1 l0) l4 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923055] -> [b6989586621679923056] -> [c6989586621679923057] -> [d6989586621679923058] -> [e6989586621679923059] -> TyFun [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) -> *) (Zip7Sym5 f6989586621679923060 g6989586621679923061 e6989586621679923059 d6989586621679923058 c6989586621679923057 b6989586621679923056 a6989586621679923055) # | |
type Apply [f6989586621679923060] (TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> Type) (Zip7Sym5 f6989586621679923060 g6989586621679923061 e6989586621679923059 d6989586621679923058 c6989586621679923057 b6989586621679923056 a6989586621679923055 l4 l3 l2 l1 l0) l5 # | |
Instances
SuppressUnusedWarnings ([a6989586621679923055] -> [b6989586621679923056] -> [c6989586621679923057] -> [d6989586621679923058] -> [e6989586621679923059] -> [f6989586621679923060] -> TyFun [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] -> *) (Zip7Sym6 g6989586621679923061 f6989586621679923060 e6989586621679923059 d6989586621679923058 c6989586621679923057 b6989586621679923056 a6989586621679923055) # | |
type Apply [g6989586621679923061] [(a6989586621679923055, b6989586621679923056, c6989586621679923057, d6989586621679923058, e6989586621679923059, f6989586621679923060, g6989586621679923061)] (Zip7Sym6 g6989586621679923061 f6989586621679923060 e6989586621679923059 d6989586621679923058 c6989586621679923057 b6989586621679923056 a6989586621679923055 l5 l4 l3 l2 l1 l0) l6 # | |
data ZipWith4Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679923050 (TyFun b6989586621679923051 (TyFun c6989586621679923052 (TyFun d6989586621679923053 e6989586621679923054 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679923050] (TyFun [b6989586621679923051] (TyFun [c6989586621679923052] (TyFun [d6989586621679923053] [e6989586621679923054] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith4Sym0 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) # | |
type Apply (TyFun a6989586621679923050 (TyFun b6989586621679923051 (TyFun c6989586621679923052 (TyFun d6989586621679923053 e6989586621679923054 -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679923050] (TyFun [b6989586621679923051] (TyFun [c6989586621679923052] (TyFun [d6989586621679923053] [e6989586621679923054] -> Type) -> Type) -> Type) -> Type) (ZipWith4Sym0 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) l0 # | |
data ZipWith4Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923050 (TyFun b6989586621679923051 (TyFun c6989586621679923052 (TyFun d6989586621679923053 e6989586621679923054 -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679923050] (TyFun [b6989586621679923051] (TyFun [c6989586621679923052] (TyFun [d6989586621679923053] [e6989586621679923054] -> Type) -> Type) -> Type) -> *) (ZipWith4Sym1 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) # | |
type Apply [a6989586621679923050] (TyFun [b6989586621679923051] (TyFun [c6989586621679923052] (TyFun [d6989586621679923053] [e6989586621679923054] -> Type) -> Type) -> Type) (ZipWith4Sym1 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054 l0) l1 # | |
data ZipWith4Sym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923050 (TyFun b6989586621679923051 (TyFun c6989586621679923052 (TyFun d6989586621679923053 e6989586621679923054 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923050] -> TyFun [b6989586621679923051] (TyFun [c6989586621679923052] (TyFun [d6989586621679923053] [e6989586621679923054] -> Type) -> Type) -> *) (ZipWith4Sym2 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) # | |
type Apply [b6989586621679923051] (TyFun [c6989586621679923052] (TyFun [d6989586621679923053] [e6989586621679923054] -> Type) -> Type) (ZipWith4Sym2 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054 l1 l0) l2 # | |
data ZipWith4Sym3 l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923050 (TyFun b6989586621679923051 (TyFun c6989586621679923052 (TyFun d6989586621679923053 e6989586621679923054 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923050] -> [b6989586621679923051] -> TyFun [c6989586621679923052] (TyFun [d6989586621679923053] [e6989586621679923054] -> Type) -> *) (ZipWith4Sym3 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) # | |
type Apply [c6989586621679923052] (TyFun [d6989586621679923053] [e6989586621679923054] -> Type) (ZipWith4Sym3 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054 l2 l1 l0) l3 # | |
data ZipWith4Sym4 l l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923050 (TyFun b6989586621679923051 (TyFun c6989586621679923052 (TyFun d6989586621679923053 e6989586621679923054 -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923050] -> [b6989586621679923051] -> [c6989586621679923052] -> TyFun [d6989586621679923053] [e6989586621679923054] -> *) (ZipWith4Sym4 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054) # | |
type Apply [d6989586621679923053] [e6989586621679923054] (ZipWith4Sym4 a6989586621679923050 b6989586621679923051 c6989586621679923052 d6989586621679923053 e6989586621679923054 l3 l2 l1 l0) l4 # | |
type ZipWith4Sym5 t t t t t = ZipWith4 t t t t t #
data ZipWith5Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679923044] (TyFun [b6989586621679923045] (TyFun [c6989586621679923046] (TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym0 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) # | |
type Apply (TyFun a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679923044] (TyFun [b6989586621679923045] (TyFun [c6989586621679923046] (TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym0 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) l0 # | |
data ZipWith5Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679923044] (TyFun [b6989586621679923045] (TyFun [c6989586621679923046] (TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym1 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) # | |
type Apply [a6989586621679923044] (TyFun [b6989586621679923045] (TyFun [c6989586621679923046] (TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym1 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049 l0) l1 # | |
data ZipWith5Sym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923044] -> TyFun [b6989586621679923045] (TyFun [c6989586621679923046] (TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> Type) -> Type) -> *) (ZipWith5Sym2 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) # | |
type Apply [b6989586621679923045] (TyFun [c6989586621679923046] (TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> Type) -> Type) (ZipWith5Sym2 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049 l1 l0) l2 # | |
data ZipWith5Sym3 l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923044] -> [b6989586621679923045] -> TyFun [c6989586621679923046] (TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> Type) -> *) (ZipWith5Sym3 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) # | |
type Apply [c6989586621679923046] (TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> Type) (ZipWith5Sym3 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049 l2 l1 l0) l3 # | |
data ZipWith5Sym4 l l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923044] -> [b6989586621679923045] -> [c6989586621679923046] -> TyFun [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) -> *) (ZipWith5Sym4 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) # | |
type Apply [d6989586621679923047] (TyFun [e6989586621679923048] [f6989586621679923049] -> Type) (ZipWith5Sym4 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049 l3 l2 l1 l0) l4 # | |
data ZipWith5Sym5 l l l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923044 (TyFun b6989586621679923045 (TyFun c6989586621679923046 (TyFun d6989586621679923047 (TyFun e6989586621679923048 f6989586621679923049 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923044] -> [b6989586621679923045] -> [c6989586621679923046] -> [d6989586621679923047] -> TyFun [e6989586621679923048] [f6989586621679923049] -> *) (ZipWith5Sym5 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049) # | |
type Apply [e6989586621679923048] [f6989586621679923049] (ZipWith5Sym5 a6989586621679923044 b6989586621679923045 c6989586621679923046 d6989586621679923047 e6989586621679923048 f6989586621679923049 l4 l3 l2 l1 l0) l5 # | |
type ZipWith5Sym6 t t t t t t = ZipWith5 t t t t t t #
data ZipWith6Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679923037] (TyFun [b6989586621679923038] (TyFun [c6989586621679923039] (TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym0 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # | |
type Apply (TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679923037] (TyFun [b6989586621679923038] (TyFun [c6989586621679923039] (TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym0 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) l0 # | |
data ZipWith6Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679923037] (TyFun [b6989586621679923038] (TyFun [c6989586621679923039] (TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym1 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # | |
type Apply [a6989586621679923037] (TyFun [b6989586621679923038] (TyFun [c6989586621679923039] (TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym1 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043 l0) l1 # | |
data ZipWith6Sym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923037] -> TyFun [b6989586621679923038] (TyFun [c6989586621679923039] (TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym2 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # | |
type Apply [b6989586621679923038] (TyFun [c6989586621679923039] (TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym2 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043 l1 l0) l2 # | |
data ZipWith6Sym3 l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923037] -> [b6989586621679923038] -> TyFun [c6989586621679923039] (TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> Type) -> *) (ZipWith6Sym3 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # | |
type Apply [c6989586621679923039] (TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> Type) (ZipWith6Sym3 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043 l2 l1 l0) l3 # | |
data ZipWith6Sym4 l l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923037] -> [b6989586621679923038] -> [c6989586621679923039] -> TyFun [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) -> *) (ZipWith6Sym4 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # | |
type Apply [d6989586621679923040] (TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> Type) (ZipWith6Sym4 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043 l3 l2 l1 l0) l4 # | |
data ZipWith6Sym5 l l l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923037] -> [b6989586621679923038] -> [c6989586621679923039] -> [d6989586621679923040] -> TyFun [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) -> *) (ZipWith6Sym5 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # | |
type Apply [e6989586621679923041] (TyFun [f6989586621679923042] [g6989586621679923043] -> Type) (ZipWith6Sym5 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043 l4 l3 l2 l1 l0) l5 # | |
data ZipWith6Sym6 l l l l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923037 (TyFun b6989586621679923038 (TyFun c6989586621679923039 (TyFun d6989586621679923040 (TyFun e6989586621679923041 (TyFun f6989586621679923042 g6989586621679923043 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923037] -> [b6989586621679923038] -> [c6989586621679923039] -> [d6989586621679923040] -> [e6989586621679923041] -> TyFun [f6989586621679923042] [g6989586621679923043] -> *) (ZipWith6Sym6 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043) # | |
type Apply [f6989586621679923042] [g6989586621679923043] (ZipWith6Sym6 a6989586621679923037 b6989586621679923038 c6989586621679923039 d6989586621679923040 e6989586621679923041 f6989586621679923042 g6989586621679923043 l5 l4 l3 l2 l1 l0) l6 # | |
type ZipWith6Sym7 t t t t t t t = ZipWith6 t t t t t t t #
data ZipWith7Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679923029] (TyFun [b6989586621679923030] (TyFun [c6989586621679923031] (TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym0 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # | |
type Apply (TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a6989586621679923029] (TyFun [b6989586621679923030] (TyFun [c6989586621679923031] (TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym0 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) l0 # | |
data ZipWith7Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a6989586621679923029] (TyFun [b6989586621679923030] (TyFun [c6989586621679923031] (TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym1 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # | |
type Apply [a6989586621679923029] (TyFun [b6989586621679923030] (TyFun [c6989586621679923031] (TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym1 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036 l0) l1 # | |
data ZipWith7Sym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923029] -> TyFun [b6989586621679923030] (TyFun [c6989586621679923031] (TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym2 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # | |
type Apply [b6989586621679923030] (TyFun [c6989586621679923031] (TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym2 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036 l1 l0) l2 # | |
data ZipWith7Sym3 l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923029] -> [b6989586621679923030] -> TyFun [c6989586621679923031] (TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym3 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # | |
type Apply [c6989586621679923031] (TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym3 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036 l2 l1 l0) l3 # | |
data ZipWith7Sym4 l l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923029] -> [b6989586621679923030] -> [c6989586621679923031] -> TyFun [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) -> *) (ZipWith7Sym4 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # | |
type Apply [d6989586621679923032] (TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> Type) (ZipWith7Sym4 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036 l3 l2 l1 l0) l4 # | |
data ZipWith7Sym5 l l l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923029] -> [b6989586621679923030] -> [c6989586621679923031] -> [d6989586621679923032] -> TyFun [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) -> *) (ZipWith7Sym5 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # | |
type Apply [e6989586621679923033] (TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> Type) (ZipWith7Sym5 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036 l4 l3 l2 l1 l0) l5 # | |
data ZipWith7Sym6 l l l l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923029] -> [b6989586621679923030] -> [c6989586621679923031] -> [d6989586621679923032] -> [e6989586621679923033] -> TyFun [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) -> *) (ZipWith7Sym6 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # | |
type Apply [f6989586621679923034] (TyFun [g6989586621679923035] [h6989586621679923036] -> Type) (ZipWith7Sym6 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036 l5 l4 l3 l2 l1 l0) l6 # | |
data ZipWith7Sym7 l l l l l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679923029 (TyFun b6989586621679923030 (TyFun c6989586621679923031 (TyFun d6989586621679923032 (TyFun e6989586621679923033 (TyFun f6989586621679923034 (TyFun g6989586621679923035 h6989586621679923036 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a6989586621679923029] -> [b6989586621679923030] -> [c6989586621679923031] -> [d6989586621679923032] -> [e6989586621679923033] -> [f6989586621679923034] -> TyFun [g6989586621679923035] [h6989586621679923036] -> *) (ZipWith7Sym7 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036) # | |
type Apply [g6989586621679923035] [h6989586621679923036] (ZipWith7Sym7 a6989586621679923029 b6989586621679923030 c6989586621679923031 d6989586621679923032 e6989586621679923033 f6989586621679923034 g6989586621679923035 h6989586621679923036 l6 l5 l4 l3 l2 l1 l0) l7 # | |
type ZipWith7Sym8 t t t t t t t t = ZipWith7 t t t t t t t t #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700049 (TyFun a6989586621679700049 Bool -> Type) -> Type) (TyFun [a6989586621679700049] [a6989586621679700049] -> Type) -> *) (NubBySym0 a6989586621679700049) # | |
type Apply (TyFun a6989586621679700049 (TyFun a6989586621679700049 Bool -> Type) -> Type) (TyFun [a6989586621679700049] [a6989586621679700049] -> Type) (NubBySym0 a6989586621679700049) l0 # | |
Instances
data UnionBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679700047 (TyFun a6989586621679700047 Bool -> Type) -> Type) (TyFun [a6989586621679700047] (TyFun [a6989586621679700047] [a6989586621679700047] -> Type) -> Type) -> *) (UnionBySym0 a6989586621679700047) # | |
type Apply (TyFun a6989586621679700047 (TyFun a6989586621679700047 Bool -> Type) -> Type) (TyFun [a6989586621679700047] (TyFun [a6989586621679700047] [a6989586621679700047] -> Type) -> Type) (UnionBySym0 a6989586621679700047) l0 # | |
data UnionBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700047 (TyFun a6989586621679700047 Bool -> Type) -> Type) -> TyFun [a6989586621679700047] (TyFun [a6989586621679700047] [a6989586621679700047] -> Type) -> *) (UnionBySym1 a6989586621679700047) # | |
type Apply [a6989586621679700047] (TyFun [a6989586621679700047] [a6989586621679700047] -> Type) (UnionBySym1 a6989586621679700047 l0) l1 # | |
data UnionBySym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679700047 (TyFun a6989586621679700047 Bool -> Type) -> Type) -> [a6989586621679700047] -> TyFun [a6989586621679700047] [a6989586621679700047] -> *) (UnionBySym2 a6989586621679700047) # | |
type Apply [a6989586621679700047] [a6989586621679700047] (UnionBySym2 a6989586621679700047 l1 l0) l2 # | |
type UnionBySym3 t t t = UnionBy t t t #
data GenericLengthSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679700045] i6989586621679700044 -> *) (GenericLengthSym0 a6989586621679700045 i6989586621679700044) # | |
type Apply [a6989586621679700045] k2 (GenericLengthSym0 a6989586621679700045 k2) l0 # | |
type GenericLengthSym1 t = GenericLength t #
data GenericTakeSym0 l #
Instances
SuppressUnusedWarnings (TyFun i6989586621679923027 (TyFun [a6989586621679923028] [a6989586621679923028] -> Type) -> *) (GenericTakeSym0 i6989586621679923027 a6989586621679923028) # | |
type Apply i6989586621679923027 (TyFun [a6989586621679923028] [a6989586621679923028] -> Type) (GenericTakeSym0 i6989586621679923027 a6989586621679923028) l0 # | |
data GenericTakeSym1 l l #
Instances
SuppressUnusedWarnings (i6989586621679923027 -> TyFun [a6989586621679923028] [a6989586621679923028] -> *) (GenericTakeSym1 a6989586621679923028 i6989586621679923027) # | |
type Apply [a6989586621679923028] [a6989586621679923028] (GenericTakeSym1 a6989586621679923028 i6989586621679923027 l0) l1 # | |
type GenericTakeSym2 t t = GenericTake t t #
data GenericDropSym0 l #
Instances
SuppressUnusedWarnings (TyFun i6989586621679923025 (TyFun [a6989586621679923026] [a6989586621679923026] -> Type) -> *) (GenericDropSym0 i6989586621679923025 a6989586621679923026) # | |
type Apply i6989586621679923025 (TyFun [a6989586621679923026] [a6989586621679923026] -> Type) (GenericDropSym0 i6989586621679923025 a6989586621679923026) l0 # | |
data GenericDropSym1 l l #
Instances
SuppressUnusedWarnings (i6989586621679923025 -> TyFun [a6989586621679923026] [a6989586621679923026] -> *) (GenericDropSym1 a6989586621679923026 i6989586621679923025) # | |
type Apply [a6989586621679923026] [a6989586621679923026] (GenericDropSym1 a6989586621679923026 i6989586621679923025 l0) l1 # | |
type GenericDropSym2 t t = GenericDrop t t #
data GenericSplitAtSym0 l #
Instances
SuppressUnusedWarnings (TyFun i6989586621679923023 (TyFun [a6989586621679923024] ([a6989586621679923024], [a6989586621679923024]) -> Type) -> *) (GenericSplitAtSym0 i6989586621679923023 a6989586621679923024) # | |
type Apply i6989586621679923023 (TyFun [a6989586621679923024] ([a6989586621679923024], [a6989586621679923024]) -> Type) (GenericSplitAtSym0 i6989586621679923023 a6989586621679923024) l0 # | |
data GenericSplitAtSym1 l l #
Instances
SuppressUnusedWarnings (i6989586621679923023 -> TyFun [a6989586621679923024] ([a6989586621679923024], [a6989586621679923024]) -> *) (GenericSplitAtSym1 a6989586621679923024 i6989586621679923023) # | |
type Apply [a6989586621679923024] ([a6989586621679923024], [a6989586621679923024]) (GenericSplitAtSym1 a6989586621679923024 i6989586621679923023 l0) l1 # | |
type GenericSplitAtSym2 t t = GenericSplitAt t t #
data GenericIndexSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679923022] (TyFun i6989586621679923021 a6989586621679923022 -> Type) -> *) (GenericIndexSym0 i6989586621679923021 a6989586621679923022) # | |
type Apply [a6989586621679923022] (TyFun i6989586621679923021 a6989586621679923022 -> Type) (GenericIndexSym0 i6989586621679923021 a6989586621679923022) l0 # | |
data GenericIndexSym1 l l #
Instances
SuppressUnusedWarnings ([a6989586621679923022] -> TyFun i6989586621679923021 a6989586621679923022 -> *) (GenericIndexSym1 i6989586621679923021 a6989586621679923022) # | |
type Apply i6989586621679923021 a6989586621679923022 (GenericIndexSym1 i6989586621679923021 a6989586621679923022 l0) l1 # | |
type GenericIndexSym2 t t = GenericIndex t t #
data GenericReplicateSym0 l #
Instances
SuppressUnusedWarnings (TyFun i6989586621679923019 (TyFun a6989586621679923020 [a6989586621679923020] -> Type) -> *) (GenericReplicateSym0 i6989586621679923019 a6989586621679923020) # | |
type Apply i6989586621679923019 (TyFun a6989586621679923020 [a6989586621679923020] -> Type) (GenericReplicateSym0 i6989586621679923019 a6989586621679923020) l0 # | |
data GenericReplicateSym1 l l #
Instances
SuppressUnusedWarnings (i6989586621679923019 -> TyFun a6989586621679923020 [a6989586621679923020] -> *) (GenericReplicateSym1 a6989586621679923020 i6989586621679923019) # | |
type Apply a6989586621679923020 [a6989586621679923020] (GenericReplicateSym1 a6989586621679923020 i6989586621679923019 l0) l1 # | |
type GenericReplicateSym2 t t = GenericReplicate t t #