Copyright | (C) 2014 Jan Stolarek |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Jan Stolarek (jan.stolarek@p.lodz.pl) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Defines promoted functions and datatypes relating to List
,
including a promoted version of all the definitions in Data.List
.
Because many of these definitions are produced by Template Haskell,
it is not possible to create proper Haddock documentation. Please look
up the corresponding operation in Data.List
. Also, please excuse
the apparent repeated variable names. This is due to an interaction
between Template Haskell and Haddock.
- type family (a :: [a]) :++ (a :: [a]) :: [a] where ...
- type family Head (a :: [a]) :: a where ...
- type family Last (a :: [a]) :: a where ...
- type family Tail (a :: [a]) :: [a] where ...
- type family Init (a :: [a]) :: [a] where ...
- type family Null (a :: [a]) :: Bool where ...
- type family Length (a :: [a]) :: Nat where ...
- type family Map (a :: TyFun a b -> Type) (a :: [a]) :: [b] where ...
- type family Reverse (a :: [a]) :: [a] where ...
- type family Intersperse (a :: a) (a :: [a]) :: [a] where ...
- type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ...
- type family Transpose (a :: [[a]]) :: [[a]] where ...
- type family Subsequences (a :: [a]) :: [[a]] where ...
- type family Permutations (a :: [a]) :: [[a]] where ...
- type family Foldl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- type family Foldl' (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- type family Foldl1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
- type family Foldl1' (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
- type family Foldr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- type family Foldr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
- type family Concat (a :: [[a]]) :: [a] where ...
- type family ConcatMap (a :: TyFun a [b] -> Type) (a :: [a]) :: [b] where ...
- type family And (a :: [Bool]) :: Bool where ...
- type family Or (a :: [Bool]) :: Bool where ...
- type family Any_ (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ...
- type family All (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ...
- type family Sum (a :: [a]) :: a where ...
- type family Product (a :: [a]) :: a where ...
- type family Maximum (a :: [a]) :: a where ...
- type family Minimum (a :: [a]) :: a where ...
- any_ :: 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 ... Source #
Length '[] = FromInteger 0 | |
Length ((:) _z_1627954120 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply LengthSym0 xs) |
List transformations
type family Intersperse (a :: a) (a :: [a]) :: [a] where ... Source #
Intersperse _z_1627957149 '[] = '[] | |
Intersperse sep ((:) x xs) = Apply (Apply (:$) x) (Apply (Apply PrependToAllSym0 sep) xs) |
type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ... Source #
Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) |
type family Subsequences (a :: [a]) :: [[a]] where ... Source #
Subsequences xs = Apply (Apply (:$) '[]) (Apply NonEmptySubsequencesSym0 xs) |
type family Permutations (a :: [a]) :: [[a]] where ... Source #
Reducing lists (folds)
type family Foldl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #
type family Foldl' (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #
type family Foldr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #
Special folds
type family Sum (a :: [a]) :: a where ... Source #
Sum l = Apply (Apply (Let1627954153Sum'Sym1 l) l) (FromInteger 0) |
type family Product (a :: [a]) :: a where ... Source #
Product l = Apply (Apply (Let1627954129ProdSym1 l) l) (FromInteger 1) |
Building lists
Scans
type family Scanl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ... Source #
type family Scanr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ... Source #
Accumulating maps
type family MapAccumL (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... Source #
type family MapAccumR (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... Source #
Infinite lists
type family Replicate (a :: Nat) (a :: a) :: [a] where ... Source #
Replicate n x = Case_1627954113 n x (Let1627954105Scrutinee_1627953948Sym2 n x) |
Unfolding
type family Unfoldr (a :: TyFun b (Maybe (a, b)) -> Type) (a :: b) :: [a] where ... Source #
Unfoldr f b = Case_1627955820 f b (Let1627955812Scrutinee_1627953868Sym2 f b) |
Sublists
Extracting sublists
type family Span (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... Source #
Span _z_1627954447 '[] = Apply (Apply Tuple2Sym0 (Let1627954450XsSym1 _z_1627954447)) (Let1627954450XsSym1 _z_1627954447) | |
Span p ((:) x xs') = Case_1627954483 p x xs' (Let1627954470Scrutinee_1627953928Sym3 p x xs') |
type family Break (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... Source #
Break _z_1627954342 '[] = Apply (Apply Tuple2Sym0 (Let1627954345XsSym1 _z_1627954342)) (Let1627954345XsSym1 _z_1627954342) | |
Break p ((:) x xs') = Case_1627954378 p x xs' (Let1627954365Scrutinee_1627953930Sym3 p x xs') |
type family StripPrefix (a :: [a]) (a :: [a]) :: Maybe [a] where ... Source #
StripPrefix '[] ys = Apply JustSym0 ys | |
StripPrefix arg_1628251755 arg_1628251757 = Case_1628252366 arg_1628251755 arg_1628251757 (Apply (Apply Tuple2Sym0 arg_1628251755) arg_1628251757) |
type family Group (a :: [a]) :: [[a]] where ... Source #
Group xs = Apply (Apply GroupBySym0 (:==$)) xs |
Predicates
type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
IsPrefixOf '[] '[] = TrueSym0 | |
IsPrefixOf '[] ((:) _z_1627955752 _z_1627955755) = TrueSym0 | |
IsPrefixOf ((:) _z_1627955758 _z_1627955761) '[] = FalseSym0 | |
IsPrefixOf ((:) x xs) ((:) y ys) = Apply (Apply (:&&$) (Apply (Apply (:==$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) |
type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ... Source #
IsSuffixOf x y = Apply (Apply IsPrefixOfSym0 (Apply ReverseSym0 x)) (Apply ReverseSym0 y) |
Searching lists
Searching by equality
type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... Source #
Lookup _key '[] = NothingSym0 | |
Lookup key ((:) '(x, y) xys) = Case_1627954257 key x y xys (Let1627954238Scrutinee_1627953944Sym4 key x y xys) |
Searching with a predicate
type family Find (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe a where ... Source #
Find p a_1627954733 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FilterSym0 p)) a_1627954733 |
Indexing lists
type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ... Source #
ElemIndices x a_1627955635 = Apply (Apply FindIndicesSym0 (Apply (:==$) x)) a_1627955635 |
type family FindIndex (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe Nat where ... Source #
FindIndex p a_1627955648 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_1627955648 |
Zipping and unzipping lists
type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ... Source #
Zip3 ((:) a as) ((:) b bs) ((:) c cs) = Apply (Apply (:$) (Apply (Apply (Apply Tuple3Sym0 a) b) c)) (Apply (Apply (Apply Zip3Sym0 as) bs) cs) | |
Zip3 '[] '[] '[] = '[] | |
Zip3 '[] '[] ((:) _z_1627955484 _z_1627955487) = '[] | |
Zip3 '[] ((:) _z_1627955490 _z_1627955493) '[] = '[] | |
Zip3 '[] ((:) _z_1627955496 _z_1627955499) ((:) _z_1627955502 _z_1627955505) = '[] | |
Zip3 ((:) _z_1627955508 _z_1627955511) '[] '[] = '[] | |
Zip3 ((:) _z_1627955514 _z_1627955517) '[] ((:) _z_1627955520 _z_1627955523) = '[] | |
Zip3 ((:) _z_1627955526 _z_1627955529) ((:) _z_1627955532 _z_1627955535) '[] = '[] |
type family Zip4 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [(a, b, c, d)] where ... Source #
Zip4 a_1628252320 a_1628252322 a_1628252324 a_1628252326 = Apply (Apply (Apply (Apply (Apply ZipWith4Sym0 Tuple4Sym0) a_1628252320) a_1628252322) a_1628252324) a_1628252326 |
type family Zip5 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [(a, b, c, d, e)] where ... Source #
Zip5 a_1628252275 a_1628252277 a_1628252279 a_1628252281 a_1628252283 = Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 Tuple5Sym0) a_1628252275) a_1628252277) a_1628252279) a_1628252281) a_1628252283 |
type family Zip6 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [(a, b, c, d, e, f)] where ... Source #
Zip6 a_1628252218 a_1628252220 a_1628252222 a_1628252224 a_1628252226 a_1628252228 = Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 Tuple6Sym0) a_1628252218) a_1628252220) a_1628252222) a_1628252224) a_1628252226) a_1628252228 |
type family Zip7 (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [(a, b, c, d, e, f, g)] where ... Source #
type family ZipWith (a :: TyFun a (TyFun b c -> Type) -> Type) (a :: [a]) (a :: [b]) :: [c] where ... Source #
type family ZipWith3 (a :: TyFun a (TyFun b (TyFun c d -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ... Source #
ZipWith3 z ((:) a as) ((:) b bs) ((:) c cs) = Apply (Apply (:$) (Apply (Apply (Apply z a) b) c)) (Apply (Apply (Apply (Apply ZipWith3Sym0 z) as) bs) cs) | |
ZipWith3 _z_1627955347 '[] '[] '[] = '[] | |
ZipWith3 _z_1627955350 '[] '[] ((:) _z_1627955353 _z_1627955356) = '[] | |
ZipWith3 _z_1627955359 '[] ((:) _z_1627955362 _z_1627955365) '[] = '[] | |
ZipWith3 _z_1627955368 '[] ((:) _z_1627955371 _z_1627955374) ((:) _z_1627955377 _z_1627955380) = '[] | |
ZipWith3 _z_1627955383 ((:) _z_1627955386 _z_1627955389) '[] '[] = '[] | |
ZipWith3 _z_1627955392 ((:) _z_1627955395 _z_1627955398) '[] ((:) _z_1627955401 _z_1627955404) = '[] | |
ZipWith3 _z_1627955407 ((:) _z_1627955410 _z_1627955413) ((:) _z_1627955416 _z_1627955419) '[] = '[] |
type family ZipWith4 (a :: TyFun a (TyFun b (TyFun c (TyFun d e -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) :: [e] where ... Source #
type family ZipWith5 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e f -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) :: [f] where ... Source #
ZipWith5 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) ((:) e es) = Apply (Apply (:$) (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e)) (Apply (Apply (Apply (Apply (Apply (Apply ZipWith5Sym0 z) as) bs) cs) ds) es) | |
ZipWith5 _z_1628252076 _z_1628252079 _z_1628252082 _z_1628252085 _z_1628252088 _z_1628252091 = '[] |
type family ZipWith6 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e (TyFun f g -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) :: [g] where ... Source #
ZipWith6 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) ((:) e es) ((:) f fs) = Apply (Apply (:$) (Apply (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e) f)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith6Sym0 z) as) bs) cs) ds) es) fs) | |
ZipWith6 _z_1628252005 _z_1628252008 _z_1628252011 _z_1628252014 _z_1628252017 _z_1628252020 _z_1628252023 = '[] |
type family ZipWith7 (a :: TyFun a (TyFun b (TyFun c (TyFun d (TyFun e (TyFun f (TyFun g h -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) (a :: [d]) (a :: [e]) (a :: [f]) (a :: [g]) :: [h] where ... Source #
ZipWith7 z ((:) a as) ((:) b bs) ((:) c cs) ((:) d ds) ((:) e es) ((:) f fs) ((:) g gs) = Apply (Apply (:$) (Apply (Apply (Apply (Apply (Apply (Apply (Apply z a) b) c) d) e) f) g)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply ZipWith7Sym0 z) as) bs) cs) ds) es) fs) gs) | |
ZipWith7 _z_1628251919 _z_1628251922 _z_1628251925 _z_1628251928 _z_1628251931 _z_1628251934 _z_1628251937 _z_1628251940 = '[] |
type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... Source #
Special lists
"Set" operations
Ordered lists
type family Sort (a :: [a]) :: [a] where ... Source #
Sort a_1627954969 = Apply (Apply SortBySym0 CompareSym0) a_1627954969 |
type family Insert (a :: a) (a :: [a]) :: [a] where ... Source #
Insert e ls = Apply (Apply (Apply InsertBySym0 CompareSym0) e) ls |
Generalized functions
The "By
" operations
User-supplied equality (replacing an Eq
context)
type family NubBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [a] where ... Source #
type family DeleteBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... Source #
type family DeleteFirstsBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... Source #
DeleteFirstsBy eq a_1627955038 a_1627955040 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_1627955038) a_1627955040 |
type family UnionBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... Source #
type family GroupBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [[a]] where ... Source #
type family IntersectBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... Source #
IntersectBy _z_1627954752 '[] '[] = '[] | |
IntersectBy _z_1627954755 '[] ((:) _z_1627954758 _z_1627954761) = '[] | |
IntersectBy _z_1627954764 ((:) _z_1627954767 _z_1627954770) '[] = '[] | |
IntersectBy eq ((:) wild_1627953914 wild_1627953916) ((:) wild_1627953918 wild_1627953920) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_1627954829Sym0 eq) wild_1627953914) wild_1627953916) wild_1627953918) wild_1627953920)) (Let1627954778XsSym5 eq wild_1627953914 wild_1627953916 wild_1627953918 wild_1627953920) |
User-supplied comparison (replacing an Ord
context)
type family SortBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: [a] where ... Source #
type family InsertBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... Source #
type family MaximumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... Source #
type family MinimumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... Source #
The "generic
" operations
type family GenericLength (a :: [a]) :: i where ... Source #
GenericLength '[] = FromInteger 0 | |
GenericLength ((:) _z_1627953967 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
type family GenericTake (a :: i) (a :: [a]) :: [a] where ... Source #
GenericTake a_1628251829 a_1628251831 = Apply (Apply TakeSym0 a_1628251829) a_1628251831 |
type family GenericDrop (a :: i) (a :: [a]) :: [a] where ... Source #
GenericDrop a_1628251814 a_1628251816 = Apply (Apply DropSym0 a_1628251814) a_1628251816 |
type family GenericSplitAt (a :: i) (a :: [a]) :: ([a], [a]) where ... Source #
GenericSplitAt a_1628251799 a_1628251801 = Apply (Apply SplitAtSym0 a_1628251799) a_1628251801 |
type family GenericIndex (a :: [a]) (a :: i) :: a where ... Source #
GenericIndex a_1628251784 a_1628251786 = Apply (Apply (:!!$) a_1628251784) a_1628251786 |
type family GenericReplicate (a :: i) (a :: a) :: [a] where ... Source #
GenericReplicate a_1628251769 a_1628251771 = Apply (Apply ReplicateSym0 a_1628251769) a_1628251771 |
Defunctionalization symbols
SuppressUnusedWarnings (TyFun (TyFun a1627796655 b1627796656 -> Type) (TyFun [a1627796655] [b1627796656] -> Type) -> *) (MapSym0 a1627796655 b1627796656) Source # | |
type Apply (TyFun a1627796655 b1627796656 -> Type) (TyFun [a1627796655] [b1627796656] -> Type) (MapSym0 a1627796655 b1627796656) l0 Source # | |
data ReverseSym0 l Source #
SuppressUnusedWarnings (TyFun [a1627953404] [a1627953404] -> *) (ReverseSym0 a1627953404) Source # | |
type Apply [a1627953404] [a1627953404] (ReverseSym0 a1627953404) l0 Source # | |
type ReverseSym1 t = Reverse t Source #
data IntersperseSym0 l Source #
SuppressUnusedWarnings (TyFun a1627953403 (TyFun [a1627953403] [a1627953403] -> Type) -> *) (IntersperseSym0 a1627953403) Source # | |
type Apply a1627953403 (TyFun [a1627953403] [a1627953403] -> Type) (IntersperseSym0 a1627953403) l0 Source # | |
data IntersperseSym1 l l Source #
SuppressUnusedWarnings (a1627953403 -> TyFun [a1627953403] [a1627953403] -> *) (IntersperseSym1 a1627953403) Source # | |
type Apply [a1627953403] [a1627953403] (IntersperseSym1 a1627953403 l1) l0 Source # | |
type IntersperseSym2 t t = Intersperse t t Source #
data IntercalateSym0 l Source #
SuppressUnusedWarnings (TyFun [a1627953402] (TyFun [[a1627953402]] [a1627953402] -> Type) -> *) (IntercalateSym0 a1627953402) Source # | |
type Apply [a1627953402] (TyFun [[a1627953402]] [a1627953402] -> Type) (IntercalateSym0 a1627953402) l0 Source # | |
data IntercalateSym1 l l Source #
SuppressUnusedWarnings ([a1627953402] -> TyFun [[a1627953402]] [a1627953402] -> *) (IntercalateSym1 a1627953402) Source # | |
type Apply [[a1627953402]] [a1627953402] (IntercalateSym1 a1627953402 l1) l0 Source # | |
type IntercalateSym2 t t = Intercalate t t Source #
data SubsequencesSym0 l Source #
SuppressUnusedWarnings (TyFun [a1627953401] [[a1627953401]] -> *) (SubsequencesSym0 a1627953401) Source # | |
type Apply [a1627953401] [[a1627953401]] (SubsequencesSym0 a1627953401) l0 Source # | |
type SubsequencesSym1 t = Subsequences t Source #
data PermutationsSym0 l Source #
SuppressUnusedWarnings (TyFun [a1627953398] [[a1627953398]] -> *) (PermutationsSym0 a1627953398) Source # | |
type Apply [a1627953398] [[a1627953398]] (PermutationsSym0 a1627953398) l0 Source # | |
type PermutationsSym1 t = Permutations t Source #
SuppressUnusedWarnings (TyFun (TyFun b1627619913 (TyFun a1627619912 b1627619913 -> Type) -> Type) (TyFun b1627619913 (TyFun [a1627619912] b1627619913 -> Type) -> Type) -> *) (FoldlSym0 a1627619912 b1627619913) Source # | |
type Apply (TyFun b1627619913 (TyFun a1627619912 b1627619913 -> Type) -> Type) (TyFun b1627619913 (TyFun [a1627619912] b1627619913 -> Type) -> Type) (FoldlSym0 a1627619912 b1627619913) l0 Source # | |
SuppressUnusedWarnings ((TyFun b1627619913 (TyFun a1627619912 b1627619913 -> Type) -> Type) -> TyFun b1627619913 (TyFun [a1627619912] b1627619913 -> Type) -> *) (FoldlSym1 a1627619912 b1627619913) Source # | |
type Apply b1627619913 (TyFun [a1627619912] b1627619913 -> Type) (FoldlSym1 a1627619912 b1627619913 l1) l0 Source # | |
data Foldl'Sym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun b1627953397 (TyFun a1627953396 b1627953397 -> Type) -> Type) (TyFun b1627953397 (TyFun [a1627953396] b1627953397 -> Type) -> Type) -> *) (Foldl'Sym0 a1627953396 b1627953397) Source # | |
type Apply (TyFun b1627953397 (TyFun a1627953396 b1627953397 -> Type) -> Type) (TyFun b1627953397 (TyFun [a1627953396] b1627953397 -> Type) -> Type) (Foldl'Sym0 a1627953396 b1627953397) l0 Source # | |
data Foldl'Sym1 l l Source #
SuppressUnusedWarnings ((TyFun b1627953397 (TyFun a1627953396 b1627953397 -> Type) -> Type) -> TyFun b1627953397 (TyFun [a1627953396] b1627953397 -> Type) -> *) (Foldl'Sym1 a1627953396 b1627953397) Source # | |
type Apply b1627953397 (TyFun [a1627953396] b1627953397 -> Type) (Foldl'Sym1 a1627953396 b1627953397 l1) l0 Source # | |
data Foldl'Sym2 l l l Source #
SuppressUnusedWarnings ((TyFun b1627953397 (TyFun a1627953396 b1627953397 -> Type) -> Type) -> b1627953397 -> TyFun [a1627953396] b1627953397 -> *) (Foldl'Sym2 a1627953396 b1627953397) Source # | |
type Apply [a1627953396] b1627953397 (Foldl'Sym2 a1627953396 b1627953397 l1 l2) l0 Source # | |
type Foldl'Sym3 t t t = Foldl' t t t Source #
data Foldl1Sym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953395 (TyFun a1627953395 a1627953395 -> Type) -> Type) (TyFun [a1627953395] a1627953395 -> Type) -> *) (Foldl1Sym0 a1627953395) Source # | |
type Apply (TyFun a1627953395 (TyFun a1627953395 a1627953395 -> Type) -> Type) (TyFun [a1627953395] a1627953395 -> Type) (Foldl1Sym0 a1627953395) l0 Source # | |
data Foldl1Sym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953395 (TyFun a1627953395 a1627953395 -> Type) -> Type) -> TyFun [a1627953395] a1627953395 -> *) (Foldl1Sym1 a1627953395) Source # | |
type Apply [a1627953395] a1627953395 (Foldl1Sym1 a1627953395 l1) l0 Source # | |
type Foldl1Sym2 t t = Foldl1 t t Source #
data Foldl1'Sym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953394 (TyFun a1627953394 a1627953394 -> Type) -> Type) (TyFun [a1627953394] a1627953394 -> Type) -> *) (Foldl1'Sym0 a1627953394) Source # | |
type Apply (TyFun a1627953394 (TyFun a1627953394 a1627953394 -> Type) -> Type) (TyFun [a1627953394] a1627953394 -> Type) (Foldl1'Sym0 a1627953394) l0 Source # | |
data Foldl1'Sym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953394 (TyFun a1627953394 a1627953394 -> Type) -> Type) -> TyFun [a1627953394] a1627953394 -> *) (Foldl1'Sym1 a1627953394) Source # | |
type Apply [a1627953394] a1627953394 (Foldl1'Sym1 a1627953394 l1) l0 Source # | |
type Foldl1'Sym2 t t = Foldl1' t t Source #
SuppressUnusedWarnings (TyFun (TyFun a1627796657 (TyFun b1627796658 b1627796658 -> Type) -> Type) (TyFun b1627796658 (TyFun [a1627796657] b1627796658 -> Type) -> Type) -> *) (FoldrSym0 a1627796657 b1627796658) Source # | |
type Apply (TyFun a1627796657 (TyFun b1627796658 b1627796658 -> Type) -> Type) (TyFun b1627796658 (TyFun [a1627796657] b1627796658 -> Type) -> Type) (FoldrSym0 a1627796657 b1627796658) l0 Source # | |
SuppressUnusedWarnings ((TyFun a1627796657 (TyFun b1627796658 b1627796658 -> Type) -> Type) -> TyFun b1627796658 (TyFun [a1627796657] b1627796658 -> Type) -> *) (FoldrSym1 a1627796657 b1627796658) Source # | |
type Apply b1627796658 (TyFun [a1627796657] b1627796658 -> Type) (FoldrSym1 a1627796657 b1627796658 l1) l0 Source # | |
data Foldr1Sym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953393 (TyFun a1627953393 a1627953393 -> Type) -> Type) (TyFun [a1627953393] a1627953393 -> Type) -> *) (Foldr1Sym0 a1627953393) Source # | |
type Apply (TyFun a1627953393 (TyFun a1627953393 a1627953393 -> Type) -> Type) (TyFun [a1627953393] a1627953393 -> Type) (Foldr1Sym0 a1627953393) l0 Source # | |
data Foldr1Sym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953393 (TyFun a1627953393 a1627953393 -> Type) -> Type) -> TyFun [a1627953393] a1627953393 -> *) (Foldr1Sym1 a1627953393) Source # | |
type Apply [a1627953393] a1627953393 (Foldr1Sym1 a1627953393 l1) l0 Source # | |
type Foldr1Sym2 t t = Foldr1 t t Source #
data ConcatSym0 l Source #
SuppressUnusedWarnings (TyFun [[a1627953392]] [a1627953392] -> *) (ConcatSym0 a1627953392) Source # | |
type Apply [[a1627953392]] [a1627953392] (ConcatSym0 a1627953392) l0 Source # | |
type ConcatSym1 t = Concat t Source #
data ConcatMapSym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953390 [b1627953391] -> Type) (TyFun [a1627953390] [b1627953391] -> Type) -> *) (ConcatMapSym0 a1627953390 b1627953391) Source # | |
type Apply (TyFun a1627953390 [b1627953391] -> Type) (TyFun [a1627953390] [b1627953391] -> Type) (ConcatMapSym0 a1627953390 b1627953391) l0 Source # | |
data ConcatMapSym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953390 [b1627953391] -> Type) -> TyFun [a1627953390] [b1627953391] -> *) (ConcatMapSym1 a1627953390 b1627953391) Source # | |
type Apply [a1627953390] [b1627953391] (ConcatMapSym1 a1627953390 b1627953391 l1) l0 Source # | |
type ConcatMapSym2 t t = ConcatMap t t Source #
SuppressUnusedWarnings (TyFun (TyFun b1627953387 (TyFun a1627953388 b1627953387 -> Type) -> Type) (TyFun b1627953387 (TyFun [a1627953388] [b1627953387] -> Type) -> Type) -> *) (ScanlSym0 a1627953388 b1627953387) Source # | |
type Apply (TyFun b1627953387 (TyFun a1627953388 b1627953387 -> Type) -> Type) (TyFun b1627953387 (TyFun [a1627953388] [b1627953387] -> Type) -> Type) (ScanlSym0 a1627953388 b1627953387) l0 Source # | |
SuppressUnusedWarnings ((TyFun b1627953387 (TyFun a1627953388 b1627953387 -> Type) -> Type) -> TyFun b1627953387 (TyFun [a1627953388] [b1627953387] -> Type) -> *) (ScanlSym1 a1627953388 b1627953387) Source # | |
type Apply b1627953387 (TyFun [a1627953388] [b1627953387] -> Type) (ScanlSym1 a1627953388 b1627953387 l1) l0 Source # | |
data Scanl1Sym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953386 (TyFun a1627953386 a1627953386 -> Type) -> Type) (TyFun [a1627953386] [a1627953386] -> Type) -> *) (Scanl1Sym0 a1627953386) Source # | |
type Apply (TyFun a1627953386 (TyFun a1627953386 a1627953386 -> Type) -> Type) (TyFun [a1627953386] [a1627953386] -> Type) (Scanl1Sym0 a1627953386) l0 Source # | |
data Scanl1Sym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953386 (TyFun a1627953386 a1627953386 -> Type) -> Type) -> TyFun [a1627953386] [a1627953386] -> *) (Scanl1Sym1 a1627953386) Source # | |
type Apply [a1627953386] [a1627953386] (Scanl1Sym1 a1627953386 l1) l0 Source # | |
type Scanl1Sym2 t t = Scanl1 t t Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953384 (TyFun b1627953385 b1627953385 -> Type) -> Type) (TyFun b1627953385 (TyFun [a1627953384] [b1627953385] -> Type) -> Type) -> *) (ScanrSym0 a1627953384 b1627953385) Source # | |
type Apply (TyFun a1627953384 (TyFun b1627953385 b1627953385 -> Type) -> Type) (TyFun b1627953385 (TyFun [a1627953384] [b1627953385] -> Type) -> Type) (ScanrSym0 a1627953384 b1627953385) l0 Source # | |
SuppressUnusedWarnings ((TyFun a1627953384 (TyFun b1627953385 b1627953385 -> Type) -> Type) -> TyFun b1627953385 (TyFun [a1627953384] [b1627953385] -> Type) -> *) (ScanrSym1 a1627953384 b1627953385) Source # | |
type Apply b1627953385 (TyFun [a1627953384] [b1627953385] -> Type) (ScanrSym1 a1627953384 b1627953385 l1) l0 Source # | |
data Scanr1Sym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953383 (TyFun a1627953383 a1627953383 -> Type) -> Type) (TyFun [a1627953383] [a1627953383] -> Type) -> *) (Scanr1Sym0 a1627953383) Source # | |
type Apply (TyFun a1627953383 (TyFun a1627953383 a1627953383 -> Type) -> Type) (TyFun [a1627953383] [a1627953383] -> Type) (Scanr1Sym0 a1627953383) l0 Source # | |
data Scanr1Sym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953383 (TyFun a1627953383 a1627953383 -> Type) -> Type) -> TyFun [a1627953383] [a1627953383] -> *) (Scanr1Sym1 a1627953383) Source # | |
type Apply [a1627953383] [a1627953383] (Scanr1Sym1 a1627953383 l1) l0 Source # | |
type Scanr1Sym2 t t = Scanr1 t t Source #
data MapAccumLSym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun acc1627953380 (TyFun x1627953381 (acc1627953380, y1627953382) -> Type) -> Type) (TyFun acc1627953380 (TyFun [x1627953381] (acc1627953380, [y1627953382]) -> Type) -> Type) -> *) (MapAccumLSym0 x1627953381 acc1627953380 y1627953382) Source # | |
type Apply (TyFun acc1627953380 (TyFun x1627953381 (acc1627953380, y1627953382) -> Type) -> Type) (TyFun acc1627953380 (TyFun [x1627953381] (acc1627953380, [y1627953382]) -> Type) -> Type) (MapAccumLSym0 x1627953381 acc1627953380 y1627953382) l0 Source # | |
data MapAccumLSym1 l l Source #
SuppressUnusedWarnings ((TyFun acc1627953380 (TyFun x1627953381 (acc1627953380, y1627953382) -> Type) -> Type) -> TyFun acc1627953380 (TyFun [x1627953381] (acc1627953380, [y1627953382]) -> Type) -> *) (MapAccumLSym1 x1627953381 acc1627953380 y1627953382) Source # | |
type Apply acc1627953380 (TyFun [x1627953381] (acc1627953380, [y1627953382]) -> Type) (MapAccumLSym1 x1627953381 acc1627953380 y1627953382 l1) l0 Source # | |
data MapAccumLSym2 l l l Source #
SuppressUnusedWarnings ((TyFun acc1627953380 (TyFun x1627953381 (acc1627953380, y1627953382) -> Type) -> Type) -> acc1627953380 -> TyFun [x1627953381] (acc1627953380, [y1627953382]) -> *) (MapAccumLSym2 x1627953381 acc1627953380 y1627953382) Source # | |
type Apply [x1627953381] (acc1627953380, [y1627953382]) (MapAccumLSym2 x1627953381 acc1627953380 y1627953382 l1 l2) l0 Source # | |
type MapAccumLSym3 t t t = MapAccumL t t t Source #
data MapAccumRSym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun acc1627953377 (TyFun x1627953378 (acc1627953377, y1627953379) -> Type) -> Type) (TyFun acc1627953377 (TyFun [x1627953378] (acc1627953377, [y1627953379]) -> Type) -> Type) -> *) (MapAccumRSym0 x1627953378 acc1627953377 y1627953379) Source # | |
type Apply (TyFun acc1627953377 (TyFun x1627953378 (acc1627953377, y1627953379) -> Type) -> Type) (TyFun acc1627953377 (TyFun [x1627953378] (acc1627953377, [y1627953379]) -> Type) -> Type) (MapAccumRSym0 x1627953378 acc1627953377 y1627953379) l0 Source # | |
data MapAccumRSym1 l l Source #
SuppressUnusedWarnings ((TyFun acc1627953377 (TyFun x1627953378 (acc1627953377, y1627953379) -> Type) -> Type) -> TyFun acc1627953377 (TyFun [x1627953378] (acc1627953377, [y1627953379]) -> Type) -> *) (MapAccumRSym1 x1627953378 acc1627953377 y1627953379) Source # | |
type Apply acc1627953377 (TyFun [x1627953378] (acc1627953377, [y1627953379]) -> Type) (MapAccumRSym1 x1627953378 acc1627953377 y1627953379 l1) l0 Source # | |
data MapAccumRSym2 l l l Source #
SuppressUnusedWarnings ((TyFun acc1627953377 (TyFun x1627953378 (acc1627953377, y1627953379) -> Type) -> Type) -> acc1627953377 -> TyFun [x1627953378] (acc1627953377, [y1627953379]) -> *) (MapAccumRSym2 x1627953378 acc1627953377 y1627953379) Source # | |
type Apply [x1627953378] (acc1627953377, [y1627953379]) (MapAccumRSym2 x1627953378 acc1627953377 y1627953379 l1 l2) l0 Source # | |
type MapAccumRSym3 t t t = MapAccumR t t t Source #
data UnfoldrSym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun b1627953375 (Maybe (a1627953376, b1627953375)) -> Type) (TyFun b1627953375 [a1627953376] -> Type) -> *) (UnfoldrSym0 b1627953375 a1627953376) Source # | |
type Apply (TyFun b1627953375 (Maybe (a1627953376, b1627953375)) -> Type) (TyFun b1627953375 [a1627953376] -> Type) (UnfoldrSym0 b1627953375 a1627953376) l0 Source # | |
data UnfoldrSym1 l l Source #
SuppressUnusedWarnings ((TyFun b1627953375 (Maybe (a1627953376, b1627953375)) -> Type) -> TyFun b1627953375 [a1627953376] -> *) (UnfoldrSym1 a1627953376 b1627953375) Source # | |
type Apply b1627953375 [a1627953376] (UnfoldrSym1 a1627953376 b1627953375 l1) l0 Source # | |
type UnfoldrSym2 t t = Unfoldr t t Source #
data IsPrefixOfSym0 l Source #
data IsPrefixOfSym1 l l Source #
SuppressUnusedWarnings ([a1627953372] -> TyFun [a1627953372] Bool -> *) (IsPrefixOfSym1 a1627953372) Source # | |
type Apply [a1627953372] Bool (IsPrefixOfSym1 a1627953372 l1) l0 Source # | |
type IsPrefixOfSym2 t t = IsPrefixOf t t Source #
data IsSuffixOfSym0 l Source #
data IsSuffixOfSym1 l l Source #
SuppressUnusedWarnings ([a1627953371] -> TyFun [a1627953371] Bool -> *) (IsSuffixOfSym1 a1627953371) Source # | |
type Apply [a1627953371] Bool (IsSuffixOfSym1 a1627953371 l1) l0 Source # | |
type IsSuffixOfSym2 t t = IsSuffixOf t t Source #
data IsInfixOfSym0 l Source #
data IsInfixOfSym1 l l Source #
SuppressUnusedWarnings ([a1627953370] -> TyFun [a1627953370] Bool -> *) (IsInfixOfSym1 a1627953370) Source # | |
type Apply [a1627953370] Bool (IsInfixOfSym1 a1627953370 l1) l0 Source # | |
type IsInfixOfSym2 t t = IsInfixOf t t Source #
data NotElemSym0 l Source #
data NotElemSym1 l l Source #
SuppressUnusedWarnings (a1627953368 -> TyFun [a1627953368] Bool -> *) (NotElemSym1 a1627953368) Source # | |
type Apply [a1627953368] Bool (NotElemSym1 a1627953368 l1) l0 Source # | |
type NotElemSym2 t t = NotElem t t Source #
SuppressUnusedWarnings (TyFun [a1627953363] (TyFun [b1627953364] (TyFun [c1627953365] [(a1627953363, b1627953364, c1627953365)] -> Type) -> Type) -> *) (Zip3Sym0 a1627953363 b1627953364 c1627953365) Source # | |
type Apply [a1627953363] (TyFun [b1627953364] (TyFun [c1627953365] [(a1627953363, b1627953364, c1627953365)] -> Type) -> Type) (Zip3Sym0 a1627953363 b1627953364 c1627953365) l0 Source # | |
SuppressUnusedWarnings ([a1627953363] -> TyFun [b1627953364] (TyFun [c1627953365] [(a1627953363, b1627953364, c1627953365)] -> Type) -> *) (Zip3Sym1 b1627953364 c1627953365 a1627953363) Source # | |
type Apply [b1627953364] (TyFun [c1627953365] [(a1627953363, b1627953364, c1627953365)] -> Type) (Zip3Sym1 b1627953364 c1627953365 a1627953363 l1) l0 Source # | |
SuppressUnusedWarnings ([a1627953363] -> [b1627953364] -> TyFun [c1627953365] [(a1627953363, b1627953364, c1627953365)] -> *) (Zip3Sym2 c1627953365 b1627953364 a1627953363) Source # | |
type Apply [c1627953365] [(a1627953363, b1627953364, c1627953365)] (Zip3Sym2 c1627953365 b1627953364 a1627953363 l1 l2) l0 Source # | |
data ZipWithSym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953360 (TyFun b1627953361 c1627953362 -> Type) -> Type) (TyFun [a1627953360] (TyFun [b1627953361] [c1627953362] -> Type) -> Type) -> *) (ZipWithSym0 a1627953360 b1627953361 c1627953362) Source # | |
type Apply (TyFun a1627953360 (TyFun b1627953361 c1627953362 -> Type) -> Type) (TyFun [a1627953360] (TyFun [b1627953361] [c1627953362] -> Type) -> Type) (ZipWithSym0 a1627953360 b1627953361 c1627953362) l0 Source # | |
data ZipWithSym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953360 (TyFun b1627953361 c1627953362 -> Type) -> Type) -> TyFun [a1627953360] (TyFun [b1627953361] [c1627953362] -> Type) -> *) (ZipWithSym1 a1627953360 b1627953361 c1627953362) Source # | |
type Apply [a1627953360] (TyFun [b1627953361] [c1627953362] -> Type) (ZipWithSym1 a1627953360 b1627953361 c1627953362 l1) l0 Source # | |
data ZipWithSym2 l l l Source #
SuppressUnusedWarnings ((TyFun a1627953360 (TyFun b1627953361 c1627953362 -> Type) -> Type) -> [a1627953360] -> TyFun [b1627953361] [c1627953362] -> *) (ZipWithSym2 a1627953360 b1627953361 c1627953362) Source # | |
type Apply [b1627953361] [c1627953362] (ZipWithSym2 a1627953360 b1627953361 c1627953362 l1 l2) l0 Source # | |
type ZipWithSym3 t t t = ZipWith t t t Source #
data ZipWith3Sym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953356 (TyFun b1627953357 (TyFun c1627953358 d1627953359 -> Type) -> Type) -> Type) (TyFun [a1627953356] (TyFun [b1627953357] (TyFun [c1627953358] [d1627953359] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a1627953356 b1627953357 c1627953358 d1627953359) Source # | |
type Apply (TyFun a1627953356 (TyFun b1627953357 (TyFun c1627953358 d1627953359 -> Type) -> Type) -> Type) (TyFun [a1627953356] (TyFun [b1627953357] (TyFun [c1627953358] [d1627953359] -> Type) -> Type) -> Type) (ZipWith3Sym0 a1627953356 b1627953357 c1627953358 d1627953359) l0 Source # | |
data ZipWith3Sym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953356 (TyFun b1627953357 (TyFun c1627953358 d1627953359 -> Type) -> Type) -> Type) -> TyFun [a1627953356] (TyFun [b1627953357] (TyFun [c1627953358] [d1627953359] -> Type) -> Type) -> *) (ZipWith3Sym1 a1627953356 b1627953357 c1627953358 d1627953359) Source # | |
type Apply [a1627953356] (TyFun [b1627953357] (TyFun [c1627953358] [d1627953359] -> Type) -> Type) (ZipWith3Sym1 a1627953356 b1627953357 c1627953358 d1627953359 l1) l0 Source # | |
data ZipWith3Sym2 l l l Source #
SuppressUnusedWarnings ((TyFun a1627953356 (TyFun b1627953357 (TyFun c1627953358 d1627953359 -> Type) -> Type) -> Type) -> [a1627953356] -> TyFun [b1627953357] (TyFun [c1627953358] [d1627953359] -> Type) -> *) (ZipWith3Sym2 a1627953356 b1627953357 c1627953358 d1627953359) Source # | |
type Apply [b1627953357] (TyFun [c1627953358] [d1627953359] -> Type) (ZipWith3Sym2 a1627953356 b1627953357 c1627953358 d1627953359 l1 l2) l0 Source # | |
data ZipWith3Sym3 l l l l Source #
SuppressUnusedWarnings ((TyFun a1627953356 (TyFun b1627953357 (TyFun c1627953358 d1627953359 -> Type) -> Type) -> Type) -> [a1627953356] -> [b1627953357] -> TyFun [c1627953358] [d1627953359] -> *) (ZipWith3Sym3 a1627953356 b1627953357 c1627953358 d1627953359) Source # | |
type Apply [c1627953358] [d1627953359] (ZipWith3Sym3 a1627953356 b1627953357 c1627953358 d1627953359 l1 l2 l3) l0 Source # | |
type ZipWith3Sym4 t t t t = ZipWith3 t t t t Source #
data Unzip3Sym0 l Source #
SuppressUnusedWarnings (TyFun [(a1627953351, b1627953352, c1627953353)] ([a1627953351], [b1627953352], [c1627953353]) -> *) (Unzip3Sym0 a1627953351 b1627953352 c1627953353) Source # | |
type Apply [(a1627953351, b1627953352, c1627953353)] ([a1627953351], [b1627953352], [c1627953353]) (Unzip3Sym0 a1627953351 b1627953352 c1627953353) l0 Source # | |
type Unzip3Sym1 t = Unzip3 t Source #
data Unzip4Sym0 l Source #
SuppressUnusedWarnings (TyFun [(a1627953347, b1627953348, c1627953349, d1627953350)] ([a1627953347], [b1627953348], [c1627953349], [d1627953350]) -> *) (Unzip4Sym0 a1627953347 b1627953348 c1627953349 d1627953350) Source # | |
type Apply [(a1627953347, b1627953348, c1627953349, d1627953350)] ([a1627953347], [b1627953348], [c1627953349], [d1627953350]) (Unzip4Sym0 a1627953347 b1627953348 c1627953349 d1627953350) l0 Source # | |
type Unzip4Sym1 t = Unzip4 t Source #
data Unzip5Sym0 l Source #
SuppressUnusedWarnings (TyFun [(a1627953342, b1627953343, c1627953344, d1627953345, e1627953346)] ([a1627953342], [b1627953343], [c1627953344], [d1627953345], [e1627953346]) -> *) (Unzip5Sym0 a1627953342 b1627953343 c1627953344 d1627953345 e1627953346) Source # | |
type Apply [(a1627953342, b1627953343, c1627953344, d1627953345, e1627953346)] ([a1627953342], [b1627953343], [c1627953344], [d1627953345], [e1627953346]) (Unzip5Sym0 a1627953342 b1627953343 c1627953344 d1627953345 e1627953346) l0 Source # | |
type Unzip5Sym1 t = Unzip5 t Source #
data Unzip6Sym0 l Source #
SuppressUnusedWarnings (TyFun [(a1627953336, b1627953337, c1627953338, d1627953339, e1627953340, f1627953341)] ([a1627953336], [b1627953337], [c1627953338], [d1627953339], [e1627953340], [f1627953341]) -> *) (Unzip6Sym0 a1627953336 b1627953337 c1627953338 d1627953339 e1627953340 f1627953341) Source # | |
type Apply [(a1627953336, b1627953337, c1627953338, d1627953339, e1627953340, f1627953341)] ([a1627953336], [b1627953337], [c1627953338], [d1627953339], [e1627953340], [f1627953341]) (Unzip6Sym0 a1627953336 b1627953337 c1627953338 d1627953339 e1627953340 f1627953341) l0 Source # | |
type Unzip6Sym1 t = Unzip6 t Source #
data Unzip7Sym0 l Source #
SuppressUnusedWarnings (TyFun [(a1627953329, b1627953330, c1627953331, d1627953332, e1627953333, f1627953334, g1627953335)] ([a1627953329], [b1627953330], [c1627953331], [d1627953332], [e1627953333], [f1627953334], [g1627953335]) -> *) (Unzip7Sym0 a1627953329 b1627953330 c1627953331 d1627953332 e1627953333 f1627953334 g1627953335) Source # | |
type Apply [(a1627953329, b1627953330, c1627953331, d1627953332, e1627953333, f1627953334, g1627953335)] ([a1627953329], [b1627953330], [c1627953331], [d1627953332], [e1627953333], [f1627953334], [g1627953335]) (Unzip7Sym0 a1627953329 b1627953330 c1627953331 d1627953332 e1627953333 f1627953334 g1627953335) l0 Source # | |
type Unzip7Sym1 t = Unzip7 t Source #
data DeleteSym0 l Source #
SuppressUnusedWarnings (TyFun a1627953328 (TyFun [a1627953328] [a1627953328] -> Type) -> *) (DeleteSym0 a1627953328) Source # | |
type Apply a1627953328 (TyFun [a1627953328] [a1627953328] -> Type) (DeleteSym0 a1627953328) l0 Source # | |
data DeleteSym1 l l Source #
SuppressUnusedWarnings (a1627953328 -> TyFun [a1627953328] [a1627953328] -> *) (DeleteSym1 a1627953328) Source # | |
type Apply [a1627953328] [a1627953328] (DeleteSym1 a1627953328 l1) l0 Source # | |
type DeleteSym2 t t = Delete t t Source #
data IntersectSym0 l Source #
SuppressUnusedWarnings (TyFun [a1627953314] (TyFun [a1627953314] [a1627953314] -> Type) -> *) (IntersectSym0 a1627953314) Source # | |
type Apply [a1627953314] (TyFun [a1627953314] [a1627953314] -> Type) (IntersectSym0 a1627953314) l0 Source # | |
data IntersectSym1 l l Source #
SuppressUnusedWarnings ([a1627953314] -> TyFun [a1627953314] [a1627953314] -> *) (IntersectSym1 a1627953314) Source # | |
type Apply [a1627953314] [a1627953314] (IntersectSym1 a1627953314 l1) l0 Source # | |
type IntersectSym2 t t = Intersect t t Source #
data InsertSym0 l Source #
SuppressUnusedWarnings (TyFun a1627953301 (TyFun [a1627953301] [a1627953301] -> Type) -> *) (InsertSym0 a1627953301) Source # | |
type Apply a1627953301 (TyFun [a1627953301] [a1627953301] -> Type) (InsertSym0 a1627953301) l0 Source # | |
data InsertSym1 l l Source #
SuppressUnusedWarnings (a1627953301 -> TyFun [a1627953301] [a1627953301] -> *) (InsertSym1 a1627953301) Source # | |
type Apply [a1627953301] [a1627953301] (InsertSym1 a1627953301 l1) l0 Source # | |
type InsertSym2 t t = Insert t t Source #
data DeleteBySym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953326 (TyFun a1627953326 Bool -> Type) -> Type) (TyFun a1627953326 (TyFun [a1627953326] [a1627953326] -> Type) -> Type) -> *) (DeleteBySym0 a1627953326) Source # | |
type Apply (TyFun a1627953326 (TyFun a1627953326 Bool -> Type) -> Type) (TyFun a1627953326 (TyFun [a1627953326] [a1627953326] -> Type) -> Type) (DeleteBySym0 a1627953326) l0 Source # | |
data DeleteBySym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953326 (TyFun a1627953326 Bool -> Type) -> Type) -> TyFun a1627953326 (TyFun [a1627953326] [a1627953326] -> Type) -> *) (DeleteBySym1 a1627953326) Source # | |
type Apply a1627953326 (TyFun [a1627953326] [a1627953326] -> Type) (DeleteBySym1 a1627953326 l1) l0 Source # | |
data DeleteBySym2 l l l Source #
SuppressUnusedWarnings ((TyFun a1627953326 (TyFun a1627953326 Bool -> Type) -> Type) -> a1627953326 -> TyFun [a1627953326] [a1627953326] -> *) (DeleteBySym2 a1627953326) Source # | |
type Apply [a1627953326] [a1627953326] (DeleteBySym2 a1627953326 l1 l2) l0 Source # | |
type DeleteBySym3 t t t = DeleteBy t t t Source #
data DeleteFirstsBySym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953325 (TyFun a1627953325 Bool -> Type) -> Type) (TyFun [a1627953325] (TyFun [a1627953325] [a1627953325] -> Type) -> Type) -> *) (DeleteFirstsBySym0 a1627953325) Source # | |
type Apply (TyFun a1627953325 (TyFun a1627953325 Bool -> Type) -> Type) (TyFun [a1627953325] (TyFun [a1627953325] [a1627953325] -> Type) -> Type) (DeleteFirstsBySym0 a1627953325) l0 Source # | |
data DeleteFirstsBySym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953325 (TyFun a1627953325 Bool -> Type) -> Type) -> TyFun [a1627953325] (TyFun [a1627953325] [a1627953325] -> Type) -> *) (DeleteFirstsBySym1 a1627953325) Source # | |
type Apply [a1627953325] (TyFun [a1627953325] [a1627953325] -> Type) (DeleteFirstsBySym1 a1627953325 l1) l0 Source # | |
data DeleteFirstsBySym2 l l l Source #
SuppressUnusedWarnings ((TyFun a1627953325 (TyFun a1627953325 Bool -> Type) -> Type) -> [a1627953325] -> TyFun [a1627953325] [a1627953325] -> *) (DeleteFirstsBySym2 a1627953325) Source # | |
type Apply [a1627953325] [a1627953325] (DeleteFirstsBySym2 a1627953325 l1 l2) l0 Source # | |
type DeleteFirstsBySym3 t t t = DeleteFirstsBy t t t Source #
data IntersectBySym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953313 (TyFun a1627953313 Bool -> Type) -> Type) (TyFun [a1627953313] (TyFun [a1627953313] [a1627953313] -> Type) -> Type) -> *) (IntersectBySym0 a1627953313) Source # | |
type Apply (TyFun a1627953313 (TyFun a1627953313 Bool -> Type) -> Type) (TyFun [a1627953313] (TyFun [a1627953313] [a1627953313] -> Type) -> Type) (IntersectBySym0 a1627953313) l0 Source # | |
data IntersectBySym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953313 (TyFun a1627953313 Bool -> Type) -> Type) -> TyFun [a1627953313] (TyFun [a1627953313] [a1627953313] -> Type) -> *) (IntersectBySym1 a1627953313) Source # | |
type Apply [a1627953313] (TyFun [a1627953313] [a1627953313] -> Type) (IntersectBySym1 a1627953313 l1) l0 Source # | |
data IntersectBySym2 l l l Source #
SuppressUnusedWarnings ((TyFun a1627953313 (TyFun a1627953313 Bool -> Type) -> Type) -> [a1627953313] -> TyFun [a1627953313] [a1627953313] -> *) (IntersectBySym2 a1627953313) Source # | |
type Apply [a1627953313] [a1627953313] (IntersectBySym2 a1627953313 l1 l2) l0 Source # | |
data SortBySym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953324 (TyFun a1627953324 Ordering -> Type) -> Type) (TyFun [a1627953324] [a1627953324] -> Type) -> *) (SortBySym0 a1627953324) Source # | |
type Apply (TyFun a1627953324 (TyFun a1627953324 Ordering -> Type) -> Type) (TyFun [a1627953324] [a1627953324] -> Type) (SortBySym0 a1627953324) l0 Source # | |
data SortBySym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953324 (TyFun a1627953324 Ordering -> Type) -> Type) -> TyFun [a1627953324] [a1627953324] -> *) (SortBySym1 a1627953324) Source # | |
type Apply [a1627953324] [a1627953324] (SortBySym1 a1627953324 l1) l0 Source # | |
type SortBySym2 t t = SortBy t t Source #
data InsertBySym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953323 (TyFun a1627953323 Ordering -> Type) -> Type) (TyFun a1627953323 (TyFun [a1627953323] [a1627953323] -> Type) -> Type) -> *) (InsertBySym0 a1627953323) Source # | |
type Apply (TyFun a1627953323 (TyFun a1627953323 Ordering -> Type) -> Type) (TyFun a1627953323 (TyFun [a1627953323] [a1627953323] -> Type) -> Type) (InsertBySym0 a1627953323) l0 Source # | |
data InsertBySym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953323 (TyFun a1627953323 Ordering -> Type) -> Type) -> TyFun a1627953323 (TyFun [a1627953323] [a1627953323] -> Type) -> *) (InsertBySym1 a1627953323) Source # | |
type Apply a1627953323 (TyFun [a1627953323] [a1627953323] -> Type) (InsertBySym1 a1627953323 l1) l0 Source # | |
data InsertBySym2 l l l Source #
SuppressUnusedWarnings ((TyFun a1627953323 (TyFun a1627953323 Ordering -> Type) -> Type) -> a1627953323 -> TyFun [a1627953323] [a1627953323] -> *) (InsertBySym2 a1627953323) Source # | |
type Apply [a1627953323] [a1627953323] (InsertBySym2 a1627953323 l1 l2) l0 Source # | |
type InsertBySym3 t t t = InsertBy t t t Source #
data MaximumBySym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953322 (TyFun a1627953322 Ordering -> Type) -> Type) (TyFun [a1627953322] a1627953322 -> Type) -> *) (MaximumBySym0 a1627953322) Source # | |
type Apply (TyFun a1627953322 (TyFun a1627953322 Ordering -> Type) -> Type) (TyFun [a1627953322] a1627953322 -> Type) (MaximumBySym0 a1627953322) l0 Source # | |
data MaximumBySym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953322 (TyFun a1627953322 Ordering -> Type) -> Type) -> TyFun [a1627953322] a1627953322 -> *) (MaximumBySym1 a1627953322) Source # | |
type Apply [a1627953322] a1627953322 (MaximumBySym1 a1627953322 l1) l0 Source # | |
type MaximumBySym2 t t = MaximumBy t t Source #
data MinimumBySym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953321 (TyFun a1627953321 Ordering -> Type) -> Type) (TyFun [a1627953321] a1627953321 -> Type) -> *) (MinimumBySym0 a1627953321) Source # | |
type Apply (TyFun a1627953321 (TyFun a1627953321 Ordering -> Type) -> Type) (TyFun [a1627953321] a1627953321 -> Type) (MinimumBySym0 a1627953321) l0 Source # | |
data MinimumBySym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953321 (TyFun a1627953321 Ordering -> Type) -> Type) -> TyFun [a1627953321] a1627953321 -> *) (MinimumBySym1 a1627953321) Source # | |
type Apply [a1627953321] a1627953321 (MinimumBySym1 a1627953321 l1) l0 Source # | |
type MinimumBySym2 t t = MinimumBy t t Source #
data LengthSym0 l Source #
SuppressUnusedWarnings (TyFun [a1627953292] Nat -> *) (LengthSym0 a1627953292) Source # | |
type Apply [a1627953292] Nat (LengthSym0 a1627953292) l0 Source # | |
type LengthSym1 t = Length t Source #
data ProductSym0 l Source #
SuppressUnusedWarnings (TyFun [a1627953293] a1627953293 -> *) (ProductSym0 a1627953293) Source # | |
type Apply [a1627953293] a1627953293 (ProductSym0 a1627953293) l0 Source # | |
type ProductSym1 t = Product t Source #
data ReplicateSym0 l Source #
data ReplicateSym1 l l Source #
SuppressUnusedWarnings (Nat -> TyFun a1627953291 [a1627953291] -> *) (ReplicateSym1 a1627953291) Source # | |
type Apply a1627953291 [a1627953291] (ReplicateSym1 a1627953291 l1) l0 Source # | |
type ReplicateSym2 t t = Replicate t t Source #
data TransposeSym0 l Source #
SuppressUnusedWarnings (TyFun [[a1627953290]] [[a1627953290]] -> *) (TransposeSym0 a1627953290) Source # | |
type Apply [[a1627953290]] [[a1627953290]] (TransposeSym0 a1627953290) l0 Source # | |
type TransposeSym1 t = Transpose t Source #
data SplitAtSym0 l Source #
data SplitAtSym1 l l Source #
SuppressUnusedWarnings (Nat -> TyFun [a1627953305] ([a1627953305], [a1627953305]) -> *) (SplitAtSym1 a1627953305) Source # | |
type Apply [a1627953305] ([a1627953305], [a1627953305]) (SplitAtSym1 a1627953305 l1) l0 Source # | |
type SplitAtSym2 t t = SplitAt t t Source #
data TakeWhileSym0 l Source #
data TakeWhileSym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953312 Bool -> Type) -> TyFun [a1627953312] [a1627953312] -> *) (TakeWhileSym1 a1627953312) Source # | |
type Apply [a1627953312] [a1627953312] (TakeWhileSym1 a1627953312 l1) l0 Source # | |
type TakeWhileSym2 t t = TakeWhile t t Source #
data DropWhileSym0 l Source #
data DropWhileSym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953311 Bool -> Type) -> TyFun [a1627953311] [a1627953311] -> *) (DropWhileSym1 a1627953311) Source # | |
type Apply [a1627953311] [a1627953311] (DropWhileSym1 a1627953311 l1) l0 Source # | |
type DropWhileSym2 t t = DropWhile t t Source #
data DropWhileEndSym0 l Source #
data DropWhileEndSym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953310 Bool -> Type) -> TyFun [a1627953310] [a1627953310] -> *) (DropWhileEndSym1 a1627953310) Source # | |
type Apply [a1627953310] [a1627953310] (DropWhileEndSym1 a1627953310 l1) l0 Source # | |
type DropWhileEndSym2 t t = DropWhileEnd t t Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953309 Bool -> Type) (TyFun [a1627953309] ([a1627953309], [a1627953309]) -> Type) -> *) (SpanSym0 a1627953309) Source # | |
type Apply (TyFun a1627953309 Bool -> Type) (TyFun [a1627953309] ([a1627953309], [a1627953309]) -> Type) (SpanSym0 a1627953309) l0 Source # | |
SuppressUnusedWarnings (TyFun (TyFun a1627953308 Bool -> Type) (TyFun [a1627953308] ([a1627953308], [a1627953308]) -> Type) -> *) (BreakSym0 a1627953308) Source # | |
type Apply (TyFun a1627953308 Bool -> Type) (TyFun [a1627953308] ([a1627953308], [a1627953308]) -> Type) (BreakSym0 a1627953308) l0 Source # | |
data StripPrefixSym0 l Source #
data StripPrefixSym1 l l Source #
SuppressUnusedWarnings ([a1628251687] -> TyFun [a1628251687] (Maybe [a1628251687]) -> *) (StripPrefixSym1 a1628251687) Source # | |
type Apply [a1628251687] (Maybe [a1628251687]) (StripPrefixSym1 a1628251687 l1) l0 Source # | |
type StripPrefixSym2 t t = StripPrefix t t Source #
data MaximumSym0 l Source #
SuppressUnusedWarnings (TyFun [a1627953303] a1627953303 -> *) (MaximumSym0 a1627953303) Source # | |
type Apply [a1627953303] a1627953303 (MaximumSym0 a1627953303) l0 Source # | |
type MaximumSym1 t = Maximum t Source #
data MinimumSym0 l Source #
SuppressUnusedWarnings (TyFun [a1627953302] a1627953302 -> *) (MinimumSym0 a1627953302) Source # | |
type Apply [a1627953302] a1627953302 (MinimumSym0 a1627953302) l0 Source # | |
type MinimumSym1 t = Minimum t Source #
data GroupBySym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953299 (TyFun a1627953299 Bool -> Type) -> Type) (TyFun [a1627953299] [[a1627953299]] -> Type) -> *) (GroupBySym0 a1627953299) Source # | |
type Apply (TyFun a1627953299 (TyFun a1627953299 Bool -> Type) -> Type) (TyFun [a1627953299] [[a1627953299]] -> Type) (GroupBySym0 a1627953299) l0 Source # | |
data GroupBySym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953299 (TyFun a1627953299 Bool -> Type) -> Type) -> TyFun [a1627953299] [[a1627953299]] -> *) (GroupBySym1 a1627953299) Source # | |
type Apply [a1627953299] [[a1627953299]] (GroupBySym1 a1627953299 l1) l0 Source # | |
type GroupBySym2 t t = GroupBy t t Source #
data LookupSym0 l Source #
data LookupSym1 l l Source #
SuppressUnusedWarnings (a1627953297 -> TyFun [(a1627953297, b1627953298)] (Maybe b1627953298) -> *) (LookupSym1 b1627953298 a1627953297) Source # | |
type Apply [(a1627953297, b1627953298)] (Maybe b1627953298) (LookupSym1 b1627953298 a1627953297 l1) l0 Source # | |
type LookupSym2 t t = Lookup t t Source #
data FilterSym0 l Source #
data FilterSym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953320 Bool -> Type) -> TyFun [a1627953320] [a1627953320] -> *) (FilterSym1 a1627953320) Source # | |
type Apply [a1627953320] [a1627953320] (FilterSym1 a1627953320 l1) l0 Source # | |
type FilterSym2 t t = Filter t t Source #
data PartitionSym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953296 Bool -> Type) (TyFun [a1627953296] ([a1627953296], [a1627953296]) -> Type) -> *) (PartitionSym0 a1627953296) Source # | |
type Apply (TyFun a1627953296 Bool -> Type) (TyFun [a1627953296] ([a1627953296], [a1627953296]) -> Type) (PartitionSym0 a1627953296) l0 Source # | |
data PartitionSym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953296 Bool -> Type) -> TyFun [a1627953296] ([a1627953296], [a1627953296]) -> *) (PartitionSym1 a1627953296) Source # | |
type Apply [a1627953296] ([a1627953296], [a1627953296]) (PartitionSym1 a1627953296 l1) l0 Source # | |
type PartitionSym2 t t = Partition t t Source #
data ElemIndexSym0 l Source #
data ElemIndexSym1 l l Source #
SuppressUnusedWarnings (a1627953318 -> TyFun [a1627953318] (Maybe Nat) -> *) (ElemIndexSym1 a1627953318) Source # | |
type Apply [a1627953318] (Maybe Nat) (ElemIndexSym1 a1627953318 l1) l0 Source # | |
type ElemIndexSym2 t t = ElemIndex t t Source #
data ElemIndicesSym0 l Source #
data ElemIndicesSym1 l l Source #
SuppressUnusedWarnings (a1627953317 -> TyFun [a1627953317] [Nat] -> *) (ElemIndicesSym1 a1627953317) Source # | |
type Apply [a1627953317] [Nat] (ElemIndicesSym1 a1627953317 l1) l0 Source # | |
type ElemIndicesSym2 t t = ElemIndices t t Source #
data FindIndexSym0 l Source #
data FindIndexSym1 l l Source #
type FindIndexSym2 t t = FindIndex t t Source #
data FindIndicesSym0 l Source #
data FindIndicesSym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953315 Bool -> Type) -> TyFun [a1627953315] [Nat] -> *) (FindIndicesSym1 a1627953315) Source # | |
type Apply [a1627953315] [Nat] (FindIndicesSym1 a1627953315 l1) l0 Source # | |
type FindIndicesSym2 t t = FindIndices t t Source #
SuppressUnusedWarnings (TyFun [a1628251683] (TyFun [b1628251684] (TyFun [c1628251685] (TyFun [d1628251686] [(a1628251683, b1628251684, c1628251685, d1628251686)] -> Type) -> Type) -> Type) -> *) (Zip4Sym0 a1628251683 b1628251684 c1628251685 d1628251686) Source # | |
type Apply [a1628251683] (TyFun [b1628251684] (TyFun [c1628251685] (TyFun [d1628251686] [(a1628251683, b1628251684, c1628251685, d1628251686)] -> Type) -> Type) -> Type) (Zip4Sym0 a1628251683 b1628251684 c1628251685 d1628251686) l0 Source # | |
SuppressUnusedWarnings ([a1628251683] -> TyFun [b1628251684] (TyFun [c1628251685] (TyFun [d1628251686] [(a1628251683, b1628251684, c1628251685, d1628251686)] -> Type) -> Type) -> *) (Zip4Sym1 b1628251684 c1628251685 d1628251686 a1628251683) Source # | |
type Apply [b1628251684] (TyFun [c1628251685] (TyFun [d1628251686] [(a1628251683, b1628251684, c1628251685, d1628251686)] -> Type) -> Type) (Zip4Sym1 b1628251684 c1628251685 d1628251686 a1628251683 l1) l0 Source # | |
SuppressUnusedWarnings ([a1628251683] -> [b1628251684] -> TyFun [c1628251685] (TyFun [d1628251686] [(a1628251683, b1628251684, c1628251685, d1628251686)] -> Type) -> *) (Zip4Sym2 c1628251685 d1628251686 b1628251684 a1628251683) Source # | |
type Apply [c1628251685] (TyFun [d1628251686] [(a1628251683, b1628251684, c1628251685, d1628251686)] -> Type) (Zip4Sym2 c1628251685 d1628251686 b1628251684 a1628251683 l1 l2) l0 Source # | |
data Zip4Sym3 l l l l Source #
SuppressUnusedWarnings ([a1628251683] -> [b1628251684] -> [c1628251685] -> TyFun [d1628251686] [(a1628251683, b1628251684, c1628251685, d1628251686)] -> *) (Zip4Sym3 d1628251686 c1628251685 b1628251684 a1628251683) Source # | |
type Apply [d1628251686] [(a1628251683, b1628251684, c1628251685, d1628251686)] (Zip4Sym3 d1628251686 c1628251685 b1628251684 a1628251683 l1 l2 l3) l0 Source # | |
SuppressUnusedWarnings (TyFun [a1628251678] (TyFun [b1628251679] (TyFun [c1628251680] (TyFun [d1628251681] (TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip5Sym0 a1628251678 b1628251679 c1628251680 d1628251681 e1628251682) Source # | |
type Apply [a1628251678] (TyFun [b1628251679] (TyFun [c1628251680] (TyFun [d1628251681] (TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> Type) -> Type) -> Type) -> Type) (Zip5Sym0 a1628251678 b1628251679 c1628251680 d1628251681 e1628251682) l0 Source # | |
SuppressUnusedWarnings ([a1628251678] -> TyFun [b1628251679] (TyFun [c1628251680] (TyFun [d1628251681] (TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> Type) -> Type) -> Type) -> *) (Zip5Sym1 b1628251679 c1628251680 d1628251681 e1628251682 a1628251678) Source # | |
type Apply [b1628251679] (TyFun [c1628251680] (TyFun [d1628251681] (TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> Type) -> Type) -> Type) (Zip5Sym1 b1628251679 c1628251680 d1628251681 e1628251682 a1628251678 l1) l0 Source # | |
SuppressUnusedWarnings ([a1628251678] -> [b1628251679] -> TyFun [c1628251680] (TyFun [d1628251681] (TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> Type) -> Type) -> *) (Zip5Sym2 c1628251680 d1628251681 e1628251682 b1628251679 a1628251678) Source # | |
type Apply [c1628251680] (TyFun [d1628251681] (TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> Type) -> Type) (Zip5Sym2 c1628251680 d1628251681 e1628251682 b1628251679 a1628251678 l1 l2) l0 Source # | |
data Zip5Sym3 l l l l Source #
SuppressUnusedWarnings ([a1628251678] -> [b1628251679] -> [c1628251680] -> TyFun [d1628251681] (TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> Type) -> *) (Zip5Sym3 d1628251681 e1628251682 c1628251680 b1628251679 a1628251678) Source # | |
type Apply [d1628251681] (TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> Type) (Zip5Sym3 d1628251681 e1628251682 c1628251680 b1628251679 a1628251678 l1 l2 l3) l0 Source # | |
data Zip5Sym4 l l l l l Source #
SuppressUnusedWarnings ([a1628251678] -> [b1628251679] -> [c1628251680] -> [d1628251681] -> TyFun [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] -> *) (Zip5Sym4 e1628251682 d1628251681 c1628251680 b1628251679 a1628251678) Source # | |
type Apply [e1628251682] [(a1628251678, b1628251679, c1628251680, d1628251681, e1628251682)] (Zip5Sym4 e1628251682 d1628251681 c1628251680 b1628251679 a1628251678 l1 l2 l3 l4) l0 Source # | |
SuppressUnusedWarnings (TyFun [a1628251672] (TyFun [b1628251673] (TyFun [c1628251674] (TyFun [d1628251675] (TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym0 a1628251672 b1628251673 c1628251674 d1628251675 e1628251676 f1628251677) Source # | |
type Apply [a1628251672] (TyFun [b1628251673] (TyFun [c1628251674] (TyFun [d1628251675] (TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip6Sym0 a1628251672 b1628251673 c1628251674 d1628251675 e1628251676 f1628251677) l0 Source # | |
SuppressUnusedWarnings ([a1628251672] -> TyFun [b1628251673] (TyFun [c1628251674] (TyFun [d1628251675] (TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip6Sym1 b1628251673 c1628251674 d1628251675 e1628251676 f1628251677 a1628251672) Source # | |
type Apply [b1628251673] (TyFun [c1628251674] (TyFun [d1628251675] (TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> Type) -> Type) -> Type) (Zip6Sym1 b1628251673 c1628251674 d1628251675 e1628251676 f1628251677 a1628251672 l1) l0 Source # | |
SuppressUnusedWarnings ([a1628251672] -> [b1628251673] -> TyFun [c1628251674] (TyFun [d1628251675] (TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> Type) -> Type) -> *) (Zip6Sym2 c1628251674 d1628251675 e1628251676 f1628251677 b1628251673 a1628251672) Source # | |
type Apply [c1628251674] (TyFun [d1628251675] (TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> Type) -> Type) (Zip6Sym2 c1628251674 d1628251675 e1628251676 f1628251677 b1628251673 a1628251672 l1 l2) l0 Source # | |
data Zip6Sym3 l l l l Source #
SuppressUnusedWarnings ([a1628251672] -> [b1628251673] -> [c1628251674] -> TyFun [d1628251675] (TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> Type) -> *) (Zip6Sym3 d1628251675 e1628251676 f1628251677 c1628251674 b1628251673 a1628251672) Source # | |
type Apply [d1628251675] (TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> Type) (Zip6Sym3 d1628251675 e1628251676 f1628251677 c1628251674 b1628251673 a1628251672 l1 l2 l3) l0 Source # | |
data Zip6Sym4 l l l l l Source #
SuppressUnusedWarnings ([a1628251672] -> [b1628251673] -> [c1628251674] -> [d1628251675] -> TyFun [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) -> *) (Zip6Sym4 e1628251676 f1628251677 d1628251675 c1628251674 b1628251673 a1628251672) Source # | |
type Apply [e1628251676] (TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> Type) (Zip6Sym4 e1628251676 f1628251677 d1628251675 c1628251674 b1628251673 a1628251672 l1 l2 l3 l4) l0 Source # | |
data Zip6Sym5 l l l l l l Source #
SuppressUnusedWarnings ([a1628251672] -> [b1628251673] -> [c1628251674] -> [d1628251675] -> [e1628251676] -> TyFun [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] -> *) (Zip6Sym5 f1628251677 e1628251676 d1628251675 c1628251674 b1628251673 a1628251672) Source # | |
type Apply [f1628251677] [(a1628251672, b1628251673, c1628251674, d1628251675, e1628251676, f1628251677)] (Zip6Sym5 f1628251677 e1628251676 d1628251675 c1628251674 b1628251673 a1628251672 l1 l2 l3 l4 l5) l0 Source # | |
SuppressUnusedWarnings (TyFun [a1628251665] (TyFun [b1628251666] (TyFun [c1628251667] (TyFun [d1628251668] (TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym0 a1628251665 b1628251666 c1628251667 d1628251668 e1628251669 f1628251670 g1628251671) Source # | |
type Apply [a1628251665] (TyFun [b1628251666] (TyFun [c1628251667] (TyFun [d1628251668] (TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym0 a1628251665 b1628251666 c1628251667 d1628251668 e1628251669 f1628251670 g1628251671) l0 Source # | |
SuppressUnusedWarnings ([a1628251665] -> TyFun [b1628251666] (TyFun [c1628251667] (TyFun [d1628251668] (TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym1 b1628251666 c1628251667 d1628251668 e1628251669 f1628251670 g1628251671 a1628251665) Source # | |
type Apply [b1628251666] (TyFun [c1628251667] (TyFun [d1628251668] (TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> Type) -> Type) -> Type) (Zip7Sym1 b1628251666 c1628251667 d1628251668 e1628251669 f1628251670 g1628251671 a1628251665 l1) l0 Source # | |
SuppressUnusedWarnings ([a1628251665] -> [b1628251666] -> TyFun [c1628251667] (TyFun [d1628251668] (TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> Type) -> Type) -> *) (Zip7Sym2 c1628251667 d1628251668 e1628251669 f1628251670 g1628251671 b1628251666 a1628251665) Source # | |
type Apply [c1628251667] (TyFun [d1628251668] (TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> Type) -> Type) (Zip7Sym2 c1628251667 d1628251668 e1628251669 f1628251670 g1628251671 b1628251666 a1628251665 l1 l2) l0 Source # | |
data Zip7Sym3 l l l l Source #
SuppressUnusedWarnings ([a1628251665] -> [b1628251666] -> [c1628251667] -> TyFun [d1628251668] (TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> Type) -> *) (Zip7Sym3 d1628251668 e1628251669 f1628251670 g1628251671 c1628251667 b1628251666 a1628251665) Source # | |
type Apply [d1628251668] (TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> Type) (Zip7Sym3 d1628251668 e1628251669 f1628251670 g1628251671 c1628251667 b1628251666 a1628251665 l1 l2 l3) l0 Source # | |
data Zip7Sym4 l l l l l Source #
SuppressUnusedWarnings ([a1628251665] -> [b1628251666] -> [c1628251667] -> [d1628251668] -> TyFun [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) -> *) (Zip7Sym4 e1628251669 f1628251670 g1628251671 d1628251668 c1628251667 b1628251666 a1628251665) Source # | |
type Apply [e1628251669] (TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> Type) (Zip7Sym4 e1628251669 f1628251670 g1628251671 d1628251668 c1628251667 b1628251666 a1628251665 l1 l2 l3 l4) l0 Source # | |
data Zip7Sym5 l l l l l l Source #
SuppressUnusedWarnings ([a1628251665] -> [b1628251666] -> [c1628251667] -> [d1628251668] -> [e1628251669] -> TyFun [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) -> *) (Zip7Sym5 f1628251670 g1628251671 e1628251669 d1628251668 c1628251667 b1628251666 a1628251665) Source # | |
type Apply [f1628251670] (TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> Type) (Zip7Sym5 f1628251670 g1628251671 e1628251669 d1628251668 c1628251667 b1628251666 a1628251665 l1 l2 l3 l4 l5) l0 Source # | |
data Zip7Sym6 l l l l l l l Source #
SuppressUnusedWarnings ([a1628251665] -> [b1628251666] -> [c1628251667] -> [d1628251668] -> [e1628251669] -> [f1628251670] -> TyFun [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] -> *) (Zip7Sym6 g1628251671 f1628251670 e1628251669 d1628251668 c1628251667 b1628251666 a1628251665) Source # | |
type Apply [g1628251671] [(a1628251665, b1628251666, c1628251667, d1628251668, e1628251669, f1628251670, g1628251671)] (Zip7Sym6 g1628251671 f1628251670 e1628251669 d1628251668 c1628251667 b1628251666 a1628251665 l1 l2 l3 l4 l5 l6) l0 Source # | |
data ZipWith4Sym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1628251660 (TyFun b1628251661 (TyFun c1628251662 (TyFun d1628251663 e1628251664 -> Type) -> Type) -> Type) -> Type) (TyFun [a1628251660] (TyFun [b1628251661] (TyFun [c1628251662] (TyFun [d1628251663] [e1628251664] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith4Sym0 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) Source # | |
type Apply (TyFun a1628251660 (TyFun b1628251661 (TyFun c1628251662 (TyFun d1628251663 e1628251664 -> Type) -> Type) -> Type) -> Type) (TyFun [a1628251660] (TyFun [b1628251661] (TyFun [c1628251662] (TyFun [d1628251663] [e1628251664] -> Type) -> Type) -> Type) -> Type) (ZipWith4Sym0 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) l0 Source # | |
data ZipWith4Sym1 l l Source #
SuppressUnusedWarnings ((TyFun a1628251660 (TyFun b1628251661 (TyFun c1628251662 (TyFun d1628251663 e1628251664 -> Type) -> Type) -> Type) -> Type) -> TyFun [a1628251660] (TyFun [b1628251661] (TyFun [c1628251662] (TyFun [d1628251663] [e1628251664] -> Type) -> Type) -> Type) -> *) (ZipWith4Sym1 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) Source # | |
type Apply [a1628251660] (TyFun [b1628251661] (TyFun [c1628251662] (TyFun [d1628251663] [e1628251664] -> Type) -> Type) -> Type) (ZipWith4Sym1 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664 l1) l0 Source # | |
data ZipWith4Sym2 l l l Source #
SuppressUnusedWarnings ((TyFun a1628251660 (TyFun b1628251661 (TyFun c1628251662 (TyFun d1628251663 e1628251664 -> Type) -> Type) -> Type) -> Type) -> [a1628251660] -> TyFun [b1628251661] (TyFun [c1628251662] (TyFun [d1628251663] [e1628251664] -> Type) -> Type) -> *) (ZipWith4Sym2 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) Source # | |
type Apply [b1628251661] (TyFun [c1628251662] (TyFun [d1628251663] [e1628251664] -> Type) -> Type) (ZipWith4Sym2 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664 l1 l2) l0 Source # | |
data ZipWith4Sym3 l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251660 (TyFun b1628251661 (TyFun c1628251662 (TyFun d1628251663 e1628251664 -> Type) -> Type) -> Type) -> Type) -> [a1628251660] -> [b1628251661] -> TyFun [c1628251662] (TyFun [d1628251663] [e1628251664] -> Type) -> *) (ZipWith4Sym3 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) Source # | |
type Apply [c1628251662] (TyFun [d1628251663] [e1628251664] -> Type) (ZipWith4Sym3 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664 l1 l2 l3) l0 Source # | |
data ZipWith4Sym4 l l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251660 (TyFun b1628251661 (TyFun c1628251662 (TyFun d1628251663 e1628251664 -> Type) -> Type) -> Type) -> Type) -> [a1628251660] -> [b1628251661] -> [c1628251662] -> TyFun [d1628251663] [e1628251664] -> *) (ZipWith4Sym4 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664) Source # | |
type Apply [d1628251663] [e1628251664] (ZipWith4Sym4 a1628251660 b1628251661 c1628251662 d1628251663 e1628251664 l1 l2 l3 l4) l0 Source # | |
type ZipWith4Sym5 t t t t t = ZipWith4 t t t t t Source #
data ZipWith5Sym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a1628251654] (TyFun [b1628251655] (TyFun [c1628251656] (TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym0 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) Source # | |
type Apply (TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a1628251654] (TyFun [b1628251655] (TyFun [c1628251656] (TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym0 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) l0 Source # | |
data ZipWith5Sym1 l l Source #
SuppressUnusedWarnings ((TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a1628251654] (TyFun [b1628251655] (TyFun [c1628251656] (TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith5Sym1 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) Source # | |
type Apply [a1628251654] (TyFun [b1628251655] (TyFun [c1628251656] (TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> Type) -> Type) -> Type) (ZipWith5Sym1 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659 l1) l0 Source # | |
data ZipWith5Sym2 l l l Source #
SuppressUnusedWarnings ((TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251654] -> TyFun [b1628251655] (TyFun [c1628251656] (TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> Type) -> Type) -> *) (ZipWith5Sym2 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) Source # | |
type Apply [b1628251655] (TyFun [c1628251656] (TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> Type) -> Type) (ZipWith5Sym2 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659 l1 l2) l0 Source # | |
data ZipWith5Sym3 l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251654] -> [b1628251655] -> TyFun [c1628251656] (TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> Type) -> *) (ZipWith5Sym3 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) Source # | |
type Apply [c1628251656] (TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> Type) (ZipWith5Sym3 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659 l1 l2 l3) l0 Source # | |
data ZipWith5Sym4 l l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251654] -> [b1628251655] -> [c1628251656] -> TyFun [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) -> *) (ZipWith5Sym4 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) Source # | |
type Apply [d1628251657] (TyFun [e1628251658] [f1628251659] -> Type) (ZipWith5Sym4 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659 l1 l2 l3 l4) l0 Source # | |
data ZipWith5Sym5 l l l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251654 (TyFun b1628251655 (TyFun c1628251656 (TyFun d1628251657 (TyFun e1628251658 f1628251659 -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251654] -> [b1628251655] -> [c1628251656] -> [d1628251657] -> TyFun [e1628251658] [f1628251659] -> *) (ZipWith5Sym5 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659) Source # | |
type Apply [e1628251658] [f1628251659] (ZipWith5Sym5 a1628251654 b1628251655 c1628251656 d1628251657 e1628251658 f1628251659 l1 l2 l3 l4 l5) l0 Source # | |
type ZipWith5Sym6 t t t t t t = ZipWith5 t t t t t t Source #
data ZipWith6Sym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a1628251647] (TyFun [b1628251648] (TyFun [c1628251649] (TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym0 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # | |
type Apply (TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a1628251647] (TyFun [b1628251648] (TyFun [c1628251649] (TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym0 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) l0 Source # | |
data ZipWith6Sym1 l l Source #
SuppressUnusedWarnings ((TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a1628251647] (TyFun [b1628251648] (TyFun [c1628251649] (TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym1 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # | |
type Apply [a1628251647] (TyFun [b1628251648] (TyFun [c1628251649] (TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym1 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653 l1) l0 Source # | |
data ZipWith6Sym2 l l l Source #
SuppressUnusedWarnings ((TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251647] -> TyFun [b1628251648] (TyFun [c1628251649] (TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith6Sym2 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # | |
type Apply [b1628251648] (TyFun [c1628251649] (TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> Type) -> Type) (ZipWith6Sym2 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653 l1 l2) l0 Source # | |
data ZipWith6Sym3 l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251647] -> [b1628251648] -> TyFun [c1628251649] (TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> Type) -> *) (ZipWith6Sym3 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # | |
type Apply [c1628251649] (TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> Type) (ZipWith6Sym3 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653 l1 l2 l3) l0 Source # | |
data ZipWith6Sym4 l l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251647] -> [b1628251648] -> [c1628251649] -> TyFun [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) -> *) (ZipWith6Sym4 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # | |
type Apply [d1628251650] (TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> Type) (ZipWith6Sym4 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653 l1 l2 l3 l4) l0 Source # | |
data ZipWith6Sym5 l l l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251647] -> [b1628251648] -> [c1628251649] -> [d1628251650] -> TyFun [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) -> *) (ZipWith6Sym5 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # | |
type Apply [e1628251651] (TyFun [f1628251652] [g1628251653] -> Type) (ZipWith6Sym5 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653 l1 l2 l3 l4 l5) l0 Source # | |
data ZipWith6Sym6 l l l l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251647 (TyFun b1628251648 (TyFun c1628251649 (TyFun d1628251650 (TyFun e1628251651 (TyFun f1628251652 g1628251653 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251647] -> [b1628251648] -> [c1628251649] -> [d1628251650] -> [e1628251651] -> TyFun [f1628251652] [g1628251653] -> *) (ZipWith6Sym6 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653) Source # | |
type Apply [f1628251652] [g1628251653] (ZipWith6Sym6 a1628251647 b1628251648 c1628251649 d1628251650 e1628251651 f1628251652 g1628251653 l1 l2 l3 l4 l5 l6) l0 Source # | |
type ZipWith6Sym7 t t t t t t t = ZipWith6 t t t t t t t Source #
data ZipWith7Sym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a1628251639] (TyFun [b1628251640] (TyFun [c1628251641] (TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym0 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # | |
type Apply (TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (TyFun [a1628251639] (TyFun [b1628251640] (TyFun [c1628251641] (TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym0 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) l0 Source # | |
data ZipWith7Sym1 l l Source #
SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> TyFun [a1628251639] (TyFun [b1628251640] (TyFun [c1628251641] (TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym1 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # | |
type Apply [a1628251639] (TyFun [b1628251640] (TyFun [c1628251641] (TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym1 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646 l1) l0 Source # | |
data ZipWith7Sym2 l l l Source #
SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251639] -> TyFun [b1628251640] (TyFun [c1628251641] (TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym2 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # | |
type Apply [b1628251640] (TyFun [c1628251641] (TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym2 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646 l1 l2) l0 Source # | |
data ZipWith7Sym3 l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251639] -> [b1628251640] -> TyFun [c1628251641] (TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> Type) -> *) (ZipWith7Sym3 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # | |
type Apply [c1628251641] (TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> Type) (ZipWith7Sym3 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646 l1 l2 l3) l0 Source # | |
data ZipWith7Sym4 l l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251639] -> [b1628251640] -> [c1628251641] -> TyFun [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) -> *) (ZipWith7Sym4 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # | |
type Apply [d1628251642] (TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> Type) (ZipWith7Sym4 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646 l1 l2 l3 l4) l0 Source # | |
data ZipWith7Sym5 l l l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251639] -> [b1628251640] -> [c1628251641] -> [d1628251642] -> TyFun [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) -> *) (ZipWith7Sym5 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # | |
type Apply [e1628251643] (TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> Type) (ZipWith7Sym5 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646 l1 l2 l3 l4 l5) l0 Source # | |
data ZipWith7Sym6 l l l l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251639] -> [b1628251640] -> [c1628251641] -> [d1628251642] -> [e1628251643] -> TyFun [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) -> *) (ZipWith7Sym6 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # | |
type Apply [f1628251644] (TyFun [g1628251645] [h1628251646] -> Type) (ZipWith7Sym6 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646 l1 l2 l3 l4 l5 l6) l0 Source # | |
data ZipWith7Sym7 l l l l l l l l Source #
SuppressUnusedWarnings ((TyFun a1628251639 (TyFun b1628251640 (TyFun c1628251641 (TyFun d1628251642 (TyFun e1628251643 (TyFun f1628251644 (TyFun g1628251645 h1628251646 -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) -> [a1628251639] -> [b1628251640] -> [c1628251641] -> [d1628251642] -> [e1628251643] -> [f1628251644] -> TyFun [g1628251645] [h1628251646] -> *) (ZipWith7Sym7 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646) Source # | |
type Apply [g1628251645] [h1628251646] (ZipWith7Sym7 a1628251639 b1628251640 c1628251641 d1628251642 e1628251643 f1628251644 g1628251645 h1628251646 l1 l2 l3 l4 l5 l6 l7) l0 Source # | |
type ZipWith7Sym8 t t t t t t t t = ZipWith7 t t t t t t t t Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953287 (TyFun a1627953287 Bool -> Type) -> Type) (TyFun [a1627953287] [a1627953287] -> Type) -> *) (NubBySym0 a1627953287) Source # | |
type Apply (TyFun a1627953287 (TyFun a1627953287 Bool -> Type) -> Type) (TyFun [a1627953287] [a1627953287] -> Type) (NubBySym0 a1627953287) l0 Source # | |
data UnionBySym0 l Source #
SuppressUnusedWarnings (TyFun (TyFun a1627953285 (TyFun a1627953285 Bool -> Type) -> Type) (TyFun [a1627953285] (TyFun [a1627953285] [a1627953285] -> Type) -> Type) -> *) (UnionBySym0 a1627953285) Source # | |
type Apply (TyFun a1627953285 (TyFun a1627953285 Bool -> Type) -> Type) (TyFun [a1627953285] (TyFun [a1627953285] [a1627953285] -> Type) -> Type) (UnionBySym0 a1627953285) l0 Source # | |
data UnionBySym1 l l Source #
SuppressUnusedWarnings ((TyFun a1627953285 (TyFun a1627953285 Bool -> Type) -> Type) -> TyFun [a1627953285] (TyFun [a1627953285] [a1627953285] -> Type) -> *) (UnionBySym1 a1627953285) Source # | |
type Apply [a1627953285] (TyFun [a1627953285] [a1627953285] -> Type) (UnionBySym1 a1627953285 l1) l0 Source # | |
data UnionBySym2 l l l Source #
SuppressUnusedWarnings ((TyFun a1627953285 (TyFun a1627953285 Bool -> Type) -> Type) -> [a1627953285] -> TyFun [a1627953285] [a1627953285] -> *) (UnionBySym2 a1627953285) Source # | |
type Apply [a1627953285] [a1627953285] (UnionBySym2 a1627953285 l1 l2) l0 Source # | |
type UnionBySym3 t t t = UnionBy t t t Source #
data GenericLengthSym0 l Source #
SuppressUnusedWarnings (TyFun [a1627953283] i1627953282 -> *) (GenericLengthSym0 a1627953283 i1627953282) Source # | |
type Apply [a1627953283] k2 (GenericLengthSym0 a1627953283 k2) l0 Source # | |
type GenericLengthSym1 t = GenericLength t Source #
data GenericTakeSym0 l Source #
SuppressUnusedWarnings (TyFun i1628251637 (TyFun [a1628251638] [a1628251638] -> Type) -> *) (GenericTakeSym0 i1628251637 a1628251638) Source # | |
type Apply i1628251637 (TyFun [a1628251638] [a1628251638] -> Type) (GenericTakeSym0 i1628251637 a1628251638) l0 Source # | |
data GenericTakeSym1 l l Source #
SuppressUnusedWarnings (i1628251637 -> TyFun [a1628251638] [a1628251638] -> *) (GenericTakeSym1 a1628251638 i1628251637) Source # | |
type Apply [a1628251638] [a1628251638] (GenericTakeSym1 a1628251638 i1628251637 l1) l0 Source # | |
type GenericTakeSym2 t t = GenericTake t t Source #
data GenericDropSym0 l Source #
SuppressUnusedWarnings (TyFun i1628251635 (TyFun [a1628251636] [a1628251636] -> Type) -> *) (GenericDropSym0 i1628251635 a1628251636) Source # | |
type Apply i1628251635 (TyFun [a1628251636] [a1628251636] -> Type) (GenericDropSym0 i1628251635 a1628251636) l0 Source # | |
data GenericDropSym1 l l Source #
SuppressUnusedWarnings (i1628251635 -> TyFun [a1628251636] [a1628251636] -> *) (GenericDropSym1 a1628251636 i1628251635) Source # | |
type Apply [a1628251636] [a1628251636] (GenericDropSym1 a1628251636 i1628251635 l1) l0 Source # | |
type GenericDropSym2 t t = GenericDrop t t Source #
data GenericSplitAtSym0 l Source #
SuppressUnusedWarnings (TyFun i1628251633 (TyFun [a1628251634] ([a1628251634], [a1628251634]) -> Type) -> *) (GenericSplitAtSym0 i1628251633 a1628251634) Source # | |
type Apply i1628251633 (TyFun [a1628251634] ([a1628251634], [a1628251634]) -> Type) (GenericSplitAtSym0 i1628251633 a1628251634) l0 Source # | |
data GenericSplitAtSym1 l l Source #
SuppressUnusedWarnings (i1628251633 -> TyFun [a1628251634] ([a1628251634], [a1628251634]) -> *) (GenericSplitAtSym1 a1628251634 i1628251633) Source # | |
type Apply [a1628251634] ([a1628251634], [a1628251634]) (GenericSplitAtSym1 a1628251634 i1628251633 l1) l0 Source # | |
type GenericSplitAtSym2 t t = GenericSplitAt t t Source #
data GenericIndexSym0 l Source #
SuppressUnusedWarnings (TyFun [a1628251632] (TyFun i1628251631 a1628251632 -> Type) -> *) (GenericIndexSym0 i1628251631 a1628251632) Source # | |
type Apply [a1628251632] (TyFun i1628251631 a1628251632 -> Type) (GenericIndexSym0 i1628251631 a1628251632) l0 Source # | |
data GenericIndexSym1 l l Source #
SuppressUnusedWarnings ([a1628251632] -> TyFun i1628251631 a1628251632 -> *) (GenericIndexSym1 i1628251631 a1628251632) Source # | |
type Apply i1628251631 a1628251632 (GenericIndexSym1 i1628251631 a1628251632 l1) l0 Source # | |
type GenericIndexSym2 t t = GenericIndex t t Source #
data GenericReplicateSym0 l Source #
SuppressUnusedWarnings (TyFun i1628251629 (TyFun a1628251630 [a1628251630] -> Type) -> *) (GenericReplicateSym0 i1628251629 a1628251630) Source # | |
type Apply i1628251629 (TyFun a1628251630 [a1628251630] -> Type) (GenericReplicateSym0 i1628251629 a1628251630) l0 Source # | |
data GenericReplicateSym1 l l Source #
SuppressUnusedWarnings (i1628251629 -> TyFun a1628251630 [a1628251630] -> *) (GenericReplicateSym1 a1628251630 i1628251629) Source # | |
type Apply a1628251630 [a1628251630] (GenericReplicateSym1 a1628251630 i1628251629 l1) l0 Source # | |
type GenericReplicateSym2 t t = GenericReplicate t t Source #